Re: ghc-4.04: memory leak with foreign export dynamic?

1999-09-28 Thread Sven Panne

Armin Groesslinger wrote:
 I think I have found a memory leak in GHC/FFI. [...]

I think it's problem with stable pointers. You can start the following
program several times and get several funny results, ranging from a
sudden but silent death at different values of count with return
value 1 to

   Fail: resource exhausted
   Action: writeChunks
   Reason: argument list too long
 
(ghc-4.05 from CVS on Linux).


import Stable

loop :: Int - IO ()
loop count = do 
   p - makeStablePtr count
   print count
   loop (count+1)

main :: IO ()
main = loop 1


Cheers,
   Sven
-- 
Sven PanneTel.: +49/89/2178-2235
LMU, Institut fuer Informatik FAX : +49/89/2178-2211
LFE Programmier- und Modellierungssprachen  Oettingenstr. 67
mailto:[EMAIL PROTECTED]D-80538 Muenchen
http://www.informatik.uni-muenchen.de/~Sven.Panne



Re: CynWinTclHaskell...?

1999-09-28 Thread Alex Ferguson


Does anyone else have experiences of building TclHaskell under CygWin?
I'm assured that it ought to be possible, but have had no luck;  crib
sheets greatly appreciated.

(Partial credit for negative results like 'it's a bust, drop back
and punt to Linux'.)

Cheers,
Alex.



Re: CynWinTclHaskell...?

1999-09-28 Thread John Atwood

Alex Ferguson wrote:
 Does anyone else have experiences of building TclHaskell under CygWin?
 I'm assured that it ought to be possible, but have had no luck;  crib
 sheets greatly appreciated.
 
 (Partial credit for negative results like 'it's a bust, drop back
 and punt to Linux'.)

In comp.lang.tcl, there's a thread on tcl and cygwin tools, also on
DLL's and VC++ vs. Borland compilers.  One scary statement was seen:
  
The DLL in Borland is different from the VC++. I guess you may check it
if there is the "C" prefix and __dllexport.


John Atwood



Re: more on Cryptarithm test

1999-09-28 Thread Fergus Henderson

On 27-Sep-1999, S.D.Mechveliani [EMAIL PROTECTED] wrote:
 -- C++ -
...
 int condition2 (vectorlong x)
 {int i = 0;
  while  ( i  20x[i]==9-i )  i++;

That has undefined behaviour, since your vector `x' only has length 10,
not 20.

I suppose this goes to show that although it may be easier to write 
fast programs in C++ than in Haskell, it certainly does seem easier to
write correct programs in Haskell than in C++ ;-)

-- 
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: more on Cryptarithm test

1999-09-28 Thread Fergus Henderson

On 27-Sep-1999, D. Tweed [EMAIL PROTECTED] wrote:
 One small comment is that in your functions condition1  condition2 I
 think most C++ programmers would say that you want to write
 
 int condition1 (const vectorlong x)
  
 since otherwise the compiler generally has to obey the normal function
 call semantics and create a copy of the vector when it passes it the
 function, rather than work directly with the existing list.

Yes, when writing C++, objects with expensive copy constructors
should always be passed by const reference, not by value.

 Personally I'd
 always write the above, not so much for performance reasons as the fact
 that if the objects in the vector have a shallow copy constructor
 (generated automatically  silently)  but a destructor that deallocates
 resources you've got an awful mess to debug when it crashes after leaving
 the function; consequently I do this even when it isn't strictly
 necessary. The few other C++ programmers I know do the same thing so
 it's probably reasonable to assume everyone does. 

That's not a reasonable assumption.  If you have a class which has a
shallow copy constructor but a destructor that deallocates resources,
then you're already in deep trouble.  Passing by const reference in
such a case will at best only stave off the inevitable disaster.

Your conclusion is correct, in this case, but the motivation should
be performance, not defending against buggy code with mismatched
destructors and copy-constructors.

-- 
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: What *I* thinks Haskell Needs.

1999-09-28 Thread Fergus Henderson

On 27-Sep-1999, Alex Ferguson [EMAIL PROTECTED] wrote:
 
 Kevin Atkinson:
  Yes but often putting things in type classes is tedious to do.  I also
  want to be able to overload not only on the TYPE of parameters but also
  on the NUMBER of parameters.  It IS possible to do these things and it
  DOES make sense in a curing system.
 
 That's far from clear.  Certainly, I don't think it's likely to be
 reasonably possible a conversative extension.

I think it could be.
However, whether it is in "the spirit of Haskell" is another question.

Mercury supports both type classes and ad-hoc overloading.
You can define two different symbols with the same name in
different modules and import them into another module
and the compiler will use your type declarations to disambiguate.
You can define the same symbol with different arities (number of parameters)
within a single module, and the compiler will use the types and the
context to disambiguate.

Ad-hoc overloading and type inference don't mix so well, because
you can easily get ambiguities which the compiler cannot resolve.
However, the user can add explicit type annotations where necessary
to resolve the ambiguities.  And I find this preferable to making
the explicit type annotations part of the symbol names, which is
what I currently tend to do when writing Haskell.

(Note that the Mercury compiler currently does not do nearly as good
a job of dealing with type inference in the presense of ambiguities
as it could do.)

2) Support for TRUE OO style programming.
 
  No. I mean being able to do things such as.
  
  Have a collection of object of a common base class AND be able to up
  cast them when necessary.
 
 If I understand you correctly, then the best way of doing this would be
 with existentially (boundedly) quantified data types, currently a
 non-standard extention present in hbc (and I think, ghc, these days, not
 sure if it's with the same generality.)

ghc does not offer any facility for type class casts.
As far as I'm aware, hbc doesn't either, but I don't know for sure.

-- 
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: What *I* thinks Haskell Needs.

1999-09-28 Thread Fergus Henderson

On 27-Sep-1999, Alex Ferguson [EMAIL PROTECTED] wrote:
 
 Fergus Henderson, replying to me:
   That's far from clear.  Certainly, I don't think it's likely to be
   reasonably possible a conversative extension.
 
 [...]
  Ad-hoc overloading and type inference don't mix so well, because
  you can easily get ambiguities which the compiler cannot resolve.
  However, the user can add explicit type annotations where necessary
  to resolve the ambiguities.
 
 If you can can ambiguities arising in what would otherwise be a well-typed
 Haskell program, then that'd make it a non-conservative (which I shall
 spell right, this time) extension, in my book.

No, you only get ambiguities if there are two symbols that have the same
name both in scope at the same time, and currently that can't happen in
a well-typed Haskell program.  So I believe it would be conservative,
at least up until the point where you start modifying the Haskell
standard library to take advantage of it...

-- 
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: What *I* thinks Haskell Needs.

1999-09-28 Thread Fergus Henderson

On 27-Sep-1999, Alex Ferguson [EMAIL PROTECTED] wrote:
 
 Fergus Henderson, replying to me:
  ghc does not offer any facility for type class casts.
 
 I'm not clear what's meant by this;  are we speaking of some sort of
 conversion to a common _type_, in some manner?

Well, roughly speaking, I'm talking about a family of built-in functions
`castC', where `C' is some type class, having type

data CastResultC = Failed | C t = Succeeded t
castC :: t - CastResultC

and with the semantics

castC (x::t) | C t   = Succeeded x
   | otherwise = Failed

where `C t' in the guard is to be interpreted as a boolean expression
that returns True if the type `t' is an instance of the class `C',
and False otherwise.  Here `t' is the type of the argument `x'.

-- 
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: Haskell and Parallelism (was: What is a functional language?)

1999-09-28 Thread S. Alexander Jacobson

On Tue, 28 Sep 1999, Adrian Hey wrote:

 So (a  b) = (b  a) is invalid

 has type
::Boolean-Boolean-Boolean

_|_ is not of type Boolean.  So, if you pass  a value of type _|_, 
you have violated its type requirements (precondition) and should not 
expect expect a lawful result.  

Haskell's type checker is not able to prevent you from passing _|_ to .
I don't think this failure makes Haskell not a functional language (all
functions have preconditions!).  
I do think it makes Haskel less than perfectly type-safe.

I believe that Charity disallows _|_.  I don't know whether the cost of
doing so is worth the gain in type safety.

-Alex-

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











Re: What is a functional language?

1999-09-28 Thread Bjorn Lisper

Me:
 Yes, it makes a lot of sense. The parallel or above is a classical example
 of a function for which there exists no semantically correct sequential
 evaluation order of its arguments (i.e., an evaluation order where an
 argument is evaluated in full before the evaluation of the next argument
 starts). Therefore, it has usually been discarded as infeasible to implement
 since the in the worst-case scenario its evaluation may require that you
 spawn off an exponential number of concurrent threads (imagine a function
 calling the parallel or recursively on both sides).

Adrian Hey:
This is the biggest problem I think.
Implementation would be very difficult. It requires a compiler smart
enough to only start separate threads if it's going to make some
difference to the termination properties, and a very efficient
implementation capable of supporting an arbitary number of threads.
I don't see the potential problem with infinite nos. of threads as
a reason not to do this though. Haskell as it stands provides plenty of
opportunity to screw up with infinite things :-)

This is not to discourage you (I think your idea is quite interesting), but
the parallel or actually provided a big headache to early researchers in
semantics. It pops up in the standard functional domains used for
denotational semantics and its non-sequential nature was seen as kind of
unnatural. (For instance, it cannot be encoded in the lambda calculus.)
Great efforts were spent do define function domains where non-sequential
functions like the parallel or did not exist. I don't think these efforts
really ever succeeded.

I have always felt that these efforts were somewhat misguided.
(Theoreticians out there, please don't kill me!) There is nothing strange
with parallel threads, or a function that requires parallel threads for its
faithful implementation. But there might be a serious problem with
efficiency. There have been attempts in this direction: Early
implementations of the language Oz, for instance, used a parallel strategy
where a thread was spawned off for each call. I think it was done this way
just because it was simple to implement (Oz is concurrent, so they needed to
support parallel threads anyway.) In later version of Oz this strategy has
been abandonded, though., for efficiency reasons I think.

Björn Lisper






Re: OO in Haskell (was Re: What *I* thinks Haskell Needs.)

1999-09-28 Thread Alex Ferguson

 From [EMAIL PROTECTED]  Mon Sep 27 18:50:33 1999
 X-Authentication-Warning: sun00pg2.wam.umd.edu: kevina owned process doing -bs
 Date: Mon, 27 Sep 1999 13:50:59 -0400 (EDT)

Kevin Atkinson:
 You have a collection of Shapes.  Some of these shapes are circles,   
 however, others are rectangle.  Occasionally you will need to extract
 these specific shapes form the collection of generic shapes as there is no   
 way to find the length and width of a generic shape, only its area and
 circumference.  So I need to cast the objects in shapes that are *really*
 rectangles back up to rectangles.
 
 1) test for the true type of the object
 2) cast it back up to its true type

There's no need for a 'cast' here, as Shape can be represented as a
class.  The trickier part is putting different types into a heterogenous
collection, and then manipulating according to their _individual_ types.
Unless you want to restrict yourself to a particular set of possible
types (in which case it's straightforward, anyway), this seems to me
like it _is_ a case of dynamic programming.


  I'm aware that Haskell doesn't precisely ape that sorts of 'OOP
  style' that the likes of C++ admits  What I've yet to see is any
  argument that this is anything other than the wisest possible decision...

 And by this you mean...

That C++ has a very poor type system.

Slán,
Alex.






Re: To all those who don't like ad-hoc overloading

1999-09-28 Thread Alex Ferguson


Kevin Atkinson:
 I take it that you are happy with names such as:

[long list]

Yes.  Certainly I'm more than happy that types with completely different
signatures have different names.






Re: OO in Haskell (was Re: What *I* thinks Haskell Needs.)

1999-09-28 Thread Andreas C. Doering

 The trickier part is putting different types into a heterogenous
 collection, and then manipulating according to their _individual_ types.

If we are already at this point, a naive question:

Assume we add the type of all types. Hence we can declare a 
function, say from type to string, we can manipulate types and 
so forth. 
This would us allow to deal with this situation. 
What is the danger, what would it break?

Ex.: 

tuple_arity:: Type - Maybe Int
tuple_arity () = Just 0
tuple_arity (a,b) = Just 1
...
tuple_arity [a] = Nothing

Of course we would have to add a huge amount 
of predefined functions to work with types, but I guess most of them are
already defined in the compiler/interpreter sources. 

Andreas
---
Andreas C. Doering
Medizinische Universitaet zu Luebeck
Institut fuer Technische Informatik
Ratzeburger Allee, Luebeck, Germany
Email: [EMAIL PROTECTED]
Home: http://www.iti.mu-luebeck.de/~doering 
"The fear of the LORD is the beginning of ... science" (Proverbs 1.7)







Re: Haskell and Parallelism (was: What is a functional language?)

1999-09-28 Thread Kevin Hammond

At 8:02 pm +0100 28/9/99, Adrian Hey wrote:
On Mon 27 Sep, Kevin Hammond wrote:
 It's entirely possible to have a parallel
 implementation of a language
 defining serial pattern matching [**], but in which the actual execution is
 parallel.

Yes, I think I understand. You mean the implementation is parallel for
efficiency reasons but it still behaves as if it were serial.

Yes, that's correct.  The result is the same as with sequential execution
(including perhaps
_|_) but the evaluation order is different.  This is also what allows
strictness analysis to
be exploited: strict arguments can be evaluated in any order, since they
will eventually be
required -- if they turn out to be undefined, then the entire computation
must be undefined.

 Of course, depending on your perspective, a fully parallel semantics for
 e.g. pattern matching may be better,
 but it can make programs less intuitive or less compact.  For example,
given:

 f 0 n = 1
 f n 0 = 2
 f m n = 3

 What is f 0 0?

f 0 0 = 1

 What if I change the order of the rules?

You get a different function.

In Haskell, I do, but there are systems where this isn't the case!

 Do you really want to have to write:

 f m n | m == 0  n != 0 = 1
   | m != 0  n == 0 = 2
   | m != 0  n != 0 = 3

No, I like the current rules for dealing with overlapping patterns just fine.
But there's a difference between the rules used to disambiguate overlapping
patterns in the 'syntactic sugar', (which are conceptually sequential,
serial or whatever) and the semantics of the resulting case expressions
(which really are serial).

Serial, but still not sequential!  That is, they define an outcome but not
an order (unless
you're referring to the operational semantics of the STG machine).  The
compiler will
rearrange the order of case-expressions if it's safe to do so, for example.

By this I mean you could keep the current rules for disambiguation, but
do the resulting un-abiguious pattern matching with something other than
case expressions.

Or just reorder the case expressions (or do them in parallel) if you like,
and if it's safe.

Current Haskell semantics specify that when reducing am expression of form..
case e of ..
e gets reduced. (The definition of seq relies on this if I remember).
So, for example, the transformation..
 (case e of
  True  - e'
  False - e') = e' is not allowed by Haskell semantics.
So if e=_|_, case e of .. = _|_.

So I don't understand how you can say 'Absolutely NOT'.
Is the behaviour of  unspecified with Haskell as it is?

In a non-strict context, the *behaviour* is as you say below.  In a strict
context,
it need not be (though the *value* will be the same!).

I think it's..
  True   True  = True
  True   False = False
  False  True  = False
  False  False = False
  _|_True  = _|_
  _|_False = _|_
  True   _|_   = _|_
  False  _|_   = False
  _|__|_   = _|_

So (a  b) = (b  a) is invalid

Not exactly: it's valid if and only if both a and b are needed (in which case
False  _|_ = _|_, so the asymmetry is eliminated)!  This is the basis for
a number of theorems.

wheras with what I called 'concurrent non-strict semantics' it should be..
  True   True  = True
  True   False = False
  False  True  = False
  False  False = False
  _|_True  = _|_
  _|_False = False  -- This is different
  True   _|_   = _|_
  False  _|_   = False
  _|__|_   = _|_

I think this is called 'parallel and' in the literature?  It's one of
several interesting ways to define the semantics of ,
and is used in e.g. some logic languages.

The problem is (as I think Alexander has pointed out) that in Haskell you
can't tell
whether an expression will evaluate to _|_ without actually evaluating it
(at which point it's too
late, since _|_ is not necessarily a value that can be matched -- it might
be non-termination or
an unhandled exception, for example).  If it's already evaluated, you're OK
of course (we use this trick in a paper that deals
with parallel databases -- a variant of Friedman and Wise 'if'  -- bibtex
attached).  A secondary problem is that
you lose the straightforward translation from pattern matching into
lambda-calculus.

The semantics of _|_ is fundamental to non-strict languages (and isn't just
operational!).

Best Wishes,
Kevin

@inproceedings{AHPT93,
author ="Akerholt, G. and Hammond, K. and Peyton~Jones, S.L.  and
Trinder, P.W.",
title = "Processing Transactions on {GRIP}: a Parallel Graph Reducer",
booktitle = "Proceedings of {PARLE~'93} -- Parallel Architectures and
Reduction Languages Europe, M{\"{u}}nchen, Germany",
year =  1993,
publisher = "Springer-Verlag",
volume ="LNCS~694",
pages = "634--647"
}

--
Division of Computer Science,   Tel: +44-1334 463241 (Direct)
School of Mathematical  Fax: +44-1334 463278
 and Computational Sciences,URL:
http://www.dcs.st-and.ac.uk/~kh/kh.html
University of St. Andrews, Fife, KY16 9SS.


efficiency of functional programs

1999-09-28 Thread S.D.Mechveliani


To my benchmark proposal with the  determinant  programs

Juergen Pfitzenmaier [EMAIL PROTECTED]  writes

 The setting for the suggested benchmark needs some clarification. For
 a dense matrix of sufficient size haskell should be able to beat C.
 I think Sergey knows this and therefor didn't mention a benchmark
 involving a sparse matrix ;)


No. I am quite naive about this. Just curious to know the average 
performance ratio of Haskell to other languages.
The DoCon-2 manual (section 'pe') contains certain comparison to the
strict, non-functional system MuPAD-1.3. 
But here i suggest to program in C the same mathematical method 
(1 - Gauss, 2 - expansion by row) as in Haskell and compare.
I expect C to be about 8 times faster. But if it occurs 100 times, i
would have to think, what is the matter.
I also want to show that arrays are not so necessary.
The Haskell program was given.
But it is harder for me to provide the C program, do not want to
recall the C programming.
The program is for the matrices over  Int-s modulo prime  p.
But, probably,  type C = Float  will do as well.

And why the dense matrix representation is better for Haskell?
Rather i would expect it is the sparse one.


--
Sergey Mechveliani
[EMAIL PROTECTED]









RE: Where would one use Maybe as a monad?

1999-09-28 Thread Frank A. Christoph

  However, I note that Maybe is an instance of Monad.  What for?

 Someone, I think at Glasgow, has a web page called something
 like "What the hell are monads?", which I thought gave a pretty
 good practical description of them.  I can't remember who
 made this page, though.  Anybody know who/where it was?
 It's been mentioned on this list in the past couple of
 months, I think.

Noel Winstanley. http://www.dcs.gla.ac.uk/~nww/Monad.html

You can find this and other information at the Haskell Bookshelf at
http://haskell.org.

Many of the Haskell designers also have interesting and useful papers
available from their own web pages. You can find those links, for example,
in the online version of the Haskell 98 Report,
http://haskell.cs.yale.edu/onlinereport/.

--FC







Re: advice wanted on GUI design patterns

1999-09-28 Thread Sven Panne

Antony Courtney wrote:
 Havoc Pennington wrote:
  [...] It seems to me that the event-driven model requires "keeping
  your data" ina way that Haskell does not provide for, because you
  need to access "the same" data structure in all your event handlers
  over time, yet there is no way to communicate between event handlers
  without updating some fixed memory location...
 
 Right.  The GUIRef monad provided by TclHaskell allows the programmer to
 perform get and set operations to access/update mutable state.  This at
 least enables the programmer to cleanly seperate the mutable state part
 of the program from the purely functional part.
 [...]

Just a few words for clarification:
In programming languages allowing mutation you have to distinguish
between a value and a location containing a value ("box"). If you
don't mess around with pointers you can easily forget this distinction
in imperative programs, e.g. in C's "x = x + x;" the x on the left
side means something quite different from the x on the right side
(lvalue vs. rvalue). In Haskell you always have to be explicit about
this: There are different kinds of boxes (IORefs, MVars, ...), each
having operations for

   * the creation of a new (typed) box with an initial value in it,
   * getting the value out of a box, and
   * putting a new value into a box

The type of these operations ensure that although actual mutation is
done, nothing "goes wrong" in a functional sense. The different kinds
serve different purposes: "simple" boxes in the IO monad, boxes for
synchronization between threads, etc., see

   http://www.haskell.org/ghc/docs/latest/libraries/libs-9.html
   http://www.haskell.org/ghc/docs/latest/libraries/libs-4.html

In the event-driven model for GUIs this means that you have to share
boxes between your event handlers, not values. Here a some pseudo-code
for this technique:


main = do
   ...
   flag - newIORef False
   registerRedisplayCallback (redisplay flag)
   registerKeyboardCallback (keyboard flag)
   guiMainLoop


redisplay :: IORef Bool - ...
redisplay flag = do
   flagValue - readIORef flag
   doSomethingWith flagValue

keyboard :: IORef Bool - ...
keyboard flag = do
   when somethingHappened $ do
  writeIORef flag newFlagValue
  postRedisplay


This shows the following:

   * You can use Haskell like C.   :-}

   * It is explicit which state is shared between the event handlers.

   * For larger programs this box fiddling should better be hidden in
 some GUI abstraction (URLs have already been given in this thread).

Cheers,
   Sven
-- 
Sven PanneTel.: +49/89/2178-2235
LMU, Institut fuer Informatik FAX : +49/89/2178-2211
LFE Programmier- und Modellierungssprachen  Oettingenstr. 67
mailto:[EMAIL PROTECTED]D-80538 Muenchen
http://www.informatik.uni-muenchen.de/~Sven.Panne






RE: What *I* thinks Haskell Needs

1999-09-28 Thread Adrian Hey

On Mon 27 Sep, Frank A. Christoph wrote:
 I must admit that I don't like the idea of determining a value based on its
 type, at least in a language like Haskell. For me, functional programming is
 about how to write programs combinatorially, and justifying your hypotheses
 by encoding their proofs; so a type is something that ought to be uniquely
 derivable from a value, not the other way around. Haskell's class system
 already goes too far against this idea for my taste.
 
 I know that some people do not feel this way, however.

I agree. This is one of the things I was griping about many moons ago
on the 'pattern match success changes types' thread, but your statement
above is far more eloquent.

This whole overloading business seems to complicate the Haskell type
system unnecessarily, and makes programs harder to understand, 
not easier, in my humble opinion. I think I would prefer something
closer to the ML approach.

Regards
-- 
Adrian Hey







Re: Haskell and Parallelism (was: What is a functional language?)

1999-09-28 Thread Martin Norb{ck


--QKdGvSO+nmPlgiQ/
Content-Type: text/plain; charset=us-ascii
Content-Transfer-Encoding: quoted-printable

Mon Sep 27 1999, S. Alexander Jacobson -
 On Tue, 28 Sep 1999, Adrian Hey wrote:
=20
  So (a  b) =3D (b  a) is invalid
=20
  has type
 ::Boolean-Boolean-Boolean
=20
 _|_ is not of type Boolean.  So, if you pass  a value of type _|_,=20
 you have violated its type requirements (precondition) and should not=20
 expect expect a lawful result. =20

Oh, but _|_ is a member of the type Boolean.=20
_|_ is a member of all types.

For instance, I can write the following:

bottom :: a
bottom =3D bottom

Then bottom is equal to _|_ and=20
bottom  bottom :: Bool
and
(bottom  False) is not equal to (False  bottom)
(at least not in Haskell with the specification of  and pattern matching)

n.

--=20
[ http://www.dtek.chalmers.se/~d95mback/ ] [ PGP: 0x453504F1 ] [ UIN: 44394=
98 ]
Opinions expressed above are mine, and not those of my future employees.

--QKdGvSO+nmPlgiQ/
Content-Type: application/pgp-signature

-BEGIN PGP SIGNATURE-
Version: 2.6.3ia

iQCVAwUBN/CsXRl6xbhFNQTxAQFi0wP/RWh6ijuJvHaUI4NwGVleVqy9IdvxIoam
4S7FyKPnsIqsbs+nkfcT2e1V8DpinKr9ns3Iv4hhaF/8KDsxeGPkHh3XBxcZGosn
8xppxASplbXnfdjq4ABpOCSQTKZeP6lBLxqaE4bQMTcxC+M+zG2QomUk6XJZTdkX
hZiL6jXaT+w=
=JvdP
-END PGP SIGNATURE-

--QKdGvSO+nmPlgiQ/--






Re: What is a functional language?

1999-09-28 Thread Adrian Hey

On Mon 27 Sep, Bjorn Lisper wrote:
 Adrian Hey [EMAIL PROTECTED]:
 This seems completely contrary to normal equational reasoning (which is
 one thing functional languages are supposed to support), where we aren't
 so constrained. 
 
 No. Equational reasoning simply means that we use equations which are valid
 to transform expressions.  When used for program transformations, the set of
 valid equations is determined by the semantics of the language. This set of
 equations will change depending on whether the language is strict or
 nonstrict. For instance, a logical or which is strict in both arguments will
 be commutative and associative, while a nonstrict or with a left-to-right
 evaluation order of its arguments will be non-commutative but still
 associative.

But should we let such operational issues muddy the waters?

Is a function..

 1- A mapping between input values and output values (which don't include
_|_). I imagine this is what mathematicians would call a function.

or..

 2- A method of computation. For all its abstraction, as far as Haskell
is concerned this has to be the correct way to view a function. This
is what makes Haskell a _programming_ language, rather than a tool
for reasoning about the properties of functions.

So, I guess the answer is.. Yes, we do need to let such operational
issues muddy the waters. What worries me here is that there might be
some unjustifiable assumptions about the nature of the machine which is
performing those operations. In particular by talking about things
like 'reduction order' and 'order of pattern matching' aren't we
assuming a sequential machine. If so, should such considerations be
allowed to 'pollute' the semantics of a general purpose high level
programming language. 

 Nonstrict languages actually have the property that function definitions can
 be seen as equations.

Almost, but not quite, as Fergus Henderson noted.

 I would say this is what makes the language
 referentially transparent! This means that a function call can always be
 symbolically unfolded without altering the semantics. Strict languages do
 not have this property in general. So in this sense nonstrict languages are
 more amenable to equational reasoning!
 
 Note that if we want the transformations to preserve the semantics of the
 language w.r.t. termination we will have to deal with bottom in equations
 also in strict languages, since also strict languages contain certain
 operations with nonstrict semantics (e.g., conditionals). Of course, we can
 consider a coarser semantics without the bottom, where we do not distinguish
 functions w.r.t. termination properties, and then have a different set of
 equalities: a good example is x - x = 0 which is valid if bottom is
 discarded but not valid if it is included. (I believe it may be this kind of
 discrepancy which has lead you to think that nonstrict languages do not
 permit equational reasoning.)

I didn't say they did not permit equational reasoning. I only said that
they complicate it (as in your example above), by forcing us to consider
_|_ as a value. The result seems to be that many intuative and useful
transformations are invalidated.
 
 So is it unfair to say that as soon as issues like strict vs. non-strict
 semantics become an important, the language is no longer purely functional?
 
 It is not only unfair, it is wrong.

Well, I suppose it depends what you call purely functional. I would
say that a language which derives it's semantics from specific (non general)
assumptions about the nature of the underlying computational machinery
is less than ideal.

What started me thinking about this is the 'World as Value' thread on the
Clean discussion list, where I tried (unsuccessfully I suspect) to make the
case for using a concurrent non-deterministic machine as the basic model
for I/O.

Then I started thinking about how one would compile function definitions
into 'computational actions' on such a machine (a Haskell compiler does
this for sequential machines) and realised that this would give that
language subtly different semantics wrt the way _|_ was treated. I don't
know what the proper name for such semantics is, so I'll call it
'concurrent non-strict' semantics as distinct from 'sequential non-strict'
semantics.

I think concurrent non-strict semantics restores many (perhaps all?)
useful transformations. An obvious example being it restores
transformations like..
  a  b = b  a 

Does this make sense?

Regards
-- 
Adrian Hey







Re: efficiency of functional programs

1999-09-28 Thread George Russell

"S.D.Mechveliani" wrote:
[snip]
 And why the dense matrix representation is better for Haskell?
 Rather i would expect it is the sparse one.
I really don't think this kind of comparison is going to be very meaningful.
I've written some sparse matrix code in C myself.  Since memory is often
as important as CPU-time (it was in that case) you work tremendously hard
getting the most efficient storage representation. For example, you
use elements of an array at one time as pointers in a circular list, at 
another time as column indices.  You store rows if possible as consecutive
elements in an array, rather than as linked lists.  (This is of course
also a big CPU time saver.) And so on.  Of course
this kind of implementation is going to completely assassinate any
Haskell sparse-matrix routines that just maintain rows as lists, but that
proves nothing.  

Suppose I were writing a new sparse matrix package.  (I certainly won't;
Netlib, which I highly recommend if you want well-written numerical code,
almost certainly has anything I want, written better than I could write it.)
I doubt if I would use Glasgow Haskell, because it takes geological ages
to compile compared with gcc, and the small gain from GHC's sophisticated
type system would be outweighed by irritation at the syntax required to
access unboxed arrays fast and unsafely.  But so what?  Only about 0.01%
of programmers can write numerical code well anyway.  (I'm not one of them.)
To them the difficulties Haskell is designed to cure are as nothing compared
with the difficulties of devising exactly the right algorithm to
do something fast and accurately.  The rest of us
would be better advised to stick to the sort of things Haskell is good at.
And if I wanted to do linear algebra or compute a log-gamma function
in Haskell I would get the relevant code from Netlib or some similar
source and link it in.






improved Cryptarithm test

1999-09-28 Thread S.D.Mechveliani

Fergus Henderson [EMAIL PROTECTED]  writes

 On 28-Sep-1999, S.D.Mechveliani [EMAIL PROTECTED] wrote:
 D. Tweed [EMAIL PROTECTED]  writes
 T One small comment is that in your functions condition1  condition2 I
 T think most C++ programmers would say that you want to write
 T 
 T int condition1 (const vectorlong x)
 T  
 T since otherwise the compiler generally has to obey the normal function
 T call semantics and create a copy of the vector when it passes it the
 T function, rather than work directly with the existing list. 
 
 Thank you.
 Here is again the improved test.
...
 And now the performance ratio shows  * 16 *.
 
 I understand this so, that this particular task allows to set
 `const'. Because first,  condition1, condition2  apply to the 
 vector  x;  as they do not modify  x,  next_permutation(x)
 yields the correct value when applied after them.
 
 Probably, other tasks and `condition1' variants would not allow to 
 set `const' like here.
 Do i understand right?
 And for these cases the ratio is smaller, say,  6, as showed the 
 earlier test - ?


 No.  `const' here probably has no effect on the efficiency.
 The difference in efficiency is due to the copying, which is
 because your original C++ program unwisely used pass-by-value,
 rather than pass-by-const-reference.  Most likely pass-by-reference
 and pass-by-const-reference will have exactly the same performance.


Sorry, this C so so difficult ...
What i wrote on `const', probably it refers to `'.
Because in the initial program  x  of type  vector  was passed to
`condition1'  (if i recall right).
And now appears `' (right?). That is passed is the pointer to the 
vector.
Now, if i reformulate my last assertion  ` .. '
replacing `const' with `' will it be true?


--
Sergey Mechveliani
[EMAIL PROTECTED]











Re: advice wanted on GUI design patterns

1999-09-28 Thread Josef Sveningsson

On Mon, 27 Sep 1999, Havoc Pennington wrote:

 The question is: how do you structure a GUI program?

There is one paper I can recommend that tries to answer this question;
"Structuring Graphical Paradigms in TkGofer". It can be found here:

http://www.cs.chalmers.se/~koen/Papers/tkgofer.ps

The paper show how it's possible to structure programs using the MVC
paradigm. The paper uses TkGofer, but I think it's possible to use the
ideas in TclHaskell also (but I don't know since I haven't tested it).

/Josef

--
|Josef Svenningsson|http://www.dtek.chalmers.se/~d95josef|
|Rubingatan 39 |  email: [EMAIL PROTECTED]   |
|421 62 Göteborg   |  tel: 031-7090774   |
--
What is a magician but a practising theorist?
-- Obi-Wan Kenobi








Re: What *I* thinks Haskell Needs.

1999-09-28 Thread Fergus Henderson

On 27-Sep-1999, Alex Ferguson [EMAIL PROTECTED] wrote:
 
 Kevin Atkinson, replying to me:
 
   If I understand you correctly, then the best way of doing this would be
   with existentially (boundedly) quantified data types, currently a
   non-standard extention present in hbc (and I think, ghc, these days, not
   sure if it's with the same generality.)
  
  existentially (boundedly) quantified data types can not cast up.
 
 'Cast up' to what?  If you can't write a class context that descibes
 the relatedness of everything you want to put in a heterogenous collection,
 then I'm inclined to doubt if it isn't more heterogenous than is
 sensible.
...
 I don't see how this relates to anything other than heterogenous collections;
 perhaps an example?

One example is the case where you already have existing code that
creates a heterogenous collection, and you want to extract an
element from that heterogenous collection, and then if it is
a member of a particular type class perform action A otherwise
perform action B, *without* modifying the existing code.

The same issue comes up if you have an existing interface
that invokes a callback function with a polymorphic type,
and you want some particular instance of this callback function
to examine the polymorphically typed value that it was given
and to perform action A if it is a member of a particular
type class and action B otherwise.

Typically action A will be some action that makes use of the methods
in the type class, and action B will be a fall-back algorithm.

  In order to do that you would ALSO need to use the dramatic typing
  extensions found in the GHC/Hugs library.

I think you mean the _dynamic_ typing extensions ;-)

The dynamic typing extensions in GHC/Hugs will let you cast to a particular
type, but they won't let you check whether that a dynamically typed value
is a member of a particular type class, or cast such a value to a type class
constrained type.

-- 
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: Where would one use Maybe as a monad?

1999-09-28 Thread Julian Seward (Intl Vendor)


 However, I note that Maybe is an instance of Monad.  What for?

Someone, I think at Glasgow, has a web page called something
like "What the hell are monads?", which I thought gave a pretty
good practical description of them.  I can't remember who
made this page, though.  Anybody know who/where it was?
It's been mentioned on this list in the past couple of
months, I think.

Apologies if I misquote the name.  I only vaguely remember it.

J






Re: advice wanted on GUI design patterns

1999-09-28 Thread Havoc Pennington


On Tue, 28 Sep 1999, Manuel M. T. Chakravarty wrote:

[very helpful explanation cut, thanks Manuel]

 There is absolutely no reason why a Haggis-like or
 FranTk-like framework couldn't be build on top of Gtk+HS.
 (In fact, there is somebody working on a Haggis-clone for
 Gtk+HS.)  From the outset, the idea was to provide with
 Gtk+HS a Haskell binding for GTK+ that keeps as close to the
 C API as possible while embedding the interface nicely in
 Haskell's type system - as a consequence, you get a C API in
 Haskell, which requires the use of imperative Haskell.  (And
 Sven has outlined how to use the `IORef's in a GUI context.)
 
 On top of this basic binding, I would like to see some more
 declarative framework(s) for implementing GUIs, but as this
 is still a research issue, I think it is very important to
 keep these two layers of abstraction cleanly separated (this
 is in addition to the obvious software engineering benefits
 of separating the two layers).  The separation should also
 make it easier to maybe at some point utilise a GUI builder
 like Glade in conjunction with Gtk+HS.
 

It makes perfect sense to do a simple binding first then write your
higher-level code in Haskell; I'm also glad to hear that you are keeping
Glade in mind. Sounds excellent.

Havoc










improved Cryptarithm test

1999-09-28 Thread S.D.Mechveliani

To my letter with the "improved" Cryptarithm test

Fergus Henderson [EMAIL PROTECTED]  writes


 -- C++ -
...
 int condition2 (vectorlong x)
 {int i = 0;
  while  ( i  20x[i]==9-i )  i++;

 That has undefined behaviour, since your vector `x' only has length 10,
 not 20.


Thank you.
It should be   while  ( i  10x[i]==9-i )  i++;

By occasion, this error had not spoiled the test, because 
for  i  9   x[i]==9-i  is false.


Also  D. Tweed [EMAIL PROTECTED]  writes


 Now it shows the ratio  * 6 *.


T One small comment is that in your functions condition1  condition2 I
T think most C++ programmers would say that you want to write
T 
T int condition1 (const vectorlong x)
T  
T since otherwise the compiler generally has to obey the normal function
T call semantics and create a copy of the vector when it passes it the
T function, rather than work directly with the existing list. 
T [..]


Thank you.
Here is again the improved test.
As earlier,
condition1  corresponds to Haskell program's  all ( 20) p
(for all i  x[i]  20),
condition2  corresponds top == [9,8..0].

And now the performance ratio shows  * 16 *.

I understand this so, that this particular task allows to set
`const'. Because first,  condition1, condition2  apply to the 
vector  x;  as they do not modify  x,  next_permutation(x)
yields the correct value when applied after them.

Probably, other tasks and `condition1' variants would not allow to 
set `const' like here.
Do i understand right?
And for these cases the ratio is smaller, say,  6, as showed the 
earlier test
- ?

--
Sergey Mechveliani
[EMAIL PROTECTED]



- C++,  improved program -
#include vector
#include algorithm
#include iostream.h

using namespace std;

int condition1 (const vectorlong x)
{
 int i = 0;
 while  (i  10x[i]  20)  i++;
 return (i  9);
}
int condition2 (const vectorlong x)
{
 int i = 0;
 while  (i  10x[i]==9-i)  i++;
 return (i  9);
}
void main()
{long t,h,i,r,y,w,e,l,v,n;
 long temp[10] = {0,1,2,3,4,5,6,7,8,9};
 vectorlong x(temp,temp+10);

 while (!(condition1(x)  condition2(x)))
 {
  next_permutation(x.begin(), x.end());
 }
 cout  x[0]  x[1]  x[2]  x[3]  x[4]  x[5]  x[6] 
 x[7]  x[8]  x[9]  '\n';
}


-- Haskell --
import List (find)

permutations :: [Int] - [[Int]]
-- build the full permutation list given an ordered list
permutations [] = [[]]
permutations (j:js) = addOne $ permutations js
 where
 addOne []   = []
 addOne (ks:pms) = (ao ks)++(addOne pms)

 ao [] = [[j]]
 ao (k:ks) = (j:k:ks):(map (k:) $ ao ks)

main = putStr $ shows (find condition $ permutations p0) "\n"
 where
 (p0, pLast) = ([0..9], reverse [0..9])
 condition p = all ( 20) pp==pLast














Re: Haskell and Parallelism (was: What is a functional language?)

1999-09-28 Thread S. Alexander Jacobson


On Tue, 28 Sep 1999, Martin Norb{ck wrote:
 Oh, but _|_ is a member of the type Boolean. 
 _|_ is a member of all types.
 
 For instance, I can write the following:

Someone else said this as well.  
Every login textbook I have seen says that to be a boolean is to be either
True or False, not True, False, or I_dunno.
Don't mistake features of the simulation for features of reality.
As an implementation matter, Haskell allows you to pass _|_ to a function
that takes only boolean arguments.  That does not mean _|_ is a boolean.  
It does mean that Haskell's model for booleans is less than perfect.
I think Adrian's complaints revolve around this distinctinction.

-Alex-

PS Martin, if your comments come with an implied smirk, then I apologize
for my lack of sense of humor

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









Re: improved Cryptarithm test

1999-09-28 Thread Dave Tweed

On Tue, 28 Sep 1999, S.D.Mechveliani wrote:

  I understand this so, that this particular task allows to set
  `const'. Because first,  condition1, condition2  apply to the 
  vector  x;  as they do not modify  x,  next_permutation(x)
  yields the correct value when applied after them.
  
  Probably, other tasks and `condition1' variants would not allow to 
  set `const' like here.
  Do i understand right?
  And for these cases the ratio is smaller, say,  6, as showed the 
  earlier test - ?
 
 
  No.  `const' here probably has no effect on the efficiency.
  The difference in efficiency is due to the copying, which is
  because your original C++ program unwisely used pass-by-value,
  rather than pass-by-const-reference.  Most likely pass-by-reference
  and pass-by-const-reference will have exactly the same performance.
 
 
 Sorry, this C so so difficult ...
 What i wrote on `const', probably it refers to `'.
 Because in the initial program  x  of type  vector  was passed to
 `condition1'  (if i recall right).
 And now appears `' (right?). That is passed is the pointer to the 
 vector.
 Now, if i reformulate my last assertion  ` .. '
 replacing `const' with `' will it be true?

I think you're in an unfortunate position Sergey: you sound like you
learned C for `extensive' use and have only picked up C++ informally,
whereas the distinction we're talking about here is unique to C++.
(This is because C uses only raw pointers rather than giving also the
option of safer references.) To try and answer your question:

* making arguments const refs is possible precisely when the function only
looks at the class, not if modification is desired

* if you used just x and modified x then you're right: next_permutation
would generate different values and you'd lose the neat guarantee that you
will cycle through all permutations

* when Fergus talks about copying this is in the C++ sense of invoking the
copy constructor; this actually consists of allocating memory and making a
copy of the vector's contents. _IF_ most of the time is spent allocating
as opposed to copying, you might be able to get almost the same efficiency
by having x and temp_x as vectors defined in main, copying the contents of
x into temp_x before each call and then using temp_x (in an imperative
language overwriting existing allocated memory isn't unreasonable if it's
a simple case, as this is); _IF_ the copying overhead is big then having
condition[1|2] need to modify a version of x will slow down the C++
significantly, as you suggest in your question.

* however if condition[1|2] can't easily be written in C++ without needing
to modify a copy of it's argument then the Haskell equivalent will also
need to do this, so the Haskell program will be slower too. Because the
haskell run-time will allocate the memory one-list element at a time
whereas the C++ most natural allocates the worst-case memory requirement
at the beginnig, I'd guess you get a smaller ratio if on average you only
build a small part of the new list before you know what the outcome of the
test is but you get a bigger ratio if on average you need to look at
almost the entire new list before you know the outcome of the test.

* from where i sit, further `adjustments' to such a small fragment of code
are unlikely to occur `in the real world'

hope this helps.

PS: I'm on the list so feel free to remove my name from the Reply To line
:-)

___cheers,_dave_
email: [EMAIL PROTECTED]   "He believed in substitions
www.cs.bris.ac.uk/~tweed/pi.htm   sometimes things just
work tel: (0117) 954-5253 just happen" -- Terry Pratchett, Jingo







Re: Haskell and Parallelism (was: What is a functional language?)

1999-09-28 Thread Paul Hudak

  Oh, but _|_ is a member of the type Boolean.
  _|_ is a member of all types.
 
  For instance, I can write the following:
 
 Someone else said this as well.
 Every login textbook I have seen says that to be a boolean is 
 to be either True or False, not True, False, or I_dunno.
 Don't mistake features of the simulation for features of reality.
 As an implementation matter, Haskell allows you to pass _|_ to a
 function that takes only boolean arguments.  That does not mean 
 _|_ is a boolean.
 It does mean that Haskell's model for booleans is less than perfect.

There seems to be serious confusion here!

True and False are the only "fully determined" members of Bool.  But,
even in imperative languages, it is possible for a boolean-typed
expression to diverge, or possibly cause an error -- neither of these is
True or False.  So the question to every language designer that permits
this is: How do you handle this situation?  If the answer is given in
terms of denotational semantics, then the notion of _|_ invariably
creeps in, or possibly even more complex domains with error elements,
etc.  This is not something unique to Haskell.

Haskell's particular solution, of course, is that both divergence and
errors are modelled in the same way: as _|_.  More precisely, Bool is
modelled as a a flat domain with incomparable values True and False, and
least (bottom) element _|_.  The bottom element in each data type in
Haskell is UNIQUE, however: _|_ in Bool is different from _|_ in Int,
etc, and they are usually distinguished by subscripting, as in
\perp_{Bool} in LaTeX terms.  On the other hand, the completely
polymorphic type "a" can be used to represent all of these bottom
values, as it will take on the value of the appropriate version of _|_
in a given context.  That _|_ is the ONLY inhabitant of this completely
polymorphic type is really a result of parametricity.

Although identifying errors with non-termination is somewhat
over-simplistic, it generally simplifies equational reasoning, where we
like to think in terms of "values", even though non-termination and an
error are not really "values".

So as pointed out by others, a  b is not the same as b  a, simply
because  is strict in its first argument (but not in its second). 
That is, _|_  e is always _|_, whereas e  _|_ is not (necessarily)
_|_.  But note that this is also true in most imperative languages, even
when e has no side effects!  Operationally speaking, both Haskell and
other langauges evaluate the first argument, and then ONLY IF THAT VALUE
IS TRUE is the second argument evaluated.  So of course  is not
commutative.

I hope this helps,

  -Paul






Re: Sets of IOErrors?

1999-09-28 Thread Alastair Reid


 On 08-Sep-1999, Alastair Reid [EMAIL PROTECTED] wrote:
  What
  I'd like (in some future version of Haskell) is an IOError constructor
  which lets me merge two IOErrors together and appropriate operations
  to test for it and, perhaps, take it apart:

Fergus Henderson [EMAIL PROTECTED] replied:
 What existing functions for testing IOErrors?
 Apart from the Eq and Show classes, Haskell 98 doesn't define any, AFAIK.

The IO library defines these functions.
(http://haskell.cs.yale.edu/onlinelibrary/io.html)

 isAlreadyExistsError  :: IOError - Bool
 isDoesNotExistError   :: IOError - Bool
 isAlreadyInUseError   :: IOError - Bool
 isFullError   :: IOError - Bool
 isEOFError:: IOError - Bool
 isIllegalOperation:: IOError - Bool
 isPermissionError :: IOError - Bool
 isUserError   :: IOError - Bool
 ioeGetErrorString :: IOError - String
 ioeGetHandle  :: IOError - Maybe Handle
 ioeGetFileName:: IOError - Maybe FilePath

The idea of these functions is to make use of the type abstract and,
hence, simplify extension of the type.  (I'm not sure it achieves this
because existing code that carefully checks for the above errors would
probably break if we added a new kind of error.)

 If you're suggesting that Eq or Show be undefined for IOErrors that
 represent sets of exceptions, then I would have to disagree...

No problem with Show - I use it all the time.
I think having and using Eq is ok (though it defeats whatever
abstraction the above operations provide).  Obviously we'd want to add
an "elem"-like function as well if we have sets of exceptions.

I was going to suggest that we redefine isAlreadyExistsError and
friends to return true if the associated error is a member of the set.
But if we do this, what do we do with ioeGetErrorString and friends?

 The exception handling in Haskell 98 needs substantial work, IMHO.

I'd certainly agree with that.  My suggestion was meant as a minimal
change to what is already there.

 IMHO Haskell 200X should pick up the Hugs/ghc extensions related to
 exception handling, or something along those lines, in particular:
 (a) allow throwing exceptions from arbitrary code, not just from within
 the IO monad

Fergus and I are in complete agreement here - but then we are
coauthors on a paper[1] that describes how to do it :-) I think this
is quite a minor change - but very, very important if you're trying
to do real things with Haskell.

 (b) allow throwing and catching of dynamically typed values,
 e.g. using an interface like the Hugs/ghc Dynamic library

Despite having written a good deal of the Hugs-GHC Dynamic library[2],
I'm wary of making it part of the standard because it is limited to
handling monomorphic values only: no polymorphism, no overloading.

I'm also a little leery of the lack of structure that would result
from using dynamic typing to provide extensibility.  The hierarchial
organisation of exceptions in Java and other OO languages seems to be
a good match to the task.  (Though, again, how does this interact
with having sets of errors?)

It is probably possible to encode such a hierarchy using Haskell's
type classes but I worry that the lack of overloading in the present
Dynamic library would prevent us from combining the two.  (Anyone care
to prove me wrong on this claim?)


--
Alastair Reid[EMAIL PROTECTED]http://www2.cs.utah.edu/~reid/


[1] http://www2.cs.utah.edu/~reid/except-pldi.ps.gz
@inproceedings{ReidA:PLDI99
,author="S.L. {Peyton Jones} and A. Reid and Tony Hoare and  Simon Marlow and Fergus 
Henderson"
,title="A semantics for imprecise exceptions"
,booktitle = "Programming Languages Design and Implementation (PLDI'99)"
,organization = "ACM press"
,year = "1999"
,month ="May"
,pages="25-36"
,abstract="
Some modern superscalar microprocessors provide only imprecise
exceptions. That is, they do not guarantee to report the same
exception that would be encountered by a straightforward
sequential execution of the program. In exchange, the offer
increased performance or decreased area (which amount to much the
same thing).  This performance/precision tradeoff has not so far
been explored at the programming langauge level. In this paper we
propose a design for imprecise exceptions in the lazy functional
programming language Haskell. We discuss various simpler designs,
and conclude that imprecision is essential if the language is
still to enjoy its current rich algebra of transformations. We
sketch a precise semantics for the language extended with
exceptions.  From the functional programming point of view, the
paper shows how to extend Haskell with exceptions without
crippling the language or its compilers. From the point of view
of the wider programming language community, we pose the question
of whether precision and performance can be traded off in other
languages too.
"
}

[2] http://haskell.cs.yale.edu/ghc/docs/latest/libraries/libs.html






Re: What *I* thinks Haskell Needs.

1999-09-28 Thread Alex Ferguson


Fergus Henderson:
 One example is the case where you already have existing code that
 creates a heterogenous collection, and you want to extract an
 element from that heterogenous collection, and then if it is
 a member of a particular type class perform action A otherwise
 perform action B, *without* modifying the existing code.

OK, it sounds like this would indeed require 'tweaking' (at least)
the existing code, it the representation of the collection doesn't
admit the required operations.


 The dynamic typing extensions in GHC/Hugs will let you cast to a particular
 type, but they won't let you check whether that a dynamically typed value
 is a member of a particular type class, or cast such a value to a type class
 constrained type.

I had noticed that apparent limitation myself, while pondering a certain
problem (to which it turns out that (I think) existential types are
an adequate solution, in that case).

It would be interesting to investigate adding 'dynamic classes' to
Haskell, but it introduces the issue of what type to give the resulting
function:  I think I'd want to clearly distinguish between a genuine
(boundedly) polymorphic function, and one which covertly does a case
analysis of the (sub-)classes of its argument.

Cheers,
Alex.






Re: Sets of IOErrors?

1999-09-28 Thread Alastair Reid


   (b) allow throwing and catching of dynamically typed values,
   e.g. using an interface like the Hugs/ghc Dynamic library

[discussion of Dynamic library, etc deleted]

[The following is a bit of a straw-man: it doesn't quite work but
may have good parts which can be used in other designs.]

(part of) Another approach is to extend Haskell with extensible
datatypes as is done in ML.  This is what I did in the late,
unlamented GreenCard 1 - you could define a new IOError constructor
whenever you wanted.  

This was easy to do because GreenCard 1's implementation exploited the
fact that it had full access to Hugs' internal data structures.  When
we moved onto GreenCard 2 and had to add GHC support, this was no
longer such an easy choice and we reluctantly switched to encoding
errors as strings.

If Haskell supported extensible datatypes, it would be easy to define a
hierarchy of exception values.  For example, the attached pseudocode
creates a hierarchy like this:

  IOError
Win32Error
  GDIError
BadRegion
BadBrush
PosixError
  ENOTDIR
  ENAMETOOLONG
  EINTR
UserError
AlreadyExists

Disadvantages of this approach include:

o Most Haskell features can be described as "just syntactic sugar"
  - it's hard to do this here.

o It's hard to write total functions over extensible datatypes (eg
  try writing a Show function for the attached definition of IOError).

o This is the only compelling use for extensible datatypes - wouldn't
  it be better to support exception handling more directly?



--
Alastair Reid[EMAIL PROTECTED]http://www2.cs.utah.edu/~reid/


module IO(...) where
  ...
  -- define the type
  extensible  IOError :: *  
  
  -- define some constructors
  constructor UserError :: String   - IOError  
  constructor AlreadyExists :: FilePath - IOError
  

module Posix(...) where   -- Posix Stuff

  import IO(IOError)

  -- define a new hierarchy of errors
  extensible  PosixError :: *

  -- link the new hierarchy into IOError
  constructor PosixError :: PosixError - IOError

  -- define some Posix errors
  constructor ENOTDIR  :: FilePath - PosixError
  constructor ENAMETOOLONG :: FilePath - PosixError
  constructor EINTR:: PosixError
  ...


module Win32(...) where   -- Windows 95/98/NT stuff

  import IO(IOError)

  -- define a new hierarchy of errors
  extensible  Win32Error :: *

  -- link the new hierarchy into IOError
  constructor Win32Error :: Win32Error - IOError



module Win32GDI(...) where   -- Windows graphics primitives

  import Win32(Win32Error)

  -- define a new hierarchy of errors
  extensible  GDIError :: *

  -- link the new hierarchy into IOError
  constructor GDIError :: GDIError - Win32Error

  -- define some GDI errors
  constructor BadRegion :: HREGION - GDIError
  constructor BadBrush  :: HBRUSH  - GDIError
  ...






Re: advice wanted on GUI design patterns

1999-09-28 Thread Adrian Hey

On Mon 27 Sep, Havoc Pennington wrote:
 
 Hi,
 
 I'm trying to learn Haskell, and I'm wondering what experiences people
 have with designing programs with graphical user interfaces.

I have none, but I think you need concurrency to do it properly,
so perhaps consider looking at Concurrent Haskell and Haggis.
Perhaps someone else out there can say if this is useable.

Regards
-- 
Adrian Hey







New Gentle Introduction now available.

1999-09-28 Thread John Peterson

I've dumped a new version of the Gentle Intro on haskell.org.  We've
updated to Haskell 98 (finally!) and added a new chapter on monads.
I've also resurrected the ancient online supplement we used to
distribute with the late, lamented Yale Haskell compiler so all of the
source code is now there and ready to execute in Hugs as you read.

I could use help packaging some more versions of the document - if
anyone wants to generate a .pdf for me that would be really nice!

We're now done with the Gentle Intro at Yale - I'm "setting it free".
We've added a copyright that allows anyone to modify, update, or
improve the tutorial and made full sources for the tutorial
available.  So instead of complaining, just fix  extend it yourself!
We'll probably put this into a public CVS repository once we get a
chance. 

   John Peterson
   [EMAIL PROTECTED]






Re: Haskell and Parallelism (was: What is a functional language?)

1999-09-28 Thread S. Alexander Jacobson

On Tue, 28 Sep 1999, Paul Hudak wrote:
 I'm not sure what you mean by "sane" vs "consistent".

Sanity means, in this context that boolean functions comply with
boolean logic when passed boolean values.
Boolean logic does not specify a behavior for functions with non-boolean
domains (like _|_).  However, as you note, from a developer perspective,
all Haskell implementations should agree on a _consistent_ behavior for
Haskell functions.
(I am making a really simple and mundane point.  I am surprised that people
are disputing it.  George Bool did not have a concept of _|_ when he
documented Boolean logic!)

  PS Charity claims to eliminate _|_.  I don't know enough about
  category theory and programming language design to know the 
  costs of doing so.
 
 I have no idea what Charity is, but if this is indeed the case then, at
 least for Booleans, all expressions must be strongly normalizing, i.e.
 will always terminate with value True or False.  Usually languages such
 as these sacrifice expressivity (for example, no general recursion!),
 such as languages based on constructive type theory.  (Either that or
 they have solved the halting problem :-)

Yes.  Charity is categorical programming language.  From  
http://ftp.cpsc.ucalgary.ca/projects/charity/home.html:

 Charity is based on the theory of strong categorical datatypes. These are
 divided into two subclasses: the inductive datatypes
 (built up by constructors in the familiar way) and the coinductive
 datatypes (broken down by destructors). Programs over
 these datatypes are expressed by folds (catamorphisms) and by unfolds
 (anamorphisms), respectively. 

They claim that you don't really need general recursion.  As I said
before, I don't know enough to evaluate this claim.

-Alex-

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











Re: Haskell and Parallelism (was: What is a functional language?)

1999-09-28 Thread Paul Hudak

 It's very important that the operational semantics be sound
 with respect to the declarative semantics.  It's much less
 important that it be complete w.r.t. the declarative semantics.
 
 Completeness (in this sense) is often highly overrated, IMHO.

I agree.  Actually, it's not only overrated, its hard to achieve in
practice.

 In order to prove that my program meets its requirements,
 I need to prove not only that it terminates, but also that
 the resources that it consumes are within the available
 resource limits.  To do that, I need to use the operational
 semantics.

Well, in this sense I think that operational semantics is overrated!  In
practice you run the program on some test cases and try a couple of
different compilers and even then you cross your fingers :-)

But I must stress that reasoning about nontermination as a value (_|_)
is really useful, in functional languages anyway.  _|_ is also very
useful when reasoning about partial and infinite lists.

  What
  does the declarative semantics say for the denotation of a program,
  written in one of these languages, that does not terminate?
 
 That depends.  ...

Thanks for the interesting explanation.  I hadn't thought much about
what a denotational semantics means for logic programs.  I have one
final question:

 For this program,
 
 Loop - Loop.   loop :- loop.
 Q - Loop  False.  q :- loop, fail.
 
 the denotation of the program is the theory
 { Loop = Loop } U { Q = Loop /\ False },
 which is equivalent to the theory { ~Q } which asserts that Q is
 false, and for that program and the same query
 
 - Q.   ?- q.
 
 the operational semantics says that the implementation may either
 loop, report an error message, or report the answer "False".

Are you saying that the operational semantics is nondeterministic?  Why
can't the semantics be tweaked such that the operational and declarative
semantics agree?  Or at least be such that the operational semantics is
deterministic?

  -Paul






Haskell and Parallelism (was: What is a functional language?)

1999-09-28 Thread Jan-Willem Maessen

There's been a good deal of debate about parallel versus sequential
semantics on this list.  As one of the pH (eager, parallel haskell)
implementors, I wanted to weigh in on a couple of issues, mostly
relating to eager versus lazy semantics.

Others have pointed out very nicely the distinction between parallel
semantics and a parallel implementation.  In pH we perform
pattern-matching and boolean tests in a sequential fashion, even
though the items being tested are evaluated in parallel.  Thus, we can
use a Haskell definition of or (||):
 True  || _ = True
 False || True  = True
 False || False = False

Again, note that because pH is eager the arguments are being evaluated
in parallel; only the final pattern matching is being done
sequentially (left to right).

Even this very slight loosening of Haskell semantics can cause
trouble, though.  What is the value of the following expression when
xs==[]?  How should it be implemented in an eager system?
null xs || head xs == 3 (A)
Clearly with lazy semantics this expression will be True; for eager
semantics our pattern matching again indicates a True result, but it's
less than clear what should become of the error produced by "head []".

Well, that's easy, you say, GHC allows us to catch errors; obviously
this is doable in other systems, and we can simply ignore bottom
values which are never referenced.  But then what do we make of this
(again, xs==[])?
bottom _ = bottom ()
null xs || bottom ()(B)

We might hope that (for example) the garbage collector will eventually
get rid of the nonterminating "bottom ()" computation, or that our
scheduler is fair, and that fairness will be enough for our system to
eventually eke out a meaningful result from the swath of useless
computations.

Note that the usual notion of parallel or gives us the most defined
possible semantics on both examples, and indeed would continue giving
a defined answer if the arguments were transposed (when haskell would
yield _|_ for both):
head xs == 3 || null xs (A')
bottom () || null xs(B')


Fundamentally, though, the semantic decisions we make have a strong
effect not only on the kind of programs we are able to write, but also
on the efficiency of our implementation:

* Adding eagerness requires a "parallel" execution model (even if the
parallelism is simulated by multitasking of some sort).

* Ignoring errors requires us to have a mechanism for catching and
recovering from those errors.

* Ignoring non-termination requires not only parallelism, but fair
scheduling---and a mechanism for killing parallel computations which
are no longer useful.


Often, these mechanisms are at odds with other aspects of our
implementation.  For example, the programmer doesn't actually want a
parallel program to be fairly scheduled if resources are
limited---instead, work needed to obtain an answer should be performed
in preference to speculative computation.  Indeed, it is my belief
that providing a fair schedule is fundamentally at odds with providing
an efficient schedule for Haskell programs.  

For this reason, actual parallel implementations of Haskell invariably
_reduce_ the number of programs that will terminate with an answer.
Contrast this with Haskell + parallel or, which _increases_ the number
of programs which terminate with an answer.  GpH (which is lazy and
explicitly parallel) requires the programmer to specify a parallel
evaluation strategy---only hand-scheduling seems to provide acceptable
performance.  The chosen strategy may result in nontermination when
the original program produced an answer.

In pH, we deal with the matter by separating termination semantics
from value semantics.  Our value domain still has a notion of
bottom---what does an erroneous or nonterminating computation return?
But we say that the meaning of a program fragment is always given
_modulo_error-free_termination_.  For both the examples above, we
obtain the value "True" when xs==[]; however, both examples contain
computations which are either erroneous or non-terminating.  Our
system (which does the scheduling for us in a hopefully efficient
manner) will print the error (A) or not terminate (B), and can choose
whether the result "True" happens to be returned as well.  This choice
may vary from run to run, but the existence of an error (A) or
non-termination (B) will not.

Note that Id, the predecessor of pH, provided parallel and/or and
parallel pattern matching; however, program behavior was once again
defined modulo termination.  This allowed pattern matching to
terminate quickly in some cases, but the "modulo termination" side
condition meant it didn't add measurable extra power, just a bit of
speed when one argument ran much faster than another.

-Jan-Willem Maessen