using [d| class or fun |] and only substituting names?
Is there a way to write something like this? -- packages: template-haskell -- ghc-options: -fth module Main where import Language.Haskell.TH import Control.Monad main = do putStrLn . show =<< runQ [d| class $(mkName "abc") m elc stc3 elc3 st2 el2 st3 el3 -- line 9 | st2 stc3 -> st3, el2 elc3 -> el3 where $(mkName "foo") :: m Int elc Int elc stc3 elc3 a -> m st el st2 el2 st3 el3 a |] |9 col 12| parse error on input `$(' Marc Weber
On Wed, Sep 3, 2008 at 7:11 PM, Marc Weber
Is there a way to write something like this?
No, unfortunately only expressions can be spliced. I'm afraid, You'll have to build the declaration manually.
On Wed, Sep 03, 2008 at 07:33:07PM +0200, Alfonso Acosta wrote:
On Wed, Sep 3, 2008 at 7:11 PM, Marc Weber
wrote: Is there a way to write something like this?
No, unfortunately only expressions can be spliced. I'm afraid, You'll have to build the declaration manually.
Do you think its worth opening a ticket? I feel this is much harder to read.. Maybe I'm still not used to template haskell let names = [ "m", "elc", "stc2", "elc3", "st2", "el2", "st2", "el3" ] [ m, elc, stc2, elc3, st2, el2, st2, el3 ] = map mkName names in classD [] (mkName $ (classElem ng) n) names [funDep [st2,stc3] [st3],FunDep [el2,elc3] [el3]] [sigD (mkName $ (elemName ng) n) (ForallT [a,st,el] [] (appTn (varT m) [ conT elst, varT elc, conT elst, varT elc, varT stc3, varT elc3, varT a] )] Sincerly Marc Weber
--- On Wed, 9/3/08, Marc Weber
Do you think its worth opening a ticket?
There already is a ticket that covers what you want, I believe: http://hackage.haskell.org/trac/ghc/ticket/1476 As I understand it, it won't be included in GHC 6.10, but definitely not dead forever, especially splicing types. Indeed, a small bit of hacking (for my own amusement) on a recent snapshot of 6.9 got it partly working, as the implementation in GHC was already mostly there. rcg
participants (3)
-
Alfonso Acosta -
Marc Weber -
Robert Greayer