Suggestion for module system (to get rid of many uses of unsafePerformIO)

Stephen Dolan stedolan at gmail.com
Sun May 20 14:21:11 EDT 2007


unsafePerformIO is possibly the most ugly feature of Haskell, yet is
necessary to do many things which should be possible without it, such
as reading configuration from a file at startup or creating global
IORefs, e.g

module Main where
import Data.IORef
a = unsafePerformIO $ newIORef 42
fac n = product [1..n]
main = do
 val <- readIORef a
 putStrLn $ show (fac val)

This can be avoided by putting everything in the monad in main, i.e.
module Main where
import Data.IORef
main = do
a <- unsafePerformIO $ newIORef 42
let fac n = product [1..n]
let mainFunc = do
 val <- readIORef a
 putStrLn $ show (fac val)
mainFunc

However, this approach does not work for modules which need to do
their own initialisation with the current module system.

I propose that it be legal to write things like this:
MyModule.hs:
fac n = product [1..n]
do
 ref <- newIORef 42
 module MyModule (ref, fac)

and then, in a different file, write this:
module Main where
main = do
 import qualified MyModule as M -- implies evaluating newIORef
 val <- readIORef M.ref
 putStrLn $ show (M.fac val)

The statement "module <name> [(<exported symbols>)]" would,
informally, give a value of type Module. This would not be a
first-class type, so it can't be passed around or bound to a variable.
So,
do
 ref <- newIORef 42
 module MyModule (ref, fac)
 writeIORef ref 43
would be illegal, since if you expand the do-notation, it is trying to
pass around an object of type "IO Module". So, in the previous
example, Main :: Module and MyModule :: IO Module. The only valid
operation you can perform on a module is to import it, so while import
Main would be valid anywhere, import MyModule would only be valid in
the IO monad, and would cause the line "ref <- newIORef 42" to be run
when the IO action was executed. Following lexical scoping rules, its
symbols would only be accessible in the do-block it was imported into,
so the IORef "ref" could never "escape" from the IO monad.

This would also mean that if main were run twice, each run would see a
different IORef for "ref", since the call to newIORef has, in effect,
been included into main. If the module were imported in two different
places, both places would see different values for "ref", since the
evaluation of newIORef has been done twice.

Would this be useful, useless, or just downright silly?
Thanks,
Stephen Dolan


More information about the Haskell-prime mailing list