Re: Compiler bug

2007-02-28 Thread Ian Lynagh

Hi Paul,

On Sun, Jan 28, 2007 at 12:49:44PM +0300, Paul wrote:
 
 Chasing modules from: hask1.hs
 Compiling Main ( hask1.hs, hask1.o )
 ghc-6.4: panic! (the `impossible' happened, GHC version 6.4):
 ds_app_type Main.Tree{tc r16z} [a{tv a1a9}]
 
 Please report it as a compiler bug to glasgow-haskell-bugs@haskell.org,
 or http://sourceforge.net/projects/ghc/.

Thanks for the report. I think the problem is fixed in newer versions of
GHC (I've tried 6.4.2 and 6.6), which give the error

hask1.hs:24:1:
Class `Tree' used as a type
In the class declaration for `Tree'

when using data Node ... and

Multiple declarations of `Main.Tree'
Declared at: hask1.hs:12:5
 hask1.hs:14:6

when using data Tree 


Thanks
Ian

___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Compiler bug

2007-02-17 Thread Paul
Hi,

After attempting to build Haksell programm (through KDevelop),
i have got such a message:




Chasing modules from: hask1.hs
Compiling Main ( hask1.hs, hask1.o )
ghc-6.4: panic! (the `impossible' happened, GHC version 6.4):
ds_app_type Main.Tree{tc r16z} [a{tv a1a9}]

Please report it as a compiler bug to glasgow-haskell-bugs@haskell.org,
or http://sourceforge.net/projects/ghc/.




File hask.hs (with little comment) is attached.

Please wright back if you have accepted this signal or 
if you are not interested in such a feedback.

Best regards, Paul.



module Main
where

import IO
import Random
import Monad

data TypeOfLexem = Variable | Number | Plus | Minus

data Lexem = Lexem {t::TypeOfLexem, branches::Int}

data Node a = Nil | Node a [Tree a]
{-
	This line caused compiler panic.
	Previously it was was:

data Tree a = Nil | Node a [Tree a]

-}

class Tree a where


 (-) :: Tree a - Tree a - Tree a

 (-) a1 a2 = Node Lexem{t=Minus,branches=2} (a1:a2:[])





{-

	All the rest doesn,t make sense (i suppose)

-}
main = do
 hSetBuffering stdin LineBuffering
 num - randomRIO (1::Int, 100)
 putStrLn I'm thinking of a number between 1 and 100
 doGuessing num


doGuessing num = do
 putStrLn Enter your guess:
 guess - getLine
 let guessNum = read guess
 if guessNum  num
   then do putStrLn Too low!
   doGuessing num
   else if read guess  num
  then do putStrLn Too high!
  doGuessing num
  else do putStrLn You Win!___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


compiler bug

2007-02-17 Thread D.A.Turner
Dear GHC people,

I downloaded and installed the debian package fpr GHC-6 (on an AMD64 platform) 
and
got the following error from ghci (below).  Is this because you don't support 
64bit
platforms?  Thanks for any info.

David Turner

mandarin:~$ ghci
   ___ ___ _
  / _ \ /\  /\/ __(_)
 / /_\// /_/ / /  | |  GHC Interactive, version 6.2.2, for Haskell 
98.
/ /_\\/ __  / /___| |  http://www.haskell.org/ghc/
\/\/ /_/\/|_|  Type :? for help.

Loading package base ... /usr/lib/ghc-6.2.2/HSbase.o: unknown 
architecture
ghc-6.2.2: panic! (the `impossible' happened, GHC version 6.2.2):
loadObj: failed

Please report it as a compiler bug to glasgow-haskell-bugs@haskell.org,
or http://sourceforge.net/projects/ghc/.

___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: compiler bug

2007-02-17 Thread Kirsten Chevalier

On 1/24/07, D.A.Turner [EMAIL PROTECTED] wrote:


Dear GHC people,

I downloaded and installed the debian package fpr GHC-6 (on an AMD64
platform) and
got the following error from ghci (below).  Is this because you don't
support 64bit
platforms?  Thanks for any info.




GHC 6.2.2 is a very old version. Is there any reason why you can't download
and install GHC 6.6? There should be a debian package for 6.6.

Cheers,
Kirsten

--
Kirsten Chevalier* [EMAIL PROTECTED] *Often in error, never in
doubt
Ana Ng and I are getting old and we still haven't walked in the glow of
each
other's majestic presence / Listen Ana hear my words, they're the ones you
would think I would say if there was a me for you -- TMBG
___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


[GHC] #871: compiler bug concerning arrays

2006-08-21 Thread GHC
#871: compiler bug concerning arrays
-+--
Reporter:  guest |Owner: 
Type:  bug   |   Status:  new
Priority:  normal|Milestone: 
   Component:  Compiler  |  Version:  6.4.2  
Severity:  normal| Keywords: 
  Os:  Linux |   Difficulty:  Unknown
Architecture:  x86   |  
-+--
It seems that ghc always gives up when an array is built using  listArray
 while the size of the given range is larger than the length of the list
 and the range and the list are big enough.

 The following is an example; it was created under SuSE 9.3:


 {{{
 [EMAIL PROTECTED]:~/kodu/mat/inf/p/d/f/fpm/materjal/Tyybid ghci -v
___ ___ _
   / _ \ /\  /\/ __(_)
  / /_\// /_/ / /  | |  GHC Interactive, version 6.4.2, for Haskell 98.
 / /_\\/ __  / /___| |  http://www.haskell.org/ghc/
 \/\/ /_/\/|_|  Type :? for help.

 Using package config file: /usr/lib/ghc-6.4.2/package.conf
 Hsc static flags: -static
 *** Parser:
 *** Desugar:
 *** Simplify:
 *** CorePrep:
 *** ByteCodeGen:
 Loading package base-1.0 ... linking ... done.
 *** Parser:
 *** Desugar:
 *** Simplify:
 *** CorePrep:
 *** ByteCodeGen:
 Prelude :m Array
 Prelude Array listArray (0 , maxBound :: Int) (replicate (2 ^ 22) 0)
 *** Parser:
 *** Desugar:
 *** Simplify:
 *** CorePrep:
 *** ByteCodeGen:
 array interactive: internal error: evacuate: strange closure type 16540
 Please report this as a compiler bug.  See:
 http://www.haskell.org/ghc/reportabug
 }}}

 In the same case, Hugs gives a message array index out of range.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/871
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #342: GHC: panic! (compiler bug?)

2006-01-04 Thread GHC
#342: GHC: panic! (compiler bug?)
---+
  Reporter:  nobody|  Owner:  nobody
  Type:  bug   | Status:  closed
  Priority:  normal|  Milestone:
 Component:  Compiler  |Version:  6.4.1 
  Severity:  major | Resolution:  worksforme
  Keywords:| Os:  Unknown   
Difficulty:  Unknown   |   Architecture:  Unknown   
---+
Changes (by simonmar):

  * architecture:  = Unknown
  * resolution:  None = worksforme
  * difficulty:  = Unknown
  * status:  assigned = closed
  * os:  = Unknown

Comment:

 We haven't managed to find a reproducible test case for this one, so
 closing it for now.  Will re-open if it reappears.

-- 
Ticket URL: http://cvs.haskell.org/trac/ghc/ticket/342
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


compiler bug in ghc-6.4 (building a class declaration with TH)

2005-09-09 Thread Benjamin Franksen
This is command and output:

 ghc -fth -ddump-splices --make TestBuffers.hs
Chasing modules from: TestBuffers.hs
Compiling Buffers  ( ./Buffers.hs, ./Buffers.o )
Compiling Main ( TestBuffers.hs, TestBuffers.o )
Loading package base-1.0 ... linking ... done.
Loading package haskell98-1.0 ... linking ... done.
Loading package template-haskell-1.0 ... linking ... done.
TestBuffers.hs:1:0:
TestBuffers.hs:1:0: Splicing declarations
mkBufferClasses 12
  ==
class HasZero f where { zero :: a; emptyBag }
class HasOne f where {ghc-6.4: panic! (the `impossible' 
happened, GHC version 6.4):
hsSyn/Convert.lhs:(339,8)-(350,91): Non-exhaustive patterns in 
function trans


Please report it as a compiler bug to glasgow-haskell-bugs@haskell.org,
or http://sourceforge.net/projects/ghc/.

I attached the two (short) source files.

Ben
module Buffers where

import Language.Haskell.TH
import Control.Monad (when)
import Data.Char (toUpper)

numNames = [zero,one,two,three,four,five,
six,seven,eight,nine,ten,eleven,twelve]
++ map show [13..]

numNames' = [toUpper x : xs | (x:xs) - front] ++ back
  where (front,back) = splitAt 13 numNames

mkBufferType :: String - [Int] - Q [Dec]
mkBufferType name quantities = do
  let tc_name = mkName name
  let tv_name = mkName a
  let tvars = [tv_name]
  let dcs = [NormalC (mkName (name++(numNames'!!i))) (replicate i (NotStrict, 
VarT tv_name)) | i - quantities]
  let derivs = []
  return [DataD [] tc_name tvars dcs derivs]

mkBufferClasses :: Int - Q [Dec]
mkBufferClasses max = do
let class_name i = mkName (Has++(numNames'!!i))
let ctx = []
let tv_name_coll = mkName f
let tv_name_elem = mkName a
let tvars = [tv_name_coll]
let fundeps = []
let meth_name i = mkName (numNames !! i)
let meth_type i = type_nx_to_y i (VarT tv_name_elem) (VarT tv_name_coll)
let meth_decls i = [SigD (meth_name i) (meth_type i)]
return [ClassD ctx (class_name i) tvars fundeps (meth_decls i) | i - 
[0..max]]
  where
type_nx_to_y n xt yt
  | n == 0= xt
  | n  0 = AppT ArrowT (AppT xt (type_nx_to_y (n-1) xt yt))
  | otherwise = error Buffers.type_nx_to_y: n  0

-- class HasOne c where
--   one :: e - c e
import Buffers

$(mkBufferClasses 12)

$(mkBufferType BufferZeroToTen [0..10])
$(mkBufferType BufferThreeToFive [3..5])
$(mkBufferType BufferTwoSixFour [2,6,4])
___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


[ ghc-Bugs-1177320 ] GHC: panic! (compiler bug?)

2005-07-06 Thread SourceForge.net
Bugs item #1177320, was opened at 2005-04-05 19:47
Message generated for change (Comment added) made by simonpj
You can respond by visiting: 
https://sourceforge.net/tracker/?func=detailatid=108032aid=1177320group_id=8032

Please note that this message will contain a full copy of the comment thread,
including the initial issue submission, for this request,
not just the latest update.
Category: None
Group: None
Status: Open
Resolution: None
Priority: 5
Submitted By: Nobody/Anonymous (nobody)
Assigned to: Nobody/Anonymous (nobody)
Summary: GHC: panic! (compiler bug?)

Initial Comment:
I just tried to compile the most recent version of Pugs
( www.pugscode.org ), and I got this:


Compiling Prim ( src/Prim.hs, src/Prim.o )
ghc.EXE: panic! (the `impossible' happened, GHC version
6.4):
Maybe.fromJust: Nothing

Please report it as a compiler bug to
glasgow-haskell-bugs@haskell.org,
or http://sourceforge.net/projects/ghc/.


Well, here I am, reporting this bug. 

The link to the Prim.hs file:
http://svn.openfoundry.org/pugs/src/Prim.hs

I didn't write the code, so can't really tell what's
going on here, the only thing I know is that it did
compile with yesterday's revision (don't know the exact
number; the current svn-revision as I'm writing this is
1572).

I'm running GHC 6.4 on WinXP SP2

Regards,
Martin
[EMAIL PROTECTED]

--

Comment By: Simon Peyton Jones (simonpj)
Date: 2005-07-06 10:00

Message:
Logged In: YES 
user_id=50165

We've never managed to reproduce this.  Can anyone else? 

Martin, can you reproduce it?  



--

You can respond by visiting: 
https://sourceforge.net/tracker/?func=detailatid=108032aid=1177320group_id=8032
___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


compiler bug

2005-06-16 Thread Johan van der Teems
Here output of ghci on ubuntu Hoary

543 $ ghci
   ___ ___ _
  / _ \ /\  /\/ __(_)
 / /_\// /_/ / /  | |  GHC Interactive, version 6.2.2, for Haskell
98.
/ /_\\/ __  / /___| |  http://www.haskell.org/ghc/
\/\/ /_/\/|_|  Type :? for help.

Loading package base ... /usr/lib/ghc-6.2.2/HSbase.o: unknown
architecture
ghc-6.2.2: panic! (the `impossible' happened, GHC version 6.2.2):
loadObj: failed

Please report it as a compiler bug to glasgow-haskell-bugs@haskell.org,
or http://sourceforge.net/projects/ghc/.


uname -a gives:
Linux ollie 2.6.10-5-amd64-k8 #1 Tue Jun 7 08:26:38 UTC 2005 x86_64
GNU/Linux



-- 
Johan van der Teems
St Annaparochie
___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


RE: compiler bug

2005-06-16 Thread Simon Marlow
On 15 June 2005 18:46, Johan van der Teems wrote:

 Here output of ghci on ubuntu Hoary
 
 543 $ ghci
___ ___ _
   / _ \ /\  /\/ __(_)
  / /_\// /_/ / /  | |  GHC Interactive, version 6.2.2, for Haskell
 98.
 / /_\\/ __  / /___| |  http://www.haskell.org/ghc/
 \/\/ /_/\/|_|  Type :? for help.
 
 Loading package base ... /usr/lib/ghc-6.2.2/HSbase.o: unknown
 architecture
 ghc-6.2.2: panic! (the `impossible' happened, GHC version 6.2.2):
 loadObj: failed
 
 Please report it as a compiler bug to
 glasgow-haskell-bugs@haskell.org, or
 http://sourceforge.net/projects/ghc/. 

GHCi does not currently work on amd64.  Sorry about the uninformative
error message (later versions of GHC are/will be better in this regard).

Cheers,
Simon
___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


RE: compiler bug

2005-06-07 Thread Simon Marlow



The 
error message indicates that GHCi is trying to load an object file that it 
doesn't recognise. Could you upgrade your version of GHC to 6.4 and 
try again, and if that fails can you send us a complete reproduction case so 
that we can investigate the problem here.

Cheers,
 Simon


From: [EMAIL PROTECTED] 
[mailto:[EMAIL PROTECTED] On Behalf Of Kevin 
AlamSent: 03 June 2005 13:26To: 
glasgow-haskell-bugs@haskell.orgSubject: compiler 
bug


To Whom It May Concern,

while working with GHCi on xemacs, I tried running the program 
but come up with this error

"*Main maingNot x86 PEi386hc.exe: panic! (the 
`impossible' happened, GHC version 6.2.2):loadObj: failed

Please report it as a compiler bug to glasgow-haskell-bugs@haskell.org,or 
http://sourceforge.net/projects/ghc/."

thats the message I get. 

Thanks.

Kevin


P.S. what can I do to be able to run the program in 
GHCi?
___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


compiler bug

2005-06-05 Thread Kevin Alam
To Whom It May Concern,

while working with GHCi on xemacs, I tried running the program but come up with this error

"*Main maingNot x86 PEi386hc.exe: panic! (the `impossible' happened, GHC version 6.2.2):loadObj: failed

Please report it as a compiler bug to glasgow-haskell-bugs@haskell.org,or http://sourceforge.net/projects/ghc/."

thats the message I get. 

Thanks.

Kevin


P.S. what can I do to be able to run the program in GHCi?

___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


compiler bug (in version 6.4)

2005-04-25 Thread Henning Günther
Hi,

I've tried to run the command ghc -c ikosaeder.hs and got the
following:

ghc-6.4: panic! (the `impossible' happened, GHC version 6.4):
ds_app_type Main.Neighbor{tc r15r} []

Please report it as a compiler bug to glasgow-haskell-bugs@haskell.org,
or http://sourceforge.net/projects/ghc/.

So here is my bugreport. My GHC Version is 6.4. My system is Gentoo
Linux running on an x86. Hope that helps.
-- 
Henning Günther
Am Heidbergstift 15c
28717 Bremen

öffentlicher Schlüssel(PGP):
http://eq.homelinux.org/~eq/henning_guenther.key
class Neighbor a where
	neighborLeft :: a - Neighbor
	neighborRight :: a - Neighbor
	neighborBottom :: a - Neighbor

data LeftArea
	= LArea1
	| LArea2
	| LArea3
	| LArea4

data RightArea
	= RightArea LeftArea

data LeftAreaComplement
	= LCArea1
	| LCArea2
	| LCArea3

rightArea :: LeftArea - RightArea
rightArea lft = RightArea lft

leftAreaComplement :: LeftArea - LeftAreaComplement - LeftArea
leftAreaComplement LArea1 LCArea1 = LArea2
leftAreaComplement LArea1 LCArea2 = LArea3
leftAreaComplement LArea1 LCArea3 = LArea4

leftAreaComplement LArea2 LCArea1 = LArea1
leftAreaComplement LArea2 LCArea2 = LArea3
leftAreaComplement LArea2 LCArea3 = LArea4

leftAreaComplement LArea3 LCArea1 = LArea1
leftAreaComplement LArea3 LCArea2 = LArea2
leftAreaComplement LArea3 LCArea3 = LArea4

leftAreaComplement LArea4 LCArea1 = LArea1
leftAreaComplement LArea4 LCArea2 = LArea2
leftAreaComplement LArea4 LCArea3 = LArea3 

data Sub1Area
	= Sub1Area LeftArea LeftAreaComplement

instance Neighbor Sub1Area where
	neighborLeft a = a

instance Neighbor LeftArea where
	neighborLeft LArea1 = Sub1Area LArea1 LCArea3
	neighborLeft LArea2 = Sub1Area LArea2 LCArea2
	neighborLeft LArea3 = Sub1Area LArea3 LCArea2
	neighborLeft LArea4 = Sub1Area LArea4 LCArea1


signature.asc
Description: This is a digitally signed message part
___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


RE: compiler bug (in version 6.4)

2005-04-25 Thread Simon Marlow
On 23 April 2005 16:44, Henning Günther wrote:

 I've tried to run the command ghc -c ikosaeder.hs and got the
 following:
 
 ghc-6.4: panic! (the `impossible' happened, GHC version 6.4):
 ds_app_type Main.Neighbor{tc r15r} []
 
 Please report it as a compiler bug to
 glasgow-haskell-bugs@haskell.org, or
 http://sourceforge.net/projects/ghc/. 
 
 So here is my bugreport. My GHC Version is 6.4. My system is Gentoo
 Linux running on an x86. Hope that helps.

This is a known bug, caused by trying to use a class name as a type name.  The 
fix will be in 6.4.1.

Cheers,
Simon
___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


[ ghc-Bugs-1177320 ] GHC: panic! (compiler bug?)

2005-04-05 Thread SourceForge.net
Bugs item #1177320, was opened at 2005-04-05 12:47
Message generated for change (Tracker Item Submitted) made by Item Submitter
You can respond by visiting: 
https://sourceforge.net/tracker/?func=detailatid=108032aid=1177320group_id=8032

Category: None
Group: None
Status: Open
Resolution: None
Priority: 5
Submitted By: Nobody/Anonymous (nobody)
Assigned to: Nobody/Anonymous (nobody)
Summary: GHC: panic! (compiler bug?)

Initial Comment:
I just tried to compile the most recent version of Pugs
( www.pugscode.org ), and I got this:


Compiling Prim ( src/Prim.hs, src/Prim.o )
ghc.EXE: panic! (the `impossible' happened, GHC version
6.4):
Maybe.fromJust: Nothing

Please report it as a compiler bug to
glasgow-haskell-bugs@haskell.org,
or http://sourceforge.net/projects/ghc/.


Well, here I am, reporting this bug. 

The link to the Prim.hs file:
http://svn.openfoundry.org/pugs/src/Prim.hs

I didn't write the code, so can't really tell what's
going on here, the only thing I know is that it did
compile with yesterday's revision (don't know the exact
number; the current svn-revision as I'm writing this is
1572).

I'm running GHC 6.4 on WinXP SP2

Regards,
Martin
[EMAIL PROTECTED]

--

You can respond by visiting: 
https://sourceforge.net/tracker/?func=detailatid=108032aid=1177320group_id=8032
___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


RE: Possible compiler bug

2003-09-22 Thread Simon Marlow
 
 I was playing around with GHC and my compiled
 dll-library of wxHaskell(see sourceForge for details).
 
 The compilation was done with the last versions of
 msys and MinGW.
 
 In the GHC usersguide, I saw that it was possible to
 link libraries with GHCi. So I thought, ok lets try
 that. 
 
 The result can be seen below.
 
 Greets Ron
 
 C:\ghc\ghc-6.0.1\binghci -l
 C:\msys\1.0\local\lib\wxc.dll
___ ___ _
   / _ \ /\  /\/ __(_)
  / /_\// /_/ / /  | |  GHC Interactive, version
 6.0.1, for Haskell 98.
 / /_\\/ __  / /___| |  http://www.haskell.org/ghc/
 \/\/ /_/\/|_|  Type :? for help.
 
 Loading package base ... linking ... done.
 Loading object (static) C:/msys/1.0/local/lib/wxc.dll
 ... Not x86 PEi386
 C:\GHC\GHC-60~1.1\BIN\GHC.EXE: panic! (the
 `impossible' happened, GHC version 6
 0.1):
 loadObj: failed

To do this you need to use slightly different command-line flags,
something like this:

   ghci -LC;\msys\1.0\local\lib -lwxc

GHCi should really allow DLLs and SOs to be named explicitly on the
command line without having to use the -L/-l combination.  I'll look
into fixing it.

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


Re: compiler bug? sunos 5.8, ghci-6.0.1 -package unix

2003-09-15 Thread Volker Stolz
In local.glasgow-haskell-bugs, you wrote:
 and the some for the precompiled version, 
 i getting the following error. 

 Loading package unix ... linking ... /home/xxx/local/lib/HSunix.o: unknown symbol 
 `sendfile'

Hrmph. Sorry for the hassle. Please try adding sendfile to the list
of extra_libraries in the file unix.conf in your installed ghc-tree.
-- 
http://www-i2.informatik.rwth-aachen.de/stolz/ *** PGP *** S/MIME
rage against the finite state machine 
___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Compiler bug

2003-06-09 Thread Terje Slettebø
Hi.

I'm just starting out learning Haskell, and I tried the following at the
command line (rather than in a source file):

Prelude let f 0 = 1

and got the following error:

C:\ghc\ghc-6.0\bin\ghc.exe: panic! (the `impossible' happened, GHC version
6.0):

getLinkDeps No iface for [pkg]GHCziErr

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


Regards,

Terje

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


ghc-6.0 compiler bug

2003-06-06 Thread Ch. A. Herrmann
Hi,

playing around with partial evaluation, 
I encountered the following bug:

65 ghc --make -fglasgow-exts -package haskell-src Main.hs -o Main -ddump-splices
Chasing modules from: Main.hs
Compiling Power( Power.hs, ./Power.o )
Compiling Main ( Main.hs, ./Main.o )
ghc-6.0: panic! (the `impossible' happened, GHC version 6.0):
nameModule x {- v a1BE -}

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

 import Language.Haskell.THSyntax

 pow :: ExpQ - Int - ExpQ
 pow x 0   = [| const 1 |]
 pow x n | n0 = [| $x * $(pow x (n-1)) |]
--
module Main where

 import Power (pow)

 main = let x = 2 :: Double
in putStrLn (show ($(pow [|x|] 5)))
--
Good luck
-- 
 Dr. Christoph Herrmann
 Teaching and Research Assistant 
 University of Passau, Germany 
 http://www.fmi.uni-passau.de/~herrmann
___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


RE: ghc-6.0 compiler bug

2003-06-06 Thread Simon Peyton-Jones
Yes, this is a known bug, but thank you for reporting it anyway.  I'm
going to fix it as part of my next sweep though.

I enclose a message that gives a workaround.

Simon

| -Original Message-
| From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] On
| Behalf Of Ch. A. Herrmann
| Sent: 05 June 2003 14:28
| To: [EMAIL PROTECTED]
| Subject: ghc-6.0 compiler bug
| 
| Hi,
| 
| playing around with partial evaluation,
| I encountered the following bug:
| 
| 65 ghc --make -fglasgow-exts -package haskell-src Main.hs -o Main
-ddump-splices
| Chasing modules from: Main.hs
| Compiling Power( Power.hs, ./Power.o )
| Compiling Main ( Main.hs, ./Main.o )
| ghc-6.0: panic! (the `impossible' happened, GHC version 6.0):
|   nameModule x {- v a1BE -}
| 
| Please report it as a compiler bug to
[EMAIL PROTECTED],
| or http://sourceforge.net/projects/ghc/.
|

--
| module Power where
| 
|  import Language.Haskell.THSyntax
| 
|  pow :: ExpQ - Int - ExpQ
|  pow x 0   = [| const 1 |]
|  pow x n | n0 = [| $x * $(pow x (n-1)) |]
|

--
| module Main where
| 
|  import Power (pow)
| 
|  main = let x = 2 :: Double
| in putStrLn (show ($(pow [|x|] 5)))
|

--
| Good luck
| --
|  Dr. Christoph Herrmann
|  Teaching and Research Assistant
|  University of Passau, Germany
|  http://www.fmi.uni-passau.de/~herrmann
| ___
| Glasgow-haskell-bugs mailing list
| [EMAIL PROTECTED]
| http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


---BeginMessage---
Thomas

Absolutely right!  There is a total omission in the TH implementation
for the free 'x' in 
\x - $(power 2 [| x |])

You can get round this in a clunky way by wrapping the whole thing in
$[| |], thus

$([| \x - $(power 2 [| x |]) |])

This works, but it's not pretty.  The Right Thing is to fix it, which I
hope to do.

thanks for pointing this out.  TH is pretty subtle

Simon

|  -Original Message-
|  From: Thomas Harke [mailto:[EMAIL PROTECTED]
|  Sent: 10 March 2003 18:15
|  To: [EMAIL PROTECTED]
|  
|  Hi,
|  
|  while experimenting with template haskell I encountered the
following:
|  
|  ] ghc --make Main.hs
|  ] Chasing modules from: Main.hs
|  ] Skipping  Power( Power.hs, ./Power.o )
|  ] Compiling Main ( Main.hs, ./Main.o )
|  ] ghc-5.05: panic! (the `impossible' happened, GHC version 5.05):
|  ] nameModule x {- v a1fV -}
|  ]
|  ] Please report it as a compiler bug to
[EMAIL PROTECTED],
|  ] or http://sourceforge.net/projects/ghc/.
|  ]
|  ]
|  ] make: *** [main] Error 1
|  
|  This was using a version very recently checked out of CVS (Friday, 14
March)
|  
|  The files that caused the problem are attached.
|  
|  --
|  Tom Harke
|  Computer Science and Engineering Department
|  Oregon Graduate Institute
|  
|  Weiler's Law:
|Nothing is impossible for the man who doesn't have to do it himself

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

---End Message---


RE: ghc-6.0 compiler bug

2003-06-06 Thread Ch. A. Herrmann
Hi Simon

Simon Yes, this is a known bug,

Sorry that I'm not perfectly aware of everything going
on with Template Haskell.

Simon but thank you for reporting it
Simon anyway.  I'm going to fix it as part of my next sweep though.

Thank you very much. I'm happy to know that it is really possible
to apply the generated code to run-time values; taking the 
idea of the workaround:

 main = $([| do
  s - getLine
  let x = read s :: Double   
  putStrLn (show ($(pow [|x|] 5))) |])
-- 
 Dr. Christoph Herrmann
 Teaching and Research Assistant 
 University of Passau, Germany 
 http://www.fmi.uni-passau.de/~herrmann
___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


RE: compiler bug in ghc

2001-11-15 Thread Simon Peyton-Jones

Thanks.  This one is fixed in 5.02.1.  (which is available now)

Simon

| -Original Message-
| From: Thorsten Seitz [mailto:[EMAIL PROTECTED]] 
| Sent: 13 November 2001 22:39
| To: [EMAIL PROTECTED]
| Subject: compiler bug in ghc
| 
| 
| Hi,
| 
| while trying to compile the attached file MonadT.hs I got the 
| following error:
| 
| ghc  -fglasgow-exts   -c -o MonadT.o MonadT.hs
| ghc-5.02: panic! (the `impossible' happened, GHC version 5.02):
| coreSyn/Subst.lhs:387: Non-exhaustive patterns in 
| function zip_ty_env
|  
|  
| Please report it as a compiler bug to 
| [EMAIL PROTECTED], or 
| http://sourceforge.net/projects/ghc/.
| 
| --
| uname -a
| Linux hobbes 2.2.17 #2 SMP Sun Dec 3 22:42:15 CET 2000 i686 
| unknown   
|
| gcc -v
| Reading specs from /usr/lib/gcc-lib/i386-linux/2.95.2/specs
| gcc version 2.95.2 2220 (Debian GNU/Linux)
| 
| output while running with -v enabled:
| ghc  -fglasgow-exts -v   -c -o MonadT.o MonadT.hs
| Glasgow Haskell Compiler, Version 5.02, for Haskell 98, 
| compiled by GHC 
| version 5.02
| Using package config file: /usr/lib/ghc-5.02/package.conf
| 
|  Packages 
| Package
|{name = gmp,
| import_dirs = [],
| source_dirs = [],
| library_dirs = [],
| hs_libraries = [],
| extra_libraries = [gmp],
| include_dirs = [],
| c_includes = [],
| package_deps = [],
| extra_ghc_opts = [],
| extra_cc_opts = [],
| extra_ld_opts = []}
| Package
|{name = rts,
| import_dirs = [],
| source_dirs = [],
| library_dirs = [/usr/lib/ghc-5.02],
| hs_libraries = [HSrts],
| extra_libraries = [m],
| include_dirs = [/usr/lib/ghc-5.02/include],
| c_includes = [Stg.h],
| package_deps = [gmp],
| extra_ghc_opts = [],
| extra_cc_opts = [],
| extra_ld_opts =
|   [-u,
|PrelBase_Izh_static_info,
|-u,
|PrelBase_Czh_static_info,
|-u,
|PrelFloat_Fzh_static_info,
|-u,
|PrelFloat_Dzh_static_info,
|-u,
|PrelPtr_Ptr_static_info,
|-u,
|PrelWord_Wzh_static_info,
|-u,
|PrelInt_I8zh_static_info,
|-u,
|PrelInt_I16zh_static_info,
|-u,
|PrelInt_I32zh_static_info,
|-u,
|PrelInt_I64zh_static_info,
|-u,
|PrelWord_W8zh_static_info,
|-u,
|PrelWord_W16zh_static_info,
|-u,
|PrelWord_W32zh_static_info,
|-u,
|PrelWord_W64zh_static_info,
|-u,
|PrelStable_StablePtr_static_info,
|-u,
|PrelBase_Izh_con_info,
|-u,
|PrelBase_Czh_con_info,
|-u,
|PrelFloat_Fzh_con_info,
|-u,
|PrelFloat_Dzh_con_info,
|-u,
|PrelPtr_Ptr_con_info,
|-u,
|PrelStable_StablePtr_con_info,
|-u,
|PrelBase_False_closure,
|-u,
|PrelBase_True_closure,
|-u,
|PrelPack_unpackCString_closure,
|-u,
|PrelIOBase_stackOverflow_closure,
|-u,
|PrelIOBase_heapOverflow_closure,
|-u,
|PrelIOBase_NonTermination_closure,
|-u,
|PrelIOBase_BlockedOnDeadMVar_closure,
|-u,
|PrelWeak_runFinalizzerBatch_closure,
|-u,
|__stginit_Prelude]}
| Package
|{name = std,
| import_dirs = [/usr/lib/ghc-5.02/imports/std],
| source_dirs = [],
| library_dirs = [/usr/lib/ghc-5.02],
| hs_libraries = [HSstd],
| extra_libraries = [HSstd_cbits],
| include_dirs = [],
| c_includes = [HsStd.h],
| package_deps = [rts],
| extra_ghc_opts = [],
| extra_cc_opts = [],
| extra_ld_opts = []}
| Package
|{name = lang,
| import_dirs = [/usr/lib/ghc-5.02/imports/lang],
| source_dirs = [],
| library_dirs = [/usr/lib/ghc-5.02],
| hs_libraries = [HSlang],
| extra_libraries = [HSlang_cbits],
| include_dirs = [],
| c_includes = [HsLang.h],
| package_deps = [],
| extra_ghc_opts = [],
| extra_cc_opts = [],
| extra_ld_opts = [-u, Addr_Azh_static_info]}
| Package
|{name = concurrent,
| import_dirs = [/usr/lib/ghc-5.02/imports/concurrent],
| source_dirs = [],
| library_dirs = [/usr/lib/ghc-5.02],
| hs_libraries = [HSconcurrent],
| extra_libraries = [],
| include_dirs = [],
| c_includes = [],
| package_deps = [lang],
| extra_ghc_opts = [],
| extra_cc_opts = [],
| extra_ld_opts = []}
| Package
|{name = data,
| import_dirs = [/usr/lib/ghc-5.02/imports/data],
| source_dirs = [],
| library_dirs = [/usr/lib/ghc-5.02],
| hs_libraries = [HSdata],
| extra_libraries = [],
| include_dirs = [],
| c_includes = [],
| package_deps = [lang, util],
| extra_ghc_opts = [],
| extra_cc_opts = [],
| extra_ld_opts = []}
| Package
|{name = net,
| import_dirs = [/usr/lib/ghc-5.02/imports/net],
| source_dirs

compiler bug in ghc

2001-11-13 Thread Thorsten Seitz

Hi,

while trying to compile the attached file MonadT.hs I got the following error:

ghc  -fglasgow-exts   -c -o MonadT.o MonadT.hs
ghc-5.02: panic! (the `impossible' happened, GHC version 5.02):
coreSyn/Subst.lhs:387: Non-exhaustive patterns in function zip_ty_env
 
 
Please report it as a compiler bug to [EMAIL PROTECTED],
or http://sourceforge.net/projects/ghc/.

--
uname -a
Linux hobbes 2.2.17 #2 SMP Sun Dec 3 22:42:15 CET 2000 i686 unknown   
   
gcc -v
Reading specs from /usr/lib/gcc-lib/i386-linux/2.95.2/specs
gcc version 2.95.2 2220 (Debian GNU/Linux)

output while running with -v enabled:
ghc  -fglasgow-exts -v   -c -o MonadT.o MonadT.hs
Glasgow Haskell Compiler, Version 5.02, for Haskell 98, compiled by GHC 
version 5.02
Using package config file: /usr/lib/ghc-5.02/package.conf

 Packages 
Package
   {name = gmp,
import_dirs = [],
source_dirs = [],
library_dirs = [],
hs_libraries = [],
extra_libraries = [gmp],
include_dirs = [],
c_includes = [],
package_deps = [],
extra_ghc_opts = [],
extra_cc_opts = [],
extra_ld_opts = []}
Package
   {name = rts,
import_dirs = [],
source_dirs = [],
library_dirs = [/usr/lib/ghc-5.02],
hs_libraries = [HSrts],
extra_libraries = [m],
include_dirs = [/usr/lib/ghc-5.02/include],
c_includes = [Stg.h],
package_deps = [gmp],
extra_ghc_opts = [],
extra_cc_opts = [],
extra_ld_opts =
  [-u,
   PrelBase_Izh_static_info,
   -u,
   PrelBase_Czh_static_info,
   -u,
   PrelFloat_Fzh_static_info,
   -u,
   PrelFloat_Dzh_static_info,
   -u,
   PrelPtr_Ptr_static_info,
   -u,
   PrelWord_Wzh_static_info,
   -u,
   PrelInt_I8zh_static_info,
   -u,
   PrelInt_I16zh_static_info,
   -u,
   PrelInt_I32zh_static_info,
   -u,
   PrelInt_I64zh_static_info,
   -u,
   PrelWord_W8zh_static_info,
   -u,
   PrelWord_W16zh_static_info,
   -u,
   PrelWord_W32zh_static_info,
   -u,
   PrelWord_W64zh_static_info,
   -u,
   PrelStable_StablePtr_static_info,
   -u,
   PrelBase_Izh_con_info,
   -u,
   PrelBase_Czh_con_info,
   -u,
   PrelFloat_Fzh_con_info,
   -u,
   PrelFloat_Dzh_con_info,
   -u,
   PrelPtr_Ptr_con_info,
   -u,
   PrelStable_StablePtr_con_info,
   -u,
   PrelBase_False_closure,
   -u,
   PrelBase_True_closure,
   -u,
   PrelPack_unpackCString_closure,
   -u,
   PrelIOBase_stackOverflow_closure,
   -u,
   PrelIOBase_heapOverflow_closure,
   -u,
   PrelIOBase_NonTermination_closure,
   -u,
   PrelIOBase_BlockedOnDeadMVar_closure,
   -u,
   PrelWeak_runFinalizzerBatch_closure,
   -u,
   __stginit_Prelude]}
Package
   {name = std,
import_dirs = [/usr/lib/ghc-5.02/imports/std],
source_dirs = [],
library_dirs = [/usr/lib/ghc-5.02],
hs_libraries = [HSstd],
extra_libraries = [HSstd_cbits],
include_dirs = [],
c_includes = [HsStd.h],
package_deps = [rts],
extra_ghc_opts = [],
extra_cc_opts = [],
extra_ld_opts = []}
Package
   {name = lang,
import_dirs = [/usr/lib/ghc-5.02/imports/lang],
source_dirs = [],
library_dirs = [/usr/lib/ghc-5.02],
hs_libraries = [HSlang],
extra_libraries = [HSlang_cbits],
include_dirs = [],
c_includes = [HsLang.h],
package_deps = [],
extra_ghc_opts = [],
extra_cc_opts = [],
extra_ld_opts = [-u, Addr_Azh_static_info]}
Package
   {name = concurrent,
import_dirs = [/usr/lib/ghc-5.02/imports/concurrent],
source_dirs = [],
library_dirs = [/usr/lib/ghc-5.02],
hs_libraries = [HSconcurrent],
extra_libraries = [],
include_dirs = [],
c_includes = [],
package_deps = [lang],
extra_ghc_opts = [],
extra_cc_opts = [],
extra_ld_opts = []}
Package
   {name = data,
import_dirs = [/usr/lib/ghc-5.02/imports/data],
source_dirs = [],
library_dirs = [/usr/lib/ghc-5.02],
hs_libraries = [HSdata],
extra_libraries = [],
include_dirs = [],
c_includes = [],
package_deps = [lang, util],
extra_ghc_opts = [],
extra_cc_opts = [],
extra_ld_opts = []}
Package
   {name = net,
import_dirs = [/usr/lib/ghc-5.02/imports/net],
source_dirs = [],
library_dirs = [/usr/lib/ghc-5.02],
hs_libraries = [HSnet],
extra_libraries = [],
include_dirs = [],
c_includes = [HsNet.h],
package_deps = [lang, text, concurrent],
extra_ghc_opts = [],
extra_cc_opts = [],
extra_ld_opts = []}
Package
   {name = posix,
import_dirs = [/usr/lib/ghc-5.02/imports/posix],
source_dirs = [],
library_dirs = [/usr/lib/ghc-5.02],
hs_libraries = [HSposix],
extra_libraries = [HSposix_cbits],
include_dirs = [],
c_includes = [HsPosix.h],
package_deps = [lang],
extra_ghc_opts = [],
extra_cc_opts

RE: (not too important) compiler bug

2001-11-12 Thread Simon Marlow


 I really like your work and personally I do not have to complain,
 but ghc urges me to report it as a compiler bug:
 
 ghc-c -o LinkBase.o LinkBase.hs
 
  panic! (the `impossible' happened):
   Oversize heap check detected.  Please try compiling with -O.
 
   Please report it as a compiler bug to 
 [EMAIL PROTECTED]
 
 LinkBase.hs contains (automatically generated) biiig lists, and using
 the -O flag solves the problem (especially therefore I have 
 no complain ;-)

Thanks for the report.  Fortunately I have some good news: I fixed this
bug last week, so the next release won't have it.

Cheers,
Simon

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



(not too important) compiler bug

2001-11-08 Thread Sacha Berger

Hi!

I really like your work and personally I do not have to complain,
but ghc urges me to report it as a compiler bug:

ghc-c -o LinkBase.o LinkBase.hs

 panic! (the `impossible' happened):
Oversize heap check detected.  Please try compiling with -O.

Please report it as a compiler bug to [EMAIL PROTECTED]

LinkBase.hs contains (automatically generated) biiig lists, and using
the -O flag solves the problem (especially therefore I have no complain ;-)

CU. Sacha


-- 
The sooner you fall behind, the more time you have to catch up.


module LinkBase ( eaiTestbed ) where

import Graph
import Basic
import TestEAI


descriptors  = [982700148 ,2 ,4 ,5 ,3 ,982781661 ,982776050 ,982846460 ,982782612 
,982783758 ,982785238 ,982787252 ,982791556 ,982791679 ,982791929 ,982791991 
,982792055 ,982793660 ,982793776 ,982794015 ,982794193 ,982794294 ,982839449 
,982839624 ,982839714 ,982846737 ,982846866 ,982849752 ,982850657 ,982850856 
,982851051 ,982851165 ,982851743 ,982852957 ,982853183 ,982853407 ,982857871 
,982860487 ,982860558 ,982860623 ,982860710 ,982860790 ,982860843 ,982860966 
,982861040 ,982861132 ,982861286 ,982861365 ,982861457 ,982861938 ,982862112 
,982863848 ,982869223 ,982869336 ,982870651 ,982870907 ,982871104 ,983204454 
,983207778 ,983208157 ,983208271 ,983208383 ,983208466 ,983208523 ,983213272 
,983213513 ,983213553 ,983298457 ,983298759 ,983300321 ,983300397 ,983300480 
,983300549 ,983300629 ,983301126 ,983301292 ,983302459 ,983302622 ,983302666 
,983302718 ,983303518 ,983303590 ,983303732 ,983304018 ,983304190 ,983304290 
,983304339 ,983304401 ,983304845 ,983305287 ,983384250 ,983305401 ,983305469 
,983305541 ,983305633 ,983305691 ,983305745 ,983382467 ,983382775 ,983382841 
,983383160 ,983383320 ,983383401 ,983383476 ,983383554 ,983384300 ,983384565 
,983384675 ,983385350 ,983462268 ,983462364 ,983463680 ,983463861 ,983464533 
,983464550 ,984421284 ,982791807 ,984160171 ,984160256 ,984160712 ,984161746 
,984162005 ,984162066 ,984421101 ,984422088 ,984422150 ,984422231 ,984422529 
,984422792 ,984423188 ,984423575 ,984423534 ,984492371 ,984492620 ,984492724 
,984493467 ,984493623 ,984493986 ,984678553 ,984678754 ,984679468 ,984679516 
,984679593 ,984734055 ,984734140 ,984734733 ,984734889 ,984734967 ,985029939 
,985030442 ,985030505 ,985030666 ,985030775 ,985030880 ,985031143 ,985031249 
,985078307 ,985078421 ,985078978 ,985081053 ,985081127 ,985081979 ,985082199 
,985090266 ,985090361 ,985090440 ,985109241 ,985109290 ,985109670 ,985109748 
,985109844 ,985109952 ,985110433 ,985201496 ,985280275 ,985280434 ,985612082 
,985612125 ,985612547 ,985612731 ,985613063 ,985614498 ,985614559 ,985889795 
,985889628 ,985889728 ,985890151 ,985890672 ,985953519 ,985953809 ,985963711 
,985963813 ,985964585 ,985964670 ,985965919 ,985967983 ,985968049 ,986206362 
,986287885 ,986288230 ,986290112 ,986290803 ,986293160 ,986293264 ,986295033 
,986378194 ,986378431 ,986378622 ,986378785 ,986380059 ,986383736 ,986390701 
,986390819 ,986391090 ,986391200 ,986837733 ,6 ,1 ,982787338 ,983304586 ,984423356 , 
] -- Node  is a dummy node which is removed immediately to eliminate dangling 
links. Dangling links where syntactically corrected through  sed s/,)/,)/g | sed 
s/(,/(,/g 

associations = 
[(982776050,),(6,982700148),(982781661,982782612),(982781661,982783758),(982781661,982792055),(982781661,982785238),(982781661,),(982781661,982791929),(982781661,982791807),(,),(982781661,982791679),(982781661,982791556),(982781661,982787338),(982781661,982787252),(982793776,982794015),(982793776,982794193),(982793776,982794294),(982792055,),(982792055,982839624),(982792055,982839449),(982792055,982839714),(982791991,982846460),(,982839624),(982791991,982846737),(982791991,982846866),(982791929,982849752),(982791807,982851165),(982791807,982851051),(982791807,982850856),(982791807,982850657),(982785238,982852957),(982791679,982851743),(982852957,982851051),(982852957,982853407),(982852957,982853183),(982782612,),(982782612,),(982782612,),(982791556,982787252),(982857871,982787252),(982787252,982857871),(982857871,982781661),(982851743,982860487),(982851743,982860558),(982851743,982860623),(982851743,982860710),(982851743,982860623),(982851743,982860487),(982851743,982860790),(982851743,982860843),(982851743,982860966),(982851743,982861040),(982851743,982861132),(982851743,982861286),(982851743,982861365),(982851743,982861457),(982851743,982851165),(982851743,982791679),(982791679,982863848),(982851743,982861938),(982851743,982862112),(982851743,982791807),(982851743,982791929),(982791929,982849752),(982851743,982792055),(982851743,982791991),(982851743,982791679),(982869223,982869336),(982861040,982869223),(982870907,982776050),(983204454,983207778),(983204454,983208157),(983204454,983208271),(983204454,983208383),(983204454,983208523),(983204454,983208466),(983213272,982870651),(983213513,982870907),(983298457,983298759),(983300321,983300397

compiler bug

2001-10-22 Thread Timothy Doze


Hello, 
Im relativly new at this, when i tried to compile i got this message:

-

ghc-5.00.2: panic! (the `impossible' happened, GHC version 5.00.2):
does not exist
Action: openFile
Reason: dangling symlink
File: ./GameFrontEnd.hi

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


GameFrontEnd.hi is a file that has been proven to work, by my university
lecturers, somthing we are told to take for granted, but they're not
around at the moment so i send you this in the hope you can tell me what
it means.
Cheers.



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



RE: compiler bug

2001-10-08 Thread Simon Marlow


 when i loaded my ass2 GameFrontEnd.hs into ghci, this came up
 
 
 Please report it as a compiler bug to 
 [EMAIL PROTECTED],
 or http://sourceforge.net/projects/ghc/
 
 ghc-5.00.2: panic! (the
 `impossible' happened, GHC version 5.00.2):
 loadObj: failed

Hi there, and thanks for the report.  Could you please try again with
GHC 5.02, and if the problem persists then send us more details: the
complete command line used to invoke GHCi, the output produced when the
-v flag is added, and the source/object files you were trying to lead at
the time.

Cheers,
Simon

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



compiler bug

2001-10-05 Thread Sandra Leung


hi,
when i loaded my ass2 GameFrontEnd.hs into ghci, this came up


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

ghc-5.00.2: panic! (the
`impossible' happened, GHC version 5.00.2):
loadObj: failed


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



RE: compiler bug report

2001-08-02 Thread Julian Seward (Intl Vendor)


What platform is this on?  I've had reports of wierdnesses with
the sparc-solaris binary build we made for 5.00.2 which don't
happen in the Linux builds.

J

| -Original Message-
| From: Hal Daume [mailto:[EMAIL PROTECTED]] 
| Sent: Wednesday, August 01, 2001 6:57 PM
| To: Simon Marlow
| Cc: [EMAIL PROTECTED]
| Subject: Re: compiler bug report
| 
| 
| I can't reliably repro the bug, but it happens to me a *lot*. 
|  At least one every hour or two...not only on that file...I 
| don't think it happens if I delete all the .o files...not 
| sure though...
| 
|  - Hal
| 
| Simon Marlow wrote:
|  
|  Hi there,
|  
|  Thanks for the report.  I can't repro the bug though - after I 
|  commented out the definition of beginWithBy at the end of 
| Util.hs (it 
|  had some type errors), and tried the exact same sequence of 
| commands 
|  in ghci, it happily re-loaded Util.o at the end.
|  
|  Is there any more information you can provide that will help us to 
|  repro it?
|  
|  Cheers,
|  Simon
|  
|   Here is a transcript:
|   
|   enescu:/nfs/isd/hdaume/stat-sum-ulf 54% ghci -package lang ghci 
|   -package lang
|  ___ ___ _
| / _ \ /\  /\/ __(_)
|/ /_\// /_/ / /  | |  GHC Interactive, version 5.00.2,
|   For Haskell
|   98.
|   / /_\\/ __  / /___| |  http://www.haskell.org/ghc/
|   \/\/ /_/\/|_|  Type :? for help.
|  
|   Loading package std ... linking ... done.
|   Loading package lang ... linking ... done.
|   Prelude :l Util
|   :l Util
|   Skipping  Util ( Util.hs, ./Util.o )
|   Ok, modules loaded: Util.
|   Util List.[]
|   List.[]
|  
|   Ambiguous type variable(s) `t' in the constraint 
| `PrelShow.Show t' 
|   arising from use of `PrelIO.print' at No locn in a `do' 
| expression 
|   pattern binding: PrelIO.print it
|   Util `eq`
|   `eq`
|   no file:0: parse error on input ``'
|   Util 3 `eq` 4
|   3 `eq` 4
|  
|   no file:0: Variable not in scope: `eq'
|   Util :l Util
|   :l Util
|   unloadObj: can't find `./Util.o' to unload
|   ghc-5.00.2: panic! (the `impossible' happened, GHC 
| version 5.00.2):
|   unloadObj: failed
|  
|   Please report it as a compiler bug to 
|   [EMAIL PROTECTED], or 
|   http://sourceforge.net/projects/ghc/.
|  
|  
|   Util
|   -
|  
|   I'm not sure exactly what went wrong, but here's a copy of 
|   Util.hs...
|  
|   --
|   Hal Daume III
|  
|Computer science is no more about computers| [EMAIL PROTECTED]
| than astronomy is about telescopes. -Dijkstra | 
|   www.isi.edu/~hdaume
|  
| 
| -- 
| Hal Daume III
| 
|  Computer science is no more about computers| [EMAIL PROTECTED]
|   than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume
| 
| ___
| Glasgow-haskell-bugs mailing list 
| [EMAIL PROTECTED] 
| http://www.haskell.org/mailman/listinfo/glasgo| w-haskell-bugs
| 

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



RE: compiler bug report

2001-08-01 Thread Simon Marlow

Hi there,

Thanks for the report.  I can't repro the bug though - after I commented
out the definition of beginWithBy at the end of Util.hs (it had some
type errors), and tried the exact same sequence of commands in ghci, it
happily re-loaded Util.o at the end.

Is there any more information you can provide that will help us to repro
it?

Cheers,
Simon

 Here is a transcript:
 
 enescu:/nfs/isd/hdaume/stat-sum-ulf 54% ghci -package lang
 ghci -package lang
___ ___ _
   / _ \ /\  /\/ __(_)
  / /_\// /_/ / /  | |  GHC Interactive, version 5.00.2, 
 For Haskell
 98.
 / /_\\/ __  / /___| |  http://www.haskell.org/ghc/
 \/\/ /_/\/|_|  Type :? for help.
 
 Loading package std ... linking ... done.
 Loading package lang ... linking ... done.
 Prelude :l Util
 :l Util
 Skipping  Util ( Util.hs, ./Util.o )
 Ok, modules loaded: Util.
 Util List.[]
 List.[]
 
 Ambiguous type variable(s) `t' in the constraint `PrelShow.Show t'
 arising from use of `PrelIO.print' at No locn
 in a `do' expression pattern binding: PrelIO.print it
 Util `eq`
 `eq`
 no file:0: parse error on input ``'
 Util 3 `eq` 4
 3 `eq` 4
 
 no file:0: Variable not in scope: `eq'
 Util :l Util
 :l Util
 unloadObj: can't find `./Util.o' to unload
 ghc-5.00.2: panic! (the `impossible' happened, GHC version 5.00.2):
 unloadObj: failed
 
 Please report it as a compiler bug to 
 [EMAIL PROTECTED],
 or http://sourceforge.net/projects/ghc/.
 
 
 Util 
 -
 
 I'm not sure exactly what went wrong, but here's a copy of Util.hs...
 
 -- 
 Hal Daume III
 
  Computer science is no more about computers| [EMAIL PROTECTED]
   than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume
 

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



RE: compiler bug report

2001-08-01 Thread Simon Marlow

I just thought I'd point out: this is the third report of similar
behaviour, so there's clearly something amiss.  If anyone else has seen
it and/or has any clues as to how we might track it down, please speak
up.

Cheers,
Simon

 -Original Message-
 From: Simon Marlow [mailto:[EMAIL PROTECTED]] 
 Sent: Wednesday, August 01, 2001 9:51 AM
 To: Hal Daume; [EMAIL PROTECTED]
 Subject: RE: compiler bug report
 
 
 Hi there,
 
 Thanks for the report.  I can't repro the bug though - after 
 I commented
 out the definition of beginWithBy at the end of Util.hs (it had some
 type errors), and tried the exact same sequence of commands 
 in ghci, it
 happily re-loaded Util.o at the end.
 
 Is there any more information you can provide that will help 
 us to repro
 it?
 
 Cheers,
   Simon
 
  Here is a transcript:
  
  enescu:/nfs/isd/hdaume/stat-sum-ulf 54% ghci -package lang
  ghci -package lang
 ___ ___ _
/ _ \ /\  /\/ __(_)
   / /_\// /_/ / /  | |  GHC Interactive, version 5.00.2, 
  For Haskell
  98.
  / /_\\/ __  / /___| |  http://www.haskell.org/ghc/
  \/\/ /_/\/|_|  Type :? for help.
  
  Loading package std ... linking ... done.
  Loading package lang ... linking ... done.
  Prelude :l Util
  :l Util
  Skipping  Util ( Util.hs, ./Util.o )
  Ok, modules loaded: Util.
  Util List.[]
  List.[]
  
  Ambiguous type variable(s) `t' in the constraint `PrelShow.Show t'
  arising from use of `PrelIO.print' at No locn
  in a `do' expression pattern binding: PrelIO.print it
  Util `eq`
  `eq`
  no file:0: parse error on input ``'
  Util 3 `eq` 4
  3 `eq` 4
  
  no file:0: Variable not in scope: `eq'
  Util :l Util
  :l Util
  unloadObj: can't find `./Util.o' to unload
  ghc-5.00.2: panic! (the `impossible' happened, GHC version 5.00.2):
  unloadObj: failed
  
  Please report it as a compiler bug to 
  [EMAIL PROTECTED],
  or http://sourceforge.net/projects/ghc/.
  
  
  Util 
  -
  
  I'm not sure exactly what went wrong, but here's a copy of 
 Util.hs...
  
  -- 
  Hal Daume III
  
   Computer science is no more about computers| [EMAIL PROTECTED]
than astronomy is about telescopes. -Dijkstra | 
www.isi.edu/~hdaume
 

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

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



Re: compiler bug report

2001-08-01 Thread Hal Daume

I can't reliably repro the bug, but it happens to me a *lot*.  At least
one every hour or two...not only on that file...I don't think it happens
if I delete all the .o files...not sure though...

 - Hal

Simon Marlow wrote:
 
 Hi there,
 
 Thanks for the report.  I can't repro the bug though - after I commented
 out the definition of beginWithBy at the end of Util.hs (it had some
 type errors), and tried the exact same sequence of commands in ghci, it
 happily re-loaded Util.o at the end.
 
 Is there any more information you can provide that will help us to repro
 it?
 
 Cheers,
 Simon
 
  Here is a transcript:
  
  enescu:/nfs/isd/hdaume/stat-sum-ulf 54% ghci -package lang
  ghci -package lang
 ___ ___ _
/ _ \ /\  /\/ __(_)
   / /_\// /_/ / /  | |  GHC Interactive, version 5.00.2,
  For Haskell
  98.
  / /_\\/ __  / /___| |  http://www.haskell.org/ghc/
  \/\/ /_/\/|_|  Type :? for help.
 
  Loading package std ... linking ... done.
  Loading package lang ... linking ... done.
  Prelude :l Util
  :l Util
  Skipping  Util ( Util.hs, ./Util.o )
  Ok, modules loaded: Util.
  Util List.[]
  List.[]
 
  Ambiguous type variable(s) `t' in the constraint `PrelShow.Show t'
  arising from use of `PrelIO.print' at No locn
  in a `do' expression pattern binding: PrelIO.print it
  Util `eq`
  `eq`
  no file:0: parse error on input ``'
  Util 3 `eq` 4
  3 `eq` 4
 
  no file:0: Variable not in scope: `eq'
  Util :l Util
  :l Util
  unloadObj: can't find `./Util.o' to unload
  ghc-5.00.2: panic! (the `impossible' happened, GHC version 5.00.2):
  unloadObj: failed
 
  Please report it as a compiler bug to
  [EMAIL PROTECTED],
  or http://sourceforge.net/projects/ghc/.
 
 
  Util
  -
 
  I'm not sure exactly what went wrong, but here's a copy of Util.hs...
 
  --
  Hal Daume III
 
   Computer science is no more about computers| [EMAIL PROTECTED]
than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume
 

-- 
Hal Daume III

 Computer science is no more about computers| [EMAIL PROTECTED]
  than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume

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



compiler bug report

2001-07-31 Thread Hal Daume

Here is a transcript:

enescu:/nfs/isd/hdaume/stat-sum-ulf 54% ghci -package lang
ghci -package lang
   ___ ___ _
  / _ \ /\  /\/ __(_)
 / /_\// /_/ / /  | |  GHC Interactive, version 5.00.2, For Haskell
98.
/ /_\\/ __  / /___| |  http://www.haskell.org/ghc/
\/\/ /_/\/|_|  Type :? for help.

Loading package std ... linking ... done.
Loading package lang ... linking ... done.
Prelude :l Util
:l Util
Skipping  Util ( Util.hs, ./Util.o )
Ok, modules loaded: Util.
Util List.[]
List.[]

Ambiguous type variable(s) `t' in the constraint `PrelShow.Show t'
arising from use of `PrelIO.print' at No locn
in a `do' expression pattern binding: PrelIO.print it
Util `eq`
`eq`
no file:0: parse error on input ``'
Util 3 `eq` 4
3 `eq` 4

no file:0: Variable not in scope: `eq'
Util :l Util
:l Util
unloadObj: can't find `./Util.o' to unload
ghc-5.00.2: panic! (the `impossible' happened, GHC version 5.00.2):
unloadObj: failed

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


Util 
-

I'm not sure exactly what went wrong, but here's a copy of Util.hs...

-- 
Hal Daume III

 Computer science is no more about computers| [EMAIL PROTECTED]
  than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume

module Util
where

import List
import Maybe
import Char
import IO
import IOExts

infix !=

a != b = not (a == b)

nth [] i = error (nth out of range:  ++ (show i))
nth (x:_) 1 = x
nth (_:x) (n+1) = nth x n

containsFn f l = isJust (find f l)

contains x = containsFn (==x)

mapPartial :: (a - Maybe b) - [a] - [b]
mapPartial f l = mapPartial' f l []
where mapPartial' _ [] acc = acc
  mapPartial' f (x:xs) acc = mapPartial' f xs (case f x of
   Nothing - acc
   Just x' - x':acc)

-- same as otherwise
ow = True

foldMaybe :: (a - b - Maybe a) - a - [b] - Maybe a
foldMaybe _ a [] = Just a
foldMaybe f a (b:bs) = case f a b of
 Nothing - Nothing
 Just a' - foldMaybe f a' bs

allButLast :: [a] - [a]
allButLast [] = error allButLast on []
allButLast [x] = []
allButLast (x:xs) = x:allButLast xs

putErr s = unsafePerformIO (do hPutStrLn stderr s)

maybeGood Nothing  = Error maybeGood
maybeGood (Just a) = Good a

goodMaybe (Error _) = Nothing
goodMaybe (Good a)  = Just a

infixr 9 ===, =~=

good (Good a) = a
good (Error err) = error err

class LCaseEq a where
(===) :: a - a - Bool

instance LCaseEq Char where
c1 === c2 = toLower c1 == toLower c2

instance LCaseEq a = LCaseEq [a] where
[] === [] = True
[] === _  = False
_  === [] = False
(c:cs) === (c':cs') = c === c'  cs === cs'

class Approx a where
(=~=) :: a - a - Bool

instance Eq a = Approx [a] where
a =~= b = take 50 a == take 50 b

data Errored a = Good a | Error String
 deriving (Eq, Show, Ord, Read)


isNum x = isAlphaNum x  (not (isAlpha x))

--beginsWithBy abc abcd (==) = True
--beginsWithBy abc ab   (==) = False
beginWithBy _ [] _ = True
beginWithBy _ _ [] = False
beginWithBy eq (x:xs) (y:ys) | x `eq` y  = beginWithBy xs ys eq
 | otherwise = False

beginWith = beginWithBy (==)



RE: compiler-bug

1999-06-11 Thread Simon Peyton-Jones

Andreas

Thanks for a fine report.  This one must have been lurking
for ages!  Fixed in the CVS tree. A one-line change in deSugar/DsHsSyn.lhs

Simon

[For others: this innocuous program was being desugared wrongly.]

erroR :: Int
erroR = n where
(n+1,_) = (5,2)



compiler-bug

1999-06-07 Thread Andreas Marth

Hello!

I got an error compiling my program with ghc-4.02 and ghc-4.03 (-O option)
(files error#ghc-4.02-O and error#ghc-4.03-O)
I tried compiling with ghc-4.03 without the -O option, but it did'nt help
(file error#ghc-4.03)
I would be glad if You could give me a hint how to compile it anyway.
I send You both error-files. If You need any further information, send me a
mail.

Hope, You can fix it,
A. Marth


 error#ghc-4.03
 error#ghc-4.03-O
 error#ghc-4.02-O


panic, compiler bug

1998-06-30 Thread Martin Stein

During developing a module, I tried to compile the incomplete module
SplayTree.hs to check something and got a panic!

After changing the incorrect first line of SplayTree.hs from

 module Dictionary where
to
 module SplayTree where

I got the right error messages I "wanted".
The 3 concerned modules are attached

Martin Stein

PS: I'm using 3.02 from binary distribution and Linux

the compiler messages (Dictionary.o and BinarySearchTree.o existed):
 ghc -c -fglasgow-exts SplayTree.hs

importDecl wierdness: Dictionary.delete{-r7k-}

importDecl wierdness: Dictionary.insert{-r7l-}

importDecl wierdness: Dictionary.Dictionary{-r7a-}

panic! (the `impossible' happened):
tcLookupClass Dictionary.Dictionary{-r7a-}

Please report it as a compiler bug to [EMAIL PROTECTED]

module Dictionary where

data SearchResult a = Found a | Fail

class (Eq key,Ord key) = Dictionary dict key dat where
insert :: (key,dat) - dict key dat - dict key dat
delete :: key - dict key dat - dict key dat
search :: key - dict key dat - (key,SearchResult dat,dict key dat)
update :: (key,dat) - dict key dat - dict key dat

fromList :: [(key,dat)] - dict key dat
toList :: dict key dat - [(key,dat)]

insertList :: [(key,dat)] - dict key dat - dict key dat
deleteList :: [key] - dict key dat - dict key dat
searchList :: [key] - dict key dat - ([(key,SearchResult dat)],dict key dat)
updateList :: [(key,dat)] - dict key dat - dict key dat

insertList xs d = foldr insert d xs
deleteList xs d = foldr delete d xs
updateList xs d = foldr update d xs

searchList xs d = foldr search' ([],d) xs
where  search' x (l,d) = ((x,sr):l,d') where (x,sr,d') = search x d


module BinarySearchTree where

import Dictionary

class (Eq key,Ord key) = BinarySearchTree tree key dat where
getKey :: tree key dat - key
getDat :: tree key dat - dat
getLeft :: tree key dat - tree key dat
getRight :: tree key dat - tree key dat
height :: tree key dat - Int
numberOfNodes :: tree key dat - Int
rotateRight :: tree key dat - tree key dat
rotateLeft :: tree key dat - tree key dat


data (Eq key, Ord key) = BSTree key dat = Node (BSTree key dat) (BSTree key dat) 
(key,dat) |
   Nil deriving (Eq, Ord)

instance (Eq key,Ord key) = BinarySearchTree BSTree key dat where
getKey Nil = error "getKey: empty BSTree\n"
getKey (Node _ _ (k,d)) = k

getDat Nil = error "getDat: empty BSTree\n"
getDat (Node _ _ (k,d)) = d

getLeft Nil = error "getLeft: empty BSTree\n"
getLeft (Node tl _ _) = tl

getRight Nil = error "getRight: empty BSTree\n"
getRight (Node _ tr _) = tr

height Nil = 0
height (Node tl tr _) = 1 + max (height tl) (height tr)

numberOfNodes Nil = 0
numberOfNodes (Node tl tr _) = 1 + (numberOfNodes tl) + (numberOfNodes tr)

rotateRight (Node (Node tll tlr xl) tr x) = Node tll (Node tlr tr x) xl
rotateRight Nil = error "rotateRight: empty BSTree\n"
rotateRight (Node Nil tl x) = error "rotateRight: empty left BSTree\n"

rotateLeft (Node tl (Node trl trr xr) x) = Node (Node tl trl x) trr xr
rotateLeft Nil = error "rotateLeft: empty BSTree\n"
rotateLeft (Node tl Nil x) = error "rotateLeft: empty right BSTree\n"


module Dictionary where

import BinarySearchTree
import Dictionary

type SplayTree key dat = BSTree key dat

instance (Eq key,Ord key) = Dictionary SplayTree key dat where
insert p@(x,_) t = case splay x t of
Nil - Node Nil Nil x
Node tl tr q@(y,_) - case compare x y of
  EQ - Node tl tr p
  GT - Node (Node tl Nil q) tr p
  LT - Node tl (Node Nil tr q) p

delete x t = case splay x t of
 Nil  - Nil
 t'@(Node Nil tr q@(y,_)) - if x/=y then t' else tr
 t'@(Node tl Nil q@(y,_)) - if x/=y then t' else tl
 t'@(Node tl tr q@(y,_))  - if x/=y then t' else putToRight 
(splay x tl) tr
 where t'' = putToRight (splay x tl) tr
  -- 'splay x tl' dadurch wird der groeszte 
Knoten im
  -- linken Teilbaum nach oben rotiert - 
rechts ist Nil
-- putToRight :: (Eq key, Ord key) = SplayTree key dat - SplayTree key 
dat - STree a
   putToRight (Node tl Nil p) ttr = Node tl ttr p












---
-- splay: the most important function, all dictionary functions are based on it
---

type SI key dat = (SplayTree key dat,Int)

splay :: 

Re: Compiler bug pops up when compiling ghc-2.07 with 2.02

1997-10-10 Thread Marcin Benke

Simon L Peyton Jones writes:
   
   I tried, but it seems to complete successfully. Nevertheless, later
   make all fails with the same message.
   Probably the dependencies generated by make boot (or make depend, for
   that matter) _are_ circular (citing from ghc/compiler/.depend):
   
   utils/FastString.o : basicTypes/Unique.hi
   
   basicTypes/Unique.o : utils/Pretty.hi
   
   utils/Pretty.o : utils/FastString.hi
  
  My guess is that you have not got the line
   
   Ghc2_0= YES
  
  in your build.mk file.  GHC 2.x uses a different way of dealing with
  mutual recursion (via M.hi-boot files) than GHC 0.29 (which used
  M.lhi files).

No, I had this line in my build.mk from the beginning. For the record,
here goes my builld.mk:

GhcBuilderVersion = 207

WithGhcHc = ghc-2.07
Ghc2_0=YES

GhcWithHscBuiltViaC=NO

  
  Remember, don't bother to use 2.06 or earlier for self-booting.  Only
  2.07 is up to it.
  
Yes, I use 2.07 (or so it seems):

[08:53:35] ben@kawa:~ ghc --version
The Glorious Glasgow Haskell Compilation System, version 2.07,patchlevel 0

BTW, when you are so kind as to answer my not-so-wise questions, what
is the 'proper' way of getting a .dvi from literate sources? I could
not find anything in the docs, and my attempts to follow the
literate/README fail at the make stage already.

Regards,
Marcin Benke

"Calm down, it's only ones and zeros!" -  DJ Delorie



Re: Compiler bug pops up when compiling ghc-2.07 with 2.02

1997-10-09 Thread Simon L Peyton Jones

 
 I tried, but it seems to complete successfully. Nevertheless, later
 make all fails with the same message.
 Probably the dependencies generated by make boot (or make depend, for
 that matter) _are_ circular (citing from ghc/compiler/.depend):
 
 utils/FastString.o : basicTypes/Unique.hi
 
 basicTypes/Unique.o : utils/Pretty.hi
 
 utils/Pretty.o : utils/FastString.hi

My guess is that you have not got the line

Ghc2_0= YES

in your build.mk file.  GHC 2.x uses a different way of dealing with
mutual recursion (via M.hi-boot files) than GHC 0.29 (which used M.lhi files).

When you make that change to build.mk you'll need to do a make depend again.

Yes, this should be documented.

Remember, don't bother to use 2.06 or earlier for self-booting.  Only
2.07 is up to it.

Simon




Re: Compiler bug pops up when compiling ghc-2.07 with 2.02

1997-10-09 Thread Marcin Benke

Sigbjorn Finne writes:
  
  my guess is that the Makefile dependencies aren't generated properly,
  try doing 'make depend' in ghc/compiler and see if that fails to
  complete properly for some reason.
  
I tried, but it seems to complete successfully. Nevertheless, later
make all fails with the same message.
Probably the dependencies generated by make boot (or make depend, for
that matter) _are_ circular (citing from ghc/compiler/.depend):

utils/FastString.o : basicTypes/Unique.hi

basicTypes/Unique.o : utils/Pretty.hi

utils/Pretty.o : utils/FastString.hi

...the circle closes :-( 

  BTW, mailing glasgow-haskell-bugs is probably a good idea with
  problems like these; I'm happy to help out, but I'm reading
  my e-mail infrequently at the moment.
  
  Marcin Benke writes:
   Thanks for this hint. I have downloaded binary version of 2.07 and
   tried again to recompile 2.07 with itself. However, after
   
   configure
   make boot
   
   make all fails like this:

   make[2]: Circular utils/Argv.o - utils/FastString.hi dependency dropped.
   ghc-2.07 -cpp -fglasgow-exts -Rghc-timing -I. -IcodeGen -InativeGen -Iparser 
 -iutils:basicTypes:types:hsSyn:prelude:rename:typecheck:deSugar:coreSyn:specialise:simplCore:stranal:stgSyn:simplStg:codeGen:absCSyn:main:reader:profiling:parser:nativeGen
  -recomp -DOMIT_DEFORESTER   -fvia-C  -c utils/Argv.lhs -o utils/Argv.o -osuf o

   utils/Argv.lhs:15: Could not find valid interface file `FastString'

   Compilation had errors
   make[2]: *** [utils/Argv.o] Error 1
   make[1]: *** [all] Error 2
   make: *** [all] Error 2
   

Regards,
Marcin Benke

"Calm down, it's only ones and zeros!" -  DJ Delorie



Re: Compiler bug pops up when compiling ghc-2.07 with 2.02

1997-10-03 Thread Sigbjorn Finne


Marcin Benke writes:
 
 Hi,
 
 while trying to compile GHC 2.07 with 2.02 (on i386 Linux) I
 encountered the following:
 
 
 ==fptools== make all;
  in /export/linux/ben/Dlubanie/Build/fptools/ghc/lib
 
 rm -f ghc/PrelBase.o ; if [ ! -d ghc/PrelBase ]; then mkdir ghc/PrelBase; else find 
ghc/PrelBase -name '*.o' -print | xargs rm -f __rm_food ; fi
 ../../ghc/driver/ghc -recomp -cpp -fglasgow-exts -fvia-C -Rghc-timing -O -split-objs 
-odir ghc/PrelBase  -H12m  -c ghc/PrelBase.lhs -o ghc/PrelBase.o -osuf o
 Warning: GENERATE_SPECS pre-processing pragma ignored:
   {-# GENERATE_SPECS subtract a{Int#,Double#,Int,Double,Complex(Double#),Complex 
(Double)} #-}
 Warning: GENERATE_SPECS pre-processing pragma ignored:
   {-# GENERATE_SPECS (.) a b c #-}
 Warning: GENERATE_SPECS pre-processing pragma ignored:
   {-# GENERATE_SPECS data a :: Lift a #-}
 Warning: GENERATE_SPECS pre-processing pragma ignored:
   {-# GENERATE_SPECS showList__ a #-}
  
 *** Pattern-matching error within GHC!
  
 This is a compiler bug; please report it to [EMAIL PROTECTED]
  
 Fail: "main/CmdLineOpts.lhs", line 451: incomplete pattern(s) to match in function 
"simpl_sep"
 --
 

Hi,

it seems like you're compiling with an incompatible pair of compiler
and driver. There was a change to the compiler command-line syntax
with version 2.06, which looks like what's causing the above.

Compiling 2.07 with 2.02 is hard (if not impossible). I suggest you
try out the 2.07 Linux binary distribution that the Heroic Sven
Panne has made available

   ftp://ftp.informatik.uni-muenchen.de/pub/local/pms/

(2.07 is self-compilable)

HTH,
--Sigbjorn



Compiler bug

1997-05-13 Thread Noel Winstanley

Hi,
I was compiling together a fairly hefty lump of code, when the top level
module raied the following error :-

/local/fp/bin/sparc-sun-solaris2/ghc-2.02 -H1000
-i/users/grad/nww/share/ghc/ -L/users/grad/nww/share/ghc/ -O -lnww -c
ModuleGA.lhs 

*** Pattern-matching error within GHC!

This is a compiler bug; please report it to
[EMAIL PROTECTED]

Fail: "coreSyn/CoreUtils.lhs", line 122: pattern-matching failed in case
*** Error code 1
make: Fatal error: Command failed for target `ModuleGA.o'

If it's any help, I've enclosed the code -- it's a bit scrappy, and the
error doesn't give any indication which line caused it, but it may help.
-- 
Noel Winstanley
Dept of Computing Science NEW TEL EXT. 2914


module Main where

import Program (program,machineModel,progenv,progene) -- user defined prog.
import Simulate (simulate)
import SimMonad 

import MachineModel
import Template(Template(..),template)
import Decode (result,Result(..))
import ProgramGene (depthGene,mutateProgramGene,reproduceProgramGene,
   initializeProgramGene)
import GA
import GeneUtils 
import SimulateClass


individProgramGene = I {
   eval,
   mutate = mutateProgramGene depth,
   reproduce = reproduceProgramGene depth,
   initialize = initializeProgramGene tmp}
   where
   eval pg = do -- no fixing done within simulation.
   rr - getRList 
   let
a@SimP{sumTime,rands} = run rr machineModel 
   (program :: Sim Names)  progenv pg
   updateStats sumTime
   (best,worst) - getStats
   let weightfn t = (worst - t) / (worst - best) 
   setRList rands
   return (pg,weightfn sumTime) 
   tmp = gene $ run u u  (program :: Template Names) u u
   depth = depthGene tmp

main = do
   putStrLn "population :"
   p - map read getLine :: IO Int
   putStrLn "generations :"
   g - map read getLine :: IO Int
   putStrLn "pm :"
   m - map read getLine :: IO Double
   putStrLn "pc :"
   c - map read getLine :: IO Double
   putStrLn "full results or best (f/b)"
   ch - getChar
   let param = (popsize_s p . gens_s g . pm_s m . pc_s c)
   lo = gene $ run u u  (program :: Template Names) u u 
   dispF = show . result 20 -- this shouldn't be hard-coded
   putStrLn "Wait - Initializing population"
   if ch == 'f' then
   runAll_n individProgramGene dispF param
else runBest_n individProgramGene dispF lo param
   
u :: a
u = undefined

-- utility function for eval prog.
updateStats :: Double - St ()
updateStats i= do {d - getStats; updateStats' i d}
updateStats' i (b,w) | w == -1 = setStats (b,i) -- two cases to initialize..
| b == -1 = setStats (i,w)
| i  b = setStats (i,w)
| i  w = setStats (b,i)
| otherwise = return ()



compiler bug in ghc-2.02

1997-04-22 Thread Meurig Sage

When compiling the following program, the compiler
crashed with a bug. This only happens when compiling
with -O.

--
module Test where
import GlaExts
test :: PrimIO ()
test = ioToPrimIO (putStr "bob") `seqPrimIO` test
--

--
ghc-2.02 -O -c test.hstest.hs:8: 
Warning: Possibly incomplete patterns
in a group of case alternatives beginning: 1 - ...

*** Pattern-matching error within GHC!

This is a compiler bug; please report it to [EMAIL PROTECTED]

Fail: "coreSyn/CoreUtils.lhs", line 122: pattern-matching failed in case
-

I'm using ghc-2.02, with the i386-unknown-solaris2
pre-built distribution.

Cheers,
  Meurig