Taral wrote:
On 1/17/06, Keean Schupke <[EMAIL PROTECTED]> wrote:
Just made a few modifications and thought it might be useful to
people. I have rewritten the functions as
"liftR" and "bracketR" over a "MonadIO" monad interface (allowing
monad-transformers to be used).
I'm sorry, but what is "Lib.Monad.MonadT"? How does up3 work? MonadIO
exists in Control.Monad.Trans.
It didnt when I wrote the MonadIO stuff that I use! Here is the missing
file ... I tried to put it all in
one, but missed the use of up3. (see attached)
Regards,
Keean.
{-# OPTIONS -fglasgow-exts -fallow-undecidable-instances -fallow-overlapping-instances #-}
-- parser.hs: Copyright (C)2001,2002 Keean Schupke.
--
-- Polymorphic monadic consumer based parser.
module Lib.Monad.MonadT where
import Control.Monad hiding (guard)
------------------------------------------------------------------------------
class Runnable m n where
run :: m -> n
instance Runnable (m a) (m a) where
run = id
instance Runnable (s -> m a) (s -> m a) where
run = id
class (Monad m,Monad (t m)) => MonadT t m where
up :: m a -> t m a
up1 :: (m a -> m a) -> t m a -> t m a
up2 :: (m a -> (b -> m a) -> m a) -> t m a -> (b -> t m a) -> t m a
up3 :: (m a -> (a -> m b) -> (a -> m c) -> m c) -> t m a -> (a -> t m b) -> (a -> t m c) -> t m c
down :: t m a -> m a
up1 = undefined
up2 = undefined
up3 = undefined
-- instance (Monad m,Monad n,MonadT t m,Runnable (m a) (n a)) => Runnable (t m a) (n a) where
-- run = run . down
instance (Monad m,MonadT t m,Monad (t m)) => Runnable (t m a) (m a) where
run = down
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe