File tree Expand file tree Collapse file tree 4 files changed +34
-5
lines changed
src/HaskellWorks/Data/Streams/Stream
HaskellWorks/Data/Streams Expand file tree Collapse file tree 4 files changed +34
-5
lines changed Original file line number Diff line number Diff line change @@ -38,4 +38,7 @@ bitwiseShiftDown n as = HW.zipWith splice bs (HW.drop 1 bs `append` HW.singleton
3838 splice a b = (a .>. o) .|. (b .<. (64 - o))
3939
4040add :: Stream Word64 -> Stream Word64 -> Stream Word64
41- add = HW. zipWithState (\ a b c -> let d = a + b in (c + d, d `ltWord` a)) 0
41+ add = HW. zipWithState (\ a b c ->
42+ let d = a + b + c in
43+ let e = d `ltWord` a in
44+ (d, e)) 0
Original file line number Diff line number Diff line change 1+ {-# LANGUAGE OverloadedStrings #-}
2+ {-# LANGUAGE ScopedTypeVariables #-}
3+
4+ module HaskellWorks.Data.Streams.Stream.OpsSpec
5+ ( spec
6+ ) where
7+
8+ import Data.Semigroup ((<>) )
9+ import Data.Word
10+ import HaskellWorks.Hspec.Hedgehog
11+ import Hedgehog
12+ import Test.Hspec
13+
14+ import qualified Data.Vector.Storable as DVS
15+ import qualified HaskellWorks.Data.Streams.Stream.Ops as S
16+ import qualified HaskellWorks.Data.Streams.Vector.Storable as SDVS
17+
18+ {-# ANN module ("HLint: Ignore Redundant do" :: String) #-}
19+
20+ spec :: Spec
21+ spec = describe " HaskellWorks.Data.Stream.Vector.StorableSpec" $ do
22+ it " map" $ requireTest $ do
23+ u <- forAll $ pure $ DVS. fromList $ replicate 4 (0xffffffffffffffff :: Word64 )
24+ v <- forAll $ pure $ DVS. fromList $ [0x0000000000000001 :: Word64 ] <> replicate 3 0
25+
26+ let result = SDVS. unstream (S. add (SDVS. stream u) (SDVS. stream v))
27+
28+ result === DVS. replicate 4 (0x0000000000000000 :: Word64 )
Original file line number Diff line number Diff line change 11{-# LANGUAGE OverloadedStrings #-}
22{-# LANGUAGE ScopedTypeVariables #-}
33
4- module HaskellWorks.Data.Stream .Vector.StorableSpec
4+ module HaskellWorks.Data.Streams .Vector.StorableSpec
55 ( spec
66 ) where
77
Original file line number Diff line number Diff line change 11module Test.Gen where
22
3- import Data.Vector.Storable (Storable )
4- import HaskellWorks.Hspec.Hedgehog
3+ import Data.Vector.Storable (Storable )
54import Hedgehog
6- import Test.Hspec
75
86import qualified Data.Vector.Storable as DVS
97import qualified Hedgehog.Gen as G
You can’t perform that action at this time.
0 commit comments