#4120: Iface type variable out of scope in cast
---------------------------------+------------------------------------------
Reporter: benl | Owner:
Type: bug | Status: new
Priority: normal | Component: Compiler (Type checker)
Version: 6.13 | Keywords:
Os: Unknown/Multiple | Testcase:
Architecture: Unknown/Multiple | Failure: Runtime performance bug
---------------------------------+------------------------------------------
Compiling the following module against vector-0.6 or 0.7:
{{{
module Thing where
import Data.Vector.Unboxed
import Data.Vector.Unboxed.Mutable as MV
thing :: Vector Int
thing = create (MV.new 5)
}}}
Complains about:
{{{
desire:tmp benl$ ghc -O -c -fglasgow-exts Thing.hs -fforce-recomp
/Users/benl/.cabal/lib/vector-0.7/ghc-6.13.20100607/Data/Vector/Unboxed.hi
Declaration for create
Unfolding of Data.Vector.Unboxed.create:
Iface type variable out of scope: s
}}}
Looking in the interface file we have:
{{{
create :: forall a.
Data.Vector.Unboxed.Base.Unbox a =>
(forall s. GHC.ST.ST s (Data.Vector.Unboxed.Base.MVector s a))
-> Data.Vector.Unboxed.Base.Vector a
{- Arity: 2, Strictness: U(SA)C(U(LL)),
Inline: INLINE (sat-args=0),
Unfolding: InlineRule (1, False, False)
(\ @ a
$dUnbox :: Data.Vector.Unboxed.Base.Unbox a
eta :: forall s.
GHC.ST.ST
s
(Data.Vector.Generic.Base.Mutable
Data.Vector.Unboxed.Base.Vector s a)
->
Data.Vector.Generic.new
@ Data.Vector.Unboxed.Base.Vector
@ a
(Data.Vector.Unboxed.Base.$p1Unbox @ a $dUnbox)
(Data.Vector.Generic.New.New
@ Data.Vector.Unboxed.Base.Vector
@ a
eta))
`cast`
(forall a.
Data.Vector.Unboxed.Base.Unbox a =>
GHC.ST.ST s
(Data.Vector.Unboxed.Base.TFCo:R:MutableVector s a)
-> Data.Vector.Unboxed.Base.Vector a) -}
}}}
The variable `s` in the right of the cast is indeed not in scope.
This prevents `create` being inlined into client modules, which kills
performance for benchmarks that create lots of small vectors (like a
version of quickhull in DPH).
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/4120>
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