Re: Fail: thread killed

2000-03-21 Thread Marcin 'Qrczak' Kowalczyk

Tue, 21 Mar 2000 02:09:40 -0800, Simon Marlow [EMAIL PROTECTED] pisze:

 There's a default exception handler installed on all threads forked
 with forkIO, which prints on stderr any exception caught.  Is that
 your objection?

It's OK for other exceptions, but I thought that killing a thread is
not a symptom of an error. So even if it is modelled as an exception,
IMHO this exception should not cause any error message.

OK, I could catch the exception in the thread to be killed, and
synchronize threads at the beginning to prevent a race when it is
killed before the exception handler is entered, but it does not
look nice.

BTW, is it OK to kill a thread that has already exited?

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





i386-unknown-solaris2

2000-03-21 Thread Manuel M. T. Chakravarty

We are just trying to get GHC 4.x running on
`i386-unknown-solaris2'.  The first problem seems to be that
gcc uses the Solaris assembler on our machines, which
doesn't grok the assembly GHC feeds it.  Does GHC need `gas'
on all platforms?  If so, we would add a corresponding test
to `configure'.

Didn't ghc once run on `i386-unknown-solaris2'?  Is there a
serious reason for not supporting this platform anymore, or
is it just bit rot due to lack of use?

Cheers,
Manuel

PS: ...and no jokes re running Solaris on i386 - it
certainly wasn't my idea.




Re: speed of compiled Haskell code.

2000-03-21 Thread Ketil Malde

"D. Tweed" [EMAIL PROTECTED] writes:

 "Ch. A. Herrmann" wrote:
   I believe that if as much research were spent on Haskell compilation as
   on C compilation, Haskell would outperform C.

 Unless I've got a dramatically distorted view of the amount of research
 that goes on for imperative vs functional languages, and C vs haskell it
 seems that they get, to an order of magnitude, the same amount of
 research.

I think a more appropriate term (and more directly responsible for C
performance) would be "engineering effort".  Having a well-performing
C compiler is a sine qua non for most computer manufacturers.  (We
really need to get a Haskell program into SPEC.)

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants




Re: speed of compiled Haskell code.

2000-03-21 Thread Ketil Malde

"Jan Brosius" [EMAIL PROTECTED] writes:

 But this example task was chosen as unlucky for Haskell.
 In other, average case, I expect the ratio of  6-10.

 This seems that Haskell cannot be considered as a language for real
 world applications but merely as a toy for researchers .

Yeah.  Let's just lump Haskell in with Perl, Python, Java, Lisp and
all those other toy languages, completely useless in the "real world".

The only argument against Haskell's performance that IMHO carries 
any real weight, is that GHC is dog slow as a compiler[0].  No other
Haskell programs I've used or written[1] have been slow enough for me
to notice it.

-kzm

[0] almost as bad as Microsoft's C++ compiler, imagine that.
[1] admittedly not many.  Are people using Haskell having problems
getting good enough performance?  Enough to regret choosing it as a
language? (This is not a rhetoric question!)
-- 
If I haven't seen further, it is by standing in the footprints of giants




Re: speed of compiled Haskell code.

2000-03-21 Thread Andreas C. Doering

 [1] admittedly not many.  Are people using Haskell having problems
 getting good enough performance?  Enough to regret choosing it as a
 language? (This is not a rhetoric question!)
No and yes. 
I use Haskell mainly for combinational problems in research. 
I would love to get higher performance without much effort. 
For one result I had to wait for over a week, the process used over 800MB 
main mem on our Sun Enterprise. 
GHC-compiled over Hugs gave approximately a factor 3. 
Haskell allows me to use smarter algorithms with small effort, I never had
implemented the stuff at all in C. 
I did not yet try to use parHaskell so we have nice parallel systems here 
(e.g. cluster with 96 Pentiums). 

Andreas

---
Andreas C. Doering
Medizinische Universitaet zu Luebeck
Institut fuer Technische Informatik
Ratzeburger Allee 160
D-23538 Luebeck Germany

Tel.: +49 451 500-3741, Fax: -3687
Email: [EMAIL PROTECTED]
Home: http://www.iti.mu-luebeck.de/~doering 
 quiz, papers, VHDL, music

"The fear of the LORD is the beginning of ... science" (Proverbs 1.7)





Fw: Fw: a problem concerning a paper

2000-03-21 Thread Jan Brosius


- Original Message -
From: Marcin 'Qrczak' Kowalczyk [EMAIL PROTECTED]
To: [EMAIL PROTECTED]
Sent: Monday, March 20, 2000 8:58 PM
Subject: Re: Fw: a problem concerning a paper


 Mon, 20 Mar 2000 14:59:26 +0100, Jan Brosius
[EMAIL PROTECTED] pisze:

   let v = runst (newVar True)
   in
   runST (readVar v)
  
   Consider the last line ;

 Consider the first line before, because it must be typed in order to
 type the last line.

 "newVar True" has type "ST s (MutVar s Bool)".
 runST has type "(forall s. ST s a) - a".

 The type of expected argument of runST cannot be matched with the
 type of the actual argument. "ST s (MutVar s Bool)" is not of the
 form "forall s. ST s a" for any type a, because the second argument
 of ST depends on the first, yet "forall s. ST s a" says it does not

 Yes , but what if I would say using your own explanation below that s is
not a variable anymore
but that it actually has a certain specific type say  s0. In that case ...
but to keep this discussion
in sequence I first need to know if this is correct.

 (a is bound somewhere outside).

 So the first line won't typecheck, and the question whether the last
 line would typecheck if the first line would becomes irrelevant.

I think it is relevant,  for in the paper it is said that "s is free in ...
and so it doesn't match the type of runST ".
I beg to discuss this paper since it is the most recent explanation of the
implementation of runST
that I could download . If I can understand this paper I can understand the
rest too, I think.
Moreover it is important even for those who only uses Haskell98 since the
implementation
of  IO a  comes from   ST RealWorld a .




 Now, consider the following example:

 runST $ do
 v - newVar True
 return (runST (readVar v))

 Here the cause is different. The type of "readVar v" is "ST s Bool".
 Which s? The s that comes from a lambda-bound variable v, because
 readVar requires s from the monad and s from the variable to be the
 same. The lambda is hidden inside the do notation:

 runST $
 newVar True = \v -
 return (runST (readVar v))

 "ST s Bool" with s taken from the environment does not match
 "forall s. ST s a", because runST requires the s to be free.

So , I think you mean s is no longer a variable but has a certain type say
s0. Or am I wrong ?
But again please let us focus the discussion on the paper. Once I understand
this paper I can go on further.



 BTW. In GHC and Hugs the names are actually STRef, newSTRef, readSTRef,
 writeSTRef.

Please focus the discussion on the paper. ( By the way several (not all)
compressed archived papers
could not be opened by my Winzip program (I use Windows NT ))


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








Fw: speed of compiled Haskell code.

2000-03-21 Thread Jan Brosius


- Original Message -
From: Ketil Malde [EMAIL PROTECTED]
To: Jan Brosius [EMAIL PROTECTED]
Cc: [EMAIL PROTECTED]; S.D.Mechveliani [EMAIL PROTECTED]
Sent: Tuesday, March 21, 2000 10:14 AM
Subject: Re: speed of compiled Haskell code.


 "Jan Brosius" [EMAIL PROTECTED] writes:

  But this example task was chosen as unlucky for Haskell.
  In other, average case, I expect the ratio of  6-10.


  This seems that Haskell cannot be considered as a language for real
  world applications but merely as a toy for researchers .

 Yeah.  Let's just lump Haskell in with Perl, Python, Java, Lisp and
 all those other toy languages, completely useless in the "real world".

 The only argument against Haskell's performance that IMHO carries
 any real weight, is that GHC is dog slow as a compiler[0].  No other
 Haskell programs I've used or written[1] have been slow enough for me

NO, NO and NO , please read only what I have written. E.g. I believe that
Ocaml is certainly not toy language, it gives as
far as people have communicated to me fast compact native code.
My question about the speed of Haskell is not meant to upset people. On the
contrary Haskell does attract me by its elegance.
I just wanted to know what to expect of the code produced. I thought some
people could give me some honest answers
about it. Recent (really recent ) benchmarks are not available ont the
Haskell website as far as I know

Friendly

Jan Brosius  (a lazy wanting to use Haskell )

 to notice it.

 -kzm

 [0] almost as bad as Microsoft's C++ compiler, imagine that.
 [1] admittedly not many.  Are people using Haskell having problems
 getting good enough performance?  Enough to regret choosing it as a
 language? (This is not a rhetoric question!)
 --
 If I haven't seen further, it is by standing in the footprints of giants







compressed papers [was: a problem concerning a paper]

2000-03-21 Thread Herbert Graeber

 ( By the way several (not all) compressed archived papers
 could not be opened by my Winzip program (I use Windows NT ))

I had this problem, too. I have found that Internet Explorer
automatically decompresses .gz-files, but does not remove the extension.
A easy workaround is to rename the file and remove the .gz-extension.

I hope this helps.

Herbert Graeber






Re: Fw: speed of compiled Haskell code.

2000-03-21 Thread Ketil Malde

"Jan Brosius" [EMAIL PROTECTED] writes:

 NO, NO and NO , please read only what I have written. 

You mean, apart from

 This seems that Haskell cannot be considered as a language for real
 world applications but merely as a toy for researchers .

?  I could have sworn you were saying here that Haskell was unsuitable
for "real" work, due to the cited performance loss of factor of 6-10. 

My point was that there's plenty of work being done in languages a lot 
slower than Haskell.  There may be reasons for not using Haskell in
the "real" world, performance is IMHO not an important one.

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants




Re: speed of everything

2000-03-21 Thread Jerzy Karczmarczuk

"Andreas C. Doering" wrote:

...
 I would love to get higher performance without much effort.

 For one result I had to wait for over a week, ...


So do I, so do I!

Twice I had to wait 9 months. But the results are nice.

Jerzy Karczmarczuk
Caen, France




Re: Fw: speed of compiled Haskell code.

2000-03-21 Thread Ketil Malde


In the vein of benchmarking,

For those of you who follow comp.arch (or am I the only one?), you
have probably noticed the discussion about Stalin vs. C compilers.
For those who don't, it's basically one particular Scheme program
where compiled Scheme beats a naïve rewrite in C with orders of
magnitude (5s vs 30s was cited).

When rewriting in Haskell, I got some rather interesting results, hugs 
apparently runs the program about as fast as compiled Scheme (!) (I
get 8 seconds on a P150, while the numbers above were from a PPro200), 
and a compilation with GHC brings it down to about zero (0.7s to be
exact), but returns 0 instead of some large number.

This puzzles me, so I thought I'd turn to the list to see if anybody
here can shed light on my practices.  Am I committing some grave error 
in my translations?  Have I inadvertently performed source code
optimization?  Is there a bug in GHC?  Or is it just damned good at
figuring out things analytically?

The source code is as follows, with most of the original Scheme code
submitted in comments. (The missing Scheme is the integrate*
functions, which are rather trivially translated.  If anybody asks,
I'll dig them up).  Here goes:

-8
integrate1D :: Double - Double - (Double-Double) - Double
integrate1D l u f =
  let  d = (u-l)/8.0 in
 d * sum 
  [ (f l)*0.5,
f (l+d),
f (l+(2.0*d)),
f (l+(3.0*d)),
f (l+(4.0*d)),
f (u-(3.0*d)),
f (u-(2.0*d)),
f (u-d),
(f u)*0.5]

integrate2D l1 u1 l2 u2 f = integrate1D l2 u2 
(\y-integrate1D l1 u1 
  (\x-f x y))

zark u v = integrate2D 0.0 u 0.0 v (\x-(\y-x*y))

{-
(define (r-total N)
 (do ((I 1 (+ I 1))
  (Sum 0.0 (+ Sum (zark (* I 1.0) (* I 2.0)
   (( I N) Sum)))
-}

ints = [1.0..]
zarks = zipWith zark ints (map (2.0*) ints)
rtotals = head zarks : zipWith (+) (tail zarks) rtotals
rtotal n = rtotals!!n

{-
(define (i-total N)
 (do ((I 1 (+ I 1))
  (Sum 0.0 (+ Sum (let ((I2 (* (* I I) 1.0))) (* I2 I2)
   (( I N) Sum)))
-}

is = map (^4) ints
itotals = head is : zipWith (+) (tail is) itotals
itotal n = itotals!!n

{-
(define (error-sum-of-squares N)
 (do ((I 1 (+ I 1))
  (Sum 0.0 (+ Sum (let ((E (- (r-total I) (i-total I (* E E)
   (( I N) Sum)))

(begin (display (error-sum-of-squares 1000)) (newline))
-}

es = map (^2) (zipWith (-) rtotals itotals)
etotal n = sum (take n es)

main = putStrLn (show (etotal 1000))

8




The point of literate programming

2000-03-21 Thread Ketil Malde


Since we're debating literate programming and embedded documentation,
I wonder what is the point, what are we trying to achieve?

Is it to

a) write books or papers containing pieces of code?
b) add some formatting and functionality to comment blocks?
c) make source code easier to navigate and understand?
d) embed man-pages or similar documentation in the source code?
e) something else entirely?

Anyway, I'd suggest using the existing syntax, with some simple
conventions:

Using POD as a basis, let's instead use {- and -} to delimit our
comment blocks.  Then, allow a few tags for markup in there, I'd
suggest we need to label headings, labels and references, and a few
pretty-printing tricks, like emphasis.

Syntax-wise, I'd suggest using the \style{LaTeX}, since these kind of
tags tend IMHO to be more readable than styleXML/HTML/style, and
since backslash and curly brackets tend to interfere less with text.
(Also a point to consider, commenting away existing code.)  It'd also
be easy to transit to LaTeX-lhs using the \begin{code}-\end{code}.

This should at least partly address b), c) and d), provide an upgrade
path to a), while being completely backwards compatible with existing
tools.  Existing source would also be forward compatible, since plain
text in comments would still be fine.  Conversion to HTML or
postscript should be straightforward, as well as man page generation.

I've probably not thought things thoroughly through, but at least at
first sight this seems to be a reasonable way to go.  Anything I'm
missing? 

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants




Re: Fw: HaskellDoc?

2000-03-21 Thread Jonathan King


On Tue, 21 Mar 2000, Jan Brosius wrote:

  Jonathan King [EMAIL PROTECTED] wrote:
 
  (Well, the person touting lout seemed to ignore the HTML
  requirement...)
 
 I invite you to look at he following website
 
 http://www.ptc.spbu.ru/~uwe/lout/lout.html

But, of course, I had.  Whenever I look at some piece of software new to
me, and have questions about it, I look at the FAQ.  In this case, I saw a
FAQ referenced there, read it, and saw, in the answer to question 3.1:

   3. Lout Packages

   3.1 Can I produce HTML from my Lout documents? 

   The short answer is no, not easily. The problem is that Lout is 
   quite different from HTML. Lout is a powerful language which
   allows you to place text or graphics at a specific point on the 
   page, and the ease with which this is possible is one of its nicest
   features. HTML is --purposefully-- very poor in this respect. 

OK, so the FAQ may be out of date, but I don't see that as my problem.  
I'd suggest that *this* paragraph is a fairly straightforward answer to
the question that I could best paraphrase as "no".  Which isn't to say
that lout has no nice points, but it strikes me as a better backend (along
side, e.g., HTML) for processing than an input for a literate programming
tool.

jking






Re: Fw: HaskellDoc?

2000-03-21 Thread Ketil Malde

Jonathan King [EMAIL PROTECTED] writes:

Lout is a powerful language which allows you to place text or
graphics at a specific point on the page

I'll just point out that these capabilities are *not* what one wants
to have in comments.  I think we rather want *semantic* markup. 

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants




Re: speed of compiled Haskell code.

2000-03-21 Thread Jonathan King


On 21 Mar 2000, Ketil Malde wrote:

 "Jan Brosius" [EMAIL PROTECTED] writes:
 
  But this example task was chosen as unlucky for Haskell.
  In other, average case, I expect the ratio of  6-10.
 
  This seems that Haskell cannot be considered as a language for real
  world applications but merely as a toy for researchers .
 
 Yeah.  Let's just lump Haskell in with Perl, Python, Java, Lisp and
 all those other toy languages, completely useless in the "real world".

Not sure I understand this statement.  Compiled common lisp and scheme are
pretty competitive with C at this point for a great many things.  Java is
designed to be portable as byte codes, which is a different aim than the
others.  On the string/text processing programs where it excels,
performance of both perl and C (at least in my hands :-)) tend to be I/O
bound, and perl is waaay easier to get written.  I know less about python,
but I do know they've got a version (jpython) that produces java
bytecodes, while there is also an effort going on to introduce stronger
type-checking into the language (to improve its performance).  I'm not
sure there is any pair of these 6 languages I would lump together other
than possibly perl and python.

A more reasonable question might be: what real world applications would
you use choose Haskell for today?  And other people have given better
answers here than I could.  

Which I guess is a cue to bring up my hunch that hugs/ghc *could* end up
being a language that could eventually "out-perl perl" in some
applications, since it's a good choice for parsing, and many
text-filtering applications look like good matches for a functional
programming language.

In that regard, I think the biggest problems remaining are the lack of a
standard "fast" string type, and some remaining warts in hugs.  These are
maybe easiest to see when you do something like "strace -c" on a hugs
program and the comparable perl program.  So, in my naive version of
"hello world", the hugs version generates 803 calls to 'lstat', 102 calls
to 'stat', and a performance-killing 13 calls to 'write'; yup, that's
one for every character. :-(  throw most of those out, and you're within
shouting distance of perl.  And that would be something to shout about.

Oh yeah: my code. :-)

#!/usr/bin/runhugs
module Main where
main = putStr "Hello, world\n"

---

#!/usr/bin/perl
print "Hello, world\n";

jking






Re: Fw: speed of compiled Haskell code.

2000-03-21 Thread Jan de Wit

Hi All,

   I find this interesting. It would be nice if you would like to explain me
   what you mean by " hyperstrict"
   
I think hyperstrict means that a function completely evaluates *all* of its
arguments before the body of the function, as opposed to only some of
them. 
A function f taking n arguments is strict in its i'th argument if
f a_1 .. a_i-1  _|_ a_i+1 .. a_n = _|_
E.g. const is strict in its first argument but not in its second.

f is strict in all arguments if
f a_1 .. a_n = _|_ whenever one of the a_i's is _|_.
multOrAdd x y z = if x then y * z else y + z 
is strict in all of it arguments.
Hyperstrict has, in my view at least, also an annotation of completely
evaluating all arguments before the body of the function - something else
than (eventually) evaluating them all. I'm not sure about this though,
maybe someone can shed more light on this matter. 

Hope this helps (or leads to someone else giving a better definition :-)

Jan de Wit  





Postdoc Opportunities with the Yale Haskell Group

2000-03-21 Thread John Peterson


  Post-Doctorate Research Position
  Yale University
   Department of Computer Science

The Yale Haskell Project (http://haskell.org/yale) in the Department of
Computer Science at Yale University is seeking applicants for a
Post-Doctoral Research Position.  Our research uses Haskell and
"Functional Reactive Programming" as a foundation for a variety of
embedded domain-specific languages, including FROB: a language for robot
control, and FVision: a computer vision and visual tracking language.

Our general areas of research include:
  o Foundational aspects of DSL research
  o Robotics and vision research using Haskell-based DSLs
  o Programming evironments for DSL use and construction
  o Compilation/optimization/transformation of DSLs

Successful applicants must have a PhD in Computer Science or closely
related field, and experience with modern programming languages such as
Haskell, ML, or Java.  The term of the position is 1 year with an option
to renew for additional years.  A starting date around September 2000
(or earlier) is preferred; candidates should have completed all thesis
requirements by that time.  A competitive salary will be offered,
commensurate with the applicant's qualifications and experience.  Yale
University is an Equal Opportunity/Affirmative Action employer;
qualified women and minority candidates are encouraged to apply.

Interested applicants should send a resume, a short research statement,
and three letters of recommendation to John Peterson (email address:
[EMAIL PROTECTED]).  Electronic application is preferred, but if
necessary, applications may be sent to the address below.

John Peterson
Department of Computer Science
Yale University
P.O. Box 208285
New Haven, CT 06520-8285, USA

Phone: 203-432-1272
Email: [EMAIL PROTECTED]




RE: speed of compiled Haskell code.

2000-03-21 Thread Mark P Jones

| In that regard, I think the biggest problems remaining are the lack of a
| standard "fast" string type, and some remaining warts in hugs.  These are
| maybe easiest to see when you do something like "strace -c" on a hugs
| program and the comparable perl program.  So, in my naive version of
| "hello world", the hugs version generates 803 calls to 'lstat', 102 calls
| to 'stat', and a performance-killing 13 calls to 'write'; yup, that's
| one for every character. :-(  throw most of those out, and you're within
| shouting distance of perl.  And that would be something to shout about.

I see big problems in using Hugs as an example in discussions about the
speed of compiled code.  Hugs derives from Gofer, which was designed to
fit on a 16 bit machine with a fairly small memory (several times smaller
than the PDAs, digital cameras, and video cards in use today).  It was
also designed, from the beginning, to be an interactive system based
around a simple read-eval-print loop.  Performance was never the priority.
After all, there were a couple of other places you could turn for a compiler
if you did want performance, and those folks had spent a lot of time and
effort on building their systems.  Hugs was intended to complement rather
than compete with them.

Because interactivity was a goal, Hugs, by default, does indeed call
fflush after every character, which causes the repeated calls to write
that you see.  If it didn't do that, then programs on slow machines or
with expensive underlying computations might have behavior that is counter-
intuitive and confusing, especially to beginners.  We are, after all,
talking about a lazy language, and so you wouldn't think that you'd have
to wait for a whole line of output before you saw the first character.

Surprisingly, perhaps, the performance of Hugs turned out to be good enough
for many tasks, particularly on the machines that we use today, and so
tools like runhugs have become a viable option for some purposes.  But you
should always remember that Hugs came before runhugs, and that the default
distribution is tuned primarily for use as an interactive environment.

There is, in fact, a compile-time setting that you can use to prevent
Hugs from calling fflush after every character (I think it's FLUSHEVERY,
but you should check).  If you set that appropriately, then Hugs I/O
will (or should) run a little more quickly.

All the best,
Mark


[EMAIL PROTECTED]  Pacific Software Research Center, Oregon Graduate Institute
Looking for a PhD or PostDoc?  Interested in joining PacSoft?  Let us know!





Re: speed of compiled Haskell code.

2000-03-21 Thread Manuel M. T. Chakravarty

"Andreas C. Doering" [EMAIL PROTECTED] wrote,

  [1] admittedly not many.  Are people using Haskell having problems
  getting good enough performance?  Enough to regret choosing it as a
  language? (This is not a rhetoric question!)
 No and yes. 
 I use Haskell mainly for combinational problems in research. 
 I would love to get higher performance without much effort. 
 For one result I had to wait for over a week, the process used over 800MB 
 main mem on our Sun Enterprise. 
 GHC-compiled over Hugs gave approximately a factor 3. 

Did you ever try (space) profiling the program?  IMHO if you
have applications were performance matters, profiling is
imperative. 

Manuel




Announce: MySQL-HS 0.9, interface to the MySQL database

2000-03-21 Thread Volker Wysk

Hello.

I've made an interface to the MySQL database management system. I'm
releasing it under the LGPL.

Homepage:

http://www.volker-wysk.de/mysql-hs


bye





Bcc: Re: HaskellDoc?

2000-03-21 Thread Manuel M. T. Chakravarty


George Russell [EMAIL PROTECTED] wrote,

 "Manuel M. T. Chakravarty" wrote:
  IMHO it would be much more important to think about a
  mechanism for automatically extracting all the interface
  information (including the interface comments) from a
  Haskell module.  Something like an automatically generated
  Modula-2 definition module that defines and explains the
  interface without forcing the reader to wade through the
  implementation.
 A less technological solution which has been suggested before would be an
 extension to the Haskell language to allow type annotations in
 module export lists.  This would allow a considerable part of the
 interface to be documented and automatically checked in one central
 place.  I could then write a typical Haskell module in the following order: 
 (1) module export list, listing types and comments for all values; 
 (2) import list; (3) interface and type declarations; (4) all non-trivial code.  
 Then it is easy to get at the interface (sections (1)  (3)), but at the 
 same time you don't have to duplicate the same stuff in different places.

Unfortunately, this has exactly the same problem as Modula-2
has: You have to duplicate types and comments for all
exported entities, or leave the implementation `naked'.  (In 
M-2, you had to repeat the type and people usually did not
provide comments in the implementation module.)

The implementor wants comments, type signature, and
implementation, but the user of a module (most of the time)
only wants the type signature and comments.  Thus, it seems
the best solution is to automatically strip out the
implementation (and all implementation-specific comments)
to generate a user-level interface.

Manuel






== and hyperstrictness

2000-03-21 Thread Fergus Henderson

On 21-Mar-2000, Sven Panne [EMAIL PROTECTED] wrote:
 Example: length is strict in its argument, but the following
 function is hyperstrict (at least according to my definition :-) :
 
len :: Eq a = [a] - Int
len [] = 0
len (x:xs) | x == x = 1 + len xs
 
 This 'x == x' is folklore for getting rid of some space leaks,
 AFAIK.

Actually, that raises an interesting question:
should instances of `==' be required to be hyperstrict
in cases where they return `True'?

The Haskell report is silent on this issue.

Suppose Sven implements his `len' function as above, and furthermore
implements a library which depends on this function being hyperstrict.
Suppose next that I implement an instance of `==' that returns `True' without
evaluating the arguments, and then finally suppose a third programmer called
say Joe comes along and uses my type with Sven's library.  If it breaks, who
is to blame?

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