Blow your mind
Helpful Idioms
-- splitting in twos (alternating) -- "1234567" -> ("1357", "246") foldr (\a (x,y) -> (a:y,x)) ("","")
-- splitting in N -- 2 -> "1234567" -> ["12", "34", "56", "7"] until (null . snd) (\(a,b) -> let (x,y) = splitAt 2 b in (a++[x],y)) $ ([], [1..7])
-- split at whitespace -- "hello world" -> ["hello","world"] words fst . until (null . snd) (\(a,b) -> let (x,y) = break (==' ') b in (a++[x], drop 1 y)) $ ([], "hello world")
-- combinations -- "12" -> "45" -> ["14", "15", "24", "25"] sequence ["12", "45"]
-- factorial -- 6 -> 720 product [1..6] foldl1 (*) [1..6] (!!6) $ unfoldr (\(n,f) -> Just (f, (n+1,f*n))) (1,1) fix (\f (n,g) -> if n > 6 then g else f (n+1,g*n)) (1,1)
-- interspersing with newlines -- ["hello","world"] -> "hello world" unlines intersperse '\n'
-- sorting by a custom function -- length -> ["abc", "ab", "a"] -> ["a", "ab", "abc"] sortBy length map snd . sortBy fst . map (length &&& id) -- zweierpotenzen iterate (*2) 1 unfoldr (\z -> Just (z,2*z)) 1
-- simulating lisp's cond case () of () | 1 > 2 -> True | 3 < 4 -> False | otherwise -> True
-- add indices to list for later use -- [3,3,3] -> [(0,3),(1,3),(2,3)] zip [0..] -- fibonacci series unfoldr (\(f1,f2) -> Just (f1,(f2,f1+f2))) (1,1) fibs = 1:1:zipWith (+) fibs (tail fibs) -- naive matrix operations -- m = [[1,2],[3,4],[5,6]] transpose scalMul s = map (map (s*)) invert = scalMul (-1) matMul a b = zipWith (zipWith (*)) a (transpose b) matAdd = zipWith (zipWith (+))
-- unjust'ify list of Maybe's -- [Just 4, Nothing, Just 3] -> [4,3] catMaybes
-- find substring -- "ell" -> "hello" -> True substr a b = any (a `elem`) $ liftM inits (tails b)
-- apply a list of functions to an argument -- even -> odd -> 4 -> [True,False] map ($4) [even,odd] sequence [even,odd] 4 -- apply a function to two other function the same argument -- (lifting to the function monad (->)) -- even 4 && odd 4 -> False liftM2 (&&) even odd 4 liftM2 (>>) putStrLn return "hello" -- putStrLn "hello" >> return "hello"
{- either maybe group fun with monad, monadPlus liftM -}