dynamic type class casts proposal

1999-10-07 Thread Fergus Henderson

On 06-Oct-1999, Andreas Rossberg <[EMAIL PROTECTED]> wrote:
> Down casts could be done. This would mean that each existential
> constructor had to carry dynamic type information and there would be a
> special pattern matching construct that checks this.

At first I thought a special language construct would be required.
But I realized the other day that special syntax is not essential --
it could be done using only a special library function.

So here's a concrete and very concise proposal for an extension
to Hugs/ghc.  I would propose it as an extension to Haskell,
but it relies on the `Typeable' type class and on existential types, 
which in Hugs/ghc but which are not part of Haskell 98.

===
Proposal: add a function called say `class_cast' to the standard
library, whose type is given by

class_cast :: Typeable t1 => Typeable t2 => t1 -> Maybe t2

and whose semantics are as follows: if `t2' is a type with one
constructor C that takes one argument, and `t1' is a valid type for the
argument of that constructor, then `(class_cast (x::t1)) :: Maybe t2'
returns `Just (C x)', otherwise it returns `Nothing'.
===

Here's an example of how it would be used.

class Foo t where
foo_method :: Int

-- the compiler ought to do this instance declaration automatically
instance Typeable Foo where ...

-- the compiler ought to do this type definition automatically too
data AnyFoo = forall t. Foo t => mkFoo t

bar :: Typeable t => t -> Int
bar x = case class_cast x of
Just (mkFoo x_as_foo) -> foo_method x_as_foo
Nothing -> 42

In theory, for any given program, once you know all the types and instance
declarations in the program, you could write a definition of `class_cast'
in Haskell (presuming Dynamic is extended to allow type casts to polymorphic
types, as is possible in Mercury -- this is a very simple extension which
I may describe in more detail in another message).  However, in
practice doing so would be pretty infeasible/unmaintainable.
So the idea is that the implementation would provide a definition
for `class_cast' automatically as part of the standard library, with
that definition probably making use of automatically-generated RTTI
of some kind.

Personally I think the syntax above is fine, but if more light-weight
syntax is desired, you could add syntactic sugar.

So, that's it.  Any comments?
Feedback on this proposal would be appreciated.

-- 
Fergus Henderson <[EMAIL PROTECTED]>  |  "I have always known that the pursuit
WWW:   |  of excellence is a lethal habit"
PGP: finger [EMAIL PROTECTED]| -- the last words of T. S. Garp.






Re: OO in Haskell

1999-10-07 Thread Adrian Hey

On Wed 06 Oct, Alex Ferguson wrote:
> Me:
> > >  Your 'partial' list would appear, from a initial
> > > inspection, to leave little left of either type safety or referential
> > > transparency. 
> 
> KA:
> > I can not see how State encapsulation will
> > weaken any type system.
> 
> No, that's be the 'referential transparency' part of the above.
> (I assume you're talking about something considerably different
> from state-by-monads, here.)

Is referential transparency really such a sacred cow? Sometimes
side effects are useful IMHO e.g. for IO. (Though the Cleaners regard
IO as being referentially transparent for technical reasons which I
don't quite understand.)

I've been looking at Concurrent Haskell, and more recently Johan
Nordlanders O'Haskell. I think there's a good deal of sense in both
these dialects of Haskell (I especially like the idea of getting rid
of the evil I:-)

To me, the important thing is that it should be clear when we do and
when we don't have referential transparency. Where we don't, words
like 'operation' or 'action' should be used instead of 'function'.

So I can see nothing wrong with encapsulated (mutable) state, in principle,
just so long as the state is only mutated by 'actions'.

Regards 
-- 
Adrian Hey







Re: OO in Haskell

1999-10-07 Thread trb

Adrian Hey writes:
 > On Wed 06 Oct, Johan Nordlander wrote:
 > > Just to avoid any unfortunate misconceptions: O'Haskell definitely
 > > preserves the property we commonly refer to as referential transparency,
 > > and so does Concurrent Haskell, or any other sound monadic extension of
 > > the language.
 > 
 > Hmm, I obviously don't understand what 'referential transparency' means.
 > I must say I'm puzzled by statements like this. If the presence of
 > mutable variables (and MVars in Concurrent Haskell) preserve referential
 > transparency, then why _don't_ we have referential transparency in C?

I'm not surprised you are puzzled. Concurrent Haskell, as implemented in ghc,
does NOT preserve referential transparency, nor could it. The whole point of
multi-threading is to be able to respond asynchronously to events i.e. the
relative order of events in one thread versus another thread is undefined - if
the order were defined the program would be single-threaded. Take that together
with the ability to perform side-effects e.g. I/O or mutable state, and it is
clear that the results produced by the program will in general depend on the
particular relative order of events between threads, rather than on the
declarative semantics alone.

It is possible to achieve some of the effects of multi-threading using lazy
evaluation of stream processors - this approach does not violate referential
transparency, and is used in the Fudgets GUI (Haggis uses concurrent Haskell).
I ran some Haggis programs in the days before it rotted, and it performed
well. I haven't run Fudgets programs, but got the impression from the
documentation that the stream processors would not always provide as much
responsiveness as could be wished for.

Tim






Re: OO in Haskell

1999-10-07 Thread Manuel M. T. Chakravarty

<[EMAIL PROTECTED]> wrote,

> Adrian Hey writes:
>  > On Wed 06 Oct, Johan Nordlander wrote:
>  > > Just to avoid any unfortunate misconceptions: O'Haskell definitely
>  > > preserves the property we commonly refer to as referential transparency,
>  > > and so does Concurrent Haskell, or any other sound monadic extension of
>  > > the language.
>  > 
>  > Hmm, I obviously don't understand what 'referential transparency' means.
>  > I must say I'm puzzled by statements like this. If the presence of
>  > mutable variables (and MVars in Concurrent Haskell) preserve referential
>  > transparency, then why _don't_ we have referential transparency in C?
> 
> I'm not surprised you are puzzled. Concurrent Haskell, as
> implemented in ghc, does NOT preserve referential
> transparency, nor could it. 

Of course it does!  If it wouldn't many of the optimisations
performed by GHC would be invalid and you would be doomed if
you compiled a Concurrent Haskell module with -O (actually,
you would most certainly already be doomed without -O).

Check out the type signatures of the `MVar'-related
operations and you will find that they are all nicely
encapsulated in the `IO' monad.  

Manuel

PS: We don't have referential transparency in C, because K&R 
didn't know Phil Wadler ;-)






RE: CPP is not part of Haskell

1999-10-07 Thread Manuel M. T. Chakravarty

"Frank A. Christoph" <[EMAIL PROTECTED]> wrote,

> Manuel Chakravarty wrote:
> > The problem is that a pre-processor adds a new level of
> > semantic complexity to the language - so if we can do
> > without it, we'll definitely make our lives simpler.
> >
> > Besides, one nice property of Haskell is its relatively
> > (compared to other languages) precise semantic definition
> > (ie, the translation to the Haskell kernel).  A
> > pre-processor wouldn't fit nicely in here, I suppose.
> 
> Camlp4 is not part of the language definition for Ocaml, and I don't know if
> Jan is necessarily advocating that an analogue would need to be part of the
> one for Haskell. If you don't mind parsing your source twice, a Camlp4-like
> processor can just output plain old Haskell. The actual Camlp4 can also
> output a binary form of Ocaml's ASTs, and a special switch on the compiler
> (there is only one implementation of Ocaml! :) reads it in directly and
> avoids reparsing.

If you have only one implementation of a language, things
are easier.  If we want to get a decent set of good
libraries for Haskell, we need solutions that work across
different systems.  At the moment writing Haskell code for
Real World Problems (tm), which is portable across Haskell
systems is a pain.  Something like a pre-processor, which is
expected to be used across a wide range of programs, needs
to be standardised; otherwise, it is causing more problems
than it solves.

Manuel






Num classes (was: Function algebra)

1999-10-07 Thread Koen Claessen

Fergus Henderson wrote:

 |  instance Eq b => Eq (a -> b) where
 |f == g  = error "can't compute equality of functions"

I hope that you are joking here ...

Why don't we propose this: add the following
default instance for *all* types in Haskell:

  instance Eq a where
f == g = error "can't compute equality for <>"

Using overlapping instances, we can override
this (like virtual functions in C++) for the types
that *have* equality.

;-)

This is of course the ultimate non-solution!

So the big question is:

  "WHY does the Num class hierarchy look as it looks?"

Is there a good reason for why it has to be so
complicated? Strange superclasses (Eq, Show),
strange subclasses (Integral, etc.). Add to this
the strange default rules and you have *my* most
common source of type errors and frustration in
Haskell.

Almost no other construct in the whole Haskell
language is so commonly used as Numbers, and
certainly no other construct *forces* me to look
at the report, browse preludes etc. so often!
(As soon as I want to do something more complicated
than +, that is.)

Regards,
Koen.

--
Koen Claessen http://www.cs.chalmers.se/~koen 
phone:+46-31-772 5424  e-mail:[EMAIL PROTECTED]
-
Chalmers University of Technology, Gothenburg, Sweden







Re: function algebra

1999-10-07 Thread Fergus Henderson

On 06-Oct-1999, John Atwood <[EMAIL PROTECTED]> wrote:
> Can't you trivially satisfy Eq:
> 
> instance Eq b => Eq (a -> b) where
> f == g  = False

Functions using the `Eq' class might rely on the property
that x == x is True for all x.

So

instance Eq b => Eq (a -> b) where
f == g  = error "can't compute equality of functions"

might be safer, in the sense that at worst it would result
in a runtime error, rather than silently producing incorrect
output.

However, a `Show' instance that just printed "<>"
for all functions would probably be OK.

-- 
Fergus Henderson <[EMAIL PROTECTED]>  |  "I have always known that the pursuit
WWW:   |  of excellence is a lethal habit"
PGP: finger [EMAIL PROTECTED]| -- the last words of T. S. Garp.






Re: concurrency (was OO in Haskell)

1999-10-07 Thread Manuel M. T. Chakravarty

<[EMAIL PROTECTED]> wrote,

> Manuel M. T. Chakravarty writes:
>  > <[EMAIL PROTECTED]> wrote,
>  > 
>  > > I'm not surprised you are puzzled. Concurrent Haskell, as
>  > > implemented in ghc, does NOT preserve referential
>  > > transparency, nor could it. 
>  > 
>  > Of course it does!  If it wouldn't many of the optimisations
>  > performed by GHC would be invalid and you would be doomed if
>  > you compiled a Concurrent Haskell module with -O (actually,
>  > you would most certainly already be doomed without -O).
>  > 
>  > Check out the type signatures of the `MVar'-related
>  > operations and you will find that they are all nicely
>  > encapsulated in the `IO' monad.  
> 
> That does not help. Encapsulation within the IO monad
> forces MVar operations to be explicitly ordered only
> within the thread in which they occur; it does not effect
> the relative order with respect to MVar operations in
> other threads.

Sure, a program using IO is not necessarily deterministic.

> In summary, Concurrent Haskell only has declarative
> semantics for an individual thread (called a process in
> the paper) - the entire program does *not* have
> declarative semantics i.e it is not referentially
> transparent.

The pure lambda calculus is not the only logic on which you
can base a declarative semantics.  A language based on a
semantics expressed in linear logic won't necessarily be
deterministic, but can be declarative.  Given such a
semantics, there is not necessarily a contradiction to
referential transparency.  Referential transparency means,
IMHO, that you can replace variables by their values
without changing the semantics of the program, ie,

  let x = e1
  in=   [x/e1]e2
  e2

This is still guaranteed in Concurrent Haskell, and it is
guaranteed due to the use of monads.  This does not imply
that the `=' sign above is the equality in a model that is
restricted to deterministic computations.

Manuel






Re: concurrency (was OO in Haskell)

1999-10-07 Thread trb

Manuel M. T. Chakravarty writes:
 > <[EMAIL PROTECTED]> wrote,
 > 
 > > Adrian Hey writes:
 > >  > On Wed 06 Oct, Johan Nordlander wrote:
 > >  > > Just to avoid any unfortunate misconceptions: O'Haskell definitely
 > >  > > preserves the property we commonly refer to as referential transparency,
 > >  > > and so does Concurrent Haskell, or any other sound monadic extension of
 > >  > > the language.
 > >  > 
 > >  > Hmm, I obviously don't understand what 'referential transparency' means.
 > >  > I must say I'm puzzled by statements like this. If the presence of
 > >  > mutable variables (and MVars in Concurrent Haskell) preserve referential
 > >  > transparency, then why _don't_ we have referential transparency in C?
 > > 
 > > I'm not surprised you are puzzled. Concurrent Haskell, as
 > > implemented in ghc, does NOT preserve referential
 > > transparency, nor could it. 
 > 
 > Of course it does!  If it wouldn't many of the optimisations
 > performed by GHC would be invalid and you would be doomed if
 > you compiled a Concurrent Haskell module with -O (actually,
 > you would most certainly already be doomed without -O).
 > 
 > Check out the type signatures of the `MVar'-related
 > operations and you will find that they are all nicely
 > encapsulated in the `IO' monad.  

That does not help. Encapsulation within the IO monad forces MVar operations
to be explicitly ordered only within the thread in which they occur; it does not
effect the relative order with respect to MVar operations in other threads. 

See the paper "Concurrent Haskell" by Simon Peyton Jones, Andrew Gordon and
Sigbjorn Finne, which states:

"forkIO :: IO () -> IO () forkIO a is an action which takes an action, a, as its
argument and spawns a concurrent process to perform that action. The I/O and
other side effects performed by a are interleaved in an unspecified fashion with
those that follow the forkIO."

The paper goes on to say:

"The situation worsens when concurrency is introduced, since now multiple
concurrent processes are simultaneously mutating a single state. The
purely-functional state-transformer semantics becomes untenable.

Instead, we adopt the standard approach to giving the semantics of a concurrent
language, using an operational semantics."

In summary, Concurrent Haskell only has declarative semantics for an individual
thread (called a process in the paper) - the entire program does *not* have
declarative semantics i.e it is not referentially transparent.

For example, consider a program where one thread prints a value from an MVar,
while another thread modifies it. The output of the program will vary from one
run to another, even though its input (none) is unchanged.

Tim






Re: concurrency (was OO in Haskell)

1999-10-07 Thread Christian Sievers

Tim <[EMAIL PROTECTED]> wrote:

> For example, consider a program where one thread prints a value from an MVar,
> while another thread modifies it. The output of the program will vary from one
> run to another, even though its input (none) is unchanged.

This is not a result of using concurrency.
You see the same no input/different output behaviour in a program as
simple as this:

> import Random
> main = getStdRandom (randomR (False,True)) >>= print

(Or use the Time library.)

And nothing of this breakes referential transparency.
For example, 

> main = randomints >>= print
> randomints :: IO (Int,Int)
> randomints = do a <- getStdRandom (randomR (1,100))
> b <- getStdRandom (randomR (1,100))
> return (a,b)

has the same possible results as

> main = randomints >>= print
> randomints :: IO (Int,Int)
> randomints = let rnd = getStdRandom (randomR (1,100)) in
>  do a <- rnd; b <- rnd  
> return (a,b)

Each time a program is run it is given a different world to start
with.
C is as referentially transparent as you are willing to agree that
each function has an implicit IO in its type, which won't gain you
anything. Even that is not really enough. "volatile" variables are
MVars, and what are non-volatile variables changed in signal
handlers? Uncaught type errors? Enough of that.

All the best,
Christian Sievers






Random class

1999-10-07 Thread Jose Emilio Labra Gayo

The Haskell98 Library Report defines the Random class as:

class Random a where
   randomR :: RandomGen g => (a, a) -> g -> (a, g)
   random  :: RandomGen g => g -> (a, g)

   randomRs :: RandomGen g => (a, a) -> g -> [a]
   randoms  :: RandomGen g => g -> [a]

   randomRIO :: (a,a) -> IO a
   randomIO :: IO a
   . . . 

And the report says:
"randomR takes a range (lo,hi) and a random number generator g, 
[...] It is unspecified what happens if lo>hi. "

So it suggests that lo and hi can be compared and should be instances of Ord.

I think it would be better to have:

class Random a where
random :: ...
randoms :: ...
randomIO :: ...

class (Ord a, Random a) => RandomR a where
randomR :: ...
randomRs :: ...
randomRIO :: ...

Best Regards, Jose E. Labra
http://lsi.uniovi.es/~labra



   






Re: Referential Transparency (was Re: OO in Haskell)

1999-10-07 Thread Michael Hobbs

Adrian Hey wrote:
> I've read this paper, and it is good, but I still see no reason to
> change my opinion regarding referential transparency and IO.
> But I am terribly confused about this issue, there seems to be no real
> consensus about this in the FP world. I just can't see how if the
> result of an action is dependent on unknown external world agents
> (as it is with the IO monad) it could be described as referentially
> transparent. I can accept that we have referential transparency for
> user defined monads, but not the IO monad.

Consider this:
> type IO a = StateOfUniverse -> (a, StateOfUniverse)
> -- Not syntactically correct, but you know what I mean.

So anything that is declared, say `IO Int', means that it is actually a
function that reads in the state of the universe, potentially modifies
it, and then returns an Int value along with the new state of the
universe. The interesting thing to note is that the state of the
universe never changes between calls that are strung together using the
`>>=' operator. That is, the StateOfUniverse that is returned by the
first monad is exactly same state that is fed into the second. Whether
or not you want to call this "referentially transparent", well I guess
that's up to your own philosophic bias.

- Michael Hobbs






Re: Referential Transparency (was Re: OO in Haskell)

1999-10-07 Thread Michael Hobbs

Michael Hobbs wrote:
> 
> Adrian Hey wrote:
> > I've read this paper, and it is good, but I still see no reason to
> > change my opinion regarding referential transparency and IO.
> > But I am terribly confused about this issue, there seems to be no real
> > consensus about this in the FP world. I just can't see how if the
> > result of an action is dependent on unknown external world agents
> > (as it is with the IO monad) it could be described as referentially
> > transparent. I can accept that we have referential transparency for
> > user defined monads, but not the IO monad.
> 
> Consider this:
> > type IO a = StateOfUniverse -> (a, StateOfUniverse)
> > -- Not syntactically correct, but you know what I mean.
> 
> So anything that is declared, say `IO Int', means that it is actually a
> function that reads in the state of the universe, potentially modifies
> it, and then returns an Int value along with the new state of the
> universe. The interesting thing to note is that the state of the
> universe never changes between calls that are strung together using the
> `>>=' operator. That is, the StateOfUniverse that is returned by the
> first monad is exactly same state that is fed into the second. Whether
> or not you want to call this "referentially transparent", well I guess
> that's up to your own philosophic bias.

I rescind the statement that "the state of the universe never changes
between calls that are strung together using the `>>=' operator". After
further consideration, I believe that that's incorrect.

- Michael Hobbs






Re: Referential Transparency (was Re: OO in Haskell)

1999-10-07 Thread Marcin 'Qrczak' Kowalczyk

Fri, 8 Oct 1999 01:22:43 +0100 (BST), Adrian Hey <[EMAIL PROTECTED]> pisze:

> I've read this paper, and it is good, but I still see no reason
> to change my opinion regarding referential transparency and IO.
> But I am terribly confused about this issue, there seems to be
> no real consensus about this in the FP world. I just can't see
> how if the result of an action is dependent on unknown external
> world agents (as it is with the IO monad) it could be described as
> referentially transparent.

I think that referential transparency simply depends on what entities
in the language we call `variables' and what methods of their usage
we call `referencing'.

Since languages can be very different and their concepts are not
mapped one-to-one between languages, there is no universal definition
of referential transparency that can be unambiguously applied to
any language.

In Haskell a `variable' can be meant to be either a name introduced
by a let/where/lambda/case binding, or one of IORef/STRef/MVar (or
even something in a custom monad). The first concept is referentially
transparent, the second is not if we think about the contents of
*Refs/MVars as `values of variables' and thus usages from different
(>>=)-separated segments in the relevant monad.

(I'm not sure whether I understand the referential transparency issue
correctly at all, sorry if it's all wrong.)

In other words, implementing an interpreter of a non-referentially
transparent language in the referentially transparent language does
not change the answer for the implementing language, because we start
talking about different concepts.

Similarly, matrices can be comutative or not, depending on whether
we talk about their addition or multiplication.

> I can accept that we have referential transparency for user defined
> monads, but not the IO monad.

It is satisfied for both or for neither, depending on from what side
we look at them and how we assign names to concepts.

-- 
 __("+++$ 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-







CFP: Special Issue of JFP on Algorithmic Aspects of Functional Programming Languages

1999-10-07 Thread Chris Okasaki

The Journal of Functional Programming will host 
a special issue devoted to the design, analysis,
evaluation, and/or synthesis of algorithms and
data structures in functional programming languages.
For full details, see
  http://www.dcs.gla.ac.uk/jfp/editorialAugust99.html
The deadline for submissions is February 16, 2000.

Chris Okasaki
[EMAIL PROTECTED]






O in Haskell

1999-10-07 Thread Lucilia Camarao de Figueiredo


Carlos´ got the flue and could not come to work.  I´d like to join
Kevin on his fight :-).

I think system CT is simple and will make the type system and life for
programmers simpler. A language based on system CT would require no
class or instance declarations (although they could be kept for
documentation or checking), so I am not sure about how and if Mark
Jones type checker could be used for making the system available in
Haskell.

So let´s begin fighting...

1) Repeating, overloading with system CT is simpler than with type
classes, especially for programmers. They do not need to figure out
what type to write in class and instance declarations (types are
infered). They will not anymore be concerned about strange
superclasses, strange subclasses and common frustrating unresolved
overloading error messages. Types in system CT are simpler, since, for
specifying a type, the programmer does not need to know the whole
hierarchy of necessary constraints. Programmers will not anymore be
confused about type errors that arise because they forgot to include a
constraint (for example, Eq a).

As another example, discussed recently, the type of "u . map fst",
where "u" is overloaded by bindings "u = union" and "u = unionBy"
would be, in Haskell (well, Hugs) 

  (Eq a, Functor d, U (d e) a c) => d(e, f)->[a]->c

whereas, in System CT, the *automatically inferred* type would be

  {map::((e, f)->e)->d->b, u::b->[a]->c}. d->[a]->c

in a context where map is overloaded for lists and functions:

 map::(a->b)->[a]->[b]and
 map::(a->b)->(c->a)->(c->b)

In Hugs, the programmer may not just forget about the type above (Hugs
requires it to be specified; I don´t know why).

2) Overloading as in system CT is type safe and statically typed. We
have a semantics and a type soundness proof (to be submitted for
publication soon).

3) The fact that problems are soluble does not mean that a better
solution does not exist. I think that this occurs with respect to
overloading and the use of multiple parameter type classes and
functional dependencies. The burden is on the programmer to figure out
types and their functional dependencies, where type inference and
simple overloading of definitions could be used instead. In my view,
sources of problems lie in 1) context-free instantiation of types by
the Haskell type system, and 2) the definition of ambiguity in the
Haskell type system. All "technical" :-) details to be given in the
upcoming article.

4) I think system CT should not be treated as an extension of Haskell
type classes. With system CT, class and instance declarations are not
needed.

I strongly agree with the view that Haskell has far cleaner syntax
than just about any other language. But I think that the same does not
apply to the treatment of overloading.

Lucilia







Re: Referential Transparency (was Re: OO in Haskell)

1999-10-07 Thread Jan Skibinski


Here are some comments about the prevailing view that the
concept of the World or the Universe is safe to use in
any kind of arguments related to referential transparency.
I would be quite cautious here. I am not an expert on
these issues in relation to FP, but I have seen enough
tough examples in physics that make me a bit sceptical here.
I am not fighting the concept itself, but I would like
to see it well described first to know exactly the limits
of its applicability. 

In my view, once I have introduced the idea of the outside
Universe into my model I am bound to complicate things quite
dramatically, because now I need to consider the interactions
between the two subsystems A and B (Universe). And they are
often not so simple..

To rigorously describe, and -- what is much more difficult --
to solve such a system one has to treat the compound A+B
as a whole. There are many such examples in physics, where
it is absolutely necessary to think globally. We cannot,
for example describe the system of two interacting electrons
via individual (interfering or not) waveforms: psi(x1) and
psi(x2). We have to use a function psi(x1,x2), which is an
amplitude of probability that one (we do not know exactly
which one) electron is at x1 and another at x2.

But physics also teaches us how to simplify things by
isolating the subsystem A from B -- as long as such
simplification makes practical sense. It is not always
possible though, and often not quite acurate. When you
describe the free fall of a mass "m" in the Earth gravitational
field you do, in fact, simplify the rigorous model by replacing
the two-body problem by the one-body problem. Knowing that
the gravitational pull of mass "m" has practically no effect
on the movement of Earth mass "M", you can just ignore
the Earth as such and instead introduce "one-way" gravitational
force into your model. This methodology of removing
constraints and replacing them by reaction forces (and/or
torques) dates back to Newton and is the first thing
to do in solving countless problems of classical mechanics.

You can also apply it to a quantum model of the hydrogen atom,
because the proton is much, much heavier than the electron.
But you cannot exactly apply it to the model of helium, because
now you deal -- in addition to heavy nucleus -- with two
electrons of the same mass.
 
I think that the monadic IO provides us with such a
simplification. As long as we realize what are its limitations
and as long as we stay within reasonable limits of the concept
we should be fine here. The operative word here is "realize".
Do we really know those limitations? 

I have seen engineers nondiscriminantly applying simplified
engineering formulas to problems where such simplifications
were not valid at all. You know, formulas of the sort "beam
bending moment", taken from some engineering handbook. Such
formulas had been, of course, derived from some basic theory
-- but with a lot of simplifying assumptions: linearity, isotropy,
small deflections, limits put on ratio of dimensions, etc.
But, by the time the formula hit the handbook, all those
assumption have been long forgotten.

I am afraid that once we start taking the monadic concept
too far we are bound to find some obstacles (philosophical or
practical) sooner or later. Same applies to the concept of
the Universe, because we often do not know what is exactly our
model of Universe. How do we model interactions of unknown
or imprecise nature?


Jan








Re: Num classes (was: Function algebra)

1999-10-07 Thread Marcin 'Qrczak' Kowalczyk

Thu, 7 Oct 1999 08:23:23 +0200 (MET DST), Koen Claessen <[EMAIL PROTECTED]> pisze:

> So the big question is:
> 
>   "WHY does the Num class hierarchy look as it looks?"

How should it look like? Yes, at first I was confused about many
classes like RealFrac etc., but after some thinking I realized
that this is about the only sensible scheme, when we want to
polymorphically support various kinds of numbers, don't want to
artificially implement "illegal" operations (like (/) of integers as
div) and don't have a natural way of converting an integer to some
"appropriate" fractional type.

The three exponentiation operators all have their uses. They could
be unified only if Haskell supported overloading, or when we accept
unneeded type conversions back and forth, or if Haskell's type system
looked differently, or when we loss expressiveness.

I have no idea how to make it simpler without drawbacks.

-- 
 __("+++$ 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: Referential Transparency (was Re: OO in Haskell)

1999-10-07 Thread Michael Hobbs

Michael Hobbs wrote:
> > Consider this:
> > > type IO a = StateOfUniverse -> (a, StateOfUniverse)
> > > -- Not syntactically correct, but you know what I mean.
> >
> > So anything that is declared, say `IO Int', means that it is actually a
> > function that reads in the state of the universe, potentially modifies
> > it, and then returns an Int value along with the new state of the
> > universe. The interesting thing to note is that the state of the
> > universe never changes between calls that are strung together using the
> > `>>=' operator. That is, the StateOfUniverse that is returned by the
> > first monad is exactly same state that is fed into the second. Whether
> > or not you want to call this "referentially transparent", well I guess
> > that's up to your own philosophic bias.
> 
> I rescind the statement that "the state of the universe never changes
> between calls that are strung together using the `>>=' operator". After
> further consideration, I believe that that's incorrect.

Unless, of course, you consider StateOfUniverse to encapsulate all past,
present, and future events (a 4-dimensional value). In which case, you
don't need to return a new StateOfUniverse, since it will be exactly the
same as the one given, except maybe with different `currentTime' value.
But I'm getting way too deep here.

The problem is a function like `getChar' that is declared `IO Char'. If
the user has not typed a character when this monad is invoked, it will
sit and wait for the event. That is, the current StateOfUniverse that is
passed to getChar has absolutely nothing in it to indicate what
character will be returned, unless it also contains future events.

However, if we define `getChar' like this, we might get around the nasty
issue of future events:
> getChar = do
>   c <- peekKbdBuffer :: IO [Char]  -- length of 0 or 1
>   if null c then getChar else return head c
In this case, `getChar' will continue looping until StateOfUniverse
changes such that the keyboard buffer actually has a value in it. Of
course, this means that the StateOfUniverse must be able to alter itself
somehow between the function calls.

Philosophy Thursday,
- Michael Hobbs






Re: concurrency (was OO in Haskell)

1999-10-07 Thread Adrian Hey

On Thu 07 Oct, [EMAIL PROTECTED] wrote:
> See the paper "Concurrent Haskell" by Simon Peyton Jones, Andrew Gordon and
> Sigbjorn Finne, which states:
> 
> "forkIO :: IO () -> IO () forkIO a is an action which takes an action, a, as
> its argument and spawns a concurrent process to perform that action. The I/O
> and other side effects performed by a are interleaved in an unspecified
> fashion with those that follow the forkIO."
> 
> The paper goes on to say:
> 
> "The situation worsens when concurrency is introduced, since now multiple
> concurrent processes are simultaneously mutating a single state. The
> purely-functional state-transformer semantics becomes untenable.

Yes, my opinion seems to be very much in line with yours, and that of
the Concurrent Haskell designers as far as I can see.

Regards
-- 
Adrian Hey







Re: OO in Haskell

1999-10-07 Thread Adrian Hey

On Thu 07 Oct, Manuel M. T. Chakravarty wrote:
> Check out the type signatures of the `MVar'-related
> operations and you will find that they are all nicely
> encapsulated in the `IO' monad.  

This is true, but I think the point of contention is does the IO monad
itself provide referential transparency. My opinion is that even thinking
in such terms for IO is pretty meaningless. I am aware of various
attempts to fix up the IO semantics with world models, but none of these
accurately model the world. How could they?

So what difference does it make if you regard unpredictablity in the result
of IO operations as caused by non-deterministic world models or Side
Effect Goblins? Both theories seem equally valid, and both tell us
very little about the nature or behaviour of the real world.

Regards
-- 
Adrian Hey







Re: Referential Transparency (was Re: OO in Haskell)

1999-10-07 Thread Adrian Hey

On Thu 07 Oct, Joe English wrote:
> The way I understand the term "referntially transparent",
> it means that if you have
> 
> let x = y in z
> 
> then you can substitute all free occurrences of 'x' in 'z'
> with 'y', or vice versa, without changing the meaning of
> the expression.  This is true in Haskell even if 'y' has
> type 'IO a'.  (For example, "the action which, when performed,
> returns the contents of the file /var/log/messages" always
> _means_ the same thing, even though it may _do_ different things
> each time it's performed.)

As you say, I think the problem is predictability of the results of
_invoking_ actions. I'm quite happy with the idea of an action as a
value which does not damage referential transparency if it appears
in an expression.

Regards
-- 
Adrian Hey







Re: Referential Transparency (was Re: OO in Haskell)

1999-10-07 Thread Adrian Hey

On Thu 07 Oct, Marcin 'Qrczak' Kowalczyk wrote:
> In Haskell a `variable' can be meant to be either a name introduced
> by a let/where/lambda/case binding, or one of IORef/STRef/MVar (or
> even something in a custom monad). The first concept is referentially
> transparent, the second is not if we think about the contents of
> *Refs/MVars as `values of variables' and thus usages from different
> (>>=)-separated segments in the relevant monad.
> 
> (I'm not sure whether I understand the referential transparency issue
> correctly at all, sorry if it's all wrong.)

I agree with you. I think as far as this discussion is concerned
its the monadic mutable variables which are problematic.
 
> > I can accept that we have referential transparency for user defined
> > monads, but not the IO monad.
> 
> It is satisfied for both or for neither, depending on from what side
> we look at them and how we assign names to concepts.

I would opt for the 'both' option, _provided_ the world which the IO
monad is interacting with is closed, finite and deterministic. If this
is true we should be able to develop a model the world as a Haskell data
type and associated functions which reproduce the observable properties
of the world exactly, in every detail. For example, that world could
be a dedicated hardware array processor which interacted with nothing but
the Haskell program. In such cases I would aggree that computation by
IO monad is just another form of purely functional computation, with
referential transparency intact.

Unfortunately, we can't do this for the real world. So I'm still
sceptical about IO monads.  

Regards
-- 
Adrian Hey







Re: OO in Haskell

1999-10-07 Thread Kevin Atkinson

Marcin 'Qrczak' Kowalczyk wrote:
> 
> Tue, 5 Oct 1999 14:10:26 -0400 (EDT), Kevin Atkinson <[EMAIL PROTECTED]> pisze:
> 
> > 1) Dynamic types.  You can't cast up.  That is you can't recover the
> > original type from an object in a existential collection.  You need to
> > use a dynamic type library for that.  And the library proved with hugs
> > and ghc leaves a lot to be desired.  In an OO langauge all classes
> > automatically cary dynamic typing information.
> 
> Please, no. Don't require existentials to carry dynamic type
> information. IMHO it's as ugly as Dynamic.
> 

The types won't be required to carry dynamic type information.  It will
just be there if you need it.  It there will be a special function or
the like you can call to get information about the original object.  If
you don't won't to use it, you don't have to and you will NEVER know its
there.  Also if none of the code uses dynamic typing the compile will be
able to optimize away the dynamic type information.

> The concept of existentials works well without it. The essence of
> existential is that you don't care what type is inside as long as it
> has the stated properties. If you need it, I think this is either
> wrong design (e.g. the operation that would use the cast should be
> put inside the existential as a method) or some more fundamental lack
> in the Haskell's type system. Don't break existentials.
> 
> If you like this, you must also like Dynamic, so simply require the
> type under the existential to be Typeable and cast it through Dynamic.
> The effect would be the same, without a penalty to those that don't
> use it.
> 
> In simple cases where the set of types that need to be casted is
> fixed, there can be methods returning `Maybe ACastedType', with
> obvious semantics.
> 
> Sorry that I really can't explain well why I think that this concept
> does not fit into Haskell. I must have heard that such "typecase"
> is most often a bad design.
> 

I am not going to argue with you here but there are times where some
casting is unavoidable and I think haskell should provide a safe clean
way of allowing it and the Dynamic type library is not it.

> > 3) Encapsulation.  You can't have private and protected members.  Some
> > of this can be done using modules.  However it is more work.
> 
> Please, no. C++'s friends are symptoms that this does not work well.
> This belongs to the module system.
> 
> Functions does not "belong" to the type of objects they act on, which
> is obvious when we consider functions working symmetrically on more
> than one argument: which does it belong to? And what about constants:
> in what sense does the emptySet belong to a Set type? I have never
> accepted the OO way, where the first argument is distinguished as
> the owner.
> 
> When thinking about whether the implementation details of something are
> known to a function, it should be obvious that they are "more known"
> to a function in the same file acting on different types than to some
> function defined in other file, even acting on the same type.
> 
> Haskell's modules, unlike Pascal's, can reexport entities imported
> from other modules, so there may be views of a family of entities
> with various levels of visibility of the inner details.

Perhaps.  However I have also think Haskell's module system is a bit to
simple.  One think I really think it needs is the ability to group a
collection of functions with a tag.  And then when importing a module
you can ask to only import that tag.  For example:

module A
  list: head tail foldr foldl
  array: index (!!) foldr foldl

...

import A(list)

which will make using modules a LOT more convent.  

Also, Haskell currently allows you to explicitly import one module with
another.  However, I think that this should be extended to be able to
import part of the module for example:

module Mod1(module Mod2 hiding foo, module Mod3(foo))

and the like.  Right now when ever a module uses a prelude function you
have to import it like so:

import Prelude hiding head
import Mod1

which can be VERY annoying when a module overrides a lot of the prelude
functions.

> 
> > 4) Cleaner more natural syntax.
> 
> I know no other language that has cleaner and more natural syntax
> than Haskell :-)
> 
> In particular I dislike typical OO syntax: object.method(args).
> It's good that Haskell makes field selection functions look like
> normal functions, because they _are_ normal functions that could be
> defined elsewhere. Or else you could argue that fst and head should
> look like pair.fst and list.head. Please, no.

I guess its a matter of personal taste.


-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/






Re: OO in Haskell

1999-10-07 Thread Marcin 'Qrczak' Kowalczyk

Tue, 5 Oct 1999 14:10:26 -0400 (EDT), Kevin Atkinson <[EMAIL PROTECTED]> pisze:

> 1) Dynamic types.  You can't cast up.  That is you can't recover the
> original type from an object in a existential collection.  You need to
> use a dynamic type library for that.  And the library proved with hugs
> and ghc leaves a lot to be desired.  In an OO langauge all classes
> automatically cary dynamic typing information.

Please, no. Don't require existentials to carry dynamic type
information. IMHO it's as ugly as Dynamic.

The concept of existentials works well without it. The essence of
existential is that you don't care what type is inside as long as it
has the stated properties. If you need it, I think this is either
wrong design (e.g. the operation that would use the cast should be
put inside the existential as a method) or some more fundamental lack
in the Haskell's type system. Don't break existentials.

If you like this, you must also like Dynamic, so simply require the
type under the existential to be Typeable and cast it through Dynamic.
The effect would be the same, without a penalty to those that don't
use it.

In simple cases where the set of types that need to be casted is
fixed, there can be methods returning `Maybe ACastedType', with
obvious semantics.

Sorry that I really can't explain well why I think that this concept
does not fit into Haskell. I must have heard that such "typecase"
is most often a bad design.

> 2) More specific types, you can't _easilly_ call the more general type.
> For example in OO this is very commen:
> 
> class Base
>   virtual foo()
> do stuff
> 
> class Derived, extends Base
>   foo()
> call Base::foo()
> doo stuff

Yes, subtyping is an interesting issue that Haskell lacks that *may* be
good. It is not obvious however, what exactly it could mean in Haskell.

IMHO it is not as useful as in some imperative languages. In C++ or
Java you typically have methods mutating objects, where in functional
languages you have functions returning new objects. Analogous to
methods Base::foo(int) and Derived::foo(int) are functions of types
`Base -> Int -> Base' and `Derived -> Int -> Derived'. Here their
signatures differ not only on the first argument, as in imperative OO,
but also on the result. So you cannot say that the second function
is simply the first one specialized to the case of Derived.

They may however be methods of type `a -> Int -> a' in some class,
that is, where types are instances of an interface, not the other
type - because you don't have "values of type AHaskellClass" which
could be passed through such a function yielding another "value of
type AHaskellClass". Instead the types of argument and result are
constrained to be the same at the place of the usage, no matter what
the actual type is. In other words, it's good that Haskell makes
a difference between an interface and a concrete type, and in a
functional language instances of an interface make more sense than
instances of a type (i.e. subtypes).

It is also more general in the way that there may be more than
one argument of the "self" type (as (==) in Eq), or none (as pi
in Floating). Type inference makes the latter case convenient.

> 3) Encapsulation.  You can't have private and protected members.  Some
> of this can be done using modules.  However it is more work.

Please, no. C++'s friends are symptoms that this does not work well.
This belongs to the module system.

Functions does not "belong" to the type of objects they act on, which
is obvious when we consider functions working symmetrically on more
than one argument: which does it belong to? And what about constants:
in what sense does the emptySet belong to a Set type? I have never
accepted the OO way, where the first argument is distinguished as
the owner.

When thinking about whether the implementation details of something are
known to a function, it should be obvious that they are "more known"
to a function in the same file acting on different types than to some
function defined in other file, even acting on the same type.

Haskell's modules, unlike Pascal's, can reexport entities imported
from other modules, so there may be views of a family of entities
with various levels of visibility of the inner details.

> 4) Cleaner more natural syntax.

I know no other language that has cleaner and more natural syntax
than Haskell :-)

In particular I dislike typical OO syntax: object.method(args).
It's good that Haskell makes field selection functions look like
normal functions, because they _are_ normal functions that could be
defined elsewhere. Or else you could argue that fst and head should
look like pair.fst and list.head. Please, no.

*   *   *

I have escaped from the way to OO because I don't believe it is as
good as many people claim. Haskell designed surprisingly many things
in the way that I either have thought about before and liked (elegant
design, strong typing, parametric polymorphism, types 

Re: OO in Haskell

1999-10-07 Thread Adrian Hey

On Wed 06 Oct, Johan Nordlander wrote:
> Just to avoid any unfortunate misconceptions: O'Haskell definitely
> preserves the property we commonly refer to as referential transparency,
> and so does Concurrent Haskell, or any other sound monadic extension of
> the language.

Hmm, I obviously don't understand what 'referential transparency' means.
I must say I'm puzzled by statements like this. If the presence of
mutable variables (and MVars in Concurrent Haskell) preserve referential
transparency, then why _don't_ we have referential transparency in C?

Does it have something to do with denotational semantics and world
models containing infinite trees of random numbers?

Regards
-- 
Adrian Hey







Re: OO in Haskell

1999-10-07 Thread Michael T. Richter

At 05:12 PM 10/7/99 , you wrote:
> Sorry that I really can't explain well why I think that this concept
> does not fit into Haskell. I must have heard that such "typecase"
> is most often a bad design.

In most situations, type-casting is a symptom of bad design.  The only C++
situation, for example, where some form of casting from a base class to a
derived class isn't symptomatic of a bad design is the situation of the
so-called "virtual constructor" -- building objects from a persistent
store, say.  In most to all other situations, use of dynamic_cast or
equivalent is just plain sucky design.

I don't know enough about Haskell's type system yet to form an opinion if
there is any point where such casts are necessary as opposed to being
merely expedient.  Haskell's type system is... well, I guess "quirky" and
"complex" leap to mind immediately.  I'm sure that at some point I will
grok it and will either go "Aha!" or "Ew!".  Until then I'll reserve opinions.

> Functions does not "belong" to the type of objects they act on, which
> is obvious when we consider functions working symmetrically on more
> than one argument: which does it belong to? And what about constants:
> in what sense does the emptySet belong to a Set type? I have never
> accepted the OO way, where the first argument is distinguished as
> the owner.

But this isn't "the" OO way.  It is "an" OO way.  Dylan, for example,
doesn't make any particular argument on a method as the "owner".

--
Michael T. Richter<[EMAIL PROTECTED]>http://www.igs.net/~mtr/
  PGP Key: http://www.igs.net/~mtr/pgp-key.html
PGP Fingerprint: 40D1 33E0 F70B 6BB5 8353 4669 B4CC DD09 04ED 4FE8 






Re: Referential Transparency (was Re: OO in Haskell)

1999-10-07 Thread Adrian Hey

On Thu 07 Oct, Michael Hobbs wrote:
> Michael Hobbs wrote:
> > > Consider this:
> > > > type IO a = StateOfUniverse -> (a, StateOfUniverse)
> > > > -- Not syntactically correct, but you know what I mean.
> > >
> > > So anything that is declared, say `IO Int', means that it is actually a
> > > function that reads in the state of the universe, potentially modifies
> > > it, and then returns an Int value along with the new state of the
> > > universe. The interesting thing to note is that the state of the
> > > universe never changes between calls that are strung together using the
> > > `>>=' operator. That is, the StateOfUniverse that is returned by the
> > > first monad is exactly same state that is fed into the second. Whether
> > > or not you want to call this "referentially transparent", well I guess
> > > that's up to your own philosophic bias.
> > 
> > I rescind the statement that "the state of the universe never changes
> > between calls that are strung together using the `>>=' operator". After
> > further consideration, I believe that that's incorrect.
> 
> Unless, of course, you consider StateOfUniverse to encapsulate all past,
> present, and future events (a 4-dimensional value). In which case, you
> don't need to return a new StateOfUniverse, since it will be exactly the
> same as the one given, except maybe with different `currentTime' value.
> But I'm getting way too deep here.
> 
> The problem is a function like `getChar' that is declared `IO Char'. If
> the user has not typed a character when this monad is invoked, it will
> sit and wait for the event. That is, the current StateOfUniverse that is
> passed to getChar has absolutely nothing in it to indicate what
> character will be returned, unless it also contains future events.
> 
> However, if we define `getChar' like this, we might get around the nasty
> issue of future events:
> > getChar = do
> >   c <- peekKbdBuffer :: IO [Char]  -- length of 0 or 1
> >   if null c then getChar else return head c
> In this case, `getChar' will continue looping until StateOfUniverse
> changes such that the keyboard buffer actually has a value in it. Of
> course, this means that the StateOfUniverse must be able to alter itself
> somehow between the function calls.

This is another reason I'm sceptical about referential transparency in
any functional system of IO (streams, monads, continuations, world as value..)
It is hard to sensibly define interaction between a timeless universe
of pure functions and values and a real universe which continually evolves
in real time. A state transformer method is about as good as you'll
get, but this requires that somehow the times of future events is
information which is embedded in the whatever state the program last left
the universe in. Perhaps some people believe this, but I don't think
the world works this way. (And even if this were true, unless we had
some systematic way of extracting this information and predicting the
future, it won't help us at all.) 

Regards
-- 
Adrian Hey