#5290: Add UNPACK support to Template Haskell
-----------------------------------+----------------------------------------
Reporter: mikhail.vorozhtsov | Owner:
Type: feature request | Status: new
Priority: normal | Component: Template Haskell
Version: 7.1 | Keywords:
Testcase: | Blockedby:
Os: Unknown/Multiple | Blocking:
Architecture: Unknown/Multiple | Failure: None/Unknown
-----------------------------------+----------------------------------------
I've just hacked it in:
{{{
$ ghci -XTemplateHaskell
GHCi, version 7.1.20110630: http://www.haskell.org/ghc/ :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer-gmp ... linking ... done.
Loading package base ... linking ... done.
Loading package ffi-1.0 ... linking ... done.
λ> import Language.Haskell.TH
λ> runQ [d| data T = T {-# UNPACK #-} !Int |]
Loading package array-0.3.0.2 ... linking ... done.
Loading package containers-0.4.0.0 ... linking ... done.
Loading package pretty-1.0.2.0 ... linking ... done.
Loading package template-haskell ... linking ... done.
[DataD [] T [] [NormalC T [(Unpacked,ConT GHC.Types.Int)]] []]
λ>
}}}
TH.hs:
{{{
{-# LANGUAGE TemplateHaskell #-}
module TH where
import Language.Haskell.TH
d :: Q [Dec]
d = return [DataD [] n [] [NormalC n [(Unpacked,ConT ''Int)]] []]
where n = mkName "T"
}}}
Main.hs:
{{{
{-# LANGUAGE TemplateHaskell #-}
import TH
$(d)
instance Show T where
show (T i) = show i
main = putStrLn $ show (T 10)
}}}
Compiling and running:
{{{
$ ghc -ddump-splices -fforce-recomp 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 ffi-1.0 ... linking ... done.
Loading package pretty-1.0.2.0 ... linking ... done.
Loading package array-0.3.0.2 ... linking ... done.
Loading package containers-0.4.0.0 ... linking ... done.
Loading package template-haskell ... linking ... done.
Main.hs:1:1: Splicing declarations
d
======>
Main.hs:5:3
data T = T {-# UNPACK #-} !Int
Linking Main ...
$ ./Main
10
}}}
Please consider merging.
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/5290>
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