Polymorphism inside monads - haskell

I'm trying to pull a value out of a monad, but keep the value, which doesn't depend on the monad, polymorphic. Specifically:
foo :: (Monad mon, Ring a) => mon a
foo = return 3
main :: IO ()
main = do
x <- foo
print (x :: Double)
print (x :: Int)
The point is that the monadic portion of the computation is expensive to compute, so I only want to do it once, while keeping the value in the monad polymorphic. All of my attempts so far:
giving x the signature forall a. (Ring a) => a)
giving foo :: (Monad mon) => mon (forall a . (Ring a) => a)
enabling -XNoMonomorphismRestriction and NoMonoLocalBins
have either not worked or given errors about impredicative polymorphism, which I'm not willing to use. Is there some way to pull a polymorphic value out of a monad without impredicative polymorphism (or alternatively: is there a safe way to use impredicative polymorphism in GHC)?

You can work around the absence of impredicative polymorphism by wrapping the polymorphic value in a special data type.
newtype AnyRing = AnyRing (forall a. Ring a => a)
foo :: Monad m => m AnyRing
main = do
AnyRing x <- foo
print (x :: Double)
print (x :: Int)

I found another interesting solution, which came from this paper on typed, tagless, final interpreters (section 2.3).
The idea is to use a "duplicator":
data Dup a b = Dup a b
duplicate :: Dup a b -> (a,b)
duplicate (Dup a b) = (a,b)
instance (Num a, Num b) => Num (Dup a b) where
fromInteger x = Dup (fromInteger x) (fromInteger x)
...
foo :: (Monad mon, Num a) => mon a
foo = return 3
main :: IO ()
main = do
x <- foo
let (y,z) = duplicate x
print (y :: Double)
print (z :: Int)
This solution isn't as general as Li-yao Xia's (it only works when the monadic value is an instance of a type class), but it is interesting because you don't need higher-rank polymorphism.

Related

Using >> without explicitly declaring it in a monad

I am trying to get good at Monads and have written the following Monads and functions in which I use the >> (in the apply-function) although it is not declared in the Monad itself. How come this is possible to compile, as I understand http://learnyouahaskell.com/a-fistful-of-monads#walk-the-line it is required to declare it in the instantiation of the Monad as is the case with the Maybe Monad.
data Value =
NoneVal
| TrueVal | FalseVal
| IntVal Int
| StringVal String
| ListVal [Value]
deriving (Eq, Show, Read)
data RunErr = EBadV VName | EBadF FName | EBadA String
deriving (Eq, Show)
newtype CMonad a = CMonad {runCMonad :: Env -> (Either RunErr a, [String]) }
instance Monad CMonad where
return a = CMonad (\_ -> (Right a, []))
m >>= f = CMonad (\env -> case runCMonad m env of
(Left a, strLst) -> (Left a, strLst)
(Right a, strLst) -> let (a', strLst') = runCMonad (f a) env in (a', strLst ++ strLst'))
output :: String -> CMonad ()
output s = CMonad(\env -> (Right (), [] ++ [s]))
apply :: FName -> [Value] -> CMonad Value
apply "print" [] = output "" >> return NoneVal
Furthermore, how would I make it possible to show the output (print it) from the console when running apply. Currently I get the following error message, although my types have derive Show:
<interactive>:77:1: error:
* No instance for (Show (CMonad Value)) arising from a use of `print'
* In a stmt of an interactive GHCi command: print it
The >> operator is optional, not required. The documentation states that the minimal complete definition is >>=. While you can implement both >> and return, you don't have to. If you don't supply them, Haskell can use default implementations that are derived from either >> and/or Applicative's pure.
The type class definition is (current GHC source code, reduced to essentials):
class Applicative m => Monad m where
(>>=) :: forall a b. m a -> (a -> m b) -> m b
(>>) :: forall a b. m a -> m b -> m b
m >> k = m >>= \_ -> k
return :: a -> m a
return = pure
Notice that >>= lacks an implementation, which means that you must supply it. The two other functions have a default implementation, but you can 'override' them if you want to.
If you want to see output from GHCi, the type must be a Show instance. If the type wraps a function, there's no clear way to do that.
The declaration of Monad in the standard Prelude is as follows: (simplified from the Prelude source)
class Applicative m => Monad m where
(>>=) :: forall a b. m a -> (a -> m b) -> m b
(>>) :: forall a b. m a -> m b -> m b
m >> k = m >>= \_ -> k
{-# INLINE (>>) #-}
return :: a -> m a
return = pure
It's a typeclass with three methods, (>>=), (>>) and return.
Of those three, two have a default implementation - the function is implemented in the typeclass, and one does not.
Monad is a subclass of Applicative, and return is the same as pure - it is included in the Monad typeclass (or at all) for historical reasons.
Of the remaining two, (>>=) is all that is needed to define a Monad in Haskell. (>>) could be defined outside of the typeclass, like this:
(>>) :: (Monad m) => forall a b. m a -> m b -> m b
m >> k = m >>= \_ -> k
The reason this is included is in case a monad author wants to override the default implementation with an implementation which is more efficient.
A typeclass method which is not required is know as optional.
Haddock documentation automatically generates a 'Mnimal complete definition' based on the methods without default implementations. You can see here that the minimal definition of Monad is indeed (>>=).
Sometimes, all methods can have default implementations, but they are not optional. This can happen when one of two methods must be provided, and the other is defined in terms of it. This is the case for the Traversable typeclass, where traverse and sequenceA are both implemented in terms of each other. Not implementing either method will cause them to go into an infinite loop.
To let you mark this, GHC provides the MINIMAL pragma, which generates the neccesary compiler warnings, and ensures the Haddocks are correct.
As an aside, failing to implement a required typeclass method is by default a compiler warning, not an error, and will cause a runtime exception if called. There is no good reason for this behaviour.
You can change this default using the -Werror=missing-methods GHC flag.
Happy Haskelling!

Why does this type annotation make my functional dependency conflict go away? (and why does it only happen on some versions of GHC?)

So I've been playing around with MonadState class and I have encountered something I consider very strange.
I can try to write a monad like the following:
test ::
( MonadState Int m
, MonadState Bool m
)
=> m ()
test = do
((+1) <$> get) >>= put
(not <$> get) >>= put
If we compile this in ghc 8.6.4 we get the following:
MonadTrans.hs:10:13: error:
• Couldn't match type ‘Int’ with ‘Bool’
arising from a functional dependency between constraints:
‘MonadState Bool m’
arising from a use of ‘get’ at MonadTrans.hs:10:13-15
‘MonadState Int m’
arising from the type signature for:
test :: forall (m :: * -> *).
(MonadState Int m, MonadState Bool m) =>
m ()
at MonadTrans.hs:(4,1)-(8,11)
• In the second argument of ‘(<$>)’, namely ‘get’
In the first argument of ‘(>>=)’, namely ‘((+ 1) <$> get)’
In a stmt of a 'do' block: ((+ 1) <$> get) >>= put
|
10 | ((+1) <$> get) >>= put
|
(older versions of GHC for example 8.2.2 are actually fine with this and compile. I have no idea why.)
Ok this makes sense since the declaration of MonadState has a dependency in it:
class Monad m => MonadState s m | m -> s where
we cannot have a single Monad be both MonadState Int and MonadState Bool. But here is where things get a little strange.
If I add a type annotation the code will compile
test ::
( MonadState Int m
, MonadState Bool m
)
=> m ()
test = do
(((+1) :: Int -> Int) <$> get) >>= put
(not <$> get) >>= put
To me this seems very strange. A moment ago it was complaining about a very real functional dependency conflict between the two. I don't see how disambiguating the type of (+1) makes that conflict go away.
What is happening here? How does the second one compile while the first fails? And why does the first compile on 8.2.2?
Try this:
plus1 :: Int -> Int
plus1 = (+ 1)
test :: (MonadState Int m, MonadState Bool m) => m ()
test = do
(plus1 <$> get) >>= put
(not <$> get) >>= put
Compiles fine, even without the inline type annotation.
What the functor?!
The thing is, when the compiler complains in your first example, it doesn't complain about the type signature just because it decided to verify it for the heck of it. Look a bit further in the error message: ...In the second argument of ‘(<$>)’, namely ‘get’...
Aha! The source of trouble is actually get! But why?
The trouble is the bloody overloaded arithmetic. You see, operator (+) has a polymorphic type, like this:
(+) :: Num a => a -> a -> a
And naked literals also have similar type:
1 :: Num a => a
So when you write (+1), it doesn't let the compiler know that you meant Int. It admits any type a as long as there is Num a.
So the compiler turns to further surroundings to get the type. But wait! Further surroundings are also generic:
get :: MonadState a m => m a
put :: MonadState a m => a -> m ()
Ok, so maybe we can get the type from the signature of test? Let's check that! Oh, no, the signature actually contains a conflict! Bail, bail, bail! That's when you get the error.
All of this doesn't happen on the second line, because not has a non-polymorphic type not :: Bool -> Bool, so the required type of get is known. And this is why either giving an inline type annotation Int -> Int or having it come from an external function plus1 helps on the first line as well.
If you do provide enough type information for the values in the body, the compiler never has to analyze the test signature. The signature specifies that there should be a MonadState Int m dictionary, and that's good enough. Whoever calls the function will have provide the dictionary, and we'll just use that.
Now, of course, when you get around to calling this function, you'll need to provide both dictionaries MonadState Int m and MonadState Bool m, and you can't get those, so you can't actually call such function. But you sure can define it.
That being said, you CAN actually have a monad with two different MonadState instances if you're willing to be sneaky enough about it.
Of course, if you try it straight up, you get a very straight up error:
data M a = M
instance MonadState Int M
instance MonadState Bool M
> Functional dependencies conflict between instance declarations:
> instance MonadState Int M -- Defined at ...
> instance MonadState Bool M -- Defined at ...
Ok, let's start small:
data M a = M
instance MonadState Int M
> Illegal instance declaration for `MonadState a M'
> The liberal coverage condition fails in class `MonadState'
> for functional dependency: `m -> s'
> Reason: lhs type `M' does not determine rhs type `a'
> Un-determined variable: a
Alright, so something in the type of M must indicate the type Int. That makes sense. Let's add it:
data M x a = M a
instance MonadState Int (M Int)
Ok, this works. So far so good.
But of course, in order to define MonadState Bool, I need to add Bool to the type as well:
data M x y a = M a
instance MonadState Int (M Int y)
instance MonadState Bool (M x Bool)
> Functional dependencies conflict between instance declarations:
Ah, still fundep failure! Ok, well, that makes sense too.
So is there a way I can fool the compiler into not checking the instances for the fundep? Yes, there is! I can be sneaky and make the instances overlapped, like this:
instance {-# OVERLAPPABLE #-} (Num a, Show a) => MonadState a (M a y) where
get = M 42
put x = M ()
instance {-# OVERLAPPING #-} MonadState Bool (M x Bool) where
get = M True
put x = M ()
Now all that's left is the Monad instance, and we can have it all actually run:
data M x y a = M a deriving (Functor, Show)
instance Applicative (M x y) where
pure = M
(M f) <*> (M x) = M $ f x
instance Monad (M x y) where
(M x) >>= f = f x
instance {-# OVERLAPPABLE #-} (Num a, Show a) => MonadState a (M a y) where
get = M 42
put x = trace ("Setting Num: " ++ show x) $ M ()
instance {-# OVERLAPPING #-} MonadState Bool (M x Bool) where
get = M True
put x = trace ("Setting Bool: " ++ show x) $ M ()
g :: M Int Bool ()
g = test
main = print g
I've included debug trace to verify how they're actually going to work, so the above program prints:
Setting Num: 43
Setting Bool: False
M ()

Can the type of this function be declared in standard Haskell

The following program compiles under GHC 8.0.2 with no language extensions, and produces the expected two lines of output.
However, it does not compile if the (non-top-level) type declaration for the value write' is removed.
Also, I cannot find any (top-level) type declaration for the function write.
I find this rather odd. If this is acceptable standard Haskell, surely it should be possible to create a type declaration for the function write.
So my question is: is there such a type declaration?
import Control.Monad.Trans.Maybe (MaybeT, runMaybeT)
import Control.Monad.Writer (MonadTrans, Writer, lift, runWriter, tell, when)
import ListT (ListT, toList) -- Volkov's list-t package
logging = True
write x = when logging write' where
write' :: MonadTrans m => m (Writer [String]) ()
write' = lift $ tell [x]
f :: ListT (Writer [String]) String
f = do
write "Hello from f"
return "ABC"
g :: MaybeT (Writer [String]) Int
g = do
write "Hello from g"
return 123
main :: IO ()
main = do
print $ runWriter $ toList f
print $ runWriter $ runMaybeT g
Using GHCi (remember to put this into a separate file and load it on GHCi's command line lest you get confused by GHCi's altered typing rules):
> :t write
write :: (Applicative (m (Writer [String])), MonadTrans m) =>
String -> m (Writer [String]) ()
Why? Well,
write' :: MonadTrans m => m (Writer [String]) ()
when :: Applicative f => Bool -> f () -> f ()
when logging :: Applicative f => f () -> f ()
so, when logging write' must unify write''s m (Writer [String]) with when loggings's f, causing the combined constraint (Applicative (m (Writer [String])), MonadTrans m). But wait, let's remove the type signatures and see what the most general type is:
-- equivalent but slightly easier to talk about
write = when logging . lift . tell . (:[])
(:[]) :: a -> [a]
tell :: MonadWriter w m -> w -> m ()
lift :: (Monad m, MonadTrans t) => m a -> t m a
tell . (:[]) :: MonadWriter [a] m => a -> m ()
lift . tell . (:[]) :: (MonadWriter [a] m, MonadTrans t) => a -> t m ()
when logging . lift . tell . (:[]) = write
:: (Applicative (t m), MonadWriter [a] m, MonadTrans t) => a -> t m ()
-- GHCi agrees
Per se, there's nothing wrong with this type. However, standard Haskell does not allow this. In standard Haskell, a constraint must be of the form C v or C (v t1 t2 ...) where v is a type variable. In the compiling case, this holds: the Applicative constraint has the type variable m on the outside, and the MonadTrans is just m. This is true in the non-compiling version, too, but we also have the constraint MonadWriter ([] a) m. [] is no type variable, so the type here is rejected. This constraint arises in the compiling version, too, but the type signatures nail the variables down to produce MonadWriter [String] (Writer [String]), which is immediately satisfied and does not need to appear in the context of write.
The restriction is lifted by enabling FlexibleContexts (preferably via a {-# LANGUAGE FlexibleContexts #-} pragma, but also maybe by -XFlexibleContexts). It originally existed to prevent things such as the following:
class C a where c :: a -> a
-- no instance C Int
foo :: C Int => Int
foo = c (5 :: Int)
-- with NoFlexibleContexts: foo's definition is in error
-- with FlexibleContexts: foo is fine; all usages of foo are in error for
-- not providing C Int. This might obscure the source of the problem.
-- slightly more insiduous
data Odd a = Odd a
-- no Eq (Odd a)
oddly (Odd 0) (Odd 0) = False
oddly l r = l == r
-- oddly :: (Num a, Eq (Odd a), Eq a) => Odd a -> Odd a -> Bool
-- Now the weird type is inferred! With FlexibleContexts,
-- the weird constraint can propagate quite far, causing errors in distant
-- places. This is confusing. NoFlexibleContexts places oddly in the spotlight.
But it happens to get in the way a lot when you have MultiParamTypeClasses on.

Taking monadic functions out of a monad

Haskell has the function join, which "runs" a monadic action which is inside a monad:
join :: Monad m => m (m a) -> m a
join m = m >>= \f -> f
We can write a similar function for monadic functions with one argument:
join1 :: Monad m => m (a -> m b) -> (a -> m b)
join1 m arg1 = m >>= \f -> f arg1
And for two arguments:
join2 :: Monad m => m (a -> b -> m c) -> (a -> b -> m c)
join2 m arg1 arg2 = m >>= \f -> f arg1 arg2
Is it possible to write a general function joinN, that can handle monadic functions with N arguments?
You can do something like this with a fair amount of ugliness if you really desire.
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE UndecidableInstances #-}
import Control.Monad (join, liftM)
class Joinable m z | z -> m where
joins :: m z -> z
instance Monad m => Joinable m (m a) where
joins = join
instance (Monad m, Joinable m z) => Joinable m (r -> z) where
joins m r = joins (liftM ($ r) m)
But, as you can see this relies on some shaky typeclass magic (in particular, the unenviable UndecidableInstances). It is quite possibly better—if ugly looking—to write all of the instances join1...join10 and export them directly. This is the pattern established in the base library as well.
Notably, inference won't work too well under this regime. For instance
λ> joins (return (\a b -> return (a + b))) 1 2
Overlapping instances for Joinable ((->) t0) (t0 -> t0 -> IO t0)
arising from a use of ‘joins’
Matching instances:
instance Monad m => Joinable m (m a)
-- Defined at /Users/tel/tmp/ASD.hs:11:10
instance (Monad m, Joinable m z) => Joinable m (r -> z)
-- Defined at /Users/tel/tmp/ASD.hs:14:10
but if we give an explicit type to our argument
λ> let {q :: IO (Int -> Int -> IO Int); q = return (\a b -> return (a + b))}
then it can still work as we hope
λ> joins q 1 2
3
This arises because with typeclasses alone it becomes quite difficult to indicate whether you want to operate on the monad m in the final return type of the function chain or the monad (->) r that is the function chain itself.
The short answer is no. The slightly longer answer is you could probably define an infix operator.
Take a look at the implementation for liftM: http://hackage.haskell.org/package/base-4.7.0.2/docs/src/Control-Monad.html#liftM
It defines up to liftM5. This is because it's not possible to define liftMN, just like your joinN isn't possible.
But we can take a lesson from Appicative <$> and <*> and define our own infix operator:
> let infixr 1 <~> ; x <~> f = fmap ($ x) f
> :t (<~>)
(<~>) :: Functor f => a -> f (a -> b) -> f b
> let foo x y = Just (x + y)
> let foobar = Just foo
> join $ 1 <~> 2 <~> foobar
Just 3
This is quite reminiscent of a common applicative pattern:
f <$> a1 <*> a2 .. <*> an
join $ a1 <~> a2 .. <~> an <~> f
A single function for every possible N? Not really. Generalizing over functions with different numbers of arguments like this is difficult in Haskell, in part because "number of arguments" is not always well-defined. The following are all valid specializations of id's type:
id :: a -> a
id :: (a -> a) -> a -> a
id :: (a -> a -> a) -> a -> a -> a
...
We'd need some way to get N at the type level, and then do a different thing depending on what N is.
Existing "variadic" functions like printf do this with typeclasses. They establish what N is by induction on ->: they have a "base case" instance for a non-function type like String and a recursive instance for functions:
instance PrintfType String ...
instance (PrintfArg a, PrintfType r) => PrintfType (a -> r) ...
We can (after a lot of thinking :P) use the same approach here, with one caveat: our base case is a bit ugly. We want to start with the normal join, which produces a result of type m a; the problem is that to support any m a, we have to overlap with normal functions. This means that we need to enable a few scary extensions and that we might confuse the type inference system when we actually use our joinN. But, with the right type signatures in place, I believe it should work correctly.
First off, here's the helper class:
class Monad m => JoinN m ma where
joinN :: m ma -> ma
ma will take the relevant function type like a -> m b, a -> b -> m c and so on. I couldn't figure out how to leave m out of the class definition, so right off the bat we need to enable MultiParamTypeClasses.
Next, our base case, which is just normal join:
instance Monad m => JoinN m (m a) where
joinN = join
Finally, we have our recursive case. What we need to do is "peel off" an argument and then implement the function in terms of a smaller joinN. We do this with ap, which is <*> specialized to monads:
instance (Monad m, JoinN m ma) => JoinN m (b -> ma) where
joinN m arg = joinN (m `ap` return arg)
We can read the => in the instance as implication: if we know how to joinN an ma, we also know how to do a b -> ma.
This instance is slightly weird, so it requires FlexibleInstances to work. More troublingly, because our base case (m (m a)) is made up entirely of variables, it actually overlaps with a bunch of other reasonable types. To actually make this work we have to enable OverlappingInstances and IncoherentInstances, which are relatively tricky and bug-prone.
After a bit of cursory testing, it seems to work:
λ> let foo' = do getLine >>= \ x -> return $ \ a b c d -> putStrLn $ a ++ x ++ b ++ x ++ c ++ x ++ d
λ> let join4 m a b c d = m >>= \ f -> f a b c d
λ> join4 foo' "a" "b" "c" "d"
a b c d
λ> joinN foo' "a" "b" "c" "d"
a b c d

Repacking monads -- any generic way?

Given two monads, Monad m and Monad n, I would like to transform m (n a) into n (m a). But there seems to be no generic way because both (>>=) and return deals with only one monad type, and although (>>=) allows extracting content from a monad, you must pack them back to the same monad type so it can be a result value.
However, if we set m to a fixed type, the job becomes easy. Take Maybe as an example:
reorder :: (Monad n) => Maybe (n a) -> n (Maybe a)
reorder Nothing = return Nothing
reorder (Just x) = do
x' <- x
return $ Just x'
Or a list:
reorder :: (Monad n) => [n a] -> n [a]
reorder [] = return []
reorder (x:xs) = do
x' <- x
xs' <- reorder xs
return (x':xs')
Not hard to see, we've got a pattern here. To be more obvious, write it in a Applicative way, and it's no more than applying the data constructor to each element:
reorder (Just x) = Just <$> x
reorder (x:xs) = (:) <$> x <*> (reorder xs)
My question is: does a haskell typeclass already exist to describe such operations, or do I have to invent the wheel myself?
I had a brief search in the GHC documentation, and found nothing useful for this topic.
Data.Traversable provides what you are looking for:
sequenceA :: (Traversable t, Applicative f) => t (f a) -> f (t a)
GHC even provides support for automatically deriving instances:
{-# LANGUAGE DeriveFunctor, DeriveFoldable, DeriveTraversable #-}
import Data.Foldable
import Data.Traversable
data List a = Nil | Cons a (List a)
deriving(Functor, Foldable, Traversable)
A quick search on hoogle for (Monad m, Monad n) => m (n a) -> n (m a) showed me that there are several functions that (roughly) comply with the signature you're looking for:
Data.Traversable.sequence :: (Traversable t, Monad m) => t (m a) -> m (t a);
Data.Traversable.sequenceA :: Applicative f => t (f a) -> f (t a);
Contro.Monad.sequence :: Monad m => [m a] -> m [a] (also exported by Prelude).
Both [a] and Maybe a are instances of traversable, so your reorder functions are just applications of Data.Traversable.sequence. One could write, in example:
ghci> (Data.Traversable.sequence $ Just (return 1)) :: IO (Maybe Int)
Just 1
it :: Maybe Int
ghci> (Data.Traversable.sequence $ Just ([1])) :: [Maybe Int]
[Just 1]
it :: [Maybe Int]
ghci> (Data.Traversable.sequence $ [Just 1]) :: Maybe [Int]
Just [1]
it :: Maybe [Int]
Please note however that the specific class declaration is class (Functor t, Foldable t) => Traversable t, and if you look also at the types of the other two functions, it does not seems like what you're looking for could possibly be done in a generic way for all monads m and n without restrictions/preconditions.
It can't be done in general: a good example of a monad that can't do this is the reader (or function) monad. That would require the following function to be definable:
impossible :: (r -> IO a) -> IO (r -> a)
It's not straightforward to prove that a function cannot be implemented. But intuitively, the problem is that whatever IO has to be done in the value returned has to be done before we know what the r parameter is. So impossible readFile would have to yield a pure function FilePath -> String before it knew which files to open. Clearly, at least, impossible can't do what you'd want it to.
Not all Monads can commute in that way. Edward Kmett's distributive package provides a typeclass Distributive for type constructors that is similar to what you desire (simplified):
class Functor g => Distributive g where
distribute :: Functor f => f (g a) -> g (f a)
collect :: Functor f => (a -> g b) -> f a -> g (f b)
Default definitions are provided for distribute and collect, written in terms of each other. I found this package by searching hayoo for the desired type signature.

Resources