Reputation: 4326
I am trying to write a dynamic STVector
that will be expanded within a ST monad
(for an imperative algorithm) when the vector capacity is exceeded. To do that, I created a new data constructor that wraps a STVector
, and add an Int
to keep track of last inserted vector. The problem is I am getting error from typechecker because it seems my state implementation isn't correct. I will appreciate pointers on how to correctly manage state for DVec s
in the example below:
{-# LANGUAGE BangPatterns #-}
module Test where
import Data.Vector.Unboxed.Mutable as MU
import Control.Monad.ST as ST
import Control.Monad.Primitive (PrimState)
import GHC.Float.RealFracMethods (int2Float)
type MVI1 s = MVector (PrimState (ST s)) Int
data DVec s = DV {-# UNPACK #-}!Int -- this one keeps track of index of last vector
(MVI1 s)
append :: DVec s -> Int -> ST s (DVec s)
append (DV i v) x = do
if i < MU.length v then MU.unsafeWrite v i x >> return $ DV (i+1) v
else MU.unsafeGrow v (floor $ 1.5 * (int2Float $ MU.length v)) >>= (\y -> MU.unsafeWrite y i x >> return $ DV (i+1) y)
Error from typechecker:
Couldn't match type `s' with `PrimState ((->) (DVec s))'
`s' is a rigid type variable bound by
the type signature for append :: DVec s -> Int -> ST s (DVec s)
at B.hs:11:11
Expected type: MVector (PrimState ((->) (DVec s))) Int
Actual type: MVI1 s
In the first argument of `unsafeWrite', namely `y'
In the first argument of `(>>)', namely `unsafeWrite y i x'
In the expression: unsafeWrite y i x >> return
Upvotes: 2
Views: 297
Reputation: 3480
The problem is that the $
operator has the least precedence and, thus, everything to the left of it is treated as one function.
Instead of return $ DV (i+1) v
use return (DV (i+1) v)
.
How did I figure this out?
I removed your type annotation to see what type will ghci determine. Ghci detected a type with this constraint (Control.Monad.Primitive.PrimMonad ((->) (DVec (PrimState m)))
. This means that there is something wrong which makes ghci think that the PrimMonad
in use is also a function. It then became obvious that ($)
is the reason behind this.
Upvotes: 4