Tidying, mainly parsers
authorNeil Smith <NeilNjae@users.noreply.github.com>
Wed, 10 Jan 2024 17:37:46 +0000 (17:37 +0000)
committerNeil Smith <NeilNjae@users.noreply.github.com>
Wed, 10 Jan 2024 17:37:46 +0000 (17:37 +0000)
19 files changed:
advent02/Main.hs
advent02/MainApplicative.hs
advent04/Main.hs
advent05/Main.hs
advent05/MainDirect.hs
advent06/Main.hs
advent07/Main.hs
advent07/MainWithCase.hs
advent08/Main.hs
advent12/Main.hs
advent12/MainBruteForce.hs
advent15/Main.hs
advent18/Main.hs
advent19/Main.hs
advent20/Main.hs
advent22/Main.hs
advent23/Main.hs
advent24/Main.hs
advent25/Main.hs

index 2e96f1b040fa2867f9e34d5a174464e4921bf2bd..e8e8f03e3ca90b5f7f404079e1baec1d13c0d035 100644 (file)
@@ -91,11 +91,11 @@ cubeP :: Parser Cube
 colourP, redP, greenP, blueP :: Parser Colour
 
 gamesP = gameP `sepBy` endOfLine
-gameP = ParsedGame <$> (("Game " *> decimal) <* ": ") <*> showingsP
+gameP = ParsedGame <$ "Game " <*> decimal <* ": " <*> showingsP
 
 showingsP = showingP `sepBy` "; "
 showingP = cubeP `sepBy` ", "
-cubeP = (flip Cube) <$> (decimal  <* " ") <*> colourP 
+cubeP = (flip Cube) <$> decimal  <* " " <*> colourP 
 
 colourP = redP <|> greenP <|> blueP
 redP = Red <$ "red"
index 14cb248db042a1fb0a851608c4e7fbc5e7a71f70..acbcb5fa6741aa1b52ecbeb8a5b5b099283cb344 100644 (file)
@@ -85,11 +85,11 @@ cubeP :: Parser Cube
 colourP, redP, greenP, blueP :: Parser Colour
 
 gamesP = gameP `sepBy` endOfLine
-gameP = ParsedGame <$> (("Game " *> decimal) <* ": ") <*> showingsP
+gameP = ParsedGame <$ "Game " <*> decimal <* ": " <*> showingsP
 
 showingsP = showingP `sepBy` "; "
 showingP = cubeP `sepBy` ", "
-cubeP = (flip Cube) <$> (decimal  <* " ") <*> colourP 
+cubeP = (flip Cube) <$> decimal  <* " " <*> colourP 
 
 colourP = redP <|> greenP <|> blueP
 redP = Red <$ "red"
index 0d8b7735b6ce7a0bd7978b77edd47b8d46314b94..3448edc112681f02c4026fd75797aa153b6a3ddb 100644 (file)
@@ -62,8 +62,9 @@ cardP :: Parser Card
 numbersP :: Parser [Int]
 
 cardsP = cardP `sepBy` endOfLine
-cardP = Card <$> (("Card" *> skipSpace *> decimal) <* ":" <* skipSpace) 
-             <*> (numbersP <* " |" <* skipSpace) 
+cardP = Card <$  "Card" <* skipSpace 
+             <*> decimal <* ":" <* skipSpace
+             <*> numbersP <* " |" <* skipSpace
              <*> numbersP
 
 numbersP = decimal `sepBy` skipSpace
index d8bb80651619e20b6408db47ece5cfb9e999f897..16e4f4cb270dfd5af3d03e0344d889e034d88e6a 100644 (file)
@@ -125,10 +125,10 @@ seedsP = "seeds: " *> numbersP
 almanacP = M.fromList <$> (aMapP `sepBy` blankLineP)
 
 aMapP = aMapify <$> aMapHeaderP <*> rulesP
-aMapHeaderP = (,) <$> (nameP <* "-to-") <*> (nameP <* " map:" <* endOfLine)
+aMapHeaderP = (,) <$> nameP <* "-to-" <*> nameP <* " map:" <* endOfLine
 
 rulesP = ruleP `sepBy` endOfLine
-ruleP = ruleify <$> (decimal <* space) <*> (decimal <* space) <*> decimal
+ruleP = ruleify <$> decimal <* space <*> decimal <* space <*> decimal
 
 numbersP = decimal `sepBy` skipSpace
 nameP = many1 letter
index ca59a51b682b5e9ae499ff1dc35e752d235ff2af..9a56bba965800fde924c7ef09418590a4478900c 100644 (file)
@@ -82,10 +82,10 @@ seedsP = "seeds: " *> numbersP
 almanacP = M.fromList <$> (aMapP `sepBy` blankLineP)
 
 aMapP = aMapify <$> aMapHeaderP <*> rulesP
-aMapHeaderP = (,) <$> (nameP <* "-to-") <*> (nameP <* " map:" <* endOfLine)
+aMapHeaderP = (,) <$> nameP <* "-to-" <*> nameP <* " map:" <* endOfLine
 
 rulesP = ruleP `sepBy` endOfLine
-ruleP = Rule <$> (decimal <* space) <*> (decimal <* space) <*> decimal
+ruleP = Rule <$> decimal <* space <*> decimal <* space <*> decimal
 
 numbersP = decimal `sepBy` skipSpace
 nameP = many1 letter
index 2a056bb9f14c00e63acc69e8ab61e6865bbb5dee..8e29367cb3f8b3487df452f465e6b848cae4804a 100644 (file)
@@ -30,9 +30,9 @@ waysToWin (Race timeLimit record) =
 racesP :: Parser [Race]
 timesP, distancesP, numbersP :: Parser [Int]
 
-racesP = zipWith Race <$> (timesP <* endOfLine) <*> distancesP
-timesP = ("Time:" *> skipSpace) *> numbersP
-distancesP = ("Distance:" *> skipSpace) *> numbersP
+racesP = zipWith Race <$> timesP <* endOfLine <*> distancesP
+timesP = "Time:" *> skipSpace *> numbersP
+distancesP = "Distance:" *> skipSpace *> numbersP
 numbersP = decimal `sepBy` skipSpace
 
 successfulParse :: T.Text -> [Race] 
index 8f4350d293e9fd37abba85ad702396b214a923dd..8f3a42445d74b6ffa4596856b47b815a645d7fb6 100644 (file)
@@ -95,7 +95,7 @@ handP :: Parser Hand
 cardP :: Parser Card
 
 handsP = handP `sepBy` endOfLine
-handP = Hand <$> ((many1 cardP) <* space) <*> decimal
+handP = Hand <$> many1 cardP <* space <*> decimal
 
 cardP = (Two <$ "2") <|> (Three <$ "3") <|> (Four <$ "4") <|> 
         (Five <$ "5") <|> (Six <$ "6") <|> (Seven <$ "7") <|> 
index e5a181fd6217a43804e9233f71cdd6eb1c99d7fe..bd0aa85906dab170f5235500673f0ca25d3786f7 100644 (file)
@@ -71,7 +71,7 @@ handP :: Parser Hand
 cardP :: Parser Card
 
 handsP = handP `sepBy` endOfLine
-handP = Hand <$> ((many1 cardP) <* space) <*> decimal
+handP = Hand <$> many1 cardP <* space <*> decimal
 
 cardP = (Two <$ "2") <|> (Three <$ "3") <|> (Four <$ "4") <|> 
         (Five <$ "5") <|> (Six <$ "6") <|> (Seven <$ "7") <|> 
index b2c9895b9929f4a922bb4e51c25fe83a39c291c3..5ab2916ced95bbdf93ebe3c6b3e7667f108c33d0 100644 (file)
@@ -31,7 +31,7 @@ main =
       -- print $ desert
       print $ part1 desert directions
       print $ part2 desert directions
-      print $ part3 desert directions
+      -- print $ part3 desert directions
 
 part1, part2 :: Desert -> [Direction] -> Int
 part1 desert directions = getSteps $ walk desert directions (State "AAA" 0)
@@ -50,16 +50,16 @@ generateRouteLengths desert directions = M.unions ((fmap snd sResults) ++ (fmap
         gResults = fmap (walkWithCache desert directions M.empty) fromGoals
 
 
-part3 desert directions = multiWalk desert directions M.empty starts
-  where starts = fmap (\s -> State s 0) $ startsOf desert
+-- part3 desert directions = multiWalk desert directions M.empty starts
+--   where starts = fmap (\s -> State s 0) $ startsOf desert
 
-multiWalk desert directions cache states@(s:ss)
-  | (all isGoal states) && (sameTime states) = states
-  | otherwise = multiWalk desert directions newCache $ sort (s':ss)
-  where (s', newCache) = walkWithCache desert directions cache s
+-- multiWalk desert directions cache states@(s:ss)
+--   | (all isGoal states) && (sameTime states) = states
+--   | otherwise = multiWalk desert directions newCache $ sort (s':ss)
+--   where (s', newCache) = walkWithCache desert directions cache s
 
-sameTime states = (length $ nub times) == 1
-  where times = fmap getSteps states
+-- sameTime states = (length $ nub times) == 1
+--   where times = fmap getSteps states
 
 walk :: Desert -> [Direction] -> State -> State
 walk desert directions start = head $ dropWhile (not . isGoal) path
@@ -103,13 +103,13 @@ desertLineP :: Parser (String, Node)
 nodeP :: Parser Node
 nameP :: Parser String
 
-problemP = (,) <$> ((many1 directionP) <* many1 endOfLine) <*> desertP
+problemP = (,) <$> many1 directionP <* many1 endOfLine <*> desertP
 directionP = (L <$ "L") <|> (R <$ "R")
 
 desertP = M.fromList <$> desertLineP `sepBy` endOfLine
-desertLineP = (,) <$> (nameP <* " = ") <*> nodeP
+desertLineP = (,) <$> nameP <* " = " <*> nodeP
 
-nodeP = Node <$> ("(" *> nameP <* ", ") <*> (nameP <* ")")
+nodeP = Node <$ "(" <*> nameP <* ", " <*> nameP <* ")"
 nameP = many1 (letter <|> digit) 
 
 successfulParse :: Text -> ([Direction], Desert)
index 2c07b389c78b434da585a14d2c2bc5d40a3bf214..7f1177d387fb7257ba7f0144a2b235505b52ec27 100644 (file)
@@ -82,7 +82,7 @@ recordP :: Parser Record
 springP :: Parser Spring
 
 recordsP = recordP `sepBy` endOfLine
-recordP = Record <$> (many1 springP <* " ") <*> (decimal `sepBy` ",")
+recordP = Record <$> many1 springP <* " " <*> decimal `sepBy` ","
 springP = (Unknown <$ "?") <|> (Damaged <$ "#") <|> (Operational <$ ".")
 
 successfulParse :: Text -> [Record]
index 6b8620395a377b30138beae95080ccfa3895606d..7d11334d9c38ea378d8ffb4589ea7b2f7dd5b48b 100644 (file)
@@ -78,7 +78,7 @@ recordP :: Parser Record
 springP :: Parser Spring
 
 recordsP = recordP `sepBy` endOfLine
-recordP = Record <$> (many1 springP <* " ") <*> (decimal `sepBy` ",")
+recordP = Record <$> many1 springP <* " " <*> decimal `sepBy` ","
 springP = (Unknown <$ "?") <|> (Damaged <$ "#") <|> (Operational <$ ".")
 
 successfulParse :: Text -> [Record]
index 7fa47890163291cfe8e4baf228b2897f88f2d091..384c88c4c2b4a4595c119e1d59caeff79ba8acc6 100644 (file)
@@ -69,8 +69,8 @@ instructionP, removeP, insertP :: Parser Instruction
 instructionsP = instructionP `sepBy` ","
 instructionP = removeP <|> insertP
 
-removeP = Remove <$> (many1 letter) <* "-"
-insertP = Insert <$> ((many1 letter) <* "=") <*> decimal
+removeP = Remove <$> many1 letter <* "-"
+insertP = Insert <$> many1 letter <* "=" <*> decimal
 
 successfulParse :: Text -> [Instruction]
 successfulParse input = 
index 9e5a97c5beadb6c76f1a3f75abc6c4bc1b7697eb..97bcf6d35396769877a2f839c949de90882f2e23 100644 (file)
@@ -79,9 +79,9 @@ direction2P = choice [ U <$ "3"
 instructions2P = instruction2P `sepBy` endOfLine
 
 instruction2P = 
-  instrify <$> (preambleP *> (AT.take 5)) <*> (direction2P <* ")")
+  instrify <$ preambleP <*> AT.take 5 <*> direction2P <* ")"
 
-preambleP = (direction1P *> " " *> decimal <* " (#")
+preambleP = direction1P *> " " *> decimal <* " (#"
 
 instrify :: Text -> Direction -> Instruction
 instrify h d = Instr d (fst $ fromRight (0, "") $ TR.hexadecimal h)
index eed9e357c5fc0726c9cdd47db7ce5b7ffca9fd0a..1a05fa56498bc328229fc03f66e95fc979bab8ae 100644 (file)
@@ -217,13 +217,13 @@ partP :: Parser (Part Int)
 rulePartP = (,) <$> (rulesP <* endOfLine <* endOfLine) <*> partsP
 
 rulesP = M.fromList <$> ruleP `sepBy` endOfLine
-ruleP = (,) <$> (nameP <* "{") <*> (ruleBodyP <* "}")
+ruleP = (,) <$> nameP <* "{" <*> ruleBodyP <* "}"
 
 nameP = unpack <$> AT.takeWhile (inClass "a-z") -- many1 letter
 ruleBodyP = ruleElementP `sepBy` ","
 ruleElementP = withTestP <|> withoutTestP
 
-withTestP = WithTest <$> (testP <* ":") <*> destinationP
+withTestP = WithTest <$> testP <* ":" <*> destinationP
 withoutTestP = WithoutTest <$> destinationP
 
 testP = Test <$> registerP <*> comparatorP <*> decimal
index 931c8673e922a0983a992ea81d91167d0bb3605b..c3a9cf3e7bd858f19515eb52e0548dcafe03bbaa 100644 (file)
@@ -9,7 +9,7 @@ import Data.Attoparsec.Text hiding (take)
 import Control.Applicative
 import Data.List
 import qualified Data.Map.Strict as M
-import Data.Map ((!))
+import Data.Map.Strict ((!))
 import qualified Data.Sequence as Q
 import Data.Sequence ((|>), (><), Seq( (:|>), (:<|) ) ) 
 import Control.Lens hiding (Level)
@@ -179,13 +179,13 @@ moduleP, broadcastP, flipFlopP, conjunctionP :: Parser (Module, Name)
 nameP :: Parser Name
 
 configLinesP = configLineP `sepBy` endOfLine
-configLineP = (,) <$> (moduleP <* " -> ") <*> (nameP `sepBy` ", ")
+configLineP = (,) <$> moduleP <* " -> " <*> nameP `sepBy` ", "
 
 moduleP = broadcastP <|> flipFlopP <|> conjunctionP
 
 broadcastP = (Broadcast, "broadcaster") <$ "broadcaster"
-flipFlopP = (FlipFlop False, ) <$> ("%" *> nameP)
-conjunctionP = (Conjunction M.empty, ) <$> ("&" *> nameP)
+flipFlopP = (FlipFlop False, ) <$ "%" <*> nameP
+conjunctionP = (Conjunction M.empty, ) <$ "&" <*> nameP
   
 -- namesP = nameP `sepBy` ", "
 nameP = many1 letter
index a80afe48cc59bebddcfaa34579cc5528c903f340..55b64b636a83f0d86512e03ec074e40bf46887e8 100644 (file)
@@ -12,8 +12,8 @@ import Linear
 -- import Linear.V3
 import Data.List
 import Data.Function
-import qualified Data.Map as M
-import Data.Map ((!))
+import qualified Data.Map.Strict as M
+import Data.Map.Strict ((!))
 import qualified Data.Set as S
 
 type Block = (V3 Int, V3 Int)
@@ -126,7 +126,7 @@ blockP :: Parser Block
 vertexP :: Parser (V3 Int)
 
 blocksP = blockP `sepBy` endOfLine
-blockP = cubify <$> (vertexP <* "~") <*> vertexP
+blockP = cubify <$> vertexP <* "~" <*> vertexP
   where cubify (V3 x1 y1 z1) (V3 x2 y2 z2) = 
           ( (V3 (min x1 x2) (min y1 y2) (min z1 z2))
           , (V3 (max x1 x2) (max y1 y2) (max z1 z2))
index 457f42bf4ae3ccf0c3395f2e98da083a2cf0da42..82982614816689c43b009398f45278bf39ef30d2 100644 (file)
@@ -5,7 +5,7 @@ import qualified Debug.Trace as DT
 import AoC
 import Linear -- (V2(..), (^+^))
 import qualified Data.Set as S
-import qualified Data.Map as M
+import qualified Data.Map.Strict as M
 import Control.Lens
 import Data.List (foldl')
 
index 4e9cc78125986cf5e24cb80d1ef965e972b74fff..b33b2f3daf9fce3232424acc03f2688e84ffb964 100644 (file)
@@ -115,12 +115,14 @@ stoneP :: Parser Hailstone
 vertexP :: Parser (V3 Rational)
 
 stonesP = stoneP `sepBy` endOfLine
-stoneP = Hailstone <$> (vertexP <* symbolP "@") <*> vertexP
-vertexP = vecify <$> signed decimal <*> (symbolP "," *> signed decimal) <*> (symbolP "," *> signed decimal)
+stoneP = Hailstone <$> vertexP <* symbolP "@" <*> vertexP
+vertexP = vecify <$> signed decimal <* symbolP "," 
+                 <*> signed decimal <* symbolP "," 
+                 <*> signed decimal
   where vecify x y z = V3 (x % 1) (y % 1) (z % 1)
 
 symbolP :: Text -> Parser Text
-symbolP s = (skipSpace *> string s) <* skipSpace
+symbolP s = skipSpace *> string s <* skipSpace
 
 successfulParse :: Text -> [Hailstone]
 successfulParse input = 
index 0b9c02a2c1ec18716175f34b352f66975ec903b9..57d94f235444ec27b411efc7e89abd7ac09ea4bc 100644 (file)
@@ -7,8 +7,8 @@ import qualified Data.Text.IO as TIO
 import Data.Attoparsec.Text hiding (take)
 -- import Control.Applicative
 import Data.List (foldl', unfoldr, sort, delete)
-import qualified Data.Map as M
-import Data.Map ((!))
+import qualified Data.Map.Strict as M
+import Data.Map.Strict ((!))
 import qualified Data.Set as S
 import Data.Set ((\\))
 import qualified Data.Sequence as Q
@@ -93,7 +93,7 @@ nodeP :: Parser (String, [String])
 nameP :: Parser String
 
 graphP = M.fromList <$> nodeP `sepBy` endOfLine
-nodeP = (,) <$> (nameP <* ": ") <*> (nameP `sepBy` " ")
+nodeP = (,) <$> nameP <* ": " <*> nameP `sepBy` " "
 
 nameP = many1 letter