Underscores in qualified names in HsParser

2002-07-13 Thread Anders Lau Olsen


HsParser is confused by the combination of qualified names and
identifiers starting with underscores. For example:

module M where

_f _ _ = 0

x = 0 `M._f` 0 -- parse error at '.'

y = M._f 0 0 -- parses as M . (_f 0 0)

I have tested this only for GHC 5.02. For what it's worth, I am pretty
sure the later versions behave the same, and that the fix is to
replace line 336 in Lexer.hs

| isLower c -> do   -- qualified varid?

with

| isLower c || c == '_' -> do   -- qualified varid?


Anders

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



Position calculations in HsParser

2001-12-16 Thread Anders Lau Olsen


HsParser miscalculates column-positions if qualified names are used.
The problem seems to be the lexer forgetting to count the '.' in the
qualified name when deciding how much to move forward. In this
function, for instance,

f M.A M.B M.C = 0
   ^

HsParser reports that the '=' is located at the column marked by the ^.

Anders Lau Olsen


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



Repeated calls to installHandler

2001-11-19 Thread Anders Lau Olsen


If `installHandler' is called more than a few times in a row, the
run-time system terminates with an error message.

The program:

main =
sequence_ $
replicate 33 $
installHandler sigINT (Catch (return ())) Nothing

The shell output:

% ./program
program: fatal error: getStablePtr: too light

% uname -a
Linux localhost 2.2.5-15 #1 Mon Apr 19 22:21:09 EDT 1999 i586 unknown

% ghc --version
The Glorious Glasgow Haskell Compilation System, version 5.02

Anders Lau Olsen


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



Misc. bugs in HsParser

2001-11-08 Thread Anders Lau Olsen


HsParser does not allow method declarations to follow a default
implementation of a method.

class G a where
f :: a -> a
f x = x
g :: a -> a

Optional semicolons or empty statements are not permitted in
do-expressions.

f x = do ;; x ;

That is probably the reason why this example fails to parse too:

f x = do
y
where y = x

Anders Lau Olsen


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



RE: installHandler, sleep, and interrupts.

2001-10-30 Thread Anders Lau Olsen


I later ran into another problem that may or may not be related with the
first. This is the program I am running:

module Main where
import Posix

main = do
installHandler sigCONT (Catch (putStrLn "- resumed -")) Nothing
forever $ do
c <- getChar
putChar c

forever = sequence_ . repeat

This is the output from a conversation with the shell:

% ./program &
[2] 8959
[2]  + Suspended (tty input) ./program
% fg
./program
a
a
b
b
c
c
d
d
e
e- resumed -

The handler is run not shortly after the signal is received, but only
after a sufficient amount of I/O or processing has been done by the main
process.

Anders Lau Olsen


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



installHandler, sleep, and interrupts.

2001-10-29 Thread Anders Lau Olsen


When interrupting this program, the signal handler does not get called:

module Main where
import Posix

main = do
installHandler 2 (Catch (putStrLn "Hello, world!")) Nothing
sleep 600
-- putStr ""

Curiously, if the last line is uncommented, the program works as expected:

% ./program
^C
Hello, world!

This is for GHC version 5.02, run on Linux 2.2.5-15.

Anders Lau Olsen


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



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 }