Copyright | (c) Laurent P. René de Cotret |
---|---|
License | MIT-style |
Maintainer | Laurent P. René de Cotret |
Portability | portable |
Safe Haskell | Safe-Inferred |
Language | GHC2021 |
This module contains the definition of Index
, a sequence of unique and sorted
keys which can be used to efficient index a Series
.
Construction
Constructing an Index
can be done from the usual list using fromList
. Note that
the Index
length could be smaller than the input list, due to the requirement that
an Index
be a sequence of unique keys. A better way to construct an Index
is
to use a Set
(fromSet
)
For quick INLINABLE definitions of an Index
, you can also make use of the OverloadedLists
extension:
>>>
:set -XOverloadedLists
>>>
let (ix :: Index Int) = [1,2,3,4,5,5,5]
>>>
ix
Index [1,2,3,4,5]
Another useful function to construct an Index
is range
. This allows to build an Index
from a starting value up to an ending value, with a custom step function. For example,
here's an Index
with values from 1 to 10, in steps of 3:
>>>
range (+3) (1 :: Int) 10
Index [1,4,7,10]
Note that range
is a special case of the unfoldr
function, which is also provided in this module.
Set operations
Just like a Set
, Index
supports efficient member
, notMember
, union
, intersection
, and difference
operations.
Like Set
, the Semigroup
and Monoid
instance of Index
are defined using the union
operation:
>>>
fromList ['a', 'b', 'c'] <> fromList ['b', 'c', 'd']
Index "abcd"
Mapping
Because of the restriction that all keys be unique, an Index
is not a true Functor
; you can't use
fmap
to map elements of an index. Instead, you can use the general-purpose function map
. If you want
to map elements of an Index
with a monotonic function (i.e. a function which will not re-order elements and won't
create duplicate elements), you can use the mapMonotonic
function which operates faster.
Indexing
One of the key operations for Series
is to find the integer index of an element in an Index
. For this purpose, you
can use lookupIndex
:
>>>
lookupIndex 'b' $ fromList ['a', 'b', 'c']
Just 1>>>
lookupIndex 'd' $ fromList ['a', 'b', 'c']
Nothing
Synopsis
- data Index k
- singleton :: k -> Index k
- unfoldr :: Ord a => (b -> Maybe (a, b)) -> b -> Index a
- range :: Ord a => (a -> a) -> a -> a -> Index a
- class IsIndex t k where
- fromSet :: Set k -> Index k
- fromList :: Ord k => [k] -> Index k
- fromVector :: (Vector v k, Ord k) => v k -> Index k
- toSet :: Index k -> Set k
- toAscList :: Index k -> [k]
- toAscVector :: Vector v k => Index k -> v k
- null :: Index k -> Bool
- member :: Ord k => k -> Index k -> Bool
- notMember :: Ord k => k -> Index k -> Bool
- union :: Ord k => Index k -> Index k -> Index k
- intersection :: Ord k => Index k -> Index k -> Index k
- difference :: Ord k => Index k -> Index k -> Index k
- symmetricDifference :: Ord k => Index k -> Index k -> (Index k, Index k)
- contains :: Ord k => Index k -> Index k -> Bool
- size :: Index k -> Int
- take :: Int -> Index k -> Index k
- drop :: Int -> Index k -> Index k
- map :: Ord g => (k -> g) -> Index k -> Index g
- indexed :: Index k -> Index (Int, k)
- filter :: (k -> Bool) -> Index k -> Index k
- traverse :: (Applicative f, Ord b) => (k -> f b) -> Index k -> f (Index b)
- lookupIndex :: Ord k => k -> Index k -> Maybe Int
- insert :: Ord k => k -> Index k -> Index k
- delete :: Ord k => k -> Index k -> Index k
Documentation
Representation of the index of a series.
An index is a sequence of sorted elements. All elements are unique, much like a Set
.
You can construct an Index
from a set (fromSet
), from a list (fromList
), or from a vector (fromVector
). You can
also make use of the OverloadedLists
extension:
>>>
:set -XOverloadedLists
>>>
let (ix :: Index Int) = [1, 2, 3]
>>>
ix
Index [1,2,3]
Since keys in an Index
are always sorted and unique, Index
is not a Functor
. To map a function
over an Index
, use map
.
Instances
Foldable Index Source # | |
Defined in Data.Series.Index.Definition fold :: Monoid m => Index m -> m # foldMap :: Monoid m => (a -> m) -> Index a -> m # foldMap' :: Monoid m => (a -> m) -> Index a -> m # foldr :: (a -> b -> b) -> b -> Index a -> b # foldr' :: (a -> b -> b) -> b -> Index a -> b # foldl :: (b -> a -> b) -> b -> Index a -> b # foldl' :: (b -> a -> b) -> b -> Index a -> b # foldr1 :: (a -> a -> a) -> Index a -> a # foldl1 :: (a -> a -> a) -> Index a -> a # elem :: Eq a => a -> Index a -> Bool # maximum :: Ord a => Index a -> a # minimum :: Ord a => Index a -> a # | |
Selection Index Source # | |
Ord k => Monoid (Index k) Source # | |
Ord k => Semigroup (Index k) Source # | |
Ord k => IsList (Index k) Source # | |
Show k => Show (Index k) Source # | |
NFData k => NFData (Index k) Source # | |
Defined in Data.Series.Index.Definition | |
Eq k => Eq (Index k) Source # | |
Ord k => Ord (Index k) Source # | |
Defined in Data.Series.Index.Definition | |
type Item (Index k) Source # | |
Defined in Data.Series.Index.Definition |
Creation and Conversion
unfoldr :: Ord a => (b -> Maybe (a, b)) -> b -> Index a Source #
\(O(n \log n)\) Create an Index
from a seed value.
Note that the order in which elements are generated does not matter; elements are stored
in order. See the example below.
>>>
unfoldr (\x -> if x < 1 then Nothing else Just (x, x-1)) (7 :: Int)
Index [1,2,3,4,5,6,7]
:: Ord a | |
=> (a -> a) | Function to generate the next element in the index |
-> a | Starting value of the |
-> a | Ending value of the |
-> Index a |
\(O(n \log n)\) Create an Index
as a range of values. range f start end
will generate
an Index
with values [start, f start, f (f start), ... ]
such that the largest element
less or equal to end
is included. See examples below.
>>>
range (+3) (1 :: Int) 10
Index [1,4,7,10]>>>
range (+3) (1 :: Int) 11
Index [1,4,7,10]
class IsIndex t k where Source #
The IsIndex
typeclass allow for ad-hoc definition
of conversion functions, converting to / from Index
.
toIndex :: t -> Index k Source #
Construct an Index
from some container of keys. There is no
condition on the order of keys. Duplicate keys are silently dropped.
fromIndex :: Index k -> t Source #
Construct a container from keys of an Index
.
The elements are returned in ascending order of keys.
fromList :: Ord k => [k] -> Index k Source #
\(O(n \log n)\) Build an Index
from a list. Note that since an Index
is
composed of unique elements, the length of the index may not be
the same as the length of the input list:
>>>
fromList ['c', 'a', 'b', 'b']
Index "abc"
If the list is already sorted, fromAscList
is generally faster.
fromVector :: (Vector v k, Ord k) => v k -> Index k Source #
\(O(n \log n)\) Build an Index
from a Vector
. Note that since an Index
is
composed of unique elements, the length of the index may not be
the same as the length of the input vector:
>>>
import Data.Vector as V
>>>
fromVector $ V.fromList ['c', 'a', 'b', 'b']
Index "abc"
If the Vector
is already sorted, fromAscVector
is generally faster.
toAscList :: Index k -> [k] Source #
\(O(n)\) Convert an Index
to a list. Elements will be produced in ascending order.
toAscVector :: Vector v k => Index k -> v k Source #
\(O(n)\) Convert an Index
to a list. Elements will be produced in ascending order.
Set-like operations
member :: Ord k => k -> Index k -> Bool Source #
\(O(n \log n)\) Check whether the element is in the index.
notMember :: Ord k => k -> Index k -> Bool Source #
\(O(n \log n)\) Check whether the element is NOT in the index.
union :: Ord k => Index k -> Index k -> Index k Source #
\(O\bigl(m \log\bigl(\frac{n+1}{m+1}\bigr)\bigr), \; m \leq n\) Union of two Index
, containing
elements either in the left index, right right index, or both.
intersection :: Ord k => Index k -> Index k -> Index k Source #
\(O\bigl(m \log\bigl(\frac{n+1}{m+1}\bigr)\bigr), \; m \leq n\) Intersection of two Index
, containing
elements which are in both the left index and the right index.
difference :: Ord k => Index k -> Index k -> Index k Source #
\(O\bigl(m \log\bigl(\frac{n+1}{m+1}\bigr)\bigr), \; m \leq n\) Returns the elements of the first index which are not found in the second index.
>>>
difference (fromList ['a', 'b', 'c']) (fromList ['b', 'c', 'd'])
Index "a"
symmetricDifference :: Ord k => Index k -> Index k -> (Index k, Index k) Source #
\(O(n+m)\). The symmetric difference of two Index
.
The first element of the tuple is an Index
containing all elements which
are only found in the left Index
, while the second element of the tuple is an Index
containing
all elements which are only found in the right Index
:
>>>
left = fromList ['a', 'b', 'c']
>>>
right = fromList ['c', 'd', 'e']
>>>
left `symmetricDifference` right
(Index "ab",Index "de")
contains :: Ord k => Index k -> Index k -> Bool Source #
\(O\bigl(m \log\bigl(\frac{n+1}{m+1}\bigr)\bigr), \; m \leq n\).
(ix1 'contains' ix2)
indicates whether all keys in ix2
are also in ix1
.
take :: Int -> Index k -> Index k Source #
\(O(\log n)\). Take n
elements from the index, in ascending order.
Taking more than the number of elements in the index is a no-op:
>>>
take 10 $ fromList [1::Int,2,3]
Index [1,2,3]
drop :: Int -> Index k -> Index k Source #
\(O(\log n)\). Drop n
elements from the index, in ascending order.
Mapping and filtering
map :: Ord g => (k -> g) -> Index k -> Index g Source #
\(O(n \log n)\) Map a function over keys in the index.
Note that since keys in an Index
are unique, the length of the resulting
index may not be the same as the input:
>>>
map (\x -> if even x then 0::Int else 1) $ fromList [0::Int,1,2,3,4]
Index [0,1]
If the mapping is monotonic, see mapMonotonic
, which has better performance
characteristics.
indexed :: Index k -> Index (Int, k) Source #
\(O(n)\) Pair each key in the index with its position in the index, starting with 0:
>>>
indexed (fromList ['a', 'b', 'c', 'd'])
Index [(0,'a'),(1,'b'),(2,'c'),(3,'d')]
Since: 0.1.1.0
filter :: (k -> Bool) -> Index k -> Index k Source #
\(O(n)\) Filter elements satisfying a predicate.
>>>
filter even $ fromList [1::Int,2,3,4,5]
Index [2,4]
traverse :: (Applicative f, Ord b) => (k -> f b) -> Index k -> f (Index b) Source #
\(O(n \log n)\). Map each element of an Index
to an applicative action,
evaluate these actions from left to right, and collect the results.
Note that the data type Index
is not a member of Traversable
because it is not a Functor
.
Indexing
lookupIndex :: Ord k => k -> Index k -> Maybe Int Source #
\(O(\log n)\). Returns the integer index of a key, if the key is in the index.
>>>
lookupIndex 'b' $ fromList ['a', 'b', 'c']
Just 1>>>
lookupIndex 'd' $ fromList ['a', 'b', 'c']
Nothing