#5854: TH: INLINABLE pragma support (patch)
--------------------------------+-------------------------------------------
Reporter: mikhail.vorozhtsov | Owner:
Type: feature request | Status: new
Priority: normal | Component: Template Haskell
Version: 7.4.1 | Keywords:
Os: Unknown/Multiple | Architecture: Unknown/Multiple
Failure: None/Unknown | Testcase:
Blockedby: | Blocking:
Related: |
--------------------------------+-------------------------------------------
I needed it for my [https://github.com/mvv/data-dword data-dword] library,
so here it is:
{{{
GHCi, version 7.5.20120206: http://www.haskell.org/ghc/ :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer-gmp ... linking ... done.
Loading package base ... linking ... done.
λ> import Language.Haskell.TH
λ> (mapM_ print =<<) $ runQ [d| f1 = id; {-# NOINLINE f1 #-}; f2 = id; {-#
INLINE f2 #-}; f3 = id; {-# INLINABLE f3 #-} |]
Loading package array-0.3.0.3 ... linking ... done.
Loading package deepseq-1.2.0.1 ... linking ... done.
Loading package containers-0.4.2.0 ... linking ... done.
Loading package pretty-1.1.1.0 ... linking ... done.
Loading package template-haskell ... linking ... done.
ValD (VarP f1_2) (NormalB (VarE GHC.Base.id)) []
PragmaD (InlineP f1_2 (InlineSpec NoInline False Nothing))
ValD (VarP f2_1) (NormalB (VarE GHC.Base.id)) []
PragmaD (InlineP f2_1 (InlineSpec Inline False Nothing))
ValD (VarP f3_0) (NormalB (VarE GHC.Base.id)) []
PragmaD (InlineP f3_0 (InlineSpec Inlinable False Nothing))
}}}
The other way around:
{{{
{-# LANGUAGE UnicodeSyntax #-}
module TH where
import Language.Haskell.TH
noInlineP ∷ Name → DecsQ
noInlineP n = fmap return $ pragInlD n $ inlineSpecNoPhase NoInline False
inlineP ∷ Name → DecsQ
inlineP n = fmap return $ pragInlD n $ inlineSpecNoPhase Inline False
inlinableP ∷ Name → DecsQ
inlinableP n = fmap return $ pragInlD n $ inlineSpecNoPhase Inlinable
False
}}}
{{{
{-# LANGUAGE UnicodeSyntax #-}
{-# LANGUAGE TemplateHaskell #-}
import TH
f1, f2, f3 ∷ α → α
f1 = id
f2 = id
f3 = id
$(noInlineP 'f1)
$(inlineP 'f2)
$(inlinableP 'f3)
main = return ()
}}}
{{{
$ ghc-stage2 -ddump-splices -fforce-recomp TH.hs Main.hs
[1 of 2] Compiling TH ( TH.hs, TH.o )
[2 of 2] Compiling Main ( Main.hs, Main.o )
Loading package ghc-prim ... linking ... done.
Loading package integer-gmp ... linking ... done.
Loading package base ... linking ... done.
Loading package pretty-1.1.1.0 ... linking ... done.
Loading package array-0.3.0.3 ... linking ... done.
Loading package deepseq-1.2.0.1 ... linking ... done.
Loading package containers-0.4.2.0 ... linking ... done.
Loading package template-haskell ... linking ... done.
Main.hs:1:1: Splicing declarations
noInlineP 'f1
======>
Main.hs:11:3-15
{-# NOINLINE f1 #-}
Main.hs:1:1: Splicing declarations
inlineP 'f2
======>
Main.hs:12:3-13
{-# INLINE f2 #-}
Main.hs:1:1: Splicing declarations
inlinableP 'f3
======>
Main.hs:13:3-16
{-# INLINABLE[ALWAYS] f3 #-}
Linking Main ...
}}}
Please review the patches.
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/5854>
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