RE: Singletons and Reflection

1999-12-15 Thread Daan Leijen

> If we had implicit parameters then all graphics functions 
> would have types
> (? context :: Context) => (explicit arguments) => IO (result) 
> and the main 
> function would be something like
>do 
>   context <- getContext
>   doBusiness with context=context
> 

The catch is off course that every function with an explicit
type signature:

> explicit arguments -> IO result

needs a new type signature:

>  (?context :: Context) => explicit arguments -> IO result

Here, partial type declarations proposed by Koen Claessen would help.
Those declarations are quite usefull if one plans to use implicit
parameters a lot, allthough they improve flexibility in general. 
i.e. one could write:

... => explicit arguments -> IO result

all the time and add any extra implicit arguments as needed 
without change to existing source code.

All the best,
Daan.






Re: Singletons and Reflection

1999-12-15 Thread George Russell

Daan Leijen wrote:
[snip]
> Representing the 'args' as a value in haskell is probably not
> the right thing to do. For one thing, it is not possible to substitute the
> value 'args' with its definition, since it is unknown until load time.
> 
> I think that the 'dynamic environment' info is much better represented with
> implicit arguments. (already implemented by Jeffrey Lewis in the november
> hugs release).
> (Implicit Parameters: Dynamic Scoping with Static Types. Jeffrey Lewis, Mark
> Shields,
> Erik Meijer, John Launchbury:
> http://www.cse.ogi.edu/~mbs/pub/implicit.ps.gz )
> 
> The type of main would than be:
> 
> > main :: (?arguments, ?environment) => IO ()
> 
> And we could use these arguments anywhere in the haskell program
> (without making everything part of the IO monad)
[snip]

I like the implicit parameter idea a lot.  All the uses of unsafePerformIO 
within the main core of the UniForM workbench are there to do initialisation.
Suppose for example you have a single graphics context (I don't
care what sort of graphics context, maybe a text window or an X server)
for the program.  You are provided with something like:

getContext :: IO Context --  to be used at the start of the program

writeStringToContext :: String -> Context -> IO ()

To avoid passing the context all over, I think the current best solution is
something like:

programContext = unsafePerformIO (getContext)

writeString s = writeStringToContext s programContext

The UniForM code does this sort of thing several times.  I don't actually object
to using functions with "unsafe" in their name, but there are two serious problems
with this approach:
(1) There is a serious gotcha because you don't actually know when the context
will be opened.  Probably the window or whatever will only be created the
first time you try to do something with it, which may be at any time or never.
(2) The whole idea of compositional IO is destroyed.  For example, given a main
action, you cannot clone it to get two independent universes; you are stuck
with just one monolithic universe.

If we had implicit parameters then all graphics functions would have types
(? context :: Context) => (explicit arguments) => IO (result) and the main 
function would be something like
   do 
  context <- getContext
  doBusiness with context=context



RE: Singletons and Reflection

1999-12-15 Thread Chris Angus

Ok ... this is a lot neater than what I had in mind but what about the
reflective part?

-Original Message-
From: Daan Leijen [mailto:[EMAIL PROTECTED]]
Sent: 15 December 1999 10:49
To: 'Chris Angus'; [EMAIL PROTECTED]
Subject: RE: Singletons and Reflection


> 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
>

Representing the 'args' as a value in haskell is probably not
the right thing to do. For one thing, it is not possible to substitute the
value 'args' with its definition, since it is unknown until load time.

I think that the 'dynamic environment' info is much better represented with
implicit arguments. (already implemented by Jeffrey Lewis in the november
hugs release).
(Implicit Parameters: Dynamic Scoping with Static Types. Jeffrey Lewis, Mark
Shields,
Erik Meijer, John Launchbury:
http://www.cse.ogi.edu/~mbs/pub/implicit.ps.gz )

The type of main would than be:

> main :: (?arguments, ?environment) => IO ()

And we could use these arguments anywhere in the haskell program
(without making everything part of the IO monad)

> numArgs :: (?arguments) => Int
> numArgs  = length (?arguments)

Actually, the H/Direct compiler uses an unsafePerformIO to avoid having to
pass around options through all the compiler. Implicit arguments would help
here too.

All the best,
Daan.




RE: Singletons and Reflection

1999-12-15 Thread Daan Leijen

> 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
>

Representing the 'args' as a value in haskell is probably not
the right thing to do. For one thing, it is not possible to substitute the
value 'args' with its definition, since it is unknown until load time.

I think that the 'dynamic environment' info is much better represented with
implicit arguments. (already implemented by Jeffrey Lewis in the november
hugs release).
(Implicit Parameters: Dynamic Scoping with Static Types. Jeffrey Lewis, Mark
Shields,
Erik Meijer, John Launchbury:
http://www.cse.ogi.edu/~mbs/pub/implicit.ps.gz )

The type of main would than be:

> main :: (?arguments, ?environment) => IO ()

And we could use these arguments anywhere in the haskell program
(without making everything part of the IO monad)

> numArgs :: (?arguments) => Int
> numArgs  = length (?arguments)

Actually, the H/Direct compiler uses an unsafePerformIO to avoid having to
pass around options through all the compiler. Implicit arguments would help
here too.

All the best,
Daan.




Singletons and Reflection

1999-12-14 Thread Chris Angus

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