-
Notifications
You must be signed in to change notification settings - Fork 41
/
Copy pathForeign.hs
68 lines (57 loc) · 1.99 KB
/
Foreign.hs
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
-- | Utilities for FFI
module Cardano.Foreign (
-- * Sized pointer
SizedPtr (..),
allocaSized,
memcpySized,
memsetSized,
-- * Low-level C functions
c_memcpy,
c_memset,
) where
import Control.Monad (void)
import Data.Proxy (Proxy (..))
import Data.Void (Void)
import Data.Word (Word8)
import Foreign.C.Types (CSize (..))
import Foreign.Marshal.Alloc (allocaBytes)
import Foreign.Ptr (Ptr)
import GHC.TypeLits
-------------------------------------------------------------------------------
-- Sized pointer
-------------------------------------------------------------------------------
-- A pointer which knows the size of underlying memory block
newtype SizedPtr (n :: Nat) = SizedPtr (Ptr Void)
-- | Like 'allocaBytes'.
allocaSized :: forall n b. KnownNat n => (SizedPtr n -> IO b) -> IO b
allocaSized k = allocaBytes size (k . SizedPtr)
where
size :: Int
size = fromInteger (natVal (Proxy @n))
memcpySized :: forall n. KnownNat n => SizedPtr n -> SizedPtr n -> IO ()
memcpySized (SizedPtr dest) (SizedPtr src) = void (c_memcpy dest src size)
where
size :: CSize
size = fromInteger (natVal (Proxy @n))
memsetSized :: forall n. KnownNat n => SizedPtr n -> Word8 -> IO ()
memsetSized (SizedPtr s) c = void (c_memset s (fromIntegral c) size)
where
size :: CSize
size = fromInteger (natVal (Proxy @n))
-------------------------------------------------------------------------------
-- Some C functions
-------------------------------------------------------------------------------
-- | @void *memcpy(void *dest, const void *src, size_t n);@
--
-- Note: this is safe foreign import
foreign import ccall "memcpy"
c_memcpy :: Ptr a -> Ptr a -> CSize -> IO (Ptr ())
-- | @void *memset(void *s, int c, size_t n);@
--
-- Note: for sure zeroing memory use @c_sodium_memzero@.
foreign import ccall "memset"
c_memset :: Ptr a -> Int -> CSize -> IO (Ptr ())