[Haskell] Real life examples
Keean Schupke
k.schupke at imperial.ac.uk
Wed Nov 24 06:31:19 EST 2004
Okay, I have reconsidered, and I think I would be happy with top-level TWI's
providing they can be qualified on import, for example:
module Main where
import Library as L1
import Library as L2
main :: IO ()
main = do
L1.do_something_with_library
L2.do_something_with_library
Keean.
John Meacham wrote:
[i've cut this becuse its long...]
>data AtomHash = ...
>data Atom = ... (abstract)
>
>instance Ord Atom
>instance Eq Atom
>newAtomHash :: IO AtomHash
>toAtom :: AtomHash -> String -> IO Atom
>fromAtom :: AtomHash -> Atom -> IO String
>
>
>note a couple things:
>
>1. The pure functions now are stuck in the IO monad, since I made their
>dependence on AtomHash explicit, the fact that they modify AtomHash must
>be made explicit by placing them in the IO monad. (it is possible to
>come up with other formulations not in the IO monad, but they would have
>similar problems) This alone is almost enough to kill the idea, but even
>worse is the second
>
>
>2. The fundamental property that there is an isomorphism between Atoms
>and Strings is broken. because one might create multiple AtomHashs.
>Suddenly what was a STATIC COMPILE TIME GUARENTEE becomes a run-time
>obscure bug generating probelem.
>
>
>furthermore, imagine you carefully avoided ever creating more than one
>AtomHash, what purpose does it serve to pass everywhere then? it is
>meerly a source of confusion and obfuscation. and someone could come
>along to use your library, call 'newAtomHash' and break everything in a
>way that would be very tricky to debug.
>
>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.
>
>
More information about the Haskell
mailing list