Skip to content

Instantly share code, notes, and snippets.

@chris-taylor
Created June 14, 2012 23:05
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save chris-taylor/2933547 to your computer and use it in GitHub Desktop.
Save chris-taylor/2933547 to your computer and use it in GitHub Desktop.
Generic unfolds (partial solution)
{-# LANGUAGE ViewPatterns, GADTs, ScopedTypeVariables #-}
-- Functions to fold and unfold. We are using ViewPatterns to make the symmetry between fold and unfold explicity.
foldr2 :: (Either (a,b) () -> b) -> [a] -> b
foldr2 f [] = f $ Right ()
foldr2 f (x:xs) = f $ Left (x, foldr2 f xs)
unfoldr2 :: (b -> Either (a,b) ()) -> b -> [a]
unfoldr2 f (f -> Right () ) = []
unfoldr2 f (f -> Left (x, unfoldr2 f -> xs)) = x : xs
-- An example of using unfold to write a decending list from n to 1.
go :: Int -> Either (Int,Int) ()
go 0 = Right ()
go n = Left (n, n-1)
dec2 :: Int -> [Int]
dec2 n = unfoldr2 go n
-- A more generic unfold which can build data structures other than lists (although it can probably only build structures which are *isomorphic* to lists). Here s is the seed type, and c is the final type produced by the unfold.
unfoldr3 :: c -> (a -> c -> c) -> (s -> Either (a,s) ()) -> s -> c
unfoldr3 nil cons f (f -> Right () ) = nil
unfoldr3 nil cons f (f -> Left (x, unfoldr3 nil cons f -> xs)) = cons x xs
-- Example of usage
data List a = Nil | Cons a (List a) deriving (Show)
dec3 :: Int -> List Int
dec3 n = unfoldr3 Nil Cons go n
-- A GADT for an even more generic unfold. The constructors work as follows:
-- X is a wrapper for base types - it can hold values of any type. Typically this is either a function that builds up a recursive type, or the base value for the unfold (e.g. [] in the case of lists). It plays the role of [].
-- (:$) plays the role of (:). The second argument is a piece of data that we want stored in the unfolded data structure. The first argument is a constructor that can place data inside a data structure (in the same way that (2:) can place the element 2 into a list)
-- (:?) instructs us how to do the unfolding. The new seed value appears as the right hand argument. If the structure can be unfolded in more than one direction (i.e. if one of your data constructors has more than two arguments) then you can stack the :?s to determine how the final structure is unfolded (see the Tree example later)
data X s c a where
X :: a -> X s c a
(:$) :: X s c (a -> b) -> a -> X s c b
(:?) :: X s c (c -> b) -> s -> X s c b
-- The unfolding function. Here s is the seed type, and c is the final type produced by the unfold.
unf :: forall s c . (s -> X s c c) -> s -> c
unf f = go . f
where
go :: X s c b -> b
go (X x) = x
go (x :$ a) = go x a
go (x :? s) = go x (unf f s)
-- Usage example.
dec4 :: Int -> [Int]
dec4 n = unf go n
where
go 0 = X []
go n = X (:) :$ n :? (n-1)
dec5 :: Int -> List Int
dec5 n = unf go n
where
go 0 = X Nil
go n = X Cons :$ n :? (n-1)
-- Tree unfolding
data Tree a = Null | Fork a (Tree a) (Tree a) deriving (Show)
tree n = unf go n
where
go 0 = X Null
go n = X Fork :$ n :? (n-1) :? (n-1)
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment