Skip to content

Commit c39baba

Browse files
committed
Address review comments
1 parent db7b272 commit c39baba

File tree

6 files changed

+129
-51
lines changed

6 files changed

+129
-51
lines changed

vec/src/Data/Vec/DataFamily/SpineStrict.hs

Lines changed: 21 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,4 @@
1+
{-# LANGUAGE BangPatterns #-}
12
{-# LANGUAGE CPP #-}
23
{-# LANGUAGE DataKinds #-}
34
{-# LANGUAGE FlexibleInstances #-}
@@ -851,29 +852,36 @@ ifoldr = getIFoldr $ N.induction1 start step where
851852
newtype IFoldr a n b = IFoldr { getIFoldr :: (Fin n -> a -> b -> b) -> b -> Vec n a -> b }
852853

853854
scanr :: forall a b n. N.SNatI n => (a -> b -> b) -> b -> Vec n a -> Vec ('S n) b
854-
scanr f z = getScan $ N.induction1 start step where
855-
start :: Scan a 'Z b
856-
start = Scan $ \_ -> singleton z
855+
scanr f z = getScanr $ N.induction1 start step where
856+
start :: Scanr a 'Z b
857+
start = Scanr $ \_ -> singleton z
857858

858-
step :: Scan a m b -> Scan a ('S m) b
859-
step (Scan go) = Scan $ \(x ::: xs) -> let ys@(y ::: _) = go xs in f x y ::: ys
859+
step :: Scanr a m b -> Scanr a ('S m) b
860+
step (Scanr go) = Scanr $ \(x ::: xs) -> let ys@(y ::: _) = go xs in f x y ::: ys
860861

861-
newtype Scan a n b = Scan { getScan :: Vec n a -> Vec ('S n) b }
862+
newtype Scanr a n b = Scanr { getScanr :: Vec n a -> Vec ('S n) b }
862863

863864
scanl :: forall a b n. N.SNatI n => (b -> a -> b) -> b -> Vec n a -> Vec ('S n) b
864-
scanl f z = reverse . scanr (flip f) z . reverse
865+
scanl f = getScanl $ N.induction1 start step where
866+
start :: Scanl a 'Z b
867+
start = Scanl $ \z VNil -> singleton z
868+
869+
step :: Scanl a m b -> Scanl a ('S m) b
870+
step (Scanl go) = Scanl $ \(!acc) (x ::: xs) -> acc ::: go (f acc x) xs
871+
872+
newtype Scanl a n b = Scanl { getScanl :: b -> Vec n a -> Vec ('S n) b }
865873

866874
scanr1 :: forall a n. N.SNatI n => (a -> a -> a) -> Vec n a -> Vec n a
867-
scanr1 f = getScan1 $ N.induction1 start step where
868-
start :: Scan1 'Z a
869-
start = Scan1 $ \_ -> VNil
875+
scanr1 f = getScanr1 $ N.induction1 start step where
876+
start :: Scanr1 'Z a
877+
start = Scanr1 $ \_ -> VNil
870878

871-
step :: forall m. N.SNatI m => Scan1 m a -> Scan1 ('S m) a
872-
step (Scan1 go) = Scan1 $ \(x ::: xs) -> case N.snat :: N.SNat m of
879+
step :: forall m. N.SNatI m => Scanr1 m a -> Scanr1 ('S m) a
880+
step (Scanr1 go) = Scanr1 $ \(x ::: xs) -> case N.snat :: N.SNat m of
873881
N.SZ -> x ::: VNil
874882
N.SS -> let ys@(y ::: _) = go xs in f x y ::: ys
875883

876-
newtype Scan1 n a = Scan1 { getScan1 :: Vec n a -> Vec n a }
884+
newtype Scanr1 n a = Scanr1 { getScanr1 :: Vec n a -> Vec n a }
877885

878886
scanl1 :: forall a n. N.SNatI n => (a -> a -> a) -> Vec n a -> Vec n a
879887
scanl1 f xs = case N.snat :: N.SNat n of

vec/src/Data/Vec/Lazy.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -700,7 +700,7 @@ scanr :: forall a b n. (a -> b -> b) -> b -> Vec n a -> Vec ('S n) b
700700
scanr f z = go where
701701
go :: Vec m a -> Vec ('S m) b
702702
go VNil = singleton z
703-
go (x ::: xs) = let ys@(y ::: _) = go xs in f x y ::: ys
703+
go (x ::: xs) = case go xs of ys@(y ::: _) -> f x y ::: ys
704704

705705
scanl :: forall a b n. (b -> a -> b) -> b -> Vec n a -> Vec ('S n) b
706706
scanl f = go where
@@ -713,7 +713,7 @@ scanr1 f = go where
713713
go :: Vec m a -> Vec m a
714714
go VNil = VNil
715715
go (x ::: VNil) = x ::: VNil
716-
go (x ::: xs@(_ ::: _)) = let ys@(y ::: _) = go xs in f x y ::: ys
716+
go (x ::: xs@(_ ::: _)) = case go xs of ys@(y ::: _) -> f x y ::: ys
717717

718718
scanl1 :: forall a n. (a -> a -> a) -> Vec n a -> Vec n a
719719
scanl1 _ VNil = VNil

vec/src/Data/Vec/Lazy/Inline.hs

Lines changed: 33 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,4 @@
1+
{-# LANGUAGE BangPatterns #-}
12
{-# LANGUAGE CPP #-}
23
{-# LANGUAGE DataKinds #-}
34
{-# LANGUAGE FlexibleInstances #-}
@@ -12,7 +13,7 @@
1213
-- The hypothesis is that these (goursive) functions could be fully unrolled,
1314
-- if the 'Vec' size @n@ is known at compile time.
1415
--
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'').
1617
-- /Note:/ instance methods aren't changed, the 'Vec' type is the same.
1718
module Data.Vec.Lazy.Inline (
1819
Vec (..),
@@ -53,7 +54,9 @@ module Data.Vec.Lazy.Inline (
5354
ifoldr,
5455
-- * Scans
5556
scanr,
57+
scanl,
5658
scanr1,
59+
scanl1,
5760
-- * Special folds
5861
length,
5962
null,
@@ -524,26 +527,42 @@ ifoldr = getIFoldr $ N.induction1 start step where
524527
newtype IFoldr a n b = IFoldr { getIFoldr :: (Fin n -> a -> b -> b) -> b -> Vec n a -> b }
525528

526529
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
530533

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
533537

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 }
535549

536550
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
540554

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
543557
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 }
545561

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
547566

548567
-- | Yield the length of a 'Vec'. /O(n)/
549568
length :: forall n a. N.SNatI n => Vec n a -> Int

vec/src/Data/Vec/Pull.hs

Lines changed: 1 addition & 21 deletions
Original file line numberDiff line numberDiff line change
@@ -12,7 +12,7 @@
1212
--
1313
-- The module tries to have same API as "Data.Vec.Lazy", missing bits:
1414
-- @withDict@, @toPull@, @fromPull@, @traverse@ (and variants),
15-
-- @(++)@, @concat@ and @split@.
15+
-- @scanr@ (and variants), @(++)@, @concat@ and @split@.
1616
module Data.Vec.Pull (
1717
Vec (..),
1818
-- * Construction
@@ -43,11 +43,6 @@ module Data.Vec.Pull (
4343
foldr,
4444
ifoldr,
4545
foldl',
46-
-- * Scans
47-
scanr,
48-
scanl,
49-
scanr1,
50-
scanl1,
5146
-- * Special folds
5247
length,
5348
null,
@@ -74,10 +69,7 @@ import Prelude
7469
import Control.Applicative (Applicative (..), (<$>))
7570
import Data.Boring (Boring (..))
7671
import Data.Fin (Fin (..))
77-
import qualified Data.List as List
7872
import Data.List.NonEmpty (NonEmpty (..))
79-
import qualified Data.List.NonEmpty as NonEmpty
80-
import Data.Maybe (fromJust)
8173
import Data.Monoid (Monoid (..))
8274
import Data.Nat (Nat (..))
8375
import Data.Proxy (Proxy (..))
@@ -388,18 +380,6 @@ ifoldr f z (Vec v) = I.foldr (\a b -> f a (v a) b) z F.universe
388380
foldl' :: N.SNatI n => (b -> a -> b) -> b -> Vec n a -> b
389381
foldl' f z (Vec v) = I.foldl' (\b a -> f b (v a)) z F.universe
390382

391-
scanr :: forall a b n. N.SNatI n => (a -> b -> b) -> b -> Vec n a -> Vec ('S n) b
392-
scanr f z = fromJust . fromList . NonEmpty.toList . NonEmpty.scanr f z
393-
394-
scanl :: forall a b n. N.SNatI n => (b -> a -> b) -> b -> Vec n a -> Vec ('S n) b
395-
scanl f z = fromJust . fromList . NonEmpty.toList . NonEmpty.scanl f z
396-
397-
scanr1 :: forall a n. N.SNatI n => (a -> a -> a) -> Vec n a -> Vec n a
398-
scanr1 f = fromJust . fromList . List.scanr1 f . toList
399-
400-
scanl1 :: forall a n. N.SNatI n => (a -> a -> a) -> Vec n a -> Vec n a
401-
scanl1 f = fromJust . fromList . List.scanl1 f . toList
402-
403383
-- | Yield the length of a 'Vec'.
404384
length :: forall n a. N.SNatI n => Vec n a -> Int
405385
length _ = N.reflectToNum (Proxy :: Proxy n)

vec/test/Inspection.hs

Lines changed: 48 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -6,7 +6,6 @@ module Inspection where
66
import Prelude hiding (zipWith)
77

88
import Data.Fin (Fin (..))
9-
import qualified Data.List as List
109
import Data.List.NonEmpty (NonEmpty (..))
1110
import Data.Vec.Lazy (Vec (..))
1211
import Test.Inspection
@@ -185,3 +184,51 @@ rhsScanr = (-2) ::: 3 ::: (-1) ::: 4 ::: 0 ::: VNil
185184

186185
inspect $ 'lhsScanr === 'rhsScanr
187186
inspect $ 'lhsScanr' =/= 'rhsScanr
187+
188+
-------------------------------------------------------------------------------
189+
-- scanl
190+
-------------------------------------------------------------------------------
191+
192+
lhsScanl :: Vec N.Nat5 Int
193+
lhsScanl = I.scanl (-) 0 $ 1 ::: 2 ::: 3 ::: 4 ::: VNil
194+
195+
lhsScanl' :: Vec N.Nat5 Int
196+
lhsScanl' = L.scanl (-) 0 $ 1 ::: 2 ::: 3 ::: 4 ::: VNil
197+
198+
rhsScanl :: Vec N.Nat5 Int
199+
rhsScanl = 0 ::: (-1) ::: (-3) ::: (-6) ::: (-10) ::: VNil
200+
201+
inspect $ 'lhsScanl === 'rhsScanl
202+
inspect $ 'lhsScanl' =/= 'rhsScanl
203+
204+
-------------------------------------------------------------------------------
205+
-- scanr1
206+
-------------------------------------------------------------------------------
207+
208+
lhsScanr1 :: Vec N.Nat4 Int
209+
lhsScanr1 = I.scanr1 (-) $ 1 ::: 2 ::: 3 ::: 4 ::: VNil
210+
211+
lhsScanr1' :: Vec N.Nat4 Int
212+
lhsScanr1' = L.scanr1 (-) $ 1 ::: 2 ::: 3 ::: 4 ::: VNil
213+
214+
rhsScanr1 :: Vec N.Nat4 Int
215+
rhsScanr1 = (-2) ::: 3 ::: (-1) ::: 4 ::: VNil
216+
217+
inspect $ 'lhsScanr1 === 'rhsScanr1
218+
inspect $ 'lhsScanr1' =/= 'rhsScanr1
219+
220+
-------------------------------------------------------------------------------
221+
-- scanl1
222+
-------------------------------------------------------------------------------
223+
224+
lhsScanl1 :: Vec N.Nat4 Int
225+
lhsScanl1 = I.scanl1 (-) $ 1 ::: 2 ::: 3 ::: 4 ::: VNil
226+
227+
lhsScanl1' :: Vec N.Nat4 Int
228+
lhsScanl1' = L.scanl1 (-) $ 1 ::: 2 ::: 3 ::: 4 ::: VNil
229+
230+
rhsScanl1 :: Vec N.Nat4 Int
231+
rhsScanl1 = 1 ::: (-1) ::: (-4) ::: (-8) ::: VNil
232+
233+
inspect $ 'lhsScanl1 === 'rhsScanl1
234+
inspect $ 'lhsScanl1' =/= 'rhsScanl1

vec/test/Inspection/DataFamily/SpineStrict.hs

Lines changed: 24 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -117,3 +117,27 @@ rhsScanl :: Vec N.Nat5 Int
117117
rhsScanl = 0 ::: (-1) ::: (-3) ::: (-6) ::: (-10) ::: VNil
118118

119119
inspect $ 'lhsScanl === 'rhsScanl
120+
121+
-------------------------------------------------------------------------------
122+
-- scanr1
123+
-------------------------------------------------------------------------------
124+
125+
lhsScanr1 :: Vec N.Nat4 Int
126+
lhsScanr1 = I.scanr1 (-) $ 1 ::: 2 ::: 3 ::: 4 ::: VNil
127+
128+
rhsScanr1 :: Vec N.Nat4 Int
129+
rhsScanr1 = (-2) ::: 3 ::: (-1) ::: 4 ::: VNil
130+
131+
inspect $ 'lhsScanr1 === 'rhsScanr1
132+
133+
-------------------------------------------------------------------------------
134+
-- scanl1
135+
-------------------------------------------------------------------------------
136+
137+
lhsScanl1 :: Vec N.Nat4 Int
138+
lhsScanl1 = I.scanl1 (-) $ 1 ::: 2 ::: 3 ::: 4 ::: VNil
139+
140+
rhsScanl1 :: Vec N.Nat4 Int
141+
rhsScanl1 = 1 ::: (-1) ::: (-4) ::: (-8) ::: VNil
142+
143+
inspect $ 'lhsScanl1 === 'rhsScanl1

0 commit comments

Comments
 (0)