module RandomCompositionGraph.RandomCompositionGraph
(
mkRandomCompositionGraph,
defaultMkRandomCompositionGraph
)
where
import FiniteCategory.FiniteCategory
import CompositionGraph.CompositionGraph (Graph(..), CGMorphism(..), CompositionLaw(..), CompositionGraph(..), Arrow(..), mkCompositionGraph, isGen, isComp)
import System.Random (RandomGen, uniformR)
import Data.Maybe (isNothing, fromJust)
import Utils.AssociationList
import Utils.Sample
import Utils.Tuple
compositeMorphisms :: (Eq a, Eq b, Show a) => CompositionGraph a b -> [CGMorphism a b]
compositeMorphisms :: forall a b.
(Eq a, Eq b, Show a) =>
CompositionGraph a b -> [CGMorphism a b]
compositeMorphisms CompositionGraph a b
c = [CGMorphism a b
g CGMorphism a b -> CGMorphism a b -> CGMorphism a b
forall m o. Morphism m o => m -> m -> m
@ CGMorphism a b
f | CGMorphism a b
f <- CompositionGraph a b -> [CGMorphism a b]
forall c m o.
(GeneratedFiniteCategory c m o, GeneratedFiniteCategory c m o,
Morphism m o) =>
c -> [m]
genArrows CompositionGraph a b
c, CGMorphism a b
g <- CompositionGraph a b -> a -> [CGMorphism a b]
forall c m o.
(GeneratedFiniteCategory c m o, Morphism m o) =>
c -> o -> [m]
genArFrom CompositionGraph a b
c (CGMorphism a b -> a
forall m o. Morphism m o => m -> o
target CGMorphism a b
f), Bool -> Bool
not (CGMorphism a b -> [CGMorphism a b] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
elem (CGMorphism a b
g CGMorphism a b -> CGMorphism a b -> CGMorphism a b
forall m o. Morphism m o => m -> m -> m
@ CGMorphism a b
f) (CompositionGraph a b -> a -> a -> [CGMorphism a b]
forall c m o.
(GeneratedFiniteCategory c m o, Morphism m o) =>
c -> o -> o -> [m]
genAr CompositionGraph a b
c (CGMorphism a b -> a
forall m o. Morphism m o => m -> o
source CGMorphism a b
f) (CGMorphism a b -> a
forall m o. Morphism m o => m -> o
target CGMorphism a b
g)))]
mergeNodes :: (Eq a) => CompositionGraph a b -> a -> a -> CompositionGraph a b
mergeNodes :: forall a b.
Eq a =>
CompositionGraph a b -> a -> a -> CompositionGraph a b
mergeNodes cg :: CompositionGraph a b
cg@CompositionGraph{graph :: forall a b. CompositionGraph a b -> Graph a b
graph=g :: Graph a b
g@([a]
objs,[Arrow a b]
ars),law :: forall a b. CompositionGraph a b -> CompositionLaw a b
law=CompositionLaw a b
l} a
s a
t
| Bool -> Bool
not (a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
elem a
s [a]
objs) = [Char] -> CompositionGraph a b
forall a. HasCallStack => [Char] -> a
error [Char]
"mapped but not in rcg."
| Bool -> Bool
not (a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
elem a
t [a]
objs) = [Char] -> CompositionGraph a b
forall a. HasCallStack => [Char] -> a
error [Char]
"mapped to but not in rcg."
| a
s a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
t = CompositionGraph a b
cg
| Bool
otherwise = CompositionGraph :: forall a b. Graph a b -> CompositionLaw a b -> CompositionGraph a b
CompositionGraph {graph :: Graph a b
graph=((a -> Bool) -> [a] -> [a]
forall a. (a -> Bool) -> [a] -> [a]
filter (a -> a -> Bool
forall a. Eq a => a -> a -> Bool
/=a
s) [a]
objs,Arrow a b -> Arrow a b
forall {c}. (a, a, c) -> (a, a, c)
replaceArrow (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]
ars), law :: CompositionLaw a b
law=CompositionLaw a b
newLaw}
where
replace :: a -> a
replace a
x = if a
x a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
s then a
t else a
x
replaceArrow :: (a, a, c) -> (a, a, c)
replaceArrow (a
s1,a
t1,c
l1) = (a -> a
replace a
s1, a -> a
replace a
t1, c
l1)
newLaw :: CompositionLaw a b
newLaw = (\([Arrow a b]
k,[Arrow a b]
v) -> (Arrow a b -> Arrow a b
forall {c}. (a, a, c) -> (a, a, c)
replaceArrow (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]
k, Arrow a b -> Arrow a b
forall {c}. (a, a, c) -> (a, a, c)
replaceArrow (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]
v)) (([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
mergeMorphisms :: (Eq a, Eq b) => CompositionGraph a b -> CGMorphism a b -> CGMorphism a b -> CompositionGraph a b
mergeMorphisms :: forall a b.
(Eq a, Eq b) =>
CompositionGraph a b
-> CGMorphism a b -> CGMorphism a b -> CompositionGraph a b
mergeMorphisms cg :: CompositionGraph a b
cg@CompositionGraph{graph :: forall a b. CompositionGraph a b -> Graph a b
graph=Graph a b
g,law :: forall a b. CompositionGraph a b -> CompositionLaw a b
law=CompositionLaw a b
l} s :: CGMorphism a b
s@CGMorphism{path :: forall a b. CGMorphism a b -> Path a b
path=p1 :: Path a b
p1@(a
s1,RawPath a b
rp1,a
t1),compositionLaw :: forall a b. CGMorphism a b -> CompositionLaw a b
compositionLaw=CompositionLaw a b
l1} t :: CGMorphism a b
t@CGMorphism{path :: forall a b. CGMorphism a b -> Path a b
path=p2 :: Path a b
p2@(a
s2,RawPath a b
rp2,a
t2),compositionLaw :: forall a b. CGMorphism a b -> CompositionLaw a b
compositionLaw=CompositionLaw a b
l2}
| (CGMorphism a b -> Bool
forall a b. Eq a => CGMorphism a b -> Bool
isGen CGMorphism a b
s) = [Char] -> CompositionGraph a b
forall a. HasCallStack => [Char] -> a
error [Char]
"Generator at the start of a merge"
| (CGMorphism a b -> Bool
forall a b. Eq a => CGMorphism a b -> Bool
isComp CGMorphism a b
t) = [Char] -> CompositionGraph a b
forall a. HasCallStack => [Char] -> a
error [Char]
"Composite at the end of a merge"
| a
s1 a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
t1 = CompositionGraph a b -> a -> a -> CompositionGraph a b
forall a b.
Eq a =>
CompositionGraph a b -> a -> a -> CompositionGraph a b
mergeNodes CompositionGraph :: forall a b. Graph a b -> CompositionLaw a b -> CompositionGraph a b
CompositionGraph{graph :: Graph a b
graph=Graph a b
g, law :: CompositionLaw a b
law=CompositionLaw a b
newLaw} (CGMorphism a b -> a
forall m o. Morphism m o => m -> o
source CGMorphism a b
s) (CGMorphism a b -> a
forall m o. Morphism m o => m -> o
source CGMorphism a b
t)
| a
s1 a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
t2 = CompositionGraph a b -> a -> a -> CompositionGraph a b
forall a b.
Eq a =>
CompositionGraph a b -> a -> a -> CompositionGraph a b
mergeNodes (CompositionGraph a b -> a -> a -> CompositionGraph a b
forall a b.
Eq a =>
CompositionGraph a b -> a -> a -> CompositionGraph a b
mergeNodes CompositionGraph :: forall a b. Graph a b -> CompositionLaw a b -> CompositionGraph a b
CompositionGraph{graph :: Graph a b
graph=Graph a b
g, law :: CompositionLaw a b
law=CompositionLaw a b
newLaw} (CGMorphism a b -> a
forall m o. Morphism m o => m -> o
source CGMorphism a b
s) (CGMorphism a b -> a
forall m o. Morphism m o => m -> o
source CGMorphism a b
t)) (CGMorphism a b -> a
forall m o. Morphism m o => m -> o
target CGMorphism a b
s) (CGMorphism a b -> a
forall m o. Morphism m o => m -> o
source CGMorphism a b
t)
| Bool
otherwise = CompositionGraph a b -> a -> a -> CompositionGraph a b
forall a b.
Eq a =>
CompositionGraph a b -> a -> a -> CompositionGraph a b
mergeNodes (CompositionGraph a b -> a -> a -> CompositionGraph a b
forall a b.
Eq a =>
CompositionGraph a b -> a -> a -> CompositionGraph a b
mergeNodes CompositionGraph :: forall a b. Graph a b -> CompositionLaw a b -> CompositionGraph a b
CompositionGraph{graph :: Graph a b
graph=Graph a b
g, law :: CompositionLaw a b
law=CompositionLaw a b
newLaw} (CGMorphism a b -> a
forall m o. Morphism m o => m -> o
source CGMorphism a b
s) (CGMorphism a b -> a
forall m o. Morphism m o => m -> o
source CGMorphism a b
t)) (CGMorphism a b -> a
forall m o. Morphism m o => m -> o
target CGMorphism a b
s) (CGMorphism a b -> a
forall m o. Morphism m o => m -> o
target CGMorphism a b
t) where
newLaw :: CompositionLaw a b
newLaw = (((a, a, b) -> (a, a, b)
forall {c}. (a, a, c) -> (a, a, c)
replaceArrow ((a, a, b) -> (a, a, b)) -> RawPath a b -> RawPath a b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> RawPath a b
rp1,(a, a, b) -> (a, a, b)
forall {c}. (a, a, c) -> (a, a, c)
replaceArrow ((a, a, b) -> (a, a, b)) -> RawPath a b -> RawPath a b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> RawPath a b
rp2)(RawPath a b, RawPath a b)
-> CompositionLaw a b -> CompositionLaw a b
forall a. a -> [a] -> [a]
:((\(RawPath a b
k,RawPath a b
v) -> ((a, a, b) -> (a, a, b)
forall {c}. (a, a, c) -> (a, a, c)
replaceArrow ((a, a, b) -> (a, a, b)) -> RawPath a b -> RawPath a b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> RawPath a b
k, (a, a, b) -> (a, a, b)
forall {c}. (a, a, c) -> (a, a, c)
replaceArrow ((a, a, b) -> (a, a, b)) -> RawPath a b -> RawPath a b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> RawPath a b
v)) ((RawPath a b, RawPath a b) -> (RawPath a b, RawPath a b))
-> CompositionLaw a b -> CompositionLaw a b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> CompositionLaw a b
l))
where
replace :: a -> a
replace a
x = if a
x a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
s1 then a
s2 else (if a
x a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
t1 then a
t2 else a
x)
replaceArrow :: (a, a, c) -> (a, a, c)
replaceArrow (a
s3,a
t3,c
l3) = (a -> a
replace a
s3, a -> a
replace a
t3, c
l3)
checkAssociativity :: (Eq a, Eq b, Show a) => CompositionGraph a b -> Bool
checkAssociativity :: forall a b. (Eq a, Eq b, Show a) => CompositionGraph a b -> Bool
checkAssociativity CompositionGraph a b
cg = (Bool -> Bool -> Bool) -> Bool -> [Bool] -> Bool
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr Bool -> Bool -> Bool
(&&) Bool
True [(CGMorphism a b, CGMorphism a b, CGMorphism a b) -> Bool
forall {m} {o}. (Morphism m o, Eq m) => (m, m, m) -> Bool
checkTriplet (CGMorphism a b
f,CGMorphism a b
g,CGMorphism a b
h) | CGMorphism a b
f <- CompositionGraph a b -> [CGMorphism a b]
forall c m o.
(GeneratedFiniteCategory c m o, GeneratedFiniteCategory c m o,
Morphism m o) =>
c -> [m]
genArrows CompositionGraph a b
cg, CGMorphism a b
g <- CompositionGraph a b -> a -> [CGMorphism a b]
forall c m o.
(GeneratedFiniteCategory c m o, Morphism m o) =>
c -> o -> [m]
genArFrom CompositionGraph a b
cg (CGMorphism a b -> a
forall m o. Morphism m o => m -> o
target CGMorphism a b
f), CGMorphism a b
h <- CompositionGraph a b -> a -> [CGMorphism a b]
forall c m o.
(GeneratedFiniteCategory c m o, Morphism m o) =>
c -> o -> [m]
genArFrom CompositionGraph a b
cg (CGMorphism a b -> a
forall m o. Morphism m o => m -> o
target CGMorphism a b
g)]
where
checkTriplet :: (m, m, m) -> Bool
checkTriplet (m
f,m
g,m
h) = (m
h m -> m -> m
forall m o. Morphism m o => m -> m -> m
@ m
g) m -> m -> m
forall m o. Morphism m o => m -> m -> m
@ m
f m -> m -> Bool
forall a. Eq a => a -> a -> Bool
== m
h m -> m -> m
forall m o. Morphism m o => m -> m -> m
@ (m
g m -> m -> m
forall m o. Morphism m o => m -> m -> m
@ m
f)
identifyCompositeToGen :: (RandomGen g, Eq a, Eq b, Show a) => CompositionGraph a b -> Int -> g -> (Maybe (CompositionGraph a b), g)
identifyCompositeToGen :: forall g a b.
(RandomGen g, Eq a, Eq b, Show a) =>
CompositionGraph a b
-> Int -> g -> (Maybe (CompositionGraph a b), g)
identifyCompositeToGen CompositionGraph a b
_ Int
0 g
rGen = (Maybe (CompositionGraph a b)
forall a. Maybe a
Nothing, g
rGen)
identifyCompositeToGen CompositionGraph a b
cg Int
n g
rGen
| Bool -> Bool
not (CompositionGraph a b -> Bool
forall a b. (Eq a, Eq b, Show a) => CompositionGraph a b -> Bool
checkAssociativity CompositionGraph a b
cg) = (Maybe (CompositionGraph a b)
forall a. Maybe a
Nothing, g
rGen)
| [CGMorphism a b] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [CGMorphism a b]
compositeMorphs = (CompositionGraph a b -> Maybe (CompositionGraph a b)
forall a. a -> Maybe a
Just CompositionGraph a b
cg, g
rGen)
| Bool
otherwise = if Maybe (CompositionGraph a b) -> Bool
forall a. Maybe a -> Bool
isNothing Maybe (CompositionGraph a b)
newCG then CompositionGraph a b
-> Int -> g -> (Maybe (CompositionGraph a b), g)
forall g a b.
(RandomGen g, Eq a, Eq b, Show a) =>
CompositionGraph a b
-> Int -> g -> (Maybe (CompositionGraph a b), g)
identifyCompositeToGen CompositionGraph a b
cg (Int
n Int -> Int -> Int
forall a. Integral a => a -> a -> a
`div` Int
2) g
newGen2 else (Maybe (CompositionGraph a b)
newCG, g
newGen2)
where
compositeMorphs :: [CGMorphism a b]
compositeMorphs = CompositionGraph a b -> [CGMorphism a b]
forall a b.
(Eq a, Eq b, Show a) =>
CompositionGraph a b -> [CGMorphism a b]
compositeMorphisms CompositionGraph a b
cg
morphToMap :: CGMorphism a b
morphToMap = ([CGMorphism a b] -> CGMorphism a b
forall a. [a] -> a
head [CGMorphism a b]
compositeMorphs)
(CGMorphism a b
selectedGen,g
newGen1) = if (CGMorphism a b -> a
forall m o. Morphism m o => m -> o
source CGMorphism a b
morphToMap a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== CGMorphism a b -> a
forall m o. Morphism m o => m -> o
target CGMorphism a b
morphToMap) then [CGMorphism a b] -> g -> (CGMorphism a b, g)
forall g a. RandomGen g => [a] -> g -> (a, g)
pickOne [CGMorphism a b
fs | a
obj <- CompositionGraph a b -> [a]
forall c m o. FiniteCategory c m o => c -> [o]
ob CompositionGraph a b
cg, CGMorphism a b
fs <- (CompositionGraph a b -> a -> a -> [CGMorphism a b]
forall c m o.
(GeneratedFiniteCategory c m o, Morphism m o) =>
c -> o -> o -> [m]
genAr CompositionGraph a b
cg a
obj a
obj)] g
rGen else [CGMorphism a b] -> g -> (CGMorphism a b, g)
forall g a. RandomGen g => [a] -> g -> (a, g)
pickOne (CompositionGraph a b -> [CGMorphism a b]
forall c m o.
(GeneratedFiniteCategory c m o, GeneratedFiniteCategory c m o,
Morphism m o) =>
c -> [m]
genArrows CompositionGraph a b
cg) g
rGen
(Maybe (CompositionGraph a b)
newCG,g
newGen2) = CompositionGraph a b
-> Int -> g -> (Maybe (CompositionGraph a b), g)
forall g a b.
(RandomGen g, Eq a, Eq b, Show a) =>
CompositionGraph a b
-> Int -> g -> (Maybe (CompositionGraph a b), g)
identifyCompositeToGen (CompositionGraph a b
-> CGMorphism a b -> CGMorphism a b -> CompositionGraph a b
forall a b.
(Eq a, Eq b) =>
CompositionGraph a b
-> CGMorphism a b -> CGMorphism a b -> CompositionGraph a b
mergeMorphisms CompositionGraph a b
cg CGMorphism a b
morphToMap CGMorphism a b
selectedGen) Int
n g
newGen1
monoidificationAttempt :: (RandomGen g, Eq a, Eq b, Show a) => CompositionGraph a b -> Int -> g -> (CompositionGraph a b, g, [a])
monoidificationAttempt :: forall g a b.
(RandomGen g, Eq a, Eq b, Show a) =>
CompositionGraph a b -> Int -> g -> (CompositionGraph a b, g, [a])
monoidificationAttempt CompositionGraph a b
cg Int
p g
g = if Maybe (CompositionGraph a b) -> Bool
forall a. Maybe a -> Bool
isNothing Maybe (CompositionGraph a b)
result then (CompositionGraph a b
cg,g
finalGen,[]) else (Maybe (CompositionGraph a b) -> CompositionGraph a b
forall a. HasCallStack => Maybe a -> a
fromJust Maybe (CompositionGraph a b)
result, g
finalGen, [a
s,a
t])
where
([a
s,a
t],g
newGen) = if (([a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length (CompositionGraph a b -> [a]
forall c m o. FiniteCategory c m o => c -> [o]
ob CompositionGraph a b
cg)) Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
1) then [a] -> Int -> g -> ([a], g)
forall g a. RandomGen g => [a] -> Int -> g -> ([a], g)
sample (CompositionGraph a b -> [a]
forall c m o. FiniteCategory c m o => c -> [o]
ob CompositionGraph a b
cg) Int
2 g
g else (CompositionGraph a b -> [a]
forall c m o. FiniteCategory c m o => c -> [o]
ob CompositionGraph a b
cg [a] -> [a] -> [a]
forall a. [a] -> [a] -> [a]
++ CompositionGraph a b -> [a]
forall c m o. FiniteCategory c m o => c -> [o]
ob CompositionGraph a b
cg,g
g)
newCG :: CompositionGraph a b
newCG = CompositionGraph a b -> a -> a -> CompositionGraph a b
forall a b.
Eq a =>
CompositionGraph a b -> a -> a -> CompositionGraph a b
mergeNodes CompositionGraph a b
cg a
s a
t
(Maybe (CompositionGraph a b)
result,g
finalGen) = CompositionGraph a b
-> Int -> g -> (Maybe (CompositionGraph a b), g)
forall g a b.
(RandomGen g, Eq a, Eq b, Show a) =>
CompositionGraph a b
-> Int -> g -> (Maybe (CompositionGraph a b), g)
identifyCompositeToGen CompositionGraph a b
newCG Int
p g
newGen
initRandomCG :: Int -> CompositionGraph Int Int
initRandomCG :: Int -> CompositionGraph Int Int
initRandomCG Int
n = CompositionGraph :: forall a b. Graph a b -> CompositionLaw a b -> CompositionGraph a b
CompositionGraph{graph :: Graph Int Int
graph=([Int
0..Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1],[((Int
iInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
i),(Int
iInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
iInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1), Int
i) | Int
i <- [Int
0..Int
n]]),law :: CompositionLaw Int Int
law=[]}
mkRandomCompositionGraph :: (RandomGen g) => Int
-> Int
-> Int
-> g
-> (CompositionGraph Int Int, g)
mkRandomCompositionGraph :: forall g.
RandomGen g =>
Int -> Int -> Int -> g -> (CompositionGraph Int Int, g)
mkRandomCompositionGraph Int
nbAr Int
nbAttempts Int
perseverance g
gen = CompositionGraph Int Int
-> Int -> Int -> g -> (CompositionGraph Int Int, g)
forall {t} {t} {a} {b}.
(Eq t, Num t, RandomGen t, Eq a, Eq b, Show a) =>
CompositionGraph a b -> t -> Int -> t -> (CompositionGraph a b, t)
attempt (Int -> CompositionGraph Int Int
initRandomCG Int
nbAr) Int
nbAttempts Int
perseverance g
gen
where
attempt :: CompositionGraph a b -> t -> Int -> t -> (CompositionGraph a b, t)
attempt CompositionGraph a b
cg t
0 Int
_ t
gen = (CompositionGraph a b
cg, t
gen)
attempt CompositionGraph a b
cg t
n Int
p t
gen = CompositionGraph a b -> t -> Int -> t -> (CompositionGraph a b, t)
attempt CompositionGraph a b
newCG (t
nt -> t -> t
forall a. Num a => a -> a -> a
-t
1) Int
p t
newGen
where
(CompositionGraph a b
newCG, t
newGen,[a]
_) = (CompositionGraph a b -> Int -> t -> (CompositionGraph a b, t, [a])
forall g a b.
(RandomGen g, Eq a, Eq b, Show a) =>
CompositionGraph a b -> Int -> g -> (CompositionGraph a b, g, [a])
monoidificationAttempt CompositionGraph a b
cg Int
p t
gen)
defaultMkRandomCompositionGraph :: (RandomGen g) => g -> (CompositionGraph Int Int, g)
defaultMkRandomCompositionGraph :: forall g. RandomGen g => g -> (CompositionGraph Int Int, g)
defaultMkRandomCompositionGraph g
g1 = Int -> Int -> Int -> g -> (CompositionGraph Int Int, g)
forall g.
RandomGen g =>
Int -> Int -> Int -> g -> (CompositionGraph Int Int, g)
mkRandomCompositionGraph Int
nbArrows (Int -> Int -> Int
forall a. Ord a => a -> a -> a
min Int
nbAttempts Int
20) Int
4 g
g3
where
(Int
nbArrows, g
g2) = (Int, Int) -> g -> (Int, g)
forall g a. (RandomGen g, UniformRange a) => (a, a) -> g -> (a, g)
uniformR (Int
1,Int
20) g
g1
(Int
nbAttempts, g
g3) = (Int, Int) -> g -> (Int, g)
forall g a. (RandomGen g, UniformRange a) => (a, a) -> g -> (a, g)
uniformR (Int
0,Int
nbArrowsInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
nbArrows) g
g2