{- | Arguments and return types. Note that functions for 'Int' and 'Word' are not provided here, as Haskell merely defines that 'Int' is a \"fixed-precision integer type with at least the range [-2^29 .. 2^29-1]\", and 'Word' is an \"unsigned integral type, with the same size as 'Int'\". (As both types are instances of 'Storable', the user may easily define them himself when determined useful.) Note also that on e.g. Linux x86_64, 'Int' \/= 'CInt'. -} module Foreign.CInvoke.Types ( -- * Arguments -- ** Integral types argCShort, argCUShort, argCInt, argCUInt, argCLong, argCULong, argCLLong, argCULLong, argInt8, argInt16, argInt32, argInt64, argWord8, argWord16, argWord32, argWord64, -- ** Floating point types argCFloat, argCDouble, -- ** Various other C types argCSize, argCTime, argCChar, argCSChar, argCUChar, argCWchar, argPtr, argFunPtr, -- ** Strings argString, argByteString, argConstByteString, -- * Return types -- ** Integral types retVoid, retCShort, retCUShort, retCInt, retCUInt, retCLong, retCULong, retCLLong, retCULLong, retInt8, retInt16, retInt32, retInt64, retWord8, retWord16, retWord32, retWord64, -- ** Floating point types retCFloat, retCDouble, -- ** Various other C types retCSize, retCTime, retCChar, retCSChar, retCUChar, retCWchar, retPtr, retFunPtr, -- ** Strings retCString, retString, retByteString, retMallocByteString ) where import Control.Monad import Data.List import Data.Char import Data.Int import Data.Word import Foreign.C.Types import Foreign.Ptr import Foreign.Storable import Foreign.C.String import Foreign.Marshal import qualified Data.ByteString as BS import qualified Data.ByteString.Unsafe as BSU import Foreign.CInvoke.Base argCShort = mkStorableArg :: CShort -> Arg argCUShort = mkStorableArg :: CUShort -> Arg argCInt = mkStorableArg :: CInt -> Arg argCUInt = mkStorableArg :: CUInt -> Arg argCLong = mkStorableArg :: CLong -> Arg argCULong = mkStorableArg :: CULong -> Arg argCLLong = mkStorableArg :: CLLong -> Arg argCULLong = mkStorableArg :: CULLong -> Arg argInt8 = mkStorableArg :: Int8 -> Arg argInt16 = mkStorableArg :: Int16 -> Arg argInt32 = mkStorableArg :: Int32 -> Arg argInt64 = mkStorableArg :: Int64 -> Arg argWord8 = mkStorableArg :: Word8 -> Arg argWord16 = mkStorableArg :: Word16 -> Arg argWord32 = mkStorableArg :: Word32 -> Arg argWord64 = mkStorableArg :: Word64 -> Arg argCFloat = mkStorableArg :: CFloat -> Arg argCDouble = mkStorableArg :: CDouble -> Arg argCSize = mkStorableArg :: CSize -> Arg argCTime = mkStorableArg :: CTime -> Arg argCChar = mkStorableArg :: CChar -> Arg argCSChar = mkStorableArg :: CSChar -> Arg argCUChar = mkStorableArg :: CUChar -> Arg argCWchar = mkStorableArg :: CWchar -> Arg argPtr = mkStorableArg :: Ptr a -> Arg argFunPtr = mkStorableArg :: FunPtr a -> Arg {- | The string argument is passed to C as a char * pointer, which is freed afterwards. The argument should not contain zero-bytes. -} argString :: String -> Arg argString = mkPointerArg newCString free -- | Like 'argString', but for 'ByteString''s. argByteString :: BS.ByteString -> Arg argByteString = mkPointerArg (flip BS.useAsCString return) (const $ return ()) -- | Like 'argByteString', but changing the string from C breaks referential transparency. argConstByteString :: BS.ByteString -> Arg argConstByteString = mkPointerArg (flip BSU.unsafeUseAsCString return) (const $ return ()) retVoid :: RetType () retVoid = RetType (\write -> write 0 nullPtr >> return ()) retCShort = mkStorableRetType :: RetType CShort retCUShort = mkStorableRetType :: RetType CUShort retCInt = mkStorableRetType :: RetType CInt retCUInt = mkStorableRetType :: RetType CUInt retCLong = mkStorableRetType :: RetType CLong retCULong = mkStorableRetType :: RetType CULong retCLLong = mkStorableRetType :: RetType CLLong retCULLong = mkStorableRetType :: RetType CULLong retInt8 = mkStorableRetType :: RetType Int8 retInt16 = mkStorableRetType :: RetType Int16 retInt32 = mkStorableRetType :: RetType Int32 retInt64 = mkStorableRetType :: RetType Int64 retWord8 = mkStorableRetType :: RetType Word8 retWord16 = mkStorableRetType :: RetType Word16 retWord32 = mkStorableRetType :: RetType Word32 retWord64 = mkStorableRetType :: RetType Word64 retCFloat = mkStorableRetType :: RetType CFloat retCDouble = mkStorableRetType :: RetType CDouble retCSize = mkStorableRetType :: RetType CSize retCTime = mkStorableRetType :: RetType CTime retCChar = mkStorableRetType :: RetType CChar retCSChar = mkStorableRetType :: RetType CSChar retCUChar = mkStorableRetType :: RetType CUChar retCWchar = mkStorableRetType :: RetType CWchar retFunPtr :: RetType a -> RetType (FunPtr a) retFunPtr _ = mkStorableRetType retPtr :: RetType a -> RetType (Ptr a) retPtr _ = mkStorableRetType retCString :: RetType CString retCString = retPtr retCChar {- | Peek a 'String' out of the returned char *. The char * is not freed. -} retString :: RetType String retString = withRetType peekCString (retPtr retCChar) {- | Like 'retString', but for 'ByteString''s -} retByteString :: RetType BS.ByteString retByteString = withRetType BS.packCString (retPtr retCChar) {- | Make a 'ByteString' out of the returned char *. The char * will be free(3)ed when the 'ByteString' is garbage collected. -} retMallocByteString :: RetType BS.ByteString retMallocByteString = withRetType BSU.unsafePackMallocCString (retPtr retCChar)