Menu Close

Número como suma de sus dígitos

El número 23 se puede escribir de 4 formas como suma de sus dígitos

   2 + 2 + 2 + 2 + 2 + 2 + 2 + 2 + 2 + 2 + 3
   2 + 2 + 2 + 2 + 2 + 2 + 2 + 3 + 3 + 3
   2 + 2 + 2 + 2 + 3 + 3 + 3 + 3 + 3
   2 + 3 + 3 + 3 + 3 + 3 + 3 + 3

La de menor número de sumando es la última, que tiene 8 sumandos.

Definir las funciones

   minimoSumandosDigitos        :: Integer -> Integer
   graficaMinimoSumandosDigitos :: Integer -> IO ()

tales que

  • (minimoSumandosDigitos n) es el menor número de dígitos de n cuya suma es n. Por ejemplo,
     minimoSumandosDigitos 23    ==  8
     minimoSumandosDigitos 232   ==  78
     minimoSumandosDigitos 2323  ==  775
     map minimoSumandosDigitos [10..20] == [10,11,6,5,5,3,6,5,4,3,10]
  • (graficaMinimoSumandosDigitos n) dibuja la gráfica de (minimoSumandosDigitos k) par los k primeros números naturales. Por ejemplo, (graficaMinimoSumandosDigitos 300) dibuja

Soluciones

import Test.QuickCheck
import Graphics.Gnuplot.Simple
import Data.List (nub, genericLength, sort)
import Data.Array (array, (!))
 
minimoSumandosDigitos :: Integer -> Integer
minimoSumandosDigitos n =
  minimoSumandos (digitos n) n
 
-- (digitos n) es el conjunto de los dígitos no nulos de n. Por ejemplo,
--    digitos 2032  ==  [2,3]
digitos :: Integer -> [Integer]
digitos n =
  nub [read [c] | c <- show n, c /= '0']
 
-- (minimoSumandos xs n) es el menor número de elementos de la lista de
-- enteros positivos xs (con posibles repeticiones) cuya suma es n. Por
-- ejemplo, 
--    minimoSumandos [7,2,4] 11  ==  2
minimoSumandos :: [Integer] -> Integer -> Integer
minimoSumandos xs n =
  minimum (map genericLength (sumas xs n))
 
-- (sumas xs n) es la lista de elementos de la lista de enteros
-- positivos xs (con posibles repeticiones) cuya suma es n. Por ejemplo,  
--    sumas [7,2,4] 11  ==  [[7,2,2],[7,4]]
sumas :: [Integer] -> Integer -> [[Integer]]
sumas [] 0 = [[]]
sumas [] _ = []
sumas (x:xs) n
  | x <= n    = map (x:) (sumas (x:xs) (n-x)) ++ sumas xs n
  | otherwise = sumas xs n
 
-- 2ª solución
-- ===========
 
minimoSumandosDigitos2 :: Integer -> Integer
minimoSumandosDigitos2 n = aux n 
  where
    aux 0 = 0
    aux k = 1 + minimo [aux (k - x) | x <- ds,  k >= x]
    ds    = digitos n
    infinito = 10^100
    minimo xs | null xs   = infinito
              | otherwise = minimum xs
 
-- 3ª solución
-- ===========
 
minimoSumandosDigitos3 :: Integer -> Integer
minimoSumandosDigitos3 n = v ! n
  where
    v   = array (0,n) [(i,f i) | i <- [0..n]]
    f 0 = 0
    f k = 1 + minimo [v ! (k - x) | x <- ds, k >= x]
    ds       = digitos n
    infinito = 10^100
    minimo xs | null xs   = infinito
              | otherwise = minimum xs
 
-- Equivalencia de las definiciones
-- ================================
 
-- La propiedad es
prop_minimoSumandosDigitos :: Positive Integer -> Bool
prop_minimoSumandosDigitos (Positive n) =
  r1 == r2 && r2 == r3
  where
    r1 = minimoSumandosDigitos n
    r2 = minimoSumandosDigitos n
    r3 = minimoSumandosDigitos n
 
-- La comprobación es
--    λ> quickCheckWith (stdArgs {maxSize=9}) prop_minimoSumandosDigitos
--    +++ OK, passed 100 tests.
 
-- Definición de graficaMinimoSumandosDigitos
-- ==========================================
 
graficaMinimoSumandosDigitos :: Integer -> IO ()
graficaMinimoSumandosDigitos n =
  plotList [ Key Nothing
           -- , PNG "Numero_como_suma_de_sus_digitos.png"
           ]
           [minimoSumandosDigitos k | k <- [0..n-1]]
Inicial

2 soluciones de “Número como suma de sus dígitos

  1. pabserpoz
    import Data.List
    import Graphics.Gnuplot.Simple
     
    minimoSumandosDigitos :: Integer -> Integer
    minimoSumandosDigitos n = minimoSumandos (digitos n) n
     
    digitos :: Integer -> [Integer]
    digitos n
        | n < 10    = [n]
        | otherwise = (n `rem` 10) : digitos (n `div` 10)
     
    minimoSumandos :: [Integer] -> Integer -> Integer
    minimoSumandos _ 0 = 0
    minimoSumandos [] _ = 1
    minimoSumandos xs n
      | x <= n && ( ys == [] || (n-x)>= maximum ys) || x==n  = 1 + minimoSumandos xs (n-x)
      | otherwise = minimoSumandos ys n
        where x = maximum xs
              ys = delete x xs
     
    graficaMinimoSumandosDigitos :: Integer -> IO ()
    graficaMinimoSumandosDigitos n = do
      plotList [ Key Nothing
               ]
               (map minimoSumandosDigitos [1..n] )
  2. Enrique Zubiría
    import Data.List(nub,sort,genericLength)
    import Graphics.Gnuplot.Simple
     
    minimoSumandosDigitos        :: Integer -> Integer
    minimoSumandosDigitos y = genericLength $ concat (msd y ns [])
      where ns = reverse $ sort $ nub [read [c] :: Integer | c <- show y]
            msd n [] sol = msd (y-ssp) rs sp
              where sp = init (init sol) ++ [init (last (init sol))]
                    ssp = sum $ concat sp
                    rs = filter (r -> not (elem r (nub $ concat sp))) ns
            msd n (x:xs) sol
              | r == 0           = sol ++ [replicate (fromIntegral m) x]
              | n < x && null xs = msd (n+l) (x:xs) ((init sol) ++ [init (last sol)])
              | n < x            = msd n xs sol
              | otherwise        = msd r xs (sol ++ [replicate (fromIntegral m) x])
              where r = rem n x
                    m = div n x
                    l = head (last sol)
     
    graficaMinimoSumandosDigitos :: Integer -> IO ()
    graficaMinimoSumandosDigitos n = do
      plotList [ Key Nothing
               , PNG "graficas/numeroComoSumaDeCaminos.png"
               ]
               (map minimoSumandosDigitos [1..n])

Escribe tu solución

Este sitio usa Akismet para reducir el spam. Aprende cómo se procesan los datos de tus comentarios.