[Haskell-cafe] Re: Is my code too complicated?
Ertugrul Soeylemez
es at ertes.de
Mon Jul 5 06:30:09 EDT 2010
Stephen Tetley <stephen.tetley at gmail.com> wrote:
> On 5 July 2010 10:39, Yves Parès <limestrael at gmail.com> wrote:
>
> > Then what is your alternative? How do you replace monad
> > transformers?
>
> Possibly more a case of doing without rather than replacing them with
> something else, you would amalgamate all the monadic effects you want
> into one monad.
>
> E.g. State and Environment (reader) and partiality (Maybe)
>
> newtype Amalgamated s e a = Amalgamated { getAmalgamated :: e -> s ->
> (Maybe a,st) }
>
> instance Monad (Amalgamated s e) where
> return a = Amalgamated $ \e s -> return (Just a, st)
> m >>= k = Amalgamated $ \e s -- TODO (after the first coffee of the
> morning...)
That's what monad transformers are good for. Why reinvent the wheel?
type Amalgamated s e m = MaybeT (StateT s (ReaderT e m))
This is all you need to create your own monad with the specified
functionality.
testComp :: Amalgamated Int Bool IO ()
testComp = do
x <- return (Just 3)
y <- ask
z0 <- get
when y $ sets_ (+1)
z1 <- get
inBase $ print (x, y, z0, z1)
However, MaybeT as defined in the 'MaybeT' package will probably not
work here. But this is not a transformer-related problem, just
compatibility.
Greets,
Ertugrul
--
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/
More information about the Haskell-Cafe
mailing list