Thomas Hartman wrote:
sorry, wrong function.

should be

partitions [] xs = []
partitions (n:parts) xs =
  let (beg,end) = splitAt n xs
  in beg : ( case end of
               [] -> []
               xs -> partitions parts xs)


It's not tail recursive, FWIW. The recursive expression has (:) as it's head before it hits `partitions`. It is however nicely coinductive, which has other good properties.

We could make it tail-recursive easily,

  partitions = go id
      where
      go k []     xs = k []
      go k (n:ns) xs =
          let (beg,end) = splitAt n xs
              k'        = k . (beg:)
          in  case end of
              []  -> k' []
              xs' -> go k' ns xs'

(Note how this version has `go` as the head of the recursive expression.)

...however this version has different strictness properties. In particular, let both input lists be infinite (and take a finite portion of the result). The original version works fine because it gives a little bit of output (beg:) at each step of the recursion ---which is all "coinductive" means. The tail-recursive version hits _|_ however, because we've delayed giving any input (k []) until one of the two lists hits [] ---we've tried doing induction on co-data and so we hit an infinite loop.

This dichotomy between coinduction and tail-recursion is quite common. It's another example of the recently discussed problem of defining foldr in terms of foldl. Whether the termination differences matter depends on how the function is to be used.


Another nice property of coinduction is that it means we can do build/fold fusion easily:

  partitions = \ns xs -> build (\cons nil -> go cons nil ns xs)
      where
      go cons nil = go'
          where
          go' []     xs = nil
          go' (n:ns) xs =
               let (beg,end) = splitAt n xs
               in  beg `cons` case end of
                              []  -> nil
                              xs' -> go' ns xs'

By using the GHC.Exts.build wrapper the fusion rules will automatically apply. The second wrapper, go, is just so that the worker, go', doesn't need to pass cons and nil down through the recursion.

--
Live well,
~wren
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to