La semana en Exercitium (10 de junio de 2023)
Esta semana he publicado en Exercitium las soluciones de los siguientes problemas sobre el tipo abstracto de datos de los grafos
- 1. Generadores de grafos
 - 2. Grado de un vértice
 - 3. Lema del apretón de manos
 - 4. Grafos regulares
 - 5. Grafos k-regulares
 
A continuación se muestran las soluciones.
1. Generadores de grafos
Definir un generador de grafos para comprobar propiedades de grafos con QuickCheck y hacer el tipo de los Grafos un subtipo de Arbitrary.
Usando el generador, con QuickCheck que para cualquier grafo g, las sumas de los grados positivos y la de los grados negativos de los vértices de g son iguales.
Soluciones
A continuación se muestran las soluciones en Haskell y las soluciones en Python.
La definición del generador es
| 
					 1 2 3 4 5 6 7 8 9 10 11 12 13 14 15 16 17 18 19 20 21 22 23 24 25 26 27 28 29 30 31 32 33 34 35 36 37 38 39 40 41 42 43 44 45 46 47 48 49 50 51 52 53 54 55 56 57 58 59 60 61 62 63 64 65 66 67 68 69 70 71 72 73 74 75 76 77 78 79 80 81 82 83 84 85  | 
						{-# LANGUAGE FlexibleInstances #-} {-# OPTIONS_GHC -fno-warn-orphans #-} module TAD.GrafoGenerador where import TAD.Grafo (Grafo, Orientacion (D, ND), creaGrafo) import Test.QuickCheck (Arbitrary, Gen, arbitrary, choose, vectorOf) -- (generaGND n ps) es el grafo completo de orden n tal que los pesos -- están determinados por ps. Por ejemplo, --    λ> generaGND 3 [4,2,5] --    G ND ([1,2,3],[((1,2),4),((1,3),2),((2,3),5)]) --    λ> generaGND 3 [4,-2,5] --    G ND ([1,2,3],[((1,2),4),((2,3),5)]) generaGND :: Int -> [Int] -> Grafo Int Int generaGND n ps  = creaGrafo ND (1,n) l3   where l1 = [(x,y) | x <- [1..n], y <- [1..n], x < y]         l2 = zip l1 ps         l3 = [(x,y,z) | ((x,y),z) <- l2, z > 0] -- (generaGD n ps) es el grafo completo de orden n tal que los pesos -- están determinados por ps. Por ejemplo, --    λ> generaGD 3 [4,2,5] --    G D ([1,2,3],[((1,1),4),((1,2),2),((1,3),5)]) --    λ> generaGD 3 [4,2,5,3,7,9,8,6] --    G D ([1,2,3],[((1,1),4),((1,2),2),((1,3),5), --                  ((2,1),3),((2,2),7),((2,3),9), --                  ((3,1),8),((3,2),6)]) generaGD :: Int -> [Int] -> Grafo Int Int generaGD n ps = creaGrafo D (1,n) l3   where l1 = [(x,y) | x <- [1..n], y <- [1..n]]         l2 = zip l1 ps         l3 = [(x,y,z) | ((x,y),z) <- l2, z > 0] -- genGD es un generador de grafos dirigidos. Por ejemplo, --    λ> sample genGD --    G D ([1],[]) --    G D ([1,2],[((1,1),5),((2,1),4)]) --    G D ([1,2],[((1,1),3),((1,2),3)]) --    G D ([1,2,3,4,5,6],[]) --    G D ([1,2],[((2,2),16)]) --    ... genGD :: Gen (Grafo Int Int) genGD = do   n <- choose (1,10)   xs <- vectorOf (n*n) arbitrary   return (generaGD n xs) -- genGND es un generador de grafos dirigidos. Por ejemplo, --    λ> sample genGND --    G ND ([1,2,3,4,5,6,7,8],[]) --    G ND ([1],[]) --    G ND ([1,2,3,4,5],[((1,2),2),((2,3),5),((3,4),5),((3,5),5)]) --    G ND ([1,2,3,4,5],[((1,2),6),((1,3),5),((1,5),1),((3,5),9),((4,5),6)]) --    G ND ([1,2,3,4],[((1,2),5),((3,4),2)]) --    G ND ([1,2,3],[]) --    G ND ([1,2,3,4],[((1,2),5),((1,4),14),((2,4),10)]) --    G ND ([1,2,3,4,5],[((1,5),8),((4,5),5)]) --    G ND ([1,2,3,4],[((1,2),1),((1,4),4),((2,3),4),((3,4),5)]) --    G ND ([1,2,3],[((1,2),8),((1,3),8),((2,3),3)]) --    ... genGND :: Gen (Grafo Int Int) genGND = do   n <- choose (1,10)   xs <- vectorOf (n*n) arbitrary   return (generaGND n xs) -- genG es un generador de grafos. Por ejemplo, --    λ> sample genG --    G ND ([1,2,3,4,5,6],[]) --    G D ([1],[((1,1),2)]) --    G D ([1,2],[((1,1),9)]) --    ... genG :: Gen (Grafo Int Int) genG = do   d <- choose (True,False)   n <- choose (1,10)   xs <- vectorOf (n*n) arbitrary   if d then return (generaGD n xs)        else return (generaGND n xs) -- Los grafos está contenido en la clase de los objetos generables -- aleatoriamente. instance Arbitrary (Grafo Int Int) where   arbitrary = genG  | 
					
La comprobación de la propiedad es
| 
					 1 2 3 4 5 6 7 8 9 10 11 12 13 14 15 16  | 
						module Grafo_Propiedades_de_grados_positivos_y_negativos where import TAD.Grafo (Grafo, nodos) import TAD.GrafoGenerador import Grafo_Grados_positivos_y_negativos (gradoPos, gradoNeg) import Test.QuickCheck -- La propiedad es prop_sumaGrados :: Grafo Int Int -> Bool prop_sumaGrados g =   sum [gradoPos g v | v <- vs] == sum [gradoNeg g v | v <- vs]   where vs = nodos g -- La comprobación es --    λ> quickCheck prop_sumaGrados --    +++ OK, passed 100 tests.  | 
					
La definición del generador es
| 
					 1 2 3 4 5 6 7 8 9 10 11 12 13 14 15 16 17 18 19 20 21 22 23 24 25 26 27 28 29 30 31 32 33 34 35 36 37 38 39 40 41 42 43 44 45 46 47 48 49 50 51 52 53 54 55 56 57 58 59 60 61  | 
						from hypothesis import strategies as st from hypothesis.strategies import composite from src.TAD.Grafo import Orientacion, creaGrafo_ # Generador de aristas. Por ejemplo, #    >>> gen_aristas(5).example() #    [(2, 5), (4, 5), (1, 2), (2, 3), (4, 1)] #    >>> gen_aristas(5).example() #    [(3, 4)] #    >>> gen_aristas(5).example() #    [(5, 3), (3, 2), (1, 3), (5, 2)] @composite def gen_aristas(draw, n):     as_ = draw(st.lists(st.tuples(st.integers(1,n),                                   st.integers(1,n)),                         unique=True))     return as_ # Generador de grafos no dirigidos. Por ejemplo, #    >>> gen_grafoND().example() #    G ND ([1, 2, 3, 4, 5], [(1, 4), (5, 5)]) #    >>> gen_grafoND().example() #    G ND ([1], []) #    >>> gen_grafoND().example() #    G ND ([1, 2, 3, 4, 5, 6, 7, 8], [(7, 7)]) #    >>> gen_grafoND().example() #    G ND ([1, 2, 3, 4, 5, 6], [(1, 3), (2, 4), (3, 3), (3, 5)]) @composite def gen_grafoND(draw):     n = draw(st.integers(1,10))     as_ = [(x, y) for (x, y ) in draw(gen_aristas(n)) if x <= y]     return creaGrafo_(Orientacion.ND, (1,n), as_) # Generador de grafos dirigidos. Por ejemplo, #    >>> gen_grafoD().example() #    G D ([1, 2, 3, 4], [(3, 3), (4, 1)]) #    >>> gen_grafoD().example() #    G D ([1, 2], [(1, 1), (2, 1), (2, 2)]) #    >>> gen_grafoD().example() #    G D ([1, 2], []) @composite def gen_grafoD(draw):     n = draw(st.integers(1,10))     as_ = draw(gen_aristas(n))     return creaGrafo_(Orientacion.D, (1,n), as_) # Generador de grafos. Por ejemplo, #    >>> gen_grafo().example() #    G ND ([1, 2, 3, 4, 5, 6, 7], [(1, 3)]) #    >>> gen_grafo().example() #    G D ([1], []) #    >>> gen_grafo().example() #    G D ([1, 2, 3, 4, 5, 6, 7], [(1, 3), (3, 4), (5, 5)]) @composite def gen_grafo(draw):     o = draw(st.sampled_from([Orientacion.D, Orientacion.ND]))     if o == Orientacion.ND:         return draw(gen_grafoND())     return draw(gen_grafoD())  | 
					
La comprobación de la propiedad es
| 
					 1 2 3 4 5 6 7 8 9 10 11 12 13 14 15 16  | 
						from hypothesis import given from src.Grafo_Grados_positivos_y_negativos import gradoNeg, gradoPos from src.TAD.Grafo import nodos from src.TAD.GrafoGenerador import gen_grafo # La propiedad es @given(gen_grafo()) def test_sumaGrados(g):     vs = nodos(g)     assert sum((gradoPos(g, v) for v in vs)) == sum((gradoNeg(g, v) for v in vs)) # La comprobación es #    src> poetry run pytest -q Grafo_Propiedades_de_grados_positivos_y_negativos.py #    1 passed in 0.31s  | 
					
2. Grado de un vértice
El grado de un vértice v de un grafo dirigido g, es el número aristas de g que contiene a v. Si g es no dirigido, el grado de un vértice v es el número de aristas incidentes en v, teniendo en cuenta que los lazos se cuentan dos veces.
Usando el tipo abstracto de datos de los grafos, definir las funciones,
| 
					 1  | 
						   grado :: (Ix v,Num p) => Grafo v p -> v -> Int  | 
					
tal que grado g v es el grado del vértice v en el grafo g. Por ejemplo,
| 
					 1 2 3 4 5 6 7 8 9 10 11 12 13 14 15  | 
						   g1 = creaGrafo' ND (1,5) [(1,2),(1,3),(1,5),(2,4),(2,5),(3,4),(3,5),(4,5)]    g2 = creaGrafo' D  (1,5) [(1,2),(1,3),(1,5),(2,4),(2,5),(4,3),(4,5)]    g3 = creaGrafo' D  (1,3) [(1,2),(2,2),(3,1),(3,2)]    g4 = creaGrafo' D  (1,1) [(1,1)]    g5 = creaGrafo' ND (1,3) [(1,2),(1,3),(2,3),(3,3)]    g6 = creaGrafo' D  (1,3) [(1,2),(1,3),(2,3),(3,3)]    grado g1 5 ==  4    grado g2 5 ==  3    grado g2 1 ==  3    grado g3 2 ==  4    grado g3 1 ==  2    grado g3 3 ==  2    grado g4 1 ==  2    grado g6 3 ==  4    grado g6 3 ==  4  | 
					
Comprobar con QuickCheck que en todo grafo, el número de nodos de grado impar es par.
Soluciones
A continuación se muestran las soluciones en Haskell y las soluciones en Python.
| 
					 1 2 3 4 5 6 7 8 9 10 11 12 13 14 15 16 17 18 19 20 21 22 23 24 25 26 27 28 29 30 31 32 33 34 35 36 37 38 39 40 41 42 43 44 45 46 47 48 49 50 51 52 53 54 55 56 57 58 59 60 61 62 63 64 65 66 67 68 69 70 71 72 73  | 
						module Grafo_Grado_de_un_vertice where import TAD.Grafo (Grafo, Orientacion (D, ND), dirigido, nodos, creaGrafo') import Data.Ix (Ix) import Grafo_Lazos_de_un_grafo (lazos) import Grafo_Incidentes_de_un_vertice (incidentes) import Grafo_Grados_positivos_y_negativos (gradoPos, gradoNeg) import Test.Hspec (Spec, hspec, it, shouldBe) grado :: (Ix v,Num p) => Grafo v p -> v -> Int grado g v | dirigido g           = gradoNeg g v + gradoPos g v           | (v,v) `elem` lazos g = length (incidentes g v) + 1           | otherwise            = length (incidentes g v) -- La propiedad es prop_numNodosGradoImpar :: Grafo Int Int -> Bool prop_numNodosGradoImpar g =   even (length [v | v <- nodos g, odd (grado g v)]) -- La comprobación es --    λ> quickCheck prop_numNodosGradoImpar --    +++ OK, passed 100 tests. -- Verificación -- ============ verifica :: IO () verifica = hspec spec spec :: Spec spec = do   it "e1" $     grado g1 5 `shouldBe`  4   it "e2" $     grado g2 5 `shouldBe`  3   it "e3" $     grado g2 1 `shouldBe`  3   it "e4" $     grado g3 2 `shouldBe`  4   it "e5" $     grado g3 1 `shouldBe`  2   it "e6" $     grado g3 3 `shouldBe`  2   it "e7" $     grado g4 1 `shouldBe`  2   it "e8" $     grado g5 3 `shouldBe`  4   it "e9" $     grado g6 3 `shouldBe`  4   where     g1, g2, g3, g4, g5, g6 :: Grafo Int Int     g1 = creaGrafo' ND (1,5) [(1,2),(1,3),(1,5),(2,4),(2,5),(3,4),(3,5),(4,5)]     g2 = creaGrafo' D  (1,5) [(1,2),(1,3),(1,5),(2,4),(2,5),(4,3),(4,5)]     g3 = creaGrafo' D  (1,3) [(1,2),(2,2),(3,1),(3,2)]     g4 = creaGrafo' D  (1,1) [(1,1)]     g5 = creaGrafo' ND (1,3) [(1,2),(1,3),(2,3),(3,3)]     g6 = creaGrafo' D  (1,3) [(1,2),(1,3),(2,3),(3,3)] -- La verificación es --    λ> verifica -- --    e1 --    e2 --    e3 --    e4 --    e5 --    e6 --    e7 --    e8 --    e9 -- --    Finished in 0.0015 seconds --    9 examples, 0 failures  | 
					
| 
					 1 2 3 4 5 6 7 8 9 10 11 12 13 14 15 16 17 18 19 20 21 22 23 24 25 26 27 28 29 30 31 32 33 34 35 36 37 38 39 40 41 42 43 44 45 46 47 48 49 50 51 52 53 54 55 56  | 
						from hypothesis import given from src.Grafo_Grados_positivos_y_negativos import gradoNeg, gradoPos from src.Grafo_Incidentes_de_un_vertice import incidentes from src.Grafo_Lazos_de_un_grafo import lazos from src.TAD.Grafo import (Grafo, Orientacion, Vertice, creaGrafo_, dirigido,                            nodos) from src.TAD.GrafoGenerador import gen_grafo def grado(g: Grafo, v: Vertice) -> int:     if dirigido(g):         return gradoNeg(g, v) + gradoPos(g, v)     if (v, v) in lazos(g):         return len(incidentes(g, v)) + 1     return len(incidentes(g, v)) # La propiedad esp @given(gen_grafo()) def test_grado1(g):     assert len([v for v in nodos(g) if grado(g, v) % 2 == 1]) % 2 == 0 # La comprobación es #    src> poetry run pytest -q Grafo_Grado_de_un_vertice.py #    1 passed in 0.36s # Verificación # ============ def test_grado() -> None:     g1 = creaGrafo_(Orientacion.ND, (1,5),                     [(1,2),(1,3),(1,5),(2,4),(2,5),(3,4),(3,5),(4,5)])     g2 = creaGrafo_(Orientacion.D, (1,5),                     [(1,2),(1,3),(1,5),(2,4),(2,5),(4,3),(4,5)])     g3 = creaGrafo_(Orientacion.D, (1,3),                     [(1,2),(2,2),(3,1),(3,2)])     g4 = creaGrafo_(Orientacion.D, (1,1),                     [(1,1)])     g5 = creaGrafo_(Orientacion.ND, (1,3),                     [(1,2),(1,3),(2,3),(3,3)])     g6 = creaGrafo_(Orientacion.D, (1,3),                     [(1,2),(1,3),(2,3),(3,3)])     assert grado(g1, 5) == 4     assert grado(g2, 5) == 3     assert grado(g2, 1) == 3     assert grado(g3, 2) == 4     assert grado(g3, 1) == 2     assert grado(g3, 3) == 2     assert grado(g4, 1) == 2     assert grado(g5, 3) == 4     assert grado(g6, 3) == 4     print("Verificado") # La verificación es #    >>> test_grado() #    Verificado  | 
					
3. Lema del apretón de manos
En la teoría de grafos, se conoce como “Lema del apretón de manos” la siguiente propiedad: la suma de los grados de los vértices de g es el doble del número de aristas de g.
Comprobar con QuickCheck que para cualquier grafo g, se verifica dicha propiedad.
Soluciones
A continuación se muestran las soluciones en Haskell y las soluciones en Python.
| 
					 1 2 3 4 5 6 7 8 9 10 11 12 13  | 
						import TAD.Grafo (Grafo, nodos) import TAD.GrafoGenerador import Grafo_Grado_de_un_vertice (grado) import Grafo_Numero_de_aristas_de_un_grafo (nAristas) import Test.QuickCheck prop_apretonManos :: Grafo Int Int -> Bool prop_apretonManos g =   sum [grado g v | v <- nodos g] == 2 * nAristas g -- La comprobación es --    λ> quickCheck prop_apretonManos --    +++ OK, passed 100 tests.  | 
					
| 
					 1 2 3 4 5 6 7 8 9 10 11 12 13 14 15 16  | 
						from hypothesis import given from src.Grafo_Grado_de_un_vertice import grado from src.Grafo_Numero_de_aristas_de_un_grafo import nAristas from src.TAD.Grafo import nodos from src.TAD.GrafoGenerador import gen_grafo # La propiedad es @given(gen_grafo()) def test_apreton(g):     assert sum((grado(g, v) for v in nodos(g))) == 2 * nAristas(g) # La comprobación es #    src> poetry run pytest -q Grafo_Lema_del_apreton_de_manos.py #    1 passed in 0.32s  | 
					
4. Grafos regulares
Un grafo regular es un grafo en el que todos sus vértices tienen el mismo grado.
Usando el tipo abstracto de datos de los grafos, definir la función,
| 
					 1  | 
						   regular :: (Ix v,Num p) => Grafo v p -> Bool  | 
					
tal que (regular g) se verifica si el grafo g es regular. Por ejemplo,
| 
					 1 2 3 4 5 6  | 
						   λ> regular (creaGrafo' D (1,3) [(1,2),(2,3),(3,1)])    True    λ> regular (creaGrafo' ND (1,3) [(1,2),(2,3)])    False    λ> regular (completo 4)    True  | 
					
Comprobar que los grafos completos son regulares.
Soluciones
A continuación se muestran las soluciones en Haskell y las soluciones en Python.
| 
					 1 2 3 4 5 6 7 8 9 10 11 12 13 14 15 16 17 18 19 20 21 22 23 24 25 26 27 28 29 30 31 32 33 34 35 36 37 38 39 40 41 42 43 44 45 46 47 48 49 50 51  | 
						module Grafo_Grafos_regulares where import TAD.Grafo (Grafo, Orientacion (D, ND), nodos, creaGrafo') import Data.Ix (Ix) import Grafo_Grado_de_un_vertice (grado) import Grafo_Grafos_completos (completo) import Test.Hspec (Spec, hspec, it, shouldBe) regular :: (Ix v,Num p) => Grafo v p -> Bool regular g = and [grado g v == k | v <- vs]   where vs = nodos g         k  = grado g (head vs) -- La propiedad de la regularidad de todos los grafos completos de orden -- entre m y n es prop_CompletoRegular :: Int -> Int -> Bool prop_CompletoRegular m n =   and [regular (completo x) | x <- [m..n]] -- La comprobación es --    λ> prop_CompletoRegular 1 30 --    True -- Verificación -- ============ verifica :: IO () verifica = hspec spec spec :: Spec spec = do   it "e1" $     regular g1 `shouldBe` True   it "e2" $     regular g2 `shouldBe` False   it "e3" $     regular (completo 4) `shouldBe` True   where     g1, g2 :: Grafo Int Int     g1 = creaGrafo' D (1,3) [(1,2),(2,3),(3,1)]     g2 = creaGrafo' ND (1,3) [(1,2),(2,3)] -- La verificación es --    λ> verifica -- --    e1 --    e2 --    e3 -- --    Finished in 0.0006 seconds --    3 examples, 0 failures  | 
					
| 
					 1 2 3 4 5 6 7 8 9 10 11 12 13 14 15 16 17 18 19 20 21 22 23 24 25 26 27 28 29 30 31 32 33  | 
						from src.Grafo_Grado_de_un_vertice import grado from src.Grafo_Grafos_completos import completo from src.TAD.Grafo import Grafo, Orientacion, creaGrafo_, nodos def regular(g: Grafo) -> bool:     vs = nodos(g)     k = grado(g, vs[0])     return all(grado(g, v) == k for v in vs) # La propiedad de la regularidad de todos los grafos completos de orden # entre m y n es def prop_CompletoRegular(m: int, n: int) -> bool:     return all(regular(completo(x)) for x in range(m, n + 1)) # La comprobación es #    >>> prop_CompletoRegular(1, 30) #    True # Verificación # ============ def test_regular() -> None:     g1 = creaGrafo_(Orientacion.D, (1,3), [(1,2),(2,3),(3,1)])     g2 = creaGrafo_(Orientacion.ND, (1,3), [(1,2),(2,3)])     assert regular(g1)     assert not regular(g2)     assert regular(completo(4))     print("Verificado") # La verificación es #    >>> test_regular() #    Verificado  | 
					
5. Grafos k-regulares
Un grafo k-regular es un grafo con todos sus vértices son de grado k.
Usando el tipo abstracto de datos de los grafos, definir la función,
| 
					 1  | 
						   regularidad :: (Ix v,Num p) => Grafo v p -> Maybe Int  | 
					
tal que (regularidad g) es la regularidad de g. Por ejemplo,
| 
					 1 2 3 4 5 6  | 
						   regularidad (creaGrafo' ND (1,2) [(1,2),(2,3)]) == Just 1    regularidad (creaGrafo' D (1,2) [(1,2),(2,3)])  == Nothing    regularidad (completo 4)                        == Just 3    regularidad (completo 5)                        == Just 4    regularidad (grafoCiclo 4)                      == Just 2    regularidad (grafoCiclo 5)                      == Just 2  | 
					
Comprobar que el grafo completo de orden n es (n-1)-regular (para n de 1 a 20) y el grafo ciclo de orden n es 2-regular (para n de 3 a 20).
Soluciones
A continuación se muestran las soluciones en Haskell y las soluciones en Python.
| 
					 1 2 3 4 5 6 7 8 9 10 11 12 13 14 15 16 17 18 19 20 21 22 23 24 25 26 27 28 29 30 31 32 33 34 35 36 37 38 39 40 41 42 43 44 45 46 47 48 49 50 51 52 53 54 55 56 57 58 59 60 61 62 63 64 65 66 67 68 69 70  | 
						module Grafo_Grafos_k_regulares where import TAD.Grafo (Grafo, Orientacion (D, ND), nodos, creaGrafo') import Data.Ix (Ix) import Grafo_Grado_de_un_vertice (grado) import Grafo_Grafos_regulares (regular) import Grafo_Grafos_completos (completo) import Grafo_Grafos_ciclos (grafoCiclo) import Test.Hspec (Spec, hspec, it, shouldBe) regularidad :: (Ix v,Num p) => Grafo v p -> Maybe Int regularidad g   | regular g = Just (grado g (head (nodos g)))   | otherwise = Nothing -- La propiedad de k-regularidad de los grafos completos es prop_completoRegular :: Int -> Bool prop_completoRegular n =   regularidad (completo n) == Just (n-1) -- La comprobación es --    λ> and [prop_completoRegular n | n <- [1..20]] --    True -- La propiedad de k-regularidad de los grafos ciclos es prop_cicloRegular :: Int -> Bool prop_cicloRegular n =   regularidad (grafoCiclo n) == Just 2 -- La comprobación es --    λ> and [prop_cicloRegular n | n <- [3..20]] --    True -- Verificación -- ============ verifica :: IO () verifica = hspec spec spec :: Spec spec = do   it "e1" $     regularidad g1             `shouldBe` Just 1   it "e2" $     regularidad g2             `shouldBe` Nothing   it "e3" $     regularidad (completo 4)   `shouldBe` Just 3   it "e4" $     regularidad (completo 5)   `shouldBe` Just 4   it "e5" $     regularidad (grafoCiclo 4) `shouldBe` Just 2   it "e6" $     regularidad (grafoCiclo 5) `shouldBe` Just 2   where     g1, g2 :: Grafo Int Int     g1 = creaGrafo' ND (1,2) [(1,2),(2,3)]     g2 = creaGrafo' D (1,2) [(1,2),(2,3)] -- La verificación es --    λ> verifica -- --    e1 --    e2 --    e3 --    e4 --    e5 --    e6 -- --    Finished in 0.0027 seconds --    6 examples, 0 failures  | 
					
| 
					 1 2 3 4 5 6 7 8 9 10 11 12 13 14 15 16 17 18 19 20 21 22 23 24 25 26 27 28 29 30 31 32 33 34 35 36 37 38 39 40 41 42 43 44 45 46 47  | 
						from typing import Optional from src.Grafo_Grado_de_un_vertice import grado from src.Grafo_Grafos_ciclos import grafoCiclo from src.Grafo_Grafos_completos import completo from src.Grafo_Grafos_regulares import regular from src.TAD.Grafo import Grafo, Orientacion, creaGrafo_, nodos def regularidad(g: Grafo) -> Optional[int]:     if regular(g):         return grado(g, nodos(g)[0])     return None # La propiedad de k-regularidad de los grafos completos es def prop_completoRegular(n: int) -> bool:     return regularidad(completo(n)) == n - 1 # La comprobación es #    >>> all(prop_completoRegular(n) for n in range(1, 21)) #    True # La propiedad de k-regularidad de los grafos ciclos es def prop_cicloRegular(n: int) -> bool:     return regularidad(grafoCiclo(n)) == 2 # La comprobación es #    >>> all(prop_cicloRegular(n) for n in range(3, 21)) #    True # Verificación # ============ def test_k_regularidad() -> None:     g1 = creaGrafo_(Orientacion.ND, (1,2), [(1,2),(2,3)])     g2 = creaGrafo_(Orientacion.D, (1,2), [(1,2),(2,3)])     assert regularidad(g1) == 1     assert regularidad(g2) is None     assert regularidad(completo(4)) == 3     assert regularidad(completo(5)) == 4     assert regularidad(grafoCiclo(4)) == 2     assert regularidad(grafoCiclo(5)) == 2     print("Verificado") # La verificación es #    >>> test_k_regularidad() #    Verificado  |