Allow declaration splices inside declaration brackets
I would like to be able to write code like:
{-# LANGUAGE TemplateHaskell #-}
import Language.Haskell.TH
decs :: Q [Dec]
decs = [d| data MyType = MyCon | MyOtherCon
val1 :: MyType
val1 = MyCon
val2 :: MyType
val2 = MyOtherCon
$( do let mkFun v i = [| if $v == i then val1 else val2 |]
[d| fun3 x = $(mkFun [| x |] 3)
fun4 x = $(mkFun [| x |] 4) |] ) |]
but GHC says:
$ ghci decSplices.hs
GHCi, version 7.5.20120420: http://www.haskell.org/ghc/ :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer-gmp ... linking ... done.
Loading package base ... linking ... done.
[1 of 1] Compiling Main ( decSplices.hs, interpreted )
decSplices.hs:15:15:
Declaration splices are not permitted inside declaration brackets
Failed, modules loaded: none.
As far as I can see there is no technical reason why this couldn't work, with a splice within a declaration bracket splitting the declarations into 3. The declarations before the splice would be renamed, typechecked etc first, then those in the splice, and finally those after the splice.
Trac metadata
Trac field | Value |
---|---|
Version | 7.4.1 |
Type | FeatureRequest |
TypeOfFailure | OtherFailure |
Priority | normal |
Resolution | Unresolved |
Component | Template Haskell |
Test case | |
Differential revisions | |
BlockedBy | |
Related | |
Blocking | |
CC | |
Operating system | |
Architecture |