Copyright | (c) 2003 Graham Klyne 2009 Vasili I Galchin 2011 2012 2016 2020 2022 Douglas 2024 Burke |
---|---|
License | GPL V2 |
Maintainer | Douglas Burke |
Stability | experimental |
Portability | CPP, DeriveTraversable, DerivingStrategies, MultiParamTypeClasses |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
This module defines a Labelled Directed Graph and Label classes, and the Arc datatype.
Synopsis
- class LDGraph lg lb where
- emptyGraph :: lg lb
- setArcs :: lg lb -> ArcSet lb -> lg lb
- getArcs :: lg lb -> ArcSet lb
- extract :: Ord lb => Selector lb -> lg lb -> lg lb
- addGraphs :: Ord lb => lg lb -> lg lb -> lg lb
- delete :: Ord lb => lg lb -> lg lb -> lg lb
- labels :: Ord lb => lg lb -> Set lb
- nodes :: Ord lb => lg lb -> Set lb
- update :: (ArcSet lb -> ArcSet lb) -> lg lb -> lg lb
- class (Ord lb, Show lb) => Label lb where
- data Arc lb = Arc {}
- type ArcSet lb = Set (Arc lb)
- type Selector lb = Arc lb -> Bool
- arc :: lb -> lb -> lb -> Arc lb
- arcToTriple :: Arc lb -> (lb, lb, lb)
- arcFromTriple :: (lb, lb, lb) -> Arc lb
- hasLabel :: Eq lb => lb -> Arc lb -> Bool
- arcLabels :: Arc lb -> [lb]
- getComponents :: Ord b => (a -> [b]) -> Set a -> Set b
Documentation
class LDGraph lg lb where Source #
Labelled Directed Graph class.
Minimum required implementation:
emptyGraph
, setArcs
, and getArcs
.
emptyGraph :: lg lb Source #
Create the empty graph.
setArcs :: lg lb -> ArcSet lb -> lg lb Source #
Replace the existing arcs in the graph.
getArcs :: lg lb -> ArcSet lb Source #
Extract all the arcs from a graph
extract :: Ord lb => Selector lb -> lg lb -> lg lb Source #
Extract those arcs that match the given Selector
.
addGraphs :: Ord lb => lg lb -> lg lb -> lg lb Source #
Add the two graphs
:: Ord lb | |
=> lg lb | g1 |
-> lg lb | g2 |
-> lg lb | g2 - g1 -> g3 |
Remove those arcs in the first graph from the second graph
labels :: Ord lb => lg lb -> Set lb Source #
Enumerate the distinct labels contained in a graph;
that is, any label that appears in the subject,
predicate or object position of an Arc
.
nodes :: Ord lb => lg lb -> Set lb Source #
Enumerate the distinct nodes contained in a graph;
that is, any label that appears in the subject
or object position of an Arc
.
update :: (ArcSet lb -> ArcSet lb) -> lg lb -> lg lb Source #
Update the arcs in a graph using a supplied function.
Instances
class (Ord lb, Show lb) => Label lb where Source #
Label class.
A label may have a fixed binding, which means that the label identifies (is) a particular graph node, and different such labels are always distinct nodes. Alternatively, a label may be unbound (variable), which means that it is a placeholder for an unknown node label. Unbound node labels are used as graph-local identifiers for indicating when the same node appears in several arcs.
For the purposes of graph-isomorphism testing, fixed labels are matched when they are the same. Variable labels may be matched with any other variable label. Our definition of isomorphism (for RDF graphs) does not match variable labels with fixed labels.
labelIsVar :: lb -> Bool Source #
Does this node have a variable binding?
labelHash :: Int -> lb -> Int Source #
Calculate the hash of the label using the supplied seed.
getLocal :: lb -> String Source #
Extract the local id from a variable node.
makeLabel :: String -> lb Source #
Make a label value from a local id.
Instances
Label LabelMem Source # | |
Label RDFLabel Source # | |
Label lb => Label (ScopedLabel lb) Source # | |
Defined in Swish.GraphMatch labelIsVar :: ScopedLabel lb -> Bool Source # labelHash :: Int -> ScopedLabel lb -> Int Source # getLocal :: ScopedLabel lb -> String Source # makeLabel :: String -> ScopedLabel lb Source # |
Arc type.
Prior to 0.7.0.0
you could also use asubj
, apred
and aobj
to access the elements of the arc.
Instances
Foldable Arc Source # | |
Defined in Swish.GraphClass fold :: Monoid m => Arc m -> m # foldMap :: Monoid m => (a -> m) -> Arc a -> m # foldMap' :: Monoid m => (a -> m) -> Arc a -> m # foldr :: (a -> b -> b) -> b -> Arc a -> b # foldr' :: (a -> b -> b) -> b -> Arc a -> b # foldl :: (b -> a -> b) -> b -> Arc a -> b # foldl' :: (b -> a -> b) -> b -> Arc a -> b # foldr1 :: (a -> a -> a) -> Arc a -> a # foldl1 :: (a -> a -> a) -> Arc a -> a # elem :: Eq a => a -> Arc a -> Bool # maximum :: Ord a => Arc a -> a # | |
Traversable Arc Source # | |
Functor Arc Source # | |
Show lb => Show (Arc lb) Source # | |
Eq lb => Eq (Arc lb) Source # | |
Ord lb => Ord (Arc lb) Source # | |
Hashable lb => Hashable (Arc lb) Source # | |
Defined in Swish.GraphClass |
:: lb | The subject of the arc. |
-> lb | The predicate of the arc. |
-> lb | The object of the arc. |
-> Arc lb |
Create an arc.
arcToTriple :: Arc lb -> (lb, lb, lb) Source #
Convert an Arc into a tuple.
arcFromTriple :: (lb, lb, lb) -> Arc lb Source #
Create an Arc from a tuple.