Copyright | (c) Laurent P. René de Cotret |
---|---|
License | MIT |
Maintainer | laurent.decotret@outlook.com |
Portability | portable |
Safe Haskell | Safe-Inferred |
Language | GHC2021 |
This module contains data structures and functions to work with Series
capable of holding unboxed values,
i.e. values of types which are instances of Unbox
.
Why use unboxed series?
Unboxed series can have much better performance, at the cost of less flexibility. For example,
an unboxed series cannot contain values of type
. Moreover, unboxed series aren't instances of
Maybe
aFunctor
or Foldable
.
If you are hesitating, you should prefer the series implementation in the Data.Series module.
Introduction to series
A Series
of type Series k a
is a labeled array of values of type a
,
indexed by keys of type k
.
Like Map
from the containers
package, Series
support efficient:
- random access by key ( \(O(\log n)\) );
- slice by key ( \(O(\log n)\) ).
Like Vector
, they support efficient:
- random access by index ( \(O(1)\) );
- slice by index ( \(O(1)\) );
- numerical operations.
This module re-exports most of the content of Data.Series.Generic, with type signatures
specialized to the unboxed vector type Vector
.
Synopsis
- type Series = Series Vector
- index :: Series k a -> Index k
- values :: Series k a -> Vector a
- singleton :: Unbox a => k -> a -> Series k a
- fromIndex :: Unbox a => (k -> a) -> Index k -> Series k a
- fromList :: (Ord k, Unbox a) => [(k, a)] -> Series k a
- toList :: Unbox a => Series k a -> [(k, a)]
- fromVector :: (Ord k, Unbox k, Unbox a) => Vector (k, a) -> Series k a
- toVector :: (Unbox a, Unbox k) => Series k a -> Vector (k, a)
- data Occurrence
- fromListDuplicates :: (Ord k, Unbox a) => [(k, a)] -> Series (k, Occurrence) a
- fromVectorDuplicates :: (Unbox k, Unbox a, Ord k) => Vector (k, a) -> Series (k, Occurrence) a
- fromStrictMap :: Unbox a => Map k a -> Series k a
- toStrictMap :: Unbox a => Series k a -> Map k a
- fromLazyMap :: Unbox a => Map k a -> Series k a
- toLazyMap :: Unbox a => Series k a -> Map k a
- class IsSeries t v k a where
- toSeries :: t -> Series v k a
- fromSeries :: Series v k a -> t
- convert :: (Vector v1 a, Vector v2 a) => Series v1 k a -> Series v2 k a
- map :: (Unbox a, Unbox b) => (a -> b) -> Series k a -> Series k b
- mapWithKey :: (Unbox a, Unbox b) => (k -> a -> b) -> Series k a -> Series k b
- mapIndex :: (Unbox a, Ord k, Ord g) => Series k a -> (k -> g) -> Series g a
- concatMap :: (Unbox a, Unbox k, Unbox b, Ord k) => (a -> Series k b) -> Series k a -> Series k b
- take :: Unbox a => Int -> Series k a -> Series k a
- takeWhile :: Unbox a => (a -> Bool) -> Series k a -> Series k a
- drop :: Unbox a => Int -> Series k a -> Series k a
- dropWhile :: Unbox a => (a -> Bool) -> Series k a -> Series k a
- filter :: (Unbox a, Ord k) => (a -> Bool) -> Series k a -> Series k a
- filterWithKey :: (Unbox a, Ord k) => (k -> a -> Bool) -> Series k a -> Series k a
- mapWithKeyM :: (Unbox a, Unbox b, Monad m, Ord k) => (k -> a -> m b) -> Series k a -> m (Series k b)
- mapWithKeyM_ :: (Unbox a, Monad m) => (k -> a -> m b) -> Series k a -> m ()
- forWithKeyM :: (Unbox a, Unbox b, Monad m, Ord k) => Series k a -> (k -> a -> m b) -> m (Series k b)
- forWithKeyM_ :: (Unbox a, Monad m) => Series k a -> (k -> a -> m b) -> m ()
- zipWithMatched :: (Unbox a, Unbox b, Unbox c, Ord k) => (a -> b -> c) -> Series k a -> Series k b -> Series k c
- zipWithKey :: (Unbox a, Unbox b, Unbox c, Unbox k, Ord k) => (k -> a -> b -> c) -> Series k a -> Series k b -> Series k c
- zipWithMatched3 :: (Unbox a, Unbox b, Unbox c, Unbox d, Ord k) => (a -> b -> c -> d) -> Series k a -> Series k b -> Series k c -> Series k d
- zipWithKey3 :: (Unbox a, Unbox b, Unbox c, Unbox d, Unbox k, Ord k) => (k -> a -> b -> c -> d) -> Series k a -> Series k b -> Series k c -> Series k d
- type ZipStrategy k a b = k -> a -> Maybe b
- skipStrategy :: ZipStrategy k a b
- mapStrategy :: (a -> b) -> ZipStrategy k a b
- constStrategy :: b -> ZipStrategy k a b
- zipWithStrategy :: (Ord k, Unbox a, Unbox b, Unbox c) => (a -> b -> c) -> ZipStrategy k a c -> ZipStrategy k b c -> Series k a -> Series k b -> Series k c
- zipWithStrategy3 :: (Ord k, Unbox a, Unbox b, Unbox c, Unbox d) => (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
- zipWithMonoid :: (Monoid a, Monoid b, Unbox a, Unbox b, Unbox c, Ord k) => (a -> b -> c) -> Series k a -> Series k b -> Series k c
- esum :: (Ord k, Num a, Unbox a) => Series k a -> Series k a -> Series k a
- eproduct :: (Ord k, Num a, Unbox a) => Series k a -> Series k a -> Series k a
- unzip :: (Unbox a, Unbox b) => Series k (a, b) -> (Series k a, Series k b)
- unzip3 :: (Unbox a, Unbox b, Unbox c) => Series k (a, b, c) -> (Series k a, Series k b, Series k c)
- require :: (Unbox a, Ord k) => (k -> a) -> Series k a -> Index k -> Series k a
- dropIndex :: Series k a -> Series Int a
- select :: (Unbox a, Selection s, Ord k) => Series k a -> s k -> Series k a
- selectWhere :: (Unbox a, Ord k) => Series k a -> Series k Bool -> Series k a
- data Range k
- to :: Ord k => k -> k -> Range k
- from :: k -> Range k
- upto :: k -> Range k
- class Selection s
- at :: (Unbox a, Ord k) => Series k a -> k -> Maybe a
- iat :: Unbox a => Series k a -> Int -> Maybe a
- replace :: (Unbox a, Ord k) => Series k a -> Series k a -> Series k a
- (|->) :: (Unbox a, Ord k) => Series k a -> Series k a -> Series k a
- (<-|) :: (Unbox a, Ord k) => Series k a -> Series k a -> Series k a
- groupBy :: Series k a -> (k -> g) -> Grouping k g a
- type Grouping k g a = Grouping k g Vector a
- aggregateWith :: (Ord g, Unbox a, Unbox b) => Grouping k g a -> (Series k a -> b) -> Series g b
- foldWith :: (Ord g, Unbox a) => Grouping k g a -> (a -> a -> a) -> Series g a
- windowing :: (Ord k, Unbox a, Unbox b) => (k -> Range k) -> (Series k a -> b) -> Series k a -> Series k b
- expanding :: (Unbox a, Unbox b) => Series k a -> (Series k a -> b) -> Series k b
- fold :: Unbox a => Fold a b -> Series k a -> b
- foldM :: (Monad m, Unbox a) => FoldM m a b -> Series k a -> m b
- foldWithKey :: (Unbox k, Unbox a) => Fold (k, a) b -> Series k a -> b
- foldMWithKey :: (Monad m, Unbox a, Unbox k) => FoldM m (k, a) b -> Series k a -> m b
- foldMap :: (Monoid m, Unbox a) => (a -> m) -> Series k a -> m
- foldMap' :: (Monoid m, Unbox a) => (a -> m) -> Series k a -> m
- foldMapWithKey :: (Monoid m, Unbox a, Unbox k) => (k -> a -> m) -> Series k a -> m
- mean :: Fractional a => Fold a a
- variance :: Fractional a => Fold a a
- std :: Floating a => Fold a a
- null :: Unbox a => Series k a -> Bool
- length :: Unbox a => Series k a -> Int
- all :: Unbox a => (a -> Bool) -> Series k a -> Bool
- any :: Unbox a => (a -> Bool) -> Series k a -> Bool
- and :: Series k Bool -> Bool
- or :: Series k Bool -> Bool
- sum :: (Unbox a, Num a) => Series k a -> a
- product :: (Unbox a, Num a) => Series k a -> a
- maximum :: (Ord a, Unbox a) => Series k a -> Maybe a
- maximumOn :: (Ord b, Unbox a) => (a -> b) -> Series k a -> Maybe a
- minimum :: (Ord a, Unbox a) => Series k a -> Maybe a
- minimumOn :: (Ord b, Unbox a) => (a -> b) -> Series k a -> Maybe a
- argmin :: (Ord a, Unbox a) => Series k a -> Maybe k
- argmax :: (Ord a, Unbox a) => Series k a -> Maybe k
- postscanl :: (Unbox a, Unbox b) => (a -> b -> a) -> a -> Series k b -> Series k a
- prescanl :: (Unbox a, Unbox b) => (a -> b -> a) -> a -> Series k b -> Series k a
- display :: (Unbox a, Show k, Show a) => Series k a -> String
- displayWith :: Unbox a => DisplayOptions k a -> Series k a -> String
- noLongerThan :: (a -> String) -> Int -> a -> String
- data DisplayOptions k a = DisplayOptions {
- maximumNumberOfRows :: Int
- indexHeader :: String
- valuesHeader :: String
- keyDisplayFunction :: k -> String
- valueDisplayFunction :: a -> String
- defaultDisplayOptions :: (Show k, Show a) => DisplayOptions k a
Documentation
type Series = Series Vector Source #
A series is a labeled array of values of type a
,
indexed by keys of type k
.
Like Data.Map
and Data.HashMap
, they support efficient:
- random access by key ( \(O(\log n)\) );
- slice by key ( \(O(\log n)\) ).
Like Data.Vector.Vector
, they support efficient:
- random access by index ( \(O(1)\) );
- slice by index ( \(O(1)\) );
- numerical operations.
Building/converting Series
fromIndex :: Unbox a => (k -> a) -> Index k -> Series k a Source #
\(O(n)\) Generate a Series
by mapping every element of its index.
>>>
fromIndex (const (0::Int)) $ Index.fromList ['a','b','c','d']
index | values ----- | ------ 'a' | 0 'b' | 0 'c' | 0 'd' | 0
Lists
fromList :: (Ord k, Unbox a) => [(k, a)] -> Series k a Source #
Construct a series from a list of key-value pairs. There is no condition on the order of pairs.
>>>
let xs = fromList [('b', 0::Int), ('a', 5), ('d', 1) ]
>>>
xs
index | values ----- | ------ 'a' | 5 'b' | 0 'd' | 1
If you need to handle duplicate keys, take a look at fromListDuplicates
.
toList :: Unbox a => Series k a -> [(k, a)] Source #
Construct a list from key-value pairs. The elements are in order sorted by key:
>>>
let xs = Series.fromList [ ('b', 0::Int), ('a', 5), ('d', 1) ]
>>>
xs
index | values ----- | ------ 'a' | 5 'b' | 0 'd' | 1>>>
toList xs
[('a',5),('b',0),('d',1)]
Vectors
fromVector :: (Ord k, Unbox k, Unbox a) => Vector (k, a) -> Series k a Source #
Construct a Series
from a Vector
of key-value pairs. There is no
condition on the order of pairs. Duplicate keys are silently dropped. If you
need to handle duplicate keys, see fromVectorDuplicates
.
Note that due to differences in sorting,
Series.fromList
and Series.fromVector . Vector.fromList
may not be equivalent if the input list contains duplicate keys.
toVector :: (Unbox a, Unbox k) => Series k a -> Vector (k, a) Source #
Construct a Vector
of key-value pairs. The elements are in order sorted by key.
Handling duplicates
data Occurrence Source #
Integer-like, non-negative number that specifies how many occurrences
of a key is present in a Series
.
The easiest way to convert from an Occurrence
to another integer-like type
is the fromIntegral
function.
Instances
fromListDuplicates :: (Ord k, Unbox a) => [(k, a)] -> Series (k, Occurrence) a Source #
Construct a series from a list of key-value pairs.
Contrary to fromList
, values at duplicate keys are preserved. To keep each
key unique, an Occurrence
number counts up.
>>>
let xs = fromListDuplicates [('b', 0::Int), ('a', 5), ('d', 1), ('d', -4), ('d', 7) ]
>>>
xs
index | values ----- | ------ ('a',0) | 5 ('b',0) | 0 ('d',0) | 1 ('d',1) | -4 ('d',2) | 7
fromVectorDuplicates :: (Unbox k, Unbox a, Ord k) => Vector (k, a) -> Series (k, Occurrence) a Source #
Construct a series from a Vector
of key-value pairs.
Contrary to fromVector
, values at duplicate keys are preserved. To keep each
key unique, an Occurrence
number counts up.
>>>
import qualified Data.Vector.Unboxed as Unboxed
>>>
let xs = fromVectorDuplicates $ Unboxed.fromList [('b', 0::Int), ('a', 5), ('d', 1), ('d', -4), ('d', 7) ]
>>>
xs
index | values ----- | ------ ('a',0) | 5 ('b',0) | 0 ('d',0) | 1 ('d',1) | -4 ('d',2) | 7
Strict Maps
Lazy Maps
Ad-hoc conversion with other data structures
class IsSeries t v k a where Source #
The IsSeries
typeclass allow for ad-hoc definition
of conversion functions, converting to / from Series
.
toSeries :: t -> Series v k a Source #
Construct a Series
from some container of key-values pairs. There is no
condition on the order of pairs. Duplicate keys are silently dropped. If you
need to handle duplicate keys, see fromListDuplicates
or fromVectorDuplicates
.
fromSeries :: Series v k a -> t Source #
Construct a container from key-value pairs of a Series
.
The elements are returned in ascending order of keys.
Instances
Vector v a => IsSeries (IntMap a) (v :: Type -> Type) Int (a :: Type) Source # | |
(Ord k, Vector v a) => IsSeries (Seq (k, a)) (v :: Type -> Type) k (a :: Type) Source # | |
Vector v a => IsSeries (Set (k, a)) (v :: Type -> Type) k (a :: Type) Source # | |
Ord k => IsSeries (Vector (k, a)) Vector k (a :: Type) Source # | |
(Ord k, Unbox a, Unbox k) => IsSeries (Vector (k, a)) Vector k (a :: Type) Source # | |
(Ord k, Vector v a) => IsSeries [(k, a)] (v :: Type -> Type) k (a :: Type) Source # | |
Defined in Data.Series.Generic.Definition | |
Vector v a => IsSeries (Map k a) (v :: Type -> Type) k (a :: Type) Source # | |
Conversion between Series
types
convert :: (Vector v1 a, Vector v2 a) => Series v1 k a -> Series v2 k a Source #
\(O(n)\) Convert between two types of Series
.
Mapping and filtering
map :: (Unbox a, Unbox b) => (a -> b) -> Series k a -> Series k b Source #
\(O(n)\) Map every element of a Series
.
mapWithKey :: (Unbox a, Unbox b) => (k -> a -> b) -> Series k a -> Series k b Source #
\(O(n)\) Map every element of a Series
, possibly using the key as well.
mapIndex :: (Unbox a, Ord k, Ord g) => Series k a -> (k -> g) -> Series g a Source #
\(O(n \log n)\). Map each key in the index to another value. Note that the resulting series may have less elements, because each key must be unique.
In case new keys are conflicting, the first element is kept.
>>>
let xs = Series.fromList [("Paris", 1 :: Int), ("London", 2), ("Lisbon", 4)]
>>>
xs
index | values ----- | ------ "Lisbon" | 4 "London" | 2 "Paris" | 1>>>
import qualified Data.List
>>>
xs `mapIndex` (Data.List.take 1)
index | values ----- | ------ "L" | 4 "P" | 1
concatMap :: (Unbox a, Unbox k, Unbox b, Ord k) => (a -> Series k b) -> Series k a -> Series k b Source #
take :: Unbox a => Int -> Series k a -> Series k a Source #
\(O(\log n)\)
returns at most take
n xsn
elements of the Series
xs
.
>>>
let xs = Series.fromList [("Paris", 1 :: Int), ("London", 2), ("Lisbon", 4), ("Vienna", 5)]
>>>
xs
index | values ----- | ------ "Lisbon" | 4 "London" | 2 "Paris" | 1 "Vienna" | 5>>>
take 2 xs
index | values ----- | ------ "Lisbon" | 4 "London" | 2
takeWhile :: Unbox a => (a -> Bool) -> Series k a -> Series k a Source #
\(O(n)\) Returns the longest prefix (possibly empty) of the input Series
that satisfy a predicate.
>>>
let xs = Series.fromList [("Paris", 1 :: Int), ("London", 2), ("Lisbon", 4), ("Vienna", 5)]
>>>
xs
index | values ----- | ------ "Lisbon" | 4 "London" | 2 "Paris" | 1 "Vienna" | 5
drop :: Unbox a => Int -> Series k a -> Series k a Source #
\(O(\log n)\)
drops at most drop
n xsn
elements from the Series
xs
.
>>>
let xs = Series.fromList [("Paris", 1 :: Int), ("London", 2), ("Lisbon", 4), ("Vienna", 5)]
>>>
xs
index | values ----- | ------ "Lisbon" | 4 "London" | 2 "Paris" | 1 "Vienna" | 5>>>
drop 2 xs
index | values ----- | ------ "Paris" | 1 "Vienna" | 5
dropWhile :: Unbox a => (a -> Bool) -> Series k a -> Series k a Source #
\(O(n)\) Returns the complement of takeWhile
.
>>>
let xs = Series.fromList [("Paris", 1 :: Int), ("London", 2), ("Lisbon", 4), ("Vienna", 5)]
>>>
xs
index | values ----- | ------ "Lisbon" | 4 "London" | 2 "Paris" | 1 "Vienna" | 5
filter :: (Unbox a, Ord k) => (a -> Bool) -> Series k a -> Series k a Source #
Filter elements. Only elements for which the predicate is True
are kept.
Notice that the filtering is done on the values, not on the keys.
>>>
let xs = Series.fromList [("Paris", 1 :: Int), ("London", 2), ("Lisbon", 4)]
>>>
xs
index | values ----- | ------ "Lisbon" | 4 "London" | 2 "Paris" | 1>>>
filter (>2) xs
index | values ----- | ------ "Lisbon" | 4
See also filterWithKey
.
filterWithKey :: (Unbox a, Ord k) => (k -> a -> Bool) -> Series k a -> Series k a Source #
Filter elements, taking into account the corresponding key. Only elements for which
the predicate is True
are kept.
Mapping with effects
mapWithKeyM :: (Unbox a, Unbox b, Monad m, Ord k) => (k -> a -> m b) -> Series k a -> m (Series k b) Source #
\(O(n)\) Apply the monadic action to every element of a series and its index, yielding a series of results.
mapWithKeyM_ :: (Unbox a, Monad m) => (k -> a -> m b) -> Series k a -> m () Source #
\(O(n)\) Apply the monadic action to every element of a series and its index, discarding the results.
forWithKeyM :: (Unbox a, Unbox b, Monad m, Ord k) => Series k a -> (k -> a -> m b) -> m (Series k b) Source #
\(O(n)\) Apply the monadic action to all elements of the series and their associated keys, yielding a series of results.
forWithKeyM_ :: (Unbox a, Monad m) => Series k a -> (k -> a -> m b) -> m () Source #
\(O(n)\) Apply the monadic action to all elements of the series and their associated keys, discarding the results.
Combining series
zipWithMatched :: (Unbox a, Unbox b, Unbox c, Ord k) => (a -> b -> c) -> Series k a -> Series k b -> Series k c Source #
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 [ ('a', 0::Int), ('b', 1), ('g', 2) ]
>>>
let ys = Series.fromList [ ('a', 10::Int), ('b', 11), ('d', 13) ]
>>>
zipWithMatched (+) xs ys
index | values ----- | ------ 'a' | 10 'b' | 12
zipWithKey :: (Unbox a, Unbox b, Unbox c, Unbox k, Ord k) => (k -> a -> b -> c) -> Series k a -> Series k b -> Series k c Source #
Apply a function elementwise to two series, matching elements based on their keys. Keys present only in the left or right series are dropped.
>>>
import Data.Char ( ord )
>>>
let xs = Series.fromList [ ('a', 0::Int), ('b', 1), ('c', 2) ]
>>>
let ys = Series.fromList [ ('a', 10::Int), ('b', 11), ('d', 13) ]
>>>
zipWithKey (\k x y -> ord k + x + y) xs ys
index | values ----- | ------ 'a' | 107 'b' | 110
zipWithMatched3 :: (Unbox a, Unbox b, Unbox c, Unbox d, Ord k) => (a -> b -> c -> d) -> Series k a -> Series k b -> Series k c -> Series k d Source #
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 [ ('a', 0::Int), ('b', 1), ('g', 2) ]
>>>
let ys = Series.fromList [ ('a', 10::Int), ('b', 11), ('d', 13) ]
>>>
let zs = Series.fromList [ ('a', 20::Int), ('d', 13), ('e', 6) ]
>>>
zipWithMatched3 (\x y z -> x + y + z) xs ys zs
index | values ----- | ------ 'a' | 30
zipWithKey3 :: (Unbox a, Unbox b, Unbox c, Unbox d, Unbox k, Ord k) => (k -> a -> b -> c -> d) -> Series k a -> Series k b -> Series k c -> Series k d Source #
Apply a function elementwise to three series, matching elements based on their keys. Keys present only in the left or right series are dropped.
>>>
import Data.Char ( ord )
>>>
let xs = Series.fromList [ ('a', 0::Int), ('b', 1), ('g', 2) ]
>>>
let ys = Series.fromList [ ('a', 10::Int), ('b', 11), ('d', 13) ]
>>>
let zs = Series.fromList [ ('a', 20::Int), ('b', 7), ('d', 5) ]
>>>
zipWithKey3 (\k x y z -> ord k + x + y + z) xs ys zs
index | values ----- | ------ 'a' | 127 'b' | 117
type ZipStrategy k a b = k -> a -> Maybe b Source #
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
for key Just
vk
, 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 =
(see Nothing
skipStrategy
).
skipStrategy :: ZipStrategy k a b Source #
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
mapStrategy :: (a -> b) -> ZipStrategy k a b Source #
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
constStrategy :: b -> ZipStrategy k a b Source #
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
:: (Ord k, Unbox a, Unbox b, Unbox c) | |
=> (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 k a | |
-> Series k b | |
-> Series k c |
Zip two Series
with a combining function, applying a ZipStrategy
when one key is present in one of the Series
but not both.
In the example below, we want to set the value to -100
(via
) for keys which are only present
in the left constStrategy
(-100)Series
, and drop keys (via skipStrategy
) which are only present in the `right Series
>>>
let xs = Series.fromList [ ('a', 0::Int), ('b', 1), ('g', 2) ]
>>>
let ys = Series.fromList [ ('a', 10::Int), ('b', 11), ('d', 13) ]
>>>
zipWithStrategy (+) (constStrategy (-100)) skipStrategy xs ys
index | values ----- | ------ 'a' | 10 'b' | 12 'g' | -100
Note that if you want to drop keys missing in either Series
, it is faster to use
than using zipWithMatched
f
.zipWithStrategy
f skipStrategy
skipStrategy
:: (Ord k, Unbox a, Unbox b, Unbox c, Unbox d) | |
=> (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 k a | |
-> Series k b | |
-> Series k c | |
-> Series k d |
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
than using zipWithMatched3
f
.zipWithStrategy3
f skipStrategy skipStrategy skipStrategy
zipWithMonoid :: (Monoid a, Monoid b, Unbox a, Unbox b, Unbox c, Ord k) => (a -> b -> c) -> Series k a -> Series k b -> Series k c Source #
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) ]
>>>
zipWithMonoid (<>) xs ys
index | values ----- | ------ "2023-01-01" | Sum {getSum = 6} "2023-01-02" | Sum {getSum = 2} "2023-01-03" | Sum {getSum = 7}
esum :: (Ord k, Num a, Unbox a) => Series k a -> Series k a -> Series k a Source #
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
eproduct :: (Ord k, Num a, Unbox a) => Series k a -> Series k a -> Series k a Source #
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
unzip :: (Unbox a, Unbox b) => Series k (a, b) -> (Series k a, Series k b) Source #
\(O(n)\) Unzip a Series
of 2-tuples.
unzip3 :: (Unbox a, Unbox b, Unbox c) => Series k (a, b, c) -> (Series k a, Series k b, Series k c) Source #
\(O(n)\) Unzip a Series
of 3-tuples.
Index manipulation
require :: (Unbox a, Ord k) => (k -> a) -> Series k a -> Index k -> Series k a Source #
Require a series to have a specific Index
.
Contrary to select
, all keys in the Index
will be present in the resulting series.
Note that unlike the implementation for boxed series (require
), missing keys need to be mapped to some values because unboxed
series cannot contain values of type
. Maybe
a
In the example below, the missing value for key "Taipei"
is mapped to 0:
>>>
let xs = Series.fromList [("Paris", 1 :: Int), ("London", 2), ("Lisbon", 4)]
>>>
xs
index | values ----- | ------ "Lisbon" | 4 "London" | 2 "Paris" | 1>>>
require (const 0) xs (Index.fromList ["Paris", "Lisbon", "Taipei"])
index | values ----- | ------ "Lisbon" | 4 "Paris" | 1 "Taipei" | 0
dropIndex :: Series k a -> Series Int a Source #
\(O(n)\) Drop the index of a series by replacing it with an Int
-based index. Values will
be indexed from 0.
>>>
let xs = Series.fromList [("Paris", 1 :: Int), ("London", 2), ("Lisbon", 4)]
>>>
xs
index | values ----- | ------ "Lisbon" | 4 "London" | 2 "Paris" | 1>>>
dropIndex xs
index | values ----- | ------ 0 | 4 1 | 2 2 | 1
Accessors
Bulk access
select :: (Unbox a, Selection s, Ord k) => Series k a -> s k -> Series k a infixl 1 Source #
Select a subseries. There are a few ways to do this.
The first way to do this is to select a sub-series based on random keys. For example,
selecting a subseries from an Index
:
>>>
let xs = Series.fromList [('a', 10::Int), ('b', 20), ('c', 30), ('d', 40)]
>>>
xs `select` Index.fromList ['a', 'd']
index | values ----- | ------ 'a' | 10 'd' | 40
The second way to select a sub-series is to select all keys in a range:
>>>
xs `select` 'b' `to` 'c'
index | values ----- | ------ 'b' | 20 'c' | 30
Note that with select
, you'll always get a sub-series; if you ask for a key which is not
in the series, it'll be ignored:
>>>
xs `select` Index.fromList ['a', 'd', 'e']
index | values ----- | ------ 'a' | 10 'd' | 40
See require
if you want to ensure that all keys are present.
selectWhere :: (Unbox a, Ord k) => Series k a -> Series k Bool -> Series k a Source #
Select a sub-series from a series matching a condition.
>>>
let xs = Series.fromList [("Paris", 1 :: Int), ("London", 2), ("Lisbon", 4)]
>>>
xs
index | values ----- | ------ "Lisbon" | 4 "London" | 2 "Paris" | 1>>>
xs `selectWhere` (Series.map (>1) xs)
index | values ----- | ------ "Lisbon" | 4 "London" | 2
Datatype representing an inclusive range of keys, which can either be bounded
or unbounded. The canonical ways to construct a Range
are to use to
, from
, and upto
:
>>>
'a' `to` 'z'
Range (from 'a' to 'z')>>>
from 'd'
Range (from 'd')>>>
upto 'q'
Range (up to 'q')
A Range
can be used to efficiently select a sub-series with select
.
Class for datatypes which can be used to select sub-series using select
.
There are two use-cases for select
:
- Bulk random-access (selecting from an
Index
of keys); - Bulk ordered access (selecting from a
Range
of keys).
See the documentation for select
.
Instances
Selection Set Source # | Selecting a sub-series from a |
Selection Range Source # | Selecting a sub-series based on a |
Selection Index Source # | |
Selection List Source # | Selecting a sub-series from a list is a convenience function. Internally, the list is converted to an index first. |
Single-element access
at :: (Unbox a, Ord k) => Series k a -> k -> Maybe a Source #
\(O(\log n)\). Extract a single value from a series, by key.
>>>
let xs = Series.fromList [("Paris", 1 :: Int), ("London", 2), ("Lisbon", 4)]
>>>
xs `at` "Paris"
Just 1>>>
xs `at` "Sydney"
Nothing
iat :: Unbox a => Series k a -> Int -> Maybe a Source #
\(O(1)\). Extract a single value from a series, by index.
>>>
let xs = Series.fromList [("Paris", 1 :: Int), ("London", 2), ("Lisbon", 4)]
>>>
xs
index | values ----- | ------ "Lisbon" | 4 "London" | 2 "Paris" | 1>>>
xs `iat` 0
Just 4>>>
xs `iat` 3
Nothing
Replacement
replace :: (Unbox a, Ord k) => Series k a -> Series k a -> Series k a Source #
Replace values in the right series from values in the left series at matching keys. Keys not in the right series are unaffected.
See (|->)
and (<-|)
, which might be more readable.
>>>
let xs = Series.fromList [("Paris", 1 :: Int), ("London", 2), ("Lisbon", 4)]
>>>
xs
index | values ----- | ------ "Lisbon" | 4 "London" | 2 "Paris" | 1>>>
let ys = Series.singleton "Paris" (99::Int)
>>>
ys `replace` xs
index | values ----- | ------ "Lisbon" | 4 "London" | 2 "Paris" | 99
(|->) :: (Unbox a, Ord k) => Series k a -> Series k a -> Series k a infix 6 Source #
Replace values in the right series from values in the left series at matching keys. Keys not in the right series are unaffected.
>>>
let xs = Series.fromList [("Paris", 1 :: Int), ("London", 2), ("Lisbon", 4)]
>>>
xs
index | values ----- | ------ "Lisbon" | 4 "London" | 2 "Paris" | 1>>>
let ys = Series.singleton "Paris" (99::Int)
>>>
ys |-> xs
index | values ----- | ------ "Lisbon" | 4 "London" | 2 "Paris" | 99
(<-|) :: (Unbox a, Ord k) => Series k a -> Series k a -> Series k a infix 6 Source #
Replace values in the left series from values in the right series at matching keys. Keys not in the left series are unaffected.
>>>
let xs = Series.fromList [("Paris", 1 :: Int), ("London", 2), ("Lisbon", 4)]
>>>
xs
index | values ----- | ------ "Lisbon" | 4 "London" | 2 "Paris" | 1>>>
let ys = Series.singleton "Paris" (99::Int)
>>>
xs <-| ys
index | values ----- | ------ "Lisbon" | 4 "London" | 2 "Paris" | 99
Grouping and windowing operations
Group values in a Series
by some grouping function (k -> g
).
The provided grouping function is guaranteed to operate on a non-empty Series
.
This function is expected to be used in conjunction with aggregate
:
>>>
import Data.Maybe ( fromMaybe )
>>>
type Date = (Int, String)
>>>
month :: (Date -> String) = snd
>>>
:{
let xs = Series.fromList [ ((2020, "January") :: Date, 0 :: Int) , ((2021, "January"), -5) , ((2020, "June") , 20) , ((2021, "June") , 25) ] in xs `groupBy` month `aggregateWith` (fromMaybe 0 . minimum) :} index | values ----- | ------ "January" | -5 "June" | 20
aggregateWith :: (Ord g, Unbox a, Unbox b) => Grouping k g a -> (Series k a -> b) -> Series g b Source #
Aggregate groups resulting from a call to groupBy
:
>>>
import Data.Maybe ( fromMaybe )
>>>
type Date = (Int, String)
>>>
month :: (Date -> String) = snd
>>>
:{
let xs = Series.fromList [ ((2020, "January") :: Date, 0 :: Int) , ((2021, "January"), -5) , ((2020, "June") , 20) , ((2021, "June") , 25) ] in xs `groupBy` month `aggregateWith` (fromMaybe 0 . minimum) :} index | values ----- | ------ "January" | -5 "June" | 20
If you want to aggregate groups using a binary function, see foldWith
which
may be much faster.
foldWith :: (Ord g, Unbox a) => Grouping k g a -> (a -> a -> a) -> Series g a Source #
Aggregate each group in a Grouping
using a binary function.
While this is not as expressive as aggregateWith
, users looking for maximum
performance should use foldWith
as much as possible.
windowing :: (Ord k, Unbox a, Unbox b) => (k -> Range k) -> (Series k a -> b) -> Series k a -> Series k b Source #
General-purpose window aggregation.
>>>
:{
let (xs :: Series.Series Int Int) = Series.fromList [ (1, 0) , (2, 1) , (3, 2) , (4, 3) , (5, 4) , (6, 5) ] in windowing (\k -> k `to` (k+2)) sum xs :} index | values ----- | ------ 1 | 3 2 | 6 3 | 9 4 | 12 5 | 9 6 | 5
:: (Unbox a, Unbox b) | |
=> Series k a | Series vector |
-> (Series k a -> b) | Aggregation function |
-> Series k b | Resulting vector |
Expanding window aggregation.
>>>
:{
let (xs :: Series Int Int) = fromList [ (1, 0) , (2, 1) , (3, 2) , (4, 3) , (5, 4) , (6, 5) ] in (xs `expanding` sum) :: Series Int Int :} index | values ----- | ------ 1 | 0 2 | 1 3 | 3 4 | 6 5 | 10 6 | 15
Folds
General folds
fold :: Unbox a => Fold a b -> Series k a -> b Source #
\(O(n)\) Execute a Fold
over a Series
.
>>>
let xs = Series.fromList (zip [0..] [1,2,3,4]) :: Series Int Double
>>>
xs
index | values ----- | ------ 0 | 1.0 1 | 2.0 2 | 3.0 3 | 4.0>>>
import Control.Foldl (variance)
>>>
fold variance xs
1.25
See also foldM
for monadic folds, and foldWithKey
to take keys into
account while folding.
foldM :: (Monad m, Unbox a) => FoldM m a b -> Series k a -> m b Source #
\(O(n)\) Execute a monadic FoldM
over a Series
.
See also fold
for pure folds, and foldMWithKey
to take keys into
account while folding.
foldMap :: (Monoid m, Unbox a) => (a -> m) -> Series k a -> m Source #
\(O(n)\) Map each element of the structure to a monoid and combine the results.
foldMapWithKey :: (Monoid m, Unbox a, Unbox k) => (k -> a -> m) -> Series k a -> m Source #
\(O(n)\) Map each element and associated key of the structure to a monoid and combine the results.
Specialized folds
mean :: Fractional a => Fold a a #
Compute a numerically stable arithmetic mean of all elements
variance :: Fractional a => Fold a a #
Compute a numerically stable (population) variance over all elements
std :: Floating a => Fold a a #
Compute a numerically stable (population) standard deviation over all elements
all :: Unbox a => (a -> Bool) -> Series k a -> Bool Source #
\(O(n)\) Check if all elements satisfy the predicate.
any :: Unbox a => (a -> Bool) -> Series k a -> Bool Source #
\(O(n)\) Check if any element satisfies the predicate.
product :: (Unbox a, Num a) => Series k a -> a Source #
\(O(n)\) Compute the product of the elements.
argmin :: (Ord a, Unbox a) => Series k a -> Maybe k Source #
\(O(n)\) Find the index of the minimum element in the input series.
If the input series is empty, Nothing
is returned.
The index of the first occurrence of the minimum element is returned. >>> import qualified Data.Series.Unboxed as Series >>> :{ let (xs :: Series.Series Int Int) = Series.fromList [ (1, 1) , (2, 1) , (3, 2) , (4, 0) , (5, 4) , (6, 5) ] in argmin xs :} Just 4
argmax :: (Ord a, Unbox a) => Series k a -> Maybe k Source #
\(O(n)\) Find the index of the maximum element in the input series.
If the input series is empty, Nothing
is returned.
The index of the first occurrence of the maximum element is returned.
>>>
import qualified Data.Series.Unboxed as Series
>>>
:{
let (xs :: Series.Series Int Int) = Series.fromList [ (1, 0) , (2, 1) , (3, 2) , (4, 7) , (5, 4) , (6, 5) ] in argmax xs :} Just 4
Scans
postscanl :: (Unbox a, Unbox b) => (a -> b -> a) -> a -> Series k b -> Series k a Source #
\(O(n)\) Left-to-right postscan.
>>>
let xs = Series.fromList (zip [0..] [1,2,3,4]) :: Series Int Int
>>>
xs
index | values ----- | ------ 0 | 1 1 | 2 2 | 3 3 | 4>>>
postscanl (+) 0 xs
index | values ----- | ------ 0 | 1 1 | 3 2 | 6 3 | 10
prescanl :: (Unbox a, Unbox b) => (a -> b -> a) -> a -> Series k b -> Series k a Source #
\(O(n)\) Left-to-right prescan.
>>>
let xs = Series.fromList (zip [0..] [1,2,3,4]) :: Series Int Int
>>>
xs
index | values ----- | ------ 0 | 1 1 | 2 2 | 3 3 | 4>>>
prescanl (+) 0 xs
index | values ----- | ------ 0 | 0 1 | 1 2 | 3 3 | 6
Displaying Series
display :: (Unbox a, Show k, Show a) => Series k a -> String Source #
Display a Series
using default DisplayOptions
.
>>>
let xs = Series.fromList (zip [0..] [1,2,3,4,5,6,7]) :: Series Int Int
>>>
putStrLn $ display xs
index | values ----- | ------ 0 | 1 1 | 2 2 | 3 ... | ... 4 | 5 5 | 6 6 | 7
displayWith :: Unbox a => DisplayOptions k a -> Series k a -> String Source #
Display a Series
using customizable DisplayOptions
.
>>>
let xs = Series.fromList (zip [0..] [1,2,3,4,5,6,7]) :: Series Int Int
>>>
import Data.List (replicate)
>>>
:{
let opts = DisplayOptions { maximumNumberOfRows = 4 , indexHeader = "keys" , valuesHeader = "vals" , keyDisplayFunction = (\i -> replicate i 'x') `noLongerThan` 5 , valueDisplayFunction = (\i -> replicate i 'o') } in putStrLn $ displayWith opts xs :} keys | vals ----- | ------ | o x | oo ... | ... xxxxx | oooooo xxx... | ooooooo
noLongerThan :: (a -> String) -> Int -> a -> String Source #
This function modifies existing functions to limit the width of its result.
>>>
let limit7 = (show :: Int -> String) `noLongerThan` 7
>>>
limit7 123456789
"123456..."
data DisplayOptions k a Source #
Options controlling how to display Series
in the displayWith
function.
Default options are provided by defaultDisplayOptions
.
To help with creating DisplayOptions
, see noLongerThan
.
DisplayOptions | |
|
defaultDisplayOptions :: (Show k, Show a) => DisplayOptions k a Source #
Default Series
display options.