diff options
author | Akshay <[email protected]> | 2020-12-11 10:19:03 +0000 |
---|---|---|
committer | Akshay <[email protected]> | 2020-12-11 10:19:03 +0000 |
commit | 42523f2455fb30181efc29e3a47799283b05fa80 (patch) | |
tree | ce0687d20a0813cd8bcb2ccc46ff16a2db8b7251 /lib | |
parent | edd8e1fa47c6895b28bbe61ab786ab6dc30471cd (diff) |
add initial solution to day11
Diffstat (limited to 'lib')
-rw-r--r-- | lib/Utils.hs | 44 |
1 files changed, 28 insertions, 16 deletions
diff --git a/lib/Utils.hs b/lib/Utils.hs index 61c4e49..6358230 100644 --- a/lib/Utils.hs +++ b/lib/Utils.hs | |||
@@ -1,19 +1,11 @@ | |||
1 | module Utils ( binaryToInt | 1 | module Utils where |
2 | , countElem | ||
3 | , xor | ||
4 | , right | ||
5 | , bet | ||
6 | , (&+) | ||
7 | , howMany | ||
8 | , sublists | ||
9 | , windows | ||
10 | ) where | ||
11 | |||
12 | import Data.Char (digitToInt) | ||
13 | import Control.Monad | ||
14 | import Data.Either | ||
15 | import Data.List (inits, tails) | ||
16 | 2 | ||
3 | import Data.Char (digitToInt) | ||
4 | import Control.Monad | ||
5 | import Data.Either | ||
6 | import Data.List (inits, tails) | ||
7 | import Data.Map (Map) | ||
8 | import qualified Data.Map as Map | ||
17 | 9 | ||
18 | binaryToInt :: String -> Int | 10 | binaryToInt :: String -> Int |
19 | binaryToInt = foldl (\a x -> a * 2 + digitToInt x) 0 | 11 | binaryToInt = foldl (\a x -> a * 2 + digitToInt x) 0 |
@@ -28,13 +20,16 @@ right :: Either a b -> b | |||
28 | right (Right b) = b | 20 | right (Right b) = b |
29 | right _ = undefined | 21 | right _ = undefined |
30 | 22 | ||
31 | bet :: Int -> (Int, Int) -> Bool | ||
32 | bet k (l, u) = k >= l && k <= u | 23 | bet k (l, u) = k >= l && k <= u |
24 | bet' k (l, u) = k > l && k < u | ||
33 | 25 | ||
34 | -- combine filter predicates | 26 | -- combine filter predicates |
35 | (&+) :: (a -> Bool) -> (a -> Bool) -> (a -> Bool) | 27 | (&+) :: (a -> Bool) -> (a -> Bool) -> (a -> Bool) |
36 | (&+) = liftM2 (&&) | 28 | (&+) = liftM2 (&&) |
37 | 29 | ||
30 | (|+) :: (a -> Bool) -> (a -> Bool) -> (a -> Bool) | ||
31 | (|+) = liftM2 (||) | ||
32 | |||
38 | howMany :: (a -> Bool) -> [a] -> Int | 33 | howMany :: (a -> Bool) -> [a] -> Int |
39 | howMany predicate = length . filter predicate | 34 | howMany predicate = length . filter predicate |
40 | 35 | ||
@@ -49,3 +44,20 @@ kadane = go 0 0 | |||
49 | where go :: Int -> Int -> [Int] -> Int | 44 | where go :: Int -> Int -> [Int] -> Int |
50 | go best _ [] = best | 45 | go best _ [] = best |
51 | go best current (l:ls) = go (max best (current + l)) (max current (current + l)) ls | 46 | go best current (l:ls) = go (max best (current + l)) (max current (current + l)) ls |
47 | |||
48 | -- tuple stuff | ||
49 | |||
50 | add (x, y) (a, b) = (x+a, y+b) | ||
51 | shear c (x, y) = (c * x, c * y) | ||
52 | inside (p, q) (r, s) (a, b) = bet a (p, r) && bet b (q, s) | ||
53 | inside' (p, q) (r, s) (a, b) = bet' a (p, r) && bet' b (q, s) | ||
54 | |||
55 | -- [f, f.f, f.f.f, ...] | ||
56 | repeatF f = f : map (f .) (repeatF f) | ||
57 | |||
58 | makeGrid :: String -> (Map (Int, Int) Char, Int, Int) | ||
59 | makeGrid s = (grid, width, height) where | ||
60 | rows = lines s | ||
61 | grid = Map.fromList [((x, y), a) | (y, row) <- zip [0..] rows , (x, a) <- zip [0..] row] | ||
62 | width = length (head rows) | ||
63 | height = length rows | ||