Blow your mind

From HaskellWiki
Revision as of 22:08, 18 November 2006 by Remi (talk | contribs) (Add splitAts :: [Int] -> [a] -> a)
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.

  -- comparing adjacent elements
  rises xs = zipWith (<) xs (drop 1 xs)
  
  -- lazy substring search
  -- "ell" -> "hello" -> True
  substr a b = any (a `isPrefixOf`) $ tails b

  -- multiple splitAt's:
  -- splitAts [2,5,0,3] [1..15] == [[1,2],[3,4,5,6,7],[],[8,9,10],[11,12,13,14,15]]
  splitAts = foldr (\n r -> splitAt n >>> second r >>> uncurry (:)) return

Mathematical Sequences, 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 sequence
  iterate (*2) 1

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


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

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

  fib = 0:scanl (+) 1 fib


  -- pascal triangle
  pascal = iterate (\row -> zipWith (+) ([0] ++ row) (row ++ [0])) [1]


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

  -- or if you want to use the Sieve of Eratosthenes..
  diff [] l = l
  diff l [] = l
  diff xl@(x:xs) yl@(y:ys) | x < y     = x:diff xs yl
                           | x > y     = diff xl ys
                           | otherwise = diff xs ys 
  esieve [] = []
  esieve (p:ps) = p:esieve (diff ps (iterate (+p) p))
  eprimes = esieve [2..]

  -- 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, ...)
  -}

Polynomials

In abstract algebra you learn that polynomials can be used the same way integers are used given the right assumptions about their coefficients and roots. Specifically, polynomials support addition, subtraction, multiplication and sometimes division. It also turns out that one way to think of polynomials is that they are just lists of numbers (their coefficients). Here is one way to use lists to model polynomials. Since polynomials can support the same operations as integers, we model polynomials by making a list of numbers an instance of the Num type class.

-- First we tell Haskell that we want to make lists (or [a]) an instance of Num.
-- We refer to this instance of the Num type class as Num [a].
-- If you tried to use just:
-- "instance Num [a] where"
-- You'd get errors because the element type a is too general, too unconstrainted
-- for what we need.
-- So we add constraints to "a" by saying "Num a", this means whatever "a" is, it
-- must be in the Num type class.

instance Num a => Num [a] where
-- Next, we have to implement all the operations that instances of Num support.
-- A minimal set of operations is +, *, negate, abs, signum and fromInteger.
  xs + ys = zipWith' (+) xs ys
    where
    zipWith' f [] ys = ys
    zipWith' f xs [] = xs
    zipWith' f (x:xs) (y:ys) = f x y : zipWith' f xs ys
-- We define a new version of zipWith that returns a list as long as the longest
-- of the two lists it is given.  If we did not do this then when we add polynomials
-- the result would be truncated to the length of the shorter polynomial.
  xs * ys = foldl1 (+) (padZeros partialProducts)
    where
    partialProducts = map (\x -> [x*y | y <- ys]) xs
    padZeros = map (\(z,zs) -> replicate z 0 ++ zs) . (zip [0..])
-- This function is sort of hard to explain.... basically [1,2,3] should correspond
-- to the polynomial 1 + 2x + 3x^2.  partialProducts does the steps of the multiplication
-- just like you would by hand when multiplying polynomials.
-- padZeros takes a list of polynomials and creates tuples of the form
-- (offset, poly).  If you notice when you add the partial products by hand
-- that you have to shift the partial products to the left on each new line.
-- we accomplish this by padding by zeros at the beginning of the partial product.
-- Finally we use foldl1 to sum the partial products.  Since they are polynomials
-- They are added by the definition of plus we already gave.
  negate xs = map negate xs
  abs xs = map abs xs  -- is this reasonable?
  signum xs = fromIntegral ((length xs)-1)
-- signum isn't really defined for polynomials, but polynomials do have a concept
-- of degree.  We might as well reuse signum as the degree of the
-- the polynomial.  Notice that constants have degree zero.
  fromInteger x = [fromInteger x]
-- This definition of fromInteger seems cyclical, it is left
-- as an exercise to the reader to figure out why it is correct :)

The reader is encouraged to write a simple pretty printer that takes into account the many special cases of displaying a polynomial. For example, [1,3,-2, 0, 1,-1,0] should display as: -x^5 + x^4 - 2x^2 + 3x + 1

Other execrises for the reader include writing
polyApply :: (Num a) => [a] -> a -> a
which evaluates the polynomial at a specific value or writing a differentiation function.

See also Pointfree, [1].