{-# LANGUAGE UndecidableInstances, FlexibleInstances, MultiParamTypeClasses, TemplateHaskell, QuasiQuotes #-} module Data.TrieMap.Regular.TH where import Data.TrieMap.Regular.Class import Data.TrieMap.TrieKey import Language.Haskell.TH deriveM :: Q [Dec] -> Q [Dec] deriveM decs = do iT@(InstanceD cxt inst _:_) <- decs let myDecs = zipWith (\ m t -> ValD (VarP m) (NormalB (VarE t)) []) ['emptyM, 'nullM, 'lookupM, 'lookupIxM, 'assocAtM, 'alterM, 'alterLookupM, 'traverseWithKeyM, 'foldWithKeyM, 'foldlWithKeyM, 'mapEitherM, 'splitLookupM, 'unionM, 'isectM, 'diffM, 'extractM, 'isSubmapM, 'fromListM, 'fromAscListM, 'fromDistAscListM] ['emptyT, 'nullT, 'lookupT, 'lookupIxT, 'assocAtT, 'alterT, 'alterLookupT, 'traverseWithKeyT, 'foldWithKeyT, 'foldlWithKeyT, 'mapEitherT, 'splitLookupT, 'unionT, 'isectT, 'diffT, 'extractT, 'isSubmapT, 'fromListT, 'fromAscListT, 'fromDistAscListT] k <- mkVar "k" let triekey = ConT ''TrieKey let triemap = ConT ''TrieMap let ordT = ConT ''Ord return [InstanceD cxt inst myDecs] mkVar :: String -> TypeQ mkVar x = varT =<< newName x