[Haskell-cafe] Functional dependency failure
Alexander Pakhomov
ker0sin at ya.ru
Tue Sep 2 20:45:37 UTC 2014
Hi!
I have following code:
STRead.hs:
import Control.Monad.Reader
import Control.Monad.ST
import qualified Data.Vector.Mutable as MV
import qualified Data.Vector as V
type ReadVecMonad s = ReaderT (MV.MVector s Int) (ST s)
freezeV :: ReadVecMonad s (V.Vector Int)
freezeV = ask >>= lift V.freeze
Trying to compile this I have "Couldn't match type ... When using functional dependencies to combine" error
following with kind mismatch and type with literaly the same type mismatch.
How can I work this around?
There's full error message:
STRead.hs:9:11:
Couldn't match type `V.MVector s Int'
with `(->)
(V.MVector
(Control.Monad.Primitive.PrimState
(ReaderT (V.MVector s Int) (ST s)))
Int)'
When using functional dependencies to combine
MonadReader r (ReaderT r m),
arising from the dependency `m -> r'
in the instance declaration in `Control.Monad.Reader.Class'
MonadReader
((->)
(V.MVector
(Control.Monad.Primitive.PrimState
(ReaderT (V.MVector s Int) (ST s)))
Int))
(ReaderT (V.MVector s Int) (ST s)),
arising from a use of `ask' at STRead.hs:9:11-13
In the first argument of `(>>=)', namely `ask'
In the expression: ask >>= lift V.freeze
STRead.hs:9:19:
Couldn't match kind `* -> *' with `*'
Expected type: (->)
(V.MVector
(Control.Monad.Primitive.PrimState
(ReaderT (V.MVector s Int) (ST s)))
Int)
-> ReaderT (V.MVector s Int) (ST s) (V.Vector Int)
Actual type: (->)
(V.MVector
(Control.Monad.Primitive.PrimState
(ReaderT (V.MVector s Int) (ST s)))
Int)
-> ReaderT (V.MVector s Int) (ST s) (V.Vector Int)
Kind incompatibility when matching types:
(->)
(V.MVector
(Control.Monad.Primitive.PrimState
(ReaderT (V.MVector s Int) (ST s)))
Int) :: * -> *
(->)
(V.MVector
(Control.Monad.Primitive.PrimState
(ReaderT (V.MVector s Int) (ST s)))
Int) :: *
In the return type of a call of `lift'
In the second argument of `(>>=)', namely `lift V.freeze'
STRead.hs:9:24:
Couldn't match kind `*' with `* -> *'
Expected type: V.MVector
(Control.Monad.Primitive.PrimState
(ReaderT (V.MVector s Int) (ST s)))
Int
-> ReaderT (V.MVector s Int) (ST s) (V.Vector Int)
Actual type: V.MVector
(Control.Monad.Primitive.PrimState
(ReaderT (V.MVector s Int) (ST s)))
Int
-> ReaderT (V.MVector s Int) (ST s) (V.Vector Int)
Kind incompatibility when matching types:
(->)
(V.MVector
(Control.Monad.Primitive.PrimState
(ReaderT (V.MVector s Int) (ST s)))
Int) :: *
(->)
(V.MVector
(Control.Monad.Primitive.PrimState
(ReaderT (V.MVector s Int) (ST s)))
Int) :: * -> *
In the first argument of `lift', namely `V.freeze'
In the second argument of `(>>=)', namely `lift V.freeze'
More information about the Haskell-Cafe
mailing list