Binary methods

1999-07-29 Thread Marcin 'Qrczak' Kowalczyk

Is it possible to set up classes that express the following (using
ghc extensions)?

There are various kinds of geometrical shapes. They can be packed
inside an existentially qualified datatype. Values of that existential
need to be compared for equality: the comparison of figures of
different shapes yields always False, and for the same shape it calls
the appropriate function for that shape. Also they need to be checked
for inclusion: each pair of shapes defines its own inclusion relation.

Of course there can't be a datatype which enumerates all the shapes.
Any shapes may be added in future with instances of appropriate classes.

-- 
 __("Marcin Kowalczyk * [EMAIL PROTECTED] http://kki.net.pl/qrczak/
 \__/  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-



redirecting .hi

1999-07-29 Thread S.D.Mechveliani

I asked earlier how to replace in Makefile many lines of kind
  source/Categs_flags  = -ohi $(E)/Categs.hi
  source/auxil/Set__flags  = -ohi $(E)/Set_.hi
  ...
(processed by the   $($*_flags)  compilation key)
with something short.

Thanks to  Marc Van Dongen, Simon Marlow, Sigbjorn Finne 
for the advices.
Sigbjorn Finne  writes

 If you're using GNU make I'd simply add

 SRC_HC_OPTS += -ohi $(E)/$*.hi

I found that it does almost what is needed. 
Only it has to be corrected to   -ohi $(E)/$(notdir $*).hi

Thanks.

--
Sergey Mechveliani
[EMAIL PROTECTED]

















RE: I thought concurrent haskell was _preemptive_!

1999-07-29 Thread Simon Peyton-Jones

You are right that we promised this a while ago, and have
not delivered.  I'm sorry about that.  I, for one, had not
appreciated how important it was to you.

We are planning to release 4.04 this week, but this thread
stuff just won't make it in.

We'll do it right after the release, modulo holidays.
In practice that means "sometime in August".  Is that 
enough for you?

Simon

 -Original Message-
 From: George Russell 
 Sent: Thursday, July 29, 1999 11:19 AM
 To: [EMAIL PROTECTED]
 Subject: RE: I thought concurrent haskell was _preemptive_!
 
 
 I would like to add my strong support, as the person in charge of
 transferring the UniForM workbench, for the implementation of
 wait functions on input and output handles and input on Posix.FD 
 which don't block everything else to be done urgently.  I think 
 I suggested this in May, and was told it was coming soon
 but it still hasn't appeared.  Otherwise it is possible that the
 entire UniForM project may be held up for lack of this simple
 facility.
 



ANNOUNCEMENT: The Glasgow Haskell Compiler, version 4.04

1999-07-29 Thread Simon Marlow

 The Glasgow Haskell Compiler -- version 4.04
==

We are pleased to announce a new release of the Glasgow Haskell
Compiler (GHC), version 4.04.  The source distribution and various binary
distributions are freely available via the World-Wide Web and through anon.
FTP; details below.

Haskell is "the" standard lazy functional programming language; the
current language version is Haskell 98, agreed in December 1998.
Haskell related information is available from the Haskell home page at

http://haskell.org/

GHC's Web page lives at

http://research.microsoft.com/users/t-simonm/ghc/

+ What's new
=

   - GHC is now officially Open Source, see the LICENSE file in the
 distribution for details.

   - Rewrite rules can be specified in the source using the RULES
 pragma.  This is used for automatic fusion of common list
 functions.

   - Performance tuning: compiled programs now allocate 30% less
 and run 20% faster on average compared to GHC 4.02.

   - GHC now uses a Happy parser instead of the old yacc/lex one.

For full details see the release notes:


http://research.microsoft.com/users/t-simonm/ghc/Docs/latest/users_guide/use
rs_guide-1.html#ss1.4

+ Mailing lists


We run mailing lists for GHC users and bug reports; to subscribe, send
mail to [EMAIL PROTECTED]; the msg body should be:

subscribe glasgow-haskell-which Your Name [EMAIL PROTECTED]

Please send bug reports about GHC to [EMAIL PROTECTED]; GHC
users hang out on [EMAIL PROTECTED]


+ On-line GHC-related resources


Relevant URLs on the World-Wide Web:

GHC home page http://research.microsoft.com/users/t-simonm/ghc/
Haskell home page http://haskell.org/
comp.lang.functional FAQ
http://www.cs.nott.ac.uk/Department/Staff/mpj/faq.html


+ How to get it


The easy way is to go to the WWW page, which should be
self-explanatory:

http://research.microsoft.com/users/t-simonm/ghc/

Once you have the distribution, please follow the pointers in the
README file to find all of the documentation about this release.  NB:
preserve modification times when un-tarring the files (no `m' option
for tar, please)!


+ Binary Distributions
==

We currently have binary distributions for i386-unknown-linux and
sparc-sun-solaris2 available from the web page.  The following distributions
will follow shortly:

  * Win32
  * i386-unknown-freebsd3
  * hppa1.1-hp-hpux


+ System requirements
==

To compile up this release, you need a machine with 64+MB memory, GNU C
(`gcc'), `perl' plus a version of GHC installed (3.02 at least).  This
release is known to work on the following platforms:

  * i386-unknown-{linux,solaris2,freebsd,cygwin32}
  * sparc-sun-{sunos4,solaris2}
  * hppa1.1-hp-hpux{9,10}

Ports to the following platforms should be relatively easy, but
haven't been tested due to lack of time/hardware:

  * alpha-dec-osf{2,3}
  * mips-sgi-irix{5,6}
  * {rs6000,powerpc}-ibm-aix

The installer's guide included in distribution gives a complete
run-down of what-ports-work; an on-line version can be found at

 
http://research.microsoft.com/users/t-simonm/ghc/Docs/latest/installation_gu
ide/installing.html



Re: Again: Referential Equality

1999-07-29 Thread Fergus Henderson

On 28-Jul-1999, Lennart Augustsson [EMAIL PROTECTED] wrote:
 Fergus Henderson wrote:
 
  equal x y = unsafePerformIO $ do
  ptrEq - ptrEqual x y
  return (ptrEq || deep_equals x y)
 
  Note that unlike `req', `equal' here _is_ referentially transparent.
 
 No, it's not.  If x and y are both bottom you can get unexpected
 results, i.e., sometimes it terminates, sometimes it doesn't.

Sorry, you're absolutely right.  And the same problem arises with
exceptions too -- if x and y are both `raise "oops"' then sometimes it
returns `True' and other times it returns `raise "oops"'.  Oops indeed!

I'm not sure off-hand what the best fix would be.  One possible solution
would be to force evaluation of the arguments if they are equal:

 equal x y = unsafePerformIO $ do
 ptrEq - ptrEqual x y
 return (if ptrEq then x `hyperseq` True else deep_equals x y)

However, this compromises the nice O(1) performance in that case.

Another possible fix would be to rename `equal' as `unsafe_equal',
noting that it is referentially transparent so long as neither of its
arguments contains bottom or any exceptional value; it would then be
the programmer's responsibility to check that all callers ensure that
this condition is satisfied for all calls to `unsafe_equal'.

The second fix is probably best.  But it's still rather ugly.

P.S.
I'm just glad that the same problem doesn't arise in Mercury :-)

The analagous Mercury code would be

:- type bool --- yes ; no.

:- func equal(T, T) = bool.
:- func deep_equals(T, T) = bool.
:- pred ptr_equal(T::in, T::in, bool::out) is cc_multi.

equal(X, Y) = promise_only_solution((pred(Res::out) is cc_multi :-
ptr_equal(X, Y, PtrEq),
( PtrEq = yes, Res = yes
; Res = (if deep_equals(X, Y) then yes else no)
)
)).

In Mercury, for cases such as `equal(throw("oops"), throw("oops"))'
or `equal(loop, loop)' (where `loop' is defined by `loop = loop.'),
the declarative semantics says that the result must be `yes'.  The
operational semantics, however, exhibits the same nondeterminism as
the Haskell code did.  This is OK in Mercury because in Mercury
although the operational semantics is required to be sound w.r.t. the
declarative semantics, it is not required to be complete; in cases
where the declarative semantics says that the result is `yes', it may
still be acceptable for the implementation to throw an exception
rather than computing the result `yes'.  In Mercury, if you want to
reason about whether your program will terminate or throw exceptions,
you need to use the operational semantics rather than the declarative
semantics.

-- 
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: The dreaded layout rule

1999-07-29 Thread Simon Marlow


Manuel Chakravarty writes:

 What kind of implementation did the originators of this
 clause envision?  If the layout rule is really implemented
 as a filter between the scanner and the parser, it seems
 extremely awkward to add a dependency on the error condition
 of the parser - in particular, it makes a functional, ie,
 side-effect free implementation rather hard and a true two
 phase implementation impossible.  So, I guess (I hope!!) 
 there is a nifty trick that lets you achieve the same effect
 by using only conditions depending on local information
 (either during layout processing or by letting the parser
 insert the missing braces).

GHC and Hugs both make use of yacc-style error recovery, albeit in a very
limited form.  The idea is to have a production in your grammar like this:

close_brace :   '}'
| error

where the '}' token is assumed to have been inserted by the lexical analyser
as a result of layout (i.e. a token was found to be less indented than the
current layout context).  The error case fires if any other token is
encountered, and the semantic action for this production will probably pop
the current layout context and carry on (in practice you also have to tell
yacc not to continue with error recovery, otherwise all sorts of strange
things happen).  Take a look at GHC's parser for the details.

I believe you're right in that a true two-phase implementation of the
Haskell grammar is impossible.  This is consistent with Haskell's policy of
making life easy for programmers and hard for compiler writers :)

Cheers,
Simon





The dreaded layout rule

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

One of our students just pointed out an IMHO rather
problematic clause in the layout rule.  In Section 2.7 of
the Haskell 98 Report it says,

  A close brace is also inserted whenever the syntactic
  category containing the layout list ends; that is, if an
  illegal lexeme is encountered at a point where a close
  brace would be legal, a close brace is inserted.

And in B.3, we have in the first equation of the definition
of `L',

  L (t:ts) (m:ms) = } : (L (t:ts) ms)   if parse-error(t)  (Note 1)

where Note 1 says,

  The side condition parse-error(t) is to be interpreted as
  follows: if the tokens generated so far by L together with
  the next token t represent an invalid prefix of the
  Haskell grammar, and the tokens generated so far by L
  followed by the token } represent a valid prefix of the
  Haskell grammar, then parse-error(t) is true.

What kind of implementation did the originators of this
clause envision?  If the layout rule is really implemented
as a filter between the scanner and the parser, it seems
extremely awkward to add a dependency on the error condition
of the parser - in particular, it makes a functional, ie,
side-effect free implementation rather hard and a true two
phase implementation impossible.  So, I guess (I hope!!) 
there is a nifty trick that lets you achieve the same effect
by using only conditions depending on local information
(either during layout processing or by letting the parser
insert the missing braces).

Cheers,

Manuel





Re: The dreaded layout rule

1999-07-29 Thread Ian Holyer

This is a multi-part message in MIME format.
--F93F7E72348E2F23CC7D1D40
Content-Type: text/plain; charset=us-ascii
Content-Transfer-Encoding: 7bit

Manuel says

 One of our students just pointed out an IMHO rather problematic clause in the  
layout rule ... So, I guess (I hope!!) there is a nifty trick that lets you
 achieve the same effect by using only conditions depending on local
 information ...

Attached is Haskell code which handles the layout rule reasonably well as a
separate pass between scanning and parsing (though it is Haskell 1.4 rather
than 98 and imperfect).
-- 
Ian[EMAIL PROTECTED], http://www.cs.bris.ac.uk/~ian
--F93F7E72348E2F23CC7D1D40
Content-Type: text/plain; charset=us-ascii; name="Layout.hs"
Content-Transfer-Encoding: 7bit
Content-Disposition: inline; filename="Layout.hs"

{--
LAYOUT ANALYSIS

The layout function deals with the layout conventions of Haskell 1.4, inserting
extra "{", ";" and "}" tokens to represent implicit blocks.  The inserted
tokens are marked as implicit, and are inserted as early as possible in the
token stream, in order to promote well-phrased and well-positioned error
messages in case of trouble.  The layout function never fails; it is left up to
a parser to detect errors.

The Haskell standard says that a block (or layout list) is terminated "whenever
the syntactic category containing the layout list ends, that is, if an illegal
lexeme is encountered at a point where a close brace would be legal".  This can
only be implememented easily if layout processing is combined with parsing.
Here, layout processing is done separately, so an approximation to the standard
is achieved by keeping track of brackets.  See the end of this file for
examples where the layout function deviates from the standard.

ISSUES TO BE RESOLVED

-- "case" terminated by "where" may be common enough to make a special case
-- "case" terminated by "," may be worth dealing with
-- check that "let"s inside "do" (which don't have "in") are handled OK
-- check explicit blocks, and their interaction with implicit ones

Ian Holyer  @(#) $Id: Layout.hs,v 1.2 1998/10/26 15:18:39 ian Exp $
--}

module Layout (layout) where

import Haskell
import Lex

-- Start layout processing.  If the source does not begin with "module" or "{",
-- then there is an implicit surrounding block.  Here and elsewhere, a
-- lookahead past possible comments is done so that a token can be inserted
-- before the comments if necessary; also, the end-of-file token makes it
-- unnecessary to check for an empty token stream.

layout :: [Token] - [Token]
layout ts =
   if s == "module" then comments ++ scanExplicit [] (tok:rest) else
   openBlock [] (Tok "}" 1 0 Implicit) ts
   where
   comments = takeWhile isComment ts
   tok @ (Tok s r c k) : rest = dropWhile isComment ts

-- A stack of tokens is used to keep track of the surrounding blocks.  For each
-- block, its opening "{" token is pushed onto the stack.  In an implicit
-- block, the brackets "(",")" and "[","]" and "case","of" and "let","in" and
-- "if","then","else" are tracked by putting the opening bracket on the stack
-- until the matching closing bracket is found.  Each opening bracket is stored
-- on the stack with the indent for the current block in place of its actual
-- column.

type Stack = [Token]

-- Scan the source tokens while in an explicit block (or while not in any
-- blocks) when layout is inactive.  Look for an explicit close block token, or
-- a keyword which indicates the beginning of a new block. Treat field selector
-- as an explicit block.

scanExplicit :: Stack - [Token] - [Token]
scanExplicit stack [] = []
scanExplicit stack (t@(Tok s r c k) : ts1) = case s of
   "}" - t : closeBlock stack t ts1
   "where" - t : openBlock stack t ts1
   "let" - t : openBlock stack t ts1
   "do" - t : openBlock stack t ts1
   "of" - t : openBlock stack t ts1
   "{" - openBlock stack undefined (t:ts1)
   _ - t : scanExplicit stack ts1

-- Scan the source tokens while in an implicit block, with layout active.  The
-- parameters are the stack, the last token dealt with, and the remaining
-- tokens.  The block is terminated by indenting or by a suitable closing
-- bracket.  Treat field selector as an explicit block.

scanImplicit :: Stack - Token - [Token] - [Token]
scanImplicit stack@(Tok bs br bc bk : stack1) last@(Tok ls lr lc lk) ts =
   if c  bc || k == EndToken then close else
   if c == bc  r  lr then newline else
   case s of
  "where" - open
  "let" - pushopen
  "do" - open
  "of" - popopen "case"
  "in" - pop "let"
  "(" - push
  ")" - pop "("
  "[" - push
  "]" - pop "["
  "case" - push
  "if" - push
  "then" - poppush "if"
  "else" - pop "then"
  "}" - close
  "{" - 

RE: The dreaded layout rule

1999-07-29 Thread Malcolm Wallace

Manuel Chakravarty writes:
 
 What kind of implementation did the originators of this
 clause envision?  If the layout rule is really implemented
 as a filter between the scanner and the parser, it seems
 extremely awkward to add a dependency on the error condition
 of the parser - in particular, it makes a functional, ie,
 side-effect free implementation rather hard and a true two
 phase implementation impossible.

Simon Marlow replies:

 GHC and Hugs both make use of yacc-style error recovery, albeit in a very
 limited form.

And nhc uses parser combinators, which give you backtracking on error
conditions for free.  We actually do almost all layout processing at
the lexical stage, but where the parser expects a } and doesn't get
one, we just insert the }, and re-lex the remaining input.  I suppose
having to re-lex is a bit of a chore, but laziness comes to the rescue
somewhat.

Regards,
Malcolm






Re: The dreaded layout rule

1999-07-29 Thread Mike Thyer

If the scanning stage pairs the tokens it returns with
their positions, then scanning can be done once before
parsing begins.  I've done this with a parser implemented
with parser combinators, these combinators then decide
whether or not to accept a token based on which token
it is and how far it is indented.  I think this means
the grammar being parsed is a context sensitive one,
since the state of the parser is represented by more than
just a single stack.  We need a stack telling us what to
do next, and a stack of indentation levels, although
the way in which these stacks grow and shrink is related
they could not be replaced by a single stack, so the
grammar is not context free.

Now that I write this, I think that we could combine these 
stacks as a stack of stacks, although this isn't how I did it.  
I don't think this satisfies the requirements for a context free 
grammar (CFG) but I don't have a definition to hand at the moment.

Mike

Simon Marlow wrote:
 I believe you're right in that a true two-phase implementation of 
 the Haskell grammar is impossible.  This is consistent with Haskell's 
 policy of making life easy for programmers and hard for compiler 
 writers :)






Re: ANNOUNCEMENT: The Glasgow Haskell Compiler, version 4.04

1999-07-29 Thread Craig Dickson

Now that you're an (ahem) Microsoft employee, is there any intention of
allowing ghc to use Visual C++ instead of gcc, or supporting the Win32
platform without cygwin?

Thanks,

Craig

- Original Message -
From: Simon Marlow [EMAIL PROTECTED]
To: [EMAIL PROTECTED]; [EMAIL PROTECTED]
Sent: Thursday, 29 July 1999 10:37 am
Subject: ANNOUNCEMENT: The Glasgow Haskell Compiler, version 4.04


  The Glasgow Haskell Compiler -- version 4.04
 ==

[etc.]