
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 -> [] () invL [] = [()] invL (_:_) = [] How can I define this for an arbitrary Monad m? More specifically, I would like to define: inv :: (Monad m, M.MonadPlus m, ???) => m a -> m () inv m = if m fails then return () if m succeeds then fail The following obviously doesn't work: inv m = (m >> mzero) `mplus` return () because it will always return (). There's also a 'inversion' for natural numbers: invN :: Int -> Int invN 0 = 1 invN n = 0 but how can I define that without pattern matching, so only using arithmetic operations, +, -, *, ^, ...? The reason I ask this is that I'm writing a parser combinator library to understand parser a bit better. And I would like to define the combinator: notFollowedBy :: P t m a -> P t m () 'notFollowedBy p' fails when p succeeds and returns () when p fails. I will share the code when it's a bit more polished. Thanks, Bas

On Feb 6, 2008 9:39 AM, Miguel Mitrofanov
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 transformer, so *maybe* the solution is to require MonadError from the inner monad. Cheers, -- Felipe.

On Feb 6, 2008 12:45 PM, Felipe Lessa
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' constraint and see how far I come with that. I'll let you know. Thanks, Bas

On Feb 6, 2008 12:51 PM, Bas van Dijk
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 Control.Monad.Error inv :: MonadError e m => m a -> m () inv m = (m >> fail "") `catchError` \_ -> (return ()) Bas

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 (return ()) Tillmann

On Feb 6, 2008 8:27 PM, Tillmann Rendel
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 bunch of instances like below but this is a much more flexible solution. ------------------------------------------------------------------------------------------------- -- | A Monad that supports inversion. -- Turning success into failure and failure into success. class Monad m => MonadInvert m where -- | @invert m@ fails when @m@ is successfull (returns a value) -- and returns @()@ when @m@ fails . invert :: m a -> m () instance MonadInvert Maybe where invert Nothing = Just () invert (Just _) = Nothing instance MonadInvert [] where invert [] = [()] invert (_:_) = [] instance E.Error e => MonadInvert (Either e) where invert (Left _) = Right () invert (Right _) = Left E.noMsg instance (E.Error e, MonadInvert m) => MonadInvert (E.ErrorT e m) where invert = T.lift . invert . E.runErrorT instance MonadInvert m => MonadInvert (S.StateT st m) where invert m = S.StateT $ \s -> (invert $ S.runStateT m s) >>= \u -> return (u, s) ... ------------------------------------------------------------------------------------------------- Thanks very much. Bas

G'day all.
On Feb 6, 2008 12:45 PM, Felipe Lessa
I guess your parser is a monad transformer, so *maybe* the solution is to require MonadError from the inner monad.
Quoting Bas van Dijk
Indeed my parser 'P t m a' is a monad transformer. I will try out requiring 'm' to have a 'MonadError' constraint and see how far I come with that.
I've occasionally found this useful: class (Monad m) => MonadNegate m where mtrue :: m () mfalse :: m () mnot :: m a -> m () mtrue = return () mfalse = fail "False" Cheers, Andrew Bromage

On Feb 6, 2008 12:39 PM, 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?
Well in: inv :: (Monad m, ...) => m a -> m () inv m = ... I don't mind that there are more constraints on 'm' than just Monad maybe a MonadPlus constraint or others are needed. (I was even thinking about a MonadTimes class as in: class MonadPlus m => MonadTimes m where mone :: m () mtimes :: m a -> m a -> m a ) Thanks, Bas

On Feb 6, 2008 12:50 PM, Miguel Mitrofanov
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 would like to know of other possible applications of 'inv' besides my parser. So yell if you find one please) Thanks, Bas

On Feb 6, 2008 1:49 PM, Lutz Donnerhacke
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 'State'. Thanks, Bas

On Feb 6, 2008 6:32 AM, Bas van Dijk
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 -> [] () invL [] = [()] invL (_:_) = []
How can I define this for an arbitrary Monad m?
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"
http://okmij.org/ftp/Computation/monads.html#LogicT.
Essentially, this defines a class of monads with zero, plus, and a
split operation:
class (MonadPlus m) => MonadSplit m where
msplit :: m a -> m (Maybe (a, m a))
Essentially, if 'm' returns no results, then 'msplit m' returns
Nothing, otherwise it returns Just (a, m'), where a is the first
result, and m' is a computation which produces the remaining results
(if any).
There is an obvious implementation for the list monad, but msplit can
also be defined for a monad transformer.
There are a bunch of useful operations using msplit, such as the "soft cut",
ifte :: (MonadSplit m) => m a -> (a -> m b) -> m b -> m b
ifte p th el = msplit p >>= maybe el (\(a,m) -> th a `mplus` (m >>= th))
'ifte p th el' is equivalent to 'p >>= th' if p returns any results,
and 'el' otherwise. Note that it is *not* the same as (p >>= th)
`mplus` el.
Here's your inverse operation:
mnot :: (MonadSplit m) => m a -> m ()
mnot m = msplit m >>= maybe (return ()) mzero
--
Dave Menendez

On Feb 7, 2008 4:58 AM, David Menendez
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" http://okmij.org/ftp/Computation/monads.html#LogicT.
Thanks for pointing me to this very interesting paper! Bas
participants (8)
-
ajb@spamcop.net
-
Bas van Dijk
-
David Menendez
-
Felipe Lessa
-
Luke Palmer
-
Lutz Donnerhacke
-
Miguel Mitrofanov
-
Tillmann Rendel