[Haskell-cafe] runST readSTRef type error

2011-05-04 Thread Ken Takusagawa II
I run into the following type error:

foo :: ST s (STRef s Int) - Int
foo p = (runST (p = readSTRef))

with ghc 6.12.1
st.hs:8:16:
Couldn't match expected type `s1' against inferred type `s'
  `s1' is a rigid type variable bound by
   the polymorphic type `forall s1. ST s1 a' at st.hs:8:9
  `s' is a rigid type variable bound by
  the type signature for `foo' at st.hs:7:10
  Expected type: ST s1 (STRef s Int)
  Inferred type: ST s (STRef s Int)
In the first argument of `(=)', namely `p'
In the first argument of `runST', namely `(p = readSTRef)'

However, if I add
{-# LANGUAGE RankNTypes #-}

and change the type signature to
foo :: (forall s.ST s (STRef s Int)) - Int

it works.  I don't fully understand what's going on here.

Is this the right way to fix the problem?  Are there other options?
My gut feeling is, for such a simple use case of the ST monad, I
shouldn't need such a big hammer as RankNTypes.

--ken

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] runST readSTRef type error

2011-05-04 Thread Edward Z. Yang
Hello Ken,

Strictly speaking, you only need Rank-2 types.  This indeed the right
way to fix the problem. 

Cheers,
Edward

Excerpts from Ken Takusagawa II's message of Wed May 04 02:00:49 -0400 2011:
 I run into the following type error:
 
 foo :: ST s (STRef s Int) - Int
 foo p = (runST (p = readSTRef))
 
 with ghc 6.12.1
 st.hs:8:16:
 Couldn't match expected type `s1' against inferred type `s'
   `s1' is a rigid type variable bound by
the polymorphic type `forall s1. ST s1 a' at st.hs:8:9
   `s' is a rigid type variable bound by
   the type signature for `foo' at st.hs:7:10
   Expected type: ST s1 (STRef s Int)
   Inferred type: ST s (STRef s Int)
 In the first argument of `(=)', namely `p'
 In the first argument of `runST', namely `(p = readSTRef)'
 
 However, if I add
 {-# LANGUAGE RankNTypes #-}
 
 and change the type signature to
 foo :: (forall s.ST s (STRef s Int)) - Int
 
 it works.  I don't fully understand what's going on here.
 
 Is this the right way to fix the problem?  Are there other options?
 My gut feeling is, for such a simple use case of the ST monad, I
 shouldn't need such a big hammer as RankNTypes.
 
 --ken
 

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] runST readSTRef type error

2011-05-04 Thread Maciej Marcin Piechotka
On Wed, 2011-05-04 at 02:00 -0400, Ken Takusagawa II wrote:
 I run into the following type error:
 
 foo :: ST s (STRef s Int) - Int
 foo p = (runST (p = readSTRef))
 
 with ghc 6.12.1
 st.hs:8:16:
 Couldn't match expected type `s1' against inferred type `s'
   `s1' is a rigid type variable bound by
the polymorphic type `forall s1. ST s1 a' at st.hs:8:9
   `s' is a rigid type variable bound by
   the type signature for `foo' at st.hs:7:10
   Expected type: ST s1 (STRef s Int)
   Inferred type: ST s (STRef s Int)
 In the first argument of `(=)', namely `p'
 In the first argument of `runST', namely `(p = readSTRef)'
 
 However, if I add
 {-# LANGUAGE RankNTypes #-}
 
 and change the type signature to
 foo :: (forall s.ST s (STRef s Int)) - Int
 
 it works.  I don't fully understand what's going on here.
 
 Is this the right way to fix the problem?  Are there other options?
 My gut feeling is, for such a simple use case of the ST monad, I
 shouldn't need such a big hammer as RankNTypes.
 
 --ken

To make the interface of ST works - i.e. to keeps it pure the signature
of runST is:

 runST :: (forall s. ST s a) - a

Otherwise consider following code:

 incST :: Num a = STRef s a - ST s a
 incST r = readSTRef r = \v - writeSTRef r (v + 1)  return v

 add :: STRef s Int - Int - Int
 add r x = runST (incST r = \v - return (v + x))

 test :: [Int]
 test = runST (newSTRef 0) = \r - map (add r) [1,2,3]

What is the result?

And what is the result of:

 test2 :: [Int]
 test2 = runST (newSTRef 0) = \r - map (add r) (map (add r) [1,2,3])

Regards


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe