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"
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"
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
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
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
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]
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") <|>
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") <|>
-- 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)
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
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)
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]
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]
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 =
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)
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
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)
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
-- 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)
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))
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')
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 =
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
nameP :: Parser String
graphP = M.fromList <$> nodeP `sepBy` endOfLine
-nodeP = (,) <$> (nameP <* ": ") <*> (nameP `sepBy` " ")
+nodeP = (,) <$> nameP <* ": " <*> nameP `sepBy` " "
nameP = many1 letter