Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
51 changes: 28 additions & 23 deletions cbits/primitive-memops.c
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
#include <math.h>
#include <string.h>
#include "primitive-memops.h"

Expand All @@ -11,28 +12,32 @@ void hsprimitive_memmove( void *dst, ptrdiff_t doff, void *src, ptrdiff_t soff,
memmove( (char *)dst + doff, (char *)src + soff, len );
}

#define MEMSET(TYPE, ATYPE) \
#define MEMSET(TYPE, ATYPE) \
void hsprimitive_memset_ ## TYPE (Hs ## TYPE *p, ptrdiff_t off, size_t n, ATYPE x) \
{ \
p += off; \
if (x == 0) \
memset(p, 0, n * sizeof(Hs ## TYPE)); \
else if (sizeof(Hs ## TYPE) == sizeof(int)*2) { \
int *q = (int *)p; \
const int *r = (const int *)(void *)&x; \
while (n>0) { \
q[0] = r[0]; \
q[1] = r[1]; \
q += 2; \
--n; \
} \
} \
else { \
while (n>0) { \
*p++ = x; \
--n; \
} \
} \
{ \
p += off; \
if (x == 0) { \
memset(p, 0, n * sizeof(Hs ## TYPE)); \
} else { \
while (n > 0) { \
*p++ = x; \
--n; \
} \
} \
}

#define MEMSET_FLOAT(TYPE, ATYPE) \
void hsprimitive_memset_ ## TYPE (Hs ## TYPE *p, ptrdiff_t off, size_t n, ATYPE x) \
{ \
p += off; \
if (x == 0.0 && !signbit(x)) \
memset(p, 0, n * sizeof(Hs ## TYPE)); \
else { \
while (n > 0) { \
*p++ = x; \
--n; \
} \
} \
}

int hsprimitive_memcmp( HsWord8 *s1, HsWord8 *s2, size_t n )
Expand All @@ -56,6 +61,6 @@ MEMSET(Word32, HsWord32)
MEMSET(Word64, HsWord64)
MEMSET(Word, HsWord)
MEMSET(Ptr, HsPtr)
MEMSET(Float, HsFloat)
MEMSET(Double, HsDouble)
MEMSET_FLOAT(Float, HsFloat)
MEMSET_FLOAT(Double, HsDouble)
MEMSET(Char, HsChar)
19 changes: 14 additions & 5 deletions test/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -14,7 +14,7 @@
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE TypeInType #-}

Check warning on line 17 in test/Main.hs

View workflow job for this annotation

GitHub Actions / build (ubuntu-latest, 9.10)

-XTypeInType is deprecated: use -XDataKinds and -XPolyKinds instead

Check warning on line 17 in test/Main.hs

View workflow job for this annotation

GitHub Actions / build (ubuntu-latest, 9.10)

-XTypeInType is deprecated: use -XDataKinds and -XPolyKinds instead

Check warning on line 17 in test/Main.hs

View workflow job for this annotation

GitHub Actions / build (ubuntu-latest, 9.10)

-XTypeInType is deprecated: use -XDataKinds and -XPolyKinds instead

Check warning on line 17 in test/Main.hs

View workflow job for this annotation

GitHub Actions / build (ubuntu-latest, 9.10)

-XTypeInType is deprecated: use -XDataKinds and -XPolyKinds instead

Check warning on line 17 in test/Main.hs

View workflow job for this annotation

GitHub Actions / build (ubuntu-latest, 9.6)

-XTypeInType is deprecated: use -XDataKinds and -XPolyKinds instead

Check warning on line 17 in test/Main.hs

View workflow job for this annotation

GitHub Actions / build (ubuntu-latest, 9.6)

-XTypeInType is deprecated: use -XDataKinds and -XPolyKinds instead

Check warning on line 17 in test/Main.hs

View workflow job for this annotation

GitHub Actions / build (ubuntu-latest, 9.6)

-XTypeInType is deprecated: use -XDataKinds and -XPolyKinds instead

Check warning on line 17 in test/Main.hs

View workflow job for this annotation

GitHub Actions / build (ubuntu-latest, 9.6)

-XTypeInType is deprecated: use -XDataKinds and -XPolyKinds instead

Check warning on line 17 in test/Main.hs

View workflow job for this annotation

GitHub Actions / build (ubuntu-latest, 9.8)

-XTypeInType is deprecated: use -XDataKinds and -XPolyKinds instead

Check warning on line 17 in test/Main.hs

View workflow job for this annotation

GitHub Actions / build (ubuntu-latest, 9.8)

-XTypeInType is deprecated: use -XDataKinds and -XPolyKinds instead

Check warning on line 17 in test/Main.hs

View workflow job for this annotation

GitHub Actions / build (ubuntu-latest, 9.8)

-XTypeInType is deprecated: use -XDataKinds and -XPolyKinds instead

Check warning on line 17 in test/Main.hs

View workflow job for this annotation

GitHub Actions / build (ubuntu-latest, 9.8)

-XTypeInType is deprecated: use -XDataKinds and -XPolyKinds instead

Check warning on line 17 in test/Main.hs

View workflow job for this annotation

GitHub Actions / build (windows-latest, latest)

-XTypeInType is deprecated: use -XDataKinds and -XPolyKinds instead

Check warning on line 17 in test/Main.hs

View workflow job for this annotation

GitHub Actions / build (windows-latest, latest)

-XTypeInType is deprecated: use -XDataKinds and -XPolyKinds instead

Check warning on line 17 in test/Main.hs

View workflow job for this annotation

GitHub Actions / build (windows-latest, latest)

-XTypeInType is deprecated: use -XDataKinds and -XPolyKinds instead

Check warning on line 17 in test/Main.hs

View workflow job for this annotation

GitHub Actions / build (windows-latest, latest)

-XTypeInType is deprecated: use -XDataKinds and -XPolyKinds instead

Check warning on line 17 in test/Main.hs

View workflow job for this annotation

GitHub Actions / build (macOS-latest, latest)

-XTypeInType is deprecated: use -XDataKinds and -XPolyKinds instead

Check warning on line 17 in test/Main.hs

View workflow job for this annotation

GitHub Actions / build (macOS-latest, latest)

-XTypeInType is deprecated: use -XDataKinds and -XPolyKinds instead

Check warning on line 17 in test/Main.hs

View workflow job for this annotation

GitHub Actions / build (macOS-latest, latest)

-XTypeInType is deprecated: use -XDataKinds and -XPolyKinds instead

Check warning on line 17 in test/Main.hs

View workflow job for this annotation

GitHub Actions / build (macOS-latest, latest)

-XTypeInType is deprecated: use -XDataKinds and -XPolyKinds instead
#endif

import Control.Monad
Expand Down Expand Up @@ -110,6 +110,10 @@
, TQC.testProperty "Word32" (setByteArrayProp (Proxy :: Proxy Word32))
, TQC.testProperty "Word64" (setByteArrayProp (Proxy :: Proxy Word64))
, TQC.testProperty "Word" (setByteArrayProp (Proxy :: Proxy Word))
, TQC.testProperty "Float" (setByteArrayProp (Proxy :: Proxy Float))
, TQC.testProperty "Double" (setByteArrayProp (Proxy :: Proxy Double))
, TQC.testProperty "Float -0.0" (\n off len -> setByteArrayTest (Proxy :: Proxy Float) n off len 0.0 (-0.0))
, TQC.testProperty "Double -0.0" (\n off len -> setByteArrayTest (Proxy :: Proxy Double) n off len 0.0 (-0.0))
]
]
, testGroup "Resize"
Expand Down Expand Up @@ -175,6 +179,8 @@
, renameLawsToTest "Int16" (primLaws (Proxy :: Proxy Int16))
, renameLawsToTest "Int32" (primLaws (Proxy :: Proxy Int32))
, renameLawsToTest "Int64" (primLaws (Proxy :: Proxy Int64))
, renameLawsToTest "Float" (primLaws (Proxy :: Proxy Float))
, renameLawsToTest "Double" (primLaws (Proxy :: Proxy Double))
, renameLawsToTest "Const" (primLaws (Proxy :: Proxy (Const Int16 Int16)))
, renameLawsToTest "Down" (primLaws (Proxy :: Proxy (Down Int16)))
, renameLawsToTest "Identity" (primLaws (Proxy :: Proxy (Identity Int16)))
Expand Down Expand Up @@ -207,22 +213,25 @@
int32 = Proxy


setByteArrayProp :: forall a. (Prim a, Eq a, Arbitrary a, Show a) => Proxy a -> QC.Property
setByteArrayProp _ = QC.property $ \(QC.NonNegative (n :: Int)) (QC.NonNegative (off :: Int)) (QC.NonNegative (len :: Int)) (x :: a) (y :: a) ->
setByteArrayProp :: (Prim a, Eq a, Arbitrary a, Show a) => Proxy a -> QC.Property
setByteArrayProp p = QC.property (setByteArrayTest p)

setByteArrayTest :: (Prim a, Eq a, Arbitrary a, Show a) => Proxy a -> QC.NonNegative Int -> QC.NonNegative Int -> QC.NonNegative Int -> a -> a -> QC.Property
setByteArrayTest _ (QC.NonNegative (n :: Int)) (QC.NonNegative (off :: Int)) (QC.NonNegative (len :: Int)) (x :: a) (y :: a) =
(off < n && off + len <= n) ==>
-- We use PrimArray in this test because it makes it easier to
-- get the element-vs-byte distinction right.
let actual = runST $ do
let !(PrimArray actual) = runST $ do
m <- newPrimArray n
forM_ (enumFromTo 0 (n - 1)) $ \ix -> writePrimArray m ix x
setPrimArray m off len y
unsafeFreezePrimArray m
expected = runST $ do
!(PrimArray expected) = runST $ do
m <- newPrimArray n
forM_ (enumFromTo 0 (n - 1)) $ \ix -> writePrimArray m ix x
forM_ (enumFromTo off (off + len - 1)) $ \ix -> writePrimArray m ix y
unsafeFreezePrimArray m
in expected === actual
in ByteArray expected === ByteArray actual -- compare as ByteArray, so that actual bytes are compared


-- Tests that using resizeByteArray to shrink a byte array produces
Expand Down
Loading