Re: Relection

2000-01-26 Thread Marcin 'Qrczak' Kowalczyk

Wed, 26 Jan 2000 08:34:59 -, Chris Angus [EMAIL PROTECTED] pisze:

 One thing I dont like, is going through IO, although I guess this
 wouldnt matter so much.

*Of course* it has to be in IO! Loading an external function has
everything to do with I/O.

When you write
fooBar x = (getFunction "foo" x, getFunction "bar" [x])
do you really want to open the external library and load functions
each time fooBar is called? Or do you expect that the runtime system
will cache recently used functions? Argh.

And think about handling I/O errors when loading an external library.

I could accept at most something like this:
do
handle - openLibrary "filename"
-- or: readLibraryFromString "binary library contents"
f - loadValue handle "sin"
-- f has type Double - Double (as inferred from further usage).
-- You can pass f to other functions and use it.

This is something like a variant of hGetLine h = readIO, which
reads code evaluating to arbitrary values, probably compiled on the
same platform only.

loadValue has type:
loadValue :: Typeable a = LibraryHandle - String - IO a
or with some other class instead of Typeable. The class could even be
magically implicitly instantiated for all types, but it must appear in
the type. loadValue is overloaded, not universally polymorphic. It does
not uniformly work on all types: it raises exception on some types
and succeeds on others. The overloaded type requires disambiguation.

Libraries could possibly be built by compiling standard Haskell modules
with some compiler switch to produce the right format (including
information needed for dynamic typechecking).

We have to solve the problem of other modules used by dynamically
loaded ones.

If you want to load a function and use it polymorphically, probably
local universal quantification is required.

I think that Dynamic's Typeable class could also be derived
automatically - paradoxically I feel that it would be more elegant
then... Also it would be safer and more convenient.

 once I start doing that it seems I have to use glasgow's unsafe IO
 stuff or make all my functions IO-returnric :-/

Probably you can separate reading data from operating on it. Separate
what requires I/O from what does not. Code often gets more readable
when you create intermediate abstract syntax of something instead of
putting all the processing in one place, and laziness will help not
to physically create the whole structure in memory.

Or you really write code that does I/O all the time, and then IO in
their types is perfectly natural.

 I suppose it comes down to
 
 if (performUnsaveIO.f) always returns the same answer to the same arguments 
 why does f return (IO a) rather than (a)

It's in the reverse direction only: if it's (a) rather than (IO a),
it should certainly return the same answer for the same arguments.
Functions that need to perform IO for calculation of their results
should have IO type, unless it happens to be safe when they don't
and they really behave like pure functions.

One reason is above: you want more control when it is executed, since
performing I/O interacts with the changing state of the outside world,
can be expensive, can fail, and can cause troubles with polymorphism
(a value produced by IO is lambda-bound and thus monomorphic).

 This is how I feel about commandline arguments.

This is about the only exception where I could ever consider removing
IO from a function that has IO now. But when a global value has type
String, it generally means that it's a compile time constant.

When you really know what you are doing, use unsafePerformIO for
convenience, but on your own risk. Standard libraries should be safe
and not bend rules.

It's good that unsafePerformIO exists, because sometimes it can
be extremely convenient (command line arguments is nothing in
comparison). When reading a long string from an I/O resource (not
using standard readFile or hGetContents) you may want to process
it incrementally; simulating laziness yourself would be a real pain,
would cause changes all over the program, but would be required without
unsafePerformIO. I wish unsafePerformIO was standarized. But it must
not be abused. It's important that it is clearly marked as dangerous.

-- 
 __("Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/  GCS/M d- s+:-- a22 C+++$ UL++$ P+++ L++$ E-
  ^^  W++ N+++ o? K? w(---) O? M- V? PS-- PE++ Y? PGP+ t
QRCZAK  5? X- R tv-- b+++ DI D- G+ e h! r--%++ y-




RE: Relection

2000-01-25 Thread Chris Angus

By reflection I mean the sort of thing Java does in java.lang.reflect



i.e. given the name/type  of a function we can retrieve that function and
subsequently use it
in the same way that in java given the name of a class we can create
instances of that class.

i.e. it is quite common to have dialog which accepts a filename looks at the
suffix
turns that in to class name and picks up the class. That class knows how to
deal with files of that type and all classes share a common interface.

The sort of problem I'm describing is something I would try to use the
Factoy design pattern for nin OO speak (GoF Design Patterns : Elements of
Reusable Object-Oriented Software).



In Haskell we have 

module Foo
import Bmp
...
... Bmp.read filename

i.e. we can only call the functions inside modules we have imported (in this
case Foo can read bitmaps because it imports Bmp) 

However if we wanted to extend Foo's functionality so that it could read
Gifs as well
we would have to edit Foo

module Foo
import Bmp
import Gif
...
... Bmp.read filename

... Gif.read filename

etc

and for each new format we wanted to add we would edit Foo.hs ... yeugh!

if we had a mechanism for retrieving functions then this would not be
necessary

we could inspect the filename 
if it was a .gif then retrieve Gif.read
if it was a .bmp then retrieve Bmp.read
if it was a .foo then retrieve Foo.read
etc

now Foo's functionality may be extended in an additive rather than editive
way


module Foo
import Reflect 
 ...let 
fn = Reflect.getFn (bottom::String - ImageReader) name
  name = suffix+ ".read"
suffix = getSuffix filename
in 
case fn of
Nothing - error ("Function that knows how to read "
+ suffix +" files does not exist")
Just f  - f filename





-Original Message-
From: Peter Hancock [mailto:[EMAIL PROTECTED]]
Sent: 25 January 2000 11:13
To: Chris Angus
Subject: Relection


 "Chris" == Chris Angus [EMAIL PROTECTED] writes:

 I posted this to comp.lang.functional a while ago but (apparently) no
one
 had an opinion which
 I cant believe is the case :-)

Hi Chris.  The problem is likely to be that (like me) many people
don't know what you mean by "reflection" -- I couldn't make it 
out from your message.  [I know what reflection means in set
theory, but (pardon my ignorance) I haven't heard of it in FP.]

Maybe you could post a URL for a paper which explains this 
concept well? 

Regards,

Peter



RE: Relection

2000-01-25 Thread jwit

Hello everybody,

The concept of reflection can also be taken further than Chris' idea, which
is fairly useful in it's own right, but could possibly be achieved by some
smart FFI-wizard (not sure, this idea just popped into my head).

What I'm getting at is some kind of way to get your hands on an abstract 
syntax representation of a Haskell expression/datatype/module, modifying it,
re-typechecking it, and then transforming it back into a Haskell value. 
This probably would entail carrying Hugs around in the runtime-system and I 
can imagine you need some kind of monad to protect against unwanted effects.

Then you could do things like:

module CheckPartition where
import HaskellAST
import HaskellReflection

check :: Reflection String
check = do (Binding name body) - getBindingFromString "partition"
   if body /= haskellParse "\p xs - (filter p xs,filter (not.p) xs)"
then return "Read up on the Haskell mailing list!"
else return "Way to go!"

main = do string - refl2IO check
  putStr string

The possibilities are endless...

A fixed(ie standardized) HaskellAST module would be great since every wannabe 
compiler writer seems to write of her/his own (I know I do!). Maybe that 
Reflection stuff is slightly unrealistic though...

All the best,

Jan de Wit





Re: Relection

2000-01-25 Thread George Russell

Chris Angus wrote:
 
 Put simply
 
 What do people think about being able to access functions from other modules
 without
 importing the module.
 
 i.e. Rather than
 
 ---Start-
 import Foo
 -- call f
 callFoof x = f x
 --End
 
 We can do
 
 ---Start-
 callFoof x =
 case (getFunction "Foo.f" (bot::Int - Int) ) of
 (Just f) - f x
 (nothing) - error "Foo not linked in"
 ---End---
My first reaction is "ugh" but on further consideration it is at least
an intriguing idea.  But I think the syntax is wrong.  Perhaps you could
have something like this:
   loadModule :: String - IO Module 
-- dynamically load module, or raise some
-- sort of exception
   lookupName :: Module - String - IO a -- lookup name or give exception
Then code might look like
   do
  fooModule - loadModule "Foo"
  fooF - (lookupName fooModule "f") :: IO (Int - Int)
  . . .
lookupName would need to be a special compiler primitive and there would
need to be special compiler magic to pass the most general possible type
for its result to the RTS.  For example
   applyFooF x =
  do
 fooF - lookupName fooModule "f"
 return (fooF x)
might have to fail except in the unlikely case that Foo.f turned out to
have type (for all a,b) ( a - b ).



Re: Relection

2000-01-25 Thread Marcin 'Qrczak' Kowalczyk

Tue, 25 Jan 2000 18:12:32 +0100, jwit [EMAIL PROTECTED] pisze:

 What I'm getting at is some kind of way to get your
 hands on an abstract syntax representation of a Haskell
 expression/datatype/module, modifying it, re-typechecking it,
 and then transforming it back into a Haskell value.

In other words you want to embed a Haskell compiler in your program.

It could be useful in practice sometimes, but it's a very far concept
from a simple extension of the language to allow reflection.

Haskell is quite complex and can be compiled. IMHO the distance
between the source code and the running program is very big in the
case of Haskell. In other words, much is done at compile time instead
of runtime. I like this principle, because it allows an elegant and
powerful language with lots of static checking and optimizations,
even though it makes reflection harder.

A function definition is the specification of what an identifier
means in its scope, not the physical bytes of its compiled or
source code. It can be inlined, instantiated, unfolded, analyzed for
strictness, rewritten using RULES etc. - it does not have to appear
in a physical form that can be examined by the program. C's dlopen()
is different because C is a more low level language - in C there is
a closer correspondence between the source function and the execution
time object.

If you want to embed a compiler or interpreter in your program, then
OK, but the compiled or interpreted language need not to have much
in common with the language the program is written in. It's cool if
it's again Haskell because Haskell is cool (and because it's easier to
exchange values) - not because each language should contain a compiler
of itself! The compiler used to produce our program and the compiler or
interpreter working inside our program are completely different beasts.

I would be very careful in designing "reflection capabilities" in
Haskell. Especially I'm afraid of producing an inelegant solution
which would be abused because of either lack of some other mechamisms
or the laziness of a programmer ("laziness" not in FP sense).

I agree that we should design a way of allowing dynamic linking of some
plugins. IMHO it should be clearly separated from the main language
and nicely designed for dynamic linking of additional code, not for
examining the program internals by the program itself. Internals that
are not relevant for program execution should go away at the time of
compilation. Identifiers used in the source should go away.

IMHO it should be a sort of FFI specification, allowing linking at
runtime. May be Haskell-centric, but formally quite independent of
where a program using it came from. Not expressing all the details of
Haskell language in first-class values. Not needing to parse Haskell
code at runtime to link a module!

What I mean by abusing an embedded compiler. For example building
function names from pieces and parsing the resulting expression instead
of creating a mapping between function names and actual functions.
Or translating an arithmetic expression entered by the user to Haskell
expression instead of writing a parser of arithmetic expressions.
Or passing values between functions by their source name instead of
by themselves. Or doing things that are hard to fit in the type system
instead of expressing them differently or improving the type system.

I don't know what is the GHC and Hugs integration going to look like.
I have good feelings about it, only I'm afraid of abusing it or
implementing some features along with lack of some more important ones.

-- 
 __("Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/  GCS/M d- s+:-- a22 C+++$ UL++$ P+++ L++$ E-
  ^^  W++ N+++ o? K? w(---) O? M- V? PS-- PE++ Y? PGP+ t
QRCZAK  5? X- R tv-- b+++ DI D- G+ e h! r--%++ y-




Re: Relection

2000-01-25 Thread Fergus Henderson

On 25-Jan-2000, Marcin 'Qrczak' Kowalczyk [EMAIL PROTECTED] wrote:
 Tue, 25 Jan 2000 18:12:32 +0100, jwit [EMAIL PROTECTED] pisze:
 
  What I'm getting at is some kind of way to get your
  hands on an abstract syntax representation of a Haskell
  expression/datatype/module, modifying it, re-typechecking it,
  and then transforming it back into a Haskell value.
 
 In other words you want to embed a Haskell compiler in your program.
 
 It could be useful in practice sometimes, but it's a very far concept
 from a simple extension of the language to allow reflection.
 
 Haskell is quite complex and can be compiled. IMHO the distance
 between the source code and the running program is very big in the
 case of Haskell. In other words, much is done at compile time instead
 of runtime. I like this principle, because it allows an elegant and
 powerful language with lots of static checking and optimizations,
 even though it makes reflection harder.
 
 A function definition is the specification of what an identifier
 means in its scope, not the physical bytes of its compiled or
 source code. It can be inlined, instantiated, unfolded, analyzed for
 strictness, rewritten using RULES etc. - it does not have to appear
 in a physical form that can be examined by the program. C's dlopen()
 is different because C is a more low level language - in C there is
 a closer correspondence between the source function and the execution
 time object.

Well, Mercury has the same approach as Haskell, in the sense of being
a language which at least aims at being elegant and powerful with
lots of static checking and optimizations.  But we do support
dynamic linking (on some platforms), using an interface built
on top of dlopen() and dlsym().

Supporting dynamic linking need not inhibit optimization to any
significant degree, I believe.  At worst, you may need to disable
inter-module dead-function elimination.  Even that need only be done
if dynamic linking is used.

The next stage of support for reflection, being able to at run-time
get your hands on an abstract syntax representation of a Haskell
expression/datatype/module, does have a higher cost.  The compiler
needs to keep information around at run-time which it would otherwise
not need.  In Mercury we currently support that for types, but not
for expressions or modules.

One way of reducing the cost of this feature is to require
programmers to explicitly mark with some declaration
those entities for which the compiler should keep the
information around at run-time.  ISO Prolog takes this
approach; predicates for which you can use the
`clause/2' builtin to look up their definition
need to be declared "dynamic" using a `:- dynamic' declaration.
Ada takes the converse approach: by default, it keeps
around some tables to allow you to convert enumeration constants
into strings, but there is a standard pragma which allows
you to suppress that for a given enumeration.

The final stage -- being able to take a representation of
a Haskell expression, re-typechecking it, and then transforming
it back into a Haskell value -- does not actually _require_
any language or runtime support, I think; you can program
it in standard Haskell.  Though I guess some support might be
required if you want to introduce new types at run-time.

-- 
Fergus Henderson [EMAIL PROTECTED]  |  "I have always known that the pursuit
WWW: http://www.cs.mu.oz.au/~fjh  |  of excellence is a lethal habit"
PGP: finger [EMAIL PROTECTED]| -- the last words of T. S. Garp.



Re: Relection

2000-01-25 Thread S. Alexander Jacobson

This discussion feels like deja-vu all over again!
What is wrong with the various generic programming extensions that have
already been discussed? Derive, PolyP and their progeny?

-Alex-

___
S. Alexander Jacobson   Shop.Com
1-212-697-0184 voiceThe Easiest Way To Shop


On Wed, 26 Jan 2000, Fergus Henderson wrote:

 On 25-Jan-2000, Marcin 'Qrczak' Kowalczyk [EMAIL PROTECTED] wrote:
  Tue, 25 Jan 2000 18:12:32 +0100, jwit [EMAIL PROTECTED] pisze:
  
   What I'm getting at is some kind of way to get your
   hands on an abstract syntax representation of a Haskell
   expression/datatype/module, modifying it, re-typechecking it,
   and then transforming it back into a Haskell value.
  
  In other words you want to embed a Haskell compiler in your program.
  
  It could be useful in practice sometimes, but it's a very far concept
  from a simple extension of the language to allow reflection.
  
  Haskell is quite complex and can be compiled. IMHO the distance
  between the source code and the running program is very big in the
  case of Haskell. In other words, much is done at compile time instead
  of runtime. I like this principle, because it allows an elegant and
  powerful language with lots of static checking and optimizations,
  even though it makes reflection harder.
  
  A function definition is the specification of what an identifier
  means in its scope, not the physical bytes of its compiled or
  source code. It can be inlined, instantiated, unfolded, analyzed for
  strictness, rewritten using RULES etc. - it does not have to appear
  in a physical form that can be examined by the program. C's dlopen()
  is different because C is a more low level language - in C there is
  a closer correspondence between the source function and the execution
  time object.
 
 Well, Mercury has the same approach as Haskell, in the sense of being
 a language which at least aims at being elegant and powerful with
 lots of static checking and optimizations.  But we do support
 dynamic linking (on some platforms), using an interface built
 on top of dlopen() and dlsym().
 
 Supporting dynamic linking need not inhibit optimization to any
 significant degree, I believe.  At worst, you may need to disable
 inter-module dead-function elimination.  Even that need only be done
 if dynamic linking is used.
 
 The next stage of support for reflection, being able to at run-time
 get your hands on an abstract syntax representation of a Haskell
 expression/datatype/module, does have a higher cost.  The compiler
 needs to keep information around at run-time which it would otherwise
 not need.  In Mercury we currently support that for types, but not
 for expressions or modules.
 
 One way of reducing the cost of this feature is to require
 programmers to explicitly mark with some declaration
 those entities for which the compiler should keep the
 information around at run-time.  ISO Prolog takes this
 approach; predicates for which you can use the
 `clause/2' builtin to look up their definition
 need to be declared "dynamic" using a `:- dynamic' declaration.
 Ada takes the converse approach: by default, it keeps
 around some tables to allow you to convert enumeration constants
 into strings, but there is a standard pragma which allows
 you to suppress that for a given enumeration.
 
 The final stage -- being able to take a representation of
 a Haskell expression, re-typechecking it, and then transforming
 it back into a Haskell value -- does not actually _require_
 any language or runtime support, I think; you can program
 it in standard Haskell.  Though I guess some support might be
 required if you want to introduce new types at run-time.
 
 -- 
 Fergus Henderson [EMAIL PROTECTED]  |  "I have always known that the pursuit
 WWW: http://www.cs.mu.oz.au/~fjh  |  of excellence is a lethal habit"
 PGP: finger [EMAIL PROTECTED]| -- the last words of T. S. Garp.
 





Re: Relection

2000-01-25 Thread Fergus Henderson

On 25-Jan-2000, S. Alexander Jacobson [EMAIL PROTECTED] wrote:
 This discussion feels like deja-vu all over again!
 What is wrong with the various generic programming extensions that have
 already been discussed? Derive, PolyP and their progeny?

I don't think there's anything fundamentally wrong with them;
but I think they only address a small part of the
things that reflection (in the wider sense that we've
been discussing in this thread) is useful for.

-- 
Fergus Henderson [EMAIL PROTECTED]  |  "I have always known that the pursuit
WWW: http://www.cs.mu.oz.au/~fjh  |  of excellence is a lethal habit"
PGP: finger [EMAIL PROTECTED]| -- the last words of T. S. Garp.