nat-map
Safe HaskellNone
LanguageHaskell2010

Data.NatMap

Synopsis

Documentation

data NatMap (f :: Type -> Type) (g :: Type -> Type) Source #

Data structure which represents partial natural transformations, like usual Map which represents partial functions.

Map k v can be seen as a partial function.

m :: Map k v
(k -> Data.Map.lookup k m) :: k -> Maybe v

Analogically, a NatMap f g can be seen as a partial natural transformation, in the same sense Map represents a partial function.

nm :: NatMap f g
(fa -> lookup fa nm) :: forall a. f a -> Maybe (g a)

Instances

Instances details
(WeakEq f, Eq (g Var)) => Eq (NatMap f g) Source # 
Instance details

Defined in Data.NatMap

Methods

(==) :: NatMap f g -> NatMap f g -> Bool #

(/=) :: NatMap f g -> NatMap f g -> Bool #

(WeakOrd f, Ord (g Var)) => Ord (NatMap f g) Source # 
Instance details

Defined in Data.NatMap

Methods

compare :: NatMap f g -> NatMap f g -> Ordering #

(<) :: NatMap f g -> NatMap f g -> Bool #

(<=) :: NatMap f g -> NatMap f g -> Bool #

(>) :: NatMap f g -> NatMap f g -> Bool #

(>=) :: NatMap f g -> NatMap f g -> Bool #

max :: NatMap f g -> NatMap f g -> NatMap f g #

min :: NatMap f g -> NatMap f g -> NatMap f g #

Entry

data Entry (f :: Type -> Type) (g :: Type -> Type) Source #

Instances

Instances details
(Show (f Ignored), Show (g Var)) => Show (Entry f g) Source # 
Instance details

Defined in Data.NatMap

Methods

showsPrec :: Int -> Entry f g -> ShowS #

show :: Entry f g -> String #

showList :: [Entry f g] -> ShowS #

(WeakEq f, Eq (g Var)) => Eq (Entry f g) Source # 
Instance details

Defined in Data.NatMap

Methods

(==) :: Entry f g -> Entry f g -> Bool #

(/=) :: Entry f g -> Entry f g -> Bool #

(WeakOrd f, Ord (g Var)) => Ord (Entry f g) Source # 
Instance details

Defined in Data.NatMap

Methods

compare :: Entry f g -> Entry f g -> Ordering #

(<) :: Entry f g -> Entry f g -> Bool #

(<=) :: Entry f g -> Entry f g -> Bool #

(>) :: Entry f g -> Entry f g -> Bool #

(>=) :: Entry f g -> Entry f g -> Bool #

max :: Entry f g -> Entry f g -> Entry f g #

min :: Entry f g -> Entry f g -> Entry f g #

getKeyValue :: forall (f :: Type -> Type) g. Entry f g -> (Shape f, g Var) Source #

makeEntry :: (Traversable f, Traversable g, Ord k) => f k -> g k -> Maybe (Entry f g) Source #

makeIdEntry :: Traversable f => f k -> Entry f f Source #

unsafeMakeEntry :: (Traversable f, Functor g, Ord k) => f k -> g k -> Entry f g Source #

Construction

empty :: forall (f :: Type -> Type) (g :: Type -> Type). NatMap f g Source #

singleton :: forall (f :: Type -> Type) (g :: Type -> Type). Entry f g -> NatMap f g Source #

partialIdentity :: (WeakOrd f, Traversable f) => [f a] -> NatMap f f Source #

fromEntries :: forall (f :: Type -> Type) (g :: Type -> Type). WeakOrd f => [Entry f g] -> NatMap f g Source #

insert :: forall (f :: Type -> Type) (g :: Type -> Type). WeakOrd f => Entry f g -> NatMap f g -> NatMap f g Source #

delete :: forall f any (g :: Type -> Type). WeakOrd f => f any -> NatMap f g -> NatMap f g Source #

Queries

size :: forall (f :: Type -> Type) (g :: Type -> Type). NatMap f g -> Int Source #

member :: forall f a (g :: Type -> Type). WeakOrd f => f a -> NatMap f g -> Bool Source #

notMember :: forall f a (g :: Type -> Type). WeakOrd f => f a -> NatMap f g -> Bool Source #

lookup :: (WeakOrd f, Foldable f, Functor g) => f a -> NatMap f g -> Maybe (g a) Source #

lookup_ :: forall (f :: Type -> Type) g. (WeakOrd f, Functor g) => Shape f -> NatMap f g -> Maybe (g Var) Source #

keys :: forall (f :: Type -> Type) (g :: Type -> Type). NatMap f g -> [Shape f] Source #

toEntries :: forall (f :: Type -> Type) (g :: Type -> Type). Traversable f => NatMap f g -> [Entry f g] Source #

Map, Filter, Traversal

map1 :: forall g h (f :: Type -> Type). (forall a. g a -> h a) -> NatMap f g -> NatMap f h Source #

mapMaybe1 :: forall g h (f :: Type -> Type). (forall a. g a -> Maybe (h a)) -> NatMap f g -> NatMap f h Source #

traverse1 :: forall m g h (f :: Type -> Type). Applicative m => (forall a. g a -> m (h a)) -> NatMap f g -> m (NatMap f h) Source #

wither1 :: forall m g h (f :: Type -> Type). Applicative m => (forall a. g a -> m (Maybe (h a))) -> NatMap f g -> m (NatMap f h) Source #

mapWithKey1 :: Traversable f => (forall a. Ord a => f a -> g a -> h a) -> NatMap f g -> NatMap f h Source #

mapMaybeWithKey1 :: Traversable f => (forall a. Ord a => f a -> g a -> Maybe (h a)) -> NatMap f g -> NatMap f h Source #

traverseWithKey1 :: (Traversable f, Applicative m) => (forall a. Ord a => f a -> g a -> m (h a)) -> NatMap f g -> m (NatMap f h) Source #

witherWithKey1 :: (Traversable f, Applicative m) => (forall a. Ord a => f a -> g a -> m (Maybe (h a))) -> NatMap f g -> m (NatMap f h) Source #

Combinators

union :: forall (f :: Type -> Type) (g :: Type -> Type). WeakOrd f => NatMap f g -> NatMap f g -> NatMap f g Source #

unionWith :: forall (f :: Type -> Type) g. WeakOrd f => (forall a. g a -> g a -> g a) -> NatMap f g -> NatMap f g -> NatMap f g Source #

consistentUnion :: forall (f :: Type -> Type) (g :: Type -> Type). (WeakOrd f, Eq (g Var)) => NatMap f g -> NatMap f g -> Maybe (NatMap f g) Source #

As partial natural transformation

identity :: forall (f :: Type -> Type). PTraversable f => NatMap f f Source #

compose :: forall (f :: Type -> Type) (g :: Type -> Type) (h :: Type -> Type). (WeakOrd f, WeakOrd g, Foldable g, Functor h) => NatMap g h -> NatMap f g -> NatMap f h Source #

outerNat :: forall (f :: Type -> Type) (g :: Type -> Type) (h :: Type -> Type). (Traversable f, Traversable g, PTraversable h, Ord (f (h Ignored))) => NatMap f g -> NatMap (Compose f h) (Compose g h) Source #

innerNat :: forall (f :: Type -> Type) (g :: Type -> Type) (h :: Type -> Type). (Traversable f, Traversable g, PTraversable h, WeakOrd f) => NatMap f g -> NatMap (Compose h f) (Compose h g) Source #

horizontalCompose :: forall (f :: Type -> Type) (g :: Type -> Type) (h :: Type -> Type) (j :: Type -> Type). (Traversable f, Functor g, Traversable h, Functor j, Ord (f (h Ignored))) => NatMap f g -> NatMap h j -> NatMap (Compose f h) (Compose g j) Source #

Totality

fullSize :: forall (f :: Type -> Type) (g :: Type -> Type). PTraversable f => NatMap f g -> Int Source #

isTotal :: forall (f :: Type -> Type) (g :: Type -> Type). PTraversable f => NatMap f g -> Bool Source #

toTotal :: forall (f :: Type -> Type) (g :: Type -> Type). (PTraversable f, Functor g) => NatMap f g -> Maybe (f :~> g) Source #

Re-exports

newtype (f :: k -> Type) :~> (g :: k -> Type) infixr 0 #

A natural transformation suitable for storing in a container.

Constructors

NT 

Fields

Instances

Instances details
Transformation (f :: k -> Type) (g :: k -> Type) (f :~> g) 
Instance details

Defined in Control.Natural

Methods

(#) :: (f :~> g) -> forall (a :: k). f a -> g a #

Category ((:~>) :: (k -> Type) -> (k -> Type) -> Type) 
Instance details

Defined in Control.Natural

Methods

id :: forall (a :: k -> Type). a :~> a #

(.) :: forall (b :: k -> Type) (c :: k -> Type) (a :: k -> Type). (b :~> c) -> (a :~> b) -> a :~> c #

f ~ g => Monoid (f :~> g) 
Instance details

Defined in Control.Natural

Methods

mempty :: f :~> g #

mappend :: (f :~> g) -> (f :~> g) -> f :~> g #

mconcat :: [f :~> g] -> f :~> g #

f ~ g => Semigroup (f :~> g) 
Instance details

Defined in Control.Natural

Methods

(<>) :: (f :~> g) -> (f :~> g) -> f :~> g #

sconcat :: NonEmpty (f :~> g) -> f :~> g #

stimes :: Integral b => b -> (f :~> g) -> f :~> g #

wrapNT :: (forall (a :: k). f a -> g a) -> f :~> g #

wrapNT builds our natural transformation abstraction out of a natural transformation function.

An alias to NT provided for symmetry with unwrapNT.

unwrapNT :: Transformation f g t => t -> forall (a :: k). f a -> g a #

unwrapNT is the nonfix version of #. It is used to break natural transformation wrappers, including :~>.

Utility

data Var Source #

An opaque type representing syntactic variable.

Instances

Instances details
Show Var Source # 
Instance details

Defined in Data.NatMap

Methods

showsPrec :: Int -> Var -> ShowS #

show :: Var -> String #

showList :: [Var] -> ShowS #

Eq Var Source # 
Instance details

Defined in Data.NatMap

Methods

(==) :: Var -> Var -> Bool #

(/=) :: Var -> Var -> Bool #

Ord Var Source # 
Instance details

Defined in Data.NatMap

Methods

compare :: Var -> Var -> Ordering #

(<) :: Var -> Var -> Bool #

(<=) :: Var -> Var -> Bool #

(>) :: Var -> Var -> Bool #

(>=) :: Var -> Var -> Bool #

max :: Var -> Var -> Var #

min :: Var -> Var -> Var #

indices :: Traversable f => Shape f -> f Var Source #