This is a literate haskell post. Simply save it as "ChurchList.lhs" to run it.
> {-# LANGUAGE Rank2Types #-}
A Church encoded list is a way of representing a list via a function. It resembles both folding and continuation passing style.
> newtype ChurchList a = CList {runCList :: forall r. (a -> r -> r) -> r -> r}
For illustration as to how this corresponds to a list, here is a O(n) isomorphism
> fromList :: [a] -> ChurchList a
> fromList xs = CList $ \cons empty -> foldr cons empty xs
> toList :: ChurchList a -> [a]
> toList cl = runCList cl (:) []
> instance Show a => Show (ChurchList a) where
> show cl = "fromList " ++ show (toList cl)
These things have good performance charecteristics.
> singleton :: a -> ChurchList a -- O(1)
> singleton a = CList $ \cons empty -> a `cons` empty
> append :: ChurchList a -> ChurchList a -> ChurchList a -- O(1)!!! This also means cons and snoc are O(1)
> append cl1 cl2 = CList $ \cons empty -> runCList cl1 cons (runCList cl2 cons empty)
> concatCl :: ChurchList (ChurchList a) -> ChurchList a -- O(n)
> concatCl clcl = CList $ \cons empty -> runCList clcl (\cl r -> runCList cl cons r) empty
> headCl :: ChurchList a -> Maybe a -- O(1)
> headCl cl = runCList cl (\a _ -> Just a) Nothing
Now, the problem comes with tail
.
> tailClbad :: ChurchList a -> Maybe (ChurchList a) --O(n)?!!
> tailClbad cl = (fmap snd) $ runCList cl
>
> (\a r -> Just (a, case r of
> Nothing -> CList $ \cons empty -> empty
> Just (s,t) -> append (singleton s) t)) --Cons
>
> Nothing --Empty
Essentially what my implementation does is split the list into head and tail. Cons replaces the head, and appends the old head unto the tail. This is rather inefficient. It seems that Church Lists are inefficient in general at splitting.
I'm hoping that I'm wrong. Is there an implementation of tailCl
that is better than O(n) (preferably O(1)).