Actually, I Think I'm wrong - I think its not even safe if you cannot export the '<-' def. If any functions which use it are exported you are in the same situation. I cannot say the kind of code in the example I gave is good, can you? Infact the availability of these top level IO actions seems to completely change the feel of the language...

   Keean.

Keean Schupke wrote:

Well lets say:

    userInit <- oneShot realInit

where realInit defines an MVar used for state storage that is used in module A to implement
an accumulator. Now module B does some maths using the accumulator, and module C does
some maths using the accumulator. If Main uses functions defined in both B and C then they
will both be trying to use the _same_ MVar to store their state in - which will result in the wrong answer. The following is a contrived example, If arith and geom were in the same module, this would be an error on the programmers part. But consider if A were in the standard libraries, and B and C were two orthogonal extensions by different authors, do we really want the situation where they break each other. Note: this does not apply to declarations like (i=4) as this is true for all time. The problem is essentially that the declaration in the example is mutable. If mutable-declarations are not exportable, you can reasonably say it is the module authors job to make sure all uses of the MVar are consistent.


module A
   mVarA <- newMVar 1

   acc :: Int -> IO ()
   acc i = writeMVar mVarA (readMVar mVarA + i)

   val :: IO Int
   val = readMVar mVarA

module B
   import A

   arith :: IO [Int]
   arith = do
      i <- val
      acc (7+val)
      j <- arith
      return (i:j)

module C
   import A

   geom :: IO [Int]
   geom = do
      i <- val
      acc (7*val)
      j <- geom
      return (i:j)

module D
   import B
   import C

   main = do
      a <- arith
      g <- geom
      putStrLn $ show (take 100 a)
      putStrLn $ show (take 100 g)

Keean

Adrian Hey wrote:

On Saturday 13 Nov 2004 9:15 am, Keean Schupke wrote:


I'm not sure I understand what problem you think there is. Are the inits
you're talking about module inits? If so, I don't think there's a problem,
for several reasons.


The idea under discussion is that a top level (x <- newThing) should
be lazy, (no action at all occurs until value of x is demanded). IOW,
it's exactly the same as the current unsafePerformIO hack, but not unsafe
because the compiler knows the semantics. So there is no implied "module
initialisation"

Okay - I can see that with lazy semantics this might not be a problem...
What happens with
the second problem: That where module B uses A internally and C uses A
internally, then
I write a new module that tries to use B & C together... This
potentially breaks B & C. I think
you need the extra restriction that the top level '<-' bindings must not
be exported. So where
does that leave us.


Top level inits are safe (I think) iff:
- They are lazy (the definition only happens when required)
- They contain only a subset of IO actions - namely those concerned
with name creation within Haskell that don't actually do any IO.
- They are not exportable from the module that contains them.


I think that covers it... have I forgotten anything?


One of us has :-) Not sure who though.

I thought I'd covered the second problem you're alluding to already.
But if you think there's still a problem you'd better elaborate a little
more. Certainly I see no reason why top level TWI's cannot be exported
from a module. We don't have this constraint with the unsafePerformIO
hack.

For instance, if I had

userInit <- oneShot realInit

is there any reason why userInit can't be safely exported and used
in many different modules? The whole idea was that it should be.

Regards
--
Adrian Hey








_______________________________________________
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



_______________________________________________ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe


_______________________________________________
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to