The core of this package is the Object
data type, which is used for
handling scalars, sequences and mappings in a nested manner. This
is the same structure used in JSON or Yaml data.
The Object
data type is polymorphic in its keys and values. Submodules
within this package provide more concrete datatypes, such as a String
Object
and a specialized scalar type.
Besides the Object
data type, there are utility functions and type classes
for converting objects around. Care has been taken to avoid any overloaded
instances for these type classes.
- data Object key val
- type StringObject = Object String String
- type TextObject = Object Text Text
- data Scalar
- type ScalarObject = Object String Scalar
- mapKeys :: (keyIn -> keyOut) -> Object keyIn val -> Object keyOut val
- mapValues :: (valIn -> valOut) -> Object key valIn -> Object key valOut
- mapKeysValues :: (keyIn -> keyOut) -> (valIn -> valOut) -> Object keyIn valIn -> Object keyOut valOut
- mapKeysValuesA :: Applicative f => (keyIn -> f keyOut) -> (valIn -> f valOut) -> Object keyIn valIn -> f (Object keyOut valOut)
- mapKeysValuesM :: Monad m => (keyIn -> m keyOut) -> (valIn -> m valOut) -> Object keyIn valIn -> m (Object keyOut valOut)
- data ObjectExtractError
- fromScalar :: Failure ObjectExtractError m => Object k v -> m v
- fromSequence :: Failure ObjectExtractError m => Object k v -> m [Object k v]
- fromMapping :: Failure ObjectExtractError m => Object k v -> m [(k, Object k v)]
- lookupObject :: (Show k, Eq k, Failure ObjectExtractError m) => k -> [(k, Object k v)] -> m (Object k v)
- lookupScalar :: (Show k, Eq k, Failure ObjectExtractError m) => k -> [(k, Object k v)] -> m v
- lookupSequence :: (Show k, Eq k, Failure ObjectExtractError m) => k -> [(k, Object k v)] -> m [Object k v]
- lookupMapping :: (Show k, Eq k, Failure ObjectExtractError m) => k -> [(k, Object k v)] -> m [(k, Object k v)]
Object data type
Can represent nested values as scalars, sequences and mappings. A sequence is synonymous with a list, while a mapping is synonymous with a list of pairs.
Note that instances of standard library type classes for this data type
leave the key untouched while altering the value. For example, the Functor
instance defines fmap
to be synonymous with mapValues
.
Convenient type synonyms
type StringObject = Object String StringSource
Scalar data type
type ScalarObject = Object String ScalarSource
Basic mapping of keys and values
mapKeys :: (keyIn -> keyOut) -> Object keyIn val -> Object keyOut valSource
Apply some conversion to the keys of an Object
, leaving the values
unchanged.
mapKeysValues :: (keyIn -> keyOut) -> (valIn -> valOut) -> Object keyIn valIn -> Object keyOut valOutSource
Apply a conversion to both the keys and values of an Object
.
mapKeysValuesA :: Applicative f => (keyIn -> f keyOut) -> (valIn -> f valOut) -> Object keyIn valIn -> f (Object keyOut valOut)Source
Apply an Applicative
conversion to both the keys and values of an
Object
.
mapKeysValuesM :: Monad m => (keyIn -> m keyOut) -> (valIn -> m valOut) -> Object keyIn valIn -> m (Object keyOut valOut)Source
The same as mapKeysValuesA
, but using a Monad
since some people are
more comfortable with Monad
s and not all Monad
s are Applicative
.
Extracting underlying values
data ObjectExtractError Source
fromScalar :: Failure ObjectExtractError m => Object k v -> m vSource
Extract a scalar from the input, failing if the input is a sequence or mapping.
fromSequence :: Failure ObjectExtractError m => Object k v -> m [Object k v]Source
Extract a sequence from the input, failing if the input is a scalar or mapping.
fromMapping :: Failure ObjectExtractError m => Object k v -> m [(k, Object k v)]Source
Extract a mapping from the input, failing if the input is a scalar or sequence.
Lookups
lookupObject :: (Show k, Eq k, Failure ObjectExtractError m) => k -> [(k, Object k v)] -> m (Object k v)Source
lookupScalar :: (Show k, Eq k, Failure ObjectExtractError m) => k -> [(k, Object k v)] -> m vSource
lookupSequence :: (Show k, Eq k, Failure ObjectExtractError m) => k -> [(k, Object k v)] -> m [Object k v]Source
lookupMapping :: (Show k, Eq k, Failure ObjectExtractError m) => k -> [(k, Object k v)] -> m [(k, Object k v)]Source