[Haskell-cafe] I don't understand how ST works

Nicu Ionita nicu.ionita at acons.at
Thu Jun 7 23:42:23 CEST 2012


Hi,

After trying the whole afternoon to make a program work using ST and 
mutable vectors, I must give up and ask for some help.

I have a pure function which generates a list of moves. But the whole 
thing should live in the ST monad, so:

 > genMoves ... = runST $ do ...

Now, as I understand, I have a private universe (under runST) in which I 
can run "impure code", from which nothing escapes to the outside.

Now in that universe I prepare succesively (and use later) a data 
structure which contains pure and impure values, for example:

 > data MList = MList { mlVec :: MVector s Move, mlNextPh :: MList -> ST 
s (Maybe MList) }

Now comes my question: in the impure values there is always that "s". I 
was thinking that the whole structure should have s as a parameter:

 > data MList s = MList { mlVec :: MVector s Move, mlNextPh :: MList -> 
ST s (Maybe (MList s)) }

but then, when I define functions like:

 > splitMove :: MList s -> ST s (Maybe (Move, MList s))
 > splitMove ml = do
 >      m <- unsafeRead (mvVec ml) 0
 >      ...

I get this message:

Moves\MoveList.hs:217:28:
     Couldn't match type `s' with `PrimState (ST s)'
       `s' is a rigid type variable bound by
           the type signature for
             splitMove :: MList s -> ST s (Maybe (Move, MList s))
           at Moves\MoveList.hs:210:1
     Expected type: U.MVector (PrimState (ST s)) Move
          Actual type: U.MVector s Move
     In the return type of a call of `mlVec'
     In the first argument of `M.unsafeRead', namely `(mlVec ml)'

which really doesn't make sense, as the package primitive defines the 
instance:

instance PrimMonad (ST s) where
type PrimState (ST s) = s
primitive = ST
internal (ST p) = p

Should I do the structure agnostic of that s-state? (forall s. ...) This 
seems really unintuitive to me...

Anybody some hint?

Thanks,
Nicu



More information about the Haskell-Cafe mailing list