[Haskell-cafe] instance Monad AppF - Faster than the list monad?
Donald Bruce Stewart
dons at cse.unsw.edu.au
Fri May 25 23:45:01 EDT 2007
greenrd:
> The following Haskell 98 module implements a generalisation of
> Prelude.ShowS for any type. Should be pretty easy to incorporate this
> into code which currently uses the list monad non-trivially, and get
> better performance - but can this be right? Surely someone would have
> published this before if that was true? I haven't actually done any
> performance tests. Anyway, with this module you end up using function
> composition instead of list concatenation - except when converting from
> a list.
>
> module Data.List.AppF where
>
> import Control.Monad (MonadPlus (mplus, mzero), msum)
>
> -- Generalisation of ShowS
> newtype AppF a = AppF { unAppF :: [a] -> [a] }
>
> instance Monad AppF where
> (>>=) = (msum .) . flip map . appFToList
> return = AppF . (:)
>
> instance MonadPlus AppF where
> mzero = AppF id
> mplus x y = AppF $ unAppF x . unAppF y
>
> -- Use this to convert Maybe a into AppF a, or indeed any other
> -- MonadPlus instance.
> maybeToMonadPlus :: MonadPlus m => Maybe a -> m a
> maybeToMonadPlus = maybe mzero return
>
> listToAppF :: [a] -> AppF a
> listToAppF = AppF . (++)
>
> appFToList :: AppF a -> [a]
> appFToList = ($ []) . unAppF
Very nice! Perhaps stick it on the wiki, or send it as a patch to the
dlist library?
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/dlist-0.2
I'd be happy to package it in that.
-- Don
More information about the Haskell-Cafe
mailing list