[Haskell] Real life examples

Keean Schupke k.schupke at imperial.ac.uk
Wed Nov 24 10:48:56 EST 2004


Having admited to wavering on the edge of accepting top level TWIs, perhaps
one of the supporters would like to comment on qualified importing... IE 
what
happens to the unique property if I import 2 copies like so:

    module Main where

    import Library as L1
    import Library as L2

Although each library's internal state is initialised once, as required, 
any real
IO could lead to problems... With the device driver example I now have two
bits of code that think they have exclusive access to the device... But 
I can do:

    L1.readFromDevice
    L2.readFromDevice

Comments?

    Keean.

Ben Rudiak-Gould wrote:

> John Meacham wrote:
>
> > randomIO [...] Data.Unique [...] Atom.hs [...] caching
>
> These are all great examples of cases where having per-process state 
> makes sense.
>
> But they can all be implemented with George Russell's library plus 
> safe (pure) uses of unsafePerformIO. I hope his library or something 
> like it will become a part of the standard distribution, and there's 
> nothing wrong with having (pure) functions in the standard library 
> which can't be implemented in Haskell, so I don't think these examples 
> are sufficient on their own to justify a language extension. I'd still 
> like to see an example of something that can be done with top-level <- 
> but is inconvenient or impossible with George Russell's library.
>
> >This is not a minor performance gain. in ginsu it dropped the memory
> >usage from > 100megs to 10megs. I would call that vital. when it used
> >100megs it was not a usable program.
>
> Not that I think implementing Atom with a global hashtable is a bad 
> idea, but I'm curious where in that range the memory usage would be if 
> you defined
>
>    type Atom = PackedString
>    toAtom = packString
>    fromAtom = unpackPS
>
> -- Ben
>
> _______________________________________________
> Haskell mailing list
> Haskell at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell




More information about the Haskell mailing list