Blow your mind: Difference between revisions
mNo edit summary |
mNo edit summary |
||
Line 13: | Line 13: | ||
(map snd *** map snd) . partition (even . fst) . zip [0..] | (map snd *** map snd) . partition (even . fst) . zip [0..] | ||
transpose . unfoldr (\a -> if null a then Nothing else Just $ splitAt 2 a) -- see next entry | |||
-- splitting in N | -- splitting in N | ||
-- | -- "1234567" -> ["12", "34", "56", "7"] | ||
unfoldr (\a -> if null a then Nothing else Just $ splitAt 2 a) | unfoldr (\a -> if null a then Nothing else Just $ splitAt 2 a) | ||
Line 24: | Line 26: | ||
unfoldr (\a -> if null a then Nothing else Just . (second $ drop 1) . break (==' ') $ a) | unfoldr (\a -> if null a then Nothing else Just . (second $ drop 1) . break (==' ') $ a) | ||
fix (\f l -> if null l then [] else let (s,e) = break (==' ') l in s:f (drop 1 e)) | |||
Line 127: | Line 131: | ||
-- forward function concatenation | -- forward function concatenation | ||
(*3) >>> (+1) $ 2 | (*3) >>> (+1) $ 2 | ||
foldl1 (flip (.)) [(+1),(*2)] 500 | |||
Line 139: | Line 144: | ||
-- [still to categorize] | -- [still to categorize] | ||
(id >>= (+) >>= (+) >>= (+)) 3 -- (3+3)+(3+3) = 12 | (id >>= (+) >>= (+) >>= (+)) 3 -- (3+3)+(3+3) = 12 | ||
(join . liftM2) (*) (+3) 5 -- 64 | (join . liftM2) (*) (+3) 5 -- 64 | ||
mapAccumL (\acc n -> (acc+n,acc+n)) 0 [1..10] -- interesting for fac, fib, ... | mapAccumL (\acc n -> (acc+n,acc+n)) 0 [1..10] -- interesting for fac, fib, ... | ||
do f <- [not, not]; d <- [True, False]; return (f d) -- [False,True,False,True] | do f <- [not, not]; d <- [True, False]; return (f d) -- [False,True,False,True] | ||
do { Just x <- [Nothing, Just 5, Nothing, Just 6, Just 7, Nothing]; return x } | |||
-- all combinations of letters | -- all combinations of letters |
Revision as of 16:13, 1 March 2006
Useful, Cool, Magical Idioms
this collection is supposed to be comprised of short, useful, cool, magical examples, which incite curiosity in the reader and (hopefully) lead him to a deeper understanding of advanced haskell concepts. 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, ...)
-- splitting in twos (alternating)
-- "1234567" -> ("1357", "246")
foldr (\a (x,y) -> (a:y,x)) ([],[])
(map snd *** map snd) . partition (even . fst) . zip [0..]
transpose . unfoldr (\a -> if null a then Nothing else Just $ splitAt 2 a) -- see next entry
-- splitting in N
-- "1234567" -> ["12", "34", "56", "7"]
unfoldr (\a -> if null a then Nothing else Just $ splitAt 2 a)
-- split at whitespace
-- "hello world" -> ["hello","world"]
words
unfoldr (\a -> if null a then Nothing else Just . (second $ drop 1) . break (==' ') $ a)
fix (\f l -> if null l then [] else let (s,e) = break (==' ') l in s:f (drop 1 e))
-- combinations
-- "12" -> "45" -> ["14", "15", "24", "25"]
sequence ["12", "45"]
[[x,y] | x <- "12", y <- "45"]
do { x <- "12"; y <- "45"; return [x,y] }
"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 -> if n <= 0 then 1 else n * f (n-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 ]
unfoldr sieve [2..] where
sieve (p:x) = Just(p, [ n | n <- x, n `mod` p > 0 ])
-- forward function concatenation
(*3) >>> (+1) $ 2
foldl1 (flip (.)) [(+1),(*2)] 500
-- perform functions in/on a monad
fmap (+2) (Just 2)
liftM2 (+) (Just 4) (Just 2)
-- [still to categorize]
(id >>= (+) >>= (+) >>= (+)) 3 -- (3+3)+(3+3) = 12
(join . liftM2) (*) (+3) 5 -- 64
mapAccumL (\acc n -> (acc+n,acc+n)) 0 [1..10] -- interesting for fac, fib, ...
do f <- [not, not]; d <- [True, False]; return (f d) -- [False,True,False,True]
do { Just x <- [Nothing, Just 5, Nothing, Just 6, Just 7, Nothing]; return x }
-- all combinations of letters
(inits . repeat) ['a'..'z'] >>= sequence
{-
TODO, ideas:
either
maybe
group
fun with monad, monadPlus
fun with arrows (second, first, &&&, ***)
liftM, ap
list monad vs comprehensions
LINKS:
bananas, envelopes, ... (generic traversal)
why functional fp matters (lazy search, ...)
-}