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


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 

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