summaryrefslogtreecommitdiff
path: root/src
diff options
context:
space:
mode:
authorJames Crayne <jim.crayne@gmail.com>2019-10-08 01:19:09 +0000
committerJames Crayne <jim.crayne@gmail.com>2019-10-08 01:19:09 +0000
commit884a34d3dbea2a8ab977d85a430fa6b3a64aae64 (patch)
tree3a52b39e77308b728e06f66fe459fc37913aed9a /src
parent86169b961457dfcf77af1400fcc4c95ee17886af (diff)
support primitive-0.7.0.0 and remove generated bounds from build-depends
Diffstat (limited to 'src')
-rw-r--r--src/Data/Primitive/ByteArray/Util.hs17
-rw-r--r--src/Data/Primitive/Struct.hs4
2 files changed, 19 insertions, 2 deletions
diff --git a/src/Data/Primitive/ByteArray/Util.hs b/src/Data/Primitive/ByteArray/Util.hs
index 83a2e7d..4134e5f 100644
--- a/src/Data/Primitive/ByteArray/Util.hs
+++ b/src/Data/Primitive/ByteArray/Util.hs
@@ -15,11 +15,16 @@ import GHC.TypeLits
15import Control.Monad.Primitive 15import Control.Monad.Primitive
16import qualified Data.ByteString as B 16import qualified Data.ByteString as B
17import qualified Data.ByteString.Unsafe as B 17import qualified Data.ByteString.Unsafe as B
18#if !MIN_VERSION_primitive(0,7,0)
18import Data.Primitive.Addr 19import Data.Primitive.Addr
20#else
21import Data.Primitive.Ptr
22#endif
19import Data.Primitive.Types 23import Data.Primitive.Types
20import Data.Primitive.ByteArray 24import Data.Primitive.ByteArray
21import Data.Word 25import Data.Word
22import Foreign.Ptr 26import Foreign.Ptr
27import Foreign.C.Types
23 28
24newtype Offset (n :: Nat) = Offset Int 29newtype Offset (n :: Nat) = Offset Int
25 30
@@ -55,17 +60,25 @@ readAtByte :: forall a m n.
55readAtByte buf (Offset offset) = readByteArray buf (div offset $ (sizeOf (undefined :: a))) 60readAtByte buf (Offset offset) = readByteArray buf (div offset $ (sizeOf (undefined :: a)))
56{-# INLINE readAtByte #-} 61{-# INLINE readAtByte #-}
57 62
58writeStringAt :: PrimMonad m => MutableByteArray s -> Int -> B.ByteString -> m (Ptr a) 63writeStringAt :: (PrimMonad m) => MutableByteArray s -> Int -> B.ByteString -> m (Ptr a)
59writeStringAt src o bsname = do 64writeStringAt src o bsname = do
60 (p,cnt) <- unsafeIOToPrim $ B.unsafeUseAsCStringLen bsname return 65 (p,cnt) <- unsafeIOToPrim $ B.unsafeUseAsCStringLen bsname return
66#if !MIN_VERSION_primitive(0,7,0)
61 let nptr = ptr (mutableByteArrayContents src) `plusPtr` o 67 let nptr = ptr (mutableByteArrayContents src) `plusPtr` o
62 copyAddr (adr nptr) (adr p) cnt 68 copyAddr (adr nptr) (adr p) cnt
63 writeOffAddr (adr nptr) cnt (0 :: Word8) 69 writeOffAddr (adr nptr) cnt (0 :: Word8)
64 return nptr 70#else
71 let nptr = (mutableByteArrayContents src) `plusPtr` o
72 copyPtr (nptr) (p) cnt
73 writeOffPtr (castPtr nptr) cnt (0 :: Foreign.C.Types.CChar )
74#endif
75 return (castPtr nptr)
65 76
77#if !MIN_VERSION_primitive(0,7,0)
66ptr :: Addr -> Ptr a 78ptr :: Addr -> Ptr a
67ptr (Addr a) = Ptr a 79ptr (Addr a) = Ptr a
68 80
69adr :: Ptr a -> Addr 81adr :: Ptr a -> Addr
70adr (Ptr a) = Addr a 82adr (Ptr a) = Addr a
83#endif
71 84
diff --git a/src/Data/Primitive/Struct.hs b/src/Data/Primitive/Struct.hs
index 705e65d..92bd387 100644
--- a/src/Data/Primitive/Struct.hs
+++ b/src/Data/Primitive/Struct.hs
@@ -110,7 +110,11 @@ instance IsStruct IO Ptr where
110 110
111withPointer :: Struct IO base tag -> (Ptr tag -> IO x) -> IO x 111withPointer :: Struct IO base tag -> (Ptr tag -> IO x) -> IO x
112withPointer (Struct (Offset off) ary) f = do 112withPointer (Struct (Offset off) ary) f = do
113#if !MIN_VERSION_primitive(0,7,0)
113 x <- f (ptr (mutableByteArrayContents ary) `plusPtr` off) 114 x <- f (ptr (mutableByteArrayContents ary) `plusPtr` off)
115#else
116 x <- f ((mutableByteArrayContents ary) `plusPtr` off)
117#endif
114 seq ary $ return x 118 seq ary $ return x
115 119
116data ForeignStruct tag = ForeignStruct 120data ForeignStruct tag = ForeignStruct