{-# LANGUAGE CPP #-} module TemplateHaskell.Compat.V0208 where import Language.Haskell.TH hiding (conP) import TemplateHaskell.Compat.V0208.Prelude classP :: Name -> [Type] -> Pred #if MIN_VERSION_template_haskell(2,10,0) classP :: Name -> [Type] -> Type classP Name n [Type] tl = (Type -> Type -> Type) -> Type -> [Type] -> Type forall b a. (b -> a -> b) -> b -> [a] -> b forall (t :: * -> *) b a. Foldable t => (b -> a -> b) -> b -> t a -> b foldl Type -> Type -> Type AppT (Name -> Type ConT Name n) [Type] tl #else classP = ClassP #endif instanceD :: Cxt -> Type -> [Dec] -> Dec #if MIN_VERSION_template_haskell(2,11,0) instanceD :: [Type] -> Type -> [Dec] -> Dec instanceD = Maybe Overlap -> [Type] -> Type -> [Dec] -> Dec InstanceD Maybe Overlap forall a. Maybe a Nothing #else instanceD = InstanceD #endif dataD :: Cxt -> Name -> [UnitTyVarBndr] -> [Con] -> [Name] -> Dec #if MIN_VERSION_template_haskell(2,21,0) dataD cxt name varBndrs cons derivingNames = DataD cxt name preparedVarBndrs Nothing cons (pure (DerivClause Nothing (map ConT derivingNames))) where preparedVarBndrs :: [TyVarBndr BndrVis] preparedVarBndrs = fmap (fmap (const BndrReq)) varBndrs #elif MIN_VERSION_template_haskell(2,12,0) dataD :: [Type] -> Name -> [UnitTyVarBndr] -> [Con] -> [Name] -> Dec dataD [Type] cxt Name name [UnitTyVarBndr] varBndrs [Con] cons [Name] derivingNames = [Type] -> Name -> [UnitTyVarBndr] -> Maybe Type -> [Con] -> [DerivClause] -> Dec DataD [Type] cxt Name name [UnitTyVarBndr] varBndrs Maybe Type forall a. Maybe a Nothing [Con] cons (DerivClause -> [DerivClause] forall a. a -> [a] forall (f :: * -> *) a. Applicative f => a -> f a pure (Maybe DerivStrategy -> [Type] -> DerivClause DerivClause Maybe DerivStrategy forall a. Maybe a Nothing ((Name -> Type) -> [Name] -> [Type] forall a b. (a -> b) -> [a] -> [b] map Name -> Type ConT [Name] derivingNames))) #elif MIN_VERSION_template_haskell(2,11,0) dataD cxt name varBndrs cons derivingNames = DataD cxt name varBndrs Nothing cons (map ConT derivingNames) #else dataD cxt name varBndrs cons derivingNames = DataD cxt name varBndrs cons derivingNames #endif notStrict :: Strict #if MIN_VERSION_template_haskell(2,11,0) notStrict :: Strict notStrict = SourceUnpackedness -> SourceStrictness -> Strict Bang SourceUnpackedness NoSourceUnpackedness SourceStrictness NoSourceStrictness #else notStrict = NotStrict #endif tupE :: [Exp] -> Exp #if MIN_VERSION_template_haskell(2,16,0) tupE :: [Exp] -> Exp tupE = \ case [Exp a] -> Exp a [Exp] a -> [Maybe Exp] -> Exp TupE ((Exp -> Maybe Exp) -> [Exp] -> [Maybe Exp] forall a b. (a -> b) -> [a] -> [b] map Exp -> Maybe Exp forall a. a -> Maybe a Just [Exp] a) #else tupE = TupE #endif flaglessPlainTV :: Name -> UnitTyVarBndr #if MIN_VERSION_template_haskell(2,17,0) flaglessPlainTV :: Name -> UnitTyVarBndr flaglessPlainTV Name name = Name -> () -> UnitTyVarBndr forall flag. Name -> flag -> TyVarBndr flag PlainTV Name name () #else flaglessPlainTV = PlainTV #endif specifiedPlainTV :: Name -> SpecificityTyVarBndr #if MIN_VERSION_template_haskell(2,17,0) specifiedPlainTV :: Name -> SpecificityTyVarBndr specifiedPlainTV = (Name -> Specificity -> SpecificityTyVarBndr) -> Specificity -> Name -> SpecificityTyVarBndr forall a b c. (a -> b -> c) -> b -> a -> c flip Name -> Specificity -> SpecificityTyVarBndr forall flag. Name -> flag -> TyVarBndr flag PlainTV Specificity SpecifiedSpec #else specifiedPlainTV = PlainTV #endif #if MIN_VERSION_template_haskell(2,17,0) type SpecificityTyVarBndr = TyVarBndr Specificity #else type SpecificityTyVarBndr = TyVarBndr #endif #if MIN_VERSION_template_haskell(2,17,0) type UnitTyVarBndr = TyVarBndr () #else type UnitTyVarBndr = TyVarBndr #endif doE :: [Stmt] -> Exp #if MIN_VERSION_template_haskell(2,17,0) doE :: [Stmt] -> Exp doE = Maybe ModName -> [Stmt] -> Exp DoE Maybe ModName forall a. Maybe a Nothing #else doE = DoE #endif #if MIN_VERSION_template_haskell(2,17,0) tyVarBndrKind :: TyVarBndr flag -> Maybe Kind tyVarBndrKind :: forall flag. TyVarBndr flag -> Maybe Type tyVarBndrKind = \ case KindedTV Name _ flag _ Type a -> Type -> Maybe Type forall a. a -> Maybe a Just Type a TyVarBndr flag _ -> Maybe Type forall a. Maybe a Nothing #else tyVarBndrKind :: TyVarBndr -> Maybe Kind tyVarBndrKind = \ case KindedTV _ a -> Just a _ -> Nothing #endif #if MIN_VERSION_template_haskell(2,18,0) conP :: Name -> [Pat] -> Pat conP :: Name -> [Pat] -> Pat conP Name name [Pat] pats = Name -> [Type] -> [Pat] -> Pat ConP Name name [] [Pat] pats #else conP :: Name -> [Pat] -> Pat conP = ConP #endif {-# DEPRECATED conp "Use 'conP'" #-} conp :: Name -> [Pat] -> Pat conp :: Name -> [Pat] -> Pat conp = Name -> [Pat] -> Pat conP