
Hi I am trying to implement Show for a storable-mutable-vector. Does anyone have a clue why the type-system is killing me :-) Code is below... Cheers Felix ---- {-# LANGUAGE ExistentialQuantification #-} import Control.Monad (liftM2) import qualified Data.Vector.Unboxed as V import qualified Data.Vector.Unboxed.Mutable as MV import Data.Vector.Storable.Mutable import GHC.Prim (RealWorld) import Control.Monad.Primitive import Control.Monad import qualified Data.Vector as VEC import qualified Data.Vector.Generic.Mutable as GM import Data.Int import Data.Typeable.Internal import Data.Primitive data Row = forall m s. (Storable s, MV.Unbox s, Prim s, PrimMonad m) => Row (MV.MVector (PrimState m) s) instance Show Row where show (Row row) = do let xx = MV.read row 0 "Done" main :: IO () main = do print "Done" I get this error: Could not deduce (PrimState m ~ PrimState m0) from the context (Storable s, MV.Unbox s, Prim s, PrimMonad m) bound by a pattern with constructor Row :: forall (m :: * -> *) s. (Storable s, MV.Unbox s, Prim s, PrimMonad m) => MV.MVector (PrimState m) s -> Row, in an equation for `show' NB: `PrimState' is a type function, and may not be injective Expected type: MV.MVector (PrimState m0) s Actual type: MV.MVector (PrimState m) s In the first argument of `MV.read', namely `row' In the expression: MV.read row 0

Hi, Fixie,
Sadly, I've heard that data type contexts are "widely considered a
misfeature, and is going to be removed from the language." see
http://www.haskell.org/ghc/docs/7.6.1/html/users_guide/data-type-extensions....
Moreover, when Row explicitly takes its type arguments, the use of
ScopedTypeVariables lets you do the following:
https://github.com/nushio3/practice/blob/master/show/storable-mutable-vector...
Best,
2012/12/3 Fixie Fixie
Hi
I am trying to implement Show for a storable-mutable-vector.
Does anyone have a clue why the type-system is killing me :-)
Code is below...
Cheers
Felix
----
{-# LANGUAGE ExistentialQuantification #-}
import Control.Monad (liftM2) import qualified Data.Vector.Unboxed as V import qualified Data.Vector.Unboxed.Mutable as MV import Data.Vector.Storable.Mutable import GHC.Prim (RealWorld) import Control.Monad.Primitive import Control.Monad import qualified Data.Vector as VEC import qualified Data.Vector.Generic.Mutable as GM import Data.Int import Data.Typeable.Internal import Data.Primitive
data Row = forall m s. (Storable s, MV.Unbox s, Prim s, PrimMonad m) => Row (MV.MVector (PrimState m) s)
instance Show Row where show (Row row) = do let xx = MV.read row 0 "Done"
main :: IO () main = do print "Done"
I get this error:
Could not deduce (PrimState m ~ PrimState m0) from the context (Storable s, MV.Unbox s, Prim s, PrimMonad m) bound by a pattern with constructor Row :: forall (m :: * -> *) s. (Storable s, MV.Unbox s, Prim s, PrimMonad m) => MV.MVector (PrimState m) s -> Row, in an equation for `show' NB: `PrimState' is a type function, and may not be injective Expected type: MV.MVector (PrimState m0) s Actual type: MV.MVector (PrimState m) s In the first argument of `MV.read', namely `row' In the expression: MV.read row 0
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Takayuki MURANUSHI The Hakubi Center for Advanced Research, Kyoto University http://www.hakubi.kyoto-u.ac.jp/02_mem/h22/muranushi.html
participants (2)
-
Fixie Fixie
-
Takayuki Muranushi