{-# LANGUAGE TemplateHaskell #-} module STD.SharedPtr.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 STD.SharedPtr.Template t_newSharedPtr0 :: Type -> String -> Q Exp t_newSharedPtr0 typ1 suffix = mkTFunc (typ1, suffix, \ n -> "SharedPtr_newSharedPtr0" <> n, tyf) where tyf _ = let tp1 = pure typ1 in [t| IO (SharedPtr $( tp1 )) |] t_newSharedPtr :: Type -> String -> Q Exp t_newSharedPtr typ1 suffix = mkTFunc (typ1, suffix, \ n -> "SharedPtr_new" <> n, tyf) where tyf _ = let tp1 = pure typ1 in [t| $( tp1 ) -> IO (SharedPtr $( tp1 )) |] t_get :: Type -> String -> Q Exp t_get typ1 suffix = mkTFunc (typ1, suffix, \ n -> "SharedPtr_get" <> n, tyf) where tyf _ = let tp1 = pure typ1 in [t| SharedPtr $( tp1 ) -> IO $( tp1 ) |] t_reset :: Type -> String -> Q Exp t_reset typ1 suffix = mkTFunc (typ1, suffix, \ n -> "SharedPtr_reset" <> n, tyf) where tyf _ = let tp1 = pure typ1 in [t| SharedPtr $( tp1 ) -> IO () |] t_use_count :: Type -> String -> Q Exp t_use_count typ1 suffix = mkTFunc (typ1, suffix, \ n -> "SharedPtr_use_count" <> n, tyf) where tyf _ = let tp1 = pure typ1 in [t| SharedPtr $( tp1 ) -> IO CInt |] t_deleteSharedPtr :: Type -> String -> Q Exp t_deleteSharedPtr typ1 suffix = mkTFunc (typ1, suffix, \ n -> "SharedPtr_delete" <> n, tyf) where tyf _ = let tp1 = pure typ1 in [t| SharedPtr $( tp1 ) -> IO () |] genSharedPtrInstanceFor :: IsCPrimitive -> (Q Type, TemplateParamInfo) -> Q [Dec] genSharedPtrInstanceFor 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 <- mkNew "newSharedPtr0" t_newSharedPtr0 typ1 suffix f2 <- mkNew "newSharedPtr" t_newSharedPtr typ1 suffix f3 <- mkMember "get" t_get typ1 suffix f4 <- mkMember "reset" t_reset typ1 suffix f5 <- mkMember "use_count" t_use_count typ1 suffix f6 <- mkDelete "deleteSharedPtr" t_deleteSharedPtr typ1 suffix addModFinalizer (addForeignSource LangCxx ("\n#include \"MacroPatternMatch.h\"\n\n\n#include \"memory\"\n\n\n#define SharedPtr_newSharedPtr0(callmod, tp1) \\\nextern \"C\" {\\\nvoid* SharedPtr_newSharedPtr0_##tp1 ( );}\\\ninline void* SharedPtr_newSharedPtr0_##tp1 ( ) {\\\nreturn static_cast(new std::shared_ptr());\\\n}\\\nauto a_##callmod##_SharedPtr_newSharedPtr0_##tp1=SharedPtr_newSharedPtr0_##tp1;\n\n\n#define SharedPtr_new(callmod, tp1) \\\nextern \"C\" {\\\nvoid* SharedPtr_new_##tp1 ( tp1##_p p );}\\\ninline void* SharedPtr_new_##tp1 ( tp1##_p p ) {\\\nreturn static_cast(new std::shared_ptr(from_nonconst_to_nonconst(p)));\\\n}\\\nauto a_##callmod##_SharedPtr_new_##tp1=SharedPtr_new_##tp1;\n\n\n#define SharedPtr_get(callmod, tp1) \\\nextern \"C\" {\\\ntp1##_p SharedPtr_get_##tp1 ( void* p );}\\\ninline tp1##_p SharedPtr_get_##tp1 ( void* p ) {\\\nreturn from_nonconst_to_nonconst((static_cast*>(p))->get());\\\n}\\\nauto a_##callmod##_SharedPtr_get_##tp1=SharedPtr_get_##tp1;\n\n\n#define SharedPtr_reset(callmod, tp1) \\\nextern \"C\" {\\\nvoid SharedPtr_reset_##tp1 ( void* p );}\\\ninline void SharedPtr_reset_##tp1 ( void* p ) {\\\n(static_cast*>(p))->reset();\\\n}\\\nauto a_##callmod##_SharedPtr_reset_##tp1=SharedPtr_reset_##tp1;\n\n\n#define SharedPtr_use_count(callmod, tp1) \\\nextern \"C\" {\\\nint SharedPtr_use_count_##tp1 ( void* p );}\\\ninline int SharedPtr_use_count_##tp1 ( void* p ) {\\\nreturn (static_cast*>(p))->use_count();\\\n}\\\nauto a_##callmod##_SharedPtr_use_count_##tp1=SharedPtr_use_count_##tp1;\n\n\n#define SharedPtr_delete(callmod, tp1) \\\nextern \"C\" {\\\nvoid SharedPtr_delete_##tp1 ( void* p );}\\\ninline void SharedPtr_delete_##tp1 ( void* p ) {\\\ndelete static_cast*>(p);\\\n}\\\nauto a_##callmod##_SharedPtr_delete_##tp1=SharedPtr_delete_##tp1;\n\n\n#define SharedPtr_newSharedPtr0_s(callmod, tp1) \\\nextern \"C\" {\\\nvoid* SharedPtr_newSharedPtr0_##tp1 ( );}\\\ninline void* SharedPtr_newSharedPtr0_##tp1 ( ) {\\\nreturn static_cast(new std::shared_ptr());\\\n}\\\nauto a_##callmod##_SharedPtr_newSharedPtr0_##tp1=SharedPtr_newSharedPtr0_##tp1;\n\n\n#define SharedPtr_new_s(callmod, tp1) \\\nextern \"C\" {\\\nvoid* SharedPtr_new_##tp1 ( tp1 p );}\\\ninline void* SharedPtr_new_##tp1 ( tp1 p ) {\\\nreturn static_cast(new std::shared_ptr(p));\\\n}\\\nauto a_##callmod##_SharedPtr_new_##tp1=SharedPtr_new_##tp1;\n\n\n#define SharedPtr_get_s(callmod, tp1) \\\nextern \"C\" {\\\ntp1 SharedPtr_get_##tp1 ( void* p );}\\\ninline tp1 SharedPtr_get_##tp1 ( void* p ) {\\\nreturn (static_cast*>(p))->get();\\\n}\\\nauto a_##callmod##_SharedPtr_get_##tp1=SharedPtr_get_##tp1;\n\n\n#define SharedPtr_reset_s(callmod, tp1) \\\nextern \"C\" {\\\nvoid SharedPtr_reset_##tp1 ( void* p );}\\\ninline void SharedPtr_reset_##tp1 ( void* p ) {\\\n(static_cast*>(p))->reset();\\\n}\\\nauto a_##callmod##_SharedPtr_reset_##tp1=SharedPtr_reset_##tp1;\n\n\n#define SharedPtr_use_count_s(callmod, tp1) \\\nextern \"C\" {\\\nint SharedPtr_use_count_##tp1 ( void* p );}\\\ninline int SharedPtr_use_count_##tp1 ( void* p ) {\\\nreturn (static_cast*>(p))->use_count();\\\n}\\\nauto a_##callmod##_SharedPtr_use_count_##tp1=SharedPtr_use_count_##tp1;\n\n\n#define SharedPtr_delete_s(callmod, tp1) \\\nextern \"C\" {\\\nvoid SharedPtr_delete_##tp1 ( void* p );}\\\ninline void SharedPtr_delete_##tp1 ( void* p ) {\\\ndelete static_cast*>(p);\\\n}\\\nauto a_##callmod##_SharedPtr_delete_##tp1=SharedPtr_delete_##tp1;\n\n\n#define SharedPtr_instance(callmod, tp1) \\\nSharedPtr_newSharedPtr0(callmod, tp1)\\\nSharedPtr_new(callmod, tp1)\\\nSharedPtr_get(callmod, tp1)\\\nSharedPtr_reset(callmod, tp1)\\\nSharedPtr_use_count(callmod, tp1)\\\nSharedPtr_delete(callmod, tp1)\n\n\n#define SharedPtr_instance_s(callmod, tp1) \\\nSharedPtr_newSharedPtr0_s(callmod, tp1)\\\nSharedPtr_new_s(callmod, tp1)\\\nSharedPtr_get_s(callmod, tp1)\\\nSharedPtr_reset_s(callmod, tp1)\\\nSharedPtr_use_count_s(callmod, tp1)\\\nSharedPtr_delete_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 ++ "SharedPtr_instance" ++ (case isCprim of CPrim -> "_s" NonCPrim -> "") ++ "(" ++ intercalate ", " (callmod : params) ++ ")\n")) let lst = [f1, f2, f3, f4, f5, f6] pure [mkInstance [] (AppT (con "ISharedPtr") typ1) lst]