Menu Close

Sucesión contadora

Definir las siguientes funciones

   numeroContado           :: Integer -> Integer
   contadora               :: Integer -> [Integer]
   lugarPuntoFijoContadora :: Integer -> Integer -> Maybe Integer

tales que

  • (numeroContado n) es el número obtenido al contar las repeticiones de cada una de las cifras de n. Por ejemplo,
     numeroContado 1                 == 11
     numeroContado 114213            == 31121314
     numeroContado 1111111111111111  == 161
     numeroContado 555555555500      == 20105
  • (contadora n) es la sucesión cuyo primer elemento es n y los restantes se obtienen contando el número anterior de la sucesión. Por ejemplo,
     λ> take 14 (contadora 1)
     [1,11,21,1112,3112,211213,312213,212223,114213,31121314,41122314,
      31221324,21322314,21322314]
     λ> take 14 (contadora 5)
     [5,15,1115,3115,211315,31121315,41122315,3122131415,4122231415,
      3132132415,3122331415,3122331415,3122331415,3122331415]
  • (lugarPuntoFijoContadora n k) es el menor i <= k tal que son iguales los elementos en las posiciones i e i+1 de la sucesión contadora que cominza con n. Por ejemplo,
      λ> lugarPuntoFijoContadora 1 100
      Just 12
      λ> contadora 1 !! 11
      31221324
      λ> contadora 1 !! 12
      21322314
      λ> contadora 1 !! 13
      21322314
      λ> lugarPuntoFijoContadora 1 10
      Nothing
      λ> lugarPuntoFijoContadora 5 20
      Just 10
      λ> lugarPuntoFijoContadora 40 200
      Nothing

Nota: Este ejercicio ha sido propuesto por Ángel Ruiz.

Soluciones

import Data.List ( genericLength
                 , genericTake
                 , group
                 , nub
                 , sort
                 )
 
-- Definición de numeroContado
numeroContado :: Integer -> Integer
numeroContado n =
  (read . concat . map concat) [[(show . length) m,nub m]
                               | m <- (group . sort . show) n]
 
-- 1ª definición de contadora
contadora :: Integer -> [Integer]
contadora n = n : map numeroContado (contadora n)
 
-- 2ª definición de contadora
contadora2 :: Integer ->  [Integer]
contadora2 = iterate numeroContado 
 
-- Definición de lugarPuntoFijoContadora
lugarPuntoFijoContadora :: Integer -> Integer -> Maybe Integer
lugarPuntoFijoContadora n k
  | m == k-1  = Nothing
  | otherwise = Just m
  where xs = genericTake k (contadora n)
        ds = zipWith (-) xs (tail xs)
        m  = genericLength (takeWhile (/=0) ds)
Avanzado

8 soluciones de “Sucesión contadora

  1. agumaragu1
     
    numeroContado :: Integer -> Integer
    numeroContado = read.concat.(map aux).group.sort.show
      where aux xs = [aux2, head xs]
              where aux2 = (head.show.length) xs
     
    contadora :: Integer -> [Integer]
    contadora = iterate numeroContado 
     
    lugarPuntoFijoContadora :: Integer -> Integer -> Maybe Integer
    lugarPuntoFijoContadora n k = aux n 0
      where aux n ac  | ac == k = Nothing
                      | n == numeroContado n  = Just ac
                      | otherwise = aux (numeroContado n) (ac +1)
    • pabhueacu

      Si haces

      NumeroContado 11111111111111111111111111111111111111111
      41

      Cuando deberías obtener 411 como se obtiene con la definición de jaibengue.
      Creo que el problema esta en el head utilizado en el aux2 que deberías solucionar.
      Espero que te sirva de algo.

  2. jaibengue
    import Data.List
    import Data.Char
     
    numeroContado :: Integer -> Integer
    numeroContado n = read (aux s (head s) 0)
      where s                             = sort (show n)
            aux [] c long                 = show long++[c]
            aux (x:xs) c long | x==c      = aux xs c (long+1)
                              | otherwise = show long++c:(aux xs x 1)
     
    contadora :: Integer -> [Integer]
    contadora n = n:(contadora (numeroContado n))
     
    lugarPuntoFijoContadora :: Integer -> Integer -> Maybe Integer
    lugarPuntoFijoContadora n k = aux (contadora n) 0
      where aux (x:xs) q | q == (k+1)   = Nothing
                         | x == head xs = Just q
                         | otherwise    = aux xs (q+1)
  3. pabhueacu
    numeroContado :: Integer -> Integer
    numeroContado n = sum[x*10^y | (x,y) <- zip (reverse (contador n)) [0..]]
     
    contador :: Integer -> [Integer]
    contador x = (concat.filter op)[[(aux z y), y] | y <- [0..9]]
             where z = init(rCifras x)
     
    op :: [Integer] -> Bool
    op [x,y] | x == 0 = False
             | otherwise = True
    op _ = True
     
    aux :: [Integer] -> Integer -> Integer
    aux z y | y `elem` z = genericLength z - genericLength (filter (/= y) z)
            |otherwise = 0
     
    rCifras :: Integer -> [Integer]
    rCifras 0 = [0]
    rCifras x = (x `mod` 10) : rCifras (x `div` 10)
    • angruicam1

      Buenas, la definición es incorrecta. Por ejemplo:

      λ> numeroContado 11111111110
      10101
      λ> numeroContado2 11111111110
      1101

      Donde numeroContado2 es tu definición

      • pabhueacu

        Si se cambia la definción de numeroContado por:

        numeroContado :: Integer -> Integer
        numeroContado n = read (concat [ show x | x <- contador n])

        Dejando el resto igual parece que ya se soluciona el problema.

  4. carriomon1
    import Data.Char
    import Data.List
     
    numeroContado :: Integer -> Integer
    numeroContado x = aux (listaContado (listaPares x))
      where aux []     = 0
            aux (x:xs) = x*10^(genericLength (x:xs)-1) + aux xs
     
    listaPares :: Integer -> [(Integer,Integer)]
    listaPares x = zip (repeticiones x) (numeros x)
      where numeros x      = map head (listasOrdenadas x)
            repeticiones x = map genericLength (listasOrdenadas x)
     
    listasOrdenadas :: Integer -> [[Integer]]
    listasOrdenadas x =
      group . sort . map (toInteger . digitToInt) $ show x
     
    listaContado :: [(Integer,Integer)] -> [Integer]
    listaContado [] = []
    listaContado  ((a,b):ys)= [a,b] ++ listaContado ys
     
    contadora :: Integer -> [Integer]
    contadora = iterate numeroContado
     
    lugarPuntoFijoContadora :: Integer -> Integer -> Maybe Integer 
    lugarPuntoFijoContadora n k
      | aux1 n (fromIntegral k) == [] = Nothing
      | otherwise                     = Just (minimum (aux1 n (fromIntegral k)))
      where aux1 a b = map toInteger
                       [x | x <- [0..b]
                          , contadora a !! x == contadora a !! (x+1)]
    • carriomon1

      Acabo de caer en que tenía el mismo problema que pabhueacu con los 0.

      import Data.Char
      import Data.List
       
      numeroContado :: Integer -> Integer
      numeroContado x =
        read (concat [show a | a <- listaContado (listaPares x)])
       
      listaPares :: Integer -> [(Integer,Integer)]
      listaPares x = zip (repeticiones x) (numeros x)
        where numeros x      = map head (listasOrdenadas x)
              repeticiones x = map genericLength (listasOrdenadas x)
       
      listasOrdenadas :: Integer -> [[Integer]]
      listasOrdenadas x =
        group . sort . map (toInteger . digitToInt) $ show x
       
      listaContado :: [(Integer,Integer)] -> [Integer]
      listaContado []          = []
      listaContado  ((a,b):ys) = [a,b] ++ listaContado ys
       
      contadora :: Integer -> [Integer]
      contadora = iterate numeroContado
       
      lugarPuntoFijoContadora :: Integer -> Integer -> Maybe Integer 
      lugarPuntoFijoContadora n k
        | aux1 n (fromIntegral k) == [] = Nothing
        | otherwise                     = Just (minimum (aux1 n (fromIntegral k)))
        where aux1 a b = map toInteger
                         [x | x <- [0..b]
                            , contadora a !! x == contadora a !! (x+1)]

Escribe tu solución

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