{-# LANGUAGE QuasiQuotes #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE OverloadedStrings #-} module TemplateSpec where import qualified Language.C.Inline.Cpp as C import qualified Language.C.Inline.Context as CC import qualified Language.C.Types as CT import Foreign import Foreign.C import Data.Monoid data CppVector a C.context $ C.cppCtx <> C.cppTypePairs [ ("std::vector" :: CT.CIdentifier, [t|CppVector|]) ] C.include "" C.include "" -- compiles: we can return std::vector* returns_vec_of_int = do [C.block| std::vector* { return ( (std::vector*) NULL); } |] :: IO (Ptr (CppVector CInt)) -- compiles: we can return std::vector* returns_vec_of_signed = do [C.block| std::vector* { return ( (std::vector*) NULL); } |] :: IO (Ptr (CppVector CInt)) -- compiles: we can return std::vector* returns_vec_of_unsigned = do [C.block| std::vector* { return ( (std::vector*) NULL); } |] :: IO (Ptr (CppVector CUInt)) -- compiles: we can return std::vector* returns_vec_of_long_int = do [C.block| std::vector* { return ( (std::vector*) NULL); } |] :: IO (Ptr (CppVector CLong)) -- compiles: we can return std::vector* returns_vec_of_short = do [C.block| std::vector* { return ( (std::vector*) NULL); } |] :: IO (Ptr (CppVector CShort)) -- compiles: we can return std::vector* returns_vec_of_short_int = do [C.block| std::vector* { return ( (std::vector*) NULL); } |] :: IO (Ptr (CppVector CShort)) -- compiles: we can return std::vector* returns_vec_of_unsigned_int = do [C.block| std::vector* { return ( (std::vector*) NULL); } |] :: IO (Ptr (CppVector CUInt)) -- compiles: we can return long* returns_ptr_to_long = do [C.block| long* { return ( (long*) NULL); } |] :: IO (Ptr CLong) -- compiles: we can return unsigned long* returns_ptr_to_unsigned_long = do [C.block| unsigned long* { return ( (unsigned long*) NULL); } |] :: IO (Ptr CULong) -- compiles: we can return std::vector* returns_vec_of_long = do [C.block| std::vector* { return ( (std::vector*) NULL); } |] :: IO (Ptr (CppVector CLong)) -- compiles: we can return std::vector* returns_vec_of_long_long = do [C.block| std::vector* { return ( (std::vector*) NULL); } |] :: IO (Ptr (CppVector CLLong))