{-# LANGUAGE TemplateHaskell #-} module OGDF.ListIterator.TH where import Data.Char import Data.List import Data.Monoid import Foreign.C.Types import Foreign.Ptr import Language.Haskell.TH import Language.Haskell.TH.Syntax import FFICXX.Runtime.CodeGen.Cxx import FFICXX.Runtime.TH import OGDF.ListIterator.Template t_deRef :: Type -> String -> Q Exp t_deRef :: Type -> String -> Q Exp t_deRef Type typ1 String suffix = (Type, String, String -> String, Type -> Q Type) -> Q Exp forall types. (types, String, String -> String, types -> Q Type) -> Q Exp mkTFunc (Type typ1, String suffix, \ String n -> String "ListIterator_deRef" String -> String -> String forall a. Semigroup a => a -> a -> a <> String n, Type -> Q Type forall {m :: * -> *} {p}. Quote m => p -> m Type tyf) where tyf :: p -> m Type tyf p _ = let tp1 :: m Type tp1 = Type -> m Type forall a. a -> m a forall (f :: * -> *) a. Applicative f => a -> f a pure Type typ1 in [t| ListIterator $( tp1 ) -> IO $( tp1 ) |] t_listIteratorPred :: Type -> String -> Q Exp t_listIteratorPred :: Type -> String -> Q Exp t_listIteratorPred Type typ1 String suffix = (Type, String, String -> String, Type -> Q Type) -> Q Exp forall types. (types, String, String -> String, types -> Q Type) -> Q Exp mkTFunc (Type typ1, String suffix, \ String n -> String "ListIterator_listIteratorPred" String -> String -> String forall a. Semigroup a => a -> a -> a <> String n, Type -> Q Type forall {m :: * -> *} {p}. Quote m => p -> m Type tyf) where tyf :: p -> m Type tyf p _ = let tp1 :: m Type tp1 = Type -> m Type forall a. a -> m a forall (f :: * -> *) a. Applicative f => a -> f a pure Type typ1 in [t| ListIterator $( tp1 ) -> IO (ListIterator $( tp1 )) |] t_listIteratorSucc :: Type -> String -> Q Exp t_listIteratorSucc :: Type -> String -> Q Exp t_listIteratorSucc Type typ1 String suffix = (Type, String, String -> String, Type -> Q Type) -> Q Exp forall types. (types, String, String -> String, types -> Q Type) -> Q Exp mkTFunc (Type typ1, String suffix, \ String n -> String "ListIterator_listIteratorSucc" String -> String -> String forall a. Semigroup a => a -> a -> a <> String n, Type -> Q Type forall {m :: * -> *} {p}. Quote m => p -> m Type tyf) where tyf :: p -> m Type tyf p _ = let tp1 :: m Type tp1 = Type -> m Type forall a. a -> m a forall (f :: * -> *) a. Applicative f => a -> f a pure Type typ1 in [t| ListIterator $( tp1 ) -> IO (ListIterator $( tp1 )) |] t_valid :: Type -> String -> Q Exp t_valid :: Type -> String -> Q Exp t_valid Type typ1 String suffix = (Type, String, String -> String, Type -> Q Type) -> Q Exp forall types. (types, String, String -> String, types -> Q Type) -> Q Exp mkTFunc (Type typ1, String suffix, \ String n -> String "ListIterator_valid" String -> String -> String forall a. Semigroup a => a -> a -> a <> String n, Type -> Q Type forall {m :: * -> *} {p}. Quote m => p -> m Type tyf) where tyf :: p -> m Type tyf p _ = let tp1 :: m Type tp1 = Type -> m Type forall a. a -> m a forall (f :: * -> *) a. Applicative f => a -> f a pure Type typ1 in [t| ListIterator $( tp1 ) -> IO CBool |] genListIteratorInstanceFor :: IsCPrimitive -> (Q Type, TemplateParamInfo) -> Q [Dec] genListIteratorInstanceFor :: IsCPrimitive -> (Q Type, TemplateParamInfo) -> Q [Dec] genListIteratorInstanceFor IsCPrimitive isCprim (Q Type qtyp1, TemplateParamInfo param1) = do let params :: [String] params = (TemplateParamInfo -> String) -> [TemplateParamInfo] -> [String] forall a b. (a -> b) -> [a] -> [b] map TemplateParamInfo -> String tpinfoSuffix [TemplateParamInfo param1] let suffix :: String suffix = (TemplateParamInfo -> String) -> [TemplateParamInfo] -> String forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b] concatMap (\ TemplateParamInfo x -> String "_" String -> String -> String forall a. [a] -> [a] -> [a] ++ TemplateParamInfo -> String tpinfoSuffix TemplateParamInfo x) [TemplateParamInfo param1] String callmod_ <- (Loc -> String) -> Q Loc -> Q String forall a b. (a -> b) -> Q a -> Q b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap Loc -> String loc_module Q Loc location let callmod :: String callmod = String -> String dot2_ String callmod_ Type typ1 <- Q Type qtyp1 Dec f1 <- String -> (Type -> String -> Q Exp) -> Type -> String -> Q Dec forall types. String -> (types -> String -> Q Exp) -> types -> String -> Q Dec mkMember String "deRef" Type -> String -> Q Exp t_deRef Type typ1 String suffix Dec f2 <- String -> (Type -> String -> Q Exp) -> Type -> String -> Q Dec forall types. String -> (types -> String -> Q Exp) -> types -> String -> Q Dec mkMember String "listIteratorPred" Type -> String -> Q Exp t_listIteratorPred Type typ1 String suffix Dec f3 <- String -> (Type -> String -> Q Exp) -> Type -> String -> Q Dec forall types. String -> (types -> String -> Q Exp) -> types -> String -> Q Dec mkMember String "listIteratorSucc" Type -> String -> Q Exp t_listIteratorSucc Type typ1 String suffix Dec f4 <- String -> (Type -> String -> Q Exp) -> Type -> String -> Q Dec forall types. String -> (types -> String -> Q Exp) -> types -> String -> Q Dec mkMember String "valid" Type -> String -> Q Exp t_valid Type typ1 String suffix Q () -> Q () addModFinalizer (ForeignSrcLang -> String -> Q () addForeignSource ForeignSrcLang LangCxx (String "\n#include \"MacroPatternMatch.h\"\n\n\n#include \"ogdf/basic/List.h\"\n\n\n#define ListIterator_deRef(callmod, tp1) \\\nextern \"C\" {\\\ntp1##_p ListIterator_deRef_##tp1 ( void* p );}\\\ninline tp1##_p ListIterator_deRef_##tp1 ( void* p ) {\\\nreturn from_nonconst_to_nonconst<tp1##_t, tp1>((tp1*)&((static_cast<ListIterator<tp1>*>(p))->operator*()));\\\n}\\\nauto a_##callmod##_ListIterator_deRef_##tp1=ListIterator_deRef_##tp1;\n\n\n#define ListIterator_listIteratorPred(callmod, tp1) \\\nextern \"C\" {\\\nvoid* ListIterator_listIteratorPred_##tp1 ( void* p );}\\\ninline void* ListIterator_listIteratorPred_##tp1 ( void* p ) {\\\nListIterator<tp1>* r=new ListIterator<tp1>((static_cast<ListIterator<tp1>*>(p))->pred());return static_cast<void*>(r);\\\n}\\\nauto a_##callmod##_ListIterator_listIteratorPred_##tp1=ListIterator_listIteratorPred_##tp1;\n\n\n#define ListIterator_listIteratorSucc(callmod, tp1) \\\nextern \"C\" {\\\nvoid* ListIterator_listIteratorSucc_##tp1 ( void* p );}\\\ninline void* ListIterator_listIteratorSucc_##tp1 ( void* p ) {\\\nListIterator<tp1>* r=new ListIterator<tp1>((static_cast<ListIterator<tp1>*>(p))->succ());return static_cast<void*>(r);\\\n}\\\nauto a_##callmod##_ListIterator_listIteratorSucc_##tp1=ListIterator_listIteratorSucc_##tp1;\n\n\n#define ListIterator_valid(callmod, tp1) \\\nextern \"C\" {\\\nbool ListIterator_valid_##tp1 ( void* p );}\\\ninline bool ListIterator_valid_##tp1 ( void* p ) {\\\nreturn (static_cast<ListIterator<tp1>*>(p))->valid();\\\n}\\\nauto a_##callmod##_ListIterator_valid_##tp1=ListIterator_valid_##tp1;\n\n\n#define ListIterator_deRef_s(callmod, tp1) \\\nextern \"C\" {\\\ntp1 ListIterator_deRef_##tp1 ( void* p );}\\\ninline tp1 ListIterator_deRef_##tp1 ( void* p ) {\\\nreturn (static_cast<ListIterator<tp1>*>(p))->operator*();\\\n}\\\nauto a_##callmod##_ListIterator_deRef_##tp1=ListIterator_deRef_##tp1;\n\n\n#define ListIterator_listIteratorPred_s(callmod, tp1) \\\nextern \"C\" {\\\nvoid* ListIterator_listIteratorPred_##tp1 ( void* p );}\\\ninline void* ListIterator_listIteratorPred_##tp1 ( void* p ) {\\\nListIterator<tp1>* r=new ListIterator<tp1>((static_cast<ListIterator<tp1>*>(p))->pred());return static_cast<void*>(r);\\\n}\\\nauto a_##callmod##_ListIterator_listIteratorPred_##tp1=ListIterator_listIteratorPred_##tp1;\n\n\n#define ListIterator_listIteratorSucc_s(callmod, tp1) \\\nextern \"C\" {\\\nvoid* ListIterator_listIteratorSucc_##tp1 ( void* p );}\\\ninline void* ListIterator_listIteratorSucc_##tp1 ( void* p ) {\\\nListIterator<tp1>* r=new ListIterator<tp1>((static_cast<ListIterator<tp1>*>(p))->succ());return static_cast<void*>(r);\\\n}\\\nauto a_##callmod##_ListIterator_listIteratorSucc_##tp1=ListIterator_listIteratorSucc_##tp1;\n\n\n#define ListIterator_valid_s(callmod, tp1) \\\nextern \"C\" {\\\nbool ListIterator_valid_##tp1 ( void* p );}\\\ninline bool ListIterator_valid_##tp1 ( void* p ) {\\\nreturn (static_cast<ListIterator<tp1>*>(p))->valid();\\\n}\\\nauto a_##callmod##_ListIterator_valid_##tp1=ListIterator_valid_##tp1;\n\n\n#define ListIterator_instance(callmod, tp1) \\\nListIterator_deRef(callmod, tp1)\\\nListIterator_listIteratorPred(callmod, tp1)\\\nListIterator_listIteratorSucc(callmod, tp1)\\\nListIterator_valid(callmod, tp1)\n\n\n#define ListIterator_instance_s(callmod, tp1) \\\nListIterator_deRef_s(callmod, tp1)\\\nListIterator_listIteratorPred_s(callmod, tp1)\\\nListIterator_listIteratorSucc_s(callmod, tp1)\\\nListIterator_valid_s(callmod, tp1)\n\n" String -> String -> String forall a. [a] -> [a] -> [a] ++ let headers :: [HeaderName] headers = (TemplateParamInfo -> [HeaderName]) -> [TemplateParamInfo] -> [HeaderName] forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b] concatMap TemplateParamInfo -> [HeaderName] tpinfoCxxHeaders [TemplateParamInfo param1] f :: HeaderName -> String f HeaderName x = CMacro Identity -> String renderCMacro (HeaderName -> CMacro Identity forall (f :: * -> *). HeaderName -> CMacro f Include HeaderName x) in (HeaderName -> String) -> [HeaderName] -> String forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b] concatMap HeaderName -> String f [HeaderName] headers String -> String -> String forall a. [a] -> [a] -> [a] ++ let nss :: [Namespace] nss = (TemplateParamInfo -> [Namespace]) -> [TemplateParamInfo] -> [Namespace] forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b] concatMap TemplateParamInfo -> [Namespace] tpinfoCxxNamespaces [TemplateParamInfo param1] f :: Namespace -> String f Namespace x = CStatement Identity -> String renderCStmt (Namespace -> CStatement Identity forall (f :: * -> *). Namespace -> CStatement f UsingNamespace Namespace x) in (Namespace -> String) -> [Namespace] -> String forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b] concatMap Namespace -> String f [Namespace] nss String -> String -> String forall a. [a] -> [a] -> [a] ++ String "ListIterator_instance" String -> String -> String forall a. [a] -> [a] -> [a] ++ (case IsCPrimitive isCprim of IsCPrimitive CPrim -> String "_s" IsCPrimitive NonCPrim -> String "") String -> String -> String forall a. [a] -> [a] -> [a] ++ String "(" String -> String -> String forall a. [a] -> [a] -> [a] ++ String -> [String] -> String forall a. [a] -> [[a]] -> [a] intercalate String ", " (String callmod String -> [String] -> [String] forall a. a -> [a] -> [a] : [String] params) String -> String -> String forall a. [a] -> [a] -> [a] ++ String ")\n")) let lst :: [Dec] lst = [Dec f1, Dec f2, Dec f3, Dec f4] [Dec] -> Q [Dec] forall a. a -> Q a forall (f :: * -> *) a. Applicative f => a -> f a pure [Cxt -> Type -> [Dec] -> Dec mkInstance [] (Type -> Type -> Type AppT (String -> Type con String "IListIterator") Type typ1) [Dec] lst]