Sittampalam, Ganesh wrote:
Can't you write two recursive modules with <- that depend on
each other, so that there's no valid initialisation order?

Contrived example follows:

module Module1 where

glob1 :: IORef Int
glob1 <- mod2 >>= newIORef
mod1 :: IO Int
mod1 = readIORef glob1

module Module2 where

glob2 :: IORef Int
glob2 <- mod1 >>= newIORef
mod2 :: IO Int
mod2 = readIORef glob2

Immediatly breaking my promise to shut up..

This is illegal because you're only allowed to use ACIO in top level <-
bindings and readIORef isn't (and clearly could not be) ACIO.

Regards
--
Adrian Hey

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

Reply via email to