{-# LANGUAGE TemplateHaskell #-} module OGDF.List.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.List.Template import OGDF.ListIterator.Template t_begin :: Type -> String -> Q Exp t_begin typ1 suffix = mkTFunc (typ1, suffix, \ n -> "List_begin" <> n, tyf) where tyf _ = let tp1 = pure typ1 in [t| List $( tp1 ) -> IO (ListIterator $( tp1 )) |] t_end :: Type -> String -> Q Exp t_end typ1 suffix = mkTFunc (typ1, suffix, \ n -> "List_end" <> n, tyf) where tyf _ = let tp1 = pure typ1 in [t| List $( tp1 ) -> IO (ListIterator $( tp1 )) |] t_pushBack :: Type -> String -> Q Exp t_pushBack typ1 suffix = mkTFunc (typ1, suffix, \ n -> "List_pushBack" <> n, tyf) where tyf _ = let tp1 = pure typ1 in [t| List $( tp1 ) -> $( tp1 ) -> IO (ListIterator $( tp1 )) |] genListInstanceFor :: IsCPrimitive -> (Q Type, TemplateParamInfo) -> Q [Dec] genListInstanceFor 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 "begin" t_begin typ1 suffix f2 <- mkMember "end" t_end typ1 suffix f3 <- mkMember "pushBack" t_pushBack typ1 suffix addModFinalizer (addForeignSource LangCxx ("\n#include \"MacroPatternMatch.h\"\n\n\n#include \"ogdf/basic/List.h\"\n\n\n#define List_begin(callmod, tp1) \\\nextern \"C\" {\\\nvoid* List_begin_##tp1 ( void* p );}\\\ninline void* List_begin_##tp1 ( void* p ) {\\\nListIterator* r=new ListIterator((static_cast*>(p))->begin());return static_cast(r);\\\n}\\\nauto a_##callmod##_List_begin_##tp1=List_begin_##tp1;\n\n\n#define List_end(callmod, tp1) \\\nextern \"C\" {\\\nvoid* List_end_##tp1 ( void* p );}\\\ninline void* List_end_##tp1 ( void* p ) {\\\nListIterator* r=new ListIterator((static_cast*>(p))->end());return static_cast(r);\\\n}\\\nauto a_##callmod##_List_end_##tp1=List_end_##tp1;\n\n\n#define List_pushBack(callmod, tp1) \\\nextern \"C\" {\\\nvoid* List_pushBack_##tp1 ( void* p, tp1##_p x );}\\\ninline void* List_pushBack_##tp1 ( void* p, tp1##_p x ) {\\\nListIterator* r=new ListIterator((static_cast*>(p))->pushBack(*(from_nonconst_to_nonconst(x))));return static_cast(r);\\\n}\\\nauto a_##callmod##_List_pushBack_##tp1=List_pushBack_##tp1;\n\n\n#define List_begin_s(callmod, tp1) \\\nextern \"C\" {\\\nvoid* List_begin_##tp1 ( void* p );}\\\ninline void* List_begin_##tp1 ( void* p ) {\\\nListIterator* r=new ListIterator((static_cast*>(p))->begin());return static_cast(r);\\\n}\\\nauto a_##callmod##_List_begin_##tp1=List_begin_##tp1;\n\n\n#define List_end_s(callmod, tp1) \\\nextern \"C\" {\\\nvoid* List_end_##tp1 ( void* p );}\\\ninline void* List_end_##tp1 ( void* p ) {\\\nListIterator* r=new ListIterator((static_cast*>(p))->end());return static_cast(r);\\\n}\\\nauto a_##callmod##_List_end_##tp1=List_end_##tp1;\n\n\n#define List_pushBack_s(callmod, tp1) \\\nextern \"C\" {\\\nvoid* List_pushBack_##tp1 ( void* p, tp1 x );}\\\ninline void* List_pushBack_##tp1 ( void* p, tp1 x ) {\\\nListIterator* r=new ListIterator((static_cast*>(p))->pushBack(x));return static_cast(r);\\\n}\\\nauto a_##callmod##_List_pushBack_##tp1=List_pushBack_##tp1;\n\n\n#define List_instance(callmod, tp1) \\\nList_begin(callmod, tp1)\\\nList_end(callmod, tp1)\\\nList_pushBack(callmod, tp1)\n\n\n#define List_instance_s(callmod, tp1) \\\nList_begin_s(callmod, tp1)\\\nList_end_s(callmod, tp1)\\\nList_pushBack_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 ++ "List_instance" ++ (case isCprim of CPrim -> "_s" NonCPrim -> "") ++ "(" ++ intercalate ", " (callmod : params) ++ ")\n")) let lst = [f1, f2, f3] pure [mkInstance [] (AppT (con "IList") typ1) lst]