Why does "guard" differ from "if-then-else" behavior?

I have been recently trying to learn about transformers and following the example from: Haskell/Monad transformers - Wikibooks, open books for an open world

I’ve written a basic example:

module Main where

import System.Random (randomRIO)
import Control.Applicative
import Control.Monad (liftM, ap, guard, MonadPlus, mzero, mplus,)
import Formatting.ShortFormatters (x)

newtype MyLastBrainCells m a = MyLastBrainCells { idea:: m (Maybe a)}

instance Monad m => Applicative (MyLastBrainCells m) where
    pure = MyLastBrainCells . return . Just
    (<*>) = ap

instance Monad m => Functor (MyLastBrainCells m) where
    fmap = liftM

instance Monad m => Monad (MyLastBrainCells m) where
    x >>= f = MyLastBrainCells $ do val <- idea x
                                    case val of
                                        Nothing -> return Nothing
                                        Just v  -> idea $ f v
    return = pure

instance Monad m => Alternative (MyLastBrainCells m) where
    empty   = MyLastBrainCells $ return Nothing
    x <|> y = MyLastBrainCells $ do maybe_value <- idea x
                                    case maybe_value of
                                        Nothing    -> idea y
                                        Just _     -> return maybe_value

thinkAboutHaskell :: String -> IO (MyLastBrainCells IO String)
thinkAboutHaskell x = do
                        s <- randomRIO (1, 10::Int)
                        guard (s < 5)
                        return (pure x)

explain :: MyLastBrainCells IO String -> IO ()
explain m = do
                thought <- idea m
                case thought of
                    Nothing -> putStrLn "GAHH my braain."
                    Just x  -> putStrLn x

main :: IO ()
main = do
    thinkAboutHaskell "Haskell is such a hard language"
        >>= explain

There is a 50% chance that an alternative message pops up, however, it seems the triggering of guard check causes a:

haskell-playground.EXE: user error (mzero)

but if I switch the guard to an if-then-else statement, the error no longer occurs!

thinkAboutHaskell :: String -> IO (MyLastBrainCells IO String)
thinkAboutHaskell x = do
                        s <- randomRIO (1, 10::Int)
                        if s < 5 then
                            return empty
                        else
                            return (pure x)

Intended output:

GAHH my braain.

Is there a reason for this behavior? Based-off my readings for example: if statement - Guards vs. if-then-else vs. cases in Haskell - Stack Overflow

It seems that folks say that guard is equal to an if-then-else statement. There does not appear to be any type check issues either with the compiler working without errors. What could be causing the problem? I am using GHC 9.6.6, Cabal 3.10.3.0, and Stack 3.1.1 on Windows.

I have tried implementing MonadPlus as well as MonadTrans according to the tutorial but no change in behavior.

Thanks in advance!

The “guards” in that question refers to the .. | condition = ... notation. It does not refer to the Control.Monad.guard function.

The reason you’re seeing the error is that the implementation of guard for the IO monad throws an error if the guard condition is not satisfied.

2 Likes

Ah! That makes sense @jaror. The nested monads had me for a spin.

I think I was trying to trigger the guard from the Alternative defined for my custom data type. Is there a way to invoke that guard something like pure (guard x < 5) instead? Or would the if statement be my only way?

I think that should actually work

But you probably just want to write a MonadIO instance for your transformer instead. Then you could write your program like this:

thinkAboutHaskell :: String -> MyLastBrainCells IO String
thinkAboutHaskell x = do
                        s <- liftIO (randomRIO (1, 10::Int))
                        guard (s < 5)
                        return x

explain :: Maybe String -> IO ()
explain thought = do
                case thought of
                    Nothing -> putStrLn "GAHH my braain."
                    Just x  -> putStrLn x

main :: IO ()
main = do
    idea (thinkAboutHaskell "Haskell is such a hard language")
        >>= explain
1 Like

guard is a particular embedding of the Boolean values into any Alternative functor. There is also Control.Monad.when which in an imperative language corresponds to an if-then statement with an empty else {} branch. In contrast to guard, the when itself does not rely on empty and thus can not trigger IO errors.
Also note that in your original version, in the line guard (s < 5) the guard lives in the IO monad, not in your transformer.

ghci> guard False :: IO ()
*** Exception: user error (mzero)

Say you have implemented

randInt :: MyLastBrainCells IO Int
randInt = MyLastBrainCells $ fmap Just $ randomRIO (1, 10::Int)

then you can define

thinkAboutHaskell :: s -> MyLastBrainCells IO s
thinkAboutHaskell s = do
    i <- randInt
    when (i < 5) empty
    return s
-- equivalent: if i < 5 empty else return s

In your transformer, the empty is like exception throwing, only that the exception is not an IO exception but a Nothing. But it can abort computations just like you would expect in imperative code: Since your transformer obeys the left zero law empty >>= _ = empty, desugaring the do-notation one can see that despite the return s statement at the end of the do-block, the when can cause the function to return Nothing instead of the given message s.

EDIT: The two functions are related by

guard x = when (not x) empty
1 Like

Thank you everyone, quite interesting how one can architecture the code to avoid the error. Sounds like I had my monad scoping mixed up.

The approach @jaror suggested with liftIO and MonadIO implementation sounds useful and is interesting to me from a theory standpoint.

The approach @olf defines using the randInt function is also fascinating as I had not thought of it in that light.

I suppose in a real world application, one or the other may be more convenient depending on the use-case. Appreciate the response.

1 Like

The approaches are of course equivalent: randInt spells out what liftIO (randomRIO (1, 10::Int)) would amount to, given the appropriate MonadIO instance.

1 Like

I am having a huge woah moment here now that I’ve read into the liftIO monad. Perhaps folks here may know more info and put into words what I am realizing…

So if I am understanding how Monad transformation occurs, we could in theory have liftIO-like functions defined for each Monad in a stack by instancing them with a common Monad-like type. Then we can always map layers of Monads into a simplified form (assuming these Monads behave like MonadIO or something trivial.)

I am having trouble defining what “simplified” means here, but something about the intuition that we don’t lose any information that couldn’t have been captured using the equivalent Monad stack for a given data type.

I also assume that MonadIO-like is something like a Monad that does not interact with other Monads (e.g. independent) and probably adheres to MonadIO’s instances.

For example, assume we have MonadA, MonadB, and MonadC each defined with instances with their own lift variant such that:

  • MonadA has liftA, liftB, liftC defined.
  • MonadB has liftB, liftC defined,
  • MonadC has liftC defined

Then the following Monad types defined are equivalent (and infinitely more):

  • [A, B, C]
  • [A, B, A, B, C, C]
  • [C, C, A, B, A, B, C]

As long as A, B, C appears as the base ordering, then lifting can always guarantee the same result. Subsequently, the Monad stack [C, A, B] does not equal in this case as the Monads are not in the right base order.

Am I onto some property of Monads or am I overthinking this? :thinking:

What do you mean with the notation [A,B,C]? Do you mean A (B (C Identity))?

Yes, I believe so. The Identity in this case I assume is implied.

Not necessary. Monad transformer machinery consists of two separate packages and concepts. There is the transformers package defining the concrete transformer data types, like your MyLastBrainCells is one. As you correctly observed, in order to use the functionality of transformer B buried beneath a layer A, the outer transformer A must provide a liftB function.
But that quickly becomes unwieldy. Therefore the mtl package provides for each transformer T a MonadT class, whose primary purpose is to automatically select the correct chain of liftB functions to bubble the B functionality through an arbitrarily thick layer of other transformers to the surface. The instances to lift B through A is therefore of the form

instance MonadB m => MonadB (A m) where
    methodB = ... liftB ...

The MonadIO class does the same for IO actions: While the transformer A is itself not capable of doing IO, it should know how to hand this capability one layer up.

A drawback of this concept is that, when you want a number of N monad transformers to play nicely together, you must define up to N² lift functions. Luckily many can be implemented using more generic lift functions, but the combinatorical explosion is there.