Skip to content

Instantly share code, notes, and snippets.

@gallais
Last active August 29, 2015 14:11
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 gallais/ef7330d74161c46a401b to your computer and use it in GitHub Desktop.
Save gallais/ef7330d74161c46a401b to your computer and use it in GitHub Desktop.
Split for lists
{-# LANGUAGE RankNTypes #-}
module List where
import Data.Monoid
newtype List a = Abstr {
apply :: forall z . (Monoid z) => (a -> z) -> z
}
nil :: List a
nil = Abstr (\f -> mempty)
cons :: a -> List a -> List a
cons x (Abstr app) = Abstr (\f -> mappend (f x) (app f))
append :: List a -> List a -> List a
append (Abstr xs) (Abstr ys) = Abstr (\ f -> xs f <> ys f)
newtype Split a = Split { outSplit :: Maybe (a, List a) }
deriving Show
instance Monoid (Split a) where
mempty = Split Nothing
mappend (Split Nothing) (Split nns) = Split nns
mappend (Split mms) (Split Nothing) = Split mms
mappend (Split (Just (m, ms))) (Split (Just (n, ns))) =
Split $ Just (m, append ms (cons n ns))
split :: List a -> Split a
split xs = apply xs $ \ a -> Split $ Just (a, nil)
head :: List a -> Maybe a
head = fmap fst . outSplit . split
tail :: List a -> Maybe (List a)
tail = fmap snd . outSplit . split
instance Show a => Show (List a) where
show xs = show $ apply xs (:[])
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment