Recursive liftIO - haskell

I've looked at the some instances of MonadTrans, for MaybeT the implementation looks like this:
instance MonadTrans MaybeT where
lift = MaybeT . liftM Just
As I understand the instance for MonadIO is used to do a variable number of lifts from the inner most, a IO monad, directly to the outermost. For the MaybeT case it looks like this:
instance (MonadIO m) => MonadIO (MaybeT m) where
liftIO = lift . liftIO
What I don't understand is how this recursive function escapes the infinite loop. What is the base case?

Perhaps surprisingly, the definition below is not recursive, even if it looks such.
instance (MonadIO m) => MonadIO (MaybeT m) where
liftIO = lift . liftIO
This is because the liftIO on the left hand side is the liftIO for the MaybeT m monad, while the liftIO on the right hand side is the liftIO for the m monad.
Hence, this simply defines liftIO in one monad in terms of the liftIO for another monad. No recursion here.
This is similar to e.g.
instance (Show a, Show b) => Show (a,b) where
show (x,y) = "(" ++ show x ++ ", " ++ show y ++ ")"
Above, we define how to print a pair depending on how to print their components. It looks recursive, but it is not really such.
It could help visualizing this by inserting explicit type arguments, at least mentally:
-- pseudo-code
instance (Show a, Show b) => Show (a,b) where
show #(a,b) (x,y) =
"(" ++ show #a x ++ ", " ++ show #b y ++ ")"
Now show #(a,b), show #a, and show #b are distinct functions.

Simple equational reasoning and rewriting definitions for some specialization can help you. Base case for MonadIO is IO. MaybeT is monad transformer, so lets combine MaybeT and IO in some simple example.
foo :: MaybeT IO String
foo = liftIO getLine
Now let's rewrite this function definition applying instance implementations from your question step by step.
foo
= liftIO {- for MaybeT -} getLine
= lift (liftIO {- for IO here -} getLine) -- step 2
= lift (id getLine)
= lift getLine
= MaybeT (liftM Just getLine)
getLine has type IO String
liftM Just getLine has type IO (Maybe String)
MaybeT m a constructor needs value of type m (Maybe a) where m = IO and a = String in our case.
Probably hardest step to analyze is step 2. But in reality it's very easy if you remind yourself types of liftIO :: IO a -> m a and lift :: Monad m => m a -> t m a. So all work is done by type inference.

Related

Can some one explain how to use lift in haskell?

I try to understand the lifting principle by example, and found this:
https://github.com/graninas/Functional-Design-and-Architecture/blob/1736abc16d3e4917fc466010dcc182746af2fd0e/First-Edition/BookSamples/CH03/MonadStack.hs
Then, if I change it's lift (lift (putStrLn "bla-bla")) to putStrLn "bla-bla", the compiler throw error!
I do this base on my understanding: do block are just syntax sugar, and each line's result are pass into next line. If the next line do not use the args that passed from previous line, the type of args won't cause type confliction, I think.
Take bellow as example, while x<- getLine can past compiling
test:: IO ()
test = do
x <- getLine -- discarded and compiler don't care it type
let a = "bla-bla" -- discarded and compiler don't care it type
putStrLn $ "You type are discarded: "
Now back to the calculations function:
type Data = Map.Map Int String
type StateIO = StateT Data IO
type MaybeStateIO a = MaybeT StateIO a
calculations :: MaybeStateIO ()
calculations = do
lift (lift (putStrLn "bla-bla")) -- if I change this to `putStrLn "bla-bla"`, it failed compiling.
lift (modify (Map.insert 3 "3"))
lift (modify (Map.insert 1 "1"))
mb <- lift (get >>= (return . Map.lookup 1))
lift (lift (print mb))
main = runStateT (runMaybeT calculations) Map.empty
I don't understand is that to compiler require lifting on putStrLn "bla-bla".
Isn't it enough when return value of the last line of do block match the function's return value?
In this example, how does the compiler decide the do block's value type? according to function's signature?
Can anyone explains the lift for me? How do it work, when to use, etc.
Isn't it enough when return value of the last line of do block match the function's return value?
No, since that would mean that you could write a do block where the first item for example would use the instance of [] for Monad whereas the next would use for example Maybe or IO, but then how would x <- some_list make sense for a list of putStrLn x? All lines in the do block should be of type m a with m the same instance of Monad, and the as can have different types for each line. If you write a do block with:
foo = do
x <- exp1
exp2
then this is translated to exp1 >>= \x -> exp2, and since (>>=) :: Monad m => m a -> (a -> m b) -> m b operates where the two operands share the same monad m, this thus means that exp1 :: m a and exp2 :: m b thus need to work with the same monadic type m.
You require to perform lifting twice since the line should have as type MaybeT (StateT Data IO) a whereas putStrLn "bla-bla" has IO a, it thus requires one lift :: (MonadTrans t, Monad m) => m a -> t m a to lift it to StateT Data IO a and another to finally lift it to a MaybeT (StateT Data IO) a.
The value of calculations is a MaybeStateIO value. That's the monad you are operating in, so that's what every line of the do block has to produce. But putStrLn "bla-bla" does not produce a MaybeStateIO value; it just produces an IO value. The first lift takes that IO value and returns a StateIO value; the second lift takes that StateIO value and returns a MaybeStateIO value.
Remember,
do
a
b
is just syntactic sugar for a >> b, and (>>) :: Monad m => m a -> m b -> m b needs values from the same monad as arguments. It's only the "return value" (a and b) of the monad that can vary from line to line; the monad m itself is fixed.

Using Logic monad to backtrack upon exception thrown with ExceptT

I'd like to use the Logic monad to ensure that error-throwing code (in a monad stack including ExcepT) backtracks upon throwing an error. Here's a simple example:
newtype FooT m a = FooT { unFooT :: ExceptT String m a }
deriving (Functor, Applicative, Monad, MonadTrans, MonadError String, MonadFail)
foo :: FooT Logic String
foo = do
let validate s = if s == "cf" then return s else throwError "err"
let go = do
first <- msum (map return ['a', 'b', 'c'])
second <- msum (map return ['d', 'e', 'f'])
traceM $ "Guess: " ++ [first, second]
validate [first, second]
go `catchError` const mzero
testfoo :: IO ()
testfoo = do
let r = observe $ runExceptT $ unFooT foo
case r of
Left e -> print $ "Error: " ++ e
Right s -> print $ "Result: " ++
This doesn't backtrack; it produces no results.
I can make it backtrack by lifting the choice operations (ie, use lift (msum ...) instead of the plain msum call there is now).
However, for a variety of reasons I'd like to be able to write code in the ExceptT monad and basically just lift the MonadPlus instance from the Logic monad into the transformed version.
I tried to write a custom MonadPlus instance to accomplish this here:
instance MonadPlus m => MonadPlus (FooT m) where
mzero = lift mzero
mplus (FooT a) (FooT b) = lift $ do
ea <- runExceptT a
case ea of
Left _ -> do
eb <- runExceptT b
case eb of
Left _ -> mzero
Right y -> return y
Right x -> do
eb <- runExceptT b
case eb of
Left _ -> return x
Right y -> return x `mplus` return y
The same code works for the Alternative instance as well. However, this doesn't actually help; it still doesn't backtrack. Is there something wrong with this instance? Is there a better way to solve this problem? Am I trying to do something that doesn't make sense? At the end of the day I can always just lift everything, but would prefer to avoid doing so.
Edit:
Have been messing around some more. My MonadPlus instance above works if I use mplus but does not work if I use msum like I did above...
Use this instance of MonadPlus/Alternative:
instance (Alternative m, Monad m) => Alternative (FooT m) where
empty = FooT (ExceptT empty)
FooT (ExceptT a) <|> FooT (ExceptT b) = FooT (ExceptT (a <|> b))
Note: Alternative and MonadPlus are redundant, so it's simpler to just implement Alternative, and use Data.Foldable.asum instead of msum.
The one you implemented is not too different from the one that's already on ExceptT, and does not really use the Alternative m instance. Make sure to use (<|>) specialized to m to benefit from backtracking.

Understanding the MonadIO Laws

From source:
module Control.Monad.IO.Class (
MonadIO(..)
) where
-- | Monads in which 'IO' computations may be embedded.
-- Any monad built by applying a sequence of monad transformers to the
-- 'IO' monad will be an instance of this class.
--
-- Instances should satisfy the following laws, which state that 'liftIO'
-- is a transformer of monads:
--
-- * #'liftIO' . 'return' = 'return'#
--
-- * #'liftIO' (m >>= f) = 'liftIO' m >>= ('liftIO' . f)#
class (Monad m) => MonadIO m where
-- | Lift a computation from the 'IO' monad.
liftIO :: IO a -> m a
instance MonadIO IO where
liftIO = id
What is meant by
liftIO (m >>= f) = liftIO m >>= (liftIO . f)
And in particular, what is meant by (m >>= f)? Here m is a function on types and f a function on values. So isn't that notation non-sense?
As noted in the comments, the m in the law is just a value variable, and is not the same m as the type variable m used in the class definition.
If you rewrite the law as:
liftIO (act >>= f) = liftIO act >>= (liftIO . f)
equivalent to:
liftIO $ do x <- act === do x <- liftIO act
f x liftIO (f x)
with the understanding that act is an IO action, then it may be clearer what's going on. The expression act >>= f represents the composite IO action that, when run, will run the IO action act and pass its return value to f to generate a new IO action (say act2) that will then be run.
The law just says that lifting this composite IO action into a different monad creates an action that, when run, is equivalent running a lifted version of act, passing its return value to f to generate a new IO action, lifting that action to the other monad, and running that.
As a concrete example, getLine >>= print is the IO action that reads a line and then prints its value in Haskell string syntax. The law says that you can either lift this directly into another monad:
liftIO $ do x <- getLine
print x
to get an action that does that, or you can lift the IO action parts separately:
do x <- liftIO getLine
liftIO (print x)
and get exactly the same action.

Working with Maybe a, IO a, and MaybeT IO a

I'm writing a prompt - response style system with a bunch of various combinations of Maybe a, IO a, and MaybeT IO a, and there is a lof of stuff to take into account. Some IO actions for which there is no invalid input (and therefore aren't wrapped in MaybeT), some which are (and return an MaybeT IO a) some which aren't IO actions but can fail, so return Maybe a, and some that are just plain values and its beginning to seem that I have to remember inordinate combinations of <$>, Just, fmap, MaybeT, lift, =<<, and return just to get everything to be the right type. Is there any easier way to manage this or to reason about what functions I need to use to get my values where I need them? Or do I just have to hope I get better at it with time? Here is my example:
getPiece :: Player -> Board -> MaybeT IO Piece
getPiece player#(Player pieces _ _ _) board = piece
where
promptString = displayToUserForPlayer player board ++ "\n" ++ (display player) ++ "\n" ++ "Enter piece number: "
input :: MaybeT IO String
input = lift $ prompt promptString
index :: MaybeT IO Int
index = MaybeT <$> return <$> ((fmap cvtFrom1indexedInt) . maybeRead) =<< input
piece :: MaybeT IO Piece
piece = MaybeT <$> return <$> maybeIndex pieces =<< index
getRotatedPiece :: Player -> Board -> MaybeT IO Piece
getRotatedPiece player#(Player pieces _ _ _) board = piece
where
promptString :: MaybeT IO String
promptString = (++) <$> displayListString <*> restOfString
input :: MaybeT IO String
input = MaybeT <$> (fmap Just) <$> prompt =<< promptString
index :: MaybeT IO Int
index = MaybeT <$> return <$> ((fmap cvtFrom1indexedInt) . maybeRead) =<< input
piece :: MaybeT IO Piece
piece = MaybeT <$> return <$> maybeIndex pieces =<< index
rotatedPieceList :: MaybeT IO [Piece]
rotatedPieceList = rotations <$> getPiece player board
displayListString :: MaybeT IO String
displayListString = displayNumberedList <$> rotatedPieceList
restOfString :: MaybeT IO String
restOfString = MaybeT <$> return <$> Just $ "\nEnter rotation number:"
I must say, I am disappointed at the lack of conciseness, even if I removed the type hints I could likely write a shorter function to do the same thing in C# or python
Since you provided only a code fragment, I cannot try to refactor it. However, this is what I'd do: Most monads have a corresponding type class. The reason for it is exactly what you need here: When you create a monad using a monad transformer, it will inherit the operations of the inner monads (if appropriate). So you can forget about the inner monads and work just within the final monad.
In your case, you have MaybeT IO. It's instance of MonadPlus and of MonadIO. So you can refactor the code that returns Maybe something to work with a general MonadPlus instance instead, just replace Just with return and Nothing with mzero. Like:
-- before
checkNumber :: Int -> Maybe Int
checkNumber x | x > 0 = Just x
| otherwise = Nothing x
-- after
checkNumber :: MonadPlus m => Int -> m Int
checkNumber x | x > 0 = return x
| otherwise = mzero
-- or just: checkNumber = mfilter (> 0) . return
It will work with any MonadPlus, including Maybe and MaybeT IO.
And you can refactor the code that returns IO something to work with a general MonadIO instance:
-- before
doSomeIO :: IO ()
doSomeIO = getLine >>= putStrLn
-- after
doSomeIO :: MonadIO m => m ()
doSomeIO = liftIO $ getLine >>= putStrLn
This way, you can forget about <$>/fmap/liftM, Just, MaybeT etc. You just use return, mzero and in some places liftIO.
This will also help you to create a more general code. If you later realize that you need to add something to the monad stack, the existing code won't break, as long as the new monad stack implements the same type classes.
A less ambitious answer from me. Looking at your code, your operations like getPiece don't really return any information from the a particular error site. You can probably get away with just using IO and turning exceptions into Maybe values if you really want those. Some sample code I put together with some undefined functions referenced in your code:
import Control.Exception (handle, IOException)
data Board = Board deriving (Show)
data Piece = Piece deriving (Show)
type Pieces = [Piece]
data Player = Player Pieces () () () deriving (Show)
prompt :: String -> IO String
prompt = undefined
cvtFrom1indexedInt :: Int -> Int
cvtFrom1indexedInt = undefined
maybeIndex :: Pieces -> Int -> Maybe Piece
maybeIndex = undefined
displayToUserForPlayer :: Player -> Board -> String
displayToUserForPlayer = undefined
display :: Player -> String
display = undefined
-- I used this when testing, to deal with the Prelude.undefined errors
--returnSilently :: SomeException -> IO (Maybe a)
returnSilently :: IOException -> IO (Maybe a)
returnSilently e = return Nothing
getPiece :: Player -> Board -> IO (Maybe Piece)
getPiece player#(Player pieces _ _ _) board = handle returnSilently $ do
let promptString = displayToUserForPlayer player board ++ "\n" ++ (display player) ++ "\n" ++ "Enter piece number: "
input <- prompt promptString
let index = cvtFrom1indexedInt (read input)
return (maybeIndex pieces index)
main = do
maybePiece <- getPiece (Player [] () () ()) Board
putStrLn ("Got piece: " ++ show maybePiece)
Notably I've moved from MaybeT IO Piece to just IO (Maybe Piece). Instead of using fmap or lift I've just used do notation for referring to the intermediate results of my IO action.
Going on your comments about C# or Python, I hope this was the sort of simpler answer you were looking for.

How do I combine monads in Haskell?

Particularly, I need to be able to combine the CGI monad with the IO monad, but an example of how to combine the IO monad with the Maybe monad might be even better...
I assume you want to use the Maybe monad for early termination (like break or return in C).
In that case you should use MaybeT from the MaybeT package (cabal install MaybeT).
main = do
runMaybeT . forever $ do
liftIO $ putStrLn "I won't stop until you type pretty please"
line <- liftIO getLine
when ("pretty please" == line) mzero
return ()
MaybeT is a monad transformer version of the maybe monad.
Monad transformers "add functionality" to other monads.
You don't exactly say how you want to combine IO and Maybe, but I assume you have many functions that return IO (Maybe a) that you want to combine easily. Basically you want to treat IO (Maybe a) as a separate type with it's own Monad instance:
newtype IOMaybe a = IOM (IO (Maybe a))
-- "unpack" a value of the new type
runIOMaybe :: IOMaybe a -> IO (Maybe a)
runIOMaybe (IOM a) = a
instance Monad IOMaybe where
-- bind operator
(IOM ioa) >>= f = IOM $ do
a <- ioa
case a of
Nothing -> return Nothing
Just v -> runIOMaybe (f v)
-- return
return a = IOM (return (Just a))
-- maybe also some convenience functions
returnIO :: IO a -> IOMaybe a
returnIO ioa = IOM $ do
v <- ioa
return (Just v)
returnMaybe :: Maybe a -> IOMaybe a
returnMaybe ma = IOM (return ma)
With this you can use the do-Notation to combine functions that return IO (Maybe a), IO a or Maybe a:
f1 :: Int -> IO (Maybe Int)
f1 0 = return Nothing
f1 a = return (Just a)
main = runIOMaybe $ do
returnIO $ putStrLn "Hello"
a <- returnMaybe $ Just 2
IOM $ f1 a
return ()
Generally something that combines and modifies monads like this is called a monad transformer, and GHC comes with a package that includes monad transformers for common cases. If there is something in this monad transformer library that fits your scenario depends on how exactly you want to combine Maybe and IO.
In what sense do you want to combine the monads?
f :: Int -> IO (Maybe Int)
f x = do
putStrLn "Hello world!"
return $ if x == 0 then Nothing else Just x
Can be evaluated to:
[1 of 1] Compiling Main ( maybe-io.hs, interpreted )
Ok, modules loaded: Main.
*Main> f 0
Hello world!
Nothing
*Main> f 3
Hello world!
Just 3

Resources