How to nest Parser (IO a) while avoiding unsafePerformIO? - haskell

While playing around with parsing based on text-icu's BreakIterator, I've got stuck on implementing a function like this
conditionalParser :: (a -> Bool) -> Parser a -> Parser a -> Parser a -> Parser a
conditionalParser f a b c = do
a' <- a
if f a'
then b
else c
but with a type
conditionalParserIO :: (a -> Bool) -> Parser (IO a) -> Parser (IO a) -> Parser (IO a) -> Parser (IO a)
Is it possible without doing unsafePerformIO?
So far I could only get to some nested dos with the final returned type being Parser (IO (Parser (IO a))), but without any idea how to collapse them.

I think what you want is to use ParsecT instead of Parser.
conditionalParserM :: Monad m => (a -> Bool) -> ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
conditionalParserM f a b c = do
a' <- a
if f a' then b else c
This function works with all types of Monads, not just IO.
I suppose it's possible to convert from a ParsecT s u IO a to a Parser (IO a) using runParsecT, depending on which Parser (this or this?) you're using. However, I would recommend that you just restructure your code to work with ParsecT instead.
Clarification
conditionalParserM can't be used as a replacement for conditionalParserIO. I'm suggesting that you need to change how your program works, because attempting to do what your doing (without unsafePerformIO, which you should almost never use) is impossible.
You're looking to compose parsers based on the result of an IO operation, which means that the parser itself will perform side effects when it is run. In order to encapsulate this in the type, you need to use a monad transformer instead.
So, to use conditionalParserM, you need to restructure your code to work with ParsecT instead of Parser.

I just wanted to comment on the difference between Parsec s u (IO a) and ParsecT s u IO a.
You correctly observed that trying to implement your function using Parsec (IO a) yields to Parser (IO (Parser (IO a)). Since both Parser and IO are monads, for both of them we have join :: m (m a) -> m a, which allows to collapse double Parser or double IO. However, in our results we have IO and Parser interleaved. What we need is some function of type IO (Parser a) -> Parser (IO a). If we had such a function f and some x :: Parser (IO (Parser (IO a)), we could use it as liftM f x :: Parser (Parser (IO (IO a))) and then use join and liftM join to collapse both parts into desired Parser (IO a).
Unfortunately there is no such general function for swapping two monads. It's not possible to construct such a function without knowing the internals of a monad, and for some monads it's not even possible at all. For example, there is no total function of type (a -> Maybe b) -> Maybe (a -> b) (the first monad being Maybe, the second one the reader monad (->) a).
And this is why we have monad transformers. A monad transformer corresponding to some monad M knows how to interleave M with another monad. For some monads, such as Reader, swapping it with another monad in the above manner is possible and its transformer is doing exactly that. ReaderT r m a is defined as r -> m a and we can construct:
import Control.Monad
import Control.Monad.Trans
import Control.Monad.Trans.Reader
swapReader :: (Monad m) => m (Reader r a) -> Reader r (m a)
swapReader = fromReaderT . join . lift . liftM (toReaderT . liftM return)
where
-- Helpers to convert ReaderT to Reader and back
fromReaderT :: (Monad m) => ReaderT r m a -> Reader r (m a)
fromReaderT = reader . runReaderT
toReaderT :: (Monad m) => Reader r (m a) -> ReaderT r m a
toReaderT = ReaderT . runReader
We convert m (Reader r a) into ReaderT r m (ReaderT r m a) by augmenting both the inner and outer part and then just collapse it using join.
For other monads, such as MaybeT, swapping is impossible (as in the example above with the (->) a monad). So their transformers are defined differently, for example MaybeT m a is defined as m (Maybe a), not Maybe (m a). Therefore ReaderT r Maybe a is isomorphic MaybeT (ReaderT r) a! There is just one sensible way how to combine Reader and Maybe and so both transformers result in the same thing.
Luckily, we don't have to care about this stuff, once somebody defines a transformer for us.
All we need to know is that the laws hold and how to run the transformer stack at the end.
So using ParsecT s u IO a is the proper solution. ParsecT knows how to interleave parsing within another monad and allows you to combine operations from both of them, without having to deal with the internals.

Related

How to declare that the composition of two types is a monad

I have function:
step :: forall m . (MonadState IntCodeState m) => m (Maybe ())
When I use do notation in the body of the function, it uses m as the monad. As you might expect, I actually want it to be using m Maybe. But, it doesn't understand that m Maybe is a monad. How do I express that to Haskell?
EDIT: This may be slightly malformed at the moment. The concrete type should be
StateT IntCodeState Maybe (), but I'm trying not to declare the concrete type, so the question is: how do I declare that?
EDIT 2: Another attempt: I've got some functions that look like this:
getValueIndex :: (MonadState IntCodeState m) => Int -> m (Maybe Int)
Here, I'm working on the level of the state monad. However, I now want to be able to act "as if" m Maybe was the monad. I was hoping this was simple but I can't figure out a way of expressing it. The code I want to write looks like this
step :: forall m . (MonadState IntCodeState m) => m (Maybe ())
step = do
full <- opCode
let len = length (snd full) + 1
process full <* (next += len)
But opCode returns a m (Maybe a) and I want full to be an a
But opCode returns a m (Maybe a) and I want full to be an a
Looks like you want to use the MaybeT monad transformer, which is m (Maybe a) under the hood, with its Monad instance doing what you need:
The MaybeT monad transformer extends a monad with the ability to exit the computation without returning a value.
A sequence of actions produces a value only if all the actions in the sequence do. If one exits, the rest of the sequence is skipped and the composite action exits.
Here are the types:
MaybeT :: m (Maybe a) -> MaybeT m a
runMaybeT :: MaybeT m a -> m (Maybe a)
This will also be helpful, specialised from MonadTrans:
lift :: m a -> MaybeT m a
So in your case:
step :: forall m . (MonadState IntCodeState m) => m (Maybe ())
step = runMaybeT $ do
full <- MaybeT opCode -- :: MaybeT opCode :: MaybeT m a, full :: a
let len = length (snd full) + 1
lift $ process full <* (next += len)
I've assumed process returns an m () and used lift to change it into MaybeT m ().

Modifying inner reader in a transformer stack

I'm pulling together code from a number of different places, and I'm trying to deal with the following:
Problem
I have a transformer stack with the following simplified type:
action :: m (ReaderT r IO) a
and I'm trying to use the action in the context of a different stack, which has a different reader environment:
desired :: m (ReaderT r' IO) a
I can of course provide
f :: r' -> r
Example
things :: m (ReaderT r' IO) ()
things = do
-- ... some stuff
-- <want to use action here>
action :: m (ReaderT r IO) a -- broken
-- ... more stuff
pure ()
What I've considered
withReaderT :: (r' -> r) -> ReaderT r m a -> ReaderT r' m a
This has the problem that ReaderT is the outer monad, whilst I want to use it on an inner one.
I've also considered that this might be related to MonadBase or MonadTransControl, but I'm not familiar with their workings.
I don't think it's possible to write a function with signature:
changeReaderT :: (MonadTrans m)
=> (r -> r')
-> m (ReaderT r IO) a
-> m (ReaderT r' IO) a
the issue being that the only operation possible, in general, on the second argument is lifting it to t (m (ReaderT r IO)) a for some monad transformer t, which doesn't buy you anything.
That is, the MonadTrans m constraint alone doesn't provide enough structure to do what you want. You either need m to be an instance of a typeclass like MFunctor in the mmorph package that allows you to modify an inner layer of the monad stack in a general way by providing a function like:
hoist :: Monad m => (forall a. m a -> n a) -> t m b -> t n b
(which is what #Juan Pablo Santos was saying), or else you need an ability to dig into the structure of your m monad transformer to partially run and rebuild it (which will be transformer-specific).
The first approach (using hoist from the mmorph package) will be most convenient if your m is already made up of transformers supported by the mmorph package. For example, the following typechecks, and you don't have to write any instances:
type M n = MaybeT (StateT String n)
action :: M (ReaderT Double IO) a
action = undefined
f :: Int -> Double
f = fromIntegral
desired :: M (ReaderT Int IO) a
desired = (hoist $ hoist $ withReaderT fromIntegral) action
You'll need a hoist for each layer in M.
The second approach avoids hoist and requisite MFunctor instances but requires tailoring to your specific M. For the above type , it looks something like:
desired' :: M (ReaderT Int IO) a
desired' = MaybeT $ StateT $ \s ->
(withReaderT fromIntegral . flip runStateT s . runMaybeT) action
You basically need to run the monad down to the ReaderT layer and then rebuild it back up, treating layers like StateT with care. This is exactly what the MFunctor instances in mmorph are doing automatically.

Apply a function to a value inside IO Maybe

I have a function of type a -> IO (Maybe b) and I want to apply it to IO (Maybe a) and get IO (Maybe b). I wrote a function to do that:
ioMaybeApply :: (a -> IO (Maybe b)) -> IO (Maybe a) -> IO (Maybe b)
ioMaybeApply f ioMaybeA = do
maybeA <- ioMaybeA
maybe (return Nothing) f maybeA
Is there a standard Haskell function to do that? I tried searching with Hoogle but I didn't find anything. If not, is my implementation good, or could it be simpler?
This can be achieved through the MaybeT monad transformer:
GHCi> import Control.Monad.Trans.Maybe
GHCi> :t \f m -> runMaybeT (MaybeT m >>= MaybeT . f)
\f m -> runMaybeT (MaybeT m >>= MaybeT . f)
:: Monad m => (a1 -> m (Maybe a)) -> m (Maybe a1) -> m (Maybe a)
import Control.Monad.Trans.Maybe
-- Making it look like your definition, for the sake of comparison.
ioMaybeApply :: (a -> IO (Maybe b)) -> IO (Maybe a) -> IO (Maybe b)
ioMaybeApply f ioMaybeA = runMaybeT $ do
a <- MaybeT ioMaybeA
MaybeT (f a)
If you are using this pattern in multiple places, it will likely pay off to change your a -> IO (Maybe b) functions to a -> MaybeT IO b -- then you can just use (>>=) and/or seamless do-blocks instead of your special-purpose function. On the other hand, if this is just an one-off you may reasonably think that using MaybeT would be overkill; in that case, your implementation is perfectly fine.
(It is worth mentioning that while there is a general-purpose wrapper for nested functors called Compose that has Functor and Applicative instances, it doesn't have a Monad instance, as nesting two monads doesn't necessarily result in something that can be given a legal Monad instance. That being so, we typically resort to monad transformers tailored for each combination that works.)

Lift a function with a monad parameter into a monad transformer

I want to lift a function like mask_ :: IO a -> IO a to create a function with this signature: lmask_ :: StateT Bool IO a -> StateT IO a.
My problem is, how to handle the callback/first parameter? Wouldn't the following code be incorrect since it would execute the callback before mask_'s code?
lmask_ :: StateT Bool IO a -> StateT Bool IO a
lmask_ m = do
r <- m
lift (mask_ (return r))
Is there some general way to do this? A helper like lift1 :: MonadTrans t => (m a -> m a) -> (t m a -> t m a)?
If we generalize lmask_ to get rid of the StateT Bool IO, we get something like this:
lift1 :: (Monad m, Monad (t m), MonadTrans t) => (m a -> m a) -> (t m a -> t m a)
lift1 f term = do
x <- term
lift (f (return x))
In general this is not possible without knowing something about the monad transformer. However, there is a way how to do this for all the standard monad transformers. See type class MonadBaseControl. It's superclass MonadBase defines what is the bottom monad in a monad transformer stack (which is IO for all stacks that include IO), and MonadBaseControl defines a way how to embed the monad into the base monad. Its instances are somewhat convoluted, but once they're defined, it's possible to lift all such functions like mask_.
In your case, package lifted-base uses the above construction to re-define the standard IO functions lifted to MonadBaseControl. In particular, there is mask_
mask_ :: MonadBaseControl IO m => m a -> m a
which can be specialized to StateT Bool IO a -> StateT Bool IO a, as StateT s has an instance of MonadBaseControl.
See also Lift a function and its argument to a different monadic context.

Lift a function and its argument to a different monadic context

I am not sure how to formulate this question scientifically exact, so I am just going to show you an example.
I am using state in a StateT transformer. Underlying is IO. Inside the StateT IO operation I need to use alloca. However, I can't lift alloca to StateT IO because it expects an argument of type (Ptr a -> IO a) while I require it to work with an argument of (Ptr a -> StateT IO MyState a).
(However, this is a generic question about monad transformers rather than specific to IO, StateT or alloca.)
I came up with the following, working solution:
-- for reference
-- alloca :: (Storable a) => (Ptr a -> IO b) -> IO b
allocaS :: (Storable a) => (Ptr a -> StateT s IO b) -> StateT s IO b
allocaS f = do
state <- get
(res, st) <- liftIO $ alloca $ \ptr -> (runStateT (f ptr) state)
put st
return res
However, it seems wrong to me that I should have to de- and reconstruct the StateT action in order to use it with alloca. Also, I have seen this pattern in some variations more than once and it's not always as simple and safe as here with StateT.
Is there a better way to do this?
This can be accomplished using MonadBaseControl in monad-control, which has been devised exactly for this purpose:
{-# LANGUAGE FlexibleContexts #-}
import Control.Monad
import Control.Monad.Trans.Control
import qualified Foreign.Ptr as F
import qualified Foreign.Marshal.Alloc as F
import qualified Foreign.Storable as F
alloca :: (MonadBaseControl IO m, F.Storable a) => (F.Ptr a -> m b) -> m b
alloca f = control $ \runInIO -> F.alloca (runInIO . f)
This enhanced version of alloca can be used with any monad stack based on IO that implements MonadBaseControl, including StateT s IO.
Instances of MonadBaseControl allow their monadic values to be encoded in the base monad (here IO), passed to a function in the base monad (like F.alloca) and then reconstruct them back.
See also What is MonadBaseControl for?
Package lifted-base contains many of the standard IO functions lifted to MonadBaseControl IO, but alloca isn't (yet) among them.
Good afternoon,
AFAIK, there is no general way to turn a function of type (a -> m b) -> m b into (a -> t m b) -> t m b because that would imply the existence of a function of type MonadTrans t => (a -> t m b) -> (a -> m b).
Such a function cannot possibly exist, since most transformers cannot be stripped so easily from a type signature (how do you turn a MaybeT m a into an m a for all a ?). Hence, the most general way to turn (a -> m b) -> m b to (a -> t m b) -> t m b is undefined.
In the case of StateT s m, there is a loophole that allows you to define it anyway. Since StateT s m a === s -> m (s,a), we can rewrite the type equation to :
(a -> StateT s m b) -> StateT s m b
=== (a -> s -> m (s,b)) -> s -> m (s,b)
=== s -> (s -> (a -> m (s,b)) -> m (s,b) -- we reorder curried arguments
=== s -> (s -> (A -> m B)) -> m B -- where A = a, B = (s,b)
Solving this new type signature is now trivial :
liftedState f s run = f (run s)
allocaS :: Storable a => (Ptr a -> StateT IO b) -> StateT IO b
allocaS = isomorphic (liftedState alloca)
That is about the best we can do in terms of code reuse, short of defining a new subclass of MonadTrans for all monads that exhibit the same behaviour.
I hope I made myself clear enough (I didn't want to go into too much detail for fear of being confusing)
Have an excellent day :-)

Resources