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!