Could not deduce (m ~ m1) - haskell

When compiling this program in GHC:
import Control.Monad
f x = let
g y = let
h z = liftM not x
in h 0
in g 0
I receive an error:
test.hs:5:21:
Could not deduce (m ~ m1)
from the context (Monad m)
bound by the inferred type of f :: Monad m => m Bool -> m Bool
at test.hs:(3,1)-(7,8)
or from (m Bool ~ m1 Bool, Monad m1)
bound by the inferred type of
h :: (m Bool ~ m1 Bool, Monad m1) => t1 -> m1 Bool
at test.hs:5:5-21
`m' is a rigid type variable bound by
the inferred type of f :: Monad m => m Bool -> m Bool
at test.hs:3:1
`m1' is a rigid type variable bound by
the inferred type of
h :: (m Bool ~ m1 Bool, Monad m1) => t1 -> m1 Bool
at test.hs:5:5
Expected type: m1 Bool
Actual type: m Bool
In the second argument of `liftM', namely `x'
In the expression: liftM not x
In an equation for `h': h z = liftM not x
Why? Also, providing an explicit type signature for f (f :: Monad m => m Bool -> m Bool) makes the error disappear. But this is exactly the same type as the type that Haskell infers for f automatically, according to the error message!

This is pretty straightforward, actually. The inferred types of let-bound variables are implicitly generalised to type schemes, so there’s a quantifier in your way. The generalised type of h is:
h :: forall a m. (Monad m) => a -> m Bool
And the generalised type of f is:
f :: forall m. (Monad m) => m Bool -> m Bool
They’re not the same m. You would get essentially the same error if you wrote this:
f :: (Monad m) => m Bool -> m Bool
f x = let
g y = let
h :: (Monad m) => a -> m Bool
h z = liftM not x
in h 0
in g 0
And you could fix it by enabling the “scoped type variables” extension:
{-# LANGUAGE ScopedTypeVariables #-}
f :: forall m. (Monad m) => m Bool -> m Bool
f x = let
g y = let
h :: a -> m Bool
h z = liftM not x
in h 0
in g 0
Or by disabling let-generalisation with the “monomorphic local bindings” extension, MonoLocalBinds.

Related

Haskell: why does 'id' make this function no longer monadic?

I am trying to understand why adding id in the last line of the sequence below removes the monadic aspect:
Prelude> :t id
id :: a -> a
Prelude> :t Control.Monad.liftM2
Control.Monad.liftM2
:: Monad m => (a1 -> a2 -> r) -> m a1 -> m a2 -> m r
Prelude> :t (==)
(==) :: Eq a => a -> a -> Bool
Prelude> :t Control.Monad.liftM2 (==)
Control.Monad.liftM2 (==)
:: (Monad m, Eq a) => m a -> m a -> m Bool
Prelude> :t Control.Monad.liftM2 (==) id
Control.Monad.liftM2 (==) id :: Eq a => (a -> a) -> a -> Bool
Prelude>
How does adding id :: a -> a change the signature in the way it does in the last line ?
You’re fixing the type to a particular Monad instance, namely the “function reader” monad (instance Monad ((->) a)).
id :: a -> a and you are attempting to use it as an argument to a parameter of type m a, so:
m a ~ a -> a
m a ~ (->) a a
m a ~ ((->) a) a
m ~ (->) a
a ~ a
The remainder of the signature is:
m a -> m Bool
And since m ~ (->) a, the resulting type is:
(->) a a -> (->) a Bool
(a -> a) -> (a -> Bool)
(a -> a) -> a -> Bool
(Plus the Eq a constraint from the use of ==.)
This is useful in pointfree code, particularly using the Applicative instance, since you can implicitly “spread” the argument of a function to subcomputations:
nextThree = (,,) <$> (+ 1) <*> (+ 2) <*> (+ 3)
-- or
nextThree = liftA3 (,,) (+ 1) (+ 2) (+ 3)
nextThree 5 == (6, 7, 8)
uncurry' f = f <$> fst <*> snd
-- or
uncurry' f = liftA2 f fst snd
uncurry' (+) (1, 2) == 3
The signature of liftM2 (==) is (Monad m, Eq a) => m a -> m a -> m Bool. So that means that if we call this function with id :: b -> b as argument, then it means that m a and b -> b are the same type.
The fact that m ~ (->) b holds is not a problem since (->) r is an instance of Monad, indeed in the GHC.Base source code we see:
-- | #since 2.01
instance Monad ((->) r) where
f >>= k = \ r -> k (f r) r
This only makes sense if m ~ (->) b. Here the arrow (->) is a type constructor, and (->) a b is the same as a -> b.
So it means that if we calculate the type of liftM2 (==) id, we derive the following:
liftM2 (==) :: m a -> m a -> m Bool
id :: (b -> b)
-------------------------------------------
m ~ (->) b, a ~ b
This thus means that the output type of liftM2 (==) id is liftM2 (==) id :: (Monad m, Eq a) => m a -> m Bool, but we need to "specialize" this with the knowledge we obtained: that m a is (->) b and a is the same type as b, so:
liftM2 (==) id :: (Monad m, Eq a) => m a -> m Bool
-> liftM2 (==) id :: (Monad m, Eq a) => (b -> a) -> (b -> Bool)
-> liftM2 (==) id :: Eq b => (b -> b) -> (b -> Bool)
-> liftM2 (==) id :: Eq b => (b -> b) -> b -> Bool
In short the function is still "monadic", although by using id, you have selected a specific monad, and thus the function is no longer applicable to all sorts of monads, only to the (->) r monad.

When is forall not for all

In the program below test₁ will not compile but test₂ will. The reason seems to be because of the forall s. in withModulus₁. It seems that the s is a different type for each and every call to withModulus₁ because of the forall s.. Why is that the case?
{-# LANGUAGE
GADTs
, KindSignatures
, RankNTypes
, TupleSections
, ViewPatterns #-}
module Main where
import Data.Reflection
newtype Modulus :: * -> * -> * where
Modulus :: a -> Modulus s a
deriving (Eq, Show)
newtype M :: * -> * -> * where
M :: a -> M s a
deriving (Eq, Show)
add :: Integral a => Modulus s a -> M s a -> M s a -> M s a
add (Modulus m) (M a) (M b) = M (mod (a + b) m)
mul :: Integral a => Modulus s a -> M s a -> M s a -> M s a
mul (Modulus m) (M a) (M b) = M (mod (a * b) m)
unM :: M s a -> a
unM (M a) = a
withModulus₁ :: a -> (forall s. Modulus s a -> w) -> w
withModulus₁ m k = k (Modulus m)
withModulus₂ :: a -> (Modulus s a -> w) -> w
withModulus₂ m k = k (Modulus m)
test₁ = withModulus₁ 89 (\m ->
withModulus₁ 7 (\m' ->
let
a = M 131
b = M 127
in
unM $ add m' (mul m a a) (mul m b b)))
test₂ = withModulus₂ 89 (\m ->
withModulus₂ 7 (\m' ->
let
a = M 131
b = M 127
in
unM $ add m' (mul m a a) (mul m b b)))
Here is the error message:
Modulus.hs:41:29: error:
• Couldn't match type ‘s’ with ‘s1’
‘s’ is a rigid type variable bound by
a type expected by the context:
forall s. Modulus s Integer -> Integer
at app/Modulus.hs:(35,9)-(41,52)
‘s1’ is a rigid type variable bound by
a type expected by the context:
forall s1. Modulus s1 Integer -> Integer
at app/Modulus.hs:(36,11)-(41,51)
Expected type: M s1 Integer
Actual type: M s Integer
• In the second argument of ‘add’, namely ‘(mul m a a)’
In the second argument of ‘($)’, namely
‘add m' (mul m a a) (mul m b b)’
In the expression: unM $ add m' (mul m a a) (mul m b b)
• Relevant bindings include
m' :: Modulus s1 Integer (bound at app/Modulus.hs:36:28)
m :: Modulus s Integer (bound at app/Modulus.hs:35:27)
|
41 | unM $ add m' (mul m a a) (mul m b b)))
| ^^^^^^^^^
Briefly put, a function
foo :: forall s . T s -> U s
lets its caller to choose what the type s is. Indeed, it works on all types s. By comparison,
bar :: (forall s . T s) -> U
requires that its caller provides an argument x :: forall s. T s, i.e. a polymorphic value that will work on all types s. This means that bar will choose what the type s will be.
For instance,
foo :: forall a. a -> [a]
foo x = [x,x,x]
is obvious. Instead,
bar :: (forall a. a->a) -> Bool
bar x = x 12 > length (x "hello")
is more subtle. Here, bar first uses x choosing a ~ Int for x 12, and then uses x again choosing a ~ String for x "hello".
Another example:
bar2 :: Int -> (forall a. a->a) -> Bool
bar2 n x | n > 10 = x 12 > 5
| otherwise = length (x "hello") > 7
Here a is chosen to be Int or String depending on n > 10.
Your own type
withModulus₁ :: a -> (forall s. Modulus s a -> w) -> w
states that withModulus₁ must be allowed to choose s to any type it wishes. When calling this as
withModulus₁ arg (\m -> ...)
m will have type Modulus s0 a where a was chosen by the caller, while s was chosen by withModulus₁ itself. It is required that ... must be compatible with any choice withModulus₁ may take.
What if we nest calls?
withModulus₁ arg (\m1 -> ...
withModulus₁ arg (\m2 -> ...)
...
)
Now, m1 :: Modulus s0 a as before. Further m2 :: Modulus s1 a where s1 is chosen by the innermost call to withModulus₁.
The crucial point, here, is that there is no guarantee that s0 is chosen to be the same as s1. Each call might make a different choice: see e.g. bar2 above which indeed does so.
Hence, the compiler can not assume that s0 and s1 are equal. Hence, if we call a function that requires their equality, like add, we get a type error, since this would constrain the freedom of choice of s by the two withModulus₁ calls.

define type as Monad

I'm trying to run the code from:
http://citeseerx.ist.psu.edu/viewdoc/download?doi=10.1.1.39.8039&rep=rep1&type=pdf
using ghci 7.6.3
{-# LANGUAGE LiberalTypeSynonyms, TypeSynonymInstances #-}
type C m a = (a -> Action m) -> Action m
data Action m = Atom (m (Action m)) | Fork (Action m) (Action m) | Stop
This original form:
instance (Monad m) => Monad (C m) where
f >>= k = \c -> f (\a -> k a c)
return x = \c -> c x
gives this error:
Type synonym `C' should have 2 arguments, but has been given 1
In the instance declaration for `Monad (C m)'
Trying with the additional argument:
instance (Monad m) => Monad (C m b) where
f >>= k = \c -> f (\a -> k a c)
return x = \c -> c x
shows this error:
Kind mis-match
The first argument of `Monad' should have kind `* -> *',
but `C m b' has kind `*'
In the instance declaration for `Monad (C m b)'
How to correct this definition? Thanks
Partially applied type synonyms can't be type class instances, and the only way to avoid that in this case is to make this a data or newtype declaration.
You will have to change the definition of C to make this work to e.g.
newtype C m a = C ((a -> Action m) -> Action m)

Pattern matching on rank-2 type

I'm trying to understand why one version of this code compiles, and one version does not.
{-# LANGUAGE RankNTypes, FlexibleContexts #-}
module Foo where
import Data.Vector.Generic.Mutable as M
import Data.Vector.Generic as V
import Control.Monad.ST
import Control.Monad.Primitive
data DimFun v m r =
DimFun {dim::Int, func :: v (PrimState m) r -> m ()}
runFun1 :: (Vector v r, MVector (Mutable v) r) =>
(forall m . (PrimMonad m) => DimFun (Mutable v) m r) -> v r -> v r
runFun1 (DimFun dim t) x | V.length x == dim = runST $ do
y <- thaw x
t y
unsafeFreeze y
runFun2 :: (Vector v r, MVector (Mutable v) r) =>
(forall m . (PrimMonad m) => DimFun (Mutable v) m r) -> v r -> v r
runFun2 t x = runST $ do
y <- thaw x
evalFun t y
unsafeFreeze y
evalFun :: (PrimMonad m, MVector v r) => DimFun v m r -> v (PrimState m) r -> m ()
evalFun (DimFun dim f) y | dim == M.length y = f y
runFun2 compiles fine (GHC-7.8.2), but runFun1 results in errors:
Could not deduce (PrimMonad m0) arising from a pattern
from the context (Vector v r, MVector (Mutable v) r)
bound by the type signature for
tfb :: (Vector v r, MVector (Mutable v) r) =>
(forall (m :: * -> *). PrimMonad m => TensorFunc m r) -> v r -> v r
at Testing/Foo.hs:(26,8)-(28,15)
The type variable ‘m0’ is ambiguous
Note: there are several potential instances:
instance PrimMonad IO -- Defined in ‘Control.Monad.Primitive’
instance PrimMonad (ST s) -- Defined in ‘Control.Monad.Primitive’
In the pattern: TensorFunc _ f
In an equation for ‘tfb’:
tfb (TensorFunc _ f) x
= runST
$ do { y <- thaw x;
f y;
unsafeFreeze y }
Couldn't match type ‘m0’ with ‘ST s’
because type variable ‘s’ would escape its scope
This (rigid, skolem) type variable is bound by
a type expected by the context: ST s (v r)
at Testing/Foo.hs:(29,26)-(32,18)
Expected type: ST s ()
Actual type: m0 ()
Relevant bindings include
y :: Mutable v s r (bound at Testing/Foo.hs:30:3)
f :: forall (v :: * -> * -> *).
MVector v r =>
v (PrimState m0) r -> m0 ()
(bound at Testing/Foo.hs:29:19)
In a stmt of a 'do' block: f y
In the second argument of ‘($)’, namely
‘do { y <- thaw x;
f y;
unsafeFreeze y }’
Could not deduce (s ~ PrimState m0)
from the context (Vector v r, MVector (Mutable v) r)
bound by the type signature for
tfb :: (Vector v r, MVector (Mutable v) r) =>
(forall (m :: * -> *). PrimMonad m => TensorFunc m r) -> v r -> v r
at Testing/Foo.hs:(26,8)-(28,15)
‘s’ is a rigid type variable bound by
a type expected by the context: ST s (v r) at Testing/Foo.hs:29:26
Expected type: Mutable v (PrimState m0) r
Actual type: Mutable v s r
Relevant bindings include
y :: Mutable v s r (bound at Testing/Foo.hs:30:3)
f :: forall (v :: * -> * -> *).
MVector v r =>
v (PrimState m0) r -> m0 ()
(bound at Testing/Foo.hs:29:19)
In the first argument of ‘f’, namely ‘y’
In a stmt of a 'do' block: f y
I'm pretty sure the rank-2 type is to blame, possibly caused by a monomorphism restriction. However, as suggested in a previous question of mine, I enabled -XNoMonomorphismRestriction, but got the same error.
What is the difference between these seemingly identical code snippets?
I think that having a rough mental model of the type-level plumbing involved here is essential, so I'm going go talk about "implicit things" in a bit more detail, and scrutinize your problem only after that. Readers only interested in the direct solution to the question may skip to the "Pattern matching on polymorhpic values" subsection and the end.
1. Implicit function arguments
Type arguments
GHC compiles Haskell to a small intermediate language called Core, which is essentially a rank-n polymorphic typed lambda calculus called System F (plus some extensions). Below I am going use Haskell alongside a notation somewhat resembling Core; I hope it's not overly confusing.
In Core, polymorphic functions are functions which take types as additional arguments, and arguments further down the line can refer to those types or have those types:
-- in Haskell
const :: forall (a :: *) (b :: *). a -> b -> a
const x y = x
-- in pseudo-Core
const' :: (a :: *) -> (b :: *) -> a -> b -> a
const' a b x y = x
This means that we must also supply type arguments to these functions whenever we want to use them. In Haskell type inference usually figures out the type arguments and supplies them automatically, but if we look at the Core output (for example, see this introduction for how to do that), type arguments and applications are visible everywhere. Building a mental model of this makes figuring out higher-rank code a whole lot easier:
-- Haskell
poly :: (forall a. a -> a) -> b -> (Int, b)
poly f x = (f 0, f x)
-- pseudo-Core
poly' :: (b :: *) -> ((a :: *) -> a -> a) -> b -> (Int, b)
poly' b f x = (f Int 0, f b x)
And it makes clear why some things don't typecheck:
wrong :: (a -> a) -> (Int, Bool)
wrong f = (f 0, f True)
wrong' :: (a :: *) -> (a -> a) -> (Int, Bool)
wrong' a f = (f ?, f ?) -- f takes an "a", not Int or Bool.
Class constraint arguments
-- Haskell
show :: forall a. Show a => a -> String
show x = show x
-- pseudo-Core
show' :: (a :: *) -> Show a -> a -> String
show' a (ShowDict showa) x = showa x
What is ShowDict and Show a here? ShowDict is just a Haskell record containing a show instance, and GHC generates such records for each instance of a class. Show a is just the type of this instance record:
-- We translate classes to a record type:
class Show a where show :: a -> string
data Show a = ShowDict (show :: a -> String)
-- And translate instances to concrete records of the class type:
instance Show () where show () = "()"
showUnit :: Show ()
showUnit = ShowDict (\() -> "()")
For example, whenever we want to apply show, the compiler has to search the scope in order to find a suitable type argument and an instance dictionary for that type. Note that while instances are always top level, quite often in polymorphic functions the instances are passed in as arguments:
data Foo = Foo
-- instance Show Foo where show _ = "Foo"
showFoo :: Show Foo
showFoo = ShowDict (\_ -> "Foo")
-- The compiler fills in an instance from top level
fooStr :: String
fooStr = show' Foo showFoo Foo
polyShow :: (Show a, Show b) => a -> b -> String
polyShow a b = show a ++ show b
-- Here we get the instances as arguments (also, note how (++) also takes an extra
-- type argument, since (++) :: forall a. [a] -> [a] -> [a])
polyShow' :: (a :: *) -> (b :: *) -> Show a -> Show b -> a -> b -> String
polyShow' a b (ShowDict showa) (ShowDict showb) a b -> (++) Char (showa a) (showb b)
Pattern matching on polymorphic values
In Haskell, pattern matching on functions doesn't make sense. Polymorphic values can be also viewed as functions, but we can pattern match on them, just like in OP's erroneous runfun1 example. However, all the implicit arguments must be inferable in the scope, or else the mere act of pattern matching is a type error:
import Data.Monoid
-- it's a type error even if we don't use "a" or "n".
-- foo :: (forall a. Monoid a => (a, Int)) -> Int
-- foo (a, n) = 0
foo :: ((a :: *) -> Monoid a -> (a, Int)) -> Int
foo f = ? -- What are we going to apply f to?
In other words, by pattern matching on a polymorphic value, we assert that all implicit arguments have been already applied. In the case of foo here, although there isn't a syntax for type application in Haskell, we can sprinkle around type annotations:
{-# LANGUAGE ScopedTypeVariables, RankNTypes #-}
foo :: (forall a. Monoid a => (a, Int)) -> Int
foo x = case (x :: (String, Int)) of (_, n) -> n
-- or alternatively
foo ((_ :: String), n) = n
Again, pseudo-Core makes the situation clearer:
foo :: ((a :: *) -> Monoid a -> (a, Int)) -> Int
foo f = case f String monoidString of (_ , n) -> n
Here monoidString is some available Monoid instance of String.
2. Implicit data fields
Implicit data fields usually correspond to the notion of "existential types" in Haskell. In a sense, they are dual to implicit function arguments with respect to term obligations:
When we construct functions, the implicit arguments are available in the function body.
When we apply functions, we have extra obligations to fulfill.
When we construct data with implicit fields, we must supply those extra fields.
When we pattern match on data, the implicit fields also come into scope.
Standard example:
{-# LANGUAGE GADTs #-}
data Showy where
Showy :: forall a. Show a => a -> Showy
-- pseudo-Core
data Showy where
Showy :: (a :: *) -> Show a -> a -> Showy
-- when constructing "Showy", "Show a" must be also available:
someShowy :: Showy
someShowy = Showy (300 :: Int)
-- in pseudo-Core
someShowy' = Showy Int showInt 300
-- When pattern matching on "Showy", we get an instance in scope too
showShowy :: Showy -> String
showShowy (Showy x) = show x
showShowy' :: Showy -> String
showShowy' (Showy a showa x) = showa x
3. Taking a look at OP's example
We have the function
runFun1 :: (Vector v r, MVector (Mutable v) r) =>
(forall m . (PrimMonad m) => DimFun (Mutable v) m r) -> v r -> v r
runFun1 dfun#(DimFun dim t) x | V.length x == dim = runST $ do
y <- thaw x
t y
unsafeFreeze y
Remember that pattern matching on polymorphic values asserts that all implicit arguments are available in the scope. Except that here, at the point of pattern matching there is no m at all in scope, let alone a PrimMonad instance for it.
With GHC 7.8.x it's is good practice to use type holes liberally:
runFun1 :: (Vector v r, MVector (Mutable v) r) =>
(forall m . (PrimMonad m) => DimFun (Mutable v) m r) -> v r -> v r
runFun1 (DimFun dim t) x | V.length x == dim = _
Now GHC will duly display the type of the hole, and also the types of the variables in the context. We can see that t has type Mutable v (PrimState m0) r -> m0 (), and we also see that m0 is not listed as bound anywhere. Indeed, it is a notorious "ambiguous" type variable conjured up by GHC as a placeholder.
So, why don't we try manually supplying the arguments, just as in the prior example with the Monoid instance? We know that we will use t inside an ST action, so we can try fixing m as ST s and GHC automatically applies the PrimMonad instance for us:
runFun1 :: forall v r. (Vector v r, MVector (Mutable v) r) =>
(forall m . (PrimMonad m) => DimFun (Mutable v) m r) -> v r -> v r
runFun1 (DimFun dim (t :: Mutable v s r -> ST s ())) x
| V.length x == dim = runST $ do
y <- thaw x
t y
unsafeFreeze y
... except it doesn't work and we get the error "Couldn't match type ‘s’ with ‘s1’ because type variable ‘s1’ would escape its scope".
It turns out - comes as no surprise - that we've forgotten about yet another implicit argument. Recall the type of runST:
runST :: (forall s. ST s a) -> a
We can imagine that runST takes a function of type ((s :: PrimState ST) -> ST s a), and then our code looks like this:
runST $ \s -> do
y <- thaw x -- y :: Mutable v s r
t y -- error: "t" takes a "Mutable v s r" with a different "s".
unsafeFreeze y
The s in t's argument type is silently introduced at the outermost scope:
runFun1 :: forall v s r. ...
And thus the two s-es are distinct.
A possible solution is to pattern match on the DimFun argument inside the ST action. There, the correct s is in scope, and GHC can supply ST s as m:
runFun1 :: forall v r. (Vector v r, MVector (Mutable v) r) =>
(forall m . PrimMonad m => DimFun (Mutable v) m r) -> v r -> v r
runFun1 dimfun x = runST $ do
y <- thaw x
case dimfun of
DimFun dim t | dim == M.length y -> t y
unsafeFreeze y
With some parameters made explicit:
runST $ \s -> do
y <- thaw x
case dimfun (ST s) primMonadST of
DimFun dim t | dim == M.length y -> t y
unsafeFreeze y
As an exercise, let's convert all of the function to pseudo-Core (but let's not desugar the do syntax, because that would be way too ugly):
-- the full types of the functions involved, for reference
thaw :: forall m v a. (PrimMonad m, V.Vector v a) => v a -> m (V.Mutable v (PrimState m) a)
runST :: forall a. (forall s. ST s a) -> a
unsafeFreeze :: forall m v a. (PrimMonad m, Vector v a) => Mutable v (PrimState m) a -> v a
M.length :: forall v s a. MVector v s a -> Int
(==) :: forall a. Eq a => a -> a -> Bool
runFun1 ::
(v :: * -> *) -> (r :: *)
-> Vector v r -> MVector (Mutable v) r
-> ((m :: (* -> *)) -> PrimMonad m -> DimFun (Mutable v) m r)
-> v r -> v r
runFun1 v r vecInstance mvecInstance dimfun x = runST r $ \s -> do
y <- thaw (ST s) v r primMonadST vecInstance x
case dimFun (ST s) primMonadST of
DimFun dim t | (==) Int eqInt dim (M.length v s r y) -> t y
unsafeFreeze (ST s) v r primMonadST vecInstance y
That was a mouthful.
Now we are well-equipped to explain why runFun2 worked:
runFun2 :: (Vector v r, MVector (Mutable v) r) =>
(forall m . (PrimMonad m) => DimFun (Mutable v) m r) -> v r -> v r
runFun2 t x = runST $ do
y <- thaw x
evalFun t y
unsafeFreeze y
evalFun :: (PrimMonad m, MVector v r) => DimFun v m r -> v (PrimState m) r -> m ()
evalFun (DimFun dim f) y | dim == M.length y = f y
evalFun is just a polymorphic function that gets called in the right place (we ultimately pattern match on t in the right place), where the correct ST s is available as the m argument.
As a type system gets more sophisticated, pattern matching becomes a progressively more serious affair, with far-reaching consequences and non-trivial requirements. At the end of the spectrum you find full-dependent languages and proof assistants such as Agda, Idris or Coq, where pattern matching on a piece of data can mean accepting an arbitrary logical proposition as true in a certain branch of your program.
Though #AndrasKovacs gave a great answer, I think it is worth pointing out how to avoid this nastiness altogether. This answer to a related question by me shows how the "correct" definition for DimFun makes all of the rank-2 stuff go away.
By defining DimFun as
data DimFun v r =
DimFun {dim::Int, func :: forall s . (PrimMonad s) => v (PrimState s) r -> s ()}
runFun1 becomes:
runFun1 :: (Vector v r)
=> DimFun (Mutable v) r -> v r -> v r
runFun1 (DimFun dim t) x | dim == V.length x = runST $ do
y <- thaw x
t y
unsafeFreeze y
and compiles without issue.
Pattern-match on a constrained value is not allowed, I think. In particular, you could use a pattern-match, but only for a GADT constructor that fixed the type(s) in the constraint and choose a specific instance. Otherwise, I get the ambiguous type variable error.
That is, I don't think that GHC can unify the type of a value matching the pattern (DimFun dim t) with the type (forall m . (PrimMonad m) => DimFun (Mutable v) m r).
Note that the pattern match in evalFun looks similar, but it is allowed to put constraints on m since the quantification is scoped over the whole evalFun; in constrast, runFun1 as a smaller scope for the quantification of m.
HTH

Strange type error in Haskell let-expression -- what's the issue?

I came across a frustrating something in Haskell today.
Here's what happened:
I wrote a function in ghci and gave it a type signature
ghci complained about the type
I removed the type signature
ghci accepted the function
I checked the inferred type
the inferred type was exactly the same as the type I tried to give it
I was very distressed
I discovered that I could reproduce the problem in any let-expression
Gnashing of teeth; decided to consult with the experts at SO
Attempt to define the function with a type signature:
Prelude Control.Monad> let myFilterM f m = do {x <- m; guard (f x); return x} :: (MonadPlus m) => (b -> Bool) -> m b -> m b
<interactive>:1:20:
Inferred type is less polymorphic than expected
Quantified type variable `b' is mentioned in the environment:
m :: (b -> Bool) -> m b -> m b (bound at <interactive>:1:16)
f :: (m b -> m b) -> Bool (bound at <interactive>:1:14)
Quantified type variable `m' is mentioned in the environment:
m :: (b -> Bool) -> m b -> m b (bound at <interactive>:1:16)
f :: (m b -> m b) -> Bool (bound at <interactive>:1:14)
In the expression:
do { x <- m;
guard (f x);
return x } ::
(MonadPlus m) => (b -> Bool) -> m b -> m b
In the definition of `myFilterM':
myFilterM f m
= do { x <- m;
guard (f x);
return x } ::
(MonadPlus m) => (b -> Bool) -> m b -> m b
Defined the function without a type signature, checked the inferred type:
Prelude Control.Monad> let myFilterM f m = do {x <- m; guard (f x); return x}
Prelude Control.Monad> :t myFilterM
myFilterM :: (MonadPlus m) => (b -> Bool) -> m b -> m b
Used the function for great good -- it worked properly:
Prelude Control.Monad> myFilterM (>3) (Just 4)
Just 4
Prelude Control.Monad> myFilterM (>3) (Just 3)
Nothing
My best guess as to what is going on:
type annotations somehow don't work well with let-expressions, when there's a do-block.
For bonus points:
is there a function in the standard Haskell distribution that does this? I was surprised that filterM does something very different.
The problem is the precedence of the type operator (::). You're trying to describe the type of myFilterM but what you're actually doing is this:
ghci> let myFilterM f m = (\
do {x <- m; guard (f x); return x} \
:: \
(MonadPlus m) => (b -> Bool) -> m b -> m b)\
)
(backslashes inserted for readability only, not legit ghci syntax)
Do you see the issue? I get the same problem for something simple like
ghci> let f x = x + 1 :: (Int -> Int)
<interactive>:1:15:
No instance for (Num (Int -> Int))
arising from the literal `1'
Possible fix: add an instance declaration for (Num (Int -> Int))
In the second argument of `(+)', namely `1'
In the expression: x + 1 :: Int -> Int
In an equation for `f': f x = x + 1 :: Int -> Int
The solution is to attach the type signature to the proper element:
ghci> let f :: Int -> Int ; f x = x + 1
ghci> let myFilterM :: (MonadPlus m) => (b -> Bool) -> m b -> m b; myFilterM f m = do {x <- m; guard (f x); return x}
And for bonus points, you want mfilter (hoogle is your friend).
This is likely just an issue of type annotation syntax and binding precendence. If you write your example as,
let myFilterM :: (MonadPlus m) => (b -> Bool) -> m b -> m b; myFilterM f m = do {x <- m; guard (f x); return x}
then GHCi will give you a high-five and send you on your way.
I don't know what kind of compiler you use, but on my platform (GHC 7.0.3) I get a simple type mismatch:
$ ghci
GHCi, version 7.0.3: http://www.haskell.org/ghc/ :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer-gmp ... linking ... done.
Loading package base ... linking ... done.
Loading package ffi-1.0 ... linking ... done.
Prelude> :m +Control.Monad
Prelude Control.Monad> let myFilterM f m = do {x <- m; guard (f x); return x} :: (MonadPlus m) => (b -> Bool) -> m b -> m b
<interactive>:1:30:
Could not deduce (t1 ~ ((b1 -> Bool) -> m1 b1 -> m1 b1))
from the context (MonadPlus m)
bound by the inferred type of
myFilterM :: MonadPlus m => t -> t1 -> (b -> Bool) -> m b -> m b
at <interactive>:1:5-100
or from (MonadPlus m1)
bound by an expression type signature:
MonadPlus m1 => (b1 -> Bool) -> m1 b1 -> m1 b1
at <interactive>:1:21-100
`t1' is a rigid type variable bound by
the inferred type of
myFilterM :: MonadPlus m => t -> t1 -> (b -> Bool) -> m b -> m b
at <interactive>:1:5
In a stmt of a 'do' expression: x <- m
In the expression:
do { x <- m;
guard (f x);
return x } ::
MonadPlus m => (b -> Bool) -> m b -> m b
In an equation for `myFilterM':
myFilterM f m
= do { x <- m;
guard (f x);
return x } ::
MonadPlus m => (b -> Bool) -> m b -> m b
<interactive>:1:40:
Could not deduce (t ~ ((m1 b1 -> m1 b1) -> Bool))
from the context (MonadPlus m)
bound by the inferred type of
myFilterM :: MonadPlus m => t -> t1 -> (b -> Bool) -> m b -> m b
at <interactive>:1:5-100
or from (MonadPlus m1)
bound by an expression type signature:
MonadPlus m1 => (b1 -> Bool) -> m1 b1 -> m1 b1
at <interactive>:1:21-100
`t' is a rigid type variable bound by
the inferred type of
myFilterM :: MonadPlus m => t -> t1 -> (b -> Bool) -> m b -> m b
at <interactive>:1:5
The function `f' is applied to one argument,
but its type `t' has none
In the first argument of `guard', namely `(f x)'
In a stmt of a 'do' expression: guard (f x)
Prelude Control.Monad>
I guess the problem lies in the fact, that the :: does not reaches the argument. This small variation (note the separate type declaration)
let myFilterM f m = do {x <- m; guard (f x); return x}; myFilterM :: (MonadPlus m) => (b -> Bool) -> m b -> m b
runs without problems. It may be related to the new type-checker in GHC 7.

Resources