{-# LANGUAGE CPP #-} #ifdef TRUSTWORTHY {-# LANGUAGE Trustworthy #-} #endif #ifndef MIN_VERSION_template_haskell #define MIN_VERSION_template_haskell(x,y,z) (defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ >= 706) #endif #ifndef MIN_VERSION_containers #define MIN_VERSION_containers(x,y,z) 1 #endif ----------------------------------------------------------------------------- -- | -- Module : Control.Lens.Internal.TH -- Copyright : (C) 2013-2014 Edward Kmett, 2013 Eric Mertens -- License : BSD-style (see the file LICENSE) -- Maintainer : Edward Kmett -- Stability : experimental -- Portability : non-portable -- ---------------------------------------------------------------------------- module Control.Lens.Internal.TH where import Language.Haskell.TH import qualified Data.Map as Map import qualified Data.Set as Set -- | Compatibility shim for recent changes to template haskell's 'tySynInstD' tySynInstD' :: Name -> [TypeQ] -> TypeQ -> DecQ #if MIN_VERSION_template_haskell(2,9,0) tySynInstD' fam ts r = tySynInstD fam (tySynEqn ts r) #else tySynInstD' = tySynInstD #endif -- | Apply arguments to a type constructor appsT :: TypeQ -> [TypeQ] -> TypeQ appsT = foldl appT -- | Apply arguments to a function appsE1 :: ExpQ -> [ExpQ] -> ExpQ appsE1 = foldl appE -- | Construct a tuple type given a list of types. toTupleT :: [TypeQ] -> TypeQ toTupleT [x] = x toTupleT xs = appsT (tupleT (length xs)) xs -- | Construct a tuple value given a list of expressions. toTupleE :: [ExpQ] -> ExpQ toTupleE [x] = x toTupleE xs = tupE xs -- | Construct a tuple pattern given a list of patterns. toTupleP :: [PatQ] -> PatQ toTupleP [x] = x toTupleP xs = tupP xs -- | Apply arguments to a type constructor. conAppsT :: Name -> [Type] -> Type conAppsT conName = foldl AppT (ConT conName) -- | Return 'Name' contained in a 'TyVarBndr'. bndrName :: TyVarBndr -> Name bndrName (PlainTV n ) = n bndrName (KindedTV n _) = n fromSet :: Ord k => (k -> v) -> Set.Set k -> Map.Map k v #if MIN_VERSION_containers(0,5,0) fromSet = Map.fromSet #else fromSet f x = Map.fromList [ (k,f k) | k <- Set.toList x ] #endif