module Data.Series (
Series, index, values,
singleton, fromIndex,
fromList, toList,
fromVector, toVector,
Occurrence, fromListDuplicates, fromVectorDuplicates,
fromStrictMap, toStrictMap,
fromLazyMap, toLazyMap,
IsSeries(..),
G.convert,
map, mapWithKey, mapIndex, concatMap,
take, takeWhile, drop, dropWhile, filter, filterWithKey,
mapWithKeyM, mapWithKeyM_, forWithKeyM, forWithKeyM_, traverseWithKey,
zipWith, zipWithMatched, zipWithKey,
zipWith3, zipWithMatched3, zipWithKey3,
ZipStrategy, skipStrategy, mapStrategy, constStrategy, zipWithStrategy, zipWithStrategy3,
zipWithMonoid, esum, eproduct, unzip, unzip3,
require, catMaybes, dropIndex,
select, selectWhere, Range, to, from, upto, Selection,
at, iat,
replace, (|->), (<-|),
forwardFill,
groupBy, Grouping, aggregateWith, foldWith,
windowing, expanding,
fold, foldM, foldWithKey, foldMWithKey, foldMapWithKey,
G.mean, G.variance, G.std,
length, null, all, any, and, or, sum, product, maximum, maximumOn, minimum, minimumOn,
argmin, argmax,
postscanl, prescanl,
display, displayWith,
noLongerThan,
DisplayOptions(..), G.defaultDisplayOptions
) where
import Control.Foldl ( Fold, FoldM )
import qualified Data.Map.Lazy as ML
import qualified Data.Map.Strict as MS
import Data.Series.Index ( Index )
import Data.Series.Generic ( IsSeries(..), Range, Selection, ZipStrategy, Occurrence, DisplayOptions(..)
, to, from, upto, skipStrategy, mapStrategy, constStrategy, noLongerThan
)
import qualified Data.Series.Generic as G
import Data.Vector ( Vector )
import Prelude hiding ( map, concatMap, zipWith, zipWith3, filter, take, takeWhile, drop, dropWhile, last, unzip, unzip3
, length, null, all, any, and, or, sum, product, maximum, minimum,
)
infixl 1 `select`
infix 6 |->, <-|
type Series = G.Series Vector
index :: Series k a -> Index k
{-# INLINE index #-}
index :: forall k a. Series k a -> Index k
index = Series Vector k a -> Index k
forall {k1} (v :: k1 -> *) k2 (a :: k1). Series v k2 a -> Index k2
G.index
values :: Series k a -> Vector a
{-# INLINE values #-}
values :: forall k a. Series k a -> Vector a
values = Series Vector k a -> Vector a
forall {k1} (v :: k1 -> *) k2 (a :: k1). Series v k2 a -> v a
G.values
singleton :: k -> a -> Series k a
{-# INLINE singleton #-}
singleton :: forall k a. k -> a -> Series k a
singleton = k -> a -> Series Vector k a
forall (v :: * -> *) a k. Vector v a => k -> a -> Series v k a
G.singleton
fromIndex :: (k -> a) -> Index k -> Series k a
{-# INLINE fromIndex #-}
fromIndex :: forall k a. (k -> a) -> Index k -> Series k a
fromIndex = (k -> a) -> Index k -> Series Vector k a
forall (v :: * -> *) a k.
Vector v a =>
(k -> a) -> Index k -> Series v k a
G.fromIndex
fromList :: Ord k => [(k, a)] -> Series k a
{-# INLINE fromList #-}
fromList :: forall k a. Ord k => [(k, a)] -> Series k a
fromList = [(k, a)] -> Series Vector k a
forall (v :: * -> *) a k.
(Vector v a, Ord k) =>
[(k, a)] -> Series v k a
G.fromList
fromListDuplicates :: Ord k => [(k, a)] -> Series (k, Occurrence) a
{-# INLINE fromListDuplicates #-}
fromListDuplicates :: forall k a. Ord k => [(k, a)] -> Series (k, Occurrence) a
fromListDuplicates = [(k, a)] -> Series Vector (k, Occurrence) a
forall (v :: * -> *) a k.
(Vector v a, Ord k) =>
[(k, a)] -> Series v (k, Occurrence) a
G.fromListDuplicates
toList :: Series k a -> [(k, a)]
{-# INLINE toList #-}
toList :: forall k a. Series k a -> [(k, a)]
toList = Series Vector k a -> [(k, a)]
forall (v :: * -> *) a k. Vector v a => Series v k a -> [(k, a)]
G.toList
toVector :: Series k a -> Vector (k, a)
{-# INLINE toVector #-}
toVector :: forall k a. Series k a -> Vector (k, a)
toVector = Series Vector k a -> Vector (k, a)
forall (v :: * -> *) a k.
(Vector v a, Vector v k, Vector v (k, a)) =>
Series v k a -> v (k, a)
G.toVector
fromVector :: Ord k => Vector (k, a) -> Series k a
{-# INLINE fromVector #-}
fromVector :: forall k a. Ord k => Vector (k, a) -> Series k a
fromVector = Vector (k, a) -> Series Vector k a
forall k (v :: * -> *) a.
(Ord k, Vector v k, Vector v a, Vector v (k, a)) =>
v (k, a) -> Series v k a
G.fromVector
fromVectorDuplicates :: Ord k => Vector (k, a) -> Series (k, Occurrence) a
{-# INLINE fromVectorDuplicates #-}
fromVectorDuplicates :: forall k a. Ord k => Vector (k, a) -> Series (k, Occurrence) a
fromVectorDuplicates = Vector (k, a) -> Series Vector (k, Occurrence) a
forall k (v :: * -> *) a.
(Ord k, Vector v k, Vector v a, Vector v (k, a),
Vector v (k, Occurrence)) =>
v (k, a) -> Series v (k, Occurrence) a
G.fromVectorDuplicates
toLazyMap :: Series k a -> ML.Map k a
{-# INLINE toLazyMap #-}
toLazyMap :: forall k a. Series k a -> Map k a
toLazyMap = Series Vector k a -> Map k a
forall (v :: * -> *) a k. Vector v a => Series v k a -> Map k a
G.toLazyMap
fromLazyMap :: ML.Map k a -> Series k a
{-# INLINE fromLazyMap #-}
fromLazyMap :: forall k a. Map k a -> Series k a
fromLazyMap = Map k a -> Series Vector k a
forall (v :: * -> *) a k. Vector v a => Map k a -> Series v k a
G.fromLazyMap
toStrictMap :: Series k a -> MS.Map k a
{-# INLINE toStrictMap #-}
toStrictMap :: forall k a. Series k a -> Map k a
toStrictMap = Series Vector k a -> Map k a
forall (v :: * -> *) a k. Vector v a => Series v k a -> Map k a
G.toStrictMap
fromStrictMap :: MS.Map k a -> Series k a
{-# INLINE fromStrictMap #-}
fromStrictMap :: forall k a. Map k a -> Series k a
fromStrictMap = Map k a -> Series Vector k a
forall (v :: * -> *) a k. Vector v a => Map k a -> Series v k a
G.fromStrictMap
map :: (a -> b) -> Series k a -> Series k b
{-# INLINE map #-}
map :: forall a b k. (a -> b) -> Series k a -> Series k b
map = (a -> b) -> Series Vector k a -> Series Vector k b
forall (v :: * -> *) a b k.
(Vector v a, Vector v b) =>
(a -> b) -> Series v k a -> Series v k b
G.map
mapWithKey :: (k -> a -> b) -> Series k a -> Series k b
{-# INLINE mapWithKey #-}
mapWithKey :: forall k a b. (k -> a -> b) -> Series k a -> Series k b
mapWithKey = (k -> a -> b) -> Series Vector k a -> Series Vector k b
forall (v :: * -> *) a b k.
(Vector v a, Vector v b) =>
(k -> a -> b) -> Series v k a -> Series v k b
G.mapWithKey
mapIndex :: (Ord k, Ord g) => Series k a -> (k -> g) -> Series g a
{-# INLINE mapIndex #-}
mapIndex :: forall k g a.
(Ord k, Ord g) =>
Series k a -> (k -> g) -> Series g a
mapIndex = Series Vector k a -> (k -> g) -> Series Vector g a
forall (v :: * -> *) a k g.
(Vector v a, Ord k, Ord g) =>
Series v k a -> (k -> g) -> Series v g a
G.mapIndex
concatMap :: Ord k
=> (a -> Series k b)
-> Series k a
-> Series k b
{-# INLINE concatMap #-}
concatMap :: forall k a b.
Ord k =>
(a -> Series k b) -> Series k a -> Series k b
concatMap = (a -> Series Vector k b) -> Series Vector k a -> Series Vector k b
forall (v :: * -> *) a k b.
(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
G.concatMap
mapWithKeyM :: (Monad m, Ord k) => (k -> a -> m b) -> Series k a -> m (Series k b)
{-# INLINE mapWithKeyM #-}
mapWithKeyM :: forall (m :: * -> *) k a b.
(Monad m, Ord k) =>
(k -> a -> m b) -> Series k a -> m (Series k b)
mapWithKeyM = (k -> a -> m b) -> Series Vector k a -> m (Series Vector k b)
forall (v :: * -> *) a b (m :: * -> *) k.
(Vector v a, Vector v b, Monad m, Ord k) =>
(k -> a -> m b) -> Series v k a -> m (Series v k b)
G.mapWithKeyM
mapWithKeyM_ :: Monad m => (k -> a -> m b) -> Series k a -> m ()
{-# INLINE mapWithKeyM_ #-}
mapWithKeyM_ :: forall (m :: * -> *) k a b.
Monad m =>
(k -> a -> m b) -> Series k a -> m ()
mapWithKeyM_ = (k -> a -> m b) -> Series Vector k a -> m ()
forall (v :: * -> *) a (m :: * -> *) k b.
(Vector v a, Monad m) =>
(k -> a -> m b) -> Series v k a -> m ()
G.mapWithKeyM_
forWithKeyM :: (Monad m, Ord k) => Series k a -> (k -> a -> m b) -> m (Series k b)
{-# INLINE forWithKeyM #-}
forWithKeyM :: forall (m :: * -> *) k a b.
(Monad m, Ord k) =>
Series k a -> (k -> a -> m b) -> m (Series k b)
forWithKeyM = Series Vector k a -> (k -> a -> m b) -> m (Series Vector k b)
forall (v :: * -> *) a b (m :: * -> *) k.
(Vector v a, Vector v b, Monad m, Ord k) =>
Series v k a -> (k -> a -> m b) -> m (Series v k b)
G.forWithKeyM
forWithKeyM_ :: Monad m => Series k a -> (k -> a -> m b) -> m ()
{-# INLINE forWithKeyM_ #-}
forWithKeyM_ :: forall (m :: * -> *) k a b.
Monad m =>
Series k a -> (k -> a -> m b) -> m ()
forWithKeyM_ = Series Vector k a -> (k -> a -> m b) -> m ()
forall (v :: * -> *) a (m :: * -> *) k b.
(Vector v a, Monad m) =>
Series v k a -> (k -> a -> m b) -> m ()
G.forWithKeyM_
traverseWithKey :: (Applicative t, Ord k)
=> (k -> a -> t b)
-> Series k a
-> t (Series k b)
{-# INLINE traverseWithKey #-}
traverseWithKey :: forall (t :: * -> *) k a b.
(Applicative t, Ord k) =>
(k -> a -> t b) -> Series k a -> t (Series k b)
traverseWithKey = (k -> a -> t b) -> Series Vector k a -> t (Series Vector k b)
forall (t :: * -> *) k (v :: * -> *) a b.
(Applicative t, Ord k, Traversable v, Vector v a, Vector v b,
Vector v k, Vector v (k, a), Vector v (k, b)) =>
(k -> a -> t b) -> Series v k a -> t (Series v k b)
G.traverseWithKey
take :: Int -> Series k a -> Series k a
{-# INLINE take #-}
take :: forall k a. Int -> Series k a -> Series k a
take = Int -> Series Vector k a -> Series Vector k a
forall (v :: * -> *) a k.
Vector v a =>
Int -> Series v k a -> Series v k a
G.take
takeWhile :: (a -> Bool) -> Series k a -> Series k a
takeWhile :: forall a k. (a -> Bool) -> Series k a -> Series k a
takeWhile = (a -> Bool) -> Series Vector k a -> Series Vector k a
forall (v :: * -> *) a k.
Vector v a =>
(a -> Bool) -> Series v k a -> Series v k a
G.takeWhile
drop :: Int -> Series k a -> Series k a
{-# INLINE drop #-}
drop :: forall k a. Int -> Series k a -> Series k a
drop = Int -> Series Vector k a -> Series Vector k a
forall (v :: * -> *) a k.
Vector v a =>
Int -> Series v k a -> Series v k a
G.drop
dropWhile :: (a -> Bool) -> Series k a -> Series k a
dropWhile :: forall a k. (a -> Bool) -> Series k a -> Series k a
dropWhile = (a -> Bool) -> Series Vector k a -> Series Vector k a
forall (v :: * -> *) a k.
Vector v a =>
(a -> Bool) -> Series v k a -> Series v k a
G.dropWhile
zipWith :: (Ord k)
=> (a -> b -> c) -> Series k a -> Series k b -> Series k (Maybe c)
zipWith :: forall k a b c.
Ord k =>
(a -> b -> c) -> Series k a -> Series k b -> Series k (Maybe c)
zipWith = (a -> b -> c)
-> Series Vector k a
-> Series Vector k b
-> Series Vector k (Maybe c)
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)
G.zipWith
{-# INLINE zipWith #-}
zipWith3 :: (Ord k)
=> (a -> b -> c -> d)
-> Series k a
-> Series k b
-> Series k c
-> Series k (Maybe d)
{-# INLINE zipWith3 #-}
zipWith3 :: forall k a b c d.
Ord k =>
(a -> b -> c -> d)
-> Series k a -> Series k b -> Series k c -> Series k (Maybe d)
zipWith3 = (a -> b -> c -> d)
-> Series Vector k a
-> Series Vector k b
-> Series Vector k c
-> Series Vector k (Maybe d)
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)
G.zipWith3
zipWithMatched :: Ord k => (a -> b -> c) -> Series k a -> Series k b -> Series k c
{-# INLINE zipWithMatched #-}
zipWithMatched :: forall k a b c.
Ord k =>
(a -> b -> c) -> Series k a -> Series k b -> Series k c
zipWithMatched = (a -> b -> c)
-> Series Vector k a -> Series Vector k b -> Series Vector 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
G.zipWithMatched
zipWithMatched3 :: (Ord k)
=> (a -> b -> c -> d)
-> Series k a
-> Series k b
-> Series k c
-> Series k d
{-# INLINE zipWithMatched3 #-}
zipWithMatched3 :: forall k a b c d.
Ord k =>
(a -> b -> c -> d)
-> Series k a -> Series k b -> Series k c -> Series k d
zipWithMatched3 = (a -> b -> c -> d)
-> Series Vector k a
-> Series Vector k b
-> Series Vector k c
-> Series Vector 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
G.zipWithMatched3
zipWithKey :: (Ord k)
=> (k -> a -> b -> c) -> Series k a -> Series k b -> Series k c
{-# INLINE zipWithKey #-}
zipWithKey :: forall k a b c.
Ord k =>
(k -> a -> b -> c) -> Series k a -> Series k b -> Series k c
zipWithKey = (k -> a -> b -> c)
-> Series Vector k a -> Series Vector k b -> Series Vector k c
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
G.zipWithKey
zipWithKey3 :: (Ord k)
=> (k -> a -> b -> c -> d)
-> Series k a
-> Series k b
-> Series k c
-> Series k d
{-# INLINE zipWithKey3 #-}
zipWithKey3 :: forall k a b c d.
Ord k =>
(k -> a -> b -> c -> d)
-> Series k a -> Series k b -> Series k c -> Series k d
zipWithKey3 = (k -> a -> b -> c -> d)
-> Series Vector k a
-> Series Vector k b
-> Series Vector k c
-> Series Vector k d
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
G.zipWithKey3
zipWithStrategy :: (Ord k)
=> (a -> b -> c)
-> ZipStrategy k a c
-> ZipStrategy k b c
-> Series k a
-> Series k b
-> Series k c
{-# INLINE zipWithStrategy #-}
zipWithStrategy :: forall k a b c.
Ord k =>
(a -> b -> c)
-> ZipStrategy k a c
-> ZipStrategy k b c
-> Series k a
-> Series k b
-> Series k c
zipWithStrategy = (a -> b -> c)
-> ZipStrategy k a c
-> ZipStrategy k b c
-> Series Vector k a
-> Series Vector k b
-> Series Vector k c
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
G.zipWithStrategy
zipWithStrategy3 :: (Ord k)
=> (a -> b -> c -> d)
-> ZipStrategy k a d
-> ZipStrategy k b d
-> ZipStrategy k c d
-> Series k a
-> Series k b
-> Series k c
-> Series k d
{-# INLINE zipWithStrategy3 #-}
zipWithStrategy3 :: forall k a b c d.
Ord k =>
(a -> b -> c -> d)
-> ZipStrategy k a d
-> ZipStrategy k b d
-> ZipStrategy k c d
-> Series k a
-> Series k b
-> Series k c
-> Series k d
zipWithStrategy3 = (a -> b -> c -> d)
-> ZipStrategy k a d
-> ZipStrategy k b d
-> ZipStrategy k c d
-> Series Vector k a
-> Series Vector k b
-> Series Vector k c
-> Series Vector 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)
-> 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
G.zipWithStrategy3
zipWithMonoid :: ( Monoid a, Monoid b, Ord k)
=> (a -> b -> c)
-> Series k a
-> Series k b
-> Series k c
zipWithMonoid :: forall a b k c.
(Monoid a, Monoid b, Ord k) =>
(a -> b -> c) -> Series k a -> Series k b -> Series k c
zipWithMonoid = (a -> b -> c)
-> Series Vector k a -> Series Vector k b -> Series Vector k c
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
G.zipWithMonoid
{-# INLINE zipWithMonoid #-}
esum :: (Ord k, Num a)
=> Series k a
-> Series k a
-> Series k a
esum :: forall k a.
(Ord k, Num a) =>
Series k a -> Series k a -> Series k a
esum = Series Vector k a -> Series Vector k a -> Series Vector k a
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
G.esum
{-# INLINE esum #-}
eproduct :: (Ord k, Num a)
=> Series k a
-> Series k a
-> Series k a
eproduct :: forall k a.
(Ord k, Num a) =>
Series k a -> Series k a -> Series k a
eproduct = Series Vector k a -> Series Vector k a -> Series Vector k a
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
G.eproduct
{-# INLINE eproduct #-}
unzip :: Series k (a, b)
-> ( Series k a
, Series k b
)
unzip :: forall k a b. Series k (a, b) -> (Series k a, Series k b)
unzip = Series Vector k (a, b) -> (Series Vector k a, Series Vector k b)
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)
G.unzip
{-# INLINE unzip #-}
unzip3 :: Series k (a, b, c)
-> ( Series k a
, Series k b
, Series k c
)
unzip3 :: forall k a b c.
Series k (a, b, c) -> (Series k a, Series k b, Series k c)
unzip3 = Series Vector k (a, b, c)
-> (Series Vector k a, Series Vector k b, Series Vector k c)
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)
G.unzip3
{-# INLINE unzip3 #-}
require :: Ord k => Series k a -> Index k -> Series k (Maybe a)
{-# INLINE require #-}
require :: forall k a. Ord k => Series k a -> Index k -> Series k (Maybe a)
require = Series Vector k a -> Index k -> Series Vector k (Maybe a)
forall (v :: * -> *) a k.
(Vector v a, Vector v (Maybe a), Ord k) =>
Series v k a -> Index k -> Series v k (Maybe a)
G.require
dropIndex :: Series k a -> Series Int a
{-# INLINE dropIndex #-}
dropIndex :: forall k a. Series k a -> Series Int a
dropIndex = Series Vector k a -> Series Vector Int a
forall {k1} (v :: k1 -> *) k2 (a :: k1).
Series v k2 a -> Series v Int a
G.dropIndex
filter :: Ord k => (a -> Bool) -> Series k a -> Series k a
{-# INLINE filter #-}
filter :: forall k a. Ord k => (a -> Bool) -> Series k a -> Series k a
filter = (a -> Bool) -> Series Vector k a -> Series Vector k a
forall (v :: * -> *) a k.
(Vector v a, Vector v Int, Ord k) =>
(a -> Bool) -> Series v k a -> Series v k a
G.filter
filterWithKey :: Ord k
=> (k -> a -> Bool)
-> Series k a
-> Series k a
{-# INLINE filterWithKey #-}
filterWithKey :: forall k a. Ord k => (k -> a -> Bool) -> Series k a -> Series k a
filterWithKey = (k -> a -> Bool) -> Series Vector k a -> Series Vector k a
forall (v :: * -> *) a k.
(Vector v a, Vector v Int, Vector v Bool, Ord k) =>
(k -> a -> Bool) -> Series v k a -> Series v k a
G.filterWithKey
catMaybes :: Ord k => Series k (Maybe a) -> Series k a
{-# INLINE catMaybes #-}
catMaybes :: forall k a. Ord k => Series k (Maybe a) -> Series k a
catMaybes = Series Vector k (Maybe a) -> Series Vector k a
forall (v :: * -> *) a k.
(Vector v a, Vector v (Maybe a), Vector v Int, Ord k) =>
Series v k (Maybe a) -> Series v k a
G.catMaybes
select :: (Selection s, Ord k) => Series k a -> s k -> Series k a
select :: forall (s :: * -> *) k a.
(Selection s, Ord k) =>
Series k a -> s k -> Series k a
select = Series Vector k a -> s k -> Series Vector k a
forall (s :: * -> *) (v :: * -> *) a k.
(Selection s, Vector v a, Ord k) =>
Series v k a -> s k -> Series v k a
forall (v :: * -> *) a k.
(Vector v a, Ord k) =>
Series v k a -> s k -> Series v k a
G.select
selectWhere :: Ord k => Series k a -> Series k Bool -> Series k a
{-# INLINE selectWhere #-}
selectWhere :: forall k a. Ord k => Series k a -> Series k Bool -> Series k a
selectWhere = Series Vector k a -> Series Vector k Bool -> Series Vector k a
forall (v :: * -> *) a k.
(Vector v a, Vector v Int, Vector v Bool, Ord k) =>
Series v k a -> Series v k Bool -> Series v k a
G.selectWhere
at :: Ord k => Series k a -> k -> Maybe a
{-# INLINE at #-}
at :: forall k a. Ord k => Series k a -> k -> Maybe a
at = Series Vector k a -> k -> Maybe a
forall (v :: * -> *) a k.
(Vector v a, Ord k) =>
Series v k a -> k -> Maybe a
G.at
iat :: Series k a -> Int -> Maybe a
{-# INLINE iat #-}
iat :: forall k a. Series k a -> Int -> Maybe a
iat = Series Vector k a -> Int -> Maybe a
forall (v :: * -> *) a k.
Vector v a =>
Series v k a -> Int -> Maybe a
G.iat
replace :: Ord k => Series k a -> Series k a -> Series k a
{-# INLINE replace #-}
replace :: forall k a. Ord k => Series k a -> Series k a -> Series k a
replace = Series Vector k a -> Series Vector k a -> Series Vector 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
G.replace
(|->) :: (Ord k) => Series k a -> Series k a -> Series k a
{-# INLINE (|->) #-}
|-> :: forall k a. Ord k => Series k a -> Series k a -> Series k a
(|->) = Series Vector k a -> Series Vector k a -> Series Vector 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
(G.|->)
(<-|) :: (Ord k) => Series k a -> Series k a -> Series k a
{-# INLINE (<-|) #-}
<-| :: forall k a. Ord k => Series k a -> Series k a -> Series k a
(<-|) = Series Vector k a -> Series Vector k a -> Series Vector 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
(G.<-|)
forwardFill :: a
-> Series v (Maybe a)
-> Series v a
{-# INLINE forwardFill #-}
forwardFill :: forall a v. a -> Series v (Maybe a) -> Series v a
forwardFill = a -> Series Vector v (Maybe a) -> Series Vector v a
forall (v :: * -> *) a k.
(Vector v a, Vector v (Maybe a)) =>
a -> Series v k (Maybe a) -> Series v k a
G.forwardFill
fold :: Fold a b -> Series k a -> b
fold :: forall a b k. Fold a b -> Series k a -> b
fold = Fold a b -> Series Vector k a -> b
forall (v :: * -> *) a b k.
Vector v a =>
Fold a b -> Series v k a -> b
G.fold
{-# INLINE fold #-}
foldM :: (Monad m)
=> FoldM m a b
-> Series k a
-> m b
foldM :: forall (m :: * -> *) a b k.
Monad m =>
FoldM m a b -> Series k a -> m b
foldM = FoldM m a b -> Series Vector k a -> m b
forall (m :: * -> *) (v :: * -> *) a b k.
(Monad m, Vector v a) =>
FoldM m a b -> Series v k a -> m b
G.foldM
{-# INLINE foldM #-}
foldWithKey :: Fold (k, a) b -> Series k a -> b
foldWithKey :: forall k a b. Fold (k, a) b -> Series k a -> b
foldWithKey = Fold (k, a) b -> Series Vector k a -> b
forall (v :: * -> *) a k b.
(Vector v a, Vector v k, Vector v (k, a)) =>
Fold (k, a) b -> Series v k a -> b
G.foldWithKey
{-# INLINE foldWithKey #-}
foldMWithKey :: (Monad m)
=> FoldM m (k, a) b
-> Series k a
-> m b
foldMWithKey :: forall (m :: * -> *) k a b.
Monad m =>
FoldM m (k, a) b -> Series k a -> m b
foldMWithKey = FoldM m (k, a) b -> Series Vector k a -> m b
forall (m :: * -> *) (v :: * -> *) a k b.
(Monad m, Vector v a, Vector v k, Vector v (k, a)) =>
FoldM m (k, a) b -> Series v k a -> m b
G.foldMWithKey
{-# INLINE foldMWithKey #-}
foldMapWithKey :: Monoid m => (k -> a -> m) -> Series k a -> m
{-# INLINE foldMapWithKey #-}
foldMapWithKey :: forall m k a. Monoid m => (k -> a -> m) -> Series k a -> m
foldMapWithKey = (k -> a -> m) -> Series Vector k a -> m
forall m (v :: * -> *) a k.
(Monoid m, Vector v a, Vector v k, Vector v (k, a)) =>
(k -> a -> m) -> Series v k a -> m
G.foldMapWithKey
groupBy :: Series k a
->(k -> g)
-> Grouping k g a
{-# INLINE groupBy #-}
groupBy :: forall k a g. Series k a -> (k -> g) -> Grouping k g a
groupBy = Series Vector k a -> (k -> g) -> Grouping k g Vector a
forall {k1} (v :: k1 -> *) k2 (a :: k1) g.
Series v k2 a -> (k2 -> g) -> Grouping k2 g v a
G.groupBy
type Grouping k g a = G.Grouping k g Vector a
aggregateWith :: (Ord g)
=> Grouping k g a
-> (Series k a -> b)
-> Series g b
{-# INLINE aggregateWith #-}
aggregateWith :: forall g k a b.
Ord g =>
Grouping k g a -> (Series k a -> b) -> Series g b
aggregateWith = Grouping k g Vector a
-> (Series Vector k a -> b) -> Series Vector g b
forall g (v :: * -> *) a b k.
(Ord g, Vector v a, Vector v b) =>
Grouping k g v a -> (Series v k a -> b) -> Series v g b
G.aggregateWith
foldWith :: Ord g
=> Grouping k g a
-> (a -> a -> a)
-> Series g a
{-# INLINE foldWith #-}
foldWith :: forall g k a.
Ord g =>
Grouping k g a -> (a -> a -> a) -> Series g a
foldWith = Grouping k g Vector a -> (a -> a -> a) -> Series Vector g a
forall g (v :: * -> *) a k.
(Ord g, Vector v a) =>
Grouping k g v a -> (a -> a -> a) -> Series v g a
G.foldWith
expanding :: Series k a
-> (Series k a -> b)
-> Series k b
{-# INLINE expanding #-}
expanding :: forall k a b. Series k a -> (Series k a -> b) -> Series k b
expanding = Series Vector k a -> (Series Vector k a -> b) -> Series Vector k b
forall (v :: * -> *) a b k.
(Vector v a, Vector v b) =>
Series v k a -> (Series v k a -> b) -> Series v k b
G.expanding
windowing :: Ord k
=> (k -> Range k)
-> (Series k a -> b)
-> Series k a
-> Series k b
{-# INLINE windowing #-}
windowing :: forall k a b.
Ord k =>
(k -> Range k) -> (Series k a -> b) -> Series k a -> Series k b
windowing = (k -> Range k)
-> (Series Vector k a -> b)
-> Series Vector k a
-> Series Vector k b
forall k (v :: * -> *) a b.
(Ord k, Vector v a, Vector v b) =>
(k -> Range k)
-> (Series v k a -> b) -> Series v k a -> Series v k b
G.windowing
null :: Series k a -> Bool
{-# INLINE null #-}
null :: forall k a. Series k a -> Bool
null = Series Vector k a -> Bool
forall (v :: * -> *) a k. Vector v a => Series v k a -> Bool
G.null
length :: Series k a -> Int
{-# INLINE length #-}
length :: forall k a. Series k a -> Int
length = Series Vector k a -> Int
forall (v :: * -> *) a k. Vector v a => Series v k a -> Int
G.length
all :: (a -> Bool) -> Series k a -> Bool
{-# INLINE all #-}
all :: forall a k. (a -> Bool) -> Series k a -> Bool
all = (a -> Bool) -> Series Vector k a -> Bool
forall (v :: * -> *) a k.
Vector v a =>
(a -> Bool) -> Series v k a -> Bool
G.all
any :: (a -> Bool) -> Series k a -> Bool
{-# INLINE any #-}
any :: forall a k. (a -> Bool) -> Series k a -> Bool
any = (a -> Bool) -> Series Vector k a -> Bool
forall (v :: * -> *) a k.
Vector v a =>
(a -> Bool) -> Series v k a -> Bool
G.any
and :: Series k Bool -> Bool
{-# INLINE and #-}
and :: forall k. Series k Bool -> Bool
and = Series Vector k Bool -> Bool
forall (v :: * -> *) k. Vector v Bool => Series v k Bool -> Bool
G.and
or :: Series k Bool -> Bool
{-# INLINE or #-}
or :: forall k. Series k Bool -> Bool
or = Series Vector k Bool -> Bool
forall (v :: * -> *) k. Vector v Bool => Series v k Bool -> Bool
G.or
sum :: (Num a) => Series k a -> a
{-# INLINE sum #-}
sum :: forall a k. Num a => Series k a -> a
sum = Series Vector k a -> a
forall a (v :: * -> *) k. (Num a, Vector v a) => Series v k a -> a
G.sum
product :: (Num a) => Series k a -> a
{-# INLINE product #-}
product :: forall a k. Num a => Series k a -> a
product = Series Vector k a -> a
forall a (v :: * -> *) k. (Num a, Vector v a) => Series v k a -> a
G.product
maximum :: (Ord a) => Series k a -> Maybe a
{-# INLINE maximum #-}
maximum :: forall a k. Ord a => Series k a -> Maybe a
maximum = Series Vector k a -> Maybe a
forall a (v :: * -> *) k.
(Ord a, Vector v a) =>
Series v k a -> Maybe a
G.maximum
maximumOn :: (Ord b) => (a -> b) -> Series k a -> Maybe a
{-# INLINE maximumOn #-}
maximumOn :: forall b a k. Ord b => (a -> b) -> Series k a -> Maybe a
maximumOn = (a -> b) -> Series Vector k a -> Maybe a
forall b (v :: * -> *) a k.
(Ord b, Vector v a) =>
(a -> b) -> Series v k a -> Maybe a
G.maximumOn
minimum :: (Ord a) => Series k a -> Maybe a
{-# INLINE minimum #-}
minimum :: forall a k. Ord a => Series k a -> Maybe a
minimum = Series Vector k a -> Maybe a
forall a (v :: * -> *) k.
(Ord a, Vector v a) =>
Series v k a -> Maybe a
G.minimum
minimumOn :: (Ord b) => (a -> b) -> Series k a -> Maybe a
{-# INLINE minimumOn #-}
minimumOn :: forall b a k. Ord b => (a -> b) -> Series k a -> Maybe a
minimumOn = (a -> b) -> Series Vector k a -> Maybe a
forall b (v :: * -> *) a k.
(Ord b, Vector v a) =>
(a -> b) -> Series v k a -> Maybe a
G.minimumOn
argmax :: Ord a => Series k a -> Maybe k
argmax :: forall a k. Ord a => Series k a -> Maybe k
argmax = Series Vector k a -> Maybe k
forall a (v :: * -> *) k.
(Ord a, Vector v a) =>
Series v k a -> Maybe k
G.argmax
{-# INLINE argmax #-}
argmin :: Ord a => Series k a -> Maybe k
argmin :: forall a k. Ord a => Series k a -> Maybe k
argmin = Series Vector k a -> Maybe k
forall a (v :: * -> *) k.
(Ord a, Vector v a, Vector v (Down a)) =>
Series v k a -> Maybe k
G.argmin
{-# INLINE argmin #-}
postscanl :: (a -> b -> a) -> a -> Series k b -> Series k a
{-# INLINE postscanl #-}
postscanl :: forall a b k. (a -> b -> a) -> a -> Series k b -> Series k a
postscanl = (a -> b -> a) -> a -> Series Vector k b -> Series Vector k a
forall (v :: * -> *) a b k.
(Vector v a, Vector v b) =>
(a -> b -> a) -> a -> Series v k b -> Series v k a
G.postscanl
prescanl :: (a -> b -> a) -> a -> Series k b -> Series k a
{-# INLINE prescanl #-}
prescanl :: forall a b k. (a -> b -> a) -> a -> Series k b -> Series k a
prescanl = (a -> b -> a) -> a -> Series Vector k b -> Series Vector k a
forall (v :: * -> *) a b k.
(Vector v a, Vector v b) =>
(a -> b -> a) -> a -> Series v k b -> Series v k a
G.prescanl
display :: (Show k, Show a)
=> Series k a
-> String
display :: forall k a. (Show k, Show a) => Series k a -> String
display = Series Vector k a -> String
forall (v :: * -> *) a k.
(Vector v a, Show k, Show a) =>
Series v k a -> String
G.display
displayWith :: DisplayOptions k a
-> Series k a
-> String
displayWith :: forall k a. DisplayOptions k a -> Series k a -> String
displayWith = DisplayOptions k a -> Series Vector k a -> String
forall (v :: * -> *) a k.
Vector v a =>
DisplayOptions k a -> Series v k a -> String
G.displayWith