[Haskell-cafe] Problem with TemplateHaskell
Magicloud Magiclouds
magicloud.magiclouds at gmail.com
Wed Nov 2 08:42:51 CET 2011
On Tue, Nov 1, 2011 at 5:42 PM, Magicloud Magiclouds
<magicloud.magiclouds at gmail.com> wrote:
> Hi,
> I have code as following, to make a toDocument function (using
> Data.Bsin.=:) for a data structure.
>
> bson :: DecsQ -> DecsQ
> bson decsq = do
> decs <- decsq
> let datad = head decs
> DataD _ _ _ cons _ = datad
> to = mkName "toDocument"
> from = mkName "fromDocument"
> fund <- mapM (\con ->
> case con of
> RecC n types -> do
> let nvs = map (\(nv, _, _) ->
> nv
> ) types
> funD to [clause [conP n $ map varP nvs]
> (normalB $ listE $ map (\nv ->
> infixE (Just $
> litE $ stringL $ show nv)
> (varE $
> mkName "=:")
> $ Just $
> appE (varE $ mkName "val")
>
> $ varE nv
> ) nvs) []]
> ) cons
> return (datad : fund)
>
> Testing code is as:
>
> data T = T { a :: Int
> , b :: Char }
>
> *TH> runQ (bson [d|data T = T {a :: Int, b :: Char}|])
>
> [DataD [] T_0 [] [RecC T_1 [(a_2,NotStrict,ConT
> GHC.Types.Int),(b_3,NotStrict,ConT GHC.Types.Char)]] [],FunD
> toDocument [Clause [ConP T_1 [VarP a_2,VarP b_3]] (NormalB (ListE
> [InfixE (Just (LitE (StringL "a_2"))) (VarE =:) (Just (AppE (VarE val)
> (VarE a_2))),InfixE (Just (LitE (StringL "b_3"))) (VarE =:) (Just
> (AppE (VarE val) (VarE b_3)))])) []]]
>
> So you see that, it changed the name from T/a/b to T_0/T_1/a_2/b_3.
> Why is that? I did not have code to modify original data declaration.
> --
> 竹密岂妨流水过
> 山高哪阻野云飞
>
Here is the code it actually generated:
test.hs:1:1: Splicing declarations
bson [d| data T = T {a :: Int, b :: String} |]
======>
test.hs:(7,3)-(8,38)
data T_a1XY = T_a1XZ {a_a1Y0 :: Int, b_a1Y1 :: String}
toName (T_a1XZ a_a1Y0 b_a1Y1)
= [("a_1627397516" =: a_a1Y0), ("b_1627397517" =: b_a1Y1)]
How to avoid the name changing?
--
竹密岂妨流水过
山高哪阻野云飞
More information about the Haskell-Cafe
mailing list