conic-graphs-0.0.1.0: Vinyl-style extensible graphs.
Safe HaskellNone
LanguageHaskell2010

Data.Conic.Graph

Documentation

data RGraph :: (u -> *) -> Graph u -> * where Source #

Constructors

REmpty :: RGraph f 'Empty 
RVertex :: !(f r) -> RGraph f ('Vertex r) 
ROverlay :: !(RGraph f xs) -> !(RGraph f ys) -> RGraph f ('Overlay xs ys) 
RConnect :: !(RGraph f xs) -> !(RGraph f ys) -> RGraph f ('Connect xs ys) 

Instances

Instances details
(Eq (RGraph f x), Eq (RGraph f y)) => Eq (RGraph f ('Connect x y)) Source # 
Instance details

Defined in Data.Conic.Graph

Methods

(==) :: RGraph f ('Connect x y) -> RGraph f ('Connect x y) -> Bool #

(/=) :: RGraph f ('Connect x y) -> RGraph f ('Connect x y) -> Bool #

(Eq (RGraph f x), Eq (RGraph f y)) => Eq (RGraph f ('Overlay x y)) Source # 
Instance details

Defined in Data.Conic.Graph

Methods

(==) :: RGraph f ('Overlay x y) -> RGraph f ('Overlay x y) -> Bool #

(/=) :: RGraph f ('Overlay x y) -> RGraph f ('Overlay x y) -> Bool #

Eq (f r) => Eq (RGraph f ('Vertex r)) Source # 
Instance details

Defined in Data.Conic.Graph

Methods

(==) :: RGraph f ('Vertex r) -> RGraph f ('Vertex r) -> Bool #

(/=) :: RGraph f ('Vertex r) -> RGraph f ('Vertex r) -> Bool #

Eq (RGraph f ('Empty :: Graph u)) Source # 
Instance details

Defined in Data.Conic.Graph

Methods

(==) :: RGraph f 'Empty -> RGraph f 'Empty -> Bool #

(/=) :: RGraph f 'Empty -> RGraph f 'Empty -> Bool #

edge :: f a -> f b -> RGraph f (Eval (Edge a b)) Source #

data VertexList :: Graph a -> Exp [a] Source #

Instances

Instances details
type Eval (VertexList ('Connect x y) :: [a] -> Type) Source # 
Instance details

Defined in Data.Conic.Graph

type Eval (VertexList ('Connect x y) :: [a] -> Type) = Eval (LiftM2 ((++) :: [a] -> [a] -> [a] -> Type) (VertexList x) (VertexList y))
type Eval (VertexList ('Overlay x y) :: [a] -> Type) Source # 
Instance details

Defined in Data.Conic.Graph

type Eval (VertexList ('Overlay x y) :: [a] -> Type) = Eval (LiftM2 ((++) :: [a] -> [a] -> [a] -> Type) (VertexList x) (VertexList y))
type Eval (VertexList ('Vertex x) :: [k] -> Type) Source # 
Instance details

Defined in Data.Conic.Graph

type Eval (VertexList ('Vertex x) :: [k] -> Type) = '[x]
type Eval (VertexList ('Empty :: Graph a) :: [a] -> Type) Source # 
Instance details

Defined in Data.Conic.Graph

type Eval (VertexList ('Empty :: Graph a) :: [a] -> Type) = '[] :: [a]

rmap :: (forall x. f x -> g x) -> RGraph f rs -> RGraph g rs Source #

rtraverse :: Applicative h => (forall x. f x -> h (g x)) -> RGraph f rs -> h (RGraph g rs) Source #

rapply :: RGraph (Lift (->) f g) xs -> RGraph f xs -> RGraph g xs Source #

rzipWith :: (forall x. f x -> g x -> h x) -> RGraph f xs -> RGraph g xs -> RGraph h xs Source #