kvitable-1.0.0.0: Key/Value Indexed Table container and formatting library
Safe HaskellNone
LanguageHaskell2010

Data.KVITable

Description

The KVITable is similar to a Map, but the keys for a KVITable are made up of sequences of Key=Val values. The primary use of a KVITable is for rendering the information in various configurations and formats, although it may be used like any other container.

Synopsis

Documentation

data KVITable v Source #

The core KeyValue Indexed Table. This table is similar to a Map, but the values are indexed by a list of Key+Value combinations, and the table contents can be sparse.

Constructors

KVITable KeyVals (Key -> KeyVal) (Map KeySpec v) Text 

Instances

Instances details
Functor KVITable Source # 
Instance details

Defined in Data.KVITable

Methods

fmap :: (a -> b) -> KVITable a -> KVITable b #

(<$) :: a -> KVITable b -> KVITable a #

Foldable KVITable Source # 
Instance details

Defined in Data.KVITable

Methods

fold :: Monoid m => KVITable m -> m #

foldMap :: Monoid m => (a -> m) -> KVITable a -> m #

foldMap' :: Monoid m => (a -> m) -> KVITable a -> m #

foldr :: (a -> b -> b) -> b -> KVITable a -> b #

foldr' :: (a -> b -> b) -> b -> KVITable a -> b #

foldl :: (b -> a -> b) -> b -> KVITable a -> b #

foldl' :: (b -> a -> b) -> b -> KVITable a -> b #

foldr1 :: (a -> a -> a) -> KVITable a -> a #

foldl1 :: (a -> a -> a) -> KVITable a -> a #

toList :: KVITable a -> [a] #

null :: KVITable a -> Bool #

length :: KVITable a -> Int #

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

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

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

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

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

Traversable KVITable Source # 
Instance details

Defined in Data.KVITable

Methods

traverse :: Applicative f => (a -> f b) -> KVITable a -> f (KVITable b) #

sequenceA :: Applicative f => KVITable (f a) -> f (KVITable a) #

mapM :: Monad m => (a -> m b) -> KVITable a -> m (KVITable b) #

sequence :: Monad m => KVITable (m a) -> m (KVITable a) #

IsList (KVITable v) Source # 
Instance details

Defined in Data.KVITable

Associated Types

type Item (KVITable v) #

Methods

fromList :: [Item (KVITable v)] -> KVITable v #

fromListN :: Int -> [Item (KVITable v)] -> KVITable v #

toList :: KVITable v -> [Item (KVITable v)] #

Eq v => Eq (KVITable v) Source # 
Instance details

Defined in Data.KVITable

Methods

(==) :: KVITable v -> KVITable v -> Bool #

(/=) :: KVITable v -> KVITable v -> Bool #

Show v => Show (KVITable v) Source # 
Instance details

Defined in Data.KVITable

Methods

showsPrec :: Int -> KVITable v -> ShowS #

show :: KVITable v -> String #

showList :: [KVITable v] -> ShowS #

Semigroup (KVITable v) Source #

The KVITable semigroup is left biased (same as Data.Map). Note that joining tables can result in a table that has a different keyVals sequence than either input table.

Instance details

Defined in Data.KVITable

Methods

(<>) :: KVITable v -> KVITable v -> KVITable v #

sconcat :: NonEmpty (KVITable v) -> KVITable v #

stimes :: Integral b => b -> KVITable v -> KVITable v #

Monoid (KVITable v) Source # 
Instance details

Defined in Data.KVITable

Methods

mempty :: KVITable v #

mappend :: KVITable v -> KVITable v -> KVITable v #

mconcat :: [KVITable v] -> KVITable v #

type Item (KVITable v) Source # 
Instance details

Defined in Data.KVITable

type Item (KVITable v) = (KeySpec, v)

type Key = Text Source #

The Key is the first half of a tuple that makes up the list of keys (the KeySpec). The second half is the KeyVal.

type KeyVal = Text Source #

The KeyVal is the first half of a tuple that makes up the list of keys (the KeySpec). The first half is the Key.

type KeyVals = [(Key, [KeyVal])] Source #

The KeyVals specifies all valid values for a particular Key in the KVITable. The set of KeyVals can be provided at the initialization of the KVITable to ensure specific values are considered (especially if rendering includes blank rows or columns); if entries are added to the table with a KeyVal previously unknown for the Key, the KeyVals for the table is automatically updated to include the new KeyVal.

type KeySpec = [(Key, KeyVal)] Source #

The KeySpec is the list of tuples and defines the unique key for a value in the KVITable.

fromList :: [Item (KVITable v)] -> KVITable v Source #

Converts a list of ([(Key,Val)], Value) tuples to a KVI table.

toList :: KVITable v -> [Item (KVITable v)] Source #

Converts a KVI table to a list of ([(Key,Val)], Value) tuples.

lookup :: KeySpec -> KVITable v -> Maybe v Source #

Retrieve an entry from the KVITable given a keyspec. The keyspec may be minimally specified (i.e. it does not need to contain keys whose value is the default key value) and it may present the keys out of order and the lookup will still succeed (if there is a value for the normalized keyspec), but it will be faster to use the normalized key directly.

keyVals :: Lens' (KVITable v) KeyVals Source #

Fetch or set the keyvals list via lenses. Note that setting the keyval list will drop any current contents in the table that do not have entries in the keyvals list.

keyValGen :: Lens' (KVITable v) (Key -> KeyVal) Source #

Fetch or set the default KeyVal generator for this KVITable

valueColName :: Lens' (KVITable v) Text Source #

Fetch or set the column name for the actual value cell in the KVITable.

insert :: KeySpec -> v -> KVITable v -> KVITable v Source #

Inserts a new cell value into the table at the specified keyspec location. The keyspec may be minimally specified and out-of-order.

This may be an expensive operation if it has to extend the keyvals for the table. In general, insertion is expected to be less frequent than lookups so computation costs are biased towards the insertion operation.

foldlInsert :: KVITable v -> (KeySpec, v) -> KVITable v Source #

The foldlInsert is a convenience function that can be specified as the function argument of a foldl operation over the list form of a KVITable to generate the associated KVITable.

filter :: ((KeySpec, v) -> Bool) -> KVITable v -> KVITable v Source #

Filter KVITable to retain only the elements that satisfy some predicate.

adjust :: (v -> v) -> KeySpec -> KVITable v -> KVITable v Source #

Adjust a value at the specified keyspec; return the original KVITable if that keyspec is not found in the table.

adjustWithKey :: (KeySpec -> v -> v) -> KeySpec -> KVITable v -> KVITable v Source #

Adjust a value at the specified keyspec; return the original KVITable if that keyspec is not found in the table.

delete :: KeySpec -> KVITable v -> KVITable v Source #

Delete the value at the specified keyspec location in the KVITable. If the keyspec does not exist, the original table is returned.

update :: (v -> Maybe v) -> KeySpec -> KVITable v -> KVITable v Source #

Update the KVITable to remove or set a new value for the specified entry if the updating function returns Nothing or Just v, respectively. The update function is passed the value for the keyspec to be updated. If the value does not exist in the table, the original table is returned.

updateWithKey :: (KeySpec -> v -> Maybe v) -> KeySpec -> KVITable v -> KVITable v Source #

Update the KVITable to remove or set a new value for the specified entry if the updating function returns Nothing or Just v, respectively. The update function is passed both the keyspec and the current value at that key. If the value does not exist in the table, the original table is returned.

rows :: KVITable v -> [([KeyVal], v)] Source #

The rows function returns a set of rows for the KVITable as a list structure, where each list entry is a different row. A row consists of the values of the keys for that row followed by the value of the entry (to get the names of the keys, use keyVals).