#2693: Type Synonym Family Panic in GHC 6.10.0.20081007
------------------------+---------------------------------------------------
Reporter: BenMoseley | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 6.9
Severity: major | Resolution:
Keywords: panic | Difficulty: Unknown
Testcase: | Architecture: x86
Os: Windows |
------------------------+---------------------------------------------------
Changes (by igloo):
* difficulty: => Unknown
Old description:
> The following file (DM.hs) panics GHC 6.10 with this error message:
>
> c:/ws/main/depot/QA/EDG/EDG_priv/FPF_Dev.br/src $
> c:\ghc\ghc-6.10.0.20081007\bin\ghc.exe ~/DM.hs
> ghc.exe: panic! (the 'impossible' happened)
> (GHC version 6.10.0.20081007 for i386-unknown-mingw32):
> TcTyFuns.uMeta: normalisation shouldn't allow x ~ x
>
> Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug
>
> --Ben
>
> ---- DM.hs ----
> {-# LANGUAGE GADTs, TypeFamilies #-}
>
> type family TFn a :: *
>
> data PVR a = PVR {pvrX :: Int} deriving (Eq)
>
> f :: () -> Maybe (TFn a)
> f _ = undefined
>
> g :: Maybe ()
> g = do
> pvs <- mapM f undefined
>
> let n = (map pvrX pvs) `min` (map pvrX pvs)
>
> undefined
> ---- DM.hs ----
>
> Other info:
>
> c:/ws/main/depot/QA/EDG/EDG_priv/FPF_Dev.br/src $
> c:\ghc\ghc-6.10.0.20081007\bin\ghc-pkg.exe list
> c:/ghc/ghc-6.10.0.20081007\package.conf:
> Cabal-1.5.5, HUnit-1.2.0.0, QuickCheck-1.1.0.0, Win32-2.2.0.0,
> array-0.2.0.0, base-3.0.3.0, base-4.0.0.0, bytestring-0.9.1.4,
> containers-0.2.0.0, directory-1.0.0.2, (dph-base-0.3),
> (dph-par-0.3), (dph-prim-interface-0.3), (dph-prim-par-0.3),
> (dph-prim-seq-0.3), (dph-seq-0.3), filepath-1.1.0.1,
> (ghc-6.10.0.20081007), ghc-prim-0.1.0.0, haddock-2.2.2,
> haskell-src-1.0.1.2, haskell98-1.0.1.0, hpc-0.5.0.2, html-1.0.1.1,
> integer-0.1.0.0, mtl-1.1.0.1, network-2.2.0.0, old-locale-1.0.0.1,
> old-time-1.0.0.1, packedstring-0.1.0.1, parallel-1.0.0.1,
> parsec-2.1.0.1, pretty-1.0.1.0, process-1.0.1.0, random-1.0.0.1,
> regex-base-0.72.0.1, regex-compat-0.71.0.1, regex-posix-0.72.0.2,
> rts-1.0, stm-2.1.1.1, (syb-0.1.0.0), template-haskell-2.3.0.0,
> time-1.1.2.1, xhtml-3000.2.0.1
>
> c:/ws/main/depot/QA/EDG/EDG_priv/FPF_Dev.br/src $
> c:\ghc\ghc-6.10.0.20081007\bin\ghc.exe -v
> Glasgow Haskell Compiler, Version 6.10.0.20081007, for Haskell 98, stage
> 2 booted by GHC version 6.8.3
> Using package config file: C:\ghc\ghc-6.10.0.20081007\package.conf
> hiding package base-3.0.3.0 to avoid conflict with later version
> base-4.0.0.0
> wired-in package ghc-prim mapped to ghc-prim-0.1.0.0
> wired-in package integer mapped to integer-0.1.0.0
> wired-in package base mapped to base-4.0.0.0
> wired-in package rts mapped to rts-1.0
> wired-in package haskell98 mapped to haskell98-1.0.1.0
> wired-in package syb mapped to syb-0.1.0.0
> wired-in package template-haskell mapped to template-haskell-2.3.0.0
> wired-in package dph-seq mapped to dph-seq-0.3
> wired-in package dph-par mapped to dph-par-0.3
> Hsc static flags: -static
> *** Deleting temp files:
> Deleting:
> *** Deleting temp dirs:
> Deleting:
> ghc.exe: no input files
> Usage: For basic information, try the `--help' option.
New description:
The following file (DM.hs) panics GHC 6.10 with this error message:
{{{
c:/ws/main/depot/QA/EDG/EDG_priv/FPF_Dev.br/src $
c:\ghc\ghc-6.10.0.20081007\bin\ghc.exe ~/DM.hs
ghc.exe: panic! (the 'impossible' happened)
(GHC version 6.10.0.20081007 for i386-unknown-mingw32):
TcTyFuns.uMeta: normalisation shouldn't allow x ~ x
Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug
}}}
--Ben
DM.hs:
{{{
{-# LANGUAGE GADTs, TypeFamilies #-}
type family TFn a :: *
data PVR a = PVR {pvrX :: Int} deriving (Eq)
f :: () -> Maybe (TFn a)
f _ = undefined
g :: Maybe ()
g = do
pvs <- mapM f undefined
let n = (map pvrX pvs) `min` (map pvrX pvs)
undefined
}}}
Other info:
{{{
c:/ws/main/depot/QA/EDG/EDG_priv/FPF_Dev.br/src $
c:\ghc\ghc-6.10.0.20081007\bin\ghc-pkg.exe list
c:/ghc/ghc-6.10.0.20081007\package.conf:
Cabal-1.5.5, HUnit-1.2.0.0, QuickCheck-1.1.0.0, Win32-2.2.0.0,
array-0.2.0.0, base-3.0.3.0, base-4.0.0.0, bytestring-0.9.1.4,
containers-0.2.0.0, directory-1.0.0.2, (dph-base-0.3),
(dph-par-0.3), (dph-prim-interface-0.3), (dph-prim-par-0.3),
(dph-prim-seq-0.3), (dph-seq-0.3), filepath-1.1.0.1,
(ghc-6.10.0.20081007), ghc-prim-0.1.0.0, haddock-2.2.2,
haskell-src-1.0.1.2, haskell98-1.0.1.0, hpc-0.5.0.2, html-1.0.1.1,
integer-0.1.0.0, mtl-1.1.0.1, network-2.2.0.0, old-locale-1.0.0.1,
old-time-1.0.0.1, packedstring-0.1.0.1, parallel-1.0.0.1,
parsec-2.1.0.1, pretty-1.0.1.0, process-1.0.1.0, random-1.0.0.1,
regex-base-0.72.0.1, regex-compat-0.71.0.1, regex-posix-0.72.0.2,
rts-1.0, stm-2.1.1.1, (syb-0.1.0.0), template-haskell-2.3.0.0,
time-1.1.2.1, xhtml-3000.2.0.1
c:/ws/main/depot/QA/EDG/EDG_priv/FPF_Dev.br/src $
c:\ghc\ghc-6.10.0.20081007\bin\ghc.exe -v
Glasgow Haskell Compiler, Version 6.10.0.20081007, for Haskell 98, stage
2 booted by GHC version 6.8.3
Using package config file: C:\ghc\ghc-6.10.0.20081007\package.conf
hiding package base-3.0.3.0 to avoid conflict with later version
base-4.0.0.0
wired-in package ghc-prim mapped to ghc-prim-0.1.0.0
wired-in package integer mapped to integer-0.1.0.0
wired-in package base mapped to base-4.0.0.0
wired-in package rts mapped to rts-1.0
wired-in package haskell98 mapped to haskell98-1.0.1.0
wired-in package syb mapped to syb-0.1.0.0
wired-in package template-haskell mapped to template-haskell-2.3.0.0
wired-in package dph-seq mapped to dph-seq-0.3
wired-in package dph-par mapped to dph-par-0.3
Hsc static flags: -static
*** Deleting temp files:
Deleting:
*** Deleting temp dirs:
Deleting:
ghc.exe: no input files
Usage: For basic information, try the `--help' option.
}}}
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/2693#comment:2>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs