day 1
This commit is contained in:
7093
spago.lock
Normal file
7093
spago.lock
Normal file
File diff suppressed because it is too large
Load Diff
21
spago.yaml
21
spago.yaml
@@ -1,24 +1,23 @@
|
||||
package:
|
||||
build:
|
||||
strict: true
|
||||
pedantic_packages: true
|
||||
pedanticPackages: true
|
||||
dependencies:
|
||||
- prelude
|
||||
- aff
|
||||
- bifunctors
|
||||
- console
|
||||
- control
|
||||
- effect
|
||||
- either
|
||||
- maybe
|
||||
- exceptions
|
||||
- foldable-traversable
|
||||
- console
|
||||
- newtype
|
||||
- strings
|
||||
- stringutils
|
||||
- lists
|
||||
- parsing
|
||||
- prelude
|
||||
- transformers
|
||||
- tuples
|
||||
- typelevel-prelude
|
||||
name: project
|
||||
workspace:
|
||||
extra_packages: {}
|
||||
package_set:
|
||||
extraPackages: {}
|
||||
packageSet:
|
||||
url: https://raw.githubusercontent.com/purescript/package-sets/psc-0.15.10-20230930/packages.json
|
||||
hash: sha256-nTsd44o7/hrTdk0c6dh0wyBqhFFDJJIeKdQU6L1zv/A=
|
||||
|
||||
4097
src/Day1.purs
Normal file
4097
src/Day1.purs
Normal file
File diff suppressed because it is too large
Load Diff
90
src/Day1/Dial.purs
Normal file
90
src/Day1/Dial.purs
Normal file
@@ -0,0 +1,90 @@
|
||||
module Day1.Dial where
|
||||
|
||||
import Prelude
|
||||
|
||||
import Control.Monad.State (StateT, get, put, runStateT)
|
||||
import Control.Monad.Trans.Class (lift)
|
||||
import Data.Tuple (snd)
|
||||
import Data.Tuple.Nested (type (/\), (/\))
|
||||
import Day1.Instr (Instr(..), Dir(..))
|
||||
import Effect (Effect)
|
||||
import Effect.Console as Console
|
||||
|
||||
type WrappedTimes = Int
|
||||
type DialPos = Int
|
||||
type SpinAmount = Int
|
||||
type DialSize = Int
|
||||
|
||||
type DialState = { debug :: Boolean, size :: DialSize, equaledZeroTimes :: Int, crossedZeroTimes :: Int, value :: Int, crossedPlusEqualed :: Int }
|
||||
type InDial = StateT DialState Effect Unit
|
||||
|
||||
runDial :: { debug :: Boolean, size :: DialSize, value :: Int } -> InDial -> Effect DialState
|
||||
runDial { debug, size, value } =
|
||||
let
|
||||
zeroTimes = if value == 0 then 1 else 0
|
||||
in
|
||||
map snd <<< flip runStateT { debug, size, equaledZeroTimes: zeroTimes, crossedZeroTimes: 0, value, crossedPlusEqualed: zeroTimes }
|
||||
|
||||
perform :: Instr -> InDial
|
||||
perform instr@(Instr dir n) =
|
||||
let
|
||||
oneIf = if _ then 1 else 0
|
||||
|
||||
spinFor size L = spinLeft size
|
||||
spinFor size R = spinRight size
|
||||
in do
|
||||
state <- get
|
||||
|
||||
let
|
||||
spin = spinFor state.size dir
|
||||
|
||||
timesWrapped /\ value = state.value `spin` n
|
||||
isZero = value == 0
|
||||
|
||||
equaledZeroTimes = state.equaledZeroTimes + oneIf isZero
|
||||
crossedZeroTimes = state.crossedZeroTimes + timesWrapped
|
||||
|
||||
state' =
|
||||
{ value
|
||||
, equaledZeroTimes
|
||||
, crossedZeroTimes
|
||||
, crossedPlusEqualed: crossedZeroTimes + equaledZeroTimes
|
||||
, size: state.size
|
||||
, debug: state.debug
|
||||
}
|
||||
|
||||
when state.debug
|
||||
$ lift
|
||||
$ Console.log
|
||||
$ show instr <> " -> " <> show state'
|
||||
|
||||
put state'
|
||||
|
||||
spinRight :: DialSize -> DialPos -> SpinAmount -> WrappedTimes /\ DialPos
|
||||
spinRight size a b =
|
||||
let
|
||||
c = a + b
|
||||
|
||||
-- don't count "land on zero" as a wrap
|
||||
correctWraps wraps' =
|
||||
if c `mod` size == 0 then
|
||||
max 0 $ wraps' - 1
|
||||
else
|
||||
wraps'
|
||||
|
||||
wraps = correctWraps $ c / size
|
||||
in
|
||||
wraps /\ (c `mod` size)
|
||||
|
||||
spinLeft :: DialSize -> DialPos -> SpinAmount -> WrappedTimes /\ DialPos
|
||||
spinLeft size a' b =
|
||||
let
|
||||
-- don't count "left from zero" as a wrap
|
||||
a = if a' == 0 then size else a'
|
||||
|
||||
positive wraps n'
|
||||
| n' < 0 = positive (wraps + 1) (n' + size)
|
||||
| otherwise = wraps /\ n'
|
||||
wraps /\ c = positive 0 $ a - b
|
||||
in
|
||||
wraps /\ (c `mod` size)
|
||||
37
src/Day1/Instr.purs
Normal file
37
src/Day1/Instr.purs
Normal file
@@ -0,0 +1,37 @@
|
||||
module Day1.Instr where
|
||||
|
||||
import Prelude
|
||||
|
||||
import Control.Alt ((<|>))
|
||||
import Data.Either (Either)
|
||||
import Data.Generic.Rep (class Generic)
|
||||
import Data.List as List
|
||||
import Data.Show.Generic (genericShow)
|
||||
import Parsing (Parser)
|
||||
import Parsing (runParser, ParseError) as Parse
|
||||
import Parsing.Combinators (sepBy) as Parse
|
||||
import Parsing.String (string) as Parse
|
||||
import Parsing.String.Basic (intDecimal) as Parse
|
||||
|
||||
data Dir = L | R
|
||||
derive instance Generic Dir _
|
||||
derive instance Eq Dir
|
||||
derive instance Ord Dir
|
||||
instance Show Dir where show = genericShow
|
||||
|
||||
data Instr = Instr Dir Int
|
||||
derive instance Generic Instr _
|
||||
derive instance Eq Instr
|
||||
derive instance Ord Instr
|
||||
instance Show Instr where show = genericShow
|
||||
|
||||
parseInstrs :: String -> Either Parse.ParseError (Array Instr)
|
||||
parseInstrs = flip Parse.runParser parser
|
||||
|
||||
parser :: Parser String (Array Instr)
|
||||
parser =
|
||||
let
|
||||
dir = (Parse.string "L" $> L) <|> (Parse.string "R" $> R)
|
||||
single = Instr <$> dir <*> Parse.intDecimal
|
||||
in
|
||||
List.toUnfoldable <$> Parse.sepBy single (Parse.string "\n")
|
||||
@@ -1,7 +1,10 @@
|
||||
module Main where
|
||||
|
||||
import Prelude
|
||||
|
||||
import Day1 as Day1
|
||||
import Effect (Effect)
|
||||
|
||||
main :: Effect Unit
|
||||
main = pure unit
|
||||
main = do
|
||||
Day1.main
|
||||
|
||||
Reference in New Issue
Block a user