Commit 96ac136f by Stuart Kurtz

Day 13: started, but have meetings

parent 152690da
......@@ -10,7 +10,7 @@ maintainer: stuart@cs.uchicago.edu
common aoc-common
build-depends : base ^>=4.14.3.0, array, containers
hs-source-dirs : src
other-extensions : TypeApplications
default-extensions : TypeApplications
default-language : Haskell2010
ghc-options : -Wall
......
{-# LANGUAGE TypeApplications #-}
module Main where
import Control.Monad ( void, guard )
......@@ -7,7 +5,6 @@ import Data.Char ( isUpper, isAlpha )
import qualified Data.Map as M
import Data.Map (Map,(!))
import qualified Data.Set as S
import Data.Set (Set)
import Text.ParserCombinators.ReadP
( char, munch1, readP_to_S, ReadP )
......@@ -42,7 +39,6 @@ makeCaveMap es =
paths :: CaveMap -> [[Cave]]
paths cm = iter (Small "start") (S.singleton (Small "start")) [Small "start"] where
iter :: Cave -> Set Cave -> [Cave] -> [[Cave]]
iter (Small "end") _ path = [reverse path]
iter cave visited path = do
next <- cm ! cave
......
{-# LANGUAGE TypeApplications #-}
module Main where
import Control.Monad ( guard, void )
......@@ -7,7 +5,6 @@ import Data.Char ( isUpper, isAlpha )
import qualified Data.Map as M
import Data.Map (Map,(!))
import qualified Data.Set as S
import Data.Set (Set)
import Text.ParserCombinators.ReadP
( char, munch1, readP_to_S, ReadP )
......@@ -26,8 +23,7 @@ type CaveMap = Map Cave [Cave]
parseCave :: ReadP Cave
parseCave = do
nm <- munch1 isAlpha
pure $
if isUpper (head nm) then Big nm else Small nm
pure $ if isUpper (head nm) then Big nm else Small nm
parseEdge :: ReadP Edge
parseEdge = do
......@@ -41,12 +37,12 @@ makeCaveMap es =
M.unionsWith (++) . map (\(Edge c1 c2) -> M.fromList [(c1,[c2]),(c2,[c1])]) $ es
paths :: CaveMap -> [[Cave]]
paths cm = iter (Small "start") (S.singleton (Small "start")) False [Small "start"] where
iter :: Cave -> Set Cave -> Bool -> [Cave] -> [[Cave]]
paths cm = iter start (S.singleton start) False [start] where
start = Small "start"
iter (Small "end") _ _ path = [reverse path] -- end at end
iter cave visited revisited path = do
next <- cm ! cave
guard $ next /= Small "start" -- don't revist start
guard $ next /= start -- don't revist start
if next `elem` visited
then do
guard $ not revisited
......
module Main where
import Data.Array
import Data.Char
import Data.Functor
import Text.ParserCombinators.ReadP
data Fold
= FoldX Int
| FoldY Int
deriving Show
data Instructions = Instructions
{ dots :: [(Int,Int)]
, folds :: [Fold]
} deriving Show
parseInt :: ReadP Int
parseInt = read <$> munch1 isDigit
parseFold :: ReadP Fold
parseFold = parseDirection <*> parseInt where
parseDirection = parseFold' 'x' FoldX <++ parseFold' 'y' FoldY
parseFold' c op = string "fold along " *> char c *> char '=' $> op
parseInstructions :: ReadP Instructions
parseInstructions = do
ds <- many $ do
x <- parseInt
void $ char ','
y <- parseInt
skipSpaces
pure $ (x,y)
fs <- many $ parseFold <* skipSpaces
pure $ Instructions ds fs
instance Read Instructions where
readsPrec _ = readP_to_S parseInstructions
data Pixels = Pixels { getPixels :: Array (Int,Int) Bool }
makePixels :: [(Int,Int)] -> Pixels
makePixels ps = Pixels $ accumArray (\_ _ -> True) False ((0,0),(xMax,yMax)) mps where
xMax = maximum $ map fst ps
yMax = maximum $ map snd ps
mps = [(p,()) | p <- ps]
showPixels :: Pixels -> String
showPixels (Pixels parr) = unlines scanLines where
scanLines = [ [ toPixel $ parr ! (x,y) | x <- [0..xMax] ] | y <- [0..yMax] ]
((0,0),(xMax,yMax)) = bounds parr
toPixel True = '#'
toPixel False = '.'
main :: IO ()
main = pure ()
main = do
input <- read @Instructions <$> readFile "test/dots.txt"
putStr . showPixels . makePixels . dots $ input
6,10
0,14
9,10
0,3
10,4
4,11
6,0
6,12
4,1
0,13
10,12
3,4
3,0
8,4
1,10
2,14
8,10
9,0
fold along y=7
fold along x=5
\ No newline at end of file
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or sign in to comment