Re: [Haskell] Incoherent instances can make ST monad unsound

2006-01-26 Thread Thomas Jäger
On Thu, 2006-01-26 at 20:29 -0800, [EMAIL PROTECTED] wrote:
> circumstances, many things break, including the ST monad. One can
> indeed break the essential guarantee of the ST monad -- for example,
> create a top level STRef *and* fruitfully use in arbitrary ST
> computations. The enclosed code does exactly that. Thus,
> unsafePerformST becomes expressible in Haskell, given enough
> features. The presence of top-level mutable cells breaks the
> referential transparency. Hopefully the authors of Haskell' and
> Haskell2 would attach all-upper-case warnings to these extensions.

I don't think this is the extensions' fault; the problem is rather a
bogus Typeable instance which basically gives you unsafeCoerce#. In
fact, the code below compiles without any extensions and also breaks
pretty much every static guarantee.


import Data.Typeable
import Data.Dynamic

newtype Foo a = Foo { runFoo :: a ()}
newtype Const a b = Const { runConst :: a }

instance Typeable (Foo a) where
  typeOf _ = mkTyConApp (mkTyCon "Anything goes") []

coerce :: a -> b
coerce = runConst . runFoo . flip fromDyn undefined . toDyn . Foo .Const


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


[Haskell] Incoherent instances can make ST monad unsound

2006-01-26 Thread oleg

In the recent message about regions I wrote:
> Typeable constraint has reduced the problem of 'region nesting' to the
> regular problem of the 'linearity' of computations -- which is already
> solved in ST monad. We can add that pervasive 's' type parameter to
> our Q and IOM types. However, the simpler approach is just to use our
> 'mark' as that 's' parameter.

A small qualification should be added: although adding the 's'
parameter in addition to the unexported Z parameter we had before is
sound in all circumstances, the `simpler approach' may actually fail:
it is possible to declare an instance "Typeable a" -- and given enough
extensions, persuade GHC *and* Hugs to accept the code. The problem
with IO regions would be the least of our worries however: in these
circumstances, many things break, including the ST monad. One can
indeed break the essential guarantee of the ST monad -- for example,
create a top level STRef *and* fruitfully use in arbitrary ST
computations. The enclosed code does exactly that. Thus,
unsafePerformST becomes expressible in Haskell, given enough
features. The presence of top-level mutable cells breaks the
referential transparency. Hopefully the authors of Haskell' and
Haskell2 would attach all-upper-case warnings to these extensions.

The code below runs with GHC 6.4.1 (extensions are indicated
inline). It also runs with Hugs, as  hugs -98 +O /tmp/st.hs


{-# OPTIONS -fglasgow-exts #-}
{-# OPTIONS -fallow-undecidable-instances #-}
{-# OPTIONS -fallow-overlapping-instances #-}
{-# OPTIONS -fallow-incoherent-instances #-}

module STTest where

import Control.Monad.ST
import Data.Typeable
import Data.STRef
import Data.Dynamic

instance Typeable a where
typeOf _ = mkTyConApp (mkTyCon "Anything goes") []


-- test1 = runST ( newSTRef 'a' )
leakedST = runST ( newSTRef 'a' >>= return . toDyn )

test3 :: Char
test3 = runST (readSTRef $ ((fromDyn leakedST undefined)::STRef s Char))

{- result:

*STTest> leakedST
<>
*STTest> test3
'a'
-}
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


[Haskell] Re: ST Monad and all that

2005-07-11 Thread Srinivas Nedunuri



OK, thanks for the references. I think I've got a 
better handle on what's what. The library documentation mentions the ability to 
convert the ST monad into an IO monad. What are the reasons/pluses/minuses of 
doing this? (I can see one reason being that you won't have to use monad 
transformers to try and thread two different monads through your 
code).
 
Also, I didn't see any mention of a mutable List - 
I suppose you have to use Data.Array.ST?
 
cheers
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Re: ST Monad and all that

2005-07-08 Thread Wolfgang Jeltsch
Am Freitag, 8. Juli 2005 18:50 schrieb Peter Eriksen:
> "Srinivas Nedunuri" <[EMAIL PROTECTED]> writes:
> > Hello, in trying to understand how to use the ST Monad I've come across
> > references to a bewildering variety of related types such as STRefs,
> > STArrays, MutVar, ArrayRef, IORef, IOArray, ArrRef, etc. the list goes
> > on. Is there a place where I can get a comprehensive explanation of
> > what's what?
>
> Well, a page on the Haskell Wiki tries to be that,
> but is in need of a lot more exampels and explanation.
> It gives examples of uses of the ST monad.  The
> page very appropriately named
>
> http://haskell.org/hawiki/ImperativeHaskell
>
> Hopes, it can be of some help.  Regards
>
> Peter

It would probably a good thing if this wiki page would also cover the 
differences between LazyST and StrictST.

Best wishes,
Wolfgang
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


[Haskell] Re: ST Monad and all that

2005-07-08 Thread Peter Eriksen
"Srinivas Nedunuri" <[EMAIL PROTECTED]> writes:

> Hello, in trying to understand how to use the ST Monad I've come across 
> references to a bewildering variety of related types such as STRefs, 
> STArrays, MutVar, ArrayRef, IORef, IOArray, ArrRef, etc. the list goes on. Is 
> there a place where I can get a comprehensive explanation of what's what? 

Well, a page on the Haskell Wiki tries to be that, 
but is in need of a lot more exampels and explanation.
It gives examples of uses of the ST monad.  The
page very appropriately named

http://haskell.org/hawiki/ImperativeHaskell 

Hopes, it can be of some help.  Regards

Peter

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


Re: [Haskell] ST Monad and all that

2005-07-08 Thread Wolfgang Jeltsch
Am Freitag, 8. Juli 2005 12:48 schrieb Srinivas Nedunuri:
> Hello, in trying to understand how to use the ST Monad I've come across
> references to a bewildering variety of related types such as STRefs,
> STArrays, MutVar, ArrayRef, IORef, IOArray, ArrRef, etc. the list goes on.
> Is there a place where I can get a comprehensive explanation of what's
> what? Its a bit fustrating trying to figure out how these concepts relate
> to each other by reading snippets of information on different web sites and
> papers (e.g. "State in Haskell").
>
> Thanks for your help

Hello Srinivas,

some of these identifiers are just outdated and replaces by more current ones.  
For example, as far as I know, STRef is the new name for MutVar.  You might 
want to have a look at GHC's library documentation at

http://haskell.org/ghc/docs/latest/html/libraries/index.html

although this might not give enough information for you.

Best wishes,
Wolfgang
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


[Haskell] ST Monad and all that

2005-07-08 Thread Srinivas Nedunuri



Hello, in trying to understand how to use the ST 
Monad I've come across references to a bewildering variety of related types such 
as STRefs, STArrays, MutVar, 
ArrayRef, IORef, IOArray, ArrRef, etc. the list goes on. Is there a place 
where I can get a comprehensive explanation of what's what? Its a bit fustrating 
trying to figure out how these concepts relate to each other by reading snippets 
of information on different web sites and papers (e.g. "State in 
Haskell").
 
Thanks for your help
 
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


st monad

2002-01-29 Thread Andre W B Furtado



How do I find the implementation of the module ST? 
In the GHC documentation, I can only find the signatures of the 
functions.


Re: Type problem with ST monad

1999-04-23 Thread Olaf Chitil

Sigbjorn Finne wrote:
> forwarding to the mailing list is restricted to off-hours only at the
> moment, but thought I'd suggest a solution to you before then - use a
> (universally quantified) pattern matching function rather than a
> pattern binding, i.e.,
> 
>  deTIM :: TIM s a -> ST s a
>  deTIM (TIM m) = m
> 
>  runTIM :: (forall s. TIM s a) -> Maybe a
>  runTIM m = runST (deTIM m)

Thank you very much.
I thought I had tried this, but now I note that when I used the projection I
forgot to give the type signature for runTIM... 
Maybe you could mention this problem its solution in the ghc manual section
about second order types.

-- 
OLAF CHITIL, Lehrstuhl fuer Informatik II, RWTH Aachen, 52056 Aachen, Germany
 Tel: (+49/0)241/80-21212; Fax: (+49/0)241/-217
 URL: http://www-i2.informatik.rwth-aachen.de/~chitil/






Type problem with ST monad

1999-04-23 Thread Olaf Chitil


Hi, 

I have a problem with defining a new monad based on the state monad ST.
The new monad is a combination of ST and the Maybe monad. It is intended for
computations that use many states and may fail. If a part of the computation
fails the whole computation fails. (I want to use it for type inference).

newtype TIM s a = TIM (ST s (Maybe a))

Defining the Monad and MonadPlus instance and lifting the variable access
functions is straightforward.

However, I don't know how to define a function runTIM similar to runST which
executes the monad. The obvious definition

runTIM :: (forall s. TIM s a) -> Maybe a
runTIM (TIM m) = runST m

is rejected by both hugs -98 and ghc-4.03, because pattern matching on
polymorphic values is not permitted.

So, how can I define runTIM ???

-- 
OLAF CHITIL, Lehrstuhl fuer Informatik II, RWTH Aachen, 52056 Aachen, Germany
 Tel: (+49/0)241/80-21212; Fax: (+49/0)241/-217
 URL: http://www-i2.informatik.rwth-aachen.de/~chitil/