aboutsummaryrefslogtreecommitdiff
path: root/src/Data/Array/Nested/Mixed/Shape.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Data/Array/Nested/Mixed/Shape.hs')
-rw-r--r--src/Data/Array/Nested/Mixed/Shape.hs25
1 files changed, 20 insertions, 5 deletions
diff --git a/src/Data/Array/Nested/Mixed/Shape.hs b/src/Data/Array/Nested/Mixed/Shape.hs
index 23c3abf..a9ed2d0 100644
--- a/src/Data/Array/Nested/Mixed/Shape.hs
+++ b/src/Data/Array/Nested/Mixed/Shape.hs
@@ -105,21 +105,24 @@ listxEqual (n ::% sh) (m ::% sh')
= Just Refl
listxEqual _ _ = Nothing
+{-# INLINE listxFmap #-}
listxFmap :: (forall n. f n -> g n) -> ListX sh f -> ListX sh g
listxFmap _ ZX = ZX
listxFmap f (x ::% xs) = f x ::% listxFmap f xs
-listxFold :: Monoid m => (forall n. f n -> m) -> ListX sh f -> m
-listxFold _ ZX = mempty
-listxFold f (x ::% xs) = f x <> listxFold f xs
+{-# INLINE listxFoldMap #-}
+listxFoldMap :: Monoid m => (forall n. f n -> m) -> ListX sh f -> m
+listxFoldMap _ ZX = mempty
+listxFoldMap f (x ::% xs) = f x <> listxFoldMap f xs
listxLength :: ListX sh f -> Int
-listxLength = getSum . listxFold (\_ -> Sum 1)
+listxLength = getSum . listxFoldMap (\_ -> Sum 1)
listxRank :: ListX sh f -> SNat (Rank sh)
listxRank ZX = SNat
listxRank (_ ::% l) | SNat <- listxRank l = SNat
+{-# INLINE listxShow #-}
listxShow :: forall sh f. (forall n. f n -> ShowS) -> ListX sh f -> ShowS
listxShow f l = showString "[" . go "" l . showString "]"
where
@@ -167,6 +170,7 @@ listxZip :: ListX sh f -> ListX sh g -> ListX sh (Product f g)
listxZip ZX ZX = ZX
listxZip (i ::% irest) (j ::% jrest) = Pair i j ::% listxZip irest jrest
+{-# INLINE listxZipWith #-}
listxZipWith :: (forall a. f a -> g a -> h a) -> ListX sh f -> ListX sh g
-> ListX sh h
listxZipWith _ ZX ZX = ZX
@@ -206,10 +210,17 @@ instance Show i => Show (IxX sh i) where
#endif
instance Functor (IxX sh) where
+ {-# INLINE fmap #-}
fmap f (IxX l) = IxX (listxFmap (Const . f . getConst) l)
instance Foldable (IxX sh) where
- foldMap f (IxX l) = listxFold (f . getConst) l
+ {-# INLINE foldMap #-}
+ foldMap f (IxX l) = listxFoldMap (f . getConst) l
+ {-# INLINE foldr #-}
+ foldr _ z ZIX = z
+ foldr f z (x :.% xs) = f x (foldr f z xs)
+ null ZIX = False
+ null _ = True
instance NFData i => NFData (IxX sh i)
@@ -257,6 +268,7 @@ ixxZip :: IxX sh i -> IxX sh j -> IxX sh (i, j)
ixxZip ZIX ZIX = ZIX
ixxZip (i :.% is) (j :.% js) = (i, j) :.% ixxZip is js
+{-# INLINE ixxZipWith #-}
ixxZipWith :: (i -> j -> k) -> IxX sh i -> IxX sh j -> IxX sh k
ixxZipWith _ ZIX ZIX = ZIX
ixxZipWith f (i :.% is) (j :.% js) = f i j :.% ixxZipWith f is js
@@ -317,6 +329,7 @@ instance TestEquality f => TestEquality (SMayNat i f) where
testEquality (SKnown n) (SKnown m) | Just Refl <- testEquality n m = Just Refl
testEquality _ _ = Nothing
+{-# INLINE fromSMayNat #-}
fromSMayNat :: (n ~ Nothing => i -> r)
-> (forall m. n ~ Just m => f m -> r)
-> SMayNat i f n -> r
@@ -366,6 +379,7 @@ instance Show i => Show (ShX sh i) where
#endif
instance Functor (ShX sh) where
+ {-# INLINE fmap #-}
fmap f (ShX l) = ShX (listxFmap (fromSMayNat (SUnknown . f) SKnown) l)
instance NFData i => NFData (ShX sh i) where
@@ -472,6 +486,7 @@ shxTakeSSX :: forall sh sh' i proxy. proxy sh' -> StaticShX sh -> ShX (sh ++ sh'
shxTakeSSX _ ZKX _ = ZSX
shxTakeSSX p (_ :!% ssh1) (n :$% sh) = n :$% shxTakeSSX p ssh1 sh
+{-# INLINE shxZipWith #-}
shxZipWith :: (forall n. SMayNat i SNat n -> SMayNat j SNat n -> SMayNat k SNat n)
-> ShX sh i -> ShX sh j -> ShX sh k
shxZipWith _ ZSX ZSX = ZSX