guardian-0.4.0.0: The border guardian for your package dependencies
Safe HaskellSafe-Inferred
LanguageHaskell2010

Development.Guardian.Graph

Documentation

newtype CatMap k v Source #

Constructors

CatMap 

Fields

Instances

Instances details
(Semigroup v, Ord k) => Monoid (CatMap k v) Source # 
Instance details

Defined in Development.Guardian.Graph

Methods

mempty :: CatMap k v #

mappend :: CatMap k v -> CatMap k v -> CatMap k v #

mconcat :: [CatMap k v] -> CatMap k v #

(Semigroup v, Ord k) => Semigroup (CatMap k v) Source # 
Instance details

Defined in Development.Guardian.Graph

Methods

(<>) :: CatMap k v -> CatMap k v -> CatMap k v #

sconcat :: NonEmpty (CatMap k v) -> CatMap k v #

stimes :: Integral b => b -> CatMap k v -> CatMap k v #

newtype LOverlayed e a Source #

Constructors

LOverlayed 

Fields

Instances

Instances details
Monoid e => Monoid (LOverlayed e a) Source # 
Instance details

Defined in Development.Guardian.Graph

Methods

mempty :: LOverlayed e a #

mappend :: LOverlayed e a -> LOverlayed e a -> LOverlayed e a #

mconcat :: [LOverlayed e a] -> LOverlayed e a #

Monoid e => Semigroup (LOverlayed e a) Source # 
Instance details

Defined in Development.Guardian.Graph

Methods

(<>) :: LOverlayed e a -> LOverlayed e a -> LOverlayed e a #

sconcat :: NonEmpty (LOverlayed e a) -> LOverlayed e a #

stimes :: Integral b => b -> LOverlayed e a -> LOverlayed e a #

Generic (LOverlayed e a) Source # 
Instance details

Defined in Development.Guardian.Graph

Associated Types

type Rep (LOverlayed e a) :: Type -> Type #

Methods

from :: LOverlayed e a -> Rep (LOverlayed e a) x #

to :: Rep (LOverlayed e a) x -> LOverlayed e a #

(Show a, Show e) => Show (LOverlayed e a) Source # 
Instance details

Defined in Development.Guardian.Graph

Methods

showsPrec :: Int -> LOverlayed e a -> ShowS #

show :: LOverlayed e a -> String #

showList :: [LOverlayed e a] -> ShowS #

(Monoid e, Ord a, Eq e) => Eq (LOverlayed e a) Source # 
Instance details

Defined in Development.Guardian.Graph

Methods

(==) :: LOverlayed e a -> LOverlayed e a -> Bool #

(/=) :: LOverlayed e a -> LOverlayed e a -> Bool #

(Monoid e, Ord a, Ord e) => Ord (LOverlayed e a) Source # 
Instance details

Defined in Development.Guardian.Graph

Methods

compare :: LOverlayed e a -> LOverlayed e a -> Ordering #

(<) :: LOverlayed e a -> LOverlayed e a -> Bool #

(<=) :: LOverlayed e a -> LOverlayed e a -> Bool #

(>) :: LOverlayed e a -> LOverlayed e a -> Bool #

(>=) :: LOverlayed e a -> LOverlayed e a -> Bool #

max :: LOverlayed e a -> LOverlayed e a -> LOverlayed e a #

min :: LOverlayed e a -> LOverlayed e a -> LOverlayed e a #

type Rep (LOverlayed e a) Source # 
Instance details

Defined in Development.Guardian.Graph

type Rep (LOverlayed e a) = D1 ('MetaData "LOverlayed" "Development.Guardian.Graph" "guardian-0.4.0.0-1i0KmpldsqDJPVBdForgqe" 'True) (C1 ('MetaCons "LOverlayed" 'PrefixI 'True) (S1 ('MetaSel ('Just "getLOverlayed") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Graph e a))))

data ActualGraphs a b Source #

Constructors

AGs 

Fields

Instances

Instances details
Bifunctor ActualGraphs Source # 
Instance details

Defined in Development.Guardian.Graph

Methods

bimap :: (a -> b) -> (c -> d) -> ActualGraphs a c -> ActualGraphs b d #

first :: (a -> b) -> ActualGraphs a c -> ActualGraphs b c #

second :: (b -> c) -> ActualGraphs a b -> ActualGraphs a c #

Functor (ActualGraphs a) Source # 
Instance details

Defined in Development.Guardian.Graph

Methods

fmap :: (a0 -> b) -> ActualGraphs a a0 -> ActualGraphs a b #

(<$) :: a0 -> ActualGraphs a b -> ActualGraphs a a0 #

(Monoid a, Monoid b) => Monoid (ActualGraphs a b) Source # 
Instance details

Defined in Development.Guardian.Graph

(Semigroup a, Semigroup b) => Semigroup (ActualGraphs a b) Source # 
Instance details

Defined in Development.Guardian.Graph

Methods

(<>) :: ActualGraphs a b -> ActualGraphs a b -> ActualGraphs a b #

sconcat :: NonEmpty (ActualGraphs a b) -> ActualGraphs a b #

stimes :: Integral b0 => b0 -> ActualGraphs a b -> ActualGraphs a b #

Generic (ActualGraphs a b) Source # 
Instance details

Defined in Development.Guardian.Graph

Associated Types

type Rep (ActualGraphs a b) :: Type -> Type #

Methods

from :: ActualGraphs a b -> Rep (ActualGraphs a b) x #

to :: Rep (ActualGraphs a b) x -> ActualGraphs a b #

(Show a, Show b) => Show (ActualGraphs a b) Source # 
Instance details

Defined in Development.Guardian.Graph

(Eq a, Eq b) => Eq (ActualGraphs a b) Source # 
Instance details

Defined in Development.Guardian.Graph

Methods

(==) :: ActualGraphs a b -> ActualGraphs a b -> Bool #

(/=) :: ActualGraphs a b -> ActualGraphs a b -> Bool #

(Ord a, Ord b) => Ord (ActualGraphs a b) Source # 
Instance details

Defined in Development.Guardian.Graph

type Rep (ActualGraphs a b) Source # 
Instance details

Defined in Development.Guardian.Graph

type Rep (ActualGraphs a b) = D1 ('MetaData "ActualGraphs" "Development.Guardian.Graph" "guardian-0.4.0.0-1i0KmpldsqDJPVBdForgqe" 'False) (C1 ('MetaCons "AGs" 'PrefixI 'True) (S1 ('MetaSel ('Just "activatedGraph") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "exceptionGraph") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b)))