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

2012-06-09 Thread Nicu Ionita
Ok, the error was: I was using Control.Monad.ST.Lazy. Importing 
Control.Monad.ST compiles immediately without problem. (Is this because 
I'm using unboxed mutable vectors?)


Now, that's a little bit odd.

It's clear that the strict and lazy forms of ST are different types. But 
unfortunately they are named the same! So actually any error message 
from the compiler drives you crazy, because it's refering to another type.


Probably the reason to name the types with the same name is for easy 
interchangeability. But as we see, the types are not (always) 
interchangeable.


Anyway, now it compiles.

Thanks,
Nicu

Am 08.06.2012 23:15, schrieb Nicu Ionita:

Hi,

I created a gist with a minimal (still 111 lines) module:

https://gist.github.com/2898128

I still get the errors:

WhatsWrong.hs:53:5:
Couldn't match type `s' with `PrimState (ST s)'
  `s' is a rigid type variable bound by
  a type expected by the context: ST s [Move] at 
WhatsWrong.hs:48:21

In a stmt of a 'do' block: listMoves ml
In the second argument of `($)', namely
  `do { v - U.new maxMovesPerPos;
let ml = ...;
listMoves ml }'
In the expression:
  runST
  $ do { v - U.new maxMovesPerPos;
 let ml = ...;
 listMoves ml }

WhatsWrong.hs:65:44:
Couldn't match type `s' with `PrimState (ST s)'
  `s' is a rigid type variable bound by
  the type signature for nextPhaseOnlyCapts :: GenPhase s
  at WhatsWrong.hs:64: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 third argument of `genCapts', namely `(mlVec ml)'

Thanks,
Nicu

Am 08.06.2012 02:47, schrieb Silvio Frischknecht:

-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1


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:

Yes


data MList s = MList { mlVec :: MVector s Move, mlNextPh :: MList
-

ST s (Maybe (MList s)) }

you probably meant:

 data MList s = MList { ... , mlNextPh :: Mlist s -  ... }

Now I'm not sure about your exact problem since the following compiles
for me.

 import Data.Vector
 import Data.Vector.Mutable
 import Control.Monad.ST

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

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

Something you always have to watch out for when dealing with ST is not
to return something that depends on s in the last statement (the one
you use runST on). In other words, if you want to return a vector you
have to freeze it, so it's not mutable anymore.

If you still can't figure it out paste some complete example that
doesn't work.

silvio
-BEGIN PGP SIGNATURE-
Version: GnuPG v1.4.11 (GNU/Linux)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org/

iQIcBAEBAgAGBQJP0Uu5AAoJEDLsP+zrbatWKFoP+wYdmAwO3aKPIibOydDwPlcu
GmwWLCDoylhBsA1swskPGZTlBevFFeS0kzDMAhZ2dtR18HHf0TVLFCL6mljgQGhu
YLsT8a2Y5eepPd7CC0wHD7qLH0t6ln/urRhWNnVEGryVHmsIDCBzuKBzopshaaOm
8awNeEbmZApki193r/YJ21Zsxidx4N2tSGCd712ka9Wr7l19RzBukonTy/wNCTtN
1sj54xCKap3MpnQe4L68nep6WjMovnwn5ucPWlouPP5N99/2umiEPDwX3y9moD/Q
VkbYe0HzZtvSX7JJaDM/hJ2dWKHsg5CLdO/aW7Uz3HttTy0/FmvwhxaNAzkmQimw
L4uakvyuw1EJuSAwB5XRfeUL6LDpka165jb8V8Iy2gjYg3aGMwf9VVmObjEAA93s
nvQd+iH1lDe38cbfz8dfQdTakDVYtFNnYL+kXIF1Z7DiS25IThtS0RJRH//E+CZg
MpOtW2LBfa3vwP9NqVryGTAhWFtWHXOtpXfCXOa0+pQNn1zHkTXtIDJ4XoT5qkmd
6GDwFyGfkPZO01qNMoXwj/wBz/eaSa4Vj0qb73jNdNH2MbJ13Ws9Jlp4jwcxbG4a
m/fYV0/6LmPEiV8H9+4cG8nhUP2ie2DJqo8tzdjiaZ7C7TEym9jd6gsljMQ8qiAG
Q7aAmMed/DBlY/Anh2xY
=X9CL
-END PGP SIGNATURE-



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



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


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

2012-06-09 Thread Yves Parès
Oh my god, that was it?
I looked at your code for half an hour, and I've never thought about
that... That is really misleading.
So vector forces you to use strict ST? (That's right:
http://hackage.haskell.org/packages/archive/primitive/0.4.1/doc/html/Control-Monad-Primitive.html#t:PrimMonadshows
that only strict ST has a MonadPrime instance)

It's another plea against the sames names/interface in different modules
pattern, that vector, ST, State, ByteString suffer from.
This (the error messages being misleading), as well as the document being
hard to read (because you never know which type is mentionned, you have to
see to check at the module from which the type comes. And even with that,
it's just a matter of convention: for instance Control.Monad.State exports
the lazy version, but Control.Monad.ST exports the strict one (so that the
default version is closer to IO's behaviour).

I really prefer the approach taken by repa 3: one data family, generic
functions for every flavour and some specific functions for each flavour.
It's not perfect (not standard for instance), but I think such an approach
should be priviledged in the future, it makes things much clearer, and
enable you to choose between working generically (on 'Stuff a' types) or
specifically (either only on 'Stuff Strict' or only on 'Stuff Lazy').
I would be interested to know if someone has other ideas in that respect in
mind.


2012/6/9 Nicu Ionita nicu.ion...@acons.at

 Ok, the error was: I was using Control.Monad.ST.Lazy. Importing
 Control.Monad.ST compiles immediately without problem. (Is this because
 I'm using unboxed mutable vectors?)

 Now, that's a little bit odd.

 It's clear that the strict and lazy forms of ST are different types. But
 unfortunately they are named the same! So actually any error message from
 the compiler drives you crazy, because it's refering to another type.

 Probably the reason to name the types with the same name is for easy
 interchangeability. But as we see, the types are not (always)
 interchangeable.

 Anyway, now it compiles.

 Thanks,
 Nicu

 Am 08.06.2012 23:15, schrieb Nicu Ionita:

  Hi,

 I created a gist with a minimal (still 111 lines) module:

 https://gist.github.com/**2898128 https://gist.github.com/2898128

 I still get the errors:

 WhatsWrong.hs:53:5:
Couldn't match type `s' with `PrimState (ST s)'
  `s' is a rigid type variable bound by
  a type expected by the context: ST s [Move] at
 WhatsWrong.hs:48:21
In a stmt of a 'do' block: listMoves ml
In the second argument of `($)', namely
  `do { v - U.new maxMovesPerPos;
let ml = ...;
listMoves ml }'
In the expression:
  runST
  $ do { v - U.new maxMovesPerPos;
 let ml = ...;
 listMoves ml }

 WhatsWrong.hs:65:44:
Couldn't match type `s' with `PrimState (ST s)'
  `s' is a rigid type variable bound by
  the type signature for nextPhaseOnlyCapts :: GenPhase s
  at WhatsWrong.hs:64: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 third argument of `genCapts', namely `(mlVec ml)'

 Thanks,
 Nicu

 Am 08.06.2012 02:47, schrieb Silvio Frischknecht:

 -BEGIN PGP SIGNED MESSAGE-
 Hash: SHA1

  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:

 Yes

  data MList s = MList { mlVec :: MVector s Move, mlNextPh :: MList
 -

 ST s (Maybe (MList s)) }

 you probably meant:

 data MList s = MList { ... , mlNextPh :: Mlist s -  ... }

 Now I'm not sure about your exact problem since the following compiles
 for me.

 import Data.Vector
 import Data.Vector.Mutable
 import Control.Monad.ST

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

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

 Something you always have to watch out for when dealing with ST is not
 to return something that depends on s in the last statement (the one
 you use runST on). In other words, if you want to return a vector you
 have to freeze it, so it's not mutable anymore.

 If you still can't figure it out paste some complete example that
 doesn't work.

 silvio
 -BEGIN PGP SIGNATURE-
 Version: GnuPG v1.4.11 (GNU/Linux)
 Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org/

 iQIcBAEBAgAGBQJP0Uu5AAoJEDLsP+**zrbatWKFoP+**wYdmAwO3aKPIibOydDwPlcu
 GmwWLCDoylhBsA1swskPGZTlBevFFe**S0kzDMAhZ2dtR18HHf0TVLFCL6mljg**QGhu
 YLsT8a2Y5eepPd7CC0wHD7qLH0t6ln**/**urRhWNnVEGryVHmsIDCBzuKBzopsha**aOm
 8awNeEbmZApki193r/**YJ21Zsxidx4N2tSGCd712ka9Wr7l19**RzBukonTy/wNCTtN
 1sj54xCKap3MpnQe4L68nep6WjMovn**wn5ucPWlouPP5N99/**2umiEPDwX3y9moD/Q
 

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

2012-06-08 Thread Nicu Ionita

Hi,

I created a gist with a minimal (still 111 lines) module:

https://gist.github.com/2898128

I still get the errors:

WhatsWrong.hs:53:5:
Couldn't match type `s' with `PrimState (ST s)'
  `s' is a rigid type variable bound by
  a type expected by the context: ST s [Move] at 
WhatsWrong.hs:48:21

In a stmt of a 'do' block: listMoves ml
In the second argument of `($)', namely
  `do { v - U.new maxMovesPerPos;
let ml = ...;
listMoves ml }'
In the expression:
  runST
  $ do { v - U.new maxMovesPerPos;
 let ml = ...;
 listMoves ml }

WhatsWrong.hs:65:44:
Couldn't match type `s' with `PrimState (ST s)'
  `s' is a rigid type variable bound by
  the type signature for nextPhaseOnlyCapts :: GenPhase s
  at WhatsWrong.hs:64: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 third argument of `genCapts', namely `(mlVec ml)'

Thanks,
Nicu

Am 08.06.2012 02:47, schrieb Silvio Frischknecht:

-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1


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:

Yes


data MList s = MList { mlVec :: MVector s Move, mlNextPh :: MList
-

ST s (Maybe (MList s)) }

you probably meant:

 data MList s = MList { ... , mlNextPh :: Mlist s -  ... }

Now I'm not sure about your exact problem since the following compiles
for me.

 import Data.Vector
 import Data.Vector.Mutable
 import Control.Monad.ST

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

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

Something you always have to watch out for when dealing with ST is not
to return something that depends on s in the last statement (the one
you use runST on). In other words, if you want to return a vector you
have to freeze it, so it's not mutable anymore.

If you still can't figure it out paste some complete example that
doesn't work.

silvio
-BEGIN PGP SIGNATURE-
Version: GnuPG v1.4.11 (GNU/Linux)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org/

iQIcBAEBAgAGBQJP0Uu5AAoJEDLsP+zrbatWKFoP+wYdmAwO3aKPIibOydDwPlcu
GmwWLCDoylhBsA1swskPGZTlBevFFeS0kzDMAhZ2dtR18HHf0TVLFCL6mljgQGhu
YLsT8a2Y5eepPd7CC0wHD7qLH0t6ln/urRhWNnVEGryVHmsIDCBzuKBzopshaaOm
8awNeEbmZApki193r/YJ21Zsxidx4N2tSGCd712ka9Wr7l19RzBukonTy/wNCTtN
1sj54xCKap3MpnQe4L68nep6WjMovnwn5ucPWlouPP5N99/2umiEPDwX3y9moD/Q
VkbYe0HzZtvSX7JJaDM/hJ2dWKHsg5CLdO/aW7Uz3HttTy0/FmvwhxaNAzkmQimw
L4uakvyuw1EJuSAwB5XRfeUL6LDpka165jb8V8Iy2gjYg3aGMwf9VVmObjEAA93s
nvQd+iH1lDe38cbfz8dfQdTakDVYtFNnYL+kXIF1Z7DiS25IThtS0RJRH//E+CZg
MpOtW2LBfa3vwP9NqVryGTAhWFtWHXOtpXfCXOa0+pQNn1zHkTXtIDJ4XoT5qkmd
6GDwFyGfkPZO01qNMoXwj/wBz/eaSa4Vj0qb73jNdNH2MbJ13Ws9Jlp4jwcxbG4a
m/fYV0/6LmPEiV8H9+4cG8nhUP2ie2DJqo8tzdjiaZ7C7TEym9jd6gsljMQ8qiAG
Q7aAmMed/DBlY/Anh2xY
=X9CL
-END PGP SIGNATURE-



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


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

2012-06-07 Thread Nicu Ionita

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

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


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

2012-06-07 Thread Silvio Frischknecht
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

 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:

Yes

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

you probably meant:

data MList s = MList { ... , mlNextPh :: Mlist s - ... }

Now I'm not sure about your exact problem since the following compiles
for me.

import Data.Vector
import Data.Vector.Mutable
import Control.Monad.ST

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

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

Something you always have to watch out for when dealing with ST is not
to return something that depends on s in the last statement (the one
you use runST on). In other words, if you want to return a vector you
have to freeze it, so it's not mutable anymore.

If you still can't figure it out paste some complete example that
doesn't work.

silvio
-BEGIN PGP SIGNATURE-
Version: GnuPG v1.4.11 (GNU/Linux)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org/

iQIcBAEBAgAGBQJP0Uu5AAoJEDLsP+zrbatWKFoP+wYdmAwO3aKPIibOydDwPlcu
GmwWLCDoylhBsA1swskPGZTlBevFFeS0kzDMAhZ2dtR18HHf0TVLFCL6mljgQGhu
YLsT8a2Y5eepPd7CC0wHD7qLH0t6ln/urRhWNnVEGryVHmsIDCBzuKBzopshaaOm
8awNeEbmZApki193r/YJ21Zsxidx4N2tSGCd712ka9Wr7l19RzBukonTy/wNCTtN
1sj54xCKap3MpnQe4L68nep6WjMovnwn5ucPWlouPP5N99/2umiEPDwX3y9moD/Q
VkbYe0HzZtvSX7JJaDM/hJ2dWKHsg5CLdO/aW7Uz3HttTy0/FmvwhxaNAzkmQimw
L4uakvyuw1EJuSAwB5XRfeUL6LDpka165jb8V8Iy2gjYg3aGMwf9VVmObjEAA93s
nvQd+iH1lDe38cbfz8dfQdTakDVYtFNnYL+kXIF1Z7DiS25IThtS0RJRH//E+CZg
MpOtW2LBfa3vwP9NqVryGTAhWFtWHXOtpXfCXOa0+pQNn1zHkTXtIDJ4XoT5qkmd
6GDwFyGfkPZO01qNMoXwj/wBz/eaSa4Vj0qb73jNdNH2MbJ13Ws9Jlp4jwcxbG4a
m/fYV0/6LmPEiV8H9+4cG8nhUP2ie2DJqo8tzdjiaZ7C7TEym9jd6gsljMQ8qiAG
Q7aAmMed/DBlY/Anh2xY
=X9CL
-END PGP SIGNATURE-

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