Handling of non-layout sections in HsParser

2001-10-16 Thread Anders Lau Olsen


HsParser fails on any of these 6 examples:

data Data = A {
x :: Int
}

f1 x = let {
s = x
} in s

f2 x = do {
x
}

f3 x = case x of {
_ - 12
}

f4 x = s where {
s = 12
}

f5 y = A {
x = 45
}

The problem seems to be the production (copied from HsParser.ly)

 layout_off :: { () }  :   {% pushContext NoLayout }

This production is supposed to make the parser enter a NoLayout
context every time the lexer reaches an open brace '{'. It is used in
other productions such as

 decllist :: { [HsDecl] }
   : '{' layout_off decls '}'  { $3 }
   | layout_on  decls close{ $2 }

For some reason the use of layout_off only takes effect _after_ the
lexer has produced the next token. When the lexer reaches the second x
in

f2 x = do {
x
}

the NoLayout hasn't been pushed yet. Since x is indented to the same
column as f2, the lexer therefore inserts a ';'. The '{' followed by a ';'
causes the parser to fail. In code with a more normal indentation

f2 x = do {
x
}

the parser works fine, because the lexer in this case doesn't insert
an extra ';' or '}'.

One way of fixing this is to remove all uses of layout_off, and
instead delegate the pushing of NoLayouts to the lexer. I have
attached a patch of HsParser.ly and HsLexer.lhs to show what I had in
mind.

Anders


233c233
 '{' - special LeftCurly
---
 '{' - \ctxt - special LeftCurly (NoLayout : ctxt)


130c130
  :  '{' layout_off bodyaux '}'   { $3 }
---
  :  '{' bodyaux '}'  { $2 }
286c286
  : '{' layout_off decls '}'  { $3 }
---
  : '{' decls '}' { $2 }
370,371c370,371
  | srcloc con '{' layout_off fielddecls '}' 
  { HsRecDecl $1 $2 (reverse $5) }
---
  | srcloc con '{' fielddecls '}' 
  { HsRecDecl $1 $2 (reverse $4) }
417c417
  : 'where' '{' layout_off cbody '}'  { $4 }
---
  : 'where' '{' cbody '}' { $3 }
438c438
  : 'where' '{' layout_off valdefs '}'{ $4 }
---
  : 'where' '{' valdefs '}'   { $3 }
506c506
  : aexp '{' layout_off fbinds '}' {% mkRecConstrOrUpdate $1 (reverse $4) }
---
  : aexp '{' fbinds '}'   {% mkRecConstrOrUpdate $1 (reverse $3) }
571c571
  : '{' layout_off alts optsemi '}'   { reverse $3 }
---
  : '{' alts optsemi '}'  { reverse $2 }
601c601
: '{' layout_off stmts '}'{ $3 }
---
: '{' stmts '}'   { $2 }
738d737
  layout_off :: { () }:   {% pushContext NoLayout }



RE: Handling of non-layout sections in HsParser

2001-10-16 Thread Simon Marlow

 HsParser fails on any of these 6 examples:
 
[...]
 
 The problem seems to be the production (copied from HsParser.ly)
 
  layout_off :: { () }:   {% pushContext NoLayout }
 
 This production is supposed to make the parser enter a NoLayout
 context every time the lexer reaches an open brace '{'. It is used in
 other productions such as
 
  decllist :: { [HsDecl] }
  : '{' layout_off decls '}'  { $3 }
  | layout_on  decls close{ $2 }
 
 For some reason the use of layout_off only takes effect _after_ the
 lexer has produced the next token.

Yes, Happy seems to be grabbing a lookahead token, even though it
doesn't need to.  Anyway, your fix is the right one because it avoids
this non-deterministic behaviour in Happy, and it brings HsParser into
line with the way that GHC's parser works.  

I've committed your patches, thanks!

Cheers,
Simon

___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs



RE: Flags in GHCi

2001-10-16 Thread Simon Marlow

 I noticed a difference in behavior between running:
 
ghci -package utils
 
 And:
 
ghci
   ...
   Prelude :set -package utils
 
 On our system, the first one works (it finds all the right
 dynamic libraries and stuff), but the second one doesn't (it
 cannot find libreadline.so, and other dynamic libraries).

Thanks, this bug will be fixed in 5.02.1.

Cheers,
Simon

___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs



ghc-5.02: panic! NoCgInfo!

2001-10-16 Thread Armin Groesslinger

Hello,

when I try to compile the program below with ghc -fglasgow-exts
it says

ghc-5.02: panic! (the `impossible' happened, GHC version 5.02):
NoCgInfo!


I couldn't find a smaller example because little modifications make
the problem go away, e.g.

 - removing the type signature for `k'

 - replacing `y ([] ++ [[]] ++ [])' by `y ([] ++ [[]])'

 - changing the definition of `g' or `h', e.g.
 h ys = map (k (y [[0]])) ys


Regards,

Armin



module Test where

import List (transpose)

data X a = X a

class Y a b | a - b where
y :: a - X b

instance Y [[a]] a where
y ((x:_):_) = X x

g :: Num a = [X a] - [X a]
g xs = h xs
where
h ys = ys ++ map (k (y [[0]])) xs

k :: X a - X a - X a
k _ _ = y ([] ++ [[]] ++ [])

___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs



¯uªº¡IµL±ø¥ó°e±z¤â¾÷»Pªù¸¹

2001-10-16 Thread m2bvtr_2gk1525


§Ú­ÌÃØ°e±z¤â¾÷+ªù¸¹¡I¡I¡I¡I¡I

¨S¿ù¡I¡I§Ú­ÌÃØ°e±z¤â¾÷+ªù¸¹¡I¡I¡I¡I¡I

³oµ´¹ï¬O¯u¹êªº¡I  ½Ð¤£­n¦AÃhºÃ¤F¡I¡I

§Ú­Ì©M±z¤@¼Ë¬Oµ½¨}¡B¥¿ª½ªº¦Ñ¦Ê©m¡I¡I

«ô°U¡I¡I  «ô°U¡I¡I½Ð¤£­n¦AÃhºÃ§Ú­Ì¡I¡I¡I¡I

¤]½Ð¤£­n¦A¥´¹q¸Ü¸ß°Ý©M«H¹q°T¤F¡A

³o­ÓÃØ°e¤è®×»P©M«H¹q°T¨S¦³Ãö«Y¡I

§Ú­Ì¬O±¶°\¥ø·~ºÞ²zÅU°Ý¦³­­¤½¥q¡A

¬O§Ú­ÌÃØ°e±z¤â¾÷+ªù¸¹¡A¤£¬O©M«H¹q°T¡C



©ÒÃØ°e¤§§K¶O¤è®×¦p¤U¡G

ªù¸¹¡G   ©M«Hªù¸¹

³q¸Ü¶O­p¶O¤è®×¡G ©M«Hºëºâ188

ÃØ°e¤â¾÷¡G MOTOROLA  T2288¡]­^¤å¾÷¡^

ºëºâ188¤ë¯²¶O¡G 188¤¸

§K¶O³q¸Ü¡G  ©è188¤¸¤ë¯²¶O

¤@¯ë®É¬q¡G  0.16¤¸/¬í¡A¶g¤@¦Ü¶g¤é¥þ¤é

´î»ù®É¬q¡G  ¦P¤@¯ë®É¬q¦¬¶O

¥»ºô¤¬¥´¡G  0.08¤¸/¬í¡]¥b»ù¡^

¡]ºëºâ188­p¶O¤è¦¡¹ï¥ô¦ó©M«H¨Ï¥ÎªÌ¬Ò¬Û¦P¡^




¥t¦³¦Xºâ¥I¶O¤è®×¦p¤U¡G

ªù¸¹¡G ©M«Hªù¸¹

³q¸Ü¶O­p¶O¤è®×¡G ©M«H«¢©Ô900

¤â¾÷¡G Nokia 3310¡]¤¤¤å¾÷¡^
   ¥Ó½Ð¦¹´Ú¤â¾÷»Ý¥I¶O888¤¸¡A
   ¤ñ¦b¤@¯ë³q°T¦æ¥Ó½Ð¡A«K©y1000¤¸¥H¤W 

«¢©Ô900¤ë¯²¶O¡G 900¤¸

¨C¤ë§K¶O³q¸Ü¤ÀÄÁ¡G  200¤ÀÄÁ 

¤@¯ë®É¬q 0.11¤¸/¬í

´î»ù®É¬q 0.11¤¸/¬í

ºô¤º¤¬¼·¨C³q«e5¤ÀÄÁ¤º§K¶O¡F
¶W¹L³¡¥÷¡G1¤¸/¤À¡A
¥¼º¡1¤ÀÄÁ¥H1¤ÀÄÁ­p

¡]«¢©Ô900­p¶O¤è¦¡¹ï¥ô¦ó©M«H¨Ï¥ÎªÌ¬Ò¬Û¦P¡^




½Ðª`·N¡G«¢°Õ900¨C¤ë§K¶O³q¸Ü¤ÀÄÁ¼Æ¡A·í¤ë¥¼¥Î§¹ªº¡A
   ¤£±o»¼©µ¨ì¤U­Ó¤ë¨Ï¥Î¡C
   «¢°Õ900¤§¨C¤ë§K¶O³q¸Ü¤§200¤ÀÄÁ¤£§tºô¤º¤¬¼·¡C
   «¢°Õ900©M«Hºô¤º¤¬¼·¦³§K¶O³W©w¡A
   ºëºâ188ºô¤º¤¬¼·¦³¥b»ù³W©w¡A
   ³Ì¾A¦X±`±`¬Û¤¬Ápµ¸ªºªB¤Í­Ì¤@°_¥Ó½Ð¡C
   ºëºâ188»P«¢°Õ900¤§ªù¸¹¨Ï¥Î´Á­­³W©w¬°¦Ü¤Ö¨â¦~¡A
   »P¦b¤@¯ë³q°T¦æ¥Ó½Ð¬Û¦P¡C


¤é«áªº³q¸Ü¶O¡A±z¥i¦b©M«Hªù¥«¡B7-11¡B¶×´Ú¡B¹º¼·..µ¥µ¥Ãº¯Ç¡A
·íµM¤]¥i¥Ñ©M«H¹q°T±Ä»È¦æ±b¸¹¦Û°Ê¦©´Ú¤è¦¡¡C

¡]¨C¤ë³q¸Ü¶O¥I¶O¤è¦¡¹ï¥ô¦ó©M«H¨Ï¥ÎªÌ¬Ò¬Û¦P¡^

¥Ó½Ðªù¸¹©Ò»ÝÃÒ¥ó
1.±z»Ý·Ç³Æ¨­¥÷ÃÒ¼v¥»¡]¥¿¤Ï­±¡^
2.»È¦æ¦sºP«Ê­±¼v¥»¡]»P¨­¥÷ÃÒ¬Û¦P¦W¦r¡^
3.«K³¹¤@Áû¡]»P¨­¥÷ÃÒ¼v¥»¦W¦r¬Û¦P¡A¤£»Ý­n¦LŲÃÒ©ú¹Ï³¹¡^

¡]ªù¸¹¥Ó½Ð¤è¦¡¹ï¥ô¦ó©M«H¨Ï¥ÎªÌ¬Ò¬Û¦P¡^


¥Ó½Ð¬ù¤@¬P´Á«á¡A«K¥i¨Ï¥Î¡C

¦P¤@­Ó¦W¦r¡A³Ì¦h¥Ó½Ð3­Óªù¸¹+3­Ó¤â¾÷





¬O¯uªº½Ð¬Û«H¡I

µL±ø¥ó°e±z¤â¾÷»P©M«H¹q°Tªù¸¹¡I

¦p¿ï¾Ü§K¶O¤è®×¡A±z¤£¥²¥X¥ô¦ó¥b¤ò¿ú¡A§Y¥i¾Ö¦³¤â¾÷¡Ïªù¸¹¡I

¦p¿ï¾Ü¦Xºâ¥I¶O¤è®×¡A±z¥u­n¥I888¤¸¡A§Y¥i¾Ö¦³¤â¾÷¡Ïªù¸¹¡I



¦³·NÄ@¥Ó½ÐªÌ¡A½Ð¨Ó¥»¤½¥q¿ì²z¡I



Åwªï¨Ó¹q¸ß°Ý¡G

02-27039827

0925851019

±¶°\¥ø·~ºÞ²zÅU°Ý¦³­­¤½¥q·q¤W
²Î¤@½s¸¹¡G97225510



___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs



/tmp/ghc13435.lpp:388: Non-exhaustive patterns in function zip_ty_env

2001-10-16 Thread Thomas Hallgren

Hi,

When I compile the following module,

module ZipTyEnvBug where

type A i = i
type B = A

I get

ghc-5.02: panic! (the `impossible' happened, GHC version 5.02):
/tmp/ghc13435.lpp:388: Non-exhaustive patterns in function 
zip_ty_env

Changing the second declaration to

type B i = A i

helps, but the Haskell 98 report (section 4.2.2) explicitly allows the 
lhs of a type sysonym declaration to be of higher kind...

Regards,

Thomas Hallgren


___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs



Robustness of instance Read Char

2001-10-16 Thread Peter Thiemann

Folks,

my code has unwillingly been forced to read a large string generated
by show. This turned out to be a robustness test because the effect is
a stack overflow (with Hugs as well as with GHC) and, of course, this
error happened in a CGI script. 

If you want to try the effect yourself, just take a file foo of,
say, 150k and type this into you hungry Hugs prompt:

readFile foo = \s - putStr (read (show foo))

Digging down into the prelude code (taken from Hugs's prelude file),
you find this: 

 instance Read Char where
   readsPrec p  = readParen False
   (\r - [(c,t) | ('\'':s,t) - lex r,
   (c,\')   - readLitChar s ])
   readList = readParen False (\r - [(l,t) | ('':s, t) - lex r,
  (l,_)  - readl s ])
  where readl ('':s)  = [(,s)]
readl ('\\':'':s) = readl s
readl s= [(c:cs,u) | (c ,t) - readLitChar s,
 (cs,u) - readl t ]

which means that the parser reading this string has the ability to
fail and to backtrack *at every single character*. While this might be 
useful in the general case, it certainly causes our little one-line
program to die. 

Unfortunately, in my real program, the String is embedded in a data
type which is deriving Read, so that writing the specific instance of
read is a major pain. Two things would help me in this situation:

1. some kind-hearted maintainer of a particularly well-behaved Haskell 
   implementation might put in a more efficient definition in the
   instance Read Char (or convince me that backtracking inside of
   reading a String is a useful gadget). The following code will do:

readListChar :: String - [(String, String)]
readListChar =
  return . readListChar' . dropWhile isSpace

readListChar' ('\':rest) =
  readListChar'' rest

readListChar'' ('\':rest) =
  (,rest)
readListChar'' rest = 
  let (c, s') = head (readLitChar rest) 
  (s, s'') = readListChar'' s'
  in  (c:s, s'')

{- clearly, taking the head should be guarded and a proper error
message generated -}

2. provide a way of locally replacing the offending instance of Read
   with something else. [urgh, a language extension]

Any suggestions or comments?
-Peter

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Haskell Communities Survey - Second Call for Contributions

2001-10-16 Thread Bernard James POPE

Hi all,

I'm sending this to the whole list because maybe there are others who are
doing the same thing as me, and so it would be useful to share some
effort.

   What about a standard AST format?  What about static analysis and
   type checking/inference? 

A few of us at Melbourne have been slowly creating a front end to
Mark Jones' Typing Haskell in Haskell. It is getting close to being useable.
It is intended as a stand-alone type inference/checking tool that can give 
detailed information about static aspects of the program. It will understand 
modules.

Given Mark's approval I would like to make it available to the Haskell
community. I think seperating this element of the language from the
compilers is a useful thing to do, especially for program transformations
that need types. It uses the Hsparser library for parsing. 
As for a standard AST and interface, that would be lovely but I think it is as 
much a language issue as a library issue.

I think there was some people working on making the front end of GHC 
more independent from the rest of the compiler. I'm not sure if this is still
happening. 

Regards,
Bernie.

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Standard Prelude - Floating Class

2001-10-16 Thread Lennart Augustsson

Jerzy Karczmarczuk wrote:

 Did Joe Fasel include this consciously? If yes,
 my respect - already almost infinite, is even bigger now).

I'm pretty sure he did, but he can speak for himself.  I know he
discussed these things with his numerical collegues when designing
the prelude.
Look at this definition (from Complex, by Joe) for instance

instance  (RealFloat a) = Fractional (Complex a)  where
(x:+y) / (x':+y') =  (x*x''+y*y'') / d :+ (y*x''-x*y'') / d
  where
x'' = scaleFloat k x'
y'' = scaleFloat k y'
k   = - max (exponent x') (exponent y')
d   = x'*x'' + y'*y''

The scaleFloat calls are there for numeric reasons.

-- Lennart



___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Standard Prelude - Floating Class

2001-10-16 Thread George Russell

I wrote
 I'm afraid that I have very little faith in the numerical analysis
 expertise of the typical Haskell implementor, so I think it is dangerous
 to give them an incorrect default implementation.  I am reminded of
 the notorious ASCII C (very)-pseudo-random number generator . . .
Dylan wrote
  I don't think it's worth worrying about much.
I wrote
 This is a good argument for leaving things as they are.
Jerzy Karczmarczuk wrote
 Absolutely NO. Unless you don't care at all about the potential scientific 
 users of the language. Leaving the details which are of utmost importance for
 professional applications is killing the language. Most  readers of this forum
 are very far away from numerics, and this is normal. But languages live through
 their libraries. At least 4 times a year somebody on this list complains about
 lack of such a support even if the actual libraries are already quite
 impressive.
The potential scientific users of the language are not going to be well served
if the language includes *incorrect* implementations of mathematical functions.
This is my point.
 
 So, I would encourage to organize one day a group - not necessarily a task
 force
 like the GUI people - of people who would test all the numerics, and at least
 give to the freshmen some implementation prototypes, e.g. Padés for small
 arguments
 of sinh, etc
Yes, in the ideal world, we would form a group of numerically-knowledgable
Haskell people who would test things out properly.  Well, perhaps.  I would
like to be on this group.  I at least know what a Pad'e approximation is, and
perhaps I could even remember how you find them.  I have implemented sinh
properly in ML based on the netlib specification.  Still, I am not a numerical
analyst, and I am not sure we are going to be able to find it easy to assemble
a group of numerical analysts willing to give time to define the transcendental
functions properly.  I also doubt if this is going to be possible.  At the moment
for example, Haskell cannot even require IEEE arithmetic, because virtually no
platform supports it completely.  (Intel has too much precision which needs to
be artificially clobbered if we want IEEE, Alpha doesn't do underflows properly
unless you are very careful with inserting traps to fix things up.)  So getting
a standard which specifies exactly what Haskell transcendental functions should
do (be accurate within 0.8ULP for example, though when you think about it that
is horrendously complicated to guarantee in some instances . . .) is going to
be tricky, to say the least.
 
 And what is this: typical Haskell implementor? Do you know many of them? Do
 you
 think really that some fellow totally inconscious in the domain of STANDARD
 numeric
 maths, somebody who never heard about IEEE etc. will NOW engage in implementing
 Haskell? What is the rationale behind your little faith, Man of Little Faith?
I think numerical analysis is a prime example of A little learning is a dangerous
thing.  I think I would like a Haskell implementor to be either totally ignorant
of numerical analysis, and simply call out to C routines written by an expert,
such as the excellent ones available at netlib.  Or else a Haskell implementor should 
be a skilled numerical analyst.  Unfortunately expecting writers of functional 
compilers to be an s.n.a. seems to me rather like expecting them to be brain surgeons; 
it just isn't so.  On the other hand, they have enough mathematical learning
to know about sinh(x)=(exp(x)-exp(-x))/2, so they erroneously introduce it into their
code, having forgotten whatever they learnt in bright college days about never
subtracting two nearly-equal floating-point numbers.  Standard ML/NJ and Microsoft
Excel (when I tested it a couple of years ago) both get sinh wrong, so I think my
pessimism is well-grounded.

Incidentally, another fruitful example of ALLIADT is random number generators.  I have
yet to see a language standard which defined a random number generator which wasn't
completely pathetic.

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Haskell 98 - Standard Prelude - Floating Class

2001-10-16 Thread Marcin 'Qrczak' Kowalczyk

Tue, 16 Oct 2001 15:29:36 +1000, Fergus Henderson [EMAIL PROTECTED] pisze:

 Not giving a default definition is *not* the same as giving a default
 definition that calls error.  It's significantly safer.  The difference
 is that the former makes it much easier for compilers to issue warnings
 when you forget to define a class method in an instance declaration.

There are no warnings when default definitions are expressed in
terms of themselves such that when no explicit definition is present,
they will diverge.

In practice this is analogous to not having a definition at all.
But the compiler sees this as if they had a good definition.

If we are serious about ensuring that definitions are not omitted,
we should handle this case too. It can be done with a pragma which
tells the compiler and a programmer who wants to make instances what
are possible sets of methods to be provided by instances (in terms
of conjunctions and alternatives). This is often already specified
in comments.

An optimizing compiler could detect most of such incomplete instances
itself, with the help of strictness analysis.

-- 
 __(  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



ANNOUNCE: popenhs-0.00 released

2001-10-16 Thread Jens-Ulrik Petersen

I am happy to announce the first release of popenhs, version 0.00.

popenhs is a very small Haskell library, based on runProcess
in hslibs' posix library.  It provides lazy output from
subprocesses through two functions popen2 and popen3.

The source and rpm files are available from:

http://www.01.246.ne.jp/~juhp/haskell/popenhs/

I welcome comments and feedback.

Jens

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



ExitFailure 127

2001-10-16 Thread Sebastian Schulz

hi.

I'm trying to run an system command (wget) within a CGI script and get the following 
error:

 Exitfailure 127

How can I get more information out of an ExitFailure x error?
Can I use ioeGetErrorString? But this function doesn't work on ExitCode, which system 
returns.

TIA
sebastian


___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe