Blow your mind

From HaskellWiki
Revision as of 17:58, 2 April 2006 by JaredUpdike (talk | contribs) (PDF link changed to HTML link, reformatted comments to avoid going off right side of page)
Jump to navigation Jump to search

Useful Idioms that will blow your mind (unless you already know them :)

This collection is supposed to be comprised of short, useful, cool, magical examples, which should incite the reader's curiosity 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.

More examples are always welcome, especially "obscure" monadic ones.


List/String Operations

  -- split at whitespace
  -- "hello world" -> ["hello","world"]
  words

  takeWhile (not . null) . unfoldr (Just . (second $ drop 1) . break (==' '))

  fix (\f l -> if null l then [] else let (s,e) = break (==' ') l in s:f (drop 1 e))


  -- splitting in two (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) 
  -- this one uses the solution to the next problem in a nice way :)
  

  -- splitting into lists of length N
  -- "1234567" -> ["12", "34", "56", "7"]
  unfoldr (\a -> if null a then Nothing else Just $ splitAt 2 a)

  takeWhile (not . null) . unfoldr (Just . splitAt 2)
                 

  -- sorting by a custom function
  -- length -> ["abc", "ab", "a"] -> ["a", "ab", "abc"]
  comparing f x y = compare (f x) (f y)
  sortBy (comparing length)

  map snd . sortBy (comparing fst) . map (length &&& id) 
  -- the so called "Schwartzian Transform" for computationally more expensive 
  -- functions.
  
  
  -- lazy substring search
  -- "ell" -> "hello" -> True
  substr a b = any (a `isPrefixOf`) $ tails b

Mathematical Series, etc

  -- factorial
  -- 6 -> 720
  product [1..6]

  foldl1 (*) [1..6]

  (!!6) $ scanl (*) 1 [1..]

  fix (\f n -> if n <= 0 then 1 else n * f (n-1))


  -- powers of two series
  iterate (*2) 1

  unfoldr (\z -> Just (z,2*z)) 1


  -- fibonacci series
  unfoldr (\(f1,f2) -> Just (f1,(f2,f1+f2))) (0,1)

  fibs = 0:1:zipWith (+) fibs (tail fibs)

  fib = 0:scanl (+) 1 fib


  -- 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 ])

  -- enumerating the rationals (see [1])
  rats :: [Rational]
  rats = iterate next 1 where
       next x = recip (fromInteger n+1-y) where (n,y) = properFraction x

[1] Gibbons, Lest, Bird - Enumerating the Rationals

Monad Magic

  -- all combinations of a list of lists.
  -- these solutions are all pretty much equivalent in that they run
  -- in the List Monad. the "sequence" solution has the advantage of
  -- scaling to N sublists.
  -- "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]


  -- all combinations of letters
  (inits . repeat) ['a'..'z'] >>= sequence

  
  -- 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"

  
  -- forward function concatenation
  (*3) >>> (+1) $ 2

  foldl1 (flip (.)) [(+1),(*2)] 500


  -- perform functions in/on a monad, lifting
  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 }


Other

  -- simulating lisp's cond
  case () of () | 1 > 2     -> True
                | 3 < 4     -> False
                | otherwise -> True


  -- 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


  {- 
  TODO, IDEAS:
    more fun with monad, monadPlus (liftM, ap, guard, when)
    fun with arrows (second, first, &&&, ***)
    liftM, ap
    lazy search (searching as traversal of lazy structures)
    innovative data types (i.e. having fun with Maybe sequencing)
  
  LINKS:
    bananas, envelopes, ...   (generic traversal)
    why functional fp matters (lazy search, ...)
  -}