[ ghc-Bugs-672813 ] bad type does bad things

2003-01-22 Thread SourceForge.net
Bugs item #672813, was opened at 2003-01-22 23:41
You can respond by visiting: 
https://sourceforge.net/tracker/?func=detail&atid=108032&aid=672813&group_id=8032

Category: None
Group: None
Status: Open
Resolution: None
Priority: 5
Submitted By: Miguel Figueiredo (olliegator)
Assigned to: Nobody/Anonymous (nobody)
Summary: bad type does bad things

Initial Comment:
If I create a type like this:

data Test a = T a
 deriving Show a

I get:

*Main> :l test.hs
Compiling Main ( teste.hs, interpreted )
ghc-5.04.2: panic! (the `impossible' happened, GHC
version 5.04.2):
nameModule a{-r1qo-}

Please report it as a compiler bug to
[EMAIL PROTECTED],
or http://sourceforge.net/projects/ghc/.


--

You can respond by visiting: 
https://sourceforge.net/tracker/?func=detail&atid=108032&aid=672813&group_id=8032
___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs



higher-order typing errors

2003-01-22 Thread Dean Herington
I don't understand why GHC (I was using 5.04.2) should reject these two
programs.



{-# OPTIONS -fglasgow-exts #-}

swap1 :: (forall a. a -> a, forall a. a -> a -> a)
  -> (forall a. a -> a -> a, forall a. a -> a)
swap1 (a, b) = (b, a)

yields:

Bug2.hs:3: parse error on input `,'



{-# OPTIONS -fglasgow-exts #-}

swap2 :: ((forall a. a -> a), (forall a. a -> a -> a))
  -> ((forall a. a -> a -> a), (forall a. a -> a))
swap2 (a, b) = (b, a)

yields:

Bug2.hs:3:
Illegal polymorphic type: forall a. a -> a
In the type: (forall a. a -> a, forall a. a -> a -> a)
 -> (forall a. a -> a -> a, forall a. a -> a)
While checking the type signature for `swap2'


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



newtype deriving panic

2003-01-22 Thread Dean Herington
Given this program:

{-# OPTIONS -fglasgow-exts #-}

module Bug1 where

import Control.Monad.State

newtype T a = T (StateT Int IO a) deriving (MonadState)


GHC 5.04.2 chokes:

ghc-5.04.2: chasing modules from: Bug1
Compiling Bug1 ( Bug1.hs, ./Bug1.o )
ghc-5.04.2: panic! (the `impossible' happened, GHC version 5.04.2):
basicTypes/VarEnv.lhs:173: Non-exhaustive patterns in case


Of course, the program is in error.  (It should derive `MonadState Int`.)


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



funny bold ouput in GHCI

2003-01-22 Thread Dean Herington
Using GHCI 5.04.2, in some interpreter output (including at least error
messages and types displayed by :t), the '>' character of a '->' lexeme
appears in bold on my terminal.  For example:

*Data> :t execProgram
FilePath
-> [String]
   -> Maybe [(String, String)]
  -> Bool -> Maybe FilePath -> [(Fd, Fdx)] -> DB ()

In the above, though it obviously doesn't show here, each '>' character
(except the first!?) shows as bold.  Note that the '-' characters of the
'->' lexemes do not show as bold.  I find all of this very peculiar,
albeit innocuous.

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



Re: Invalid binding names in generated Core code

2003-01-22 Thread Tobias Gedell
There was an error in my previous posting.



The generation of binding names doesn't seem to work correctly. I have 
generated Core for Base.lhs by standing in the 
.../ghc-5.05.20030119/libraries/base directory and giving the command:

../../ghc/compiler/ghc-inplace -H16m -O -fglasgow-exts -cpp -Iinclude 
-#include HsBase.h -funbox-strict-fields -package-name base -O 
-Rghc-timing  -split-objs -O0-c GHC/Base.lhs -o GHC/Base.o  -ohi 
GHC/Base.hi

I did of course also give the flag -fext-core, the correct command 
should be:

../../ghc/compiler/ghc-inplace -H16m -O -fglasgow-exts -cpp -Iinclude 
-#include HsBase.h -funbox-strict-fields -package-name base -O 
-Rghc-timing  -split-objs -O0 -fext-core-c GHC/Base.lhs -o 
GHC/Base.o  -ohi GHC/Base.hi




I apologize for the error


//Tobias

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


Invalid binding names in generated Core code

2003-01-22 Thread Tobias Gedell
The generation of binding names doesn't seem to work correctly. I have 
generated Core for Base.lhs by standing in the 
.../ghc-5.05.20030119/libraries/base directory and giving the command:

../../ghc/compiler/ghc-inplace -H16m -O -fglasgow-exts -cpp -Iinclude 
-#include HsBase.h -funbox-strict-fields -package-name base -O 
-Rghc-timing  -split-objs -O0-c GHC/Base.lhs -o GHC/Base.o  -ohi 
GHC/Base.hi



What is wrong in Base.hcr is that there are multiple bindings sharing 
the same name. I guess that this has something to do the the generation 
of unique binding names.


Here is an example, where tpl is bound multiple times, line 63 in Base.hcr:

  GHCziBase.zsze :: %forall a . GHCziBase.ZCTEq a ->
a -> a -> GHCziBase.Bool =
\ @ a (tpl::GHCziBase.ZCTEq a) ->
	%case tpl %of (tpl::GHCziBase.ZCTEq a)
	  {GHCziBase.ZCDEq
	   (tpl::a -> a -> GHCziBase.Bool) (tpl::a -> a -> GHCziBase.Bool) ->
	 tpl};




Sincerely,
 Tobias

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


RE: ghc 5.04.2 and seg fault

2003-01-22 Thread Simon Marlow

> I have a bug which I'm having trouble reproducing on a small scale, so
> I'm not sure how to proceed to get more information to you.
> 
> When I use ghc --make to recompile a group of files, I sometimes get a
> segfault when running the target program.  If I remove all of the .o
> files and compile again, I do not get the segfault.  If I remove just
> the changed .o files and the executable and recompile, I still get the
> segfault.  
> 
> I'm not using any unsafe IO as far as I know, though I am using Happy
> and Alex.
> 
> I searched around for a while about methods for debugging ghc, but
> didn't find much.  It doesn't look like its a gc bug since I tried
> giving a big heap size and had no effect.  Can I rebuild ghc or my
> target program in some way to get more debugging information to you?
> Unfortunately, I can't post my entire program.

Could be a problem with the recompilation checking.  We know of one such
bug: if you compile first with -O, then later without -O,
inconsistencies can arise.  

If your problem is not of this form, then it would help greatly if you
could provide us with a repeatable example (indeed, it will probably be
impossible to track down without one).  The next time it happens, just
tar up the tree and send it to us, and if you can provide a description
of which changes were made recently to the tree that would help too.

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



RE: Compile problems

2003-01-22 Thread Simon Marlow

> I'm still trying to compile ghc, but it's getting worse:
> 
> Running make results in the following error message:

Do you have GHC installed?  It looks like you either don't have GHC, or
configure didn't detect it.  Could you send the output of ./configure at
the top of the tree?

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



RE: bug report

2003-01-22 Thread Simon Marlow
> I am reporting a bug in the GHCi Haskell interpreter as requested by 
> the program itself. GHC is 5.04.2 running on SunOS 5.8.
> 
> The interpreter encountered a panic condition when trying to load a
> parser produced by Happy the parser generator.

Yes, this is a known bug in 5.04.2 (although I don't think it was
reported on the lists, so you can be forgiven for not having seen it!).
The workaround is to avoid using the 'a' and 'g' flags to Happy, or to
compile the parser using GHC before loading it into GHCi.

The bug was fixed in the HEAD, but was deemed to difficult to fix in the
5.04.x branch too.

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



ghc 5.04.2 and seg fault

2003-01-22 Thread Isaac Jones
Greetings,

I have a bug which I'm having trouble reproducing on a small scale, so
I'm not sure how to proceed to get more information to you.

When I use ghc --make to recompile a group of files, I sometimes get a
segfault when running the target program.  If I remove all of the .o
files and compile again, I do not get the segfault.  If I remove just
the changed .o files and the executable and recompile, I still get the
segfault.  

I'm not using any unsafe IO as far as I know, though I am using Happy
and Alex.

I searched around for a while about methods for debugging ghc, but
didn't find much.  It doesn't look like its a gc bug since I tried
giving a big heap size and had no effect.  Can I rebuild ghc or my
target program in some way to get more debugging information to you?
Unfortunately, I can't post my entire program.


peace,

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



Compile problems

2003-01-22 Thread sonja groening

Hi!

I'm still trying to compile ghc, but it's getting worse:

Running make results in the following error message:

[snip]


===fptools== Recursively making `boot' in hasktags ghc-pkg hp2ps hsc2hs parallel 
stat2resid prof unlit genprimopcode ...
PWD = /mnt/laborpcs/home/sonja/ghc-5.04.2/ghc/utils


==fptools== make boot - --no-print-directory -r;
 in /mnt/laborpcs/home/sonja/ghc-5.04.2/ghc/utils/hasktags

M -optdep-f -optdep.depend  -osuf o-ldl -O HaskTags.hs
make[3]: M: Command not found
make[3]: [depend] Error 127 (ignored)

==fptools== make boot - --no-print-directory -r;
 in /mnt/laborpcs/home/sonja/ghc-5.04.2/ghc/utils/ghc-pkg

M -optdep-f -optdep.depend  -osuf o-ldl -cpp -DPKG_TOOL -DWANT_PRETTY -package 
lang -package util -package text -O Main.hs Package.hs ParsePkgConfLite.hs
make[3]: M: Command not found
make[3]: [depend] Error 127 (ignored)
make all
ldl -cpp -DPKG_TOOL -DWANT_PRETTY -package lang -package util -package text -O-c 
Main.hs -o Main.o
make[4]: ldl: Command not found
make[4]: [Main.o] Error 127 (ignored)
ldl -cpp -DPKG_TOOL -DWANT_PRETTY -package lang -package util -package text -O-c 
Package.hs -o Package.o
make[4]: ldl: Command not found
make[4]: [Package.o] Error 127 (ignored)
ldl -cpp -DPKG_TOOL -DWANT_PRETTY -package lang -package util -package text -O-c 
ParsePkgConfLite.hs -o ParsePkgConfLite.o
make[4]: ldl: Command not found
make[4]: [ParsePkgConfLite.o] Error 127 (ignored)
o ghc-pkg.bin -ldl -cpp -DPKG_TOOL -DWANT_PRETTY -package lang -package util -package 
text -O   Main.o Package.o ParsePkgConfLite.o
make[4]: o: Command not found
make[4]: [ghc-pkg.bin] Error 127 (ignored)
make INSTALLING=0 BIN_DIST=0 - --no-print-directory -r all
ldl -cpp -DPKG_TOOL -DWANT_PRETTY -package lang -package util -package text -O-c 
Main.hs -o Main.o
make[5]: ldl: Command not found
make[5]: [Main.o] Error 127 (ignored)
ldl -cpp -DPKG_TOOL -DWANT_PRETTY -package lang -package util -package text -O-c 
Package.hs -o Package.o
make[5]: ldl: Command not found
make[5]: [Package.o] Error 127 (ignored)
ldl -cpp -DPKG_TOOL -DWANT_PRETTY -package lang -package util -package text -O-c 
ParsePkgConfLite.hs -o ParsePkgConfLite.o
make[5]: ldl: Command not found
make[5]: [ParsePkgConfLite.o] Error 127 (ignored)
o ghc-pkg.bin -ldl -cpp -DPKG_TOOL -DWANT_PRETTY -package lang -package util -package 
text -O   Main.o Package.o ParsePkgConfLite.o
make[5]: o: Command not found
make[5]: [ghc-pkg.bin] Error 127 (ignored)

==fptools== make boot - --no-print-directory -r;
 in /mnt/laborpcs/home/sonja/ghc-5.04.2/ghc/utils/hp2ps

../../../glafp-utils/mkdependC/mkdependC -f .depend -- -O -I../../includes -Wall   
 -- AreaBelow.c AuxFile.c Axes.
 Curves.c Deviation.c Dimensions.c Error.c HpFile.c Key.c Main.c Marks.c PsFile.c 
Reorder.c Scale.c Shade.c TopTwenty.
 TraceElement.c Utilities.c 

==fptools== make boot - --no-print-directory -r;
 in /mnt/laborpcs/home/sonja/ghc-5.04.2/ghc/utils/hsc2hs

M -optdep-f -optdep.depend  -osuf o-ldl -package util -cpp -O Config.hs Main.hs
make[3]: M: Command not found
make[3]: [depend] Error 127 (ignored)

[snip]


==fptools== make boot - --no-print-directory -r;
 in /mnt/laborpcs/home/sonja/ghc-5.04.2/ghc/utils/genprimopcode

ldl -syslib text -O-c Main.hs -o Main.o
make[3]: ldl: Command not found
make[3]: [Main.o] Error 127 (ignored)
o genprimopcode -ldl -syslib text -O   Main.o
make[3]: o: Command not found
make[3]: [genprimopcode] Error 127 (ignored)
M -optdep-f -optdep.depend  -osuf o-ldl -syslib text -O Main.hs
make[3]: M: Command not found
make[3]: [depend] Error 127 (ignored)

[leads to:]


==fptools== make boot -wr;
 in /mnt/laborpcs/home/sonja/ghc-5.04.2/ghc/compiler

/bin/sh: test: too many arguments
/bin/sh: test: -lt: unary operator expected
/bin/sh: test: too many arguments
Creating main/Config.hs ... done.
rm -f prelude/primops.txt
gcc -E  -I../includes -traditional-x c prelude/primops.txt.pp | /bin/sed -e 
'/^#/d' > 

bug report

2003-01-22 Thread Juhana Helovuo
Hello.

I am reporting a bug in the GHCi Haskell interpreter as requested by 
the program itself. GHC is 5.04.2 running on SunOS 5.8.

The interpreter encountered a panic condition when trying to load a
parser produced by Happy the parser generator.

The commands I am using are as follows:

--
% happy -gac -i Parser.y 
shift/reduce conflicts:  6
% ghci Parser.hs 
   ___ ___ _
  / _ \ /\  /\/ __(_)
 / /_\// /_/ / /  | |  GHC Interactive, version 5.04.2, for Haskell 98.
/ /_\\/ __  / /___| |  http://www.haskell.org/ghc/
\/\/ /_/\/|_|  Type :? for help.

Loading package base ... linking ... done.
Loading package haskell98 ... linking ... done.
Compiling MonadLexer   ( MonadLexer.hs, interpreted )
Compiling Parser   ( Parser.hs, interpreted )
WARNING: ignoring polymorphic case in interpreted mode.
   Possibly due to strict polymorphic/functional constructor args.
   Your program may leak space unexpectedly.

ghc-5.04.2: panic! (the `impossible' happened, GHC version 5.04.2):
ByteCodeGen.pushAtom.pushStr

Please report it as a compiler bug to [EMAIL PROTECTED],
or http://sourceforge.net/projects/ghc/.


> 
--

When I try to produce the parser without GHC extensions, I get the 
following result:

--
% happy  -i Parser.y  
shift/reduce conflicts:  6
% ghci Parser.hs 
   ___ ___ _
  / _ \ /\  /\/ __(_)
 / /_\// /_/ / /  | |  GHC Interactive, version 5.04.2, for Haskell 98.
/ /_\\/ __  / /___| |  http://www.haskell.org/ghc/
\/\/ /_/\/|_|  Type :? for help.

Loading package base ... linking ... done.
Loading package haskell98 ... linking ... done.
Compiling MonadLexer   ( MonadLexer.hs, interpreted )
Compiling Parser   ( Parser.hs, interpreted )
WARNING: ignoring polymorphic case in interpreted mode.
   Possibly due to strict polymorphic/functional constructor args.
   Your program may leak space unexpectedly.


During interactive linking, GHCi couldn't find the following symbol:
  DataziTuple_Z92T_con_info or DataziTuple_Z92T_static_info
This may be due to you not asking GHCi to load extra object files,
archives or DLLs needed by your current session.  Restart GHCi, specifying
the missing library using the -L/path/to/object/dir and -lmissinglibname
flags, or simply by naming the relevant files on the GHCi command line.
Alternatively, this link failure might indicate a bug in GHCi.
If you suspect the latter, please send a bug report to:
  [EMAIL PROTECTED]
--

The Hugs interpreter seems to run the parser fine. Also, 
non-interactive compilation, i.e. "ghc -c Parser.hs" runs without 
complaints.


Juhana Helovuo
Tampere University of Technology


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