Ir al contenido principal

Mínimo número de divisiones para igualar


El mínimo número de divisiones por 2, 3 ó 5 que hay que realizar igualar 15 y 20 es 6. En efecto, 15 se reduce a 5 dividiéndolo por 3 y 20 se reduce a 5 diviéndolo dos veces por 2.

Definir la función

   minimoNumeroDivisiones :: Integer -> Integer -> Maybe Int

tal que (minimoNumeroDivisiones x y) es justamente el mínimo número de divisiones por 2, 3 ó 5 que hay que realizar para igualar x e y, o Nothing si no se pueden igualar. Por ejemplo,

   minimoNumeroDivisiones 15 20       ==  Just 3
   minimoNumeroDivisiones 15 15       ==  Just 0
   minimoNumeroDivisiones 15 16       ==  Just 6
   minimoNumeroDivisiones 15 17       ==  Nothing
   minimoNumeroDivisiones (10^99) 21  ==  Nothing

Soluciones

import Data.List (group, intersect, nub, sort)
import Data.Maybe (fromJust, isNothing, listToMaybe)
import Data.Numbers.Primes (primeFactors)
import Data.Tree (Tree (Node), flatten, levels)
import Test.QuickCheck (Property, (==>), quickCheck)

-- 1ª solución
-- ===========

minimoNumeroDivisiones :: Integer -> Integer -> Maybe Int
minimoNumeroDivisiones x y
  | isNothing a = Nothing
  | otherwise   = Just (fst (fromJust a))
  where a = minimoNumeroDivisionesAux x y

-- La definición anterior se puede simplificar
minimoNumeroDivisiones' :: Integer -> Integer -> Maybe Int
minimoNumeroDivisiones' x y =
  Just fst <*> minimoNumeroDivisionesAux x y

-- (minimoNumeroDivisiones x y) es justamente el par formado por el
-- mínimo número de divisiones por 2, 3 ó 5 que hay que realizar para
-- igualar x e y junto con el número al que se reducen, o Nothing si no
-- se pueden igualar. Por ejemplo,
--    minimoNumeroDivisionesAux 15 20  ==  Just (3,5)
--    minimoNumeroDivisionesAux 15 15  ==  Just (0,15)
--    minimoNumeroDivisionesAux 15 16  ==  Just (6,1)
--    minimoNumeroDivisionesAux 15 17  ==  Nothing
minimoNumeroDivisionesAux :: Integer -> Integer -> Maybe (Int,Integer)
minimoNumeroDivisionesAux x y
  | null as   = Nothing
  | otherwise = Just (head as)
  where as = sort [(m+n,z) | (z,(m,n)) <- minimasProfundidadesComunes x y]

-- La definición anterior se puede simplificar
minimoNumeroDivisionesAux2 :: Integer -> Integer -> Maybe (Int,Integer)
minimoNumeroDivisionesAux2 x y =
  listToMaybe (sort [(m+n,z) | (z,(m,n)) <- minimasProfundidadesComunes x y])

-- (arbolDivisiones x) es el árbol de las divisiones enteras de x entre
-- 2, 3 ó 5. Por ejemplo,
--    λ> putStrLn (drawTree (fmap show (arbolDivisiones 30)))
--    30
--    |
--    +- 15
--    |  |
--    |  +- 5
--    |  |  |
--    |  |  `- 1
--    |  |
--    |  `- 3
--    |     |
--    |     `- 1
--    |
--    +- 10
--    |  |
--    |  +- 5
--    |  |  |
--    |  |  `- 1
--    |  |
--    |  `- 2
--    |     |
--    |     `- 1
--    |
--    `- 6
--       |
--       +- 3
--       |  |
--       |  `- 1
--       |
--       `- 2
--          |
--          `- 1
arbolDivisiones :: Integer -> Tree Integer
arbolDivisiones x =
  Node x (map arbolDivisiones (divisiones x))

-- (divisiones x) es la lista de las divisiones enteras de x entre 2, 3
-- y 5. Por ejemplo,
--    divisiones 30  ==  [15,10,6]
--    divisiones 15  ==  [5,3]
divisiones :: Integer -> [Integer]
divisiones x =
  [x `div` y | y <- [2,3,5], x `mod` y == 0]

-- (nodos a) es el conjunto de nodos del árbol a. Por ejemplo,
--    nodos (Node 2 [Node 2 [], Node 5 []])  ==  [2,5]
--    nodos (arbolDivisiones 30)  ==  [30,15,5,1,3,10,2,6]
nodos :: Tree Integer -> [Integer]
nodos = nub . flatten

-- (divisionesComunes x y) es la lista de los nodos comunes de los
-- árboles de las divisiones de x e y entre 2, 3 ó 5. Por ejemplo,
--    divisionesComunes 15 20  ==  [5,1]
divisionesComunes :: Integer -> Integer -> [Integer]
divisionesComunes x y =
  nodos (arbolDivisiones x) `intersect` nodos (arbolDivisiones y)

-- (minimaProfundidad x ns) es justamente la mínima produndidad
-- donde aparece x en el árbol ns, si aparece y Nothing, en caso
-- contrario. Por ejemplo,minimaProfundidad :: Ord a => a -> Tree a -> Maybe Int
--    λ> minimaProfundidad 3 (Node 1 [Node 6 [],Node 3 [Node 1 []]])
--    Just 1
--    λ> minimaProfundidad 4 (Node 1 [Node 6 [],Node 3 [Node 1 []]])
--    Nothing
minimaProfundidad :: Ord a => a -> Tree a -> Maybe Int
minimaProfundidad x ns =
  listToMaybe [z | (z,ys) <- zip [0..] (levels ns), x `elem` ys]

-- (minimasProfundidadesComunes x e y) es la lista de pares formadas por
-- los nodos comunes de los árboles de las divisiones de x e y entre 2,
-- 3 ó 5 junto con las mínimas profundidades en cada uno de los
-- árboles. Por ejemplo,
--    minimasProfundidadesComunes 15 20  ==  [(5,(1,2)),(1,(2,3))]
--    minimasProfundidadesComunes 15 22  ==  []
minimasProfundidadesComunes :: Integer -> Integer -> [(Integer,(Int,Int))]
minimasProfundidadesComunes x1 x2 =
  [(c,(fromJust (minimaProfundidad c a1), fromJust (minimaProfundidad c a2)))
  | c <- cs]
  where a1 = arbolDivisiones x1
        a2 = arbolDivisiones x2
        cs = divisionesComunes x1 x2

-- Propiedad
-- =========

-- El mínimo número de divisiones se alcanza en el máximo común divisor.
prop_minimoNumeroDivisiones :: Integer -> Integer -> Property
prop_minimoNumeroDivisiones x y =
  x > 0 && y > 0 ==>
  isNothing a || snd (fromJust a) == gcd x y
  where a = minimoNumeroDivisionesAux x y

-- La comprobación es
--    λ> quickCheck prop_minimoNumeroDivisiones
--    +++ OK, passed 100 tests.

-- 2ª solución
-- ===========

minimoNumeroDivisiones2 :: Integer -> Integer -> Maybe Int
minimoNumeroDivisiones2 x y
  | as' == bs' = Just (sum [abs (a - b) | (a,b) <- zip as bs])
  | otherwise  = Nothing
  where (as,as') = factorizacion x
        (bs,bs') = factorizacion y

-- (factorización n) es la lista de pares cuya primera componente es la
-- lista de los exponentes de 2, 3 y 5 en la factorización de n y la
-- segunda esla lista delos restantes divisores primos. Por ejemplo,
--    factorizacion 15   ==  ([0,1,1],[])
--    factorizacion 20   ==  ([2,0,1],[])
--    factorizacion 17   ==  ([0,0,0],[17])
--    factorizacion 147  ==  ([0,1,0],[7,7])
factorizacion :: Integer -> ([Int],[Integer])
factorizacion n =
  (map length [bs,cs,ds], es)
  where as = primeFactors n
        (bs,bs') = span (==2) as
        (cs,cs') = span (==3) bs'
        (ds,es)  = span (==5) cs'

-- Equivalencia
-- ============

-- La propies de la equivalencia de las dos definiciones es
prop_equivalencia :: Integer -> Integer -> Property
prop_equivalencia x y =
  x > 0 && y > 0 ==>
  minimoNumeroDivisiones x y == minimoNumeroDivisiones2 x y

-- La comprobación es
--    λ> quickCheck prop_equivalencia
--    +++ OK, passed 100 tests.

-- Comparación de eficiencia
-- =========================

--    λ> minimoNumeroDivisiones (10^11) (3^10*7)
--    Nothing
--    (6.08 secs, 2,725,931,872 bytes)
--    λ> minimoNumeroDivisiones2(10^11) (3^10*7)
--    Nothing
--    (0.01 secs, 128,944 bytes)