1{-# LANGUAGE ConstraintKinds, GADTs, RankNTypes, RecordWildCards #-}
2{-# OPTIONS_GHC -Wno-missing-fields #-}
3-----------------------------------------------------------------------------
4-- |
5-- Module     : Algebra.Graph.Test.API
6-- Copyright  : (c) Andrey Mokhov 2016-2019
7-- License    : MIT (see the file LICENSE)
8-- Maintainer : andrey.mokhov@gmail.com
9-- Stability  : experimental
10--
11-- The complete graph API used for generic testing.
12-----------------------------------------------------------------------------
13module Algebra.Graph.Test.API (
14    -- * Graph API
15    API (..), Mono (..), toIntAPI,
16
17    -- * APIs of various graph data types
18    adjacencyMapAPI, adjacencyIntMapAPI, graphAPI, undirectedGraphAPI, relationAPI,
19    symmetricRelationAPI, labelledGraphAPI, labelledAdjacencyMapAPI
20    ) where
21
22import Data.Coerce
23import Data.List.NonEmpty (NonEmpty)
24import Data.Monoid (Any)
25import Data.IntMap (IntMap)
26import Data.IntSet (IntSet)
27import Data.Map (Map)
28import Data.Set (Set)
29import Data.Tree
30import Test.QuickCheck
31
32import qualified Algebra.Graph                                as G
33import qualified Algebra.Graph.Undirected                     as UG
34import qualified Algebra.Graph.AdjacencyIntMap                as AIM
35import qualified Algebra.Graph.AdjacencyIntMap.Algorithm      as AIM
36import qualified Algebra.Graph.AdjacencyMap                   as AM
37import qualified Algebra.Graph.AdjacencyMap.Algorithm         as AM
38import qualified Algebra.Graph.Labelled                       as LG
39import qualified Algebra.Graph.Labelled.AdjacencyMap          as LAM
40import qualified Algebra.Graph.Relation                       as R
41import qualified Algebra.Graph.Relation.Symmetric             as SR
42import qualified Algebra.Graph.ToGraph                        as T
43
44import Algebra.Graph.Test.Arbitrary ()
45
46-- | A wrapper for monomorphic data types. We cannot use 'AIM.AdjacencyIntMap'
47-- directly when defining an 'API', but we can if we wrap it into 'Mono'.
48newtype Mono g a = Mono { getMono :: g }
49    deriving (Arbitrary, Eq, Num, Ord)
50
51instance Show g => Show (Mono g a) where
52    show = show . getMono
53
54-- | Convert a polymorphic API dictionary into a monomorphic 'Int' version.
55toIntAPI :: API g Ord -> API g ((~) Int)
56toIntAPI API{..} = API{..}
57
58-- TODO: Add missing API entries for Acyclic, NonEmpty and Symmetric graphs.
59-- | The complete graph API dictionary. A graph data type, such as 'G.Graph',
60-- typically implements only a part of the whole API.
61data API g c where
62    API :: ( Arbitrary (g Int), Num (g Int), Ord (g Int), Ord (g (Int, Int))
63           , Ord (g (Int, Char)), Ord (g [Int]), Ord (g [Char])
64           , Ord (g (Int, (Int, Int))), Ord (g ((Int, Int), Int))
65           , Show (g Int)) =>
66        { empty                      :: forall a. c a => g a
67        , vertex                     :: forall a. c a => a -> g a
68        , edge                       :: forall a. c a => a -> a -> g a
69        , overlay                    :: forall a. c a => g a -> g a -> g a
70        , connect                    :: forall a. c a => g a -> g a -> g a
71        , vertices                   :: forall a. c a => [a] -> g a
72        , edges                      :: forall a. c a => [(a, a)] -> g a
73        , overlays                   :: forall a. c a => [g a] -> g a
74        , connects                   :: forall a. c a => [g a] -> g a
75        , toGraph                    :: forall a. c a => g a -> G.Graph a
76        , foldg                      :: forall a. c a => forall r. r -> (a -> r) -> (r -> r -> r) -> (r -> r -> r) -> g a -> r
77        , isSubgraphOf               :: forall a. c a => g a -> g a -> Bool
78        , structEq                   :: forall a. c a => g a -> g a -> Bool
79        , isEmpty                    :: forall a. c a => g a -> Bool
80        , size                       :: forall a. c a => g a -> Int
81        , hasVertex                  :: forall a. c a => a -> g a -> Bool
82        , hasEdge                    :: forall a. c a => a -> a -> g a -> Bool
83        , vertexCount                :: forall a. c a => g a -> Int
84        , edgeCount                  :: forall a. c a => g a -> Int
85        , vertexList                 :: forall a. c a => g a -> [a]
86        , edgeList                   :: forall a. c a => g a -> [(a, a)]
87        , vertexSet                  :: forall a. c a => g a -> Set a
88        , vertexIntSet               :: g Int -> IntSet
89        , edgeSet                    :: forall a. c a => g a -> Set (a, a)
90        , preSet                     :: forall a. c a => a -> g a -> Set a
91        , preIntSet                  :: Int -> g Int -> IntSet
92        , postSet                    :: forall a. c a => a -> g a -> Set a
93        , postIntSet                 :: Int -> g Int -> IntSet
94        , neighbours                 :: forall a. c a => a -> g a -> Set a
95        , adjacencyList              :: forall a. c a => g a -> [(a, [a])]
96        , adjacencyMap               :: forall a. c a => g a -> Map a (Set a)
97        , adjacencyIntMap            :: g Int -> IntMap IntSet
98        , adjacencyMapTranspose      :: forall a. c a => g a -> Map a (Set a)
99        , adjacencyIntMapTranspose   :: g Int -> IntMap IntSet
100        , bfsForest                  :: forall a. c a => [a] -> g a -> Forest a
101        , bfs                        :: forall a. c a => [a] -> g a -> [[a]]
102        , dfsForest                  :: forall a. c a => g a -> Forest a
103        , dfsForestFrom              :: forall a. c a => [a] -> g a -> Forest a
104        , dfs                        :: forall a. c a => [a] -> g a -> [a]
105        , reachable                  :: forall a. c a => a -> g a -> [a]
106        , topSort                    :: forall a. c a => g a -> Either (NonEmpty a) [a]
107        , isAcyclic                  :: forall a. c a => g a -> Bool
108        , toAdjacencyMap             :: forall a. c a => g a -> AM.AdjacencyMap a
109        , toAdjacencyIntMap          :: g Int -> AIM.AdjacencyIntMap
110        , toAdjacencyMapTranspose    :: forall a. c a => g a -> AM.AdjacencyMap a
111        , toAdjacencyIntMapTranspose :: g Int -> AIM.AdjacencyIntMap
112        , isDfsForestOf              :: forall a. c a => Forest a -> g a -> Bool
113        , isTopSortOf                :: forall a. c a => [a] -> g a -> Bool
114        , path                       :: forall a. c a => [a] -> g a
115        , circuit                    :: forall a. c a => [a] -> g a
116        , clique                     :: forall a. c a => [a] -> g a
117        , biclique                   :: forall a. c a => [a] -> [a] -> g a
118        , star                       :: forall a. c a => a -> [a] -> g a
119        , stars                      :: forall a. c a => [(a, [a])] -> g a
120        , tree                       :: forall a. c a => Tree a -> g a
121        , forest                     :: forall a. c a => Forest a -> g a
122        , mesh                       :: forall a b. (c a, c b) => [a] -> [b] -> g (a, b)
123        , torus                      :: forall a b. (c a, c b) => [a] -> [b] -> g (a, b)
124        , deBruijn                   :: forall a. c a => Int -> [a] -> g [a]
125        , removeVertex               :: forall a. c a => a -> g a -> g a
126        , removeEdge                 :: forall a. c a => a -> a -> g a -> g a
127        , replaceVertex              :: forall a. c a => a -> a -> g a -> g a
128        , mergeVertices              :: forall a. c a => (a -> Bool) -> a -> g a -> g a
129        , splitVertex                :: forall a. c a => a -> [a] -> g a -> g a
130        , transpose                  :: forall a. c a => g a -> g a
131        , gmap                       :: forall a b. (c a, c b) => (a -> b) -> g a -> g b
132        , bind                       :: forall a b. (c a, c b) => g a -> (a -> g b) -> g b
133        , induce                     :: forall a. c a => (a -> Bool) -> g a -> g a
134        , induceJust                 :: forall a. c a => g (Maybe a) -> g a
135        , simplify                   :: forall a. c a => g a -> g a
136        , compose                    :: forall a. c a => g a -> g a -> g a
137        , box                        :: forall a b. (c a, c b) => g a -> g b -> g (a, b)
138        , closure                    :: forall a. c a => g a -> g a
139        , reflexiveClosure           :: forall a. c a => g a -> g a
140        , symmetricClosure           :: forall a. c a => g a -> g a
141        , transitiveClosure          :: forall a. c a => g a -> g a
142        , consistent                 :: forall a. c a => g a -> Bool
143        , fromAdjacencySets          :: forall a. c a => [(a, Set a)] -> g a
144        , fromAdjacencyIntSets       :: [(Int, IntSet)] -> g Int } -> API g c
145
146-- | The API of 'AM.AdjacencyMap'.
147adjacencyMapAPI :: API AM.AdjacencyMap Ord
148adjacencyMapAPI = API
149    { empty                      = AM.empty
150    , vertex                     = AM.vertex
151    , edge                       = AM.edge
152    , overlay                    = AM.overlay
153    , connect                    = AM.connect
154    , vertices                   = AM.vertices
155    , edges                      = AM.edges
156    , overlays                   = AM.overlays
157    , connects                   = AM.connects
158    , toGraph                    = T.toGraph
159    , foldg                      = T.foldg
160    , isSubgraphOf               = AM.isSubgraphOf
161    , isEmpty                    = AM.isEmpty
162    , size                       = G.size . T.toGraph
163    , hasVertex                  = AM.hasVertex
164    , hasEdge                    = AM.hasEdge
165    , vertexCount                = AM.vertexCount
166    , edgeCount                  = AM.edgeCount
167    , vertexList                 = AM.vertexList
168    , edgeList                   = AM.edgeList
169    , vertexSet                  = AM.vertexSet
170    , vertexIntSet               = T.vertexIntSet
171    , edgeSet                    = AM.edgeSet
172    , preSet                     = AM.preSet
173    , preIntSet                  = T.preIntSet
174    , postSet                    = AM.postSet
175    , postIntSet                 = T.postIntSet
176    , adjacencyList              = AM.adjacencyList
177    , adjacencyMap               = AM.adjacencyMap
178    , adjacencyIntMap            = T.adjacencyIntMap
179    , adjacencyMapTranspose      = T.adjacencyMapTranspose
180    , adjacencyIntMapTranspose   = T.adjacencyIntMapTranspose
181    , bfsForest                  = AM.bfsForest
182    , bfs                        = AM.bfs
183    , dfsForest                  = AM.dfsForest
184    , dfsForestFrom              = AM.dfsForestFrom
185    , dfs                        = AM.dfs
186    , reachable                  = AM.reachable
187    , topSort                    = AM.topSort
188    , isAcyclic                  = AM.isAcyclic
189    , toAdjacencyMap             = T.toAdjacencyMap
190    , toAdjacencyIntMap          = T.toAdjacencyIntMap
191    , toAdjacencyMapTranspose    = T.toAdjacencyMapTranspose
192    , toAdjacencyIntMapTranspose = T.toAdjacencyIntMapTranspose
193    , isDfsForestOf              = AM.isDfsForestOf
194    , isTopSortOf                = AM.isTopSortOf
195    , path                       = AM.path
196    , circuit                    = AM.circuit
197    , clique                     = AM.clique
198    , biclique                   = AM.biclique
199    , star                       = AM.star
200    , stars                      = AM.stars
201    , tree                       = AM.tree
202    , forest                     = AM.forest
203    , removeVertex               = AM.removeVertex
204    , removeEdge                 = AM.removeEdge
205    , replaceVertex              = AM.replaceVertex
206    , mergeVertices              = AM.mergeVertices
207    , transpose                  = AM.transpose
208    , gmap                       = AM.gmap
209    , induce                     = AM.induce
210    , induceJust                 = AM.induceJust
211    , compose                    = AM.compose
212    , box                        = AM.box
213    , closure                    = AM.closure
214    , reflexiveClosure           = AM.reflexiveClosure
215    , symmetricClosure           = AM.symmetricClosure
216    , transitiveClosure          = AM.transitiveClosure
217    , consistent                 = AM.consistent
218    , fromAdjacencySets          = AM.fromAdjacencySets }
219
220-- | The API of 'G.Graph'.
221graphAPI :: API G.Graph Ord
222graphAPI = API
223    { empty                      = G.empty
224    , vertex                     = G.vertex
225    , edge                       = G.edge
226    , overlay                    = G.overlay
227    , connect                    = G.connect
228    , vertices                   = G.vertices
229    , edges                      = G.edges
230    , overlays                   = G.overlays
231    , connects                   = G.connects
232    , toGraph                    = id
233    , foldg                      = G.foldg
234    , isSubgraphOf               = G.isSubgraphOf
235    , structEq                   = (G.===)
236    , isEmpty                    = G.isEmpty
237    , size                       = G.size
238    , hasVertex                  = G.hasVertex
239    , hasEdge                    = G.hasEdge
240    , vertexCount                = G.vertexCount
241    , edgeCount                  = G.edgeCount
242    , vertexList                 = G.vertexList
243    , edgeList                   = G.edgeList
244    , vertexSet                  = G.vertexSet
245    , vertexIntSet               = T.vertexIntSet
246    , edgeSet                    = G.edgeSet
247    , preSet                     = T.preSet
248    , preIntSet                  = T.preIntSet
249    , postSet                    = T.postSet
250    , postIntSet                 = T.postIntSet
251    , adjacencyList              = G.adjacencyList
252    , adjacencyMap               = T.adjacencyMap
253    , adjacencyIntMap            = T.adjacencyIntMap
254    , adjacencyMapTranspose      = T.adjacencyMapTranspose
255    , adjacencyIntMapTranspose   = T.adjacencyIntMapTranspose
256    , dfsForest                  = T.dfsForest
257    , dfsForestFrom              = T.dfsForestFrom
258    , dfs                        = T.dfs
259    , reachable                  = T.reachable
260    , topSort                    = T.topSort
261    , isAcyclic                  = T.isAcyclic
262    , toAdjacencyMap             = T.toAdjacencyMap
263    , toAdjacencyIntMap          = T.toAdjacencyIntMap
264    , toAdjacencyMapTranspose    = T.toAdjacencyMapTranspose
265    , toAdjacencyIntMapTranspose = T.toAdjacencyIntMapTranspose
266    , isDfsForestOf              = T.isDfsForestOf
267    , isTopSortOf                = T.isTopSortOf
268    , path                       = G.path
269    , circuit                    = G.circuit
270    , clique                     = G.clique
271    , biclique                   = G.biclique
272    , star                       = G.star
273    , stars                      = G.stars
274    , tree                       = G.tree
275    , forest                     = G.forest
276    , mesh                       = G.mesh
277    , torus                      = G.torus
278    , deBruijn                   = G.deBruijn
279    , removeVertex               = G.removeVertex
280    , removeEdge                 = G.removeEdge
281    , replaceVertex              = G.replaceVertex
282    , mergeVertices              = G.mergeVertices
283    , splitVertex                = G.splitVertex
284    , transpose                  = G.transpose
285    , gmap                       = fmap
286    , bind                       = (>>=)
287    , induce                     = G.induce
288    , induceJust                 = G.induceJust
289    , simplify                   = G.simplify
290    , compose                    = G.compose
291    , box                        = G.box }
292
293-- | The API of 'UG.Graph'.
294undirectedGraphAPI :: API UG.Graph Ord
295undirectedGraphAPI = API
296    { empty                      = UG.empty
297    , vertex                     = UG.vertex
298    , edge                       = UG.edge
299    , overlay                    = UG.overlay
300    , connect                    = UG.connect
301    , vertices                   = UG.vertices
302    , edges                      = UG.edges
303    , overlays                   = UG.overlays
304    , connects                   = UG.connects
305    , toGraph                    = UG.fromUndirected
306    , foldg                      = UG.foldg
307    , isSubgraphOf               = UG.isSubgraphOf
308    , isEmpty                    = UG.isEmpty
309    , size                       = UG.size
310    , hasVertex                  = UG.hasVertex
311    , hasEdge                    = UG.hasEdge
312    , vertexCount                = UG.vertexCount
313    , edgeCount                  = UG.edgeCount
314    , vertexList                 = UG.vertexList
315    , edgeList                   = UG.edgeList
316    , vertexSet                  = UG.vertexSet
317    , edgeSet                    = UG.edgeSet
318    , neighbours                 = UG.neighbours
319    , adjacencyList              = UG.adjacencyList
320    , path                       = UG.path
321    , circuit                    = UG.circuit
322    , clique                     = UG.clique
323    , biclique                   = UG.biclique
324    , star                       = UG.star
325    , stars                      = UG.stars
326    , tree                       = UG.tree
327    , forest                     = UG.forest
328    , removeVertex               = UG.removeVertex
329    , removeEdge                 = UG.removeEdge
330    , replaceVertex              = UG.replaceVertex
331    , mergeVertices              = UG.mergeVertices
332    , transpose                  = id
333    , gmap                       = fmap
334    , induce                     = UG.induce
335    , induceJust                 = UG.induceJust }
336
337-- | The API of 'AIM.AdjacencyIntMap'.
338adjacencyIntMapAPI :: API (Mono AIM.AdjacencyIntMap) ((~) Int)
339adjacencyIntMapAPI = API
340    { empty                      = coerce AIM.empty
341    , vertex                     = coerce AIM.vertex
342    , edge                       = coerce AIM.edge
343    , overlay                    = coerce AIM.overlay
344    , connect                    = coerce AIM.connect
345    , vertices                   = coerce AIM.vertices
346    , edges                      = coerce AIM.edges
347    , overlays                   = coerce AIM.overlays
348    , connects                   = coerce AIM.connects
349    , toGraph                    = T.toGraph . getMono
350    , foldg                      = \e v o c -> T.foldg e v o c . getMono
351    , isSubgraphOf               = coerce AIM.isSubgraphOf
352    , isEmpty                    = coerce AIM.isEmpty
353    , size                       = G.size . T.toGraph . getMono
354    , hasVertex                  = coerce AIM.hasVertex
355    , hasEdge                    = coerce AIM.hasEdge
356    , vertexCount                = coerce AIM.vertexCount
357    , edgeCount                  = coerce AIM.edgeCount
358    , vertexList                 = coerce AIM.vertexList
359    , edgeList                   = coerce AIM.edgeList
360    , vertexSet                  = T.vertexSet . getMono
361    , vertexIntSet               = coerce AIM.vertexIntSet
362    , edgeSet                    = coerce AIM.edgeSet
363    , preSet                     = \x -> T.preSet x . getMono
364    , preIntSet                  = coerce AIM.preIntSet
365    , postSet                    = \x -> T.postSet x . getMono
366    , postIntSet                 = coerce AIM.postIntSet
367    , adjacencyList              = coerce AIM.adjacencyList
368    , adjacencyMap               = T.adjacencyMap . getMono
369    , adjacencyIntMap            = coerce AIM.adjacencyIntMap
370    , adjacencyMapTranspose      = T.adjacencyMapTranspose . getMono
371    , adjacencyIntMapTranspose   = T.adjacencyIntMapTranspose . getMono
372    , bfsForest                  = coerce AIM.bfsForest
373    , bfs                        = coerce AIM.bfs
374    , dfsForest                  = coerce AIM.dfsForest
375    , dfsForestFrom              = coerce AIM.dfsForestFrom
376    , dfs                        = coerce AIM.dfs
377    , reachable                  = coerce AIM.reachable
378    , topSort                    = coerce AIM.topSort
379    , isAcyclic                  = coerce AIM.isAcyclic
380    , toAdjacencyMap             = T.toAdjacencyMap . getMono
381    , toAdjacencyIntMap          = T.toAdjacencyIntMap . getMono
382    , toAdjacencyMapTranspose    = T.toAdjacencyMapTranspose . getMono
383    , toAdjacencyIntMapTranspose = T.toAdjacencyIntMapTranspose . getMono
384    , isDfsForestOf              = coerce AIM.isDfsForestOf
385    , isTopSortOf                = coerce AIM.isTopSortOf
386    , path                       = coerce AIM.path
387    , circuit                    = coerce AIM.circuit
388    , clique                     = coerce AIM.clique
389    , biclique                   = coerce AIM.biclique
390    , star                       = coerce AIM.star
391    , stars                      = coerce AIM.stars
392    , tree                       = coerce AIM.tree
393    , forest                     = coerce AIM.forest
394    , removeVertex               = coerce AIM.removeVertex
395    , removeEdge                 = coerce AIM.removeEdge
396    , replaceVertex              = coerce AIM.replaceVertex
397    , mergeVertices              = coerce AIM.mergeVertices
398    , transpose                  = coerce AIM.transpose
399    , gmap                       = coerce AIM.gmap
400    , induce                     = coerce AIM.induce
401    , compose                    = coerce AIM.compose
402    , closure                    = coerce AIM.closure
403    , reflexiveClosure           = coerce AIM.reflexiveClosure
404    , symmetricClosure           = coerce AIM.symmetricClosure
405    , transitiveClosure          = coerce AIM.transitiveClosure
406    , consistent                 = coerce AIM.consistent
407    , fromAdjacencyIntSets       = coerce AIM.fromAdjacencyIntSets }
408
409-- | The API of 'R.Relation'.
410relationAPI :: API R.Relation Ord
411relationAPI = API
412    { empty                      = R.empty
413    , vertex                     = R.vertex
414    , edge                       = R.edge
415    , overlay                    = R.overlay
416    , connect                    = R.connect
417    , vertices                   = R.vertices
418    , edges                      = R.edges
419    , overlays                   = R.overlays
420    , connects                   = R.connects
421    , toGraph                    = T.toGraph
422    , foldg                      = T.foldg
423    , isSubgraphOf               = R.isSubgraphOf
424    , isEmpty                    = R.isEmpty
425    , size                       = G.size . T.toGraph
426    , hasVertex                  = R.hasVertex
427    , hasEdge                    = R.hasEdge
428    , vertexCount                = R.vertexCount
429    , edgeCount                  = R.edgeCount
430    , vertexList                 = R.vertexList
431    , edgeList                   = R.edgeList
432    , vertexSet                  = R.vertexSet
433    , vertexIntSet               = T.vertexIntSet
434    , edgeSet                    = R.edgeSet
435    , preSet                     = R.preSet
436    , preIntSet                  = T.preIntSet
437    , postSet                    = R.postSet
438    , postIntSet                 = T.postIntSet
439    , adjacencyList              = R.adjacencyList
440    , adjacencyMap               = T.adjacencyMap
441    , adjacencyIntMap            = T.adjacencyIntMap
442    , adjacencyMapTranspose      = T.adjacencyMapTranspose
443    , adjacencyIntMapTranspose   = T.adjacencyIntMapTranspose
444    , dfsForest                  = T.dfsForest
445    , dfsForestFrom              = T.dfsForestFrom
446    , dfs                        = T.dfs
447    , reachable                  = T.reachable
448    , topSort                    = T.topSort
449    , isAcyclic                  = T.isAcyclic
450    , toAdjacencyMap             = T.toAdjacencyMap
451    , toAdjacencyIntMap          = T.toAdjacencyIntMap
452    , toAdjacencyMapTranspose    = T.toAdjacencyMapTranspose
453    , toAdjacencyIntMapTranspose = T.toAdjacencyIntMapTranspose
454    , isDfsForestOf              = T.isDfsForestOf
455    , isTopSortOf                = T.isTopSortOf
456    , path                       = R.path
457    , circuit                    = R.circuit
458    , clique                     = R.clique
459    , biclique                   = R.biclique
460    , star                       = R.star
461    , stars                      = R.stars
462    , tree                       = R.tree
463    , forest                     = R.forest
464    , removeVertex               = R.removeVertex
465    , removeEdge                 = R.removeEdge
466    , replaceVertex              = R.replaceVertex
467    , mergeVertices              = R.mergeVertices
468    , transpose                  = R.transpose
469    , gmap                       = R.gmap
470    , induce                     = R.induce
471    , induceJust                 = R.induceJust
472    , compose                    = R.compose
473    , closure                    = R.closure
474    , reflexiveClosure           = R.reflexiveClosure
475    , symmetricClosure           = R.symmetricClosure
476    , transitiveClosure          = R.transitiveClosure
477    , consistent                 = R.consistent }
478
479-- | The API of 'SR.Relation'.
480symmetricRelationAPI :: API SR.Relation Ord
481symmetricRelationAPI = API
482    { empty                      = SR.empty
483    , vertex                     = SR.vertex
484    , edge                       = SR.edge
485    , overlay                    = SR.overlay
486    , connect                    = SR.connect
487    , vertices                   = SR.vertices
488    , edges                      = SR.edges
489    , overlays                   = SR.overlays
490    , connects                   = SR.connects
491    , toGraph                    = T.toGraph
492    , foldg                      = T.foldg
493    , isSubgraphOf               = SR.isSubgraphOf
494    , isEmpty                    = SR.isEmpty
495    , size                       = G.size . T.toGraph
496    , hasVertex                  = SR.hasVertex
497    , hasEdge                    = SR.hasEdge
498    , vertexCount                = SR.vertexCount
499    , edgeCount                  = SR.edgeCount
500    , vertexList                 = SR.vertexList
501    , edgeList                   = SR.edgeList
502    , vertexSet                  = SR.vertexSet
503    , vertexIntSet               = T.vertexIntSet
504    , edgeSet                    = SR.edgeSet
505    , preSet                     = T.preSet
506    , preIntSet                  = T.preIntSet
507    , postSet                    = T.postSet
508    , postIntSet                 = T.postIntSet
509    , neighbours                 = SR.neighbours
510    , adjacencyList              = SR.adjacencyList
511    , adjacencyMap               = T.adjacencyMap
512    , adjacencyIntMap            = T.adjacencyIntMap
513    , adjacencyMapTranspose      = T.adjacencyMapTranspose
514    , adjacencyIntMapTranspose   = T.adjacencyIntMapTranspose
515    , dfsForest                  = T.dfsForest
516    , dfsForestFrom              = T.dfsForestFrom
517    , dfs                        = T.dfs
518    , reachable                  = T.reachable
519    , topSort                    = T.topSort
520    , isAcyclic                  = T.isAcyclic
521    , toAdjacencyMap             = T.toAdjacencyMap
522    , toAdjacencyIntMap          = T.toAdjacencyIntMap
523    , toAdjacencyMapTranspose    = T.toAdjacencyMapTranspose
524    , toAdjacencyIntMapTranspose = T.toAdjacencyIntMapTranspose
525    , isDfsForestOf              = T.isDfsForestOf
526    , isTopSortOf                = T.isTopSortOf
527    , path                       = SR.path
528    , circuit                    = SR.circuit
529    , clique                     = SR.clique
530    , biclique                   = SR.biclique
531    , star                       = SR.star
532    , stars                      = SR.stars
533    , tree                       = SR.tree
534    , forest                     = SR.forest
535    , removeVertex               = SR.removeVertex
536    , removeEdge                 = SR.removeEdge
537    , replaceVertex              = SR.replaceVertex
538    , mergeVertices              = SR.mergeVertices
539    , transpose                  = id
540    , gmap                       = SR.gmap
541    , induce                     = SR.induce
542    , induceJust                 = SR.induceJust
543    , consistent                 = SR.consistent }
544
545-- | The API of 'LG.Graph'.
546labelledGraphAPI :: API (LG.Graph Any) Ord
547labelledGraphAPI = API
548    { empty                      = LG.empty
549    , vertex                     = LG.vertex
550    , edge                       = LG.edge mempty
551    , overlay                    = LG.overlay
552    , connect                    = LG.connect mempty
553    , vertices                   = LG.vertices
554    , edges                      = LG.edges . map (\(x, y) -> (mempty, x, y))
555    , overlays                   = LG.overlays
556    , toGraph                    = T.toGraph
557    , foldg                      = T.foldg
558    , isSubgraphOf               = LG.isSubgraphOf
559    , isEmpty                    = LG.isEmpty
560    , size                       = LG.size
561    , hasVertex                  = LG.hasVertex
562    , hasEdge                    = LG.hasEdge
563    , vertexCount                = T.vertexCount
564    , edgeCount                  = T.edgeCount
565    , vertexList                 = LG.vertexList
566    , edgeList                   = T.edgeList
567    , vertexSet                  = LG.vertexSet
568    , vertexIntSet               = T.vertexIntSet
569    , edgeSet                    = T.edgeSet
570    , preSet                     = T.preSet
571    , preIntSet                  = T.preIntSet
572    , postSet                    = T.postSet
573    , postIntSet                 = T.postIntSet
574    , adjacencyList              = T.adjacencyList
575    , adjacencyMap               = T.adjacencyMap
576    , adjacencyIntMap            = T.adjacencyIntMap
577    , adjacencyMapTranspose      = T.adjacencyMapTranspose
578    , adjacencyIntMapTranspose   = T.adjacencyIntMapTranspose
579    , dfsForest                  = T.dfsForest
580    , dfsForestFrom              = T.dfsForestFrom
581    , dfs                        = T.dfs
582    , reachable                  = T.reachable
583    , topSort                    = T.topSort
584    , isAcyclic                  = T.isAcyclic
585    , toAdjacencyMap             = T.toAdjacencyMap
586    , toAdjacencyIntMap          = T.toAdjacencyIntMap
587    , toAdjacencyMapTranspose    = T.toAdjacencyMapTranspose
588    , toAdjacencyIntMapTranspose = T.toAdjacencyIntMapTranspose
589    , isDfsForestOf              = T.isDfsForestOf
590    , isTopSortOf                = T.isTopSortOf
591    , removeVertex               = LG.removeVertex
592    , removeEdge                 = LG.removeEdge
593    , replaceVertex              = LG.replaceVertex
594    , transpose                  = LG.transpose
595    , gmap                       = fmap
596    , induce                     = LG.induce
597    , induceJust                 = LG.induceJust
598    , closure                    = LG.closure
599    , reflexiveClosure           = LG.reflexiveClosure
600    , symmetricClosure           = LG.symmetricClosure
601    , transitiveClosure          = LG.transitiveClosure }
602
603-- | The API of 'LAM.AdjacencyMap'.
604labelledAdjacencyMapAPI :: API (LAM.AdjacencyMap Any) Ord
605labelledAdjacencyMapAPI = API
606    { empty                      = LAM.empty
607    , vertex                     = LAM.vertex
608    , edge                       = LAM.edge mempty
609    , overlay                    = LAM.overlay
610    , connect                    = LAM.connect mempty
611    , vertices                   = LAM.vertices
612    , edges                      = LAM.edges . map (\(x, y) -> (mempty, x, y))
613    , overlays                   = LAM.overlays
614    , toGraph                    = T.toGraph
615    , foldg                      = T.foldg
616    , isSubgraphOf               = LAM.isSubgraphOf
617    , isEmpty                    = LAM.isEmpty
618    , size                       = G.size . T.toGraph
619    , hasVertex                  = LAM.hasVertex
620    , hasEdge                    = LAM.hasEdge
621    , vertexCount                = LAM.vertexCount
622    , edgeCount                  = LAM.edgeCount
623    , vertexList                 = LAM.vertexList
624    , edgeList                   = T.edgeList
625    , vertexSet                  = LAM.vertexSet
626    , vertexIntSet               = T.vertexIntSet
627    , edgeSet                    = T.edgeSet
628    , preSet                     = LAM.preSet
629    , preIntSet                  = T.preIntSet
630    , postSet                    = LAM.postSet
631    , postIntSet                 = T.postIntSet
632    , adjacencyList              = T.adjacencyList
633    , adjacencyMap               = T.adjacencyMap
634    , adjacencyIntMap            = T.adjacencyIntMap
635    , adjacencyMapTranspose      = T.adjacencyMapTranspose
636    , adjacencyIntMapTranspose   = T.adjacencyIntMapTranspose
637    , dfsForest                  = T.dfsForest
638    , dfsForestFrom              = T.dfsForestFrom
639    , dfs                        = T.dfs
640    , reachable                  = T.reachable
641    , topSort                    = T.topSort
642    , isAcyclic                  = T.isAcyclic
643    , toAdjacencyMap             = T.toAdjacencyMap
644    , toAdjacencyIntMap          = T.toAdjacencyIntMap
645    , toAdjacencyMapTranspose    = T.toAdjacencyMapTranspose
646    , toAdjacencyIntMapTranspose = T.toAdjacencyIntMapTranspose
647    , isDfsForestOf              = T.isDfsForestOf
648    , isTopSortOf                = T.isTopSortOf
649    , removeVertex               = LAM.removeVertex
650    , removeEdge                 = LAM.removeEdge
651    , replaceVertex              = LAM.replaceVertex
652    , transpose                  = LAM.transpose
653    , gmap                       = LAM.gmap
654    , induce                     = LAM.induce
655    , induceJust                 = LAM.induceJust
656    , closure                    = LAM.closure
657    , reflexiveClosure           = LAM.reflexiveClosure
658    , symmetricClosure           = LAM.symmetricClosure
659    , transitiveClosure          = LAM.transitiveClosure
660    , consistent                 = LAM.consistent }
661