Ir al contenido principal

Limitación del número de repeticiones

Definir la función

conRepeticionesAcotadas :: Eq a => [a] -> Int -> [a]

tal que (conRepeticionesAcotadas xs n) es una lista que contiene cada elemento de xs como máximo n veces sin reordenar (se supone que n es un número positivo).. Por ejemplo,

conRepeticionesAcotadas [1,2,3,1,2,1,3,2,3,5] 1  ==  [1,2,3,5]
conRepeticionesAcotadas [1,2,3,1,2,1,3,2,3,5] 2  ==  [1,2,3,1,2,3,5]
conRepeticionesAcotadas [1,2,3,1,2,1,3,2,3,5] 3  ==  [1,2,3,1,2,1,3,2,3,5]
conRepeticionesAcotadas [1,2,3,1,2,1,3,2,3,5] 4  ==  [1,2,3,1,2,1,3,2,3,5]

Soluciones

import Data.List (foldl')
import Data.Maybe (fromJust, isNothing)
import Test.QuickCheck (Property, (==>),quickCheck)

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

conRepeticionesAcotadas :: Eq a => [a] -> Int -> [a]
conRepeticionesAcotadas xs n = reverse (aux [] xs)
  where aux zs []     = zs
        aux zs (y:ys) | m < n     = aux (y:zs) ys
                      | otherwise = aux zs ys
          where m = nOcurrencias y zs

-- (nOcurrencias x ys) es el número de ocurrencias de x en ys. Por
-- ejemplo,
--    nOcurrencias 7 [7,2,7,7,5]  ==  3
nOcurrencias :: Eq a => a -> [a] -> Int
nOcurrencias x ys = length (filter (== x) ys)

-- Se puede simplificar la definición de nOcurrencias:
nOcurrencias2 :: Eq a => a -> [a] -> Int
nOcurrencias2 x = length . filter (== x)

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

conRepeticionesAcotadas2 :: Eq a => [a] -> Int -> [a]
conRepeticionesAcotadas2 xs n = reverse (foldl' aux [] xs)
  where aux zs y | m < n     = y:zs
                 | otherwise = zs
          where m = nOcurrencias y zs

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

conRepeticionesAcotadas3 :: Eq a => [a] -> Int -> [a]
conRepeticionesAcotadas3 xs n = reverse (aux [] [] xs)
  where aux as _ []      = as
        aux as bs (y:ys) | y `elem` bs = aux as bs ys
                         | m < n       = aux (y:as) bs ys
                         | otherwise   = aux as (y:bs) ys
          where m = nOcurrencias y as

-- 4ª solución
-- ===========

conRepeticionesAcotadas4 :: Eq a => [a] -> Int -> [a]
conRepeticionesAcotadas4 xs n = aux xs []
  where aux [] _      = []
        aux (y:ys) ps | r == Nothing = y : aux ys ((y,1) : ps)
                      | m < n        = y : aux ys ((y,m+1) : ps)
                      | otherwise    = aux ys ps
                      where r = busca y ps
                            Just m = r

-- (busca x ps) es justamente la segunda componente del primer par de ps
-- cuya primera componente es xs, si ps tiene algún par cuya primera
-- componente es x; y Nothing en caso contrario. Por ejemplo,
--    busca 'a' [('b',2),('a',3),('a',1)]  ==  Just 3
--    busca 'c' [('b',2),('a',3),('a',1)]  ==  Nothing
busca :: Eq a => a -> [(a,b)] -> Maybe b
busca x ps
  | null ys   = Nothing
  | otherwise = Just (head ys)
  where ys = [n | (y,n) <- ps, y == x]

-- 5ª solución
-- ===========

conRepeticionesAcotadas5 :: Eq a => [a] -> Int -> [a]
conRepeticionesAcotadas5 xs n = aux xs []
  where aux [] _      = []
        aux (y:ys) ps | isNothing r = y : aux ys ((y,1) : ps)
                      | m < n       = y : aux ys ((y,m+1) : ps)
                      | otherwise   = aux ys ps
                      where r = lookup y ps
                            m = fromJust r

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

-- La propiedad es
prop_conRepeticionesAcotadas :: [Int] -> Int -> Property
prop_conRepeticionesAcotadas xs n =
  n > 0 ==>
  all (==(conRepeticionesAcotadas xs n))
      [ conRepeticionesAcotadas2 xs n
      , conRepeticionesAcotadas3 xs n
      , conRepeticionesAcotadas4 xs n
      , conRepeticionesAcotadas5 xs n]

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

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

-- La comparación es
--    λ> length (conRepeticionesAcotadas (concat [[1..n] | n <- [1..500]]) 2)
--    999
--    (5.14 secs, 64,372,768 bytes)
--    λ> length (conRepeticionesAcotadas2 (concat [[1..n] | n <- [1..500]]) 2)
--    999
--    (4.95 secs, 62,322,880 bytes)
--    λ> length (conRepeticionesAcotadas3 (concat [[1..n] | n <- [1..500]]) 2)
--    999
--    (0.38 secs, 38,764,952 bytes)
--    λ> length (conRepeticionesAcotadas4 (concat [[1..n] | n <- [1..500]]) 2)
--    999
--    (5.66 secs, 2,429,904,144 bytes)
--    λ> length (conRepeticionesAcotadas5 (concat [[1..n] | n <- [1..500]]) 2)
--    999
--    (0.68 secs, 48,536,872 bytes)