aboutsummaryrefslogtreecommitdiff
path: root/lib/Utils.hs
diff options
context:
space:
mode:
Diffstat (limited to 'lib/Utils.hs')
-rw-r--r--lib/Utils.hs44
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 @@
1module Utils ( binaryToInt 1module Utils where
2 , countElem
3 , xor
4 , right
5 , bet
6 , (&+)
7 , howMany
8 , sublists
9 , windows
10 ) where
11
12import Data.Char (digitToInt)
13import Control.Monad
14import Data.Either
15import Data.List (inits, tails)
16 2
3import Data.Char (digitToInt)
4import Control.Monad
5import Data.Either
6import Data.List (inits, tails)
7import Data.Map (Map)
8import qualified Data.Map as Map
17 9
18binaryToInt :: String -> Int 10binaryToInt :: String -> Int
19binaryToInt = foldl (\a x -> a * 2 + digitToInt x) 0 11binaryToInt = foldl (\a x -> a * 2 + digitToInt x) 0
@@ -28,13 +20,16 @@ right :: Either a b -> b
28right (Right b) = b 20right (Right b) = b
29right _ = undefined 21right _ = undefined
30 22
31bet :: Int -> (Int, Int) -> Bool
32bet k (l, u) = k >= l && k <= u 23bet k (l, u) = k >= l && k <= u
24bet' 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
38howMany :: (a -> Bool) -> [a] -> Int 33howMany :: (a -> Bool) -> [a] -> Int
39howMany predicate = length . filter predicate 34howMany 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
50add (x, y) (a, b) = (x+a, y+b)
51shear c (x, y) = (c * x, c * y)
52inside (p, q) (r, s) (a, b) = bet a (p, r) && bet b (q, s)
53inside' (p, q) (r, s) (a, b) = bet' a (p, r) && bet' b (q, s)
54
55-- [f, f.f, f.f.f, ...]
56repeatF f = f : map (f .) (repeatF f)
57
58makeGrid :: String -> (Map (Int, Int) Char, Int, Int)
59makeGrid 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