0

I'd like to parameterize the template so that the user could give a list Name's defining methods.

The following example tries to be minimal. There is a data D1 that contains fields, unknown in advance (to the template). Users wants to derive an instance that uses some of the fields and thus, it has to be told by the user next to declaring the data structure. The data structures are similar, for which we want to derive instances: however, the number of fields can vary.

{-# LANGUAGE TemplateHaskell #-}

module Main where

import Language.Haskell.TH
import Data.List (intercalate)

data D1 = D1 
  { f1 :: Int
  , f2 :: String
  , f3 :: Double
  } deriving (Show, Eq)

class Show2 a where
  show2 :: a -> String

{-
instance Show2 D1 where
  show2 d1 = "1: " ++ show (f1 d1) ++ " and 2: " ++ show (f3 d1)
 -}

tpl1 :: Name -> Q [Dec]
tpl1 nm = 
  [d|
    instance Show2 $(conT nm) where
      show2 d1 = "1: " ++ show (f1 d1) ++ " and 2: " ++ show (f3 d1)
   |]


tpl2 :: Name -> [Name] -> Q [Dec]
tpl2 nm fnms = do
  -- let showName d n = show $(varE n) d  -- stage restriction
  -- let showGo1 d n = [| show $(showName n) d |]  -- stage error 
  -- UPDATED based on a given hint:
  let nmFs = return $ ListE (map VarE fnms) :: Q Exp -- compiles, but [Int, Double] is a problem
      valF f d = AppE (VarE f) (VarE d) :: Exp
      anmFs2 f d = return $ AppE (VarE 'GHC.Show.show) (valF f d ) :: Q Exp -- compiles and works with head
      anmFs3 d f = AppE (VarE 'GHC.Show.show) (valF f d ) :: Exp 
      lstF d = return $ ListE (map (anmFs3 d) fnms)  :: Q Exp -- UPDATE ends
  [d|
    instance Show2 $(conT nm) where
      -- UPDATED based on a given hint:
      show2 d = intercalate ", " $(lstF 'd) 
      -- show2 d = $(anmFs2 (head fnms) 'd) -- compiles and works, but only head here
      -- show2 d = intercalate ", " (map (\n -> show ( n d ) ) $(nmFs) ) -- compiles, [Int, Double] is a problem
      -- UPDATE ends
      -- show2 d = intercalate ", " (map (\n -> show ( $(varE n) d) ) fnms )     -- stage error
      -- show2 d = intercalate ", " (map ( $(showName d) ) fnms ) -- showName in brackets in other module -> stage error
      -- show2 d = intercalate ", " (map ( $(showGo1 d) ) fnms ) -- showName in brackets in other module -> stage error
   |]

-- wishing to use, after data decl D1, like 
-- $(tpl2 ''D1 ['f1, 'f3])

main = do
 let d = D1 1 "hmm" 2.0
 -- putStrLn $ show2 d
 putStrLn $ "hmm"

The template could be written by using the instance or clause shown below and the combinators given in the th-lib. However, it feels a bit tedious and by using splices and brackets it would be much nicer.

So, the question is how to write the show2 when user want to tell the fields? (Is the only option to use low-level facilities?)

-- ghci:
-- pure []; $(tpl1 ''D1)
-- <interactive>:12:1-7: Splicing declarations pure [] ======>
-- <interactive>:12:12-20: Splicing declarations
--  tpl1 ''D1
--   ======>
--   instance Show2 D1 where
--     show2 d1_a5yR
--       = ("1: " ++ ((show (f1 d1_a5yR)) 
--       ++ (" and 2: " ++ (show (f3 d1_a5yR)))))
-- and
-- $(tpl1 ''D1 >>= stringE . show)
-- gives a representation mimickable with combinators. 
-- [InstanceD Nothing [] (AppT (ConT Main.Show2) (ConT Main.D1)) 
-- [FunD
--   Main.show2 
--     [Clause [VarP d1_6989586621679033595] 
--      (NormalB (InfixE (Just (LitE (StringL \"1: \"))) (VarE     GHC.Base.++) 
--       (Just (InfixE (Just (AppE (VarE GHC.Show.show) 
--        (AppE (VarE Main.f1) (VarE d1_6989586621679033595)))) (VarE
--        GHC.Base.++) (Just (InfixE (Just (LitE (StringL \" and 2: \"))) (VarE
--        GHC.Base.++) (Just (AppE (VarE GHC.Show.show) (AppE (VarE     Main.f3) (VarE
--        d1_6989586621679033595)))))))
--       ))
--      ) 
--      []
--     ]
-- ]
-- ]
--
Gspia
  • 809
  • 6
  • 15
  • The type of `varE n` is `Q Exp`. `Q` is a monad so you can write `varE n >>= (_ :: Exp -> Q a) :: Q a`. Even simpler, use `VarE` instead of `varE`. – user2407038 Feb 05 '17 at 20:41
  • Thanks, it wasn't that easy with VarE (to me) but I got it compiling and almost doing whats required and can go fwd now: see the updated question (its formulation is a bit awkward in the updated form). If you make an answer from your hint I'm willing to accept it. I didn't get (yet) your varE n >>= -hint but I'll try that one too later. – Gspia Feb 06 '17 at 05:00
  • You can write `$(lstF 'd)` as `$(listE $ map (\fn -> [| show ($(varE fn) d) |] ) fnms)` which has nested quotes, which often leads to nearly incomprehensible errors - it avoids using 'low level' things though. You can also write it as `return $ ListE $ map (\fn -> AppE (VarE 'show) (AppE (VarE fn) (VarE 'd))) fnms`, which is only slightly larger but has no quotes. I'm not sure what you're asking, as it seems `tpl2` already does what you want (i.e. "when user want to tell the fields" - the function takes a list of names - this is 'specified by the user') – user2407038 Feb 06 '17 at 08:07
  • Thanks again for clarification and yes, now it does what I was asking for with your help (without stopping to some minor details). The main point was to be able to read "the fields". So if you put something as an answer, I'll definitely accept it. – Gspia Feb 06 '17 at 16:03

0 Answers0