[Template-haskell] using [d| class or fun |] and only substituting names?

Marc Weber marco-oweber at gmx.de
Wed Sep 3 13:11:34 EDT 2008


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


More information about the template-haskell mailing list