| Copyright | (c) 2014 Patrick Bahr | 
|---|---|
| License | BSD3 | 
| Maintainer | Patrick Bahr <paba@diku.dk> | 
| Stability | experimental | 
| Portability | non-portable (GHC Extensions) | 
| Safe Haskell | None | 
| Language | Haskell98 | 
Data.Comp.Multi.Mapping
Description
This module provides functionality to construct mappings from positions in a functorial value.
- data Numbered a i = Numbered Int (a i)
 - unNumbered :: Numbered a :-> a
 - number :: HTraversable f => f a :-> f (Numbered a)
 - class HFoldable t => HTraversable t
 - class Mapping m k | m -> k where
 - lookupNumMap :: a -> Int -> NumMap t a -> a
 
Documentation
This type is used for numbering components of a functorial value.
unNumbered :: Numbered a :-> a Source #
number :: HTraversable f => f a :-> f (Numbered a) Source #
This function numbers the components of the given functorial value with consecutive integers starting at 0.
class HFoldable t => HTraversable t Source #
Instances
| HTraversable f => HTraversable (Cxt h f) Source # | |
| HTraversable f => HTraversable ((:&:) * f a) Source # | |
| (HTraversable f, HTraversable g) => HTraversable ((:+:) * f g) Source # | |
class Mapping m k | m -> k where Source #
Minimal complete definition
Methods
(&) :: m v -> m v -> m v infixr 0 Source #
left-biased union of two mappings.
(|->) :: k i -> v -> m v infix 1 Source #
This operator constructs a singleton mapping.
This is the empty mapping.
prodMap :: v1 -> v2 -> m v1 -> m v2 -> m (v1, v2) Source #
This function constructs the pointwise product of two maps each with a default value.
findWithDefault :: a -> k i -> m a -> a Source #
Returns the value at the given key or returns the given default when the key is not an element of the map.
lookupNumMap :: a -> Int -> NumMap t a -> a Source #