Exercitium

Exponente en la factorización
Publicado el 19 de marzo de 2024 por José A. Alonso

Índice

1. Enunciado

Definir la función

exponente :: Integer -> Integer -> Int

tal que (exponente x n) es el exponente de x en la factorización prima de n (se supone que x > 1 y n > 0). Por ejemplo,

exponente 2 24  ==  3
exponente 3 24  ==  1
exponente 6 24  ==  0
exponente 7 24  ==  0

2. Soluciones en Haskell

module Exponente_en_la_factorizacion where

import Data.Numbers.Primes (primeFactors)
import Test.Hspec (Spec, describe, hspec, it, shouldBe)
import Test.QuickCheck

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

exponente1 :: Integer -> Integer -> Int
exponente1 x n
  | esPrimo x = aux n
  | otherwise = 0
  where aux m | m `mod` x == 0 = 1 + aux (m `div` x)
              | otherwise      = 0

-- (esPrimo x) se verifica si x es un número primo. Por ejemplo,
--    esPrimo 7  ==  True
--    esPrimo 8  ==  False
esPrimo :: Integer -> Bool
esPrimo x =
  [y | y <- [1..x], x `mod` y == 0] == [1,x]

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

exponente2 :: Integer -> Integer -> Int
exponente2 x n
  | esPrimo x = length (takeWhile (`divisible` x) (iterate (`div` x) n))
  | otherwise = 0

-- (divisible n x) se verifica si n es divisible por x. Por ejemplo,
--    divisible 6 2  ==  True
--    divisible 7 2  ==  False
divisible :: Integer -> Integer -> Bool
divisible n x = n `mod` x == 0

-- 3ª solución
-- ===========

exponente3 :: Integer -> Integer -> Int
exponente3 x n =
  length (filter (==x) (primeFactors n))

-- Verificación
-- ============

verifica :: IO ()
verifica = hspec spec

specG :: (Integer -> Integer -> Int) -> Spec
specG exponente = do
  it "e1" $
    exponente 2 24  `shouldBe`  3
  it "e2" $
    exponente 3 24  `shouldBe`  1
  it "e3" $
    exponente 6 24  `shouldBe`  0
  it "e4" $
    exponente 7 24  `shouldBe`  0

spec :: Spec
spec = do
  describe "def. 1" $ specG exponente1
  describe "def. 2" $ specG exponente2
  describe "def. 3" $ specG exponente3

-- La verificación es
--    λ> verifica
--
--    12 examples, 0 failures

-- Equivalencia de las definiciones
-- ================================

-- La propiedad es
prop_exponente :: Integer -> Integer -> Property
prop_exponente x n =
  x > 1 && n > 0 ==>
  exponente1 x n == exponente2 x n &&
  exponente1 x n == exponente3 x n

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

3. Soluciones en Python

from itertools import takewhile
from typing import Callable, Iterator

from hypothesis import given
from hypothesis import strategies as st
from sympy.ntheory import factorint

# 1ª solución
# ===========

# esPrimo(x) se verifica si x es un número primo. Por ejemplo,
#    esPrimo(7)  ==  True
#    esPrimo(8)  ==  False
def esPrimo(x: int) -> bool:
    return [y for y in range(1, x+1) if x % y == 0] == [1,x]

def exponente1(x: int, n: int) -> int:
    def aux (m: int) -> int:
        if m % x == 0:
            return 1 + aux(m // x)
        return 0
    if esPrimo(x):
        return aux(n)
    return 0

# 2ª solución
# ===========

# iterate(f, x) es el iterador obtenido aplicando f a x y continuando
# aplicando f al resultado anterior. Por ejemplo,
#    >>> list(islice(iterate(lambda x : 4 * x, 1), 5))
#    [1, 4, 16, 64, 256]
def iterate(f: Callable[[int], int], x: int) -> Iterator[int]:
    r = x
    while True:
        yield r
        r = f(r)

# divisible(n, x) se verifica si n es divisible por x. Por ejemplo,
#    divisible(6, 2)  ==  True
#    divisible(7, 2)  ==  False
def divisible(n: int, x: int) -> bool:
    return n % x == 0

def exponente2(x: int, n: int) -> int:
    if esPrimo(x):
        return len(list(takewhile(lambda m : divisible(m, x),
                                  iterate(lambda m : m // x, n))))
    return 0

# 3ª solución
# ===========

def exponente3(x: int, n: int) -> int:
    return factorint(n, multiple = True).count(x)

# Verificación
# ============

def test_exponente() -> None:
    for exponente in [exponente1, exponente2, exponente3]:
        assert exponente(2, 24) == 3
        assert exponente(3, 24) == 1
        assert exponente(6, 24) == 0
        assert exponente(7, 24) == 0
    print("Verificado")

# La verificación es
#    >>> test_exponente()
#    Verificado

# Equivalencia de las definiciones
# ================================

# La propiedad es
@given(st.integers(min_value=1, max_value=1000),
       st.integers(min_value=0, max_value=1000))
def test_exponente_equiv(x: int, n: int) -> None:
    r = exponente1(x, n)
    assert r == exponente2(x, n)
    assert r == exponente3(x, n)

# La comprobación es
#    >>> test_exponente_equiv()
#    >>>

Exercitium

José A. Alonso Jiménez

Sevilla, 07 de abril del 2024

Licencia: Creative Commons.