Skip to content

Commit

Permalink
Add prependVector
Browse files Browse the repository at this point in the history
  • Loading branch information
Bodigrim committed Dec 28, 2023
1 parent 80f6530 commit 3ab347e
Show file tree
Hide file tree
Showing 4 changed files with 50 additions and 0 deletions.
1 change: 1 addition & 0 deletions changelog.md
Original file line number Diff line number Diff line change
Expand Up @@ -5,6 +5,7 @@
change types of `toZCurve`, `fromZCurve`, `toZCurve3`, `fromZCurve3` accordingly.
* Add `throughZCurveFix` and `throughZCurveFix3`.
* Add `imapSubvectors`.
* Add `prependVector`.

# 0.3.4.0

Expand Down
1 change: 1 addition & 0 deletions src/Data/Chimera.hs
Original file line number Diff line number Diff line change
Expand Up @@ -29,6 +29,7 @@ module Data.Chimera (

-- * Manipulation
interleave,
prependVector,

-- * Elimination
index,
Expand Down
41 changes: 41 additions & 0 deletions src/Data/Chimera/Internal.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,6 +10,7 @@
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE ViewPatterns #-}

-- |
-- Module: Data.Chimera.Internal
Expand All @@ -36,6 +37,7 @@ module Data.Chimera.Internal (

-- * Manipulation
interleave,
prependVector,

-- * Elimination
index,
Expand Down Expand Up @@ -600,6 +602,45 @@ fromVectorWithDef a = Chimera . fromListN (bits + 1) . go0
where
kk = 1 `shiftL` k

-- | Prepend a given vector to a stream of values.
--
-- @since 0.4.0.0
prependVector
:: forall v a
. G.Vector v a
=> v a
-> Chimera v a
-> Chimera v a
prependVector (G.uncons -> Nothing) ch = ch

Check warning on line 614 in src/Data/Chimera/Internal.hs

View workflow job for this annotation

GitHub Actions / build (ubuntu-latest, 8.2)

Pattern match(es) are non-exhaustive

Check warning on line 614 in src/Data/Chimera/Internal.hs

View workflow job for this annotation

GitHub Actions / build (ubuntu-latest, 8.2)

Pattern match(es) are non-exhaustive

Check warning on line 614 in src/Data/Chimera/Internal.hs

View workflow job for this annotation

GitHub Actions / build (ubuntu-latest, 8.2)

Pattern match(es) are non-exhaustive

Check warning on line 614 in src/Data/Chimera/Internal.hs

View workflow job for this annotation

GitHub Actions / build (ubuntu-latest, 8.4)

Pattern match(es) are non-exhaustive

Check warning on line 614 in src/Data/Chimera/Internal.hs

View workflow job for this annotation

GitHub Actions / build (ubuntu-latest, 8.4)

Pattern match(es) are non-exhaustive

Check warning on line 614 in src/Data/Chimera/Internal.hs

View workflow job for this annotation

GitHub Actions / build (ubuntu-latest, 8.4)

Pattern match(es) are non-exhaustive

Check warning on line 614 in src/Data/Chimera/Internal.hs

View workflow job for this annotation

GitHub Actions / build (ubuntu-latest, 8.6)

Pattern match(es) are non-exhaustive

Check warning on line 614 in src/Data/Chimera/Internal.hs

View workflow job for this annotation

GitHub Actions / build (ubuntu-latest, 8.6)

Pattern match(es) are non-exhaustive

Check warning on line 614 in src/Data/Chimera/Internal.hs

View workflow job for this annotation

GitHub Actions / build (ubuntu-latest, 8.6)

Pattern match(es) are non-exhaustive

Check warning on line 614 in src/Data/Chimera/Internal.hs

View workflow job for this annotation

GitHub Actions / build (ubuntu-latest, 8.8)

Pattern match(es) are non-exhaustive

Check warning on line 614 in src/Data/Chimera/Internal.hs

View workflow job for this annotation

GitHub Actions / build (ubuntu-latest, 8.8)

Pattern match(es) are non-exhaustive

Check warning on line 614 in src/Data/Chimera/Internal.hs

View workflow job for this annotation

GitHub Actions / build (ubuntu-latest, 8.8)

Pattern match(es) are non-exhaustive

Check warning on line 614 in src/Data/Chimera/Internal.hs

View workflow job for this annotation

GitHub Actions / build (ubuntu-latest, 8.10)

Pattern match(es) are non-exhaustive

Check warning on line 614 in src/Data/Chimera/Internal.hs

View workflow job for this annotation

GitHub Actions / build (ubuntu-latest, 8.10)

Pattern match(es) are non-exhaustive

Check warning on line 614 in src/Data/Chimera/Internal.hs

View workflow job for this annotation

GitHub Actions / build (ubuntu-latest, 8.10)

Pattern match(es) are non-exhaustive

Check warning on line 614 in src/Data/Chimera/Internal.hs

View workflow job for this annotation

GitHub Actions / build (ubuntu-latest, 9.0)

Pattern match(es) are non-exhaustive

Check warning on line 614 in src/Data/Chimera/Internal.hs

View workflow job for this annotation

GitHub Actions / build (ubuntu-latest, 9.0)

Pattern match(es) are non-exhaustive

Check warning on line 614 in src/Data/Chimera/Internal.hs

View workflow job for this annotation

GitHub Actions / build (ubuntu-latest, 9.0)

Pattern match(es) are non-exhaustive

Check warning on line 614 in src/Data/Chimera/Internal.hs

View workflow job for this annotation

GitHub Actions / build (ubuntu-latest, 9.2)

Pattern match(es) are non-exhaustive

Check warning on line 614 in src/Data/Chimera/Internal.hs

View workflow job for this annotation

GitHub Actions / build (ubuntu-latest, 9.2)

Pattern match(es) are non-exhaustive

Check warning on line 614 in src/Data/Chimera/Internal.hs

View workflow job for this annotation

GitHub Actions / build (ubuntu-latest, 9.2)

Pattern match(es) are non-exhaustive

Check warning on line 614 in src/Data/Chimera/Internal.hs

View workflow job for this annotation

GitHub Actions / build (ubuntu-latest, 9.4)

Pattern match(es) are non-exhaustive

Check warning on line 614 in src/Data/Chimera/Internal.hs

View workflow job for this annotation

GitHub Actions / build (ubuntu-latest, 9.4)

Pattern match(es) are non-exhaustive

Check warning on line 614 in src/Data/Chimera/Internal.hs

View workflow job for this annotation

GitHub Actions / build (ubuntu-latest, 9.4)

Pattern match(es) are non-exhaustive
prependVector (G.uncons -> Just (pref0, pref)) (Chimera as) =
Chimera $
fromListN (bits + 1) $
fmap sliceAndConcat $
[LazySlice 0 1 $ G.singleton pref0] : go 0 1 0 inputs
where
inputs :: [(Word, v a)]
inputs =
(int2word $ G.length pref, pref)
: zip (1 : map (1 `unsafeShiftL`) [0 .. bits - 1]) (F.toList as)

go :: Int -> Word -> Word -> [(Word, t)] -> [[LazySlice t]]
go _ _ _ [] = []
go n need off orig@((lt, t) : rest)
| n >= bits = []
| otherwise = case compare (off + need) lt of
LT -> [LazySlice off need t] : go (n + 1) (1 `shiftL` (n + 1)) (off + need) orig
EQ -> [LazySlice off need t] : go (n + 1) (1 `shiftL` (n + 1)) 0 rest
GT -> case go n (off + need - lt) 0 rest of
[] -> error "prependVector: the stream should not get exhausted prematurely"
hd : tl -> (LazySlice off (lt - off) t : hd) : tl

data LazySlice a = LazySlice !Word !Word a

sliceAndConcat :: G.Vector v a => [LazySlice (v a)] -> v a
sliceAndConcat =
G.concat
. map (\(LazySlice from len vec) -> G.slice (word2int from) (word2int len) vec)

-- | Return an infinite repetition of a given vector.
-- Throw an error on an empty vector.
--
Expand Down
7 changes: 7 additions & 0 deletions test/Test.hs
Original file line number Diff line number Diff line change
Expand Up @@ -165,6 +165,13 @@ chimeraTests = testGroup "Chimera"
(if fromIntegral jx < length xs then vs G.! fromIntegral jx else x) ===
Ch.index (Ch.fromVectorWithDef x vs :: UChimera Bool) jx

, QC.testProperty "prependVector" $
\(Blind bs) xs ix ->
let jx = ix `mod` 65536 in
let vs = G.fromList xs in
(if fromIntegral jx < length xs then vs G.! fromIntegral jx else Ch.index bs (min 65555 $ jx - fromIntegral (length xs))) ===
Ch.index (Ch.prependVector vs bs :: UChimera Bool) jx

, QC.testProperty "mapSubvectors" $
\(Blind bs) (Fun _ (g :: Word -> Word)) ix ->
let jx = ix `mod` 65536 in
Expand Down

0 comments on commit 3ab347e

Please sign in to comment.