Day eight: Use Flow for more sane piping

This commit is contained in:
2024-12-08 14:01:32 +01:00
parent ff74e85ba6
commit 3fe54232b2
5 changed files with 10 additions and 5 deletions

View File

@@ -29,6 +29,7 @@ library
build-depends: build-depends:
base >=4.7 && <5 base >=4.7 && <5
, containers , containers
, flow
default-language: Haskell2010 default-language: Haskell2010
executable day08-haskell-exe executable day08-haskell-exe

View File

@@ -25,6 +25,7 @@ library:
source-dirs: src source-dirs: src
dependencies: dependencies:
- containers - containers
- flow
executables: executables:
day08-haskell-exe: day08-haskell-exe:

View File

@@ -2,6 +2,7 @@ module Common where
import Data.Foldable (toList) import Data.Foldable (toList)
import qualified Data.Map.Strict as Map import qualified Data.Map.Strict as Map
import Flow
multiMapFromList :: Ord k => [(k, v)] -> Map.Map k [v] multiMapFromList :: Ord k => [(k, v)] -> Map.Map k [v]
multiMapFromList = Map.fromListWith (++) . map (\(k, v) -> (k, [v])) multiMapFromList = Map.fromListWith (++) . map (\(k, v) -> (k, [v]))
@@ -20,10 +21,10 @@ enumerate :: [a] -> [(Int, a)]
enumerate = zip [0..] enumerate = zip [0..]
readWorld :: String -> World readWorld :: String -> World
readWorld input = (determineSize $ lines input, readAntennas input) readWorld input = (lines input |> determineSize, readAntennas input)
where where
determineSize :: [String] -> Position determineSize :: [String] -> Position
determineSize ls = (maximum $ map length ls, length ls) determineSize ls = (map length ls |> maximum, length ls)
readAntennas :: String -> [Antenna] readAntennas :: String -> [Antenna]
readAntennas input = enumerate (lines input) >>= readLine readAntennas input = enumerate (lines input) >>= readLine

View File

@@ -4,10 +4,11 @@ import Common (Position, readWorld, multiMapFromList, pairPermutations)
import qualified Data.Map.Strict as Map import qualified Data.Map.Strict as Map
import qualified Data.Set as Set import qualified Data.Set as Set
import Control.Monad (join) import Control.Monad (join)
import Flow
task1 :: String -> Int task1 :: String -> Int
task1 input = case readWorld input of task1 input = case readWorld input of
((width, height), antennas) -> length $ Set.fromList $ filter isInWorld $ join $ map antinodesOfFrequency $ Map.elems $ multiMapFromList antennas ((width, height), antennas) -> multiMapFromList antennas |> Map.elems |> map antinodesOfFrequency |> join |> filter isInWorld |> Set.fromList |> length
where where
antinodesOfFrequency :: [Position] -> [Position] antinodesOfFrequency :: [Position] -> [Position]
antinodesOfFrequency nodes = pairPermutations nodes >>= antinodesOfPair antinodesOfFrequency nodes = pairPermutations nodes >>= antinodesOfPair

View File

@@ -4,10 +4,11 @@ import Common (Position, readWorld, multiMapFromList, pairPermutations)
import qualified Data.Map.Strict as Map import qualified Data.Map.Strict as Map
import qualified Data.Set as Set import qualified Data.Set as Set
import Control.Monad (join) import Control.Monad (join)
import Flow
task2 :: String -> Int task2 :: String -> Int
task2 input = case readWorld input of task2 input = case readWorld input of
((width, height), antennas) -> length $ Set.fromList $ join $ map antinodesOfFrequency $ Map.elems $ multiMapFromList antennas ((width, height), antennas) -> multiMapFromList antennas |> Map.elems |> map antinodesOfFrequency |> join |> Set.fromList |> length
where where
antinodesOfFrequency :: [Position] -> [Position] antinodesOfFrequency :: [Position] -> [Position]
antinodesOfFrequency nodes = pairPermutations nodes >>= antinodesOfPair antinodesOfFrequency nodes = pairPermutations nodes >>= antinodesOfPair
@@ -19,7 +20,7 @@ task2 input = case readWorld input of
in castInWorld a (-diffX, -diffY) ++ castInWorld b (diffX, diffY) in castInWorld a (-diffX, -diffY) ++ castInWorld b (diffX, diffY)
castInWorld (sx, sy) (ox, oy) = castInWorld (sx, sy) (ox, oy) =
takeWhile isInWorld $ map (\f -> (sx + ox * f, sy + oy * f)) [0..] map (\f -> (sx + ox * f, sy + oy * f)) [0..] |> takeWhile isInWorld
isInWorld :: Position -> Bool isInWorld :: Position -> Bool
isInWorld (x, y) isInWorld (x, y)