Skip to content

Commit 11f4145

Browse files
authored
Merge pull request #131 from sergv/unit-tests-for-alignment
Add unit tests for alignment of storable vectors
2 parents 08c3756 + 2a2e75d commit 11f4145

File tree

3 files changed

+55
-2
lines changed

3 files changed

+55
-2
lines changed

tests/Main.hs

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,12 +1,15 @@
11
module Main (main) where
22

33
import qualified Tests.Vector
4+
import qualified Tests.Vector.UnitTests
45
import qualified Tests.Bundle
56
import qualified Tests.Move
67

78
import Test.Framework (defaultMain)
89

10+
main :: IO ()
911
main = defaultMain $ Tests.Bundle.tests
1012
++ Tests.Vector.tests
13+
++ Tests.Vector.UnitTests.tests
1114
++ Tests.Move.tests
1215

tests/Tests/Vector/UnitTests.hs

Lines changed: 48 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,48 @@
1+
{-# LANGUAGE ScopedTypeVariables #-}
2+
3+
module Tests.Vector.UnitTests (tests) where
4+
5+
import Control.Applicative as Applicative
6+
import qualified Data.Vector.Storable as Storable
7+
import Foreign.Ptr
8+
import Foreign.Storable
9+
import Text.Printf
10+
11+
import Test.Framework
12+
import Test.Framework.Providers.HUnit (testCase)
13+
import Test.HUnit (Assertion, assertBool)
14+
15+
newtype Aligned a = Aligned { getAligned :: a }
16+
17+
instance (Storable a) => Storable (Aligned a) where
18+
sizeOf _ = sizeOf (undefined :: a)
19+
alignment _ = 128
20+
peek ptr = Aligned Applicative.<$> peek (castPtr ptr)
21+
poke ptr = poke (castPtr ptr) . getAligned
22+
23+
checkAddressAlignment :: forall a. (Storable a) => Storable.Vector a -> Assertion
24+
checkAddressAlignment xs = Storable.unsafeWith xs $ \ptr -> do
25+
let ptr' = ptrToWordPtr ptr
26+
msg = printf "Expected pointer with alignment %d but got 0x%08x" (toInteger align) (toInteger ptr')
27+
align :: WordPtr
28+
align = fromIntegral $ alignment dummy
29+
assertBool msg $ (ptr' `mod` align) == 0
30+
where
31+
dummy :: a
32+
dummy = undefined
33+
34+
tests :: [Test]
35+
tests =
36+
[ testGroup "Data.Vector.Storable.Vector Alignment"
37+
[ testCase "Aligned Double" $
38+
checkAddressAlignment alignedDoubleVec
39+
, testCase "Aligned Int" $
40+
checkAddressAlignment alignedIntVec
41+
]
42+
]
43+
44+
alignedDoubleVec :: Storable.Vector (Aligned Double)
45+
alignedDoubleVec = Storable.fromList $ map Aligned [1, 2, 3, 4, 5]
46+
47+
alignedIntVec :: Storable.Vector (Aligned Int)
48+
alignedIntVec = Storable.fromList $ map Aligned [1, 2, 3, 4, 5]

vector.cabal

Lines changed: 4 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -188,7 +188,8 @@ test-suite vector-tests-O0
188188
hs-source-dirs: tests
189189
Build-Depends: base >= 4.5 && < 5, template-haskell, vector,
190190
random,
191-
QuickCheck >= 2.9 && < 2.10 , test-framework, test-framework-quickcheck2,
191+
QuickCheck >= 2.9 && < 2.10 , HUnit, test-framework,
192+
test-framework-hunit, test-framework-quickcheck2,
192193
transformers >= 0.2.0.0
193194

194195
default-extensions: CPP,
@@ -217,7 +218,8 @@ test-suite vector-tests-O2
217218
hs-source-dirs: tests
218219
Build-Depends: base >= 4.5 && < 5, template-haskell, vector,
219220
random,
220-
QuickCheck >= 2.9 && < 2.10 , test-framework, test-framework-quickcheck2,
221+
QuickCheck >= 2.9 && < 2.10 , HUnit, test-framework,
222+
test-framework-hunit, test-framework-quickcheck2,
221223
transformers >= 0.2.0.0
222224

223225
default-extensions: CPP,

0 commit comments

Comments
 (0)