|
| 1 | +{-# LANGUAGE BangPatterns #-} |
1 | 2 | {-# LANGUAGE CPP #-} |
2 | 3 | {-# LANGUAGE DataKinds #-} |
3 | 4 | {-# LANGUAGE FlexibleInstances #-} |
|
12 | 13 | -- The hypothesis is that these (goursive) functions could be fully unrolled, |
13 | 14 | -- if the 'Vec' size @n@ is known at compile time. |
14 | 15 | -- |
15 | | --- The module has the same API as "Data.Vec.Lazy" (sans 'L.withDict', 'foldl'', 'scanl' and 'scanl1'). |
| 16 | +-- The module has the same API as "Data.Vec.Lazy" (sans 'L.withDict' and 'foldl''). |
16 | 17 | -- /Note:/ instance methods aren't changed, the 'Vec' type is the same. |
17 | 18 | module Data.Vec.Lazy.Inline ( |
18 | 19 | Vec (..), |
@@ -53,7 +54,9 @@ module Data.Vec.Lazy.Inline ( |
53 | 54 | ifoldr, |
54 | 55 | -- * Scans |
55 | 56 | scanr, |
| 57 | + scanl, |
56 | 58 | scanr1, |
| 59 | + scanl1, |
57 | 60 | -- * Special folds |
58 | 61 | length, |
59 | 62 | null, |
@@ -524,26 +527,42 @@ ifoldr = getIFoldr $ N.induction1 start step where |
524 | 527 | newtype IFoldr a n b = IFoldr { getIFoldr :: (Fin n -> a -> b -> b) -> b -> Vec n a -> b } |
525 | 528 |
|
526 | 529 | scanr :: forall a b n. N.SNatI n => (a -> b -> b) -> b -> Vec n a -> Vec ('S n) b |
527 | | -scanr f z = getScan $ N.induction1 start step where |
528 | | - start :: Scan a 'Z b |
529 | | - start = Scan $ \_ -> singleton z |
| 530 | +scanr f z = getScanr $ N.induction1 start step where |
| 531 | + start :: Scanr a 'Z b |
| 532 | + start = Scanr $ \_ -> singleton z |
530 | 533 |
|
531 | | - step :: Scan a m b -> Scan a ('S m) b |
532 | | - step (Scan go) = Scan $ \(x ::: xs) -> let ys@(y ::: _) = go xs in f x y ::: ys |
| 534 | + step :: Scanr a m b -> Scanr a ('S m) b |
| 535 | + step (Scanr go) = Scanr $ \(x ::: xs) -> case go xs of |
| 536 | + ys@(y ::: _) -> f x y ::: ys |
533 | 537 |
|
534 | | -newtype Scan a n b = Scan { getScan :: Vec n a -> Vec ('S n) b } |
| 538 | +newtype Scanr a n b = Scanr { getScanr :: Vec n a -> Vec ('S n) b } |
| 539 | + |
| 540 | +scanl :: forall a b n. N.SNatI n => (b -> a -> b) -> b -> Vec n a -> Vec ('S n) b |
| 541 | +scanl f = getScanl $ N.induction1 start step where |
| 542 | + start :: Scanl a 'Z b |
| 543 | + start = Scanl $ \z VNil -> singleton z |
| 544 | + |
| 545 | + step :: Scanl a m b -> Scanl a ('S m) b |
| 546 | + step (Scanl go) = Scanl $ \(!acc) (x ::: xs) -> acc ::: go (f acc x) xs |
| 547 | + |
| 548 | +newtype Scanl a n b = Scanl { getScanl :: b -> Vec n a -> Vec ('S n) b } |
535 | 549 |
|
536 | 550 | scanr1 :: forall a n. N.SNatI n => (a -> a -> a) -> Vec n a -> Vec n a |
537 | | -scanr1 f = getScan1 $ N.induction1 start step where |
538 | | - start :: Scan1 'Z a |
539 | | - start = Scan1 $ \_ -> VNil |
| 551 | +scanr1 f = getScanr1 $ N.induction1 start step where |
| 552 | + start :: Scanr1 'Z a |
| 553 | + start = Scanr1 $ \_ -> VNil |
540 | 554 |
|
541 | | - step :: forall m. N.SNatI m => Scan1 m a -> Scan1 ('S m) a |
542 | | - step (Scan1 go) = Scan1 $ \(x ::: xs) -> case N.snat :: N.SNat m of |
| 555 | + step :: forall m. N.SNatI m => Scanr1 m a -> Scanr1 ('S m) a |
| 556 | + step (Scanr1 go) = Scanr1 $ \(x ::: xs) -> case N.snat :: N.SNat m of |
543 | 557 | N.SZ -> x ::: VNil |
544 | | - N.SS -> let ys@(y ::: _) = go xs in f x y ::: ys |
| 558 | + N.SS -> case go xs of ys@(y ::: _) -> f x y ::: ys |
| 559 | + |
| 560 | +newtype Scanr1 n a = Scanr1 { getScanr1 :: Vec n a -> Vec n a } |
545 | 561 |
|
546 | | -newtype Scan1 n a = Scan1 { getScan1 :: Vec n a -> Vec n a } |
| 562 | +scanl1 :: forall a n. N.SNatI n => (a -> a -> a) -> Vec n a -> Vec n a |
| 563 | +scanl1 f xs = case N.snat :: N.SNat n of |
| 564 | + N.SZ -> VNil |
| 565 | + N.SS -> case xs of y ::: ys -> scanl f y ys |
547 | 566 |
|
548 | 567 | -- | Yield the length of a 'Vec'. /O(n)/ |
549 | 568 | length :: forall n a. N.SNatI n => Vec n a -> Int |
|
0 commit comments