[Haskell-cafe] Haskell Propeganda
Krzysztof Skrzętnicki
gtener at gmail.com
Sat Aug 23 18:49:34 EDT 2008
You can get nice exception (but not segfault) when trying to fire this code:
> {-# OPTIONS_GHC -XRecursiveDo #-}
>
> module Main where
>
> import Control.Concurrent
> import Control.Monad.Fix
>
> loopChan :: IO (Chan ())
> loopChan = mdo chan <- dupChan chan
> return chan
>
> main = do
> c <- loopChan
> writeChan c ()
You just can't use a duplicate of a channel to create itself.
> Prelude> :l loop_channel.hs
> [1 of 1] Compiling LC ( loop_channel.hs, interpreted )
> Ok, modules loaded: LC.
> *LC> :type loopChan
> loopChan :: IO (Chan ())
> *LC> c <- loopChan
> *** Exception: <>
Still I don't think it's a bug, but merely complicated way to crash
your program.
Haskell is great, but it also has many pitfalls, just like any other language.
Christopher Skrzętnicki
On Sun, Aug 24, 2008 at 00:15, Daniel Fischer <daniel.is.fischer at web.de> wrote:
> Am Samstag, 23. August 2008 23:17 schrieb Thomas Davie:
>>
>> I'd be interested to see your other examples -- because that error is
>> not happening in Haskell! You can't argue that Haskell doesn't give
>> you no segfaults, because you can embed a C segfault within Haskell.
>>
>> Bob
>
> Use ST(U)Arrays, and use unsafeWrite because you do the indexchecking
> yourself. Then be stupid and confuse two bounds so that you actually write
> beyond the array bounds.
> I've had that happen _once_.
> But if you explicitly say you want it unsafe, you're prepared for it :)
>
> Daniel
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
More information about the Haskell-Cafe
mailing list