Hi,
What do folk out there think to the idea of having a std module
in Haskell which contains dynamic environment info.
things I mean are
progName :: String
args :: String
and maybe funs like
getProperties :: FileName -> PropertyLookup
(obviously this getProperties fn whould have to memoise the file contents
to preserve referential transparency).
This would be an alternative to definitions like
installationRoot = "/usr/local/"
instead we could write
installationRoot = lookup "IROOT" Globals.env
Also I was thinking that other modules could "export" values as being
reflective and the compiled code could register these values
at load-time into a list
reflections :: [(FullyQualifiedName,Dynamic)]
and values could be requested from it a la...
lookup :: a -> Name -> Maybe a
Where the initial "a" is needed to make it all typesafe
If we had this we could implement additive code
i.e. rather than
myImageReader :: String -> IO Image
myImageReader name
= case (getExtension name) of
BMP -> Bmp.readBmp name
JMG -> Jpg.readJpg name
_ -> error "unknown type"
we could implement
myImageReader :: String -> IO Image
myImageReader name
= case (Reflect.lookup (bot::String -> IO Image) (makeFnName name) Just
f -> f name
Nothing -> error "unknown type"
i.e. passing "myfile.bmp" to makeFnName gives
"Bmp.readBmp"
and passing "x.yz" to it gives
"Yz.readYz"
since the list of reflections is built at load time we can extend this
functionality by simply linking extra modules with it
i.e.
main.o can read no file types
main.o + bmp.o can read bitmaps
main.o + bmp.o + jpg.o can read bmps and jpgs
i.e. we do not have to exit case statements and extend types to
add extra functionality
in Bmp.hs say we could have
module Bmp where
import Image
reflect readBmp
readBmp :: String -> IO Image
...
which would get munged to
module Bmp where
import Image
-- This gets appended to the global reflection list at load time --
[("Bmp.readBmp",toDynamic readBmp)]
readBmp :: String -> IO Image
...
All of this means that the meaning of the code is not the following
eval main userAndLibraryDefs
but the following
eval main (userAndLibraryDefs + LoadTimeDefs)
and we still have ref. transparency
Comments / Flames ?
Chris