javelin-0.1.2.0: Labeled one-dimensional arrays
Copyright(c) Laurent P. René de Cotret
LicenseMIT
Maintainerlaurent.decotret@outlook.com
Portabilityportable
Safe HaskellSafe-Inferred
LanguageGHC2021

Data.Series.Index.Internal

Description

WARNING

This module is considered internal. It contains functions which may be unsafe to use in general, for example requiring the data to be pre-sorted like fromDistinctAscList.

The Package Versioning Policy still applies.

Synopsis

Documentation

newtype Index k Source #

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.

Constructors

MkIndex (Set k) 

Instances

Instances details
Foldable Index Source # 
Instance details

Defined in Data.Series.Index.Definition

Methods

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 #

toList :: Index a -> [a] #

null :: Index a -> Bool #

length :: Index a -> Int #

elem :: Eq a => a -> Index a -> Bool #

maximum :: Ord a => Index a -> a #

minimum :: Ord a => Index a -> a #

sum :: Num a => Index a -> a #

product :: Num a => Index a -> a #

Selection Index Source # 
Instance details

Defined in Data.Series.Generic.View

Methods

select :: forall (v :: Type -> Type) a k. (Vector v a, Ord k) => Series v k a -> Index k -> Series v k a Source #

Ord k => Monoid (Index k) Source # 
Instance details

Defined in Data.Series.Index.Definition

Methods

mempty :: Index k #

mappend :: Index k -> Index k -> Index k #

mconcat :: [Index k] -> Index k #

Ord k => Semigroup (Index k) Source # 
Instance details

Defined in Data.Series.Index.Definition

Methods

(<>) :: Index k -> Index k -> Index k #

sconcat :: NonEmpty (Index k) -> Index k #

stimes :: Integral b => b -> Index k -> Index k #

Ord k => IsList (Index k) Source # 
Instance details

Defined in Data.Series.Index.Definition

Associated Types

type Item (Index k) #

Methods

fromList :: [Item (Index k)] -> Index k #

fromListN :: Int -> [Item (Index k)] -> Index k #

toList :: Index k -> [Item (Index k)] #

Show k => Show (Index k) Source # 
Instance details

Defined in Data.Series.Index.Definition

Methods

showsPrec :: Int -> Index k -> ShowS #

show :: Index k -> String #

showList :: [Index k] -> ShowS #

NFData k => NFData (Index k) Source # 
Instance details

Defined in Data.Series.Index.Definition

Methods

rnf :: Index k -> () #

Eq k => Eq (Index k) Source # 
Instance details

Defined in Data.Series.Index.Definition

Methods

(==) :: Index k -> Index k -> Bool #

(/=) :: Index k -> Index k -> Bool #

Ord k => Ord (Index k) Source # 
Instance details

Defined in Data.Series.Index.Definition

Methods

compare :: Index k -> Index k -> Ordering #

(<) :: Index k -> Index k -> Bool #

(<=) :: Index k -> Index k -> Bool #

(>) :: Index k -> Index k -> Bool #

(>=) :: Index k -> Index k -> Bool #

max :: Index k -> Index k -> Index k #

min :: Index k -> Index k -> Index k #

type Item (Index k) Source # 
Instance details

Defined in Data.Series.Index.Definition

type Item (Index k) = k

Unsafe construction

fromAscList :: Eq k => [k] -> Index k Source #

\(O(n)\) Build an Index from a list of elements in ascending order. The precondition that elements already be sorted is not checked.

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.

fromDistinctAscList :: [k] -> Index k Source #

\(O(n)\) Build an Index from a list of distinct elements in ascending order. The precondition that elements be unique and sorted is not checked.

fromAscVector :: (Vector v k, Ord k) => v k -> Index k Source #

\(O(n \log n)\) Build an Index from a Vector of elements in ascending order. The precondition that elements already be sorted is not checked.

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
>>> fromAscVector $ V.fromList ['a', 'b', 'b', 'c']
Index "abc"

fromDistinctAscVector :: Vector v k => v k -> Index k Source #

\(O(n)\) Build an Index from a Vector of unique elements in ascending order. The precondition that elements already be unique and sorted is not checked.

Functions with unchecked pre-conditions

mapMonotonic :: (k -> g) -> Index k -> Index g Source #

\(O(n)\) Map a monotonic function over keys in the index. Monotonic means that if a < b, then f a < f b. Using mapMonononic can be much faster than using map for a large Index. Note that the precondiction that the function be monotonic is not checked.

>>> mapMonotonic (+1) $ fromList [0::Int,1,2,3,4,5]
Index [1,2,3,4,5,6]

Unsafe indexing

elemAt :: HasCallStack => Int -> Index k -> k Source #

\(O(\log n)\) Returns the element at some integer index.

This function raises an exception if the integer index is out-of-bounds. Consider using lookupIndex instead.

findIndex :: HasCallStack => Ord k => k -> Index k -> Int Source #

\(O(\log n)\). Returns the integer index of a key. This function raises an exception if the key is not in the Index; see lookupIndex for a safe version.

>>> findIndex 'b' $ fromList ['a', 'b', 'c']
1