2

With Template Haskell I would like to generate records, eg:

data MyRecordA = MyRecordA
  {fooA :: String, barA :: Bool} 

The uppercase A in MyRecordA, fooA, barA and the type Bool of the second field should be variable and specified by the caller of the TH function.

I tried with several variations of:

{-# LANGUAGE TemplateHaskell #-}
module THRecord where
import Language.Haskell.TH

mkRecord :: Name -> Name -> Q [Dec] 
mkRecord name cls = [d|
  data $typeName :: $constName 
    {$fieldFoo, $fieldBar}
  |]
  where
    typeName = conT  $ "MyRecord" <> name
    constrName = RecC $ "MyRecord" <> name
    fieldFoo = sigP name ($clsString)
    fieldBar = sigP name cls
    clsString = conT "String" 

Unfortunately, I get parse errors like

src/THRecord.hs:8:9: error: parse error on input ‘$fieldFoo’

Jogger
  • 1,617
  • 2
  • 12
  • 22

1 Answers1

3

There are several issues here; lets look at them one by one. The splice you have:

[d|
  data $typeName :: $constName 
    {$fieldFoo, $fieldBar}
  |]

is simply not valid; you may only splice entire expressions, types, or declarations, and not parts thereof. You also probably meant data $typeName = $constName but of course the same restriction applies to that, so it still won't work.


The definition

fieldFoo = sigP name ($clsString)

doesn't work because you may not have an splice of a local variable without an intervening quote. This is known as the 'stage restriction'.


fieldFoo = sigP name ($clsString)
fieldBar = sigP name cls

sigP is wrong because it constructs a pattern; you don't need to build any patterns (not sure what you meant here).


typeName = conT  $ "MyRecord" <> name
constrName = RecC $ "MyRecord" <> name
clsString = conT "String" 

All of these are trying to treat a Name as a String. If it isn't clear why that doesn't make sense, perhaps you should familiarize yourself with the basics of Haskell.


Now the solution:

import Data.Monoid
import Language.Haskell.TH
import Language.Haskell.TH.Syntax

defBang = Bang NoSourceUnpackedness NoSourceStrictness
stringType = ConT ''String

mkRecord :: Name -> Name -> Q [Dec] 
mkRecord name cls = (pure.pure)$
  DataD [] typeName [] Nothing [constr] []
  where
    typeName = mkName $ "MyRecord" <> nameBase name
    constr = RecC typeName [(mkName $ "foo" <> nameBase name, defBang, stringType)
                           ,(mkName $ "bar" <> nameBase name, defBang, ConT cls)]

Note that you don't even make use of the Q monad here; not to generate names, nor to reify info about names. Therefore you can actually write a function Name -> Name -> Dec and then applying pure.pure to the result produces a type which can be spliced.

The above is for GHC 8.0.1; the AST of Template Haskell varies significantly between majour releases so it may not compile exactly as is on other versions.

Then e.g.

$(mkRecord (mkName "XYZ") ''Bool)
$(mkRecord (mkName "A") ''Int)

produces

data MyRecordXYZ = MyRecordXYZ {fooXYZ :: String, barXYZ :: Bool}
data MyRecordA = MyRecordA {fooA :: String, barA :: Int}

Finally, here is a solution which doesn't require TH. The family of types you wish to generate can be represented in a first class way:

import GHC.TypeLits

data MyRecord (nm :: Symbol) t = MyRecord { foo :: String, bar :: t }

type MyRecordA = MyRecord "A" Bool
type MyRecordXYZ = MyRecord "XYZ" Int
user2407038
  • 14,400
  • 3
  • 29
  • 42
  • 1
    I specially like the solution without TH! – Jogger Dec 26 '17 at 17:55
  • Unfortunately the nice TH-free solution has a little quirk: It doesn't generate different names for the data constructor. It generates always *MyRecord* and not *MyRecordA* and *MyRecordXYZ* – Jogger Dec 26 '17 at 18:06
  • @Jogger Indeed, but that doesn't really cost you anything. You can still restrict the type of the constructor to any name, e.g. `MyRecord :: String -> t -> MyRecord "X" t`. With `-XTypeApplications` you can even write ` MyRecord @"X"` – user2407038 Dec 26 '17 at 18:49