compdata-0.12.1: Compositional Data Types
Copyright(c) 2014 Patrick Bahr
LicenseBSD3
MaintainerPatrick Bahr <paba@diku.dk>
Stabilityexperimental
Portabilitynon-portable (GHC Extensions)
Safe HaskellNone
LanguageHaskell2010

Data.Comp.Multi.Mapping

Description

This module provides functionality to construct mappings from positions in a functorial value.

Synopsis

Documentation

data Numbered a i Source #

This type is used for numbering components of a functorial value.

Constructors

Numbered Int (a i) 

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 #

Minimal complete definition

hmapM, htraverse

Instances

Instances details
HTraversable f => HTraversable (Cxt h f) Source # 
Instance details

Defined in Data.Comp.Multi.Term

Methods

hmapM :: forall (m :: Type -> Type) (a :: Type -> Type) (b :: Type -> Type). Monad m => NatM m a b -> NatM m (Cxt h f a) (Cxt h f b) Source #

htraverse :: forall (f0 :: Type -> Type) (a :: Type -> Type) (b :: Type -> Type). Applicative f0 => NatM f0 a b -> NatM f0 (Cxt h f a) (Cxt h f b) Source #

HTraversable f => HTraversable (f :&: a) Source # 
Instance details

Defined in Data.Comp.Multi.Ops

Methods

hmapM :: forall (m :: Type -> Type) (a0 :: Type -> Type) (b :: Type -> Type). Monad m => NatM m a0 b -> NatM m ((f :&: a) a0) ((f :&: a) b) Source #

htraverse :: forall (f0 :: Type -> Type) (a0 :: Type -> Type) (b :: Type -> Type). Applicative f0 => NatM f0 a0 b -> NatM f0 ((f :&: a) a0) ((f :&: a) b) Source #

(HTraversable f, HTraversable g) => HTraversable (f :+: g) Source # 
Instance details

Defined in Data.Comp.Multi.Ops

Methods

hmapM :: forall (m :: Type -> Type) (a :: Type -> Type) (b :: Type -> Type). Monad m => NatM m a b -> NatM m ((f :+: g) a) ((f :+: g) b) Source #

htraverse :: forall (f0 :: Type -> Type) (a :: Type -> Type) (b :: Type -> Type). Applicative f0 => NatM f0 a b -> NatM f0 ((f :+: g) a) ((f :+: g) b) Source #

class Mapping m (k :: * -> *) | m -> k where Source #

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.

empty :: m v Source #

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 #