Re: [Haskell-cafe] Inverting a Monad

2008-02-09 Thread Bas van Dijk
On Feb 7, 2008 4:58 AM, David Menendez <[EMAIL PROTECTED]> wrote: > If you're doing any kind of backtracking or non-determinism, you might > consider the msplit operation defined in "Backtracking, Interleaving, > and Terminating Monad Transformers" >

Re: [Haskell-cafe] Inverting a Monad

2008-02-06 Thread David Menendez
On Feb 6, 2008 6:32 AM, Bas van Dijk <[EMAIL PROTECTED]> wrote: > Is there a way to 'invert' an arbitrary Monad? > > By 'inverting' I mean to turn success into failure and failure into > success. Here are some specific inversions of the Maybe and List > Monad: > > invM :: Maybe a -> Maybe () > invM

Re: [Haskell-cafe] Inverting a Monad

2008-02-06 Thread ajb
G'day all. On Feb 6, 2008 12:45 PM, Felipe Lessa <[EMAIL PROTECTED]> wrote: I guess your parser is a monad transformer, so *maybe* the solution is to require MonadError from the inner monad. Quoting Bas van Dijk <[EMAIL PROTECTED]>: Indeed my parser 'P t m a' is a monad transformer. I wil

Re: [Haskell-cafe] Inverting a Monad

2008-02-06 Thread Bas van Dijk
On Feb 6, 2008 8:27 PM, Tillmann Rendel <[EMAIL PROTECTED]> wrote: > What about this? > > inv :: MonadError e m => m a -> m () > inv m = join $ (m >> return mzero) `catchError` \_ -> return (return ()) Beautiful! That's the one I'm looking for! I was already defining a 'MonadInvert' class and a

Re: [Haskell-cafe] Inverting a Monad

2008-02-06 Thread Tillmann Rendel
Bas van Dijk wrote: The following obviously doesn't work: import Control.Monad.Error inv :: MonadError e m => m a -> m () inv m = (m >> fail "") `catchError` \_ -> (return ()) What about this? inv :: MonadError e m => m a -> m () inv m = join $ (m >> return mzero) `catchError` \_ -> return (

Re: [Haskell-cafe] Inverting a Monad

2008-02-06 Thread Bas van Dijk
On Feb 6, 2008 12:51 PM, Bas van Dijk <[EMAIL PROTECTED]> wrote: > I will try out requiring 'm' to have a 'MonadError' constraint and see how > far I come > with that. I'm now trying to define 'inv' using 'catchError` but I can't get it to work. The following obviously doesn't work: import Cont

Re: [Haskell-cafe] Inverting a Monad

2008-02-06 Thread Bas van Dijk
On Feb 6, 2008 1:49 PM, Lutz Donnerhacke <[EMAIL PROTECTED]> wrote: > inv m = if m == mzero then return () else mzero `asTypeOf` m Interesting! > :t inv inv :: (MonadPlus m, Eq (m ())) => m () -> m () The 'Eq' constraint on 'm ()' is a bit problemetic I think in case 'm' is a function like a 'S

Re: [Haskell-cafe] Inverting a Monad

2008-02-06 Thread Lutz Donnerhacke
* Felipe Lessa wrote: > Prelude Control.Monad> inv [] > [()] > Prelude Control.Monad> inv [10] > [()] inv m = if m == mzero then return () else mzero `asTypeOf` m Yes, unfair. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.or

Re: [Haskell-cafe] Inverting a Monad

2008-02-06 Thread Felipe Lessa
On Feb 6, 2008 10:04 AM, Luke Palmer <[EMAIL PROTECTED]> wrote: > How about: > > inv m = do > success <- (m >> return True) `mplus` return False > if success then mzero else return () Prelude Control.Monad> inv [] [()] Prelude Control.Monad> inv [10] [()] -- Felipe. ___

Re: [Haskell-cafe] Inverting a Monad

2008-02-06 Thread Luke Palmer
On Feb 6, 2008 11:32 AM, Bas van Dijk <[EMAIL PROTECTED]> wrote: > The following obviously doesn't work: > > inv m = (m >> mzero) `mplus` return () > > because it will always return (). How about: inv m = do success <- (m >> return True) `mplus` return False if success then mzero else r

Re: [Haskell-cafe] Inverting a Monad

2008-02-06 Thread Bas van Dijk
On Feb 6, 2008 12:50 PM, Miguel Mitrofanov <[EMAIL PROTECTED]> wrote: > class Monad m => MonadInv m where inv :: m a -> m () > > With this constraint you certainly can have your "inv". Yes indeed. But I was kind of hoping that I could use standard Haskell classes without adding my own. (BTW I wou

Re: [Haskell-cafe] Inverting a Monad

2008-02-06 Thread Bas van Dijk
On Feb 6, 2008 12:45 PM, Felipe Lessa <[EMAIL PROTECTED]> wrote: > I guess your parser is a monad transformer, so *maybe* the solution is to > require > MonadError from the inner monad. Indeed my parser 'P t m a' is a monad transformer. I will try out requiring 'm' to have a 'MonadError' constrai

Re: [Haskell-cafe] Inverting a Monad

2008-02-06 Thread Miguel Mitrofanov
Such as Identity? Well in: inv :: (Monad m, ...) => m a -> m () inv m = ... I don't mind that there are more constraints on 'm' than just Monad class Monad m => MonadInv m where inv :: m a -> m () With this constraint you certainly can have your "inv". _

Re: [Haskell-cafe] Inverting a Monad

2008-02-06 Thread Bas van Dijk
On Feb 6, 2008 12:39 PM, Miguel Mitrofanov <[EMAIL PROTECTED]> wrote: > > invM :: Maybe a -> Maybe () > > invM Nothing = Just () > > invM (Just _) = Nothing > > > > invL :: [] a -> [] () > > invL []= [()] > > invL (_:_) = [] > > > > > > How can I define this for an arbitrary Monad m? > > Such

Re: [Haskell-cafe] Inverting a Monad

2008-02-06 Thread Felipe Lessa
On Feb 6, 2008 9:39 AM, Miguel Mitrofanov <[EMAIL PROTECTED]> wrote: > > How can I define this for an arbitrary Monad m? > > Such as Identity? An arbirtrary monad can't be inverted, however there's Error and ErrorT that provide throwing and catching abilities. I guess your parser is a monad transf

Re: [Haskell-cafe] Inverting a Monad

2008-02-06 Thread Miguel Mitrofanov
invM :: Maybe a -> Maybe () invM Nothing = Just () invM (Just _) = Nothing invL :: [] a -> [] () invL []= [()] invL (_:_) = [] How can I define this for an arbitrary Monad m? Such as Identity? ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.

[Haskell-cafe] Inverting a Monad

2008-02-06 Thread Bas van Dijk
Hello, Is there a way to 'invert' an arbitrary Monad? By 'inverting' I mean to turn success into failure and failure into success. Here are some specific inversions of the Maybe and List Monad: invM :: Maybe a -> Maybe () invM Nothing = Just () invM (Just _) = Nothing invL :: [] a -> [] () inv