Blow your mind: Difference between revisions
mNo edit summary |
mNo edit summary |
||
Line 1: | Line 1: | ||
Helpful Idioms | = Helpful, Cool, Magical Idioms = | ||
i haven't quite formulated for myself what this collection is for. for now, i'm collecting usefull, cool idiomatic ways of solving problems in haskell. at a later time i might add explanations to the more obscure solutions. | |||
i've also started providing several alternatives to give more insight into the interrelations of solutions. | |||
whoever has any more ideas, please feel free to just add them; if you see mistakes or simpler solutions please correct my chaotic collection. | |||
i'm very interested in more "obscure" solutions, which showcase the applicability of haskell's (unique) features (i.e. monad magic, folds and unfolds, fix points, ...) | |||
this collection is supposed to be comprised of very short examples, which incite curiosity in the reader and lead him to a deeper understanding of advanced haskell concepts. | |||
<code> | |||
-- splitting in twos (alternating) | -- splitting in twos (alternating) | ||
-- "1234567" -> ("1357", "246") | -- "1234567" -> ("1357", "246") | ||
Line 111: | Line 122: | ||
list monad vs comprehensions | list monad vs comprehensions | ||
-} | -} | ||
</code> |
Revision as of 11:18, 1 March 2006
Helpful, Cool, Magical Idioms
i haven't quite formulated for myself what this collection is for. for now, i'm collecting usefull, cool idiomatic ways of solving problems in haskell. at a later time i might add explanations to the more obscure solutions.
i've also started providing several alternatives to give more insight into the interrelations of solutions.
whoever has any more ideas, please feel free to just add them; if you see mistakes or simpler solutions please correct my chaotic collection.
i'm very interested in more "obscure" solutions, which showcase the applicability of haskell's (unique) features (i.e. monad magic, folds and unfolds, fix points, ...)
this collection is supposed to be comprised of very short examples, which incite curiosity in the reader and lead him to a deeper understanding of advanced haskell concepts.
-- 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"]
[x:[y] | x <- "12", y <- "45"]
"12" >>= \a -> "45" >>= \b -> return (a:[b])
-- 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 <= 0 then g else f (n-1,g*n)) (6,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))) (0,1)
fibs = 0:1:zipWith (+) fibs (tail fibs)
fib = 0:scanl (+) 1 fib
-- 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`) $ map 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"
-- match a constructor
-- this is better than applying all the arguments, because this way the data type can be changed without touching the code (ideally).
case a of Just{} -> True
_ -> False
-- prime numbers
-- example of a memoising caf (??)
primes = sieve [2..] where
sieve (p:x) = p : sieve [ n | n <- x, n `mod` p > 0 ]
{-
either
maybe
group
fun with monad, monadPlus
liftM
list monad vs comprehensions
-}