{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-}
module CompositionGraph.SafeCompositionGraph
(
SCGMorphism(..),
SafeCompositionGraph(..),
mkSafeCompositionGraph,
mkEmptySafeCompositionGraph,
finiteCategoryToSafeCompositionGraph,
generatedFiniteCategoryToSafeCompositionGraph,
insertObjectS,
insertMorphismS,
identifyMorphismsS,
unidentifyMorphismS,
replaceObjectS,
replaceMorphismS,
deleteObjectS,
deleteMorphismS,
isGenS,
isCompS,
getLabelS
)
where
import Data.List ((\\), nub, intercalate, delete)
import FiniteCategory.FiniteCategory
import Utils.CartesianProduct (cartesianProduct, (|^|))
import Data.Maybe (isNothing, fromJust)
import IO.PrettyPrint
import Utils.AssociationList
import Utils.Tuple
import Diagram.Diagram
import Config.Config
import Cat.PartialFinCat
import Control.Monad (foldM)
import CompositionGraph.CompositionGraph
data SCGMorphism a b = SCGMorphism {forall a b. SCGMorphism a b -> Path a b
pathS :: Path a b
,forall a b. SCGMorphism a b -> CompositionLaw a b
compositionLawS :: CompositionLaw a b
,forall a b. SCGMorphism a b -> Int
maxNbCycles :: Int} deriving (Int -> SCGMorphism a b -> ShowS
[SCGMorphism a b] -> ShowS
SCGMorphism a b -> String
(Int -> SCGMorphism a b -> ShowS)
-> (SCGMorphism a b -> String)
-> ([SCGMorphism a b] -> ShowS)
-> Show (SCGMorphism a b)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall a b. (Show a, Show b) => Int -> SCGMorphism a b -> ShowS
forall a b. (Show a, Show b) => [SCGMorphism a b] -> ShowS
forall a b. (Show a, Show b) => SCGMorphism a b -> String
showList :: [SCGMorphism a b] -> ShowS
$cshowList :: forall a b. (Show a, Show b) => [SCGMorphism a b] -> ShowS
show :: SCGMorphism a b -> String
$cshow :: forall a b. (Show a, Show b) => SCGMorphism a b -> String
showsPrec :: Int -> SCGMorphism a b -> ShowS
$cshowsPrec :: forall a b. (Show a, Show b) => Int -> SCGMorphism a b -> ShowS
Show, SCGMorphism a b -> SCGMorphism a b -> Bool
(SCGMorphism a b -> SCGMorphism a b -> Bool)
-> (SCGMorphism a b -> SCGMorphism a b -> Bool)
-> Eq (SCGMorphism a b)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall a b.
(Eq a, Eq b) =>
SCGMorphism a b -> SCGMorphism a b -> Bool
/= :: SCGMorphism a b -> SCGMorphism a b -> Bool
$c/= :: forall a b.
(Eq a, Eq b) =>
SCGMorphism a b -> SCGMorphism a b -> Bool
== :: SCGMorphism a b -> SCGMorphism a b -> Bool
$c== :: forall a b.
(Eq a, Eq b) =>
SCGMorphism a b -> SCGMorphism a b -> Bool
Eq)
instance (PrettyPrintable a, PrettyPrintable b, Eq a, Eq b) => PrettyPrintable (SCGMorphism a b) where
pprint :: SCGMorphism a b -> String
pprint SCGMorphism {pathS :: forall a b. SCGMorphism a b -> Path a b
pathS=(a
s,[],a
t),compositionLawS :: forall a b. SCGMorphism a b -> CompositionLaw a b
compositionLawS=CompositionLaw a b
_,maxNbCycles :: forall a b. SCGMorphism a b -> Int
maxNbCycles=Int
_} = if a
s a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
t then String
"Id"String -> ShowS
forall a. [a] -> [a] -> [a]
++(a -> String
forall a. PrettyPrintable a => a -> String
pprint a
s) else ShowS
forall a. HasCallStack => String -> a
error String
"Identity with source different of target."
pprint SCGMorphism {pathS :: forall a b. SCGMorphism a b -> Path a b
pathS=(a
_,RawPath a b
rp,a
_),compositionLawS :: forall a b. SCGMorphism a b -> CompositionLaw a b
compositionLawS=CompositionLaw a b
_,maxNbCycles :: forall a b. SCGMorphism a b -> Int
maxNbCycles=Int
_} = String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
" o " ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ (\(a
_,a
_,b
l) -> b -> String
forall a. PrettyPrintable a => a -> String
pprint b
l) ((a, a, b) -> String) -> RawPath a b -> [String]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> RawPath a b
rp
rawpathToListOfVertices :: RawPath a b -> [a]
rawpathToListOfVertices :: forall a b. RawPath a b -> [a]
rawpathToListOfVertices [] = []
rawpathToListOfVertices [Arrow a b]
rp = ((Arrow a b -> a
forall a b c. (a, b, c) -> b
snd3 ([Arrow a b] -> Arrow a b
forall a. [a] -> a
head [Arrow a b]
rp))a -> [a] -> [a]
forall a. a -> [a] -> [a]
:(Arrow a b -> a
forall a b c. (a, b, c) -> a
fst3 (Arrow a b -> a) -> [Arrow a b] -> [a]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Arrow a b]
rp))
simplifyOnce :: (Eq a, Eq b) => CompositionLaw a b -> Int -> RawPath a b -> RawPath a b
simplifyOnce :: forall a b.
(Eq a, Eq b) =>
CompositionLaw a b -> Int -> RawPath a b -> RawPath a b
simplifyOnce CompositionLaw a b
_ Int
_ [] = []
simplifyOnce CompositionLaw a b
_ Int
_ [(a, a, b)
e] = [(a, a, b)
e]
simplifyOnce CompositionLaw a b
cl Int
nb RawPath a b
list
| RawPath a b
new_list RawPath a b -> RawPath a b -> Bool
forall a. Eq a => a -> a -> Bool
== [] = []
| Bool
isCycle Bool -> Bool -> Bool
&& Bool
tooManyCycles = []
| RawPath a b
new_list RawPath a b -> RawPath a b -> Bool
forall a. Eq a => a -> a -> Bool
/= RawPath a b
list = RawPath a b
new_list
| RawPath a b
simple_tail RawPath a b -> RawPath a b -> Bool
forall a. Eq a => a -> a -> Bool
/= (RawPath a b -> RawPath a b
forall a. [a] -> [a]
tail RawPath a b
list) = (RawPath a b -> (a, a, b)
forall a. [a] -> a
head RawPath a b
list)(a, a, b) -> RawPath a b -> RawPath a b
forall a. a -> [a] -> [a]
:RawPath a b
simple_tail
| RawPath a b
simple_init RawPath a b -> RawPath a b -> Bool
forall a. Eq a => a -> a -> Bool
/= (RawPath a b -> RawPath a b
forall a. [a] -> [a]
init RawPath a b
list) = RawPath a b
simple_initRawPath a b -> RawPath a b -> RawPath a b
forall a. [a] -> [a] -> [a]
++[(RawPath a b -> (a, a, b)
forall a. [a] -> a
last RawPath a b
list)]
| Bool
otherwise = RawPath a b
list
where
listOfVertices :: [a]
listOfVertices = RawPath a b -> [a]
forall a b. RawPath a b -> [a]
rawpathToListOfVertices RawPath a b
list
isCycle :: Bool
isCycle = ([a] -> a
forall a. [a] -> a
head [a]
listOfVertices) a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== ([a] -> a
forall a. [a] -> a
last [a]
listOfVertices)
tooManyCycles :: Bool
tooManyCycles = ([a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length ([a] -> Int) -> [a] -> Int
forall a b. (a -> b) -> a -> b
$ (a -> Bool) -> [a] -> [a]
forall a. (a -> Bool) -> [a] -> [a]
filter (([a] -> a
forall a. [a] -> a
head [a]
listOfVertices) a -> a -> Bool
forall a. Eq a => a -> a -> Bool
==) [a]
listOfVertices) Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== (Int
nbInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
2)
new_list :: RawPath a b
new_list = RawPath a b -> RawPath a b -> CompositionLaw a b -> RawPath a b
forall a b. Eq a => b -> a -> AssociationList a b -> b
(!-?) RawPath a b
list RawPath a b
list CompositionLaw a b
cl
simple_tail :: RawPath a b
simple_tail = CompositionLaw a b -> Int -> RawPath a b -> RawPath a b
forall a b.
(Eq a, Eq b) =>
CompositionLaw a b -> Int -> RawPath a b -> RawPath a b
simplifyOnce CompositionLaw a b
cl Int
nb (RawPath a b -> RawPath a b
forall a. [a] -> [a]
tail RawPath a b
list)
simple_init :: RawPath a b
simple_init = CompositionLaw a b -> Int -> RawPath a b -> RawPath a b
forall a b.
(Eq a, Eq b) =>
CompositionLaw a b -> Int -> RawPath a b -> RawPath a b
simplifyOnce CompositionLaw a b
cl Int
nb (RawPath a b -> RawPath a b
forall a. [a] -> [a]
init RawPath a b
list)
simplify :: (Eq a, Eq b) => CompositionLaw a b -> Int -> RawPath a b -> RawPath a b
simplify :: forall a b.
(Eq a, Eq b) =>
CompositionLaw a b -> Int -> RawPath a b -> RawPath a b
simplify CompositionLaw a b
_ Int
_ [] = []
simplify CompositionLaw a b
cl Int
nb RawPath a b
rp
| RawPath a b
simple_one RawPath a b -> RawPath a b -> Bool
forall a. Eq a => a -> a -> Bool
== RawPath a b
rp = RawPath a b
rp
| Bool
otherwise = CompositionLaw a b -> Int -> RawPath a b -> RawPath a b
forall a b.
(Eq a, Eq b) =>
CompositionLaw a b -> Int -> RawPath a b -> RawPath a b
simplify CompositionLaw a b
cl Int
nb RawPath a b
simple_one
where simple_one :: RawPath a b
simple_one = CompositionLaw a b -> Int -> RawPath a b -> RawPath a b
forall a b.
(Eq a, Eq b) =>
CompositionLaw a b -> Int -> RawPath a b -> RawPath a b
simplifyOnce CompositionLaw a b
cl Int
nb RawPath a b
rp
instance (Eq a, Eq b) => Morphism (SCGMorphism a b) a where
@ :: SCGMorphism a b -> SCGMorphism a b -> SCGMorphism a b
(@) SCGMorphism{pathS :: forall a b. SCGMorphism a b -> Path a b
pathS=(a
s2,RawPath a b
rp2,a
t2), compositionLawS :: forall a b. SCGMorphism a b -> CompositionLaw a b
compositionLawS=CompositionLaw a b
cl2, maxNbCycles :: forall a b. SCGMorphism a b -> Int
maxNbCycles=Int
nb1} SCGMorphism{pathS :: forall a b. SCGMorphism a b -> Path a b
pathS=(a
s1,RawPath a b
rp1,a
t1), compositionLawS :: forall a b. SCGMorphism a b -> CompositionLaw a b
compositionLawS=CompositionLaw a b
cl1, maxNbCycles :: forall a b. SCGMorphism a b -> Int
maxNbCycles=Int
nb2}
| a
t1 a -> a -> Bool
forall a. Eq a => a -> a -> Bool
/= a
s2 = String -> SCGMorphism a b
forall a. HasCallStack => String -> a
error String
"Composition of morphisms g@f where target of f is different of source of g"
| CompositionLaw a b
cl1 CompositionLaw a b -> CompositionLaw a b -> Bool
forall a. Eq a => a -> a -> Bool
/= CompositionLaw a b
cl2 = String -> SCGMorphism a b
forall a. HasCallStack => String -> a
error String
"Composition of morphisms with different composition laws"
| Int
nb1 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= Int
nb2 = String -> SCGMorphism a b
forall a. HasCallStack => String -> a
error String
"Composition of morphisms with different maximum number of cycles."
| Bool
otherwise = SCGMorphism :: forall a b.
Path a b -> CompositionLaw a b -> Int -> SCGMorphism a b
SCGMorphism{pathS :: (a, RawPath a b, a)
pathS=(a
s1,(CompositionLaw a b -> Int -> RawPath a b -> RawPath a b
forall a b.
(Eq a, Eq b) =>
CompositionLaw a b -> Int -> RawPath a b -> RawPath a b
simplify CompositionLaw a b
cl1 Int
nb1 (RawPath a b
rp2RawPath a b -> RawPath a b -> RawPath a b
forall a. [a] -> [a] -> [a]
++RawPath a b
rp1)),a
t2), compositionLawS :: CompositionLaw a b
compositionLawS=CompositionLaw a b
cl1, maxNbCycles :: Int
maxNbCycles=Int
nb1}
source :: SCGMorphism a b -> a
source SCGMorphism{pathS :: forall a b. SCGMorphism a b -> Path a b
pathS=(a
s,RawPath a b
_,a
_), compositionLawS :: forall a b. SCGMorphism a b -> CompositionLaw a b
compositionLawS=CompositionLaw a b
_, maxNbCycles :: forall a b. SCGMorphism a b -> Int
maxNbCycles=Int
_} = a
s
target :: SCGMorphism a b -> a
target SCGMorphism{pathS :: forall a b. SCGMorphism a b -> Path a b
pathS=(a
_,RawPath a b
_,a
t), compositionLawS :: forall a b. SCGMorphism a b -> CompositionLaw a b
compositionLawS=CompositionLaw a b
_, maxNbCycles :: forall a b. SCGMorphism a b -> Int
maxNbCycles=Int
_} = a
t
mkSCGMorphism :: CompositionLaw a b -> Int -> Arrow a b -> SCGMorphism a b
mkSCGMorphism :: forall a b.
CompositionLaw a b -> Int -> Arrow a b -> SCGMorphism a b
mkSCGMorphism CompositionLaw a b
cl Int
nb e :: Arrow a b
e@(a
s,a
t,b
l) = SCGMorphism :: forall a b.
Path a b -> CompositionLaw a b -> Int -> SCGMorphism a b
SCGMorphism {pathS :: Path a b
pathS=(a
s,[Arrow a b
e],a
t),compositionLawS :: CompositionLaw a b
compositionLawS=CompositionLaw a b
cl, maxNbCycles :: Int
maxNbCycles=Int
nb}
findOutwardEdges :: (Eq a) => Graph a b -> a -> [Arrow a b]
findOutwardEdges :: forall a b. Eq a => Graph a b -> a -> [Arrow a b]
findOutwardEdges ([a]
nodes,[Arrow a b]
edges) a
o = (Arrow a b -> Bool) -> [Arrow a b] -> [Arrow a b]
forall a. (a -> Bool) -> [a] -> [a]
filter (\e :: Arrow a b
e@(a
s,a
t,b
_) -> a
s a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
o Bool -> Bool -> Bool
&& a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
elem a
t [a]
nodes) [Arrow a b]
edges
findInwardEdges :: (Eq a) => Graph a b -> a -> [Arrow a b]
findInwardEdges :: forall a b. Eq a => Graph a b -> a -> [Arrow a b]
findInwardEdges ([a]
nodes,[Arrow a b]
edges) a
o = (Arrow a b -> Bool) -> [Arrow a b] -> [Arrow a b]
forall a. (a -> Bool) -> [a] -> [a]
filter (\e :: Arrow a b
e@(a
s,a
t,b
_) -> a
t a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
o Bool -> Bool -> Bool
&& a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
elem a
s [a]
nodes) [Arrow a b]
edges
mkIdentity :: (Eq a) => Graph a b -> CompositionLaw a b -> Int -> a -> SCGMorphism a b
mkIdentity :: forall a b.
Eq a =>
Graph a b -> CompositionLaw a b -> Int -> a -> SCGMorphism a b
mkIdentity g :: Graph a b
g@([a]
n,[Arrow a b]
_) CompositionLaw a b
cl Int
nb a
x
| a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
elem a
x [a]
n = SCGMorphism :: forall a b.
Path a b -> CompositionLaw a b -> Int -> SCGMorphism a b
SCGMorphism {pathS :: Path a b
pathS=(a
x,[],a
x),compositionLawS :: CompositionLaw a b
compositionLawS=CompositionLaw a b
cl, maxNbCycles :: Int
maxNbCycles=Int
nb}
| Bool
otherwise = String -> SCGMorphism a b
forall a. HasCallStack => String -> a
error (String
"Trying to construct identity of an unknown object.")
findAcyclicRawPaths :: (Eq a) => Graph a b -> a -> a -> [RawPath a b]
findAcyclicRawPaths :: forall a b. Eq a => Graph a b -> a -> a -> [RawPath a b]
findAcyclicRawPaths Graph a b
g a
s a
t = Graph a b -> a -> a -> [a] -> [[Arrow a b]]
forall {b} {c}.
Eq b =>
([b], [Arrow b c]) -> b -> b -> [b] -> [[Arrow b c]]
findAcyclicRawPathsVisitedNodes Graph a b
g a
s a
t [] where
findAcyclicRawPathsVisitedNodes :: ([b], [Arrow b c]) -> b -> b -> [b] -> [[Arrow b c]]
findAcyclicRawPathsVisitedNodes g :: ([b], [Arrow b c])
g@([b]
n,[Arrow b c]
e) b
s b
t [b]
v
| b -> [b] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
elem b
t [b]
v = []
| b
s b -> b -> Bool
forall a. Eq a => a -> a -> Bool
== b
t = [[]]
| Bool
otherwise = ([[[Arrow b c]]] -> [[Arrow b c]]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ((([[Arrow b c]] -> [[Arrow b c]])
-> [[Arrow b c]] -> [[Arrow b c]])
-> [[[Arrow b c]] -> [[Arrow b c]]]
-> [[[Arrow b c]]]
-> [[[Arrow b c]]]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith ([[Arrow b c]] -> [[Arrow b c]]) -> [[Arrow b c]] -> [[Arrow b c]]
forall a b. (a -> b) -> a -> b
($) ((([Arrow b c] -> [Arrow b c]) -> [[Arrow b c]] -> [[Arrow b c]])
-> [[Arrow b c] -> [Arrow b c]] -> [[[Arrow b c]] -> [[Arrow b c]]]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ([Arrow b c] -> [Arrow b c]) -> [[Arrow b c]] -> [[Arrow b c]]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Arrow b c -> [Arrow b c] -> [Arrow b c])
-> [Arrow b c] -> [[Arrow b c] -> [Arrow b c]]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (:) [Arrow b c]
inwardEdges)) ((Arrow b c -> [[Arrow b c]]) -> [Arrow b c] -> [[[Arrow b c]]]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\x :: Arrow b c
x@(b
s1,b
t1,c
l1) -> (([b], [Arrow b c]) -> b -> b -> [b] -> [[Arrow b c]]
findAcyclicRawPathsVisitedNodes ([b], [Arrow b c])
g b
s b
s1 (b
tb -> [b] -> [b]
forall a. a -> [a] -> [a]
:[b]
v))) [Arrow b c]
inwardEdges))) where
inwardEdges :: [Arrow b c]
inwardEdges = (([b], [Arrow b c]) -> b -> [Arrow b c]
forall a b. Eq a => Graph a b -> a -> [Arrow a b]
findInwardEdges ([b], [Arrow b c])
g b
t)
findElementaryCycles :: (Eq a, Eq b) => Graph a b -> CompositionLaw a b -> Int -> a -> [RawPath a b]
findElementaryCycles :: forall a b.
(Eq a, Eq b) =>
Graph a b -> CompositionLaw a b -> Int -> a -> [RawPath a b]
findElementaryCycles Graph a b
g CompositionLaw a b
cl Int
nb a
o = [RawPath a b] -> [RawPath a b]
forall a. Eq a => [a] -> [a]
nub (CompositionLaw a b -> Int -> RawPath a b -> RawPath a b
forall a b.
(Eq a, Eq b) =>
CompositionLaw a b -> Int -> RawPath a b -> RawPath a b
simplify CompositionLaw a b
cl Int
nb (RawPath a b -> RawPath a b) -> [RawPath a b] -> [RawPath a b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> []RawPath a b -> [RawPath a b] -> [RawPath a b]
forall a. a -> [a] -> [a]
:([[RawPath a b]] -> [RawPath a b]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat (([Arrow a b -> RawPath a b] -> Arrow a b -> [RawPath a b])
-> [[Arrow a b -> RawPath a b]] -> RawPath a b -> [[RawPath a b]]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith [Arrow a b -> RawPath a b] -> Arrow a b -> [RawPath a b]
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence (([RawPath a b] -> [Arrow a b -> RawPath a b])
-> [[RawPath a b]] -> [[Arrow a b -> RawPath a b]]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((RawPath a b -> Arrow a b -> RawPath a b)
-> [RawPath a b] -> [Arrow a b -> RawPath a b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\RawPath a b
x Arrow a b
y -> (Arrow a b
yArrow a b -> RawPath a b -> RawPath a b
forall a. a -> [a] -> [a]
:RawPath a b
x))) ((Arrow a b -> [RawPath a b]) -> RawPath a b -> [[RawPath a b]]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(a
s,a
_,b
_) -> (Graph a b -> a -> a -> [RawPath a b]
forall a b. Eq a => Graph a b -> a -> a -> [RawPath a b]
findAcyclicRawPaths Graph a b
g a
o a
s)) RawPath a b
inEdges)) RawPath a b
inEdges))) where inEdges :: RawPath a b
inEdges = (Graph a b -> a -> RawPath a b
forall a b. Eq a => Graph a b -> a -> [Arrow a b]
findInwardEdges Graph a b
g a
o)
findCycles :: (Eq a, Eq b) => Graph a b -> CompositionLaw a b -> Int -> a -> [RawPath a b]
findCycles :: forall a b.
(Eq a, Eq b) =>
Graph a b -> CompositionLaw a b -> Int -> a -> [RawPath a b]
findCycles Graph a b
g CompositionLaw a b
cl Int
nb a
o = Graph a b
-> CompositionLaw a b -> a -> [RawPath a b] -> [RawPath a b]
forall {t} {b}.
(Eq t, Eq b) =>
Graph t b
-> CompositionLaw t b -> t -> [RawPath t b] -> [RawPath t b]
findCyclesWithPreviousCycles Graph a b
g CompositionLaw a b
cl a
o (Graph a b -> CompositionLaw a b -> Int -> a -> [RawPath a b]
forall a b.
(Eq a, Eq b) =>
Graph a b -> CompositionLaw a b -> Int -> a -> [RawPath a b]
findElementaryCycles Graph a b
g CompositionLaw a b
cl Int
nb a
o) where
findCyclesWithPreviousCycles :: Graph t b
-> CompositionLaw t b -> t -> [RawPath t b] -> [RawPath t b]
findCyclesWithPreviousCycles Graph t b
g CompositionLaw t b
cl t
o [RawPath t b]
p = if [RawPath t b]
newCycles [RawPath t b] -> [RawPath t b] -> [RawPath t b]
forall a. Eq a => [a] -> [a] -> [a]
\\ [RawPath t b]
p [RawPath t b] -> [RawPath t b] -> Bool
forall a. Eq a => a -> a -> Bool
== [] then [RawPath t b]
newCycles else (Graph t b
-> CompositionLaw t b -> t -> [RawPath t b] -> [RawPath t b]
findCyclesWithPreviousCycles Graph t b
g CompositionLaw t b
cl t
o [RawPath t b]
newCycles) where
newCycles :: [RawPath t b]
newCycles = [RawPath t b] -> [RawPath t b]
forall a. Eq a => [a] -> [a]
nub ((CompositionLaw t b -> Int -> RawPath t b -> RawPath t b
forall a b.
(Eq a, Eq b) =>
CompositionLaw a b -> Int -> RawPath a b -> RawPath a b
simplify CompositionLaw t b
cl Int
nb) (RawPath t b -> RawPath t b) -> [RawPath t b] -> [RawPath t b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (RawPath t b -> RawPath t b -> RawPath t b
forall a. [a] -> [a] -> [a]
(++) (RawPath t b -> RawPath t b -> RawPath t b)
-> [RawPath t b] -> [RawPath t b -> RawPath t b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [RawPath t b]
p [RawPath t b -> RawPath t b] -> [RawPath t b] -> [RawPath t b]
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Graph t b -> CompositionLaw t b -> Int -> t -> [RawPath t b]
forall a b.
(Eq a, Eq b) =>
Graph a b -> CompositionLaw a b -> Int -> a -> [RawPath a b]
findElementaryCycles Graph t b
g CompositionLaw t b
cl Int
nb t
o))
intertwine :: [a] -> [a] -> [a]
intertwine :: forall a. [a] -> [a] -> [a]
intertwine [] [a]
l = [a]
l
intertwine [a]
l [] = [a]
l
intertwine l1 :: [a]
l1@(a
x1:[a]
xs1) l2 :: [a]
l2@(a
x2:[a]
xs2) = (a
x1a -> [a] -> [a]
forall a. a -> [a] -> [a]
:(a
x2a -> [a] -> [a]
forall a. a -> [a] -> [a]
:([a] -> [a] -> [a]
forall a. [a] -> [a] -> [a]
intertwine [a]
xs1 [a]
xs2)))
intertwineWithCycles :: (Eq a, Eq b) => Graph a b -> CompositionLaw a b -> Int -> a -> RawPath a b -> [RawPath a b]
intertwineWithCycles :: forall a b.
(Eq a, Eq b) =>
Graph a b
-> CompositionLaw a b -> Int -> a -> RawPath a b -> [RawPath a b]
intertwineWithCycles Graph a b
g CompositionLaw a b
cl Int
nb a
_ p :: RawPath a b
p@(x :: Arrow a b
x@(a
_,a
t,b
_):RawPath a b
xs) = ([RawPath a b] -> RawPath a b
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([RawPath a b] -> RawPath a b) -> [[RawPath a b]] -> [RawPath a b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [[RawPath a b] -> [RawPath a b]]
-> [RawPath a b] -> [[RawPath a b]]
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence (([RawPath a b] -> [RawPath a b] -> [RawPath a b])
-> [[RawPath a b]] -> [[RawPath a b] -> [RawPath a b]]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [RawPath a b] -> [RawPath a b] -> [RawPath a b]
forall a. [a] -> [a] -> [a]
intertwine [[RawPath a b]]
prodCycles) ((Arrow a b -> RawPath a b) -> RawPath a b -> [RawPath a b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Arrow a b -> RawPath a b -> RawPath a b
forall a. a -> [a] -> [a]
:[]) RawPath a b
p)) where
prodCycles :: [[RawPath a b]]
prodCycles = [[RawPath a b]] -> [[RawPath a b]]
forall a. [[a]] -> [[a]]
cartesianProduct [[RawPath a b]]
cycles
cycles :: [[RawPath a b]]
cycles = (Graph a b -> CompositionLaw a b -> Int -> a -> [RawPath a b]
forall a b.
(Eq a, Eq b) =>
Graph a b -> CompositionLaw a b -> Int -> a -> [RawPath a b]
findCycles Graph a b
g CompositionLaw a b
cl Int
nb a
t)[RawPath a b] -> [[RawPath a b]] -> [[RawPath a b]]
forall a. a -> [a] -> [a]
:((\(a
s,a
_,b
_) -> (Graph a b -> CompositionLaw a b -> Int -> a -> [RawPath a b]
forall a b.
(Eq a, Eq b) =>
Graph a b -> CompositionLaw a b -> Int -> a -> [RawPath a b]
findCycles Graph a b
g CompositionLaw a b
cl Int
nb a
s)) (Arrow a b -> [RawPath a b]) -> RawPath a b -> [[RawPath a b]]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> RawPath a b
p)
intertwineWithCycles Graph a b
g CompositionLaw a b
cl Int
nb a
s [] = (Graph a b -> CompositionLaw a b -> Int -> a -> [RawPath a b]
forall a b.
(Eq a, Eq b) =>
Graph a b -> CompositionLaw a b -> Int -> a -> [RawPath a b]
findCycles Graph a b
g CompositionLaw a b
cl Int
nb a
s)
mkAr :: (Eq a, Eq b) => Graph a b -> CompositionLaw a b -> Int -> a -> a -> [SCGMorphism a b]
mkAr :: forall a b.
(Eq a, Eq b) =>
Graph a b
-> CompositionLaw a b -> Int -> a -> a -> [SCGMorphism a b]
mkAr Graph a b
g CompositionLaw a b
cl Int
nb a
s a
t = (\RawPath a b
p -> SCGMorphism :: forall a b.
Path a b -> CompositionLaw a b -> Int -> SCGMorphism a b
SCGMorphism{pathS :: Path a b
pathS=(a
s,RawPath a b
p,a
t),compositionLawS :: CompositionLaw a b
compositionLawS=CompositionLaw a b
cl,maxNbCycles :: Int
maxNbCycles=Int
nb}) (RawPath a b -> SCGMorphism a b)
-> [RawPath a b] -> [SCGMorphism a b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [RawPath a b] -> [RawPath a b]
forall a. Eq a => [a] -> [a]
nub (CompositionLaw a b -> Int -> RawPath a b -> RawPath a b
forall a b.
(Eq a, Eq b) =>
CompositionLaw a b -> Int -> RawPath a b -> RawPath a b
simplify CompositionLaw a b
cl Int
nb (RawPath a b -> RawPath a b) -> [RawPath a b] -> [RawPath a b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [[RawPath a b]] -> [RawPath a b]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat((Graph a b
-> CompositionLaw a b -> Int -> a -> RawPath a b -> [RawPath a b]
forall a b.
(Eq a, Eq b) =>
Graph a b
-> CompositionLaw a b -> Int -> a -> RawPath a b -> [RawPath a b]
intertwineWithCycles Graph a b
g CompositionLaw a b
cl Int
nb a
s) (RawPath a b -> [RawPath a b]) -> [RawPath a b] -> [[RawPath a b]]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [RawPath a b]
acyclicPaths)) where
acyclicPaths :: [RawPath a b]
acyclicPaths = [RawPath a b] -> [RawPath a b]
forall a. Eq a => [a] -> [a]
nub ([RawPath a b] -> [RawPath a b]) -> [RawPath a b] -> [RawPath a b]
forall a b. (a -> b) -> a -> b
$ (CompositionLaw a b -> Int -> RawPath a b -> RawPath a b
forall a b.
(Eq a, Eq b) =>
CompositionLaw a b -> Int -> RawPath a b -> RawPath a b
simplify CompositionLaw a b
cl Int
nb) (RawPath a b -> RawPath a b) -> [RawPath a b] -> [RawPath a b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Graph a b -> a -> a -> [RawPath a b]
forall a b. Eq a => Graph a b -> a -> a -> [RawPath a b]
findAcyclicRawPaths Graph a b
g a
s a
t)
data SafeCompositionGraph a b = SafeCompositionGraph {forall a b. SafeCompositionGraph a b -> Graph a b
graphS :: Graph a b, forall a b. SafeCompositionGraph a b -> CompositionLaw a b
lawS :: CompositionLaw a b, forall a b. SafeCompositionGraph a b -> Int
maxCycles :: Int} deriving (SafeCompositionGraph a b -> SafeCompositionGraph a b -> Bool
(SafeCompositionGraph a b -> SafeCompositionGraph a b -> Bool)
-> (SafeCompositionGraph a b -> SafeCompositionGraph a b -> Bool)
-> Eq (SafeCompositionGraph a b)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall a b.
(Eq a, Eq b) =>
SafeCompositionGraph a b -> SafeCompositionGraph a b -> Bool
/= :: SafeCompositionGraph a b -> SafeCompositionGraph a b -> Bool
$c/= :: forall a b.
(Eq a, Eq b) =>
SafeCompositionGraph a b -> SafeCompositionGraph a b -> Bool
== :: SafeCompositionGraph a b -> SafeCompositionGraph a b -> Bool
$c== :: forall a b.
(Eq a, Eq b) =>
SafeCompositionGraph a b -> SafeCompositionGraph a b -> Bool
Eq, Int -> SafeCompositionGraph a b -> ShowS
[SafeCompositionGraph a b] -> ShowS
SafeCompositionGraph a b -> String
(Int -> SafeCompositionGraph a b -> ShowS)
-> (SafeCompositionGraph a b -> String)
-> ([SafeCompositionGraph a b] -> ShowS)
-> Show (SafeCompositionGraph a b)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall a b.
(Show a, Show b) =>
Int -> SafeCompositionGraph a b -> ShowS
forall a b. (Show a, Show b) => [SafeCompositionGraph a b] -> ShowS
forall a b. (Show a, Show b) => SafeCompositionGraph a b -> String
showList :: [SafeCompositionGraph a b] -> ShowS
$cshowList :: forall a b. (Show a, Show b) => [SafeCompositionGraph a b] -> ShowS
show :: SafeCompositionGraph a b -> String
$cshow :: forall a b. (Show a, Show b) => SafeCompositionGraph a b -> String
showsPrec :: Int -> SafeCompositionGraph a b -> ShowS
$cshowsPrec :: forall a b.
(Show a, Show b) =>
Int -> SafeCompositionGraph a b -> ShowS
Show)
instance (Eq a, Eq b) => FiniteCategory (SafeCompositionGraph a b) (SCGMorphism a b) a where
ob :: SafeCompositionGraph a b -> [a]
ob = ([a], [Arrow a b]) -> [a]
forall a b. (a, b) -> a
fst(([a], [Arrow a b]) -> [a])
-> (SafeCompositionGraph a b -> ([a], [Arrow a b]))
-> SafeCompositionGraph a b
-> [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.SafeCompositionGraph a b -> ([a], [Arrow a b])
forall a b. SafeCompositionGraph a b -> Graph a b
graphS
identity :: Morphism (SCGMorphism a b) a =>
SafeCompositionGraph a b -> a -> SCGMorphism a b
identity SafeCompositionGraph a b
c = ([a], [Arrow a b])
-> CompositionLaw a b -> Int -> a -> SCGMorphism a b
forall a b.
Eq a =>
Graph a b -> CompositionLaw a b -> Int -> a -> SCGMorphism a b
mkIdentity (SafeCompositionGraph a b -> ([a], [Arrow a b])
forall a b. SafeCompositionGraph a b -> Graph a b
graphS SafeCompositionGraph a b
c) (SafeCompositionGraph a b -> CompositionLaw a b
forall a b. SafeCompositionGraph a b -> CompositionLaw a b
lawS SafeCompositionGraph a b
c) (SafeCompositionGraph a b -> Int
forall a b. SafeCompositionGraph a b -> Int
maxCycles SafeCompositionGraph a b
c)
ar :: Morphism (SCGMorphism a b) a =>
SafeCompositionGraph a b -> a -> a -> [SCGMorphism a b]
ar SafeCompositionGraph a b
c = ([a], [Arrow a b])
-> CompositionLaw a b -> Int -> a -> a -> [SCGMorphism a b]
forall a b.
(Eq a, Eq b) =>
Graph a b
-> CompositionLaw a b -> Int -> a -> a -> [SCGMorphism a b]
mkAr (SafeCompositionGraph a b -> ([a], [Arrow a b])
forall a b. SafeCompositionGraph a b -> Graph a b
graphS SafeCompositionGraph a b
c) (SafeCompositionGraph a b -> CompositionLaw a b
forall a b. SafeCompositionGraph a b -> CompositionLaw a b
lawS SafeCompositionGraph a b
c) (SafeCompositionGraph a b -> Int
forall a b. SafeCompositionGraph a b -> Int
maxCycles SafeCompositionGraph a b
c)
instance (Eq a, Eq b) => GeneratedFiniteCategory (SafeCompositionGraph a b) (SCGMorphism a b) a where
genAr :: Morphism (SCGMorphism a b) a =>
SafeCompositionGraph a b -> a -> a -> [SCGMorphism a b]
genAr c :: SafeCompositionGraph a b
c@SafeCompositionGraph{graphS :: forall a b. SafeCompositionGraph a b -> Graph a b
graphS=Graph a b
g,lawS :: forall a b. SafeCompositionGraph a b -> CompositionLaw a b
lawS=CompositionLaw a b
l,maxCycles :: forall a b. SafeCompositionGraph a b -> Int
maxCycles=Int
nb} a
s a
t
| a
s a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
t = [SCGMorphism a b]
gen [SCGMorphism a b] -> [SCGMorphism a b] -> [SCGMorphism a b]
forall a. [a] -> [a] -> [a]
++ [SafeCompositionGraph a b -> a -> SCGMorphism a b
forall c m o. (FiniteCategory c m o, Morphism m o) => c -> o -> m
identity SafeCompositionGraph a b
c a
s]
| Bool
otherwise = [SCGMorphism a b]
gen
where gen :: [SCGMorphism a b]
gen = CompositionLaw a b -> Int -> Arrow a b -> SCGMorphism a b
forall a b.
CompositionLaw a b -> Int -> Arrow a b -> SCGMorphism a b
mkSCGMorphism CompositionLaw a b
l Int
nb (Arrow a b -> SCGMorphism a b) -> [Arrow a b] -> [SCGMorphism a b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ((Arrow a b -> Bool) -> [Arrow a b] -> [Arrow a b]
forall a. (a -> Bool) -> [a] -> [a]
filter (\a :: Arrow a b
a@(a
s1,a
t1,b
_) -> a
s a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
s1 Bool -> Bool -> Bool
&& a
t a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
t1) ([Arrow a b] -> [Arrow a b]) -> [Arrow a b] -> [Arrow a b]
forall a b. (a -> b) -> a -> b
$ Graph a b -> [Arrow a b]
forall a b. (a, b) -> b
snd Graph a b
g)
decompose :: Morphism (SCGMorphism a b) a =>
SafeCompositionGraph a b -> SCGMorphism a b -> [SCGMorphism a b]
decompose SafeCompositionGraph a b
c m :: SCGMorphism a b
m@SCGMorphism{pathS :: forall a b. SCGMorphism a b -> Path a b
pathS=(a
_,[Arrow a b]
rp,a
_),compositionLawS :: forall a b. SCGMorphism a b -> CompositionLaw a b
compositionLawS=CompositionLaw a b
l,maxNbCycles :: forall a b. SCGMorphism a b -> Int
maxNbCycles=Int
nb}
| SafeCompositionGraph a b -> SCGMorphism a b -> Bool
forall c m o.
(FiniteCategory c m o, Morphism m o, Eq m, Eq o) =>
c -> m -> Bool
isIdentity SafeCompositionGraph a b
c SCGMorphism a b
m = [SCGMorphism a b
m]
| Bool
otherwise = CompositionLaw a b -> Int -> Arrow a b -> SCGMorphism a b
forall a b.
CompositionLaw a b -> Int -> Arrow a b -> SCGMorphism a b
mkSCGMorphism CompositionLaw a b
l Int
nb (Arrow a b -> SCGMorphism a b) -> [Arrow a b] -> [SCGMorphism a b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Arrow a b]
rp
instance (PrettyPrintable a, PrettyPrintable b, Eq a, Eq b) => PrettyPrintable (SafeCompositionGraph a b) where
pprint :: SafeCompositionGraph a b -> String
pprint cg :: SafeCompositionGraph a b
cg@SafeCompositionGraph{graphS :: forall a b. SafeCompositionGraph a b -> Graph a b
graphS=([a]
nodes,[Arrow a b]
arrs),lawS :: forall a b. SafeCompositionGraph a b -> CompositionLaw a b
lawS=CompositionLaw a b
_,maxCycles :: forall a b. SafeCompositionGraph a b -> Int
maxCycles=Int
_} = String
"SafeCompositionGraph("String -> ShowS
forall a. [a] -> [a] -> [a]
++String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
"," (a -> String
forall a. PrettyPrintable a => a -> String
pprint (a -> String) -> [a] -> [String]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [a]
nodes)String -> ShowS
forall a. [a] -> [a] -> [a]
++String
"\n"String -> ShowS
forall a. [a] -> [a] -> [a]
++String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
"," ((\(a
a,a
b,b
c) -> b -> String
forall a. PrettyPrintable a => a -> String
pprint b
c String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
":" String -> ShowS
forall a. [a] -> [a] -> [a]
++ a -> String
forall a. PrettyPrintable a => a -> String
pprint a
a String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"->" String -> ShowS
forall a. [a] -> [a] -> [a]
++ a -> String
forall a. PrettyPrintable a => a -> String
pprint a
b) (Arrow a b -> String) -> [Arrow a b] -> [String]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Arrow a b]
arrs)
isGenS :: (Eq a) => SCGMorphism a b -> Bool
isGenS :: forall a b. Eq a => SCGMorphism a b -> Bool
isGenS m :: SCGMorphism a b
m@SCGMorphism{pathS :: forall a b. SCGMorphism a b -> Path a b
pathS=p :: Path a b
p@(a
s,RawPath a b
rp,a
t),compositionLawS :: forall a b. SCGMorphism a b -> CompositionLaw a b
compositionLawS=CompositionLaw a b
_,maxNbCycles :: forall a b. SCGMorphism a b -> Int
maxNbCycles=Int
_} = (RawPath a b -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length RawPath a b
rp ) Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
2
isCompS :: (Eq a) => SCGMorphism a b -> Bool
isCompS :: forall a b. Eq a => SCGMorphism a b -> Bool
isCompS = Bool -> Bool
not(Bool -> Bool)
-> (SCGMorphism a b -> Bool) -> SCGMorphism a b -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
.SCGMorphism a b -> Bool
forall a b. Eq a => SCGMorphism a b -> Bool
isGenS
getLabelS :: (Eq a) => SCGMorphism a b -> Maybe b
getLabelS :: forall a b. Eq a => SCGMorphism a b -> Maybe b
getLabelS SCGMorphism{pathS :: forall a b. SCGMorphism a b -> Path a b
pathS=(a
_,[(a
_,a
_,b
label)],a
_),compositionLawS :: forall a b. SCGMorphism a b -> CompositionLaw a b
compositionLawS=CompositionLaw a b
_,maxNbCycles :: forall a b. SCGMorphism a b -> Int
maxNbCycles=Int
_} = b -> Maybe b
forall a. a -> Maybe a
Just b
label
getLabelS SCGMorphism a b
_ = Maybe b
forall a. Maybe a
Nothing
mkSafeCompositionGraph :: (Eq a, Eq b, Show a) => Graph a b -> CompositionLaw a b -> Int -> Either (FiniteCategoryError (SCGMorphism a b) a) (SafeCompositionGraph a b)
mkSafeCompositionGraph :: forall a b.
(Eq a, Eq b, Show a) =>
Graph a b
-> CompositionLaw a b
-> Int
-> Either
(FiniteCategoryError (SCGMorphism a b) a)
(SafeCompositionGraph a b)
mkSafeCompositionGraph Graph a b
g CompositionLaw a b
l Int
nb
| Maybe (FiniteCategoryError (SCGMorphism a b) a) -> Bool
forall a. Maybe a -> Bool
isNothing Maybe (FiniteCategoryError (SCGMorphism a b) a)
check = SafeCompositionGraph a b
-> Either
(FiniteCategoryError (SCGMorphism a b) a)
(SafeCompositionGraph a b)
forall a b. b -> Either a b
Right SafeCompositionGraph a b
c_g
| Bool
otherwise = FiniteCategoryError (SCGMorphism a b) a
-> Either
(FiniteCategoryError (SCGMorphism a b) a)
(SafeCompositionGraph a b)
forall a b. a -> Either a b
Left (Maybe (FiniteCategoryError (SCGMorphism a b) a)
-> FiniteCategoryError (SCGMorphism a b) a
forall a. HasCallStack => Maybe a -> a
fromJust Maybe (FiniteCategoryError (SCGMorphism a b) a)
check)
where
c_g :: SafeCompositionGraph a b
c_g = SafeCompositionGraph :: forall a b.
Graph a b -> CompositionLaw a b -> Int -> SafeCompositionGraph a b
SafeCompositionGraph {graphS :: Graph a b
graphS=Graph a b
g, lawS :: CompositionLaw a b
lawS=CompositionLaw a b
l, maxCycles :: Int
maxCycles=Int
nb}
check :: Maybe (FiniteCategoryError (SCGMorphism a b) a)
check = SafeCompositionGraph a b
-> Maybe (FiniteCategoryError (SCGMorphism a b) a)
forall c m o.
(GeneratedFiniteCategory c m o, Morphism m o, Eq m, Eq o) =>
c -> Maybe (FiniteCategoryError m o)
checkGeneratedFiniteCategoryProperties SafeCompositionGraph a b
c_g
mkEmptySafeCompositionGraph :: Int -> SafeCompositionGraph a b
mkEmptySafeCompositionGraph :: forall a b. Int -> SafeCompositionGraph a b
mkEmptySafeCompositionGraph Int
maxNbOfCycles = SafeCompositionGraph :: forall a b.
Graph a b -> CompositionLaw a b -> Int -> SafeCompositionGraph a b
SafeCompositionGraph {graphS :: Graph a b
graphS=([],[]), lawS :: CompositionLaw a b
lawS=[], maxCycles :: Int
maxCycles=Int
maxNbOfCycles}
finiteCategoryToSafeCompositionGraph :: (FiniteCategory c m o, Morphism m o, Eq m, Eq o) => c -> (SafeCompositionGraph o m, Diagram c m o (SafeCompositionGraph o m) (SCGMorphism o m) o)
finiteCategoryToSafeCompositionGraph :: forall c m o.
(FiniteCategory c m o, Morphism m o, Eq m, Eq o) =>
c
-> (SafeCompositionGraph o m,
Diagram c m o (SafeCompositionGraph o m) (SCGMorphism o m) o)
finiteCategoryToSafeCompositionGraph c
cat = (SafeCompositionGraph o m
cg,Diagram c m o (SafeCompositionGraph o m) (SCGMorphism o m) o
isofunct)
where
maxnbcycles :: Int
maxnbcycles = [Int] -> Int
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum ([Int] -> Int) -> [Int] -> Int
forall a b. (a -> b) -> a -> b
$ [m] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length ([m] -> Int) -> [[m]] -> [Int]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ((\o
x -> c -> o -> o -> [m]
forall c m o.
(FiniteCategory c m o, Morphism m o) =>
c -> o -> o -> [m]
ar c
cat o
x o
x) (o -> [m]) -> [o] -> [[m]]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> c -> [o]
forall c m o. FiniteCategory c m o => c -> [o]
ob c
cat)
morphToArrow :: c -> (b, b, c)
morphToArrow c
f = ((c -> b
forall m o. Morphism m o => m -> o
source c
f),(c -> b
forall m o. Morphism m o => m -> o
target c
f),c
f)
catLaw :: [([(o, o, m)], [(o, o, m)])]
catLaw = [
if c -> m -> Bool
forall c m o.
(FiniteCategory c m o, Morphism m o, Eq m, Eq o) =>
c -> m -> Bool
isNotIdentity c
cat (m
g m -> m -> m
forall m o. Morphism m o => m -> m -> m
@ m
f) then
([m -> (o, o, m)
forall {c} {b}. Morphism c b => c -> (b, b, c)
morphToArrow m
g,m -> (o, o, m)
forall {c} {b}. Morphism c b => c -> (b, b, c)
morphToArrow m
f],[m -> (o, o, m)
forall {c} {b}. Morphism c b => c -> (b, b, c)
morphToArrow (m
g m -> m -> m
forall m o. Morphism m o => m -> m -> m
@ m
f)])
else
([m -> (o, o, m)
forall {c} {b}. Morphism c b => c -> (b, b, c)
morphToArrow m
g,m -> (o, o, m)
forall {c} {b}. Morphism c b => c -> (b, b, c)
morphToArrow m
f],[]) |
m
f <- (c -> [m]
forall c m o.
(FiniteCategory c m o, FiniteCategory c m o, Morphism m o) =>
c -> [m]
arrows c
cat), m
g <- (c -> o -> [m]
forall c m o. (FiniteCategory c m o, Morphism m o) => c -> o -> [m]
arFrom c
cat (m -> o
forall m o. Morphism m o => m -> o
target m
f)), c -> m -> Bool
forall c m o.
(FiniteCategory c m o, Morphism m o, Eq m, Eq o) =>
c -> m -> Bool
isNotIdentity c
cat m
f, c -> m -> Bool
forall c m o.
(FiniteCategory c m o, Morphism m o, Eq m, Eq o) =>
c -> m -> Bool
isNotIdentity c
cat m
g]
cg :: SafeCompositionGraph o m
cg = (SafeCompositionGraph :: forall a b.
Graph a b -> CompositionLaw a b -> Int -> SafeCompositionGraph a b
SafeCompositionGraph{graphS :: Graph o m
graphS=(c -> [o]
forall c m o. FiniteCategory c m o => c -> [o]
ob c
cat, [m -> (o, o, m)
forall {c} {b}. Morphism c b => c -> (b, b, c)
morphToArrow m
f | m
f <- (c -> [m]
forall c m o.
(FiniteCategory c m o, FiniteCategory c m o, Morphism m o) =>
c -> [m]
arrows c
cat), c -> m -> Bool
forall c m o.
(FiniteCategory c m o, Morphism m o, Eq m, Eq o) =>
c -> m -> Bool
isNotIdentity c
cat m
f])
, lawS :: [([(o, o, m)], [(o, o, m)])]
lawS= [([(o, o, m)], [(o, o, m)])]
catLaw, maxCycles :: Int
maxCycles=Int
maxnbcycles})
isofunct :: Diagram c m o (SafeCompositionGraph o m) (SCGMorphism o m) o
isofunct = Diagram :: forall c1 m1 o1 c2 m2 o2.
c1
-> c2
-> AssociationList o1 o2
-> AssociationList m1 m2
-> Diagram c1 m1 o1 c2 m2 o2
Diagram{src :: c
src=c
cat,tgt :: SafeCompositionGraph o m
tgt=SafeCompositionGraph o m
cg,omap :: AssociationList o o
omap=(o -> o) -> [o] -> AssociationList o o
forall a b. (a -> b) -> [a] -> AssociationList a b
functToAssocList o -> o
forall a. a -> a
id (c -> [o]
forall c m o. FiniteCategory c m o => c -> [o]
ob c
cat),mmap :: AssociationList m (SCGMorphism o m)
mmap=(m -> SCGMorphism o m)
-> [m] -> AssociationList m (SCGMorphism o m)
forall a b. (a -> b) -> [a] -> AssociationList a b
functToAssocList (\m
f -> if c -> m -> Bool
forall c m o.
(FiniteCategory c m o, Morphism m o, Eq m, Eq o) =>
c -> m -> Bool
isNotIdentity c
cat m
f
then
[([(o, o, m)], [(o, o, m)])] -> Int -> (o, o, m) -> SCGMorphism o m
forall a b.
CompositionLaw a b -> Int -> Arrow a b -> SCGMorphism a b
mkSCGMorphism [([(o, o, m)], [(o, o, m)])]
catLaw Int
maxnbcycles (m -> (o, o, m)
forall {c} {b}. Morphism c b => c -> (b, b, c)
morphToArrow m
f)
else
SafeCompositionGraph o m -> o -> SCGMorphism o m
forall c m o. (FiniteCategory c m o, Morphism m o) => c -> o -> m
identity SafeCompositionGraph o m
cg (m -> o
forall m o. Morphism m o => m -> o
source m
f)) (c -> [m]
forall c m o.
(FiniteCategory c m o, FiniteCategory c m o, Morphism m o) =>
c -> [m]
arrows c
cat)}
generatedFiniteCategoryToSafeCompositionGraph :: (GeneratedFiniteCategory c m o, Morphism m o, Eq m, Eq o) => c -> (SafeCompositionGraph o m, Diagram c m o (SafeCompositionGraph o m) (SCGMorphism o m) o)
generatedFiniteCategoryToSafeCompositionGraph :: forall c m o.
(GeneratedFiniteCategory c m o, Morphism m o, Eq m, Eq o) =>
c
-> (SafeCompositionGraph o m,
Diagram c m o (SafeCompositionGraph o m) (SCGMorphism o m) o)
generatedFiniteCategoryToSafeCompositionGraph c
cat = (SafeCompositionGraph o m
cg,Diagram c m o (SafeCompositionGraph o m) (SCGMorphism o m) o
isofunct)
where
maxnbcycles :: Int
maxnbcycles = [Int] -> Int
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum ([Int] -> Int) -> [Int] -> Int
forall a b. (a -> b) -> a -> b
$ [m] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length ([m] -> Int) -> [[m]] -> [Int]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ((\o
x -> c -> o -> o -> [m]
forall c m o.
(FiniteCategory c m o, Morphism m o) =>
c -> o -> o -> [m]
ar c
cat o
x o
x) (o -> [m]) -> [o] -> [[m]]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> c -> [o]
forall c m o. FiniteCategory c m o => c -> [o]
ob c
cat)
morphToArrow :: c -> (b, b, c)
morphToArrow c
f = ((c -> b
forall m o. Morphism m o => m -> o
source c
f),(c -> b
forall m o. Morphism m o => m -> o
target c
f),c
f)
catLaw :: [([(o, o, m)], [(o, o, m)])]
catLaw = [
if c -> m -> Bool
forall c m o.
(FiniteCategory c m o, Morphism m o, Eq m, Eq o) =>
c -> m -> Bool
isNotIdentity c
cat (m
g m -> m -> m
forall m o. Morphism m o => m -> m -> m
@ m
f) then
((m -> (o, o, m)
forall {c} {b}. Morphism c b => c -> (b, b, c)
morphToArrow (m -> (o, o, m)) -> [m] -> [(o, o, m)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (c -> m -> [m]
forall c m o.
(GeneratedFiniteCategory c m o, Morphism m o) =>
c -> m -> [m]
decompose c
cat m
g))[(o, o, m)] -> [(o, o, m)] -> [(o, o, m)]
forall a. [a] -> [a] -> [a]
++(m -> (o, o, m)
forall {c} {b}. Morphism c b => c -> (b, b, c)
morphToArrow (m -> (o, o, m)) -> [m] -> [(o, o, m)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (c -> m -> [m]
forall c m o.
(GeneratedFiniteCategory c m o, Morphism m o) =>
c -> m -> [m]
decompose c
cat m
f)), m -> (o, o, m)
forall {c} {b}. Morphism c b => c -> (b, b, c)
morphToArrow (m -> (o, o, m)) -> [m] -> [(o, o, m)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (c -> m -> [m]
forall c m o.
(GeneratedFiniteCategory c m o, Morphism m o) =>
c -> m -> [m]
decompose c
cat (m
g m -> m -> m
forall m o. Morphism m o => m -> m -> m
@ m
f)))
else
((m -> (o, o, m)
forall {c} {b}. Morphism c b => c -> (b, b, c)
morphToArrow (m -> (o, o, m)) -> [m] -> [(o, o, m)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (c -> m -> [m]
forall c m o.
(GeneratedFiniteCategory c m o, Morphism m o) =>
c -> m -> [m]
decompose c
cat m
g))[(o, o, m)] -> [(o, o, m)] -> [(o, o, m)]
forall a. [a] -> [a] -> [a]
++(m -> (o, o, m)
forall {c} {b}. Morphism c b => c -> (b, b, c)
morphToArrow (m -> (o, o, m)) -> [m] -> [(o, o, m)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (c -> m -> [m]
forall c m o.
(GeneratedFiniteCategory c m o, Morphism m o) =>
c -> m -> [m]
decompose c
cat m
f)),[]) |
m
f <- (c -> [m]
forall c m o.
(FiniteCategory c m o, FiniteCategory c m o, Morphism m o) =>
c -> [m]
arrows c
cat), m
g <- (c -> o -> [m]
forall c m o. (FiniteCategory c m o, Morphism m o) => c -> o -> [m]
arFrom c
cat (m -> o
forall m o. Morphism m o => m -> o
target m
f)), c -> m -> Bool
forall c m o.
(FiniteCategory c m o, Morphism m o, Eq m, Eq o) =>
c -> m -> Bool
isNotIdentity c
cat m
f, c -> m -> Bool
forall c m o.
(FiniteCategory c m o, Morphism m o, Eq m, Eq o) =>
c -> m -> Bool
isNotIdentity c
cat m
g]
cg :: SafeCompositionGraph o m
cg = (SafeCompositionGraph :: forall a b.
Graph a b -> CompositionLaw a b -> Int -> SafeCompositionGraph a b
SafeCompositionGraph{graphS :: Graph o m
graphS=(c -> [o]
forall c m o. FiniteCategory c m o => c -> [o]
ob c
cat, [m -> (o, o, m)
forall {c} {b}. Morphism c b => c -> (b, b, c)
morphToArrow m
f | m
f <- (c -> [m]
forall c m o.
(GeneratedFiniteCategory c m o, GeneratedFiniteCategory c m o,
Morphism m o) =>
c -> [m]
genArrows c
cat), c -> m -> Bool
forall c m o.
(FiniteCategory c m o, Morphism m o, Eq m, Eq o) =>
c -> m -> Bool
isNotIdentity c
cat m
f])
, lawS :: [([(o, o, m)], [(o, o, m)])]
lawS= [([(o, o, m)], [(o, o, m)])]
catLaw, maxCycles :: Int
maxCycles=Int
maxnbcycles})
isofunct :: Diagram c m o (SafeCompositionGraph o m) (SCGMorphism o m) o
isofunct = Diagram :: forall c1 m1 o1 c2 m2 o2.
c1
-> c2
-> AssociationList o1 o2
-> AssociationList m1 m2
-> Diagram c1 m1 o1 c2 m2 o2
Diagram{src :: c
src=c
cat,tgt :: SafeCompositionGraph o m
tgt=SafeCompositionGraph o m
cg,omap :: AssociationList o o
omap=(o -> o) -> [o] -> AssociationList o o
forall a b. (a -> b) -> [a] -> AssociationList a b
functToAssocList o -> o
forall a. a -> a
id (c -> [o]
forall c m o. FiniteCategory c m o => c -> [o]
ob c
cat),mmap :: AssociationList m (SCGMorphism o m)
mmap=(m -> SCGMorphism o m)
-> [m] -> AssociationList m (SCGMorphism o m)
forall a b. (a -> b) -> [a] -> AssociationList a b
functToAssocList (\m
f -> if c -> m -> Bool
forall c m o.
(FiniteCategory c m o, Morphism m o, Eq m, Eq o) =>
c -> m -> Bool
isNotIdentity c
cat m
f
then
SCGMorphism :: forall a b.
Path a b -> CompositionLaw a b -> Int -> SCGMorphism a b
SCGMorphism {pathS :: Path o m
pathS=(m -> o
forall m o. Morphism m o => m -> o
source m
f,(m -> (o, o, m)
forall {c} {b}. Morphism c b => c -> (b, b, c)
morphToArrow (m -> (o, o, m)) -> [m] -> [(o, o, m)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (c -> m -> [m]
forall c m o.
(GeneratedFiniteCategory c m o, Morphism m o) =>
c -> m -> [m]
decompose c
cat m
f)),m -> o
forall m o. Morphism m o => m -> o
target m
f),compositionLawS :: [([(o, o, m)], [(o, o, m)])]
compositionLawS=[([(o, o, m)], [(o, o, m)])]
catLaw, maxNbCycles :: Int
maxNbCycles=Int
maxnbcycles}
else
SafeCompositionGraph o m -> o -> SCGMorphism o m
forall c m o. (FiniteCategory c m o, Morphism m o) => c -> o -> m
identity SafeCompositionGraph o m
cg (m -> o
forall m o. Morphism m o => m -> o
source m
f)) (c -> [m]
forall c m o.
(FiniteCategory c m o, FiniteCategory c m o, Morphism m o) =>
c -> [m]
arrows c
cat)}
data SafeCompositionGraphError a b = InsertMorphismNonExistantSourceS {forall a b. SafeCompositionGraphError a b -> b
faultyMorphS :: b, forall a b. SafeCompositionGraphError a b -> a
faultySrcS :: a}
| InsertMorphismNonExistantTargetS {faultyMorphS :: b, forall a b. SafeCompositionGraphError a b -> a
faultyTgtS :: a}
| IdentifyGeneratorS {forall a b. SafeCompositionGraphError a b -> SCGMorphism a b
genS :: SCGMorphism a b}
| UnidentifyNonExistantMorphismS {forall a b. SafeCompositionGraphError a b -> SCGMorphism a b
morphS :: SCGMorphism a b}
| ResultingCategoryErrorS (FiniteCategoryError (SCGMorphism a b) a)
| ReplaceNonExistantObjectS {forall a b. SafeCompositionGraphError a b -> a
faultyObjS :: a}
| ReplaceCompositeMorphismS {forall a b. SafeCompositionGraphError a b -> SCGMorphism a b
compositeS :: SCGMorphism a b}
| DeleteIdentityS {forall a b. SafeCompositionGraphError a b -> SCGMorphism a b
faultyIdentityS :: SCGMorphism a b}
| DeleteCompositeMorphS {compositeS :: SCGMorphism a b}
| DeleteNonExistantObjectMorphS {forall a b. SafeCompositionGraphError a b -> SCGMorphism a b
neMorphS :: SCGMorphism a b}
| DeleteNonExistantObjectS {faultyObjS :: a}
insertObjectS :: (Eq a, Eq b) => SafeCompositionGraph a b -> a -> (SafeCompositionGraph a b, (PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a))
insertObjectS :: forall a b.
(Eq a, Eq b) =>
SafeCompositionGraph a b
-> a
-> (SafeCompositionGraph a b,
PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a)
insertObjectS prev :: SafeCompositionGraph a b
prev@SafeCompositionGraph{graphS :: forall a b. SafeCompositionGraph a b -> Graph a b
graphS=([a]
nodes,[Arrow a b]
arrs), lawS :: forall a b. SafeCompositionGraph a b -> CompositionLaw a b
lawS=CompositionLaw a b
l, maxCycles :: forall a b. SafeCompositionGraph a b -> Int
maxCycles=Int
nb} a
obj = (SafeCompositionGraph a b
new, PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a
funct)
where
new :: SafeCompositionGraph a b
new = SafeCompositionGraph :: forall a b.
Graph a b -> CompositionLaw a b -> Int -> SafeCompositionGraph a b
SafeCompositionGraph{graphS :: ([a], [Arrow a b])
graphS=(a
obja -> [a] -> [a]
forall a. a -> [a] -> [a]
:[a]
nodes,[Arrow a b]
arrs), lawS :: CompositionLaw a b
lawS=CompositionLaw a b
l, maxCycles :: Int
maxCycles=Int
nb}
funct :: PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a
funct = PartialFunctor :: forall c m o.
c
-> c
-> AssociationList o o
-> AssociationList m m
-> PartialFunctor c m o
PartialFunctor{srcPF :: SafeCompositionGraph a b
srcPF=SafeCompositionGraph a b
prev,tgtPF :: SafeCompositionGraph a b
tgtPF=SafeCompositionGraph a b
new,omapPF :: AssociationList a a
omapPF=(a -> a) -> [a] -> AssociationList a a
forall a b. (a -> b) -> [a] -> AssociationList a b
functToAssocList a -> a
forall a. a -> a
id [a]
nodes,mmapPF :: AssociationList (SCGMorphism a b) (SCGMorphism a b)
mmapPF=(SCGMorphism a b -> SCGMorphism a b)
-> [SCGMorphism a b]
-> AssociationList (SCGMorphism a b) (SCGMorphism a b)
forall a b. (a -> b) -> [a] -> AssociationList a b
functToAssocList SCGMorphism a b -> SCGMorphism a b
forall a. a -> a
id (SafeCompositionGraph a b -> [SCGMorphism a b]
forall c m o.
(FiniteCategory c m o, FiniteCategory c m o, Morphism m o) =>
c -> [m]
arrows SafeCompositionGraph a b
prev)}
insertMorphismS :: (Eq a, Eq b) => SafeCompositionGraph a b -> a -> a -> b -> Either
(SafeCompositionGraphError a b)
(SafeCompositionGraph a b, (PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a))
insertMorphismS :: forall a b.
(Eq a, Eq b) =>
SafeCompositionGraph a b
-> a
-> a
-> b
-> Either
(SafeCompositionGraphError a b)
(SafeCompositionGraph a b,
PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a)
insertMorphismS prev :: SafeCompositionGraph a b
prev@SafeCompositionGraph{graphS :: forall a b. SafeCompositionGraph a b -> Graph a b
graphS=([a]
nodes,[Arrow a b]
arrs), lawS :: forall a b. SafeCompositionGraph a b -> CompositionLaw a b
lawS=CompositionLaw a b
l, maxCycles :: forall a b. SafeCompositionGraph a b -> Int
maxCycles=Int
nb} a
src a
tgt b
morph
| a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
elem a
src [a]
nodes Bool -> Bool -> Bool
&& a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
elem a
tgt [a]
nodes = (SafeCompositionGraph a b,
PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a)
-> Either
(SafeCompositionGraphError a b)
(SafeCompositionGraph a b,
PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a)
forall a b. b -> Either a b
Right (SafeCompositionGraph a b
new, PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a
funct)
| Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
elem a
src [a]
nodes = SafeCompositionGraphError a b
-> Either
(SafeCompositionGraphError a b)
(SafeCompositionGraph a b,
PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a)
forall a b. a -> Either a b
Left InsertMorphismNonExistantSourceS :: forall a b. b -> a -> SafeCompositionGraphError a b
InsertMorphismNonExistantSourceS{faultyMorphS :: b
faultyMorphS=b
morph, faultySrcS :: a
faultySrcS=a
src}
| Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
elem a
tgt [a]
nodes = SafeCompositionGraphError a b
-> Either
(SafeCompositionGraphError a b)
(SafeCompositionGraph a b,
PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a)
forall a b. a -> Either a b
Left InsertMorphismNonExistantTargetS :: forall a b. b -> a -> SafeCompositionGraphError a b
InsertMorphismNonExistantTargetS{faultyMorphS :: b
faultyMorphS=b
morph, faultyTgtS :: a
faultyTgtS=a
tgt}
where
new :: SafeCompositionGraph a b
new = SafeCompositionGraph :: forall a b.
Graph a b -> CompositionLaw a b -> Int -> SafeCompositionGraph a b
SafeCompositionGraph{graphS :: ([a], [Arrow a b])
graphS=([a]
nodes,(a
src, a
tgt, b
morph)Arrow a b -> [Arrow a b] -> [Arrow a b]
forall a. a -> [a] -> [a]
:[Arrow a b]
arrs), lawS :: CompositionLaw a b
lawS=CompositionLaw a b
l, maxCycles :: Int
maxCycles=Int
nb}
funct :: PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a
funct = PartialFunctor :: forall c m o.
c
-> c
-> AssociationList o o
-> AssociationList m m
-> PartialFunctor c m o
PartialFunctor{srcPF :: SafeCompositionGraph a b
srcPF=SafeCompositionGraph a b
prev,tgtPF :: SafeCompositionGraph a b
tgtPF=SafeCompositionGraph a b
new,omapPF :: AssociationList a a
omapPF=(a -> a) -> [a] -> AssociationList a a
forall a b. (a -> b) -> [a] -> AssociationList a b
functToAssocList a -> a
forall a. a -> a
id [a]
nodes,mmapPF :: AssociationList (SCGMorphism a b) (SCGMorphism a b)
mmapPF=(SCGMorphism a b -> SCGMorphism a b)
-> [SCGMorphism a b]
-> AssociationList (SCGMorphism a b) (SCGMorphism a b)
forall a b. (a -> b) -> [a] -> AssociationList a b
functToAssocList SCGMorphism a b -> SCGMorphism a b
forall a. a -> a
id (SafeCompositionGraph a b -> [SCGMorphism a b]
forall c m o.
(FiniteCategory c m o, FiniteCategory c m o, Morphism m o) =>
c -> [m]
arrows SafeCompositionGraph a b
prev)}
identifyMorphismsS :: (Eq a, Eq b) => SafeCompositionGraph a b -> SCGMorphism a b -> SCGMorphism a b -> Either
(SafeCompositionGraphError a b)
(SafeCompositionGraph a b, (PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a))
identifyMorphismsS :: forall a b.
(Eq a, Eq b) =>
SafeCompositionGraph a b
-> SCGMorphism a b
-> SCGMorphism a b
-> Either
(SafeCompositionGraphError a b)
(SafeCompositionGraph a b,
PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a)
identifyMorphismsS prev :: SafeCompositionGraph a b
prev@SafeCompositionGraph{graphS :: forall a b. SafeCompositionGraph a b -> Graph a b
graphS=([a]
nodes,[Arrow a b]
arrs), lawS :: forall a b. SafeCompositionGraph a b -> CompositionLaw a b
lawS=CompositionLaw a b
l, maxCycles :: forall a b. SafeCompositionGraph a b -> Int
maxCycles=Int
nb} SCGMorphism a b
srcM SCGMorphism a b
tgtM
| SCGMorphism a b -> Bool
forall a b. Eq a => SCGMorphism a b -> Bool
isGenS SCGMorphism a b
srcM = SafeCompositionGraphError a b
-> Either
(SafeCompositionGraphError a b)
(SafeCompositionGraph a b,
PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a)
forall a b. a -> Either a b
Left IdentifyGeneratorS :: forall a b. SCGMorphism a b -> SafeCompositionGraphError a b
IdentifyGeneratorS{genS :: SCGMorphism a b
genS=SCGMorphism a b
srcM}
| Maybe (FiniteCategoryError (SCGMorphism a b) a) -> Bool
forall a. Maybe a -> Bool
isNothing Maybe (FiniteCategoryError (SCGMorphism a b) a)
check = (SafeCompositionGraph a b,
PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a)
-> Either
(SafeCompositionGraphError a b)
(SafeCompositionGraph a b,
PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a)
forall a b. b -> Either a b
Right (SafeCompositionGraph a b
new,PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a
funct)
| Bool
otherwise = SafeCompositionGraphError a b
-> Either
(SafeCompositionGraphError a b)
(SafeCompositionGraph a b,
PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a)
forall a b. a -> Either a b
Left (SafeCompositionGraphError a b
-> Either
(SafeCompositionGraphError a b)
(SafeCompositionGraph a b,
PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a))
-> SafeCompositionGraphError a b
-> Either
(SafeCompositionGraphError a b)
(SafeCompositionGraph a b,
PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a)
forall a b. (a -> b) -> a -> b
$ FiniteCategoryError (SCGMorphism a b) a
-> SafeCompositionGraphError a b
forall a b.
FiniteCategoryError (SCGMorphism a b) a
-> SafeCompositionGraphError a b
ResultingCategoryErrorS (Maybe (FiniteCategoryError (SCGMorphism a b) a)
-> FiniteCategoryError (SCGMorphism a b) a
forall a. HasCallStack => Maybe a -> a
fromJust Maybe (FiniteCategoryError (SCGMorphism a b) a)
check)
where
newLaw :: CompositionLaw a b
newLaw = (((a, [Arrow a b], a) -> [Arrow a b]
forall a b c. (a, b, c) -> b
snd3((a, [Arrow a b], a) -> [Arrow a b])
-> (SCGMorphism a b -> (a, [Arrow a b], a))
-> SCGMorphism a b
-> [Arrow a b]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.SCGMorphism a b -> (a, [Arrow a b], a)
forall a b. SCGMorphism a b -> Path a b
pathS) SCGMorphism a b
srcM,((a, [Arrow a b], a) -> [Arrow a b]
forall a b c. (a, b, c) -> b
snd3((a, [Arrow a b], a) -> [Arrow a b])
-> (SCGMorphism a b -> (a, [Arrow a b], a))
-> SCGMorphism a b
-> [Arrow a b]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.SCGMorphism a b -> (a, [Arrow a b], a)
forall a b. SCGMorphism a b -> Path a b
pathS) SCGMorphism a b
tgtM)([Arrow a b], [Arrow a b])
-> CompositionLaw a b -> CompositionLaw a b
forall a. a -> [a] -> [a]
:CompositionLaw a b
l
new :: SafeCompositionGraph a b
new = SafeCompositionGraph :: forall a b.
Graph a b -> CompositionLaw a b -> Int -> SafeCompositionGraph a b
SafeCompositionGraph{graphS :: ([a], [Arrow a b])
graphS=([a]
nodes,[Arrow a b]
arrs), lawS :: CompositionLaw a b
lawS=CompositionLaw a b
newLaw, maxCycles :: Int
maxCycles=Int
nb}
check :: Maybe (FiniteCategoryError (SCGMorphism a b) a)
check = SafeCompositionGraph a b
-> Maybe (FiniteCategoryError (SCGMorphism a b) a)
forall c m o.
(GeneratedFiniteCategory c m o, Morphism m o, Eq m, Eq o) =>
c -> Maybe (FiniteCategoryError m o)
checkGeneratedFiniteCategoryProperties SafeCompositionGraph a b
new
replaceLaw :: SCGMorphism a b -> SCGMorphism a b
replaceLaw SCGMorphism a b
m = SCGMorphism :: forall a b.
Path a b -> CompositionLaw a b -> Int -> SCGMorphism a b
SCGMorphism{pathS :: (a, [Arrow a b], a)
pathS=(SCGMorphism a b -> (a, [Arrow a b], a)
forall a b. SCGMorphism a b -> Path a b
pathS SCGMorphism a b
m)
,compositionLawS :: CompositionLaw a b
compositionLawS=CompositionLaw a b
newLaw, maxNbCycles :: Int
maxNbCycles=Int
nb}
funct :: PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a
funct = PartialFunctor :: forall c m o.
c
-> c
-> AssociationList o o
-> AssociationList m m
-> PartialFunctor c m o
PartialFunctor{srcPF :: SafeCompositionGraph a b
srcPF=SafeCompositionGraph a b
prev,tgtPF :: SafeCompositionGraph a b
tgtPF=SafeCompositionGraph a b
new,omapPF :: AssociationList a a
omapPF=(a -> a) -> [a] -> AssociationList a a
forall a b. (a -> b) -> [a] -> AssociationList a b
functToAssocList a -> a
forall a. a -> a
id [a]
nodes,mmapPF :: AssociationList (SCGMorphism a b) (SCGMorphism a b)
mmapPF=(SCGMorphism a b -> SCGMorphism a b)
-> [SCGMorphism a b]
-> AssociationList (SCGMorphism a b) (SCGMorphism a b)
forall a b. (a -> b) -> [a] -> AssociationList a b
functToAssocList SCGMorphism a b -> SCGMorphism a b
replaceLaw (SCGMorphism a b -> [SCGMorphism a b] -> [SCGMorphism a b]
forall a. Eq a => a -> [a] -> [a]
delete SCGMorphism a b
srcM (SafeCompositionGraph a b -> [SCGMorphism a b]
forall c m o.
(FiniteCategory c m o, FiniteCategory c m o, Morphism m o) =>
c -> [m]
arrows SafeCompositionGraph a b
prev))}
unidentifyMorphismS :: (Eq a, Eq b) => SafeCompositionGraph a b -> SCGMorphism a b -> Either
(SafeCompositionGraphError a b)
(SafeCompositionGraph a b, (PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a))
unidentifyMorphismS :: forall a b.
(Eq a, Eq b) =>
SafeCompositionGraph a b
-> SCGMorphism a b
-> Either
(SafeCompositionGraphError a b)
(SafeCompositionGraph a b,
PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a)
unidentifyMorphismS prev :: SafeCompositionGraph a b
prev@SafeCompositionGraph{graphS :: forall a b. SafeCompositionGraph a b -> Graph a b
graphS=([a]
nodes,[Arrow a b]
arrs), lawS :: forall a b. SafeCompositionGraph a b -> CompositionLaw a b
lawS=CompositionLaw a b
l, maxCycles :: forall a b. SafeCompositionGraph a b -> Int
maxCycles=Int
nb} SCGMorphism a b
m
| SCGMorphism a b -> [SCGMorphism a b] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
elem SCGMorphism a b
m (SafeCompositionGraph a b -> a -> a -> [SCGMorphism a b]
forall c m o.
(FiniteCategory c m o, Morphism m o) =>
c -> o -> o -> [m]
ar SafeCompositionGraph a b
prev (SCGMorphism a b -> a
forall m o. Morphism m o => m -> o
source SCGMorphism a b
m) (SCGMorphism a b -> a
forall m o. Morphism m o => m -> o
target SCGMorphism a b
m)) = (SafeCompositionGraph a b,
PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a)
-> Either
(SafeCompositionGraphError a b)
(SafeCompositionGraph a b,
PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a)
forall a b. b -> Either a b
Right (SafeCompositionGraph a b
new,PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a
funct)
| Bool
otherwise = SafeCompositionGraphError a b
-> Either
(SafeCompositionGraphError a b)
(SafeCompositionGraph a b,
PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a)
forall a b. a -> Either a b
Left UnidentifyNonExistantMorphismS :: forall a b. SCGMorphism a b -> SafeCompositionGraphError a b
UnidentifyNonExistantMorphismS{morphS :: SCGMorphism a b
morphS=SCGMorphism a b
m}
where
newLaw :: CompositionLaw a b
newLaw = (([Arrow a b], [Arrow a b]) -> Bool)
-> CompositionLaw a b -> CompositionLaw a b
forall a. (a -> Bool) -> [a] -> [a]
filter ((((a, [Arrow a b], a) -> [Arrow a b]
forall a b c. (a, b, c) -> b
snd3((a, [Arrow a b], a) -> [Arrow a b])
-> (SCGMorphism a b -> (a, [Arrow a b], a))
-> SCGMorphism a b
-> [Arrow a b]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.SCGMorphism a b -> (a, [Arrow a b], a)
forall a b. SCGMorphism a b -> Path a b
pathS (SCGMorphism a b -> [Arrow a b]) -> SCGMorphism a b -> [Arrow a b]
forall a b. (a -> b) -> a -> b
$ SCGMorphism a b
m)[Arrow a b] -> [Arrow a b] -> Bool
forall a. Eq a => a -> a -> Bool
/=)([Arrow a b] -> Bool)
-> (([Arrow a b], [Arrow a b]) -> [Arrow a b])
-> ([Arrow a b], [Arrow a b])
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
.([Arrow a b], [Arrow a b]) -> [Arrow a b]
forall a b. (a, b) -> b
snd) CompositionLaw a b
l
replaceLawInMorph :: SCGMorphism a b -> SCGMorphism a b
replaceLawInMorph SCGMorphism{pathS :: forall a b. SCGMorphism a b -> Path a b
pathS=(a, [Arrow a b], a)
p,compositionLawS :: forall a b. SCGMorphism a b -> CompositionLaw a b
compositionLawS=CompositionLaw a b
_, maxNbCycles :: forall a b. SCGMorphism a b -> Int
maxNbCycles=Int
_} = SCGMorphism :: forall a b.
Path a b -> CompositionLaw a b -> Int -> SCGMorphism a b
SCGMorphism{pathS :: (a, [Arrow a b], a)
pathS=(a, [Arrow a b], a)
p,compositionLawS :: CompositionLaw a b
compositionLawS=CompositionLaw a b
newLaw, maxNbCycles :: Int
maxNbCycles=Int
nb}
new :: SafeCompositionGraph a b
new = SafeCompositionGraph :: forall a b.
Graph a b -> CompositionLaw a b -> Int -> SafeCompositionGraph a b
SafeCompositionGraph{graphS :: ([a], [Arrow a b])
graphS=([a]
nodes,[Arrow a b]
arrs), lawS :: CompositionLaw a b
lawS=CompositionLaw a b
newLaw, maxCycles :: Int
maxCycles=Int
nb}
funct :: PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a
funct = PartialFunctor :: forall c m o.
c
-> c
-> AssociationList o o
-> AssociationList m m
-> PartialFunctor c m o
PartialFunctor{srcPF :: SafeCompositionGraph a b
srcPF=SafeCompositionGraph a b
prev,tgtPF :: SafeCompositionGraph a b
tgtPF=SafeCompositionGraph a b
new,omapPF :: AssociationList a a
omapPF=(a -> a) -> [a] -> AssociationList a a
forall a b. (a -> b) -> [a] -> AssociationList a b
functToAssocList a -> a
forall a. a -> a
id [a]
nodes,mmapPF :: AssociationList (SCGMorphism a b) (SCGMorphism a b)
mmapPF=(SCGMorphism a b -> SCGMorphism a b)
-> [SCGMorphism a b]
-> AssociationList (SCGMorphism a b) (SCGMorphism a b)
forall a b. (a -> b) -> [a] -> AssociationList a b
functToAssocList SCGMorphism a b -> SCGMorphism a b
replaceLawInMorph (SafeCompositionGraph a b -> [SCGMorphism a b]
forall c m o.
(FiniteCategory c m o, FiniteCategory c m o, Morphism m o) =>
c -> [m]
arrows SafeCompositionGraph a b
prev)}
replaceObjectS :: (Eq a, Eq b) => SafeCompositionGraph a b -> a -> a -> Either
(SafeCompositionGraphError a b)
(SafeCompositionGraph a b, (PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a))
replaceObjectS :: forall a b.
(Eq a, Eq b) =>
SafeCompositionGraph a b
-> a
-> a
-> Either
(SafeCompositionGraphError a b)
(SafeCompositionGraph a b,
PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a)
replaceObjectS prev :: SafeCompositionGraph a b
prev@SafeCompositionGraph{graphS :: forall a b. SafeCompositionGraph a b -> Graph a b
graphS=([a]
nodes,[Arrow a b]
arrs), lawS :: forall a b. SafeCompositionGraph a b -> CompositionLaw a b
lawS=CompositionLaw a b
l, maxCycles :: forall a b. SafeCompositionGraph a b -> Int
maxCycles=Int
nb} a
prevObj a
newObj
| a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
elem a
prevObj (SafeCompositionGraph a b -> [a]
forall c m o. FiniteCategory c m o => c -> [o]
ob SafeCompositionGraph a b
prev) = (SafeCompositionGraph a b,
PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a)
-> Either
(SafeCompositionGraphError a b)
(SafeCompositionGraph a b,
PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a)
forall a b. b -> Either a b
Right (SafeCompositionGraph a b
new,PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a
funct)
| Bool
otherwise = SafeCompositionGraphError a b
-> Either
(SafeCompositionGraphError a b)
(SafeCompositionGraph a b,
PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a)
forall a b. a -> Either a b
Left ReplaceNonExistantObjectS :: forall a b. a -> SafeCompositionGraphError a b
ReplaceNonExistantObjectS {faultyObjS :: a
faultyObjS=a
prevObj}
where
replace :: a -> a
replace a
x = if a
x a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
prevObj then a
newObj else a
x
replaceArr :: (a, a, c) -> (a, a, c)
replaceArr (a
s,a
t,c
a) = (a -> a
replace a
s, a -> a
replace a
t, c
a)
replaceLawEntry :: (f (a, a, c), f (a, a, c)) -> (f (a, a, c), f (a, a, c))
replaceLawEntry (f (a, a, c)
k,f (a, a, c)
v) = ((a, a, c) -> (a, a, c)
forall {c}. (a, a, c) -> (a, a, c)
replaceArr ((a, a, c) -> (a, a, c)) -> f (a, a, c) -> f (a, a, c)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> f (a, a, c)
k, (a, a, c) -> (a, a, c)
forall {c}. (a, a, c) -> (a, a, c)
replaceArr ((a, a, c) -> (a, a, c)) -> f (a, a, c) -> f (a, a, c)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> f (a, a, c)
v)
replaceCGMorph :: SCGMorphism a c -> SCGMorphism a c
replaceCGMorph SCGMorphism{pathS :: forall a b. SCGMorphism a b -> Path a b
pathS=(a
s,RawPath a c
rp,a
t),compositionLawS :: forall a b. SCGMorphism a b -> CompositionLaw a b
compositionLawS=CompositionLaw a c
l, maxNbCycles :: forall a b. SCGMorphism a b -> Int
maxNbCycles=Int
nb} = SCGMorphism :: forall a b.
Path a b -> CompositionLaw a b -> Int -> SCGMorphism a b
SCGMorphism{pathS :: (a, RawPath a c, a)
pathS=(a -> a
replace a
s,(a, a, c) -> (a, a, c)
forall {c}. (a, a, c) -> (a, a, c)
replaceArr ((a, a, c) -> (a, a, c)) -> RawPath a c -> RawPath a c
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> RawPath a c
rp,a -> a
replace a
t),compositionLawS :: CompositionLaw a c
compositionLawS=(RawPath a c, RawPath a c) -> (RawPath a c, RawPath a c)
forall {f :: * -> *} {f :: * -> *} {c} {c}.
(Functor f, Functor f) =>
(f (a, a, c), f (a, a, c)) -> (f (a, a, c), f (a, a, c))
replaceLawEntry ((RawPath a c, RawPath a c) -> (RawPath a c, RawPath a c))
-> CompositionLaw a c -> CompositionLaw a c
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> CompositionLaw a c
l, maxNbCycles :: Int
maxNbCycles=Int
nb}
new :: SafeCompositionGraph a b
new = SafeCompositionGraph :: forall a b.
Graph a b -> CompositionLaw a b -> Int -> SafeCompositionGraph a b
SafeCompositionGraph{graphS :: ([a], [Arrow a b])
graphS=(a -> a
replace (a -> a) -> [a] -> [a]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [a]
nodes,Arrow a b -> Arrow a b
forall {c}. (a, a, c) -> (a, a, c)
replaceArr (Arrow a b -> Arrow a b) -> [Arrow a b] -> [Arrow a b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Arrow a b]
arrs), lawS :: CompositionLaw a b
lawS=([Arrow a b], [Arrow a b]) -> ([Arrow a b], [Arrow a b])
forall {f :: * -> *} {f :: * -> *} {c} {c}.
(Functor f, Functor f) =>
(f (a, a, c), f (a, a, c)) -> (f (a, a, c), f (a, a, c))
replaceLawEntry (([Arrow a b], [Arrow a b]) -> ([Arrow a b], [Arrow a b]))
-> CompositionLaw a b -> CompositionLaw a b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> CompositionLaw a b
l, maxCycles :: Int
maxCycles=Int
nb}
funct :: PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a
funct = PartialFunctor :: forall c m o.
c
-> c
-> AssociationList o o
-> AssociationList m m
-> PartialFunctor c m o
PartialFunctor{srcPF :: SafeCompositionGraph a b
srcPF=SafeCompositionGraph a b
prev,tgtPF :: SafeCompositionGraph a b
tgtPF=SafeCompositionGraph a b
new,omapPF :: AssociationList a a
omapPF=(a -> a) -> [a] -> AssociationList a a
forall a b. (a -> b) -> [a] -> AssociationList a b
functToAssocList a -> a
replace [a]
nodes,mmapPF :: AssociationList (SCGMorphism a b) (SCGMorphism a b)
mmapPF=(SCGMorphism a b -> SCGMorphism a b)
-> [SCGMorphism a b]
-> AssociationList (SCGMorphism a b) (SCGMorphism a b)
forall a b. (a -> b) -> [a] -> AssociationList a b
functToAssocList SCGMorphism a b -> SCGMorphism a b
forall {c}. SCGMorphism a c -> SCGMorphism a c
replaceCGMorph (SafeCompositionGraph a b -> [SCGMorphism a b]
forall c m o.
(FiniteCategory c m o, FiniteCategory c m o, Morphism m o) =>
c -> [m]
arrows SafeCompositionGraph a b
prev)}
replaceMorphismS :: (Eq a, Eq b) => SafeCompositionGraph a b -> SCGMorphism a b -> b -> Either
(SafeCompositionGraphError a b)
(SafeCompositionGraph a b, (PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a))
replaceMorphismS :: forall a b.
(Eq a, Eq b) =>
SafeCompositionGraph a b
-> SCGMorphism a b
-> b
-> Either
(SafeCompositionGraphError a b)
(SafeCompositionGraph a b,
PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a)
replaceMorphismS prev :: SafeCompositionGraph a b
prev@SafeCompositionGraph{graphS :: forall a b. SafeCompositionGraph a b -> Graph a b
graphS=([a]
nodes,[Arrow a b]
arrs), lawS :: forall a b. SafeCompositionGraph a b -> CompositionLaw a b
lawS=CompositionLaw a b
l, maxCycles :: forall a b. SafeCompositionGraph a b -> Int
maxCycles=Int
nb} SCGMorphism a b
prevMorph b
newMorph
| SCGMorphism a b -> [SCGMorphism a b] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
elem SCGMorphism a b
prevMorph (SafeCompositionGraph a b -> a -> a -> [SCGMorphism a b]
forall c m o.
(GeneratedFiniteCategory c m o, Morphism m o) =>
c -> o -> o -> [m]
genAr SafeCompositionGraph a b
prev (SCGMorphism a b -> a
forall m o. Morphism m o => m -> o
source SCGMorphism a b
prevMorph) (SCGMorphism a b -> a
forall m o. Morphism m o => m -> o
target SCGMorphism a b
prevMorph)) = (SafeCompositionGraph a b,
PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a)
-> Either
(SafeCompositionGraphError a b)
(SafeCompositionGraph a b,
PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a)
forall a b. b -> Either a b
Right (SafeCompositionGraph a b
new,PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a
funct)
| Bool
otherwise = SafeCompositionGraphError a b
-> Either
(SafeCompositionGraphError a b)
(SafeCompositionGraph a b,
PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a)
forall a b. a -> Either a b
Left ReplaceCompositeMorphismS :: forall a b. SCGMorphism a b -> SafeCompositionGraphError a b
ReplaceCompositeMorphismS{compositeS :: SCGMorphism a b
compositeS=SCGMorphism a b
prevMorph}
where
replaceArr :: Arrow a b -> Arrow a b
replaceArr m :: Arrow a b
m@(a
s,a
t,b
a) = if [Arrow a b
m] [Arrow a b] -> [Arrow a b] -> Bool
forall a. Eq a => a -> a -> Bool
== ((a, [Arrow a b], a) -> [Arrow a b]
forall a b c. (a, b, c) -> b
snd3((a, [Arrow a b], a) -> [Arrow a b])
-> (SCGMorphism a b -> (a, [Arrow a b], a))
-> SCGMorphism a b
-> [Arrow a b]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.SCGMorphism a b -> (a, [Arrow a b], a)
forall a b. SCGMorphism a b -> Path a b
pathS (SCGMorphism a b -> [Arrow a b]) -> SCGMorphism a b -> [Arrow a b]
forall a b. (a -> b) -> a -> b
$ SCGMorphism a b
prevMorph) then (a
s, a
t, b
newMorph) else Arrow a b
m
replaceLawEntry :: (f (Arrow a b), f (Arrow a b)) -> (f (Arrow a b), f (Arrow a b))
replaceLawEntry (f (Arrow a b)
k,f (Arrow a b)
v) = (Arrow a b -> Arrow a b
replaceArr (Arrow a b -> Arrow a b) -> f (Arrow a b) -> f (Arrow a b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> f (Arrow a b)
k, Arrow a b -> Arrow a b
replaceArr (Arrow a b -> Arrow a b) -> f (Arrow a b) -> f (Arrow a b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> f (Arrow a b)
v)
replaceCGMorph :: SCGMorphism a b -> SCGMorphism a b
replaceCGMorph SCGMorphism{pathS :: forall a b. SCGMorphism a b -> Path a b
pathS=(a
s,[Arrow a b]
rp,a
t),compositionLawS :: forall a b. SCGMorphism a b -> CompositionLaw a b
compositionLawS=CompositionLaw a b
l, maxNbCycles :: forall a b. SCGMorphism a b -> Int
maxNbCycles=Int
_} = SCGMorphism :: forall a b.
Path a b -> CompositionLaw a b -> Int -> SCGMorphism a b
SCGMorphism{pathS :: (a, [Arrow a b], a)
pathS=(a
s,Arrow a b -> Arrow a b
replaceArr (Arrow a b -> Arrow a b) -> [Arrow a b] -> [Arrow a b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Arrow a b]
rp,a
t),compositionLawS :: CompositionLaw a b
compositionLawS=([Arrow a b], [Arrow a b]) -> ([Arrow a b], [Arrow a b])
forall {f :: * -> *} {f :: * -> *}.
(Functor f, Functor f) =>
(f (Arrow a b), f (Arrow a b)) -> (f (Arrow a b), f (Arrow a b))
replaceLawEntry (([Arrow a b], [Arrow a b]) -> ([Arrow a b], [Arrow a b]))
-> CompositionLaw a b -> CompositionLaw a b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> CompositionLaw a b
l, maxNbCycles :: Int
maxNbCycles=Int
nb}
new :: SafeCompositionGraph a b
new = SafeCompositionGraph :: forall a b.
Graph a b -> CompositionLaw a b -> Int -> SafeCompositionGraph a b
SafeCompositionGraph{graphS :: ([a], [Arrow a b])
graphS=([a]
nodes,Arrow a b -> Arrow a b
replaceArr (Arrow a b -> Arrow a b) -> [Arrow a b] -> [Arrow a b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Arrow a b]
arrs), lawS :: CompositionLaw a b
lawS=([Arrow a b], [Arrow a b]) -> ([Arrow a b], [Arrow a b])
forall {f :: * -> *} {f :: * -> *}.
(Functor f, Functor f) =>
(f (Arrow a b), f (Arrow a b)) -> (f (Arrow a b), f (Arrow a b))
replaceLawEntry (([Arrow a b], [Arrow a b]) -> ([Arrow a b], [Arrow a b]))
-> CompositionLaw a b -> CompositionLaw a b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> CompositionLaw a b
l, maxCycles :: Int
maxCycles=Int
nb}
funct :: PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a
funct = PartialFunctor :: forall c m o.
c
-> c
-> AssociationList o o
-> AssociationList m m
-> PartialFunctor c m o
PartialFunctor{srcPF :: SafeCompositionGraph a b
srcPF=SafeCompositionGraph a b
prev,tgtPF :: SafeCompositionGraph a b
tgtPF=SafeCompositionGraph a b
new,omapPF :: AssociationList a a
omapPF=(a -> a) -> [a] -> AssociationList a a
forall a b. (a -> b) -> [a] -> AssociationList a b
functToAssocList a -> a
forall a. a -> a
id [a]
nodes,mmapPF :: AssociationList (SCGMorphism a b) (SCGMorphism a b)
mmapPF=(SCGMorphism a b -> SCGMorphism a b)
-> [SCGMorphism a b]
-> AssociationList (SCGMorphism a b) (SCGMorphism a b)
forall a b. (a -> b) -> [a] -> AssociationList a b
functToAssocList SCGMorphism a b -> SCGMorphism a b
replaceCGMorph (SafeCompositionGraph a b -> [SCGMorphism a b]
forall c m o.
(FiniteCategory c m o, FiniteCategory c m o, Morphism m o) =>
c -> [m]
arrows SafeCompositionGraph a b
prev)}
deleteMorphismS :: (Eq a, Eq b) => SafeCompositionGraph a b -> SCGMorphism a b -> Either
(SafeCompositionGraphError a b)
(SafeCompositionGraph a b, (PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a))
deleteMorphismS :: forall a b.
(Eq a, Eq b) =>
SafeCompositionGraph a b
-> SCGMorphism a b
-> Either
(SafeCompositionGraphError a b)
(SafeCompositionGraph a b,
PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a)
deleteMorphismS prev :: SafeCompositionGraph a b
prev@SafeCompositionGraph{graphS :: forall a b. SafeCompositionGraph a b -> Graph a b
graphS=([a]
nodes,[Arrow a b]
arrs), lawS :: forall a b. SafeCompositionGraph a b -> CompositionLaw a b
lawS=CompositionLaw a b
l, maxCycles :: forall a b. SafeCompositionGraph a b -> Int
maxCycles=Int
nb} SCGMorphism a b
morph
| SafeCompositionGraph a b -> SCGMorphism a b -> Bool
forall c m o.
(FiniteCategory c m o, Morphism m o, Eq m, Eq o) =>
c -> m -> Bool
isIdentity SafeCompositionGraph a b
prev SCGMorphism a b
morph = SafeCompositionGraphError a b
-> Either
(SafeCompositionGraphError a b)
(SafeCompositionGraph a b,
PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a)
forall a b. a -> Either a b
Left DeleteIdentityS :: forall a b. SCGMorphism a b -> SafeCompositionGraphError a b
DeleteIdentityS {faultyIdentityS :: SCGMorphism a b
faultyIdentityS=SCGMorphism a b
morph}
| SCGMorphism a b -> [SCGMorphism a b] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
elem SCGMorphism a b
morph (SafeCompositionGraph a b -> a -> a -> [SCGMorphism a b]
forall c m o.
(GeneratedFiniteCategory c m o, Morphism m o) =>
c -> o -> o -> [m]
genAr SafeCompositionGraph a b
prev (SCGMorphism a b -> a
forall m o. Morphism m o => m -> o
source SCGMorphism a b
morph) (SCGMorphism a b -> a
forall m o. Morphism m o => m -> o
target SCGMorphism a b
morph)) = (SafeCompositionGraph a b,
PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a)
-> Either
(SafeCompositionGraphError a b)
(SafeCompositionGraph a b,
PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a)
forall a b. b -> Either a b
Right (SafeCompositionGraph a b
new,PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a
funct)
| SCGMorphism a b -> [SCGMorphism a b] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
elem SCGMorphism a b
morph (SafeCompositionGraph a b -> a -> a -> [SCGMorphism a b]
forall c m o.
(FiniteCategory c m o, Morphism m o) =>
c -> o -> o -> [m]
ar SafeCompositionGraph a b
prev (SCGMorphism a b -> a
forall m o. Morphism m o => m -> o
source SCGMorphism a b
morph) (SCGMorphism a b -> a
forall m o. Morphism m o => m -> o
target SCGMorphism a b
morph)) = SafeCompositionGraphError a b
-> Either
(SafeCompositionGraphError a b)
(SafeCompositionGraph a b,
PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a)
forall a b. a -> Either a b
Left DeleteCompositeMorphS :: forall a b. SCGMorphism a b -> SafeCompositionGraphError a b
DeleteCompositeMorphS{compositeS :: SCGMorphism a b
compositeS=SCGMorphism a b
morph}
| Bool
otherwise = SafeCompositionGraphError a b
-> Either
(SafeCompositionGraphError a b)
(SafeCompositionGraph a b,
PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a)
forall a b. a -> Either a b
Left DeleteNonExistantObjectMorphS :: forall a b. SCGMorphism a b -> SafeCompositionGraphError a b
DeleteNonExistantObjectMorphS{neMorphS :: SCGMorphism a b
neMorphS=SCGMorphism a b
morph}
where
arr :: Arrow a b
arr = [Arrow a b] -> Arrow a b
forall a. [a] -> a
head([Arrow a b] -> Arrow a b)
-> (SCGMorphism a b -> [Arrow a b]) -> SCGMorphism a b -> Arrow a b
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(a, [Arrow a b], a) -> [Arrow a b]
forall a b c. (a, b, c) -> b
snd3((a, [Arrow a b], a) -> [Arrow a b])
-> (SCGMorphism a b -> (a, [Arrow a b], a))
-> SCGMorphism a b
-> [Arrow a b]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.SCGMorphism a b -> (a, [Arrow a b], a)
forall a b. SCGMorphism a b -> Path a b
pathS (SCGMorphism a b -> Arrow a b) -> SCGMorphism a b -> Arrow a b
forall a b. (a -> b) -> a -> b
$ SCGMorphism a b
morph
newLaw :: CompositionLaw a b
newLaw = (([Arrow a b], [Arrow a b]) -> Bool)
-> CompositionLaw a b -> CompositionLaw a b
forall a. (a -> Bool) -> [a] -> [a]
filter (\([Arrow a b]
k,[Arrow a b]
v) -> [Bool] -> Bool
forall (t :: * -> *). Foldable t => t Bool -> Bool
and ((Arrow a b -> Arrow a b -> Bool
forall a. Eq a => a -> a -> Bool
/=Arrow a b
arr) (Arrow a b -> Bool) -> [Arrow a b] -> [Bool]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Arrow a b]
k) Bool -> Bool -> Bool
&& [Bool] -> Bool
forall (t :: * -> *). Foldable t => t Bool -> Bool
and ((Arrow a b -> Arrow a b -> Bool
forall a. Eq a => a -> a -> Bool
/=Arrow a b
arr) (Arrow a b -> Bool) -> [Arrow a b] -> [Bool]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Arrow a b]
v)) CompositionLaw a b
l
newArrows :: [SCGMorphism a b]
newArrows = (SCGMorphism a b -> Bool) -> [SCGMorphism a b] -> [SCGMorphism a b]
forall a. (a -> Bool) -> [a] -> [a]
filter (\SCGMorphism{pathS :: forall a b. SCGMorphism a b -> Path a b
pathS=(a
s,[Arrow a b]
rp,a
t),compositionLawS :: forall a b. SCGMorphism a b -> CompositionLaw a b
compositionLawS=CompositionLaw a b
_, maxNbCycles :: forall a b. SCGMorphism a b -> Int
maxNbCycles=Int
_} -> Bool -> Bool
not (Arrow a b -> [Arrow a b] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
elem Arrow a b
arr [Arrow a b]
rp)) (SafeCompositionGraph a b -> [SCGMorphism a b]
forall c m o.
(FiniteCategory c m o, FiniteCategory c m o, Morphism m o) =>
c -> [m]
arrows SafeCompositionGraph a b
prev)
replaceLaw :: SCGMorphism a b -> SCGMorphism a b
replaceLaw SCGMorphism a b
m = SCGMorphism :: forall a b.
Path a b -> CompositionLaw a b -> Int -> SCGMorphism a b
SCGMorphism{pathS :: (a, [Arrow a b], a)
pathS=(SCGMorphism a b -> (a, [Arrow a b], a)
forall a b. SCGMorphism a b -> Path a b
pathS SCGMorphism a b
m)
,compositionLawS :: CompositionLaw a b
compositionLawS=CompositionLaw a b
newLaw,maxNbCycles :: Int
maxNbCycles=Int
nb}
new :: SafeCompositionGraph a b
new = SafeCompositionGraph :: forall a b.
Graph a b -> CompositionLaw a b -> Int -> SafeCompositionGraph a b
SafeCompositionGraph{graphS :: ([a], [Arrow a b])
graphS=([a]
nodes,Arrow a b -> [Arrow a b] -> [Arrow a b]
forall a. Eq a => a -> [a] -> [a]
delete Arrow a b
arr [Arrow a b]
arrs), lawS :: CompositionLaw a b
lawS=CompositionLaw a b
newLaw, maxCycles :: Int
maxCycles=Int
nb}
funct :: PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a
funct = PartialFunctor :: forall c m o.
c
-> c
-> AssociationList o o
-> AssociationList m m
-> PartialFunctor c m o
PartialFunctor{srcPF :: SafeCompositionGraph a b
srcPF=SafeCompositionGraph a b
prev,tgtPF :: SafeCompositionGraph a b
tgtPF=SafeCompositionGraph a b
new,omapPF :: AssociationList a a
omapPF=(a -> a) -> [a] -> AssociationList a a
forall a b. (a -> b) -> [a] -> AssociationList a b
functToAssocList a -> a
forall a. a -> a
id [a]
nodes,mmapPF :: AssociationList (SCGMorphism a b) (SCGMorphism a b)
mmapPF=(SCGMorphism a b -> SCGMorphism a b)
-> [SCGMorphism a b]
-> AssociationList (SCGMorphism a b) (SCGMorphism a b)
forall a b. (a -> b) -> [a] -> AssociationList a b
functToAssocList SCGMorphism a b -> SCGMorphism a b
replaceLaw [SCGMorphism a b]
newArrows}
deleteObjectS :: (Eq a, Eq b) => SafeCompositionGraph a b -> a -> Either
(SafeCompositionGraphError a b)
(SafeCompositionGraph a b, (PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a))
deleteObjectS :: forall a b.
(Eq a, Eq b) =>
SafeCompositionGraph a b
-> a
-> Either
(SafeCompositionGraphError a b)
(SafeCompositionGraph a b,
PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a)
deleteObjectS prev :: SafeCompositionGraph a b
prev@SafeCompositionGraph{graphS :: forall a b. SafeCompositionGraph a b -> Graph a b
graphS=([a]
nodes,[Arrow a b]
arrs), lawS :: forall a b. SafeCompositionGraph a b -> CompositionLaw a b
lawS=CompositionLaw a b
l, maxCycles :: forall a b. SafeCompositionGraph a b -> Int
maxCycles=Int
nb} a
obj
| a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
elem a
obj (SafeCompositionGraph a b -> [a]
forall c m o. FiniteCategory c m o => c -> [o]
ob SafeCompositionGraph a b
prev) = (\(SafeCompositionGraph a b
cg,PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a
f) -> (\(SafeCompositionGraph a b
fcg,PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a
ffunct) -> (SafeCompositionGraph a b
fcg,PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a
ffunct PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a
-> PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a
-> PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a
forall m o. Morphism m o => m -> m -> m
@ PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a
f)) (SafeCompositionGraph a b
-> (SafeCompositionGraph a b,
PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a)
forall {b}.
Eq b =>
SafeCompositionGraph a b
-> (SafeCompositionGraph a b,
PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a)
delObj SafeCompositionGraph a b
cg)) ((SafeCompositionGraph a b,
PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a)
-> (SafeCompositionGraph a b,
PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a))
-> Either
(SafeCompositionGraphError a b)
(SafeCompositionGraph a b,
PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a)
-> Either
(SafeCompositionGraphError a b)
(SafeCompositionGraph a b,
PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Either
(SafeCompositionGraphError a b)
(SafeCompositionGraph a b,
PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a)
cgWithoutMorphs
| Bool
otherwise = SafeCompositionGraphError a b
-> Either
(SafeCompositionGraphError a b)
(SafeCompositionGraph a b,
PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a)
forall a b. a -> Either a b
Left DeleteNonExistantObjectS :: forall a b. a -> SafeCompositionGraphError a b
DeleteNonExistantObjectS {faultyObjS :: a
faultyObjS=a
obj}
where
idFunct :: PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a
idFunct = PartialFunctor :: forall c m o.
c
-> c
-> AssociationList o o
-> AssociationList m m
-> PartialFunctor c m o
PartialFunctor{srcPF :: SafeCompositionGraph a b
srcPF=SafeCompositionGraph a b
prev,tgtPF :: SafeCompositionGraph a b
tgtPF=SafeCompositionGraph a b
prev,omapPF :: AssociationList a a
omapPF=(a -> a) -> [a] -> AssociationList a a
forall a b. (a -> b) -> [a] -> AssociationList a b
functToAssocList a -> a
forall a. a -> a
id [a]
nodes,mmapPF :: AssociationList (SCGMorphism a b) (SCGMorphism a b)
mmapPF=(SCGMorphism a b -> SCGMorphism a b)
-> [SCGMorphism a b]
-> AssociationList (SCGMorphism a b) (SCGMorphism a b)
forall a b. (a -> b) -> [a] -> AssociationList a b
functToAssocList SCGMorphism a b -> SCGMorphism a b
forall a. a -> a
id (SafeCompositionGraph a b -> [SCGMorphism a b]
forall c m o.
(FiniteCategory c m o, FiniteCategory c m o, Morphism m o) =>
c -> [m]
arrows SafeCompositionGraph a b
prev)}
cgWithoutMorphs :: Either
(SafeCompositionGraphError a b)
(SafeCompositionGraph a b,
PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a)
cgWithoutMorphs = ((SafeCompositionGraph a b,
PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a)
-> SCGMorphism a b
-> Either
(SafeCompositionGraphError a b)
(SafeCompositionGraph a b,
PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a))
-> (SafeCompositionGraph a b,
PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a)
-> [SCGMorphism a b]
-> Either
(SafeCompositionGraphError a b)
(SafeCompositionGraph a b,
PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a)
forall (t :: * -> *) (m :: * -> *) b a.
(Foldable t, Monad m) =>
(b -> a -> m b) -> b -> t a -> m b
foldM (\(SafeCompositionGraph a b
cg,PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a
f) SCGMorphism a b
d -> ((\(SafeCompositionGraph a b
ncg,PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a
nf) -> (SafeCompositionGraph a b
ncg,PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a
nf PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a
-> PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a
-> PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a
forall m o. Morphism m o => m -> m -> m
@ PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a
f)) ((SafeCompositionGraph a b,
PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a)
-> (SafeCompositionGraph a b,
PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a))
-> Either
(SafeCompositionGraphError a b)
(SafeCompositionGraph a b,
PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a)
-> Either
(SafeCompositionGraphError a b)
(SafeCompositionGraph a b,
PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (SafeCompositionGraph a b
-> SCGMorphism a b
-> Either
(SafeCompositionGraphError a b)
(SafeCompositionGraph a b,
PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a)
forall a b.
(Eq a, Eq b) =>
SafeCompositionGraph a b
-> SCGMorphism a b
-> Either
(SafeCompositionGraphError a b)
(SafeCompositionGraph a b,
PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a)
deleteMorphismS SafeCompositionGraph a b
cg SCGMorphism a b
d))) (SafeCompositionGraph a b
prev,PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a
idFunct) ((SCGMorphism a b -> Bool) -> [SCGMorphism a b] -> [SCGMorphism a b]
forall a. (a -> Bool) -> [a] -> [a]
filter (SafeCompositionGraph a b -> SCGMorphism a b -> Bool
forall c m o.
(FiniteCategory c m o, Morphism m o, Eq m, Eq o) =>
c -> m -> Bool
isNotIdentity SafeCompositionGraph a b
prev) ([SCGMorphism a b] -> [SCGMorphism a b]
forall a. Eq a => [a] -> [a]
nub ((SafeCompositionGraph a b -> a -> [SCGMorphism a b]
forall c m o.
(GeneratedFiniteCategory c m o, Morphism m o) =>
c -> o -> [m]
genArFrom SafeCompositionGraph a b
prev a
obj)[SCGMorphism a b] -> [SCGMorphism a b] -> [SCGMorphism a b]
forall a. [a] -> [a] -> [a]
++(SafeCompositionGraph a b -> a -> [SCGMorphism a b]
forall c m o.
(GeneratedFiniteCategory c m o, Morphism m o) =>
c -> o -> [m]
genArTo SafeCompositionGraph a b
prev a
obj))))
delObj :: SafeCompositionGraph a b
-> (SafeCompositionGraph a b,
PartialFunctor (SafeCompositionGraph a b) (SCGMorphism a b) a)
delObj prev2 :: SafeCompositionGraph a b
prev2@SafeCompositionGraph{graphS :: forall a b. SafeCompositionGraph a b -> Graph a b
graphS=([a]
nodes2,[Arrow a b]
arrs2), lawS :: forall a b. SafeCompositionGraph a b -> CompositionLaw a b
lawS=CompositionLaw a b
l2, maxCycles :: forall a b. SafeCompositionGraph a b -> Int
maxCycles=Int
nb} = (SafeCompositionGraph a b
finalCG,
PartialFunctor :: forall c m o.
c
-> c
-> AssociationList o o
-> AssociationList m m
-> PartialFunctor c m o
PartialFunctor{srcPF :: SafeCompositionGraph a b
srcPF=SafeCompositionGraph a b
prev2,tgtPF :: SafeCompositionGraph a b
tgtPF=SafeCompositionGraph a b
finalCG,omapPF :: AssociationList a a
omapPF=(a -> a) -> [a] -> AssociationList a a
forall a b. (a -> b) -> [a] -> AssociationList a b
functToAssocList a -> a
forall a. a -> a
id (a -> [a] -> [a]
forall a. Eq a => a -> [a] -> [a]
delete a
obj [a]
nodes2),mmapPF :: AssociationList (SCGMorphism a b) (SCGMorphism a b)
mmapPF=(SCGMorphism a b -> SCGMorphism a b)
-> [SCGMorphism a b]
-> AssociationList (SCGMorphism a b) (SCGMorphism a b)
forall a b. (a -> b) -> [a] -> AssociationList a b
functToAssocList SCGMorphism a b -> SCGMorphism a b
forall a. a -> a
id ((SafeCompositionGraph a b -> [SCGMorphism a b]
forall c m o.
(FiniteCategory c m o, FiniteCategory c m o, Morphism m o) =>
c -> [m]
arrows SafeCompositionGraph a b
prev2)[SCGMorphism a b] -> [SCGMorphism a b] -> [SCGMorphism a b]
forall a. Eq a => [a] -> [a] -> [a]
\\[(SafeCompositionGraph a b -> a -> SCGMorphism a b
forall c m o. (FiniteCategory c m o, Morphism m o) => c -> o -> m
identity SafeCompositionGraph a b
prev2 a
obj)])})
where
finalCG :: SafeCompositionGraph a b
finalCG = SafeCompositionGraph :: forall a b.
Graph a b -> CompositionLaw a b -> Int -> SafeCompositionGraph a b
SafeCompositionGraph{graphS :: ([a], [Arrow a b])
graphS=(a -> [a] -> [a]
forall a. Eq a => a -> [a] -> [a]
delete a
obj [a]
nodes2,[Arrow a b]
arrs2), lawS :: CompositionLaw a b
lawS=CompositionLaw a b
l2, maxCycles :: Int
maxCycles=Int
nb}