#3011: ASSERT failed: file typecheck/TcMType.lhs line 526 t_a32G{tv}
-----------------------------+----------------------------------------------
Reporter: batterseapower | Owner:
Type: bug | Status: new
Priority: normal | Component: Compiler (Type checker)
Version: 6.11 | Severity: normal
Keywords: | Testcase:
Os: Unknown/Multiple | Architecture: Unknown/Multiple
-----------------------------+----------------------------------------------
NB: this is NOT AFAIK a duplicate of the previous ticket about the TcMType
ASSERT failure. It was observed on a recent HEAD (as of 6th February 2009)
while I happened to be using a stage 2 compiler with -DDEBUG on to compile
some code I was working on.
Error is as follows:
{{{
$ ./Setup clean && ./Setup configure --with-
compiler=/Users/mbolingbroke/Programming/Checkouts/ghc.working/ghc/stage2-inplace/ghc
--with-hc-
pkg=/Users/mbolingbroke/Programming/Checkouts/ghc.working/ghc/stage2-inplace
/ghc-pkg --ghc --global && ./Setup build && dist/build/vector-tests
/vector-tests
cleaning...
Configuring vector-tests-0.2...
Preprocessing executables for vector-tests-0.2...
Building vector-tests-0.2...
[1 of 3] Compiling Utilities ( Utilities.hs, dist/build/vector-
tests/vector-tests-tmp/Utilities.o )
WARNING: file simplCore/SimplCore.lhs line 545
Simplifier still going after 4 iterations; bailing out. Size = 1398
[2 of 3] Compiling Properties ( Properties.hs, dist/build/vector-
tests/vector-tests-tmp/Properties.o )
WARNING: file typecheck/TcTyFuns.lhs line 284
(This warning is harmless; for Simon & Manuel)
[Wanted t_a32G{tv} [tau] :: ghc-prim:GHC.Types.[]{(w) tc 317}
~
v{tv a2S9} [sk]]
ghc: panic! (the 'impossible' happened)
(GHC version 6.11.20090204 for i386-apple-darwin):
ASSERT failed! file typecheck/TcMType.lhs line 526 t_a32G{tv}
[tau]
Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug
}}}
Where that code look something like this:
{{{
do { ASSERTM2( do { details <- readMetaTyVar tyvar; return (isFlexi
details) }, ppr tyvar )
; traceTc (text "writeMetaTyVar" <+> ppr tyvar <+> text ":=" <+>
ppr ty)
; writeMutVar (metaTvRef tyvar) (Indirect ty) }
}}}
Full program is attached.
Actually, the program has a type error (as rerunning with a non -DDEBUG
build showed):
{{{
Properties.hs:78:25:
Could not deduce (Data.Vector.Unboxed.IVector [] a)
from the context (Eq a,
Ord a,
Eq (v a),
Ord (v a),
Show a,
Arbitrary a,
Model a a,
Show (v a),
Arbitrary (v a),
Model (v a) [a],
Data.Vector.Unboxed.IVector v a,
Show (v Bool),
Arbitrary (v Bool),
Model (v Bool) [Bool],
Data.Vector.Unboxed.IVector v Bool)
arising from a use of `Data.Vector.Unboxed.length'
at Properties.hs:78:25-32
Possible fix:
add (Data.Vector.Unboxed.IVector [] a) to the context of
the type signature for `testVersusLists'
or add an instance declaration for
(Data.Vector.Unboxed.IVector [] a)
In the first argument of `eq1', namely
`(Data.Vector.Unboxed.length :: v a -> Int)'
In the expression:
(Data.Vector.Unboxed.length :: v a -> Int) `eq1` length
In the definition of `prop_length':
prop_length = (Data.Vector.Unboxed.length :: v a -> Int)
`eq1`
length
Properties.hs:83:25:
No instance for (Data.Vector.Unboxed.IVector [] Bool)
arising from a use of `Data.Vector.Unboxed.and'
at Properties.hs:83:25-29
Possible fix:
add an instance declaration for
(Data.Vector.Unboxed.IVector [] Bool)
In the first argument of `eq1', namely
`(Data.Vector.Unboxed.and :: v Bool -> Bool)'
In the expression:
(Data.Vector.Unboxed.and :: v Bool -> Bool) `eq1` and
In the definition of `prop_and':
prop_and = (Data.Vector.Unboxed.and :: v Bool -> Bool) `eq1` and
Properties.hs:95:24:
Could not deduce (Eq ([a] -> [a]))
from the context (Eq a,
Ord a,
Eq (v a),
Ord (v a),
Show a,
Arbitrary a,
Model a a,
Show (v a),
Arbitrary (v a),
Model (v a) [a],
Data.Vector.Unboxed.IVector v a,
Show (v Bool),
Arbitrary (v Bool),
Model (v Bool) [Bool],
Data.Vector.Unboxed.IVector v Bool)
arising from a use of `eq2' at Properties.hs:95:24-86
Possible fix:
add (Eq ([a] -> [a])) to the context of
the type signature for `testVersusLists'
or add an instance declaration for (Eq ([a] -> [a]))
In the expression:
(Data.Vector.Unboxed.zipWith :: (a -> a -> a) -> v a -> v a -> v
a)
`eq2`
zipWith
In the definition of `prop_zipWith':
prop_zipWith = (Data.Vector.Unboxed.zipWith ::
(a -> a -> a) -> v a -> v a -> v a)
`eq2`
zipWith
In the definition of `testVersusLists':
testVersusLists _ = [testGroup "Prelude" prelude_tests,
testGroup "Data.List" data_list_tests,
testGroup "Extras" extra_tests]
where
prelude_tests = [testProperty "length"
prop_length, ....]
prop_length = (Data.Vector.Unboxed.length ::
v a -> Int)
`eq1`
length
prop_null = (Data.Vector.Unboxed.null :: v a
-> Bool) `eq1` null
prop_and = (Data.Vector.Unboxed.and :: v
Bool -> Bool) `eq1` and
....
Properties.hs:114:25:
Couldn't match expected type `v' against inferred type `[]'
`v' is a rigid type variable bound by
the type signature for `testVersusLists' at Properties.hs:19:28
In the first argument of `eq2', namely
`(enumFromTo :: a -> a -> v a)'
In the expression: (enumFromTo :: a -> a -> v a) `eq2` enumFromTo
In the definition of `prop_enumFromTo':
prop_enumFromTo = (enumFromTo :: a -> a -> v a) `eq2` enumFromTo
Properties.hs:115:76:
Could not deduce (Enum a)
from the context (Eq a,
Ord a,
Eq (v a),
Ord (v a),
Show a,
Arbitrary a,
Model a a,
Show (v a),
Arbitrary (v a),
Model (v a) [a],
Data.Vector.Unboxed.IVector v a,
Show (v Bool),
Arbitrary (v Bool),
Model (v Bool) [Bool],
Data.Vector.Unboxed.IVector v Bool)
arising from a use of `enumFromThenTo' at Properties.hs:115:76-89
Possible fix:
add (Enum a) to the context of
the type signature for `testVersusLists'
In the second argument of `eq3', namely `enumFromThenTo'
In the expression:
(enumFromThenTo :: a -> a -> a -> v a) `eq3` enumFromThenTo
In the definition of `prop_enumFromThenTo':
prop_enumFromThenTo = (enumFromThenTo :: a -> a -> a -> v a)
`eq3`
enumFromThenTo
Properties.hs:176:16:
Could not deduce (Model [a] [a])
from the context (Eq a,
Ord a,
Eq (v a),
Ord (v a),
Show a,
Arbitrary a,
Model a a,
Show (v a),
Arbitrary (v a),
Model (v a) [a],
Data.Vector.Unboxed.IVector v a,
Show (v Bool),
Arbitrary (v Bool),
Model (v Bool) [Bool],
Data.Vector.Unboxed.IVector v Bool)
arising from a use of `eq2' at Properties.hs:176:16-71
Possible fix:
add (Model [a] [a]) to the context of
the type signature for `testVersusLists'
or add an instance declaration for (Model [a] [a])
In the expression:
(Data.Vector.Unboxed.snoc :: v a -> a -> v a) `eq2` snoc
In the definition of `prop_snoc':
prop_snoc = (Data.Vector.Unboxed.snoc :: v a -> a -> v a)
`eq2`
snoc
In the definition of `testVersusLists':
testVersusLists _ = [testGroup "Prelude" prelude_tests,
testGroup "Data.List" data_list_tests,
testGroup "Extras" extra_tests]
where
prelude_tests = [testProperty "length"
prop_length, ....]
prop_length = (Data.Vector.Unboxed.length ::
v a -> Int)
`eq1`
length
prop_null = (Data.Vector.Unboxed.null :: v a
-> Bool) `eq1` null
prop_and = (Data.Vector.Unboxed.and :: v
Bool -> Bool) `eq1` and
....
}}}
But we probably still shouldn't get the ASSERT.
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/3011>
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