Lift a function and its argument to a different monadic context - haskell

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 :-)

Related

Function in Haskell to map over a MonadTrans?

I have recently decided to start using monad transformations instead of stacking my monads, since it seems it's the right thing to do. I wasn't really stacking many monads before anyway. I get (I think) the idea behind it and the lift function, that, as I understand it, acts as a sort of return for the transformation (puts something from the underlying monad into the transformed monad).
So far so good, but I don't see anything similar to an fmap function for monad transformations. Let me give you an example. Say I have a custom monad, m, and I use a StateT transformation on it, therefore using the type StateT s m a instead of m (State s a).
Now, it so happens that in my monad m, I have a function that transforms the monadic element (in fact it is one of the constructors of the monad, if you need details I can give) while keeping in some sense the underlying values: myFunc :: m a -> m a.
So I'm building a recursive function recFunc :: State s a -> [t] -> m (State s a) that looks similar to something like this:
recFunc :: State s a -> [t] -> m (State s a)
recFunc x [] = return x
recFunc x (t:ts) = myFunc (recFunc x ts)
But if I try to replicate this using monad transformations, I run into problems because I can find no way to plug in myFunc into the mix. It does not matter whether you write the input as State s a or as StateT s Identity a (which would be algebraically more precise?)
recFuncT :: StateT s Identity a -> [t] -> StateT s m a
recFuncT x [] = ???
recFuncT x (t:ts) = ????? where rec = recFuncT x ts
So what I'm looking for is something like the (invented, and don't know how I would implement, if possible) following functions:
transmap :: (MonadTrans t, Monad m) => (forall b. m b -> m b) -> t m a -> t m a
transmap = ???
transreturn :: (MonadTrans t, Monad m) => m (t Identity a) -> t m a
transreturn = ???
I have the feeling I should be able to define these using lift, but I don't see how, to be honest.
If I had them, then I could do this:
recFuncT :: StateT s Identity a -> [t] -> StateT s m a
recFuncT x [] = transreturn (return x)
recFuncT x (t:ts) = transmap myFunc (recFuncT x ts)
Maybe what I really want is something more basic. I want the assumed isomorphism between t m a and m (t Identity a) to be explicit, so I'm looking for functions:
fromTrans :: t m a -> m (t Identity a)
toTrans :: m (t Identity a) -> t m a
As far as I understand monad transformers, these functions should always exist and be fairly straightforward, right?
With these I could obviously implement transmap and transreturn:
transmap :: (MonadTrans t, Monad m) => (forall b. m b -> m b) -> t m a -> t m a
transmap f x = toTrans (f (fromTrans x))
transreturn :: (MonadTrans t, Monad m) => m (t Identity a) -> t m a
transreturn = toTrans
I am sure there is something obvious that I am overlooking. Please point at it for me.
Thanks.
It appears that one concept you're seeking can be found in the mmorph package:
class MFunctor t where
-- The argument is generally required to be a monad morphism,
-- but some instances will work sensibly when it's not.
hoist :: Monad m => (forall x. m x -> n x) -> t m a -> t n a
This is a little more general than your version because it allows the underlying monad to be replaced.
From the discussion in the comments, it sounds like what you really want is a monad transformer for your custom monad that is then applied to the base monad State. In other words, to the extent that your custom monad is "nearly" a list:
newtype Listish a = Listish [a]
its transformer version would have type:
newtype ListishT m a = ListishT [m a]
and so your final monad transformer stack would be:
type M s = ListishT (State s)
which is isomorphic to your monad stack
[State s a] AKA Listish (State s a)
Be sure not to over-generalize the pattern for creating a transformer from an underlying monad, however. While transformers for some monads:
newtype List a = List [a]
newtype Reader r a = Reader (r -> a)
are sensibly derived by replacing "a" with "m a":
newtype ListT m a = ListT [m a]
newtype ReaderT r m a = ReaderT (r -> m a)
transformers for other types are derived differently. For example:
newtype State s a = State (s -> (a, s))
newtype Writer w a = Writer (a, w)
give:
newtype StateT s a = StateT (s -> m (a, s))
-- **NOT** StateT (s -> (m a, s))
newtype WriterT s a = WriterT (m (a, w))
-- **NOT** WriterT (m a, w)
In particular, there is no monad transformer for IO, because the simple substitution
newtype BadIOT m a = BadIOT (IO (m a))
is, as you point out, silly.
EDIT: All of the below makes no sense. I leave it strikedthrough. Good answer below.
For the record, my final solution was neither to use or implement a monad transformer, and instead simply implement the following function: (my custom monad is called EnumProc):
(..>>=) :: Monad m => EnumProc (m a) -> (a -> m b) -> EnumProc (m b)
en ..>>= f = en <$> (>>= f)
infixl 7 ..>>=
This allows me to deal with monadic computations inside my monad while keeping the outside monad structure. I was surprised myself when an fmap sufficed.
I then use EnumProc (State s a) as type throughout.
After a while, I finally came up with exactly what I was looking for since the beginning. I can use StateT exactly the way I wanted, and it has exactly the semantics I thought it had, but I did not explain it well (and put mistakes in what I wrote).
Going back to my original post, I need not have a State as input, the State/StateT monad already includes the input in the monadic element. So what I needed was a function recFuncT :: [t] -> StateT s m a that behaved equivalently to the following non-transformer one:
recFunc :: a -> [t] -> m (State s a)
recFunc x [] = return (return x)
recFunc x (t:ts) = myFunc (recFunc x ts)
It can be implemented directly, using the constructor StateT and runStateT. Here it is:
recFuncT :: a -> [t] -> StateT m s a
recFuncT x [] = return x
recFuncT x (t:ts) = StateT (\s -> myFunc (runStateT (recFuncT x ts) s))
Moreover, the function transmap can also be implemented in general, at least for StateT:
transmap :: Monad m => (forall b. m b -> m b) -> StateT s m a -> StateT s m a
transmap f st = StateT (\s -> f (runStateT st s)
And then we could write recFuncT nicely in terms of it:
recFuncT :: a -> [t] -> StateT m s a
recFuncT x [] = return x
recFuncT x (t:ts) = transmap myFunc (recFuncT x ts)
I realize this does not really match with the code that I included originally, but it does match with the overall principle I was trying to appeal to saying that the StateT transformer is like adding state to my monad m, and therefore anything that can be done at the m (State s a) level can be done at the StateT s m a level.

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.

MonadBaseControl: how to lift simpleHTTP from Happstack?

How to use MonadBaseControl from monad-control to lift simpleHTTP function defined in happstack-server?
Current type of simpleHTTP:
simpleHTTP :: ToMessage a
=> Conf -> ServerPartT IO a -> IO ()
Expected type of simpleHTTPLifted:
simpleHTTPLifted :: (MonadBaseControl IO m, ToMessage a)
=> Conf -> ServerPartT m a -> m ()
My current attempt (does not compile):
simpleHTTPLifted conf action =
liftBaseWith (\runInBase ->
let
fixTypes :: UnWebT m a -> UnWebT IO a
fixTypes c = runInBase c
in simpleHTTP conf (mapServerPartT fixTypes action)
)
Note that similar puzzle is in my related question: MonadBaseControl: how to lift ThreadGroup
I'd like to understand how to in general lift such functions and what are usual steps taken when presented with such a type puzzle?
EDIT: I guess I need a function of type (StM m a -> a). restoreM is pretty close, but does not make it. I've also found an ugly version of fixTypes:
fixTypes :: UnWebT m a -> UnWebT IO a
fixTypes c = do
x <- newIORef undefined
_ <- runInBase (c >>= liftBase . writeIORef x)
readIORef x
This relies on IO being the base monad which is not an optimal solution.
I don't think you can lift this in general for any MonadBaseControl IO m. There are some ms for which we can.
In General
UnWebT m is isomorphic to WebT m which has a MonadTransControl instance. You can convert to and from WebT with mkWebT :: UnWebT m a -> WebT m a and ununWebT :: WebT m a -> UnWebT m a.
MonadBaseControl is a fancy wrapper around a stack of MonadTransControl transformers that flattens the stack so that running and restoring state happens all the way down the stack and all the way back up it again. You can understand MonadBaseControl by understanding MonadTransControl, which I'll repeat briefly here:
class MonadTrans t => MonadTransControl t where
data StT t :: * -> *
liftWith :: Monad m => (Run t -> m a) -> t m a
restoreT :: Monad m => m (StT t a) -> t m a
type Run t = forall n b. Monad n => t n b -> n (StT t b)
The class says with liftWith, "I'll provide a temporary way to run t ms in m, which you can use to build actions in m, which I will in turn run." The StT type of the result says, "the results of the t m things I run in m for you aren't going to be generally available in t m; I need to save my state somewhere, and you have to give me a chance to restore my state if you want the results."
Another way of saying approximately the same thing is, "I can temporarily unwrap the base monad". The question of implementing fixTypes is reduced to "Given that we can temporarily unwrap a WebT from an m and can temporarily unwrap an m from IO, can we permanently unwrap an m from an IO?" for which the answer, barring the capabilities of IO, is almost certainly "no".
IO Tricks
I suspect that there exist ms such that the "ugly" fixTypes will do horrible things like never call writeIORef and thus return undefined or execute code asynchronously and therefore call writeIORef after readIORef. I'm not sure. This is made complicated to reason about due to the possibility that the action created by liftBaseWith is never used in such degenerate cases.
For Comonads
There should be a way to lift simpleHttp without IO tricks precisely when the state of the monad m is a Comonad and therefore has a function extract :: StM m a -> a. For example, this would be the case for StateT s m which essentially has StM s a ~ (s, a).
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE ScopedTypeVariables #-}
import Happstack.Server.SimpleHTTP
import Control.Comonad
import Control.Monad.Base
import Control.Monad.Trans.Control
simpleHTTPLifted :: forall m a. (MonadBaseControl IO m, Comonad (StM m), ToMessage a)
=> Conf -> ServerPartT m a -> m ()
simpleHTTPLifted conf action =
liftBaseWith (\runInBase ->
let
fixTypes :: UnWebT m b -> UnWebT IO b
fixTypes = fmap extract . runInBase
in simpleHTTP conf (mapServerPartT fixTypes action)
)
In practice this isn't very useful because the newtypes defined in the older versions of monad-control don't have Comonad instances and the type synonymns in the newer versions of monad-control make no effort to have the result as the last type argument. For example, in the newest version of monad-control type StT (StateT s) a = (a, s) .

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

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.

Resources