module Data.Series.Generic.Zip (
    zipWith, zipWithMatched, zipWithKey,
    zipWith3, zipWithMatched3, zipWithKey3,
    replace, (|->), (<-|),
    
    -- * Generalized zipping with strategies
    zipWithStrategy,
    zipWithStrategy3,
    ZipStrategy,
    skipStrategy,
    mapStrategy,
    constStrategy,

    -- * Special case of zipping monoids
    zipWithMonoid,
    esum, eproduct,

    -- * Unzipping
    unzip, unzip3,
) where

import qualified Data.Map.Strict                as Map
import           Data.Monoid                    ( Sum(..), Product(..) )
import           Data.Series.Generic.Definition ( Series(MkSeries, index, values) )
import qualified Data.Series.Generic.Definition as G
import           Data.Series.Generic.View       ( selectSubset, requireWith )
import           Data.Vector.Generic            ( Vector )
import qualified Data.Vector.Generic            as Vector
import qualified Data.Series.Index              as Index
import qualified Data.Series.Index.Internal     as Index.Internal
import           Prelude                        hiding ( zipWith, zipWith3, unzip, unzip3 ) 

-- $setup
-- >>> import qualified Data.Series as Series

infix 6 |->, <-|

-- | Apply a function elementwise to two series, matching elements
-- based on their keys. For keys present only in the left or right series, 
-- the value 'Nothing' is returned.
--
-- >>> let xs = Series.fromList [ ("alpha", 0::Int), ("beta", 1), ("gamma", 2) ]
-- >>> let ys = Series.fromList [ ("alpha", 10::Int), ("beta", 11), ("delta", 13) ]
-- >>> zipWith (+) xs ys
--   index |  values
--   ----- |  ------
-- "alpha" | Just 10
--  "beta" | Just 12
-- "delta" | Nothing
-- "gamma" | Nothing
--
-- To only combine elements where keys are in both series, see 'zipWithMatched'
zipWith :: (Vector v a, Vector v b, Vector v c, Vector v (Maybe c), Ord k) 
        => (a -> b -> c) -> Series v k a -> Series v k b -> Series v k (Maybe c)
zipWith :: forall (v :: * -> *) a b c k.
(Vector v a, Vector v b, Vector v c, Vector v (Maybe c), Ord k) =>
(a -> b -> c)
-> Series v k a -> Series v k b -> Series v k (Maybe c)
zipWith a -> b -> c
f Series v k a
left Series v k b
right
    = let matched :: Series v k c
matched = (a -> b -> c) -> Series v k a -> Series v k b -> Series v k c
forall (v :: * -> *) a b c k.
(Vector v a, Vector v b, Vector v c, Ord k) =>
(a -> b -> c) -> Series v k a -> Series v k b -> Series v k c
zipWithMatched a -> b -> c
f Series v k a
left Series v k b
right
          matchedKeys :: Index k
matchedKeys   = Series v k c -> Index k
forall {k1} (v :: k1 -> *) k2 (a :: k1). Series v k2 a -> Index k2
index Series v k c
matched
          allKeys :: Index k
allKeys       = Series v k a -> Index k
forall {k1} (v :: k1 -> *) k2 (a :: k1). Series v k2 a -> Index k2
index Series v k a
left Index k -> Index k -> Index k
forall k. Ord k => Index k -> Index k -> Index k
`Index.union` Series v k b -> Index k
forall {k1} (v :: k1 -> *) k2 (a :: k1). Series v k2 a -> Index k2
index Series v k b
right
          unmatchedKeys :: Index k
unmatchedKeys = Index k
allKeys Index k -> Index k -> Index k
forall k. Ord k => Index k -> Index k -> Index k
`Index.difference` Index k
matchedKeys
          unmatched :: Series v k (Maybe c)
unmatched     = Index k -> v (Maybe c) -> Series v k (Maybe c)
forall {k} (v :: k -> *) k1 (a :: k).
Index k1 -> v a -> Series v k1 a
MkSeries Index k
unmatchedKeys (Int -> Maybe c -> v (Maybe c)
forall (v :: * -> *) a. Vector v a => Int -> a -> v a
Vector.replicate (Index k -> Int
forall k. Index k -> Int
Index.size Index k
unmatchedKeys) Maybe c
forall a. Maybe a
Nothing)
       in (c -> Maybe c) -> Series v k c -> Series v k (Maybe c)
forall (v :: * -> *) a b k.
(Vector v a, Vector v b) =>
(a -> b) -> Series v k a -> Series v k b
G.map c -> Maybe c
forall a. a -> Maybe a
Just Series v k c
matched Series v k (Maybe c)
-> Series v k (Maybe c) -> Series v k (Maybe c)
forall a. Semigroup a => a -> a -> a
<> Series v k (Maybe c)
unmatched
{-# INLINABLE zipWith #-}


-- | Apply a function elementwise to three series, matching elements
-- based on their keys. For keys present only in the left or right series, 
-- the value 'Nothing' is returned.
--
-- >>> let xs = Series.fromList [ ("alpha", 0::Int),  ("beta", 1),   ("gamma", 2) ]
-- >>> let ys = Series.fromList [ ("alpha", 10::Int), ("beta", 11),  ("delta", 13) ]
-- >>> let zs = Series.fromList [ ("alpha", 20::Int), ("delta", 13), ("epsilon", 6) ]
-- >>> zipWith3 (\x y z -> x + y + z) xs ys zs
--     index |  values
--     ----- |  ------
--   "alpha" | Just 30
--    "beta" | Nothing
--   "delta" | Nothing
-- "epsilon" | Nothing
--   "gamma" | Nothing
--
-- To only combine elements where keys are in all series, see 'zipWithMatched3'
zipWith3 :: (Vector v a, Vector v b, Vector v c, Vector v d, Vector v (Maybe d), Ord k) 
         => (a -> b -> c -> d) 
         -> Series v k a 
         -> Series v k b 
         -> Series v k c 
         -> Series v k (Maybe d)
zipWith3 :: forall (v :: * -> *) a b c d k.
(Vector v a, Vector v b, Vector v c, Vector v d,
 Vector v (Maybe d), Ord k) =>
(a -> b -> c -> d)
-> Series v k a
-> Series v k b
-> Series v k c
-> Series v k (Maybe d)
zipWith3 a -> b -> c -> d
f Series v k a
left Series v k b
center Series v k c
right
    = let matched :: Series v k d
matched       = (a -> b -> c -> d)
-> Series v k a -> Series v k b -> Series v k c -> Series v k d
forall (v :: * -> *) a b c d k.
(Vector v a, Vector v b, Vector v c, Vector v d, Ord k) =>
(a -> b -> c -> d)
-> Series v k a -> Series v k b -> Series v k c -> Series v k d
zipWithMatched3 a -> b -> c -> d
f Series v k a
left Series v k b
center Series v k c
right
          matchedKeys :: Index k
matchedKeys   = Series v k d -> Index k
forall {k1} (v :: k1 -> *) k2 (a :: k1). Series v k2 a -> Index k2
index Series v k d
matched
          allKeys :: Index k
allKeys       = Series v k a -> Index k
forall {k1} (v :: k1 -> *) k2 (a :: k1). Series v k2 a -> Index k2
index Series v k a
left Index k -> Index k -> Index k
forall k. Ord k => Index k -> Index k -> Index k
`Index.union` Series v k b -> Index k
forall {k1} (v :: k1 -> *) k2 (a :: k1). Series v k2 a -> Index k2
index Series v k b
center Index k -> Index k -> Index k
forall k. Ord k => Index k -> Index k -> Index k
`Index.union` Series v k c -> Index k
forall {k1} (v :: k1 -> *) k2 (a :: k1). Series v k2 a -> Index k2
index Series v k c
right
          unmatchedKeys :: Index k
unmatchedKeys = Index k
allKeys Index k -> Index k -> Index k
forall k. Ord k => Index k -> Index k -> Index k
`Index.difference` Index k
matchedKeys
          unmatched :: Series v k (Maybe d)
unmatched     = Index k -> v (Maybe d) -> Series v k (Maybe d)
forall {k} (v :: k -> *) k1 (a :: k).
Index k1 -> v a -> Series v k1 a
MkSeries Index k
unmatchedKeys (Int -> Maybe d -> v (Maybe d)
forall (v :: * -> *) a. Vector v a => Int -> a -> v a
Vector.replicate (Index k -> Int
forall k. Index k -> Int
Index.size Index k
unmatchedKeys) Maybe d
forall a. Maybe a
Nothing)
       in (d -> Maybe d) -> Series v k d -> Series v k (Maybe d)
forall (v :: * -> *) a b k.
(Vector v a, Vector v b) =>
(a -> b) -> Series v k a -> Series v k b
G.map d -> Maybe d
forall a. a -> Maybe a
Just Series v k d
matched Series v k (Maybe d)
-> Series v k (Maybe d) -> Series v k (Maybe d)
forall a. Semigroup a => a -> a -> a
<> Series v k (Maybe d)
unmatched
{-# INLINABLE zipWith3 #-}



-- | Apply a function elementwise to two series, matching elements
-- based on their keys. Keys present only in the left or right series are dropped.
--
-- >>> let xs = Series.fromList [ ("alpha", 0::Int), ("beta", 1), ("gamma", 2) ]
-- >>> let ys = Series.fromList [ ("alpha", 10::Int), ("beta", 11), ("delta", 13) ]
-- >>> zipWithMatched (+) xs ys
--   index | values
--   ----- | ------
-- "alpha" |     10
--  "beta" |     12
--
-- To combine elements where keys are in either series, see 'zipWith'. To combine
-- three series, see 'zipWithMatched3'.
zipWithMatched :: (Vector v a, Vector v b, Vector v c, Ord k) 
               => (a -> b -> c) -> Series v k a -> Series v k b -> Series v k c
zipWithMatched :: forall (v :: * -> *) a b c k.
(Vector v a, Vector v b, Vector v c, Ord k) =>
(a -> b -> c) -> Series v k a -> Series v k b -> Series v k c
zipWithMatched a -> b -> c
f Series v k a
left Series v k b
right
    = let matchedKeys :: Index k
matchedKeys   = Series v k a -> Index k
forall {k1} (v :: k1 -> *) k2 (a :: k1). Series v k2 a -> Index k2
index Series v k a
left Index k -> Index k -> Index k
forall k. Ord k => Index k -> Index k -> Index k
`Index.intersection` Series v k b -> Index k
forall {k1} (v :: k1 -> *) k2 (a :: k1). Series v k2 a -> Index k2
index Series v k b
right
          -- Recall that `selectSubset` is a performance optimization
          -- and is generally unsafe to use; however, in this case, we know
          -- that `matchedKeys` are subsets of the index of both series
          (MkSeries Index k
_ !v a
xs) = Series v k a
left  Series v k a -> Index k -> Series v k a
forall (v :: * -> *) a k.
(Vector v a, Ord k) =>
Series v k a -> Index k -> Series v k a
`selectSubset` Index k
matchedKeys
          (MkSeries Index k
_ !v b
ys) = Series v k b
right Series v k b -> Index k -> Series v k b
forall (v :: * -> *) a k.
(Vector v a, Ord k) =>
Series v k a -> Index k -> Series v k a
`selectSubset` Index k
matchedKeys
          -- The following construction relies on the fact that keys are always sorted
       in Index k -> v c -> Series v k c
forall {k} (v :: k -> *) k1 (a :: k).
Index k1 -> v a -> Series v k1 a
MkSeries Index k
matchedKeys (v c -> Series v k c) -> v c -> Series v k c
forall a b. (a -> b) -> a -> b
$ (a -> b -> c) -> v a -> v b -> v c
forall (v :: * -> *) a b c.
(Vector v a, Vector v b, Vector v c) =>
(a -> b -> c) -> v a -> v b -> v c
Vector.zipWith a -> b -> c
f v a
xs v b
ys
{-# INLINABLE zipWithMatched #-}


-- | Apply a function elementwise to three series, matching elements
-- based on their keys. Keys not present in all three series are dropped.
--
-- >>> let xs = Series.fromList [ ("alpha", 0::Int),  ("beta", 1),   ("gamma", 2) ]
-- >>> let ys = Series.fromList [ ("alpha", 10::Int), ("beta", 11),  ("delta", 13) ]
-- >>> let zs = Series.fromList [ ("alpha", 20::Int), ("delta", 13), ("epsilon", 6) ]
-- >>> zipWithMatched3 (\x y z -> x + y + z) xs ys zs
--   index | values
--   ----- | ------
-- "alpha" |     30
zipWithMatched3 :: (Vector v a, Vector v b, Vector v c, Vector v d, Ord k) 
                => (a -> b -> c -> d) 
                -> Series v k a 
                -> Series v k b 
                -> Series v k c
                -> Series v k d
zipWithMatched3 :: forall (v :: * -> *) a b c d k.
(Vector v a, Vector v b, Vector v c, Vector v d, Ord k) =>
(a -> b -> c -> d)
-> Series v k a -> Series v k b -> Series v k c -> Series v k d
zipWithMatched3 a -> b -> c -> d
f Series v k a
left Series v k b
center Series v k c
right
    = let matchedKeys :: Index k
matchedKeys   = Series v k a -> Index k
forall {k1} (v :: k1 -> *) k2 (a :: k1). Series v k2 a -> Index k2
index Series v k a
left Index k -> Index k -> Index k
forall k. Ord k => Index k -> Index k -> Index k
`Index.intersection` Series v k b -> Index k
forall {k1} (v :: k1 -> *) k2 (a :: k1). Series v k2 a -> Index k2
index Series v k b
center Index k -> Index k -> Index k
forall k. Ord k => Index k -> Index k -> Index k
`Index.intersection` Series v k c -> Index k
forall {k1} (v :: k1 -> *) k2 (a :: k1). Series v k2 a -> Index k2
index Series v k c
right
          -- Recall that `selectSubset` is a performance optimization
          -- and is generally unsafe to use; however, in this case, we know
          -- that `matchedKeys` are subsets of the index of all series
          (MkSeries Index k
_ !v a
xs) = Series v k a
left   Series v k a -> Index k -> Series v k a
forall (v :: * -> *) a k.
(Vector v a, Ord k) =>
Series v k a -> Index k -> Series v k a
`selectSubset` Index k
matchedKeys
          (MkSeries Index k
_ !v b
ys) = Series v k b
center Series v k b -> Index k -> Series v k b
forall (v :: * -> *) a k.
(Vector v a, Ord k) =>
Series v k a -> Index k -> Series v k a
`selectSubset` Index k
matchedKeys
          (MkSeries Index k
_ !v c
zs) = Series v k c
right  Series v k c -> Index k -> Series v k c
forall (v :: * -> *) a k.
(Vector v a, Ord k) =>
Series v k a -> Index k -> Series v k a
`selectSubset` Index k
matchedKeys
          -- The following construction relies on the fact that keys are always sorted
       in Index k -> v d -> Series v k d
forall {k} (v :: k -> *) k1 (a :: k).
Index k1 -> v a -> Series v k1 a
MkSeries Index k
matchedKeys (v d -> Series v k d) -> v d -> Series v k d
forall a b. (a -> b) -> a -> b
$ (a -> b -> c -> d) -> v a -> v b -> v c -> v d
forall (v :: * -> *) a b c d.
(Vector v a, Vector v b, Vector v c, Vector v d) =>
(a -> b -> c -> d) -> v a -> v b -> v c -> v d
Vector.zipWith3 a -> b -> c -> d
f v a
xs v b
ys v c
zs
{-# INLINABLE zipWithMatched3 #-}


-- | Apply a function elementwise to two series, matching elements
-- based on their keys. Keys present only in the left or right series are dropped.
-- 
-- >>> let xs = Series.fromList [ ("alpha", 0::Int), ("beta", 1), ("gamma", 2) ]
-- >>> let ys = Series.fromList [ ("alpha", 10::Int), ("beta", 11), ("delta", 13) ]
-- >>> zipWithKey (\k x y -> length k + x + y) xs ys
--   index | values
--   ----- | ------
-- "alpha" |     15
--  "beta" |     16
--
-- To combine elements where keys are in either series, see 'zipWith'
zipWithKey :: (Vector v a, Vector v b, Vector v c, Vector v k, Ord k) 
           => (k -> a -> b -> c) -> Series v k a -> Series v k b -> Series v k c
zipWithKey :: forall (v :: * -> *) a b c k.
(Vector v a, Vector v b, Vector v c, Vector v k, Ord k) =>
(k -> a -> b -> c) -> Series v k a -> Series v k b -> Series v k c
zipWithKey k -> a -> b -> c
f Series v k a
left Series v k b
right
    = let matchedKeys :: Index k
matchedKeys   = Series v k a -> Index k
forall {k1} (v :: k1 -> *) k2 (a :: k1). Series v k2 a -> Index k2
index Series v k a
left Index k -> Index k -> Index k
forall k. Ord k => Index k -> Index k -> Index k
`Index.intersection` Series v k b -> Index k
forall {k1} (v :: k1 -> *) k2 (a :: k1). Series v k2 a -> Index k2
index Series v k b
right
          -- Recall that `selectSubset` is a performance optimization
          -- and is generally unsafe to use; however, in this case, we know
          -- that `matchedKeys` are subsets of the index of both series
          (MkSeries Index k
_ v a
xs) = Series v k a
left  Series v k a -> Index k -> Series v k a
forall (v :: * -> *) a k.
(Vector v a, Ord k) =>
Series v k a -> Index k -> Series v k a
`selectSubset` Index k
matchedKeys
          (MkSeries Index k
_ v b
ys) = Series v k b
right Series v k b -> Index k -> Series v k b
forall (v :: * -> *) a k.
(Vector v a, Ord k) =>
Series v k a -> Index k -> Series v k a
`selectSubset` Index k
matchedKeys
          ks :: v k
ks              = Index k -> v k
forall (v :: * -> *) k. Vector v k => Index k -> v k
Index.toAscVector Index k
matchedKeys
          -- The following construction relies on the fact that keys are always sorted
       in  Index k -> v c -> Series v k c
forall {k} (v :: k -> *) k1 (a :: k).
Index k1 -> v a -> Series v k1 a
MkSeries Index k
matchedKeys (v c -> Series v k c) -> v c -> Series v k c
forall a b. (a -> b) -> a -> b
$ (k -> a -> b -> c) -> v k -> v a -> v b -> v c
forall (v :: * -> *) a b c d.
(Vector v a, Vector v b, Vector v c, Vector v d) =>
(a -> b -> c -> d) -> v a -> v b -> v c -> v d
Vector.zipWith3 k -> a -> b -> c
f v k
ks v a
xs v b
ys
{-# INLINABLE zipWithKey #-}


-- | Apply a function elementwise to three series, matching elements
-- based on their keys. Keys not present in all series are dropped.
-- 
-- >>> let xs = Series.fromList [ ("alpha", 0::Int), ("beta", 1), ("gamma", 2) ]
-- >>> let ys = Series.fromList [ ("alpha", 10::Int), ("beta", 11), ("delta", 13) ]
-- >>> let zs = Series.fromList [ ("alpha", 20::Int), ("beta", 7), ("delta", 5) ]
-- >>> zipWithKey3 (\k x y z -> length k + x + y + z) xs ys zs
--   index | values
--   ----- | ------
-- "alpha" |     35
--  "beta" |     23

zipWithKey3 :: (Vector v a, Vector v b, Vector v c, Vector v d, Vector v k, Ord k) 
            => (k -> a -> b -> c -> d) 
            -> Series v k a 
            -> Series v k b 
            -> Series v k c
            -> Series v k d
zipWithKey3 :: forall (v :: * -> *) a b c d k.
(Vector v a, Vector v b, Vector v c, Vector v d, Vector v k,
 Ord k) =>
(k -> a -> b -> c -> d)
-> Series v k a -> Series v k b -> Series v k c -> Series v k d
zipWithKey3 k -> a -> b -> c -> d
f Series v k a
left Series v k b
center Series v k c
right
    = let matchedKeys :: Index k
matchedKeys   = Series v k a -> Index k
forall {k1} (v :: k1 -> *) k2 (a :: k1). Series v k2 a -> Index k2
index Series v k a
left Index k -> Index k -> Index k
forall k. Ord k => Index k -> Index k -> Index k
`Index.intersection` Series v k c -> Index k
forall {k1} (v :: k1 -> *) k2 (a :: k1). Series v k2 a -> Index k2
index Series v k c
right
          -- Recall that `selectSubset` is a performance optimization
          -- and is generally unsafe to use; however, in this case, we know
          -- that `matchedKeys` are subsets of the index of all series
          (MkSeries Index k
_ v a
xs) = Series v k a
left   Series v k a -> Index k -> Series v k a
forall (v :: * -> *) a k.
(Vector v a, Ord k) =>
Series v k a -> Index k -> Series v k a
`selectSubset` Index k
matchedKeys
          (MkSeries Index k
_ v b
ys) = Series v k b
center Series v k b -> Index k -> Series v k b
forall (v :: * -> *) a k.
(Vector v a, Ord k) =>
Series v k a -> Index k -> Series v k a
`selectSubset` Index k
matchedKeys
          (MkSeries Index k
_ v c
zs) = Series v k c
right  Series v k c -> Index k -> Series v k c
forall (v :: * -> *) a k.
(Vector v a, Ord k) =>
Series v k a -> Index k -> Series v k a
`selectSubset` Index k
matchedKeys
          ks :: v k
ks              = Index k -> v k
forall (v :: * -> *) k. Vector v k => Index k -> v k
Index.toAscVector Index k
matchedKeys
          -- The following construction relies on the fact that keys are always sorted
       in  Index k -> v d -> Series v k d
forall {k} (v :: k -> *) k1 (a :: k).
Index k1 -> v a -> Series v k1 a
MkSeries Index k
matchedKeys (v d -> Series v k d) -> v d -> Series v k d
forall a b. (a -> b) -> a -> b
$ (k -> a -> b -> c -> d) -> v k -> v a -> v b -> v c -> v d
forall (v :: * -> *) a b c d e.
(Vector v a, Vector v b, Vector v c, Vector v d, Vector v e) =>
(a -> b -> c -> d -> e) -> v a -> v b -> v c -> v d -> v e
Vector.zipWith4 k -> a -> b -> c -> d
f v k
ks v a
xs v b
ys v c
zs
{-# INLINABLE zipWithKey3 #-}


-- | Replace values from the right series with values from the left series at matching keys.
-- Keys in the right series but not in the right series are unaffected.
replace :: (Vector v a, Vector v Int, Ord k) 
        => Series v k a -> Series v k a -> Series v k a
{-# INLINABLE replace #-}
Series v k a
xs replace :: forall (v :: * -> *) a k.
(Vector v a, Vector v Int, Ord k) =>
Series v k a -> Series v k a -> Series v k a
`replace` Series v k a
ys 
    = let keysToReplace :: Index k
keysToReplace = Series v k a -> Index k
forall {k1} (v :: k1 -> *) k2 (a :: k1). Series v k2 a -> Index k2
index Series v k a
xs Index k -> Index k -> Index k
forall k. Ord k => Index k -> Index k -> Index k
`Index.intersection` Series v k a -> Index k
forall {k1} (v :: k1 -> *) k2 (a :: k1). Series v k2 a -> Index k2
index Series v k a
ys
          iixs :: v Int
iixs          = Index Int -> v Int
forall (v :: * -> *) k. Vector v k => Index k -> v k
Index.toAscVector (Index Int -> v Int) -> Index Int -> v Int
forall a b. (a -> b) -> a -> b
$ (k -> Int) -> Index k -> Index Int
forall k g. (k -> g) -> Index k -> Index g
Index.Internal.mapMonotonic (\k
k -> k -> Index k -> Int
forall k. (HasCallStack, Ord k) => k -> Index k -> Int
Index.Internal.findIndex k
k (Series v k a -> Index k
forall {k1} (v :: k1 -> *) k2 (a :: k1). Series v k2 a -> Index k2
index Series v k a
ys)) Index k
keysToReplace
       in Index k -> v a -> Series v k a
forall {k} (v :: k -> *) k1 (a :: k).
Index k1 -> v a -> Series v k1 a
MkSeries (Series v k a -> Index k
forall {k1} (v :: k1 -> *) k2 (a :: k1). Series v k2 a -> Index k2
index Series v k a
ys) (v a -> Series v k a) -> v a -> Series v k a
forall a b. (a -> b) -> a -> b
$ v a -> v Int -> v a -> v a
forall (v :: * -> *) a.
(Vector v a, Vector v Int) =>
v a -> v Int -> v a -> v a
Vector.update_ (Series v k a -> v a
forall {k1} (v :: k1 -> *) k2 (a :: k1). Series v k2 a -> v a
values Series v k a
ys) v Int
iixs (Series v k a -> v a
forall {k1} (v :: k1 -> *) k2 (a :: k1). Series v k2 a -> v a
values (Series v k a
xs Series v k a -> Index k -> Series v k a
forall (v :: * -> *) a k.
(Vector v a, Ord k) =>
Series v k a -> Index k -> Series v k a
`selectSubset` Index k
keysToReplace))


-- | Infix version of 'replace'
(|->) :: (Vector v a, Vector v Int, Ord k)
      => Series v k a -> Series v k a -> Series v k a
{-# INLINABLE (|->) #-}
|-> :: forall (v :: * -> *) a k.
(Vector v a, Vector v Int, Ord k) =>
Series v k a -> Series v k a -> Series v k a
(|->) = Series v k a -> Series v k a -> Series v k a
forall (v :: * -> *) a k.
(Vector v a, Vector v Int, Ord k) =>
Series v k a -> Series v k a -> Series v k a
replace


-- | Flipped version of '|->',
(<-|) :: (Vector v a, Vector v Int, Ord k) 
      => Series v k a -> Series v k a -> Series v k a
{-# INLINABLE (<-|)  #-}
<-| :: forall (v :: * -> *) a k.
(Vector v a, Vector v Int, Ord k) =>
Series v k a -> Series v k a -> Series v k a
(<-|) = (Series v k a -> Series v k a -> Series v k a)
-> Series v k a -> Series v k a -> Series v k a
forall a b c. (a -> b -> c) -> b -> a -> c
flip Series v k a -> Series v k a -> Series v k a
forall (v :: * -> *) a k.
(Vector v a, Vector v Int, Ord k) =>
Series v k a -> Series v k a -> Series v k a
replace


-- | A 'ZipStrategy' is a function which is used to decide what to do when a key is missing from one
-- of two 'Series' being zipped together with 'zipWithStrategy'.
--
-- If a 'ZipStrategy' returns 'Nothing', the key is dropped.
-- If a 'ZipStrategy' returns @'Just' v@ for key @k@, then the value @v@ is inserted at key @k@.
--
-- For example, the most basic 'ZipStrategy' is to skip over any key which is missing from the other series.
-- Such a strategy can be written as @skip key value = 'Nothing'@ (see 'skipStrategy').
type ZipStrategy k a b = (k -> a -> Maybe b)


-- | This 'ZipStrategy' drops keys which are not present in both 'Series'.
--
-- >>> let xs = Series.fromList [ ("alpha", 0::Int), ("beta", 1), ("gamma", 2) ]
-- >>> let ys = Series.fromList [ ("alpha", 10::Int), ("beta", 11), ("delta", 13) ]
-- >>> zipWithStrategy (+) skipStrategy skipStrategy xs ys
--   index | values
--   ----- | ------
-- "alpha" |     10
--  "beta" |     12
skipStrategy :: ZipStrategy k a b
skipStrategy :: forall k a b. ZipStrategy k a b
skipStrategy k
_ a
_ = Maybe b
forall a. Maybe a
Nothing
{-# INLINABLE skipStrategy #-}


-- | This 'ZipStrategy' sets the value at keys which are not present in both 'Series' 
-- to the some mapping from the value present in one of the series. See the example below.
--
-- >>> let xs = Series.fromList [ ("alpha", 0::Int), ("beta", 1), ("gamma", 2) ]
-- >>> let ys = Series.fromList [ ("alpha", 5::Int), ("beta", 6), ("delta", 7) ]
-- >>> zipWithStrategy (+) (mapStrategy id) (mapStrategy (*10)) xs ys
--   index | values
--   ----- | ------
-- "alpha" |      5
--  "beta" |      7
-- "delta" |     70
-- "gamma" |      2
mapStrategy :: (a -> b) -> ZipStrategy k a b
mapStrategy :: forall a b k. (a -> b) -> ZipStrategy k a b
mapStrategy a -> b
f k
_ a
x = b -> Maybe b
forall a. a -> Maybe a
Just (a -> b
f a
x)
{-# INLINABLE mapStrategy #-}


-- | This 'ZipStrategy' sets a constant value at keys which are not present in both 'Series'.
--
-- >>> let xs = Series.fromList [ ("alpha", 0::Int), ("beta", 1), ("gamma", 2) ]
-- >>> let ys = Series.fromList [ ("alpha", 10::Int), ("beta", 11), ("delta", 13) ]
-- >>> zipWith (+) xs ys
--   index |  values
--   ----- |  ------
-- "alpha" | Just 10
--  "beta" | Just 12
-- "delta" | Nothing
-- "gamma" | Nothing
-- >>> zipWithStrategy (+) (constStrategy (-100)) (constStrategy 200)  xs ys
--   index | values
--   ----- | ------
-- "alpha" |     10
--  "beta" |     12
-- "delta" |    200
-- "gamma" |   -100
constStrategy :: b -> ZipStrategy k a b
constStrategy :: forall b k a. b -> ZipStrategy k a b
constStrategy b
v = (a -> b) -> ZipStrategy k a b
forall a b k. (a -> b) -> ZipStrategy k a b
mapStrategy (b -> a -> b
forall a b. a -> b -> a
const b
v)
{-# INLINABLE constStrategy #-}


-- | Zip two 'Series' with a combining function, applying a 'ZipStrategy' when one key is present in one of the 'Series' but not both.
--
-- Note that if you want to drop keys missing in either 'Series', it is faster to use @'zipWithMatched' f@ 
-- than using @'zipWithStrategy' f skipStrategy skipStrategy@.
zipWithStrategy :: (Vector v a, Vector v b, Vector v c, Ord k) 
                => (a -> b -> c)     -- ^ Function to combine values when present in both series
                -> ZipStrategy k a c -- ^ Strategy for when the key is in the left series but not the right
                -> ZipStrategy k b c -- ^ Strategy for when the key is in the right series but not the left
                -> Series v k a
                -> Series v k b 
                -> Series v k c
zipWithStrategy :: forall (v :: * -> *) a b c k.
(Vector v a, Vector v b, Vector v c, Ord k) =>
(a -> b -> c)
-> ZipStrategy k a c
-> ZipStrategy k b c
-> Series v k a
-> Series v k b
-> Series v k c
zipWithStrategy a -> b -> c
f ZipStrategy k a c
whenLeft ZipStrategy k b c
whenRight Series v k a
left Series v k b
right 
    = let onlyLeftKeys :: Index k
onlyLeftKeys  = Series v k a -> Index k
forall {k1} (v :: k1 -> *) k2 (a :: k1). Series v k2 a -> Index k2
index Series v k a
left  Index k -> Index k -> Index k
forall k. Ord k => Index k -> Index k -> Index k
`Index.difference` Series v k b -> Index k
forall {k1} (v :: k1 -> *) k2 (a :: k1). Series v k2 a -> Index k2
index Series v k b
right
          onlyRightKeys :: Index k
onlyRightKeys = Series v k b -> Index k
forall {k1} (v :: k1 -> *) k2 (a :: k1). Series v k2 a -> Index k2
index Series v k b
right Index k -> Index k -> Index k
forall k. Ord k => Index k -> Index k -> Index k
`Index.difference` Series v k a -> Index k
forall {k1} (v :: k1 -> *) k2 (a :: k1). Series v k2 a -> Index k2
index Series v k a
left
          -- Recall that `selectSubset` is a performance optimization
          -- and is generally unsafe to use; however, in this case, we know
          -- that `matchedKeys` are subsets of the index of both series
          leftZip :: Series v k c
leftZip =  ZipStrategy k a c -> Series v k a -> Series v k c
forall {k} {k} {k} {b} {v :: k -> *} {k1} {a :: k} {a}
       {v :: k -> *} {k1} {a :: k}.
(IsSeries (Map k b) v k1 a, IsSeries (Map k a) v k1 a) =>
(k -> a -> Maybe b) -> Series v k1 a -> Series v k1 a
applyStrategy ZipStrategy k a c
whenLeft  (Series v k a -> Series v k c) -> Series v k a -> Series v k c
forall a b. (a -> b) -> a -> b
$ Series v k a
left  Series v k a -> Index k -> Series v k a
forall (v :: * -> *) a k.
(Vector v a, Ord k) =>
Series v k a -> Index k -> Series v k a
`selectSubset` Index k
onlyLeftKeys
          rightZip :: Series v k c
rightZip = ZipStrategy k b c -> Series v k b -> Series v k c
forall {k} {k} {k} {b} {v :: k -> *} {k1} {a :: k} {a}
       {v :: k -> *} {k1} {a :: k}.
(IsSeries (Map k b) v k1 a, IsSeries (Map k a) v k1 a) =>
(k -> a -> Maybe b) -> Series v k1 a -> Series v k1 a
applyStrategy ZipStrategy k b c
whenRight (Series v k b -> Series v k c) -> Series v k b -> Series v k c
forall a b. (a -> b) -> a -> b
$ Series v k b
right Series v k b -> Index k -> Series v k b
forall (v :: * -> *) a k.
(Vector v a, Ord k) =>
Series v k a -> Index k -> Series v k a
`selectSubset` Index k
onlyRightKeys
          
        in (a -> b -> c) -> Series v k a -> Series v k b -> Series v k c
forall (v :: * -> *) a b c k.
(Vector v a, Vector v b, Vector v c, Ord k) =>
(a -> b -> c) -> Series v k a -> Series v k b -> Series v k c
zipWithMatched a -> b -> c
f Series v k a
left Series v k b
right Series v k c -> Series v k c -> Series v k c
forall a. Semigroup a => a -> a -> a
<> Series v k c
leftZip Series v k c -> Series v k c -> Series v k c
forall a. Semigroup a => a -> a -> a
<> Series v k c
rightZip
    where
        -- Application of the 'ZipStrategy' is done on a `Map` rather than
        -- the 'Series' directly to keep the type contraints of `zipWithStrategy` to
        -- a minimum. Recall that unboxed 'Series' cannot contain `Maybe a`.  
        applyStrategy :: (k -> a -> Maybe b) -> Series v k1 a -> Series v k1 a
applyStrategy k -> a -> Maybe b
strat = Map k b -> Series v k1 a
forall {k} t (v :: k -> *) k1 (a :: k).
IsSeries t v k1 a =>
t -> Series v k1 a
G.toSeries 
                            (Map k b -> Series v k1 a)
-> (Series v k1 a -> Map k b) -> Series v k1 a -> Series v k1 a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (k -> a -> Maybe b) -> Map k a -> Map k b
forall k a b. (k -> a -> Maybe b) -> Map k a -> Map k b
Map.mapMaybeWithKey k -> a -> Maybe b
strat
                            (Map k a -> Map k b)
-> (Series v k1 a -> Map k a) -> Series v k1 a -> Map k b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Series v k1 a -> Map k a
forall {k} t (v :: k -> *) k1 (a :: k).
IsSeries t v k1 a =>
Series v k1 a -> t
G.fromSeries
{-# INLINABLE zipWithStrategy #-}


-- | Zip three 'Series' with a combining function, applying a 'ZipStrategy' when one key is 
-- present in one of the 'Series' but not all of the others.
--
-- Note that if you want to drop keys missing in either 'Series', it is faster to use @'zipWithMatched3' f@ 
-- than using @'zipWithStrategy3' f skipStrategy skipStrategy skipStrategy@.
zipWithStrategy3 :: (Vector v a, Vector v b, Vector v c, Vector v d, Ord k) 
                => (a -> b -> c -> d) -- ^ Function to combine values when present in all series
                -> ZipStrategy k a d  -- ^ Strategy for when the key is in the left series but not in all the others
                -> ZipStrategy k b d  -- ^ Strategy for when the key is in the center series but not in all the others
                -> ZipStrategy k c d  -- ^ Strategy for when the key is in the right series but not in all the others
                -> Series v k a
                -> Series v k b 
                -> Series v k c
                -> Series v k d
zipWithStrategy3 :: forall (v :: * -> *) a b c d k.
(Vector v a, Vector v b, Vector v c, Vector v d, Ord k) =>
(a -> b -> c -> d)
-> ZipStrategy k a d
-> ZipStrategy k b d
-> ZipStrategy k c d
-> Series v k a
-> Series v k b
-> Series v k c
-> Series v k d
zipWithStrategy3 a -> b -> c -> d
f ZipStrategy k a d
whenLeft ZipStrategy k b d
whenCenter ZipStrategy k c d
whenRight Series v k a
left Series v k b
center Series v k c
right 
    = let onlyLeftKeys :: Index k
onlyLeftKeys  = Series v k a -> Index k
forall {k1} (v :: k1 -> *) k2 (a :: k1). Series v k2 a -> Index k2
index Series v k a
left    Index k -> Index k -> Index k
forall k. Ord k => Index k -> Index k -> Index k
`Index.difference` (Series v k b -> Index k
forall {k1} (v :: k1 -> *) k2 (a :: k1). Series v k2 a -> Index k2
index Series v k b
center Index k -> Index k -> Index k
forall k. Ord k => Index k -> Index k -> Index k
`Index.union` Series v k c -> Index k
forall {k1} (v :: k1 -> *) k2 (a :: k1). Series v k2 a -> Index k2
index Series v k c
right)
          onlyCenterKeys :: Index k
onlyCenterKeys = Series v k b -> Index k
forall {k1} (v :: k1 -> *) k2 (a :: k1). Series v k2 a -> Index k2
index Series v k b
center Index k -> Index k -> Index k
forall k. Ord k => Index k -> Index k -> Index k
`Index.difference` (Series v k a -> Index k
forall {k1} (v :: k1 -> *) k2 (a :: k1). Series v k2 a -> Index k2
index Series v k a
left   Index k -> Index k -> Index k
forall k. Ord k => Index k -> Index k -> Index k
`Index.union` Series v k c -> Index k
forall {k1} (v :: k1 -> *) k2 (a :: k1). Series v k2 a -> Index k2
index Series v k c
right)
          onlyRightKeys :: Index k
onlyRightKeys = Series v k c -> Index k
forall {k1} (v :: k1 -> *) k2 (a :: k1). Series v k2 a -> Index k2
index Series v k c
right   Index k -> Index k -> Index k
forall k. Ord k => Index k -> Index k -> Index k
`Index.difference` (Series v k b -> Index k
forall {k1} (v :: k1 -> *) k2 (a :: k1). Series v k2 a -> Index k2
index Series v k b
center Index k -> Index k -> Index k
forall k. Ord k => Index k -> Index k -> Index k
`Index.union` Series v k a -> Index k
forall {k1} (v :: k1 -> *) k2 (a :: k1). Series v k2 a -> Index k2
index Series v k a
left)
          -- Recall that `selectSubset` is a performance optimization
          -- and is generally unsafe to use; however, in this case, we know
          -- that `matchedKeys` are subsets of the index of all series
          leftZip :: Series v k d
leftZip =  ZipStrategy k a d -> Series v k a -> Series v k d
forall {k} {k} {k} {b} {v :: k -> *} {k1} {a :: k} {a}
       {v :: k -> *} {k1} {a :: k}.
(IsSeries (Map k b) v k1 a, IsSeries (Map k a) v k1 a) =>
(k -> a -> Maybe b) -> Series v k1 a -> Series v k1 a
applyStrategy ZipStrategy k a d
whenLeft  (Series v k a -> Series v k d) -> Series v k a -> Series v k d
forall a b. (a -> b) -> a -> b
$ Series v k a
left     Series v k a -> Index k -> Series v k a
forall (v :: * -> *) a k.
(Vector v a, Ord k) =>
Series v k a -> Index k -> Series v k a
`selectSubset` Index k
onlyLeftKeys
          centerZip :: Series v k d
centerZip = ZipStrategy k b d -> Series v k b -> Series v k d
forall {k} {k} {k} {b} {v :: k -> *} {k1} {a :: k} {a}
       {v :: k -> *} {k1} {a :: k}.
(IsSeries (Map k b) v k1 a, IsSeries (Map k a) v k1 a) =>
(k -> a -> Maybe b) -> Series v k1 a -> Series v k1 a
applyStrategy ZipStrategy k b d
whenCenter (Series v k b -> Series v k d) -> Series v k b -> Series v k d
forall a b. (a -> b) -> a -> b
$ Series v k b
center Series v k b -> Index k -> Series v k b
forall (v :: * -> *) a k.
(Vector v a, Ord k) =>
Series v k a -> Index k -> Series v k a
`selectSubset` Index k
onlyCenterKeys
          rightZip :: Series v k d
rightZip = ZipStrategy k c d -> Series v k c -> Series v k d
forall {k} {k} {k} {b} {v :: k -> *} {k1} {a :: k} {a}
       {v :: k -> *} {k1} {a :: k}.
(IsSeries (Map k b) v k1 a, IsSeries (Map k a) v k1 a) =>
(k -> a -> Maybe b) -> Series v k1 a -> Series v k1 a
applyStrategy ZipStrategy k c d
whenRight (Series v k c -> Series v k d) -> Series v k c -> Series v k d
forall a b. (a -> b) -> a -> b
$ Series v k c
right    Series v k c -> Index k -> Series v k c
forall (v :: * -> *) a k.
(Vector v a, Ord k) =>
Series v k a -> Index k -> Series v k a
`selectSubset` Index k
onlyRightKeys
          
        in (a -> b -> c -> d)
-> Series v k a -> Series v k b -> Series v k c -> Series v k d
forall (v :: * -> *) a b c d k.
(Vector v a, Vector v b, Vector v c, Vector v d, Ord k) =>
(a -> b -> c -> d)
-> Series v k a -> Series v k b -> Series v k c -> Series v k d
zipWithMatched3 a -> b -> c -> d
f Series v k a
left Series v k b
center Series v k c
right Series v k d -> Series v k d -> Series v k d
forall a. Semigroup a => a -> a -> a
<> Series v k d
leftZip Series v k d -> Series v k d -> Series v k d
forall a. Semigroup a => a -> a -> a
<> Series v k d
centerZip Series v k d -> Series v k d -> Series v k d
forall a. Semigroup a => a -> a -> a
<> Series v k d
rightZip
    where
        -- Application of the 'ZipStrategy' is done on a `Map` rather than
        -- the 'Series' directly to keep the type contraints of `zipWithStrategy` to
        -- a minimum. Recall that unboxed 'Series' cannot contain `Maybe a`.  
        applyStrategy :: (k -> a -> Maybe b) -> Series v k1 a -> Series v k1 a
applyStrategy k -> a -> Maybe b
strat = Map k b -> Series v k1 a
forall {k} t (v :: k -> *) k1 (a :: k).
IsSeries t v k1 a =>
t -> Series v k1 a
G.toSeries 
                            (Map k b -> Series v k1 a)
-> (Series v k1 a -> Map k b) -> Series v k1 a -> Series v k1 a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (k -> a -> Maybe b) -> Map k a -> Map k b
forall k a b. (k -> a -> Maybe b) -> Map k a -> Map k b
Map.mapMaybeWithKey k -> a -> Maybe b
strat
                            (Map k a -> Map k b)
-> (Series v k1 a -> Map k a) -> Series v k1 a -> Map k b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Series v k1 a -> Map k a
forall {k} t (v :: k -> *) k1 (a :: k).
IsSeries t v k1 a =>
Series v k1 a -> t
G.fromSeries
{-# INLINABLE zipWithStrategy3 #-}


-- | Zip two 'Series' with a combining function. The value for keys which are missing from
-- either 'Series' is replaced with the appropriate 'mempty' value.
--
-- >>> import Data.Monoid ( Sum(..) )
-- >>> let xs = Series.fromList [ ("2023-01-01", Sum (1::Int)), ("2023-01-02", Sum 2) ]
-- >>> let ys = Series.fromList [ ("2023-01-01", Sum (5::Int)), ("2023-01-03", Sum 7) ]
-- >>> zipWith (<>) xs ys
--        index |                  values
--        ----- |                  ------
-- "2023-01-01" | Just (Sum {getSum = 6})
-- "2023-01-02" |                 Nothing
-- "2023-01-03" |                 Nothing
-- >>> zipWithMonoid (<>) xs ys
--        index |           values
--        ----- |           ------
-- "2023-01-01" | Sum {getSum = 6}
-- "2023-01-02" | Sum {getSum = 2}
-- "2023-01-03" | Sum {getSum = 7}
zipWithMonoid :: ( Monoid a, Monoid b
                 , Vector v a, Vector v b, Vector v c
                 , Ord k
                 ) 
              => (a -> b -> c)
              -> Series v k a
              -> Series v k b 
              -> Series v k c
zipWithMonoid :: forall a b (v :: * -> *) c k.
(Monoid a, Monoid b, Vector v a, Vector v b, Vector v c, Ord k) =>
(a -> b -> c) -> Series v k a -> Series v k b -> Series v k c
zipWithMonoid a -> b -> c
f Series v k a
left Series v k b
right 
    = let fullindex :: Index k
fullindex = Series v k a -> Index k
forall {k1} (v :: k1 -> *) k2 (a :: k1). Series v k2 a -> Index k2
index Series v k a
left Index k -> Index k -> Index k
forall k. Ord k => Index k -> Index k -> Index k
`Index.union` Series v k b -> Index k
forall {k1} (v :: k1 -> *) k2 (a :: k1). Series v k2 a -> Index k2
index Series v k b
right
          (MkSeries Index k
ix v a
ls) = (k -> a) -> (a -> a) -> Series v k a -> Index k -> Series v k a
forall (v :: * -> *) a b k.
(Vector v a, Vector v b, Ord k) =>
(k -> b) -> (a -> b) -> Series v k a -> Index k -> Series v k b
requireWith (a -> k -> a
forall a b. a -> b -> a
const a
forall a. Monoid a => a
mempty) a -> a
forall a. a -> a
id Series v k a
left  Index k
fullindex
          (MkSeries Index k
_ v b
rs)  = (k -> b) -> (b -> b) -> Series v k b -> Index k -> Series v k b
forall (v :: * -> *) a b k.
(Vector v a, Vector v b, Ord k) =>
(k -> b) -> (a -> b) -> Series v k a -> Index k -> Series v k b
requireWith (b -> k -> b
forall a b. a -> b -> a
const b
forall a. Monoid a => a
mempty) b -> b
forall a. a -> a
id Series v k b
right Index k
fullindex          
        in Index k -> v c -> Series v k c
forall {k} (v :: k -> *) k1 (a :: k).
Index k1 -> v a -> Series v k1 a
MkSeries Index k
ix (v c -> Series v k c) -> v c -> Series v k c
forall a b. (a -> b) -> a -> b
$ (a -> b -> c) -> v a -> v b -> v c
forall (v :: * -> *) a b c.
(Vector v a, Vector v b, Vector v c) =>
(a -> b -> c) -> v a -> v b -> v c
Vector.zipWith a -> b -> c
f v a
ls v b
rs
{-# INLINABLE zipWithMonoid #-}


-- | Elementwise sum of two 'Series'. Elements missing in one or the other 'Series' is considered 0. 
--
-- >>> let xs = Series.fromList [ ("2023-01-01", (1::Int)), ("2023-01-02", 2) ]
-- >>> let ys = Series.fromList [ ("2023-01-01", (5::Int)), ("2023-01-03", 7) ]
-- >>> xs `esum` ys
--        index | values
--        ----- | ------
-- "2023-01-01" |      6
-- "2023-01-02" |      2
-- "2023-01-03" |      7
esum :: (Ord k, Num a, Vector v a, Vector v (Sum a)) 
     => Series v k a 
     -> Series v k a
     -> Series v k a
esum :: forall k a (v :: * -> *).
(Ord k, Num a, Vector v a, Vector v (Sum a)) =>
Series v k a -> Series v k a -> Series v k a
esum Series v k a
ls Series v k a
rs = (Sum a -> a) -> Series v k (Sum a) -> Series v k a
forall (v :: * -> *) a b k.
(Vector v a, Vector v b) =>
(a -> b) -> Series v k a -> Series v k b
G.map Sum a -> a
forall a. Sum a -> a
getSum (Series v k (Sum a) -> Series v k a)
-> Series v k (Sum a) -> Series v k a
forall a b. (a -> b) -> a -> b
$ (Sum a -> Sum a -> Sum a)
-> Series v k (Sum a) -> Series v k (Sum a) -> Series v k (Sum a)
forall a b (v :: * -> *) c k.
(Monoid a, Monoid b, Vector v a, Vector v b, Vector v c, Ord k) =>
(a -> b -> c) -> Series v k a -> Series v k b -> Series v k c
zipWithMonoid Sum a -> Sum a -> Sum a
forall a. Semigroup a => a -> a -> a
(<>) ((a -> Sum a) -> Series v k a -> Series v k (Sum a)
forall (v :: * -> *) a b k.
(Vector v a, Vector v b) =>
(a -> b) -> Series v k a -> Series v k b
G.map a -> Sum a
forall a. a -> Sum a
Sum Series v k a
ls) ((a -> Sum a) -> Series v k a -> Series v k (Sum a)
forall (v :: * -> *) a b k.
(Vector v a, Vector v b) =>
(a -> b) -> Series v k a -> Series v k b
G.map a -> Sum a
forall a. a -> Sum a
Sum Series v k a
rs)
{-# INLINABLE esum #-}


-- | Elementwise product of two 'Series'. Elements missing in one or the other 'Series' is considered 1. 
--
-- >>> let xs = Series.fromList [ ("2023-01-01", (2::Int)), ("2023-01-02", 3) ]
-- >>> let ys = Series.fromList [ ("2023-01-01", (5::Int)), ("2023-01-03", 7) ]
-- >>> xs `eproduct` ys
--        index | values
--        ----- | ------
-- "2023-01-01" |     10
-- "2023-01-02" |      3
-- "2023-01-03" |      7
eproduct :: (Ord k, Num a, Vector v a, Vector v (Product a)) 
         => Series v k a 
         -> Series v k a
         -> Series v k a
eproduct :: forall k a (v :: * -> *).
(Ord k, Num a, Vector v a, Vector v (Product a)) =>
Series v k a -> Series v k a -> Series v k a
eproduct Series v k a
ls Series v k a
rs = (Product a -> a) -> Series v k (Product a) -> Series v k a
forall (v :: * -> *) a b k.
(Vector v a, Vector v b) =>
(a -> b) -> Series v k a -> Series v k b
G.map Product a -> a
forall a. Product a -> a
getProduct (Series v k (Product a) -> Series v k a)
-> Series v k (Product a) -> Series v k a
forall a b. (a -> b) -> a -> b
$ (Product a -> Product a -> Product a)
-> Series v k (Product a)
-> Series v k (Product a)
-> Series v k (Product a)
forall a b (v :: * -> *) c k.
(Monoid a, Monoid b, Vector v a, Vector v b, Vector v c, Ord k) =>
(a -> b -> c) -> Series v k a -> Series v k b -> Series v k c
zipWithMonoid Product a -> Product a -> Product a
forall a. Semigroup a => a -> a -> a
(<>) ((a -> Product a) -> Series v k a -> Series v k (Product a)
forall (v :: * -> *) a b k.
(Vector v a, Vector v b) =>
(a -> b) -> Series v k a -> Series v k b
G.map a -> Product a
forall a. a -> Product a
Product Series v k a
ls) ((a -> Product a) -> Series v k a -> Series v k (Product a)
forall (v :: * -> *) a b k.
(Vector v a, Vector v b) =>
(a -> b) -> Series v k a -> Series v k b
G.map a -> Product a
forall a. a -> Product a
Product Series v k a
rs)
{-# INLINABLE eproduct #-}


-- | \(O(n)\) Unzip a 'Series' of 2-tuples.
unzip :: (Vector v a, Vector v b, Vector v (a, b)) 
      => Series v k (a, b)
      -> ( Series v k a
         , Series v k b
         )
unzip :: forall (v :: * -> *) a b k.
(Vector v a, Vector v b, Vector v (a, b)) =>
Series v k (a, b) -> (Series v k a, Series v k b)
unzip (MkSeries Index k
ix v (a, b)
vs) 
    = let (v a
left, v b
right) = v (a, b) -> (v a, v b)
forall (v :: * -> *) a b.
(Vector v a, Vector v b, Vector v (a, b)) =>
v (a, b) -> (v a, v b)
Vector.unzip v (a, b)
vs
       in (Index k -> v a -> Series v k a
forall {k} (v :: k -> *) k1 (a :: k).
Index k1 -> v a -> Series v k1 a
MkSeries Index k
ix v a
left, Index k -> v b -> Series v k b
forall {k} (v :: k -> *) k1 (a :: k).
Index k1 -> v a -> Series v k1 a
MkSeries Index k
ix v b
right)
{-# INLINABLE unzip #-}


-- | \(O(n)\) Unzip a 'Series' of 3-tuples.
unzip3 :: (Vector v a, Vector v b, Vector v c, Vector v (a, b, c)) 
       => Series v k (a, b, c)
       -> ( Series v k a
          , Series v k b
          , Series v k c
          )
unzip3 :: forall (v :: * -> *) a b c k.
(Vector v a, Vector v b, Vector v c, Vector v (a, b, c)) =>
Series v k (a, b, c) -> (Series v k a, Series v k b, Series v k c)
unzip3 (MkSeries Index k
ix v (a, b, c)
vs) 
    = let (v a
left, v b
center, v c
right) = v (a, b, c) -> (v a, v b, v c)
forall (v :: * -> *) a b c.
(Vector v a, Vector v b, Vector v c, Vector v (a, b, c)) =>
v (a, b, c) -> (v a, v b, v c)
Vector.unzip3 v (a, b, c)
vs
       in (Index k -> v a -> Series v k a
forall {k} (v :: k -> *) k1 (a :: k).
Index k1 -> v a -> Series v k1 a
MkSeries Index k
ix v a
left, Index k -> v b -> Series v k b
forall {k} (v :: k -> *) k1 (a :: k).
Index k1 -> v a -> Series v k1 a
MkSeries Index k
ix v b
center, Index k -> v c -> Series v k c
forall {k} (v :: k -> *) k1 (a :: k).
Index k1 -> v a -> Series v k1 a
MkSeries Index k
ix v c
right)
{-# INLINABLE unzip3 #-}