#5463: SPECIALISE pragmas generated from Template Haskell are ignored
---------------------------------+------------------------------------------
Reporter: NickSmallbone | Owner:
Type: bug | Status: new
Priority: normal | Component: Template Haskell
Version: 7.2.1 | Keywords:
Testcase: | Blockedby:
Os: Unknown/Multiple | Blocking:
Architecture: Unknown/Multiple | Failure: None/Unknown
---------------------------------+------------------------------------------
Hi,
I have the following program which contains a SPECIALISE pragma:
{{{
module Test(threeList) where
{-# NOINLINE three #-}
three :: Monad m => m Int
three = return 3
{-# SPECIALISE three :: [Int] #-}
threeList :: [Int]
threeList = three
}}}
The specialisation works and -ddump-simpl gives me the following:
{{{
a :: Int
[GblId, Caf=NoCafRefs, Str=DmdType m]
a = I# 3
threeList [InlPrag=NOINLINE] :: [Int]
[GblId, Caf=NoCafRefs, Str=DmdType]
threeList = : @ Int a ([] @ Int)
}}}
Suppose now I alter my program so that it uses Template Haskell to
generate the SPECIALISE pragma:
{{{
{-# LANGUAGE TemplateHaskell #-}
module TestTH(threeList) where
import TH
{-# NOINLINE three #-}
three :: Monad m => m Int
three = return 3
$(specialise 'three)
threeList :: [Int]
threeList = three
{-# LANGUAGE TemplateHaskell #-}
module TH where
import Language.Haskell.TH
specialise :: Name -> DecsQ
specialise x = do
listInt <- [t| [Int] |]
return [ PragmaD (SpecialiseP x listInt Nothing) ]
}}}
The specialisation should work just as before. However, if I compile with
-ddump-splices -ddump-simpl, I see that the correct pragma was spliced in
but no specialisation happened and GHC generated icky code:
{{{
TestTH.hs:1:1: Splicing declarations
specialise 'three
======>
TestTH.hs:9:3-19
{-# SPECIALIZE three :: [Int] #-}
==================== Tidy Core ====================
lvl :: Int
[GblId, Caf=NoCafRefs, Str=DmdType m]
lvl = I# 3
three [InlPrag=NOINLINE] :: forall (m :: * -> *). Monad m => m Int
[GblId, Arity=1, Caf=NoCafRefs, Str=DmdType U(AASA)]
three =
\ (@ m::* -> *) ($dMonad :: Monad m) ->
return @ m $dMonad @ Int lvl
threeList :: [Int]
[GblId,
Str=DmdType,
Unf=Unf{Src=<vanilla>, TopLvl=True, Arity=0, Value=False,
ConLike=False, Cheap=False, Expandable=True,
Guidance=IF_ARGS [] 2 0}]
threeList = three @ [] $fMonad[]
}}}
This happens on at least GHC 7.0.4 and 7.2.1.
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/5463>
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