Reputation: 569
I have a binding for a type [ST s (Int, [Int])]
and I am trying to apply runST
to each element using map as follows:
name :: [ST s (Int, [Int])] --Of Course there is a real value here
map runST name
This gives me an error message
Couldn't match expected type `forall s. ST s b0'
with actual type `ST s0 (Int, [Int])'
Expected type: [forall s. ST s b0]
Actual type: [ST s0 (Int, [Int])]
In the second argument of `map', namely `name'
In the expression: map runST name
There must be something I am misunderstanding. I am aware of runST and function composition, but am unsure if this applies.
Thanks for everyones time!
Upvotes: 14
Views: 1371
Reputation: 24764
I'll try to explain the reasoning for runST
's type:
runST :: (forall s. ST s a) -> a
And why it isn't like this simple one:
alternativeRunST :: ST s a -> a
Note that this alternativeRunST
would had worked for your program.
alternativeRunST
would also had allowed us to leak variables out of the ST
monad:
leakyVar :: STRef s Int
leakyVar = alternativeRunST (newSTRef 0)
evilFunction :: Int -> Int
evilFunction x =
alternativeRunST $ do
val <- readSTRef leakyVar
writeSTRef leakyVar (val+1)
return (val + x)
Then you could go in ghci and do:
>>> map evilFunction [7,7,7]
[7,8,9]
evilFunction
is not referentially transparent!
Btw, to try it out yourself here's the "bad ST" framework needed to run the code above:
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
import Control.Monad
import Data.IORef
import System.IO.Unsafe
newtype ST s a = ST { unST :: IO a } deriving Monad
newtype STRef s a = STRef { unSTRef :: IORef a }
alternativeRunST :: ST s a -> a
alternativeRunST = unsafePerformIO . unST
newSTRef :: a -> ST s (STRef s a)
newSTRef = ST . liftM STRef . newIORef
readSTRef :: STRef s a -> ST s a
readSTRef = ST . readIORef . unSTRef
writeSTRef :: STRef s a -> a -> ST s ()
writeSTRef ref = ST . writeIORef (unSTRef ref)
The real runST
doesn't allow us to construct such "evil" functions. How does it do it? It's kinda tricky, see below:
Trying to run:
>>> runST (newSTRef "Hi")
error:
Couldn't match type `a' with `STRef s [Char]'
...
>>> :t runST
runST :: (forall s. ST s a) -> a
>>> :t newSTRef "Hi"
newSTRef "Hi" :: ST s (STRef s [Char])
newSTRef "Hi"
doesn't fit (forall s. ST s a)
. As can be also seen using an even simpler example, where GHC gives us a pretty nice error:
dontEvenRunST :: (forall s. ST s a) -> Int
dontEvenRunST = const 0
>>> dontEvenRunST (newSTRef "Hi")
<interactive>:14:1:
Couldn't match type `a0' with `STRef s [Char]'
because type variable `s' would escape its scope
Note that we can also write
dontEvenRunST :: forall a. (forall s. ST s a) -> Int
And it is equivalent to omitting the forall a.
as we did before.
Note that the scope of a
is larger than that of s
, but in the case of newSTRef "Hi"
its value should depend on s
. The type system doesn't allow this.
Upvotes: 5
Reputation: 127751
Your name
is not polymorphic enough. Your statement
name :: [ST s (Int, [Int])]
means 'a list of stateful computations returning (Int, [Int]) which have exactly the same s
'. But look at the type of runST
:
runST :: (forall s. ST s a) -> a
This type means 'a function which takes a stateful computation where s
can be anything you can ever imagine'. These types of computation is not the same thing. And finally:
map runST :: [forall s. ST s a] -> [a]
You see, your list should contain more polymorphic values than it do now. s
type could be different in each element of the list, it may not be the same type as in name
. Change the type signature of name
, and all should be OK. It may require some extensions to be enabled, but GHC should be able to tell you which ones.
Upvotes: 6
Reputation: 7751
Each time you run a state transformer with runST
, it operates on some local state that is separate from all other state transformers. runST
creates a new state type and calls its argument with that type. So, for example, if you execute
let x = runST (return ())
y = runST (return ())
in (x, y)
then the first return ()
and second return ()
will have different types: ST s1 ()
and ST s2 ()
, for some unknown types s1
and s2
that are created by runST
.
You are trying to call runST
with an argument that has state type s
. That is not the state type that runST
creates, nor is any other type you can choose. To call runST
, you must pass an argument that can have any state type. Here is an example:
r1 :: forall s. ST s ()
r1 = return ()
Because r1
is polymorphic, its state can have any type, including whatever type is selected by runST
. You can map runST
over a list of polymorphic r1
s (with -XImpredicativeTypes
):
map runST ([r1, r1] :: [forall t. ST t ()])
However, you cannot map runST
over a list of non-polymorphic r1
s.
map runST ([r1, r1] :: forall t. [ST t ()]) -- Not polymorphic enough
The type forall t. [ST t ()]
says that all list elements have state type t
. But they need to all have independent state types because runST
is called on each one. That is what the error message means.
If it is okay to give the same state to all list elements, then you can call runST
once as shown below. The explicit type signature is not required.
runST (sequence ([r1, r1] :: forall t. [ST t ()]))
Upvotes: 15