Skip to content

Commit

Permalink
replace Map with HashMap where it makes sense
Browse files Browse the repository at this point in the history
  • Loading branch information
Prillan committed Dec 9, 2021
1 parent 082aee3 commit ed0e6d4
Show file tree
Hide file tree
Showing 60 changed files with 333 additions and 350 deletions.
12 changes: 6 additions & 6 deletions 2015/day11/run.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,14 +3,14 @@ import Data.List ((\\))
import Data.Maybe (mapMaybe, listToMaybe)
import Data.Vector (Vector)
import qualified Data.Vector as V
import Data.Map.Strict (Map)
import qualified Data.Map.Strict as Map
import Data.HashMap.Strict (HashMap)
import qualified Data.HashMap.Strict as HashMap

newtype Password = Password (Vector Int)

strRep :: Password -> String
strRep = V.toList . V.map (az !!) . coerce
fromStrRep = Password . V.fromList . mapMaybe (`Map.lookup` rev)
fromStrRep = Password . V.fromList . mapMaybe (`HashMap.lookup` rev)

instance Show Password where
show p = strRep p ++ " " ++ s ++ " " ++ show (toInt p)
Expand Down Expand Up @@ -39,10 +39,10 @@ instance Num Password where
upper = base ^ 8

az = ['a'..'z']
rev :: Map Char Int
rev = Map.fromList $ zip az [0..]
rev :: HashMap Char Int
rev = HashMap.fromList $ zip az [0..]

bad = mapMaybe (flip Map.lookup rev) "iol"
bad = mapMaybe (flip HashMap.lookup rev) "iol"

base = length az

Expand Down
12 changes: 6 additions & 6 deletions 2015/day13/run.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,8 +4,8 @@ import Control.Applicative

import Data.List (permutations, minimumBy, maximumBy, maximum)
import Data.Maybe (fromJust)
import Data.Map.Strict (Map)
import qualified Data.Map.Strict as Map
import Data.HashMap.Strict (HashMap)
import qualified Data.HashMap.Strict as HashMap
import Text.Parsec hiding ((<|>))

type Person = String
Expand All @@ -20,7 +20,7 @@ data Arrangement = A [Person] Integer
instance Ord Arrangement where
compare (A _ x) (A _ y) = compare x y

type Settings = Map (Person, Person) Integer
type Settings = HashMap (Person, Person) Integer

person :: Stream s m Char => ParsecT s u m String
person = choice $ map (try.string) persons
Expand All @@ -42,14 +42,14 @@ pairing = do
readPairing :: String -> Either ParseError Pairing
readPairing = parse pairing ""

unsafeLookup m (p1, p2) = fromJust $ Map.lookup (p1, p2) m <|> Map.lookup (p2, p1) m
unsafeLookup m (p1, p2) = fromJust $ HashMap.lookup (p1, p2) m <|> HashMap.lookup (p2, p1) m
happiness m (p1, p2) = fromJust $ (+) <$> lkp (p1, p2) <*> lkp (p2, p1)
where lkp (p1, p2) = Map.lookup (p1, p2) m
where lkp (p1, p2) = HashMap.lookup (p1, p2) m

unsafeRight (Right x) = x

process input = optimal
where setting = Map.fromList . map (toTuple . unsafeRight . readPairing) . lines $ input
where setting = HashMap.fromList . map (toTuple . unsafeRight . readPairing) . lines $ input
arrangements = map (head (persons):) (permutations (drop 1 persons))
value xs = sum . map (happiness setting) $ zip xs (drop 1 xs ++ [head xs])
toArrangement xs = A xs (value xs)
Expand Down
18 changes: 9 additions & 9 deletions 2015/day16/run.hs
Original file line number Diff line number Diff line change
@@ -1,34 +1,34 @@
import Data.Aeson
import Text.Parsec

import Data.Map.Strict (Map)
import qualified Data.Map.Strict as Map
import Data.HashMap.Strict (HashMap)
import qualified Data.HashMap.Strict as HashMap

data Sue = Sue { sueIndex :: Int
, sueProps :: Map String Int}
, sueProps :: HashMap String Int}
deriving Show

unsafeRight (Right x) = x

readInt = (read :: String -> Int) <$> many1 digit

sue = Sue <$> (string "Sue " *> (readInt <* string ": "))
<*> (Map.fromList <$> sepBy property (string ", "))
<*> (HashMap.fromList <$> sepBy property (string ", "))
where property = (,) <$> many1 alphaNum <*> (string ": " *> readInt)

parseAll = map unsafeRight . map (parse sue "") . lines

machineOutput = Sue {
sueIndex = -1,
sueProps = Map.fromList [("akitas",0),("cars",2),("cats",7),("children",3),("goldfish",5),("perfumes",1),("pomeranians",3),("samoyeds",2),("trees",3),("vizslas",0)]}
sueProps = HashMap.fromList [("akitas",0),("cars",2),("cats",7),("children",3),("goldfish",5),("perfumes",1),("pomeranians",3),("samoyeds",2),("trees",3),("vizslas",0)]}

matches (Sue _ props) (Sue _ toMatch) = all p . Map.toList $ props
where p (prop, count) = case Map.lookup prop toMatch of
matches (Sue _ props) (Sue _ toMatch) = all p . HashMap.toList $ props
where p (prop, count) = case HashMap.lookup prop toMatch of
Nothing -> False
Just c' -> count == c'

matches2 (Sue _ props) (Sue _ toMatch) = all p . Map.toList $ props
where p (prop, count) = case (Map.lookup prop toMatch, prop) of
matches2 (Sue _ props) (Sue _ toMatch) = all p . HashMap.toList $ props
where p (prop, count) = case (HashMap.lookup prop toMatch, prop) of
(Nothing, _) -> False
(Just c', "cats") -> count > c'
(Just c', "trees") -> count > c'
Expand Down
4 changes: 2 additions & 2 deletions 2015/day17/run.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,8 +7,8 @@ import Data.List ( permutations
, maximumBy
, sort
, subsequences )
import Data.Map.Strict (Map)
import qualified Data.Map.Strict as Map
import Data.HashMap.Strict (HashMap)
import qualified Data.HashMap.Strict as HashMap
import Text.Parsec

unsafeRight (Right x) = x
Expand Down
2 changes: 0 additions & 2 deletions 2015/day19/run.hs
Original file line number Diff line number Diff line change
@@ -1,8 +1,6 @@
{-# LANGUAGE BangPatterns #-}
import Data.Aeson
import Data.List (permutations, group, minimum, maximum, minimumBy, maximumBy, isPrefixOf, sortBy)
import Data.Map.Strict (Map)
import qualified Data.Map.Strict as Map
import Data.Maybe (mapMaybe)
import qualified Data.Set as Set
import Data.Vector ((!), (!?))
Expand Down
2 changes: 0 additions & 2 deletions 2015/day24/run.hs
Original file line number Diff line number Diff line change
@@ -1,8 +1,6 @@
import Data.Aeson
import Data.List (permutations, group, minimum, maximum, minimumBy, maximumBy, groupBy, (\\), sort)
import qualified Data.List as L
import Data.Map.Strict (Map)
import qualified Data.Map.Strict as Map
import Text.Parsec
import Debug.Trace

Expand Down
8 changes: 4 additions & 4 deletions 2015/day9/run.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,8 +2,8 @@
{-# LANGUAGE FlexibleContexts #-}
import Data.List (minimumBy, permutations, nub)
import Data.Maybe
import Data.Map.Strict (Map)
import qualified Data.Map.Strict as Map
import Data.HashMap.Strict (HashMap)
import qualified Data.HashMap.Strict as HashMap
import Data.Set (Set)
import qualified Data.Set as Set
import Data.String (IsString, fromString)
Expand Down Expand Up @@ -42,8 +42,8 @@ shortestPath paths = minimumBy (\a b -> snd a `compare` snd b)
. map (\cs -> (cs, sum $ zipWith lookup cs (drop 1 cs)))
. permutations $ cities
where cities = nub $ map start paths ++ map stop paths
distances = Map.fromList . map (\p -> ((start p, stop p), dist p)) $ paths
lookup s e = fromJust $ Map.lookup (s, e) distances <|> Map.lookup (e, s) distances
distances = HashMap.fromList . map (\p -> ((start p, stop p), dist p)) $ paths
lookup s e = fromJust $ HashMap.lookup (s, e) distances <|> HashMap.lookup (e, s) distances

remove :: Eq a => a -> [a] -> [a]
remove x = filter (/= x)
Expand Down
18 changes: 9 additions & 9 deletions 2016/day10/run.hs
Original file line number Diff line number Diff line change
@@ -1,8 +1,8 @@
{-# LANGUAGE TupleSections #-}
import Data.Bifunctor
import Data.List (sort)
import Data.Map.Strict (Map)
import qualified Data.Map.Strict as Map
import Data.HashMap.Strict (HashMap)
import qualified Data.HashMap.Strict as HashMap
import Text.Megaparsec hiding (State, empty)
import Text.Megaparsec.Char
import Data.Void (Void)
Expand All @@ -12,18 +12,18 @@ unsafeRight (Right x) = x
type BotId = Int
type OutputId = Int
data Target = B BotId | O OutputId
type Logic = (Map BotId [Int], Map OutputId Int)
type Logic = (HashMap BotId [Int], HashMap OutputId Int)

empty :: Logic
empty = (Map.empty, Map.empty)
empty = (HashMap.empty, HashMap.empty)

num = read <$> some digitChar

insertBot :: Int -> BotId -> Logic -> Logic
insertBot val bid = first (Map.insertWith (++) bid [val])
insertBot val bid = first (HashMap.insertWith (++) bid [val])

insertOut :: Int -> OutputId -> Logic -> Logic
insertOut val oid = second (Map.insert oid val)
insertOut val oid = second (HashMap.insert oid val)

insertTarget :: Int -> Target -> Logic -> Logic
insertTarget val t =
Expand All @@ -35,7 +35,7 @@ insert val bid = Just . insertBot val bid

move :: BotId -> Target -> Target -> Logic -> Maybe Logic
move bid lowTo highTo logic = do
[low, high] <- sort <$> Map.lookup bid (fst logic)
[low, high] <- sort <$> HashMap.lookup bid (fst logic)
pure . insertTarget low lowTo . insertTarget high highTo $ logic

type Inst = Logic -> Maybe Logic
Expand Down Expand Up @@ -70,15 +70,15 @@ part1 =
fst . head
. filter ((== [17, 61]) . snd)
. map (second sort)
. Map.toList
. HashMap.toList
. fst
. eval
part2 :: [Inst] -> Int
part2 =
product
. map snd
. filter ((`elem` [0,1,2]) . fst)
. Map.toList
. HashMap.toList
. snd
. eval

Expand Down
20 changes: 10 additions & 10 deletions 2016/day12/run.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
import Data.List (permutations, group, minimum, maximum, minimumBy, maximumBy)
import Data.Map.Strict (Map)
import qualified Data.Map.Strict as Map
import Data.HashMap.Strict (HashMap)
import qualified Data.HashMap.Strict as HashMap
import Data.Void (Void)
import Text.Megaparsec hiding (State)
import Text.Megaparsec.Char
Expand Down Expand Up @@ -55,13 +55,13 @@ fromList def xs =
let (x':xs') = xs ++ [def]
in Z [] x' xs'

type State = (Map Reg Val, Zipper Instr)
type State = (HashMap Reg Val, Zipper Instr)

newState instr = (Map.fromList (zip "abcd" (repeat 0)), fromList Stop instr)
newState instr = (HashMap.fromList (zip "abcd" (repeat 0)), fromList Stop instr)

val :: State -> Either Val Reg -> Val
val _ (Left v) = v
val (m, _) (Right r) = maybe 0 id (Map.lookup r m)
val (m, _) (Right r) = maybe 0 id (HashMap.lookup r m)

iter :: (a -> a) -> Int -> a -> a
iter f n = foldr (.) id (replicate n f)
Expand All @@ -81,13 +81,13 @@ jnz s v steps
| v /= 0 && steps < 0 = backward s (negate steps)

cpy :: State -> Val -> Reg -> State
cpy (m, z) v k = (Map.insert k v m, z)
cpy (m, z) v k = (HashMap.insert k v m, z)

inc :: State -> Reg -> State
inc (m, z) k = (Map.update (pure . (+1)) k m, z)
inc (m, z) k = (HashMap.update (pure . (+1)) k m, z)

dec :: State -> Reg -> State
dec (m, z) k = (Map.update (pure . (+ (-1))) k m, z)
dec (m, z) k = (HashMap.update (pure . (+ (-1))) k m, z)

exec1 :: State -> State
exec1 s =
Expand All @@ -108,8 +108,8 @@ unsafeRight (Right x) = x
parseAll = map unsafeRight .
map (parse instrP "") . lines

part1 = (Map.! 'a') . fst . exec . newState
part2 = (Map.! 'a') . fst . exec . newState . ((Cpy (Left 1) 'c'):)
part1 = (HashMap.! 'a') . fst . exec . newState
part2 = (HashMap.! 'a') . fst . exec . newState . ((Cpy (Left 1) 'c'):)

showState :: State -> String
showState (st, Z prev c next) =
Expand Down
2 changes: 0 additions & 2 deletions 2016/day17/run.hs
Original file line number Diff line number Diff line change
@@ -1,8 +1,6 @@
{-# LANGUAGE TupleSections #-}
import Control.Monad (guard)
import Data.List (permutations, group, minimum, maximum, minimumBy, maximumBy)
import Data.Map.Strict (Map)
import qualified Data.Map.Strict as Map
import Data.Set (Set)
import qualified Data.Set as Set
import Text.Megaparsec hiding (State)
Expand Down
2 changes: 0 additions & 2 deletions 2016/day2/run.hs
Original file line number Diff line number Diff line change
@@ -1,7 +1,5 @@
import Data.Aeson
import Data.List (permutations, group, minimum, maximum, minimumBy, maximumBy)
import Data.Map.Strict (Map)
import qualified Data.Map.Strict as Map
import Text.Parsec

data I = R | L | D | U
Expand Down
32 changes: 16 additions & 16 deletions 2016/day22/run.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,8 +4,8 @@ import Data.List ( intercalate
, maximum
, minimumBy
, subsequences)
import Data.Map.Strict (Map)
import qualified Data.Map.Strict as Map
import Data.HashMap.Strict (HashMap)
import qualified Data.HashMap.Strict as HashMap
import Data.PriorityQueue.FingerTree (PQueue)
import qualified Data.PriorityQueue.FingerTree as PQueue
import Data.Set (Set)
Expand All @@ -31,16 +31,16 @@ lineP = (,) <$> nodeNameP <*> nodeP

unsafeRight (Right x) = x

parseAll = Map.fromList . map unsafeRight .
parseAll = HashMap.fromList . map unsafeRight .
map (parse lineP "") . drop 2 . lines

viable :: Node -> Node -> Bool
viable a b =
used a > 0 && avail b >= used a

part1 nodes = length $ do
n1 <- Map.toList nodes
n2 <- Map.toList nodes
n1 <- HashMap.toList nodes
n2 <- HashMap.toList nodes
guard $ fst n1 /= fst n2
guard $ viable (snd n1) (snd n2)
pure $ (n1, n2)
Expand All @@ -49,7 +49,7 @@ data Reduced = NEmpty | NGoal | NBig | NNormal
deriving (Show, Eq, Ord)
data State = State { goal :: {-# UNPACK #-} !(Int, Int)
, empty :: {-# UNPACK #-} !(Int, Int)
, nodes :: Map (Int, Int) Reduced }
, nodes :: HashMap (Int, Int) Reduced }
deriving (Show, Eq, Ord)

solve :: State -> (Int, State)
Expand Down Expand Up @@ -82,34 +82,34 @@ viable' _ = False
neighboursOf :: State -> [State]
neighboursOf s = do
let (x, y) = empty s
Just en = Map.lookup (empty s) (nodes s)
Just en = HashMap.lookup (empty s) (nodes s)
(x', y') <- [(x, y-1), (x-1, y), (x, y+1), (x+1, y)]
Just bn <- pure $ Map.lookup (x', y') (nodes s)
Just bn <- pure $ HashMap.lookup (x', y') (nodes s)
guard $ viable' bn
let g' = if (x', y') == goal s
then (x, y)
else goal s
e' = (x', y')
m = Map.insert (x', y') en $
Map.insert (x, y) bn $ nodes s
m = HashMap.insert (x', y') en $
HashMap.insert (x, y) bn $ nodes s
pure $ State { goal = g'
, empty = e'
, nodes = m }

part2 = fst . solve . initialState

reduceGrid g = Map.mapWithKey f
reduceGrid g = HashMap.mapWithKey f
where f pos n
| used n == 0 = NEmpty
| pos == g = NGoal
| used n >= 100 = NBig
| otherwise = NNormal

initialState grid =
let mx = maximum . map (fst . fst) . Map.toList $ grid
let mx = maximum . map (fst . fst) . HashMap.toList $ grid
g = (mx, 0)
grid' = reduceGrid g grid
(epos, _) = head . filter ((==NEmpty).snd) . Map.toList $ grid'
(epos, _) = head . filter ((==NEmpty).snd) . HashMap.toList $ grid'
in
State { goal = g
, empty = epos
Expand All @@ -121,10 +121,10 @@ pstate s =
++ "\nh: " ++ show (h s)

pgrid s =
let xm = maximum . map (fst . fst) . Map.toList $ nodes s
ym = maximum . map (snd . fst) . Map.toList $ nodes s
let xm = maximum . map (fst . fst) . HashMap.toList $ nodes s
ym = maximum . map (snd . fst) . HashMap.toList $ nodes s
c pos =
let Just v = Map.lookup pos (nodes s)
let Just v = HashMap.lookup pos (nodes s)
in case v of
NEmpty -> '_'
NNormal -> '.'
Expand Down
Loading

0 comments on commit ed0e6d4

Please sign in to comment.