Skip to content

Commit

Permalink
Added concatMap
Browse files Browse the repository at this point in the history
  • Loading branch information
LaurentRDC committed Nov 25, 2023
1 parent e2899c4 commit a031965
Show file tree
Hide file tree
Showing 4 changed files with 37 additions and 8 deletions.
13 changes: 11 additions & 2 deletions javelin/src/Data/Series.hs
Original file line number Diff line number Diff line change
Expand Up @@ -50,7 +50,7 @@ module Data.Series (
G.convert,

-- * Mapping and filtering
map, mapWithKey, mapIndex,
map, mapWithKey, mapIndex, concatMap,
take, takeWhile, drop, dropWhile, filter, filterWithKey,
-- ** Mapping with effects
mapWithKeyM, mapWithKeyM_, forWithKeyM, forWithKeyM_, traverseWithKey,
Expand Down Expand Up @@ -100,7 +100,7 @@ import qualified Data.Series.Generic as G
import Data.Series.Generic.Zip ( skipStrategy, mapStrategy, constStrategy )
import Data.Vector ( Vector )

import Prelude hiding (map, zipWith, zipWith3, filter, take, takeWhile, drop, dropWhile, last, unzip, unzip3)
import Prelude hiding (map, concatMap, zipWith, zipWith3, filter, take, takeWhile, drop, dropWhile, last, unzip, unzip3)

-- $setup
-- >>> import qualified Data.Series as Series
Expand Down Expand Up @@ -303,6 +303,15 @@ mapIndex :: (Ord k, Ord g) => Series k a -> (k -> g) -> Series g a
mapIndex = G.mapIndex


-- | Map a function over all the elements of a 'Series' and concatenate the result into a single 'Series'.
concatMap :: Ord k
=> (a -> Series k b)
-> Series k a
-> Series k b
{-# INLINE concatMap #-}
concatMap = G.concatMap


-- | /O(n)/ Apply the monadic action to every element of a series and its
-- index, yielding a series of results.
mapWithKeyM :: (Monad m, Ord k) => (k -> a -> m b) -> Series k a -> m (Series k b)
Expand Down
4 changes: 2 additions & 2 deletions javelin/src/Data/Series/Generic.hs
Original file line number Diff line number Diff line change
Expand Up @@ -18,7 +18,7 @@ module Data.Series.Generic (
fromLazyMap, toLazyMap,

-- * Mapping and filtering
map, mapWithKey, mapIndex, filter, filterWithKey, null, length, sum,
map, mapWithKey, mapIndex, concatMap, filter, filterWithKey, null, length, sum,
take, takeWhile, drop, dropWhile,
-- ** Mapping with effects
mapWithKeyM, mapWithKeyM_, forWithKeyM, forWithKeyM_, traverseWithKey,
Expand Down Expand Up @@ -61,7 +61,7 @@ import Data.Series.Generic.Aggregation ( groupBy, Grouping, aggregateWith, fold
import Data.Series.Generic.Definition ( Series(index, values), Occurrence, convert, singleton, fromIndex, fromStrictMap
, toStrictMap, fromLazyMap, toLazyMap, fromList, fromListDuplicates, toList
, fromVector, fromVectorDuplicates, toVector
, map, mapWithKey, mapIndex, null, length, sum, take, takeWhile, drop, dropWhile
, map, mapWithKey, mapIndex, concatMap, null, length, sum, take, takeWhile, drop, dropWhile
, mapWithKeyM, mapWithKeyM_, forWithKeyM, forWithKeyM_, traverseWithKey, fold, foldM
, foldWithKey, foldMWithKey, foldMap, foldMapWithKey,
)
Expand Down
15 changes: 13 additions & 2 deletions javelin/src/Data/Series/Generic/Definition.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,7 +10,7 @@ module Data.Series.Generic.Definition (

-- * Basic interface
singleton,
headM, lastM, map, mapWithKey, mapIndex, fold, foldM,
headM, lastM, map, mapWithKey, mapIndex, concatMap, fold, foldM,
foldWithKey, foldMWithKey, foldMap, bifoldMap, foldMapWithKey,
sum, length, null, take, takeWhile, drop, dropWhile,
mapWithKeyM, mapWithKeyM_, forWithKeyM, forWithKeyM_,
Expand Down Expand Up @@ -64,7 +64,7 @@ import qualified Data.Vector.Generic.Mutable as GM
import qualified Data.Vector.Unboxed as U
import qualified Data.Vector.Unboxed.Mutable as UM

import Prelude hiding ( take, takeWhile, drop, dropWhile, map, foldMap, sum, length, null )
import Prelude hiding ( take, takeWhile, drop, dropWhile, map, concatMap, foldMap, sum, length, null )
import qualified Prelude as P


Expand Down Expand Up @@ -332,6 +332,17 @@ mapIndex (MkSeries index values) f
in fromStrictMap newvalues


-- | Map a function over all the elements of a 'Series' and concatenate the result into a single 'Series'.
concatMap :: (Vector v a, Vector v k, Vector v b, Vector v (k, a), Vector v (k, b), Ord k)
=> (a -> Series v k b)
-> Series v k a
-> Series v k b
{-# INLINE concatMap #-}
concatMap f = fromVector
. Vector.concatMap (toVector . f . snd)
. toVector


instance (Vector v a, Ord k) => Semigroup (Series v k a) where
{-# INLINE (<>) #-}
(<>) :: Series v k a -> Series v k a -> Series v k a
Expand Down
13 changes: 11 additions & 2 deletions javelin/src/Data/Series/Unboxed.hs
Original file line number Diff line number Diff line change
Expand Up @@ -55,7 +55,7 @@ module Data.Series.Unboxed (
G.convert,

-- * Mapping and filtering
map, mapWithKey, mapIndex, null, length,
map, mapWithKey, mapIndex, concatMap, null, length,
take, takeWhile, drop, dropWhile, filter, filterWithKey,
-- ** Mapping with effects
mapWithKeyM, mapWithKeyM_, forWithKeyM, forWithKeyM_,
Expand Down Expand Up @@ -106,7 +106,7 @@ import qualified Data.Series.Generic as G
import Data.Vector.Unboxed ( Vector, Unbox )
import qualified Data.Vector.Unboxed as Vector

import Prelude hiding ( map, zipWith, filter, foldMap, null, length, all, any, and, or
import Prelude hiding ( map, concatMap, zipWith, filter, foldMap, null, length, all, any, and, or
, sum, product, maximum, minimum, take, takeWhile, drop, dropWhile
, last, unzip, unzip3
)
Expand Down Expand Up @@ -313,6 +313,15 @@ mapIndex :: (Unbox a, Ord k, Ord g) => Series k a -> (k -> g) -> Series g a
mapIndex = G.mapIndex


-- | Map a function over all the elements of a 'Series' and concatenate the result into a single 'Series'.
concatMap :: (Unbox a, Unbox k, Unbox b, Ord k)
=> (a -> Series k b)
-> Series k a
-> Series k b
{-# INLINE concatMap #-}
concatMap = G.concatMap


-- | /O(n)/ Apply the monadic action to every element of a series and its
-- index, yielding a series of results.
mapWithKeyM :: (Unbox a, Unbox b, Monad m, Ord k) => (k -> a -> m b) -> Series k a -> m (Series k b)
Expand Down

0 comments on commit a031965

Please sign in to comment.