Suppose you're writing some Template Haskell code that transforms record declarations. The first transformation you would want to write is the identity one, right? So let's go over the fields and not change them:
module TH where
import Language.Haskell.TH
import Language.Haskell.TH.Syntax
foo :: DecsQ -> DecsQ
foo = fmap $ map $ \d -> case d of
DataD _ dataName tvbs Nothing [con@(RecC conName fields)] [] ->
DataD [] dataName
tvbs
Nothing
[RecC conName $ map transformField fields]
[]
_ -> d
-- TODO: Write my awesome transformation here
transformField :: VarBangType -> VarBangType
transformField (v, b, t) = (v, b, t)
You try it out in a module with a record type:
{-# LANGUAGE TemplateHaskell #-}
import TH
foo [d| data R = MkR{ x :: Int } |]
So far so good. However, things break if we turn on DuplicateRecordFields
in our program, even though we haven't written transformField
yet (i.e. it is still the identity function):
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE DuplicateRecordFields #-}
import TH
foo [d| data R = MkR{ x :: Int } |]
This program now fails to compile, with the following message:
Use.hs:5:1: error:
Illegal variable name:
$sel:x:MkR
When splicing a TH declaration:
data R_0 = MkR_1 {$sel:x:MkR_2 :: GHC.Types.Int}
Even this super-minimal program fails with a similar error:
{-# LANGUAGE DuplicateRecordFields, TemplateHaskell #-}
$([d| data R = MkR{ x :: Int } |])
There's not much mystery why this happens: as the DuplicateRecordFields
documentation explains, field selectors are mangled to be unique accross all record types, and TH gets these mangled field names.
But how to solve this is not explained on that same page. For now, I am using the following function to unmangle a mangled field name into something that roundtrips accross data declaration splices:
import Data.List.Split
unmangle :: Name -> Name
unmangle (Name occ flavour) = Name occ' flavour
where
occ' = case wordsBy (== ':') (occString occ) of
["$sel", fd, _qual] -> mkOccName fd
_ -> occ
transformField :: VarBangType -> VarBangType
transformField (v, b, t) = (unmangle v, b, t)
This works, but doesn't feel like the right solution, and probably won't survive changes to GHC-internal details of name mangling. Is there a better way to do this?