[Haskell-cafe] Search monad
Jeff Polakow
jeff.polakow at db.com
Mon Mar 19 14:04:24 EDT 2007
Hello,
You might want to look at the scrap your boilerplate papers and/or their
implementation in GHC in Data.Generics.
-Jeff
haskell-cafe-bounces at haskell.org wrote on 03/19/2007 01:11:19 PM:
> Hey,
>
> I have a structure containing Xs in various places, like so
>
> data X
> data Structure = Structure .. [X] .. [X] ..
>
> And I defined mapStructure
>
> mapStructure :: (X -> X) -> (Structure -> Structure)
>
> I then wanted to use mapStructure to define queries as well as
> transformations on structures. I generalized mapStructure to
> mapStructureM:
>
> mapStructure :: Monad m => (X -> m X) -> (Structure -> m Structure)
>
> and then defined the following search monad:
>
> > data Search f a b = Found (f a) b
> >
> > class Monad (m a) => SearchMonad m a where
> > found :: a -> m a a
> >
> > fromSearch :: Search f a b -> f a
> > fromSearch (Found a _) = a
> >
> > search :: (SearchMonad m a) => (a -> Bool) -> a -> m a a
> > search f a
> > | f a = found a
> > | otherwise = return a
>
> Instances of the monad for finding one and for finding all elements:
>
> > instance SearchMonad (Search Maybe) a where
> > found a = Found (Just a) a
> >
> > instance SearchMonad (Search []) a where
> > found a = Found [a] a
> >
> > instance Monad (Search Maybe a) where
> > return b = Found Nothing b
> > Found (Just a) a' >>= f = case f a' of
> > Found _ b -> Found (Just a) b
> > Found Nothing a' >>= f = f a'
> >
> > instance Monad (Search [] a) where
> > return b = Found [] b
> > Found as a' >>= f = case f a' of
> > Found as' b -> Found (as ++ as') b
>
> Here is a simple sample session with ghci
>
> *Util> fromSearch $ mapM (search even) [1,3,5] :: Maybe Int
> Nothing
> *Util> fromSearch $ mapM (search even) [1,2,3,4,5] :: Maybe Int
> Just 2
> *Util> fromSearch $ mapM (search even) [1,2,3,4,5] :: [Int]
> [2,4]
>
> What I'm wondering about is if this monad is an instance of a more
> general monad(if so, which one?), and generally if people have any
> comments about these definitions.
>
> Thanks!
>
> Edsko
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
---
This e-mail may contain confidential and/or privileged information. If you
are not the intended recipient (or have received this e-mail in error)
please notify the sender immediately and destroy this e-mail. Any
unauthorized copying, disclosure or distribution of the material in this
e-mail is strictly forbidden.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20070319/ed57ec9a/attachment-0001.htm
More information about the Haskell-Cafe
mailing list