{-# 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 typ1 suffix = mkTFunc (typ1, suffix, \ n -> "ListIterator_deRef" <> n, tyf) where tyf _ = let tp1 = pure typ1 in [t| ListIterator $( tp1 ) -> IO $( tp1 ) |] t_listIteratorPred :: Type -> String -> Q Exp t_listIteratorPred typ1 suffix = mkTFunc (typ1, suffix, \ n -> "ListIterator_listIteratorPred" <> n, tyf) where tyf _ = let tp1 = pure typ1 in [t| ListIterator $( tp1 ) -> IO (ListIterator $( tp1 )) |] t_listIteratorSucc :: Type -> String -> Q Exp t_listIteratorSucc typ1 suffix = mkTFunc (typ1, suffix, \ n -> "ListIterator_listIteratorSucc" <> n, tyf) where tyf _ = let tp1 = pure typ1 in [t| ListIterator $( tp1 ) -> IO (ListIterator $( tp1 )) |] t_valid :: Type -> String -> Q Exp t_valid typ1 suffix = mkTFunc (typ1, suffix, \ n -> "ListIterator_valid" <> n, tyf) where tyf _ = let tp1 = pure typ1 in [t| ListIterator $( tp1 ) -> IO CBool |] genListIteratorInstanceFor :: IsCPrimitive -> (Q Type, TemplateParamInfo) -> Q [Dec] genListIteratorInstanceFor isCprim (qtyp1, param1) = do let params = map tpinfoSuffix [param1] let suffix = concatMap (\ x -> "_" ++ tpinfoSuffix x) [param1] callmod_ <- fmap loc_module location let callmod = dot2_ callmod_ typ1 <- qtyp1 f1 <- mkMember "deRef" t_deRef typ1 suffix f2 <- mkMember "listIteratorPred" t_listIteratorPred typ1 suffix f3 <- mkMember "listIteratorSucc" t_listIteratorSucc typ1 suffix f4 <- mkMember "valid" t_valid typ1 suffix addModFinalizer (addForeignSource LangCxx ("\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*)&((static_cast*>(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* r=new ListIterator((static_cast*>(p))->pred());return static_cast(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* r=new ListIterator((static_cast*>(p))->succ());return static_cast(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*>(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*>(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* r=new ListIterator((static_cast*>(p))->pred());return static_cast(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* r=new ListIterator((static_cast*>(p))->succ());return static_cast(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*>(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" ++ let headers = concatMap tpinfoCxxHeaders [param1] f x = renderCMacro (Include x) in concatMap f headers ++ let nss = concatMap tpinfoCxxNamespaces [param1] f x = renderCStmt (UsingNamespace x) in concatMap f nss ++ "ListIterator_instance" ++ (case isCprim of CPrim -> "_s" NonCPrim -> "") ++ "(" ++ intercalate ", " (callmod : params) ++ ")\n")) let lst = [f1, f2, f3, f4] pure [mkInstance [] (AppT (con "IListIterator") typ1) lst]