MaiaVictor
MaiaVictor

Reputation: 52987

How do you create a function like "Data.Vector.modify", that receives a list?

Data.Vector has the following function:

modify :: (forall s. MVector s a -> ST s ()) -> Vector a -> Vector a

Is it possible to create a function such as:

modify :: [(forall s. MVector s a -> ST s ())] -> Vector a -> Vector a

I've tried

{-# LANGUAGE RankNTypes, ImpredicativeTypes #-}

import qualified Data.Vector.Mutable as MV
import qualified Data.Vector as V
import Control.Monad.ST
import Control.Monad.Primitive

unsafeModify :: [(forall s . MV.MVector s Int -> ST s ())] -> V.Vector Int -> V.Vector Int
unsafeModify mods vec = runST $ do
    mvec <- V.unsafeThaw vec
    sequence_ (map ($ mvec) mods)
    V.unsafeFreeze mvec

But I get the error

Muts.hs:11:28:
    Couldn't match type ‘forall s1. V.MVector s1 Int -> ST s1 ()’
                  with ‘V.MVector s Int -> ST s a0’
    Expected type: [V.MVector s Int -> ST s a0]
      Actual type: [forall s. V.MVector s Int -> ST s ()]
    Relevant bindings include
      mvec :: V.MVector s Int (bound at Muts.hs:10:5)
    In the second argument of ‘map’, namely ‘mods’
    In the first argument of ‘sequence’, namely ‘(map ($ mvec) mods)’

Upvotes: 2

Views: 131

Answers (4)

Zeta
Zeta

Reputation: 105886

Change the type of unsafeModify. In particular, float the forall s. outside of the list. You want all your functions to share the same state token (which is determined by runST), therefore you don't need to have every function potentially using another s:

{-# LANGUAGE RankNTypes #-}

import qualified Data.Vector.Mutable as MV
import qualified Data.Vector as V
import Control.Monad (mapM_)
import Control.Monad.ST
import Control.Monad.Primitive

unsafeModify :: (forall s . [MV.MVector s Int -> ST s ()]) -> V.Vector Int -> V.Vector Int
unsafeModify mods vec = runST $ do
    mvec <- V.unsafeThaw vec
    mapM_ ($ mvec) mods
    V.unsafeFreeze mvec

Upvotes: 3

Daniel Wagner
Daniel Wagner

Reputation: 152767

The usual trick is to box up your functions, thus:

data Box a = Box { unBox :: forall s. MVector s a -> ST s () }
modifyAll :: [Box a] -> Vector a -> Vector a
modifyAll fs = modify (\mvector -> mapM_ (\b -> unBox b mvector) fs)

Upvotes: 3

Andr&#225;s Kov&#225;cs
Andr&#225;s Kov&#225;cs

Reputation: 30103

When type checking, GHC only ever instantiates type variables with monomorphic types. Since map :: (a -> b) -> [a] -> [b], this already rules out your intended usage, since a would have to be instantiated to forall s. MVector s a -> ST s (), and that can't happen. This is one reason why ImpredicativeTypes is barely usable with GHC.

Since we'cant use the usual higher-order flow control functions, we have to write out an explicit recursive function:

{-# LANGUAGE ScopedTypeVariables #-}

unsafeModify :: [(forall s . MV.MVector s Int -> ST s ())] -> V.Vector Int -> V.Vector Int
unsafeModify mods vec = runST $ do
  (mvec :: MV.MVector s Int) <- V.unsafeThaw vec

  let go :: [(forall s . MV.MVector s Int -> ST s ())] -> ST s (V.Vector Int)
      go [] = V.unsafeFreeze mvec
      go (mod:mods) = do
        mod mvec
        go mods

  go mods

ScopedTypeVariables is also necessary, because we want the s in the return type of go to be the same s with which we bind mvec.

Upvotes: 1

ErikR
ErikR

Reputation: 52039

This works for me:

{-# LANGUAGE RankNTypes, ImpredicativeTypes #-}

import qualified Data.Vector as V
import qualified Data.Vector.Mutable as MV
import Control.Monad.ST

vmods :: [ forall s. ( V.MVector s a -> ST s () ) ] -> V.Vector a  -> V.Vector a
vmods [] v = v
vmods (m:ms) v = vmods ms $ V.modify m v

m1 v = MV.write v 0 'x'
m2 v = MV.write v 1 'y'
m3 v = MV.write v 2 'z'

test = vmods [m1,m2,m3] $ V.replicate 3 'a'

Upvotes: 1

Related Questions