Menu Close

Distribución de diferencias de dígitos consecutivos de pi

La distribución de las diferencias de los dígitos consecutivos para los 18 primeros dígitos de pi se calcula como sigue: los primeros 18 dígitos de pi son

   3, 1, 4, 1, 5, 9, 2, 6, 5, 3, 5, 8, 9, 7, 9, 3, 2, 3

Las diferencias de sus elementos consecutivos es

   2, -3, 3, -4, -4, 7, -4, 1, 2, -2, -3, -1, 2, -2, 6, 1, -1

y la distribución de sus frecuencias en el intervalo [-9,9] es

   0, 0, 0, 0, 0, 3, 2, 2, 2, 0, 2, 3, 1, 0, 0, 1, 1, 0, 0

es decir, el desde el -9 a -5 no aparecen, el -4 aparece 3 veces, el -2 aparece 2 veces y así sucesivamente.

Definir las funciones

   distribucionDDCpi :: Int -> [Int]
   graficas :: [Int] -> FilePath -> IO ()

tales que

  • (distribucionDDCpi n) es la distribución de las diferencias de los dígitos consecutivos para los primeros n dígitos de pi. Por ejemplo,
   λ> distribucionDDCpi 18
   [0,0,0,0,0,3,2,2,2,0,2,3,1,0,0,1,1,0,0]
   λ> distribucionDDCpi 100
   [1,2,1,7,7,7,6,5,8,6,7,14,4,9,3,6,4,1,0]
   λ> distribucionDDCpi 200
   [3,6,2,13,14,12,11,12,15,17,15,19,11,17,8,13,9,2,0]
   λ> distribucionDDCpi 1000
   [16,25,23,44,57,61,55,75,92,98,80,88,64,65,42,54,39,14,8]
   λ> distribucionDDCpi 5000
   [67,99,130,196,245,314,361,391,453,468,447,407,377,304,242,221,134,97,47]
  • (graficas ns f) dibuja en el fichero f las gráficas de las distribuciones de las diferencias de los dígitos consecutivos para los primeros n dígitos de pi, para n en ns. Por ejemplo, al evaluar (graficas [100,250..4000] “distribucionDDCpi.png” se escribe en el fichero “distribucionDDCpi.png” la siguiente gráfica
    Distribucion_de_diferencias_de_digitos_consecutivos_de_pi

Nota: Se puede usar la librería Data.Number.CReal.

Soluciones

import Data.Number.CReal
import Graphics.Gnuplot.Simple
import Data.Array
 
--    λ> digitosPi 18
--    [3,1,4,1,5,9,2,6,5,3,5,8,9,7,9,3,2,3]
digitosPi :: Int -> [Int]
digitosPi n = init [read [c] | c <- (x:xs)]
  where (x:_:xs) = showCReal n pi
 
--    λ> diferenciasConsecutivos (digitosPi 18)
--    [2,-3,3,-4,-4,7,-4,1,2,-2,-3,-1,2,-2,6,1,-1]
diferenciasConsecutivos :: Num a => [a] -> [a]
diferenciasConsecutivos xs =
  zipWith (-) xs (tail xs)
 
distribucionDDCpi :: Int -> [Int]
distribucionDDCpi =
  distribucion . diferenciasConsecutivos . digitosPi
  where distribucion xs =
          elems (accumArray (+) 0 (-9,9) (zip xs (repeat 1)))
 
graficas :: [Int] -> FilePath -> IO ()
graficas ns f = 
  plotLists [Key Nothing, PNG f]
            [puntos n | n <- ns]
  where puntos :: Int -> [(Int,Int)]
        puntos n = zip [-9..9] (distribucionDDCpi n)
Avanzado

12 soluciones de “Distribución de diferencias de dígitos consecutivos de pi

  1. albcercid
    distribucionDDCpi :: Int -> [Int]
    distribucionDDCpi x = map snd $ dist (f (map (read.(:"")) ('3':drop 2 (showCReal x pi))))
          where f [x,y] = []
                f (x:y:xs) = (x-y):f (y:xs)
                dist xs = aux xs [ (a,0) | a <- [-9..9]]
                aux [] ys = ys
                aux (x:xs) ys = aux xs (ad x ys)
                ad x ((a,b):xs) | a == x = (a,b+1):xs
                                | otherwise = (a,b):(ad x xs)
     
     
     
    graficas xs y = plotPaths [EPS y, Key Nothing] ([dist2 x | x <- xs])
     
    dist2 :: Int -> [(Int,Int)]
    dist2 x = dist (f (map (read.(:"")) ('3':drop 2 (showCReal x pi))))
          where f [x,y] = []
                f (x:y:xs) = (x-y):f (y:xs)
                dist xs = aux xs [ (a,0) | a <- [-9..9]]
                aux [] ys = ys
                aux (x:xs) ys = aux xs (ad x ys)
                ad x ((a,b):xs) | a == x = (a,b+1):xs
                                | otherwise = (a,b):(ad x xs)
  2. enrnarbej
    digitosPi :: [Integer]
    digitosPi = g(1,0,1,1,3,3) where
         g (q,r,t,k,n,l) = 
           if 4*q+r-t < n*t
           then n : g (10*q, 10*(r-n*t), t, k, div (10*(3*q+r)) t - 10*n, l)
           else g (q*k, (2*q+r)*l, t*l, k+1, div (q*(7*k+2)+r*l) (t*l), l+2)
     
     
    distribucionDDCpi :: Int -> [Int]
    distribucionDDCpi n = V.toList $ V.accum (+) (V.fromList (replicate 19 0)) (zip (map ((+9).(fromInteger)) diferencias) [1,1..])
                        where
                         dp = take n digitosPi 
                         diferencias  = zipWith (-) dp (tail dp)
     
    graficasD :: [Int] -> FilePath -> IO ()
    graficasD xs fp = plotLists [EPS fp,Key Nothing] [distribucionDDCpi n | n <- xs]
  3. glovizcas
    digitosPi :: Int -> [Integer]
    digitosPi n = 3:[read [x] | x <- drop 2 (init(showCReal (n) pi))]
     
    diferencias n = zipWith (-) (digitosPi n) (tail $digitosPi n)
     
    cuenta n [] = 0
    cuenta n (x:xs) | x == n = 1 + cuenta n xs
                    | otherwise = cuenta n xs
     
    distribucionDDCpi n = [cuenta a (diferencias n) | a <- [(-9)..9]]
  4. ignareeva
    distribucionDDCpi :: Int -> [Integer]
    distribucionDDCpi n = map (snd)[(a,ocurrenciasPi a (diferenciasPi n)) | a <- [-9..9]]
     
    diferenciasPi :: Int -> [Integer]
    diferenciasPi n = zipWith (-) (digitosPi n) (tail (digitosPi n))
     
    ocurrenciasPi :: Integer -> [Integer] -> Integer
    ocurrenciasPi a xs | a `elem` xs = 1 + ocurrenciasPi a (delete a xs)
                       | otherwise = 0
     
    digitosPi :: Int -> [Integer]
    digitosPi n = 3: [read [x] | x <- numeroPi n]
     
    numeroPi :: Int -> String
    numeroPi n = take (n-1) (drop 2 (showCReal n pi))
  5. marlobrip
    import Data.Number.CReal
    import Data.Char
    import Graphics.Gnuplot.Simple
     
    distribucionDDCpi :: Int -> [Int] 
    distribucionDDCpi n = [snd (x,aparece x (diferenciaPi n)) | x <- [-9..9] ]
          where aparece n [] = 0
                aparece n (x:xs) | n == x = 1 + aparece n xs
                                 | otherwise = aparece n xs
     
    diferenciaPi :: Int -> [Int]
    diferenciaPi n  = 2: (init (diferencia (drop 2 (showCReal n pi))))
           where diferencia [x] = []
                 diferencia (x:y:xs) =  (dT x - dT y):(diferencia (y:xs))
                 dT = digitToInt
     
    graficas :: [Int] -> FilePath -> IO ()
    graficas ns y = plotPaths [Key Nothing] [frecuencias n | n <- ns]
         where frecuencias n = [(x,aparece x (diferenciaPi n)) | x <- [-9..9] ]
               aparece n [] = 0
               aparece n (x:xs) | n == x = 1 + aparece n xs
                                | otherwise = aparece n xs
  6. antdursan
    digitosPi :: Integer -> String
    digitosPi n = take (fromIntegral n) ('3' : (drop 2 (showCReal (fromIntegral n) pi)))
     
    diferenciaPi :: Integer -> [Integer]
    diferenciaPi n = diferencia (listaPi n)
                 where diferencia [y] = []
                       diferencia (x:y:xs) = (x-y) : diferencia (y:xs)
                       listaPi n = [read [x] | x <- digitosPi n]
                       digitosPi n = take (fromIntegral n) ('3' : (drop 2 (showCReal (fromIntegral n) pi)))
     
    distribucionDDCpi :: Integer -> [Integer]
    distribucionDDCpi n = map snd [(a,ocurrencias a (diferenciaPi n)) | a <- [-9..9]]
                        where ocurrencias n [] = 0
                              ocurrencias n (x:xs) | n == x = 1 + (ocurrencias n xs)
                                                   | otherwise = ocurrencias n xs
  7. josejuan

    Puede paralelizarse fácilmente el cálculo de cada una de las series:

    {-# LANGUAGE TupleSections #-}
    import System.Environment (getArgs)
    import Data.Number.CReal (showCReal)
    import Data.Char (digitToInt)
    import Data.Map (fromList, elems, update)
    import Graphics.Gnuplot.Simple (plotLists, Attribute(PNG, Key))
    import Control.Parallel (rseq)
    import Control.Parallel.Strategies (parList)
     
    distribucionDDCpi :: Int ->Int ->[Int]
    distribucionDDCpi s n = elems $ foldr (update (Just . (+1))) range $ zipWith subtract (tail xs) xs
      where xs    = map digitToInt $ ((x:_:xs) ->x:xs) $ showCReal n pi
            range = fromList $ (,0) <$> [-s..s]
     
    grafica :: Int ->[Int] ->FilePath ->IO ()
    grafica s ns file = plotLists [PNG file, Key Nothing] (map (distribucionDDCpi s) ns `using` parList rseq)
     
    main = getArgs >>= ((f:x:xs) ->flip (grafica (read x)) f (map read xs))
     
    {-
     
    [josejuan@centella centella]$ stack exec -- ghc -O2 -threaded -rtsopts ../pidig.hs
    [1 of 1] Compiling Main             ( ../pidig.hs, ../pidig.o )
    Linking ../pidig ...
    [josejuan@centella centella]$ time -f "%E, %M" ../pidig ~/tmp/test.png 9 `seq 100 150 4000` +RTS -N6
    0:01.34, 34940
     
    -}
  8. paumacpar
    digitosPi :: Int -> [Int]
    digitosPi n = aux (showCReal n pi)
      where aux [x] = []
            aux (x:xs) | isDigit x = digitToInt x : aux xs
                       | otherwise = aux xs
     
    diferencias :: Int -> [Int]
    diferencias n = zipWith (-) (digitosPi n) (tail (digitosPi n))
     
    distribucionDDCpi :: Int -> [Int]
    distribucionDDCpi n =
        elems (accumArray (+) 0 (-9,9) [(i,1)
                                      | i <- diferencias n])
    graficas :: [Int] -> FilePath -> IO ()
    graficas ns f = plotLists [PNG f, Key Nothing] [distribucionDDCpi n | n <- ns]
  9. eliguivil
    import Data.Number.CReal
    import Graphics.Gnuplot.Simple (plotLists)
     
    distribucionDDCpi :: Int -> [Int]
    distribucionDDCpi = V.toList
                      . V.accum (+) (V.fromList $ replicate 19 0)
                      . map (n -> (n+9,1))
                      . aux
                      . map (read . (:[]))
                      . delete '.'
                      . (`showCReal`pi)
      where
        aux (x:y:[]) = [x-y]
        aux (x:y:xs) = (x-y) : aux (y:xs)
     
    graficas4 :: [Int] -> FilePath -> IO ()
    graficas4 ns f = do plotLists [PNG f, Key Nothing] (map g ns)
      where
        g :: Int -> [(Int,Int)]
        g n = zip [-9..9] $ distribucionDDCpi n
    • eliguivil

      me ha faltado importar una librería

      import qualified Data.Vector as V
      import Data.Number.CReal
      import Graphics.Gnuplot.Simple (plotLists)
       
      distribucionDDCpi :: Int -> [Int]
      distribucionDDCpi = V.toList
                        . V.accum (+) (V.fromList $ replicate 19 0)
                        . map (n -> (n+9,1))
                        . aux
                        . map (read . (:[]))
                        . delete '.'
                        . (`showCReal`pi)
        where
          aux (x:y:[]) = [x-y]
          aux (x:y:xs) = (x-y) : aux (y:xs)
       
      graficas4 :: [Int] -> FilePath -> IO ()
      graficas4 ns f = do plotLists [PNG f, Key Nothing] (map g ns)
        where
          g :: Int -> [(Int,Int)]
          g n = zip [-9..9] $ distribucionDDCpi n
  10. cescarde
    distribucionDDCpi :: Int -> [Int]
    distribucionDDCpi n = g' (f' c) [-9..9]
                      where a = init $ showCReal n pi
                            b = delete '.' $ a
                            c = map digitToInt b
     
    graficas' :: [Int] -> FilePath -> IO ()
    graficas' ns f = plotLists [EPS f, Key Nothing] [d n | n <- ns]
              where d = distribucionDDCpi
     
    --Lista de diferencias
    f' :: [Int] -> [Int]
    f' xs = zipWith (-) xs (tail xs)
     
    --Lista de frecuencias
    g' :: [Int] -> [Int] -> [Int]
    g' _ [] = []
    g' xs (y:ys) = aparece y xs : g' xs ys 
     
    aparece :: Int -> [Int] -> Int
    aparece _ [] = 0
    aparece y (x:xs) | y == x = 1 + aparece y xs
                     | otherwise = aparece y xs
  11. Juanjo Ortega (juaorture)
    import Data.Number.CReal
    import Data.Char
    import Graphics.Gnuplot.Simple
     
    diferenciaDigitosPi :: Int -> [Int]
    diferenciaDigitosPi n = aux (map digitToInt (x:xs))
                        where (x:y:xs) = showCReal (n-1) pi
                              aux (x:y:xs) = x - y : aux (y:xs)
                              aux _        = []                     
     
    distribucionDDCpi :: Int -> [Int]
    distribucionDDCpi n = aux1 (init (diferenciaDigitosPi (n+1))) (replicate 19 0)
     
    aux1 :: [Int] -> [Int] -> [Int]
    aux1 []     ys = ys
    aux1 (x:xs) ys = aux1 xs (take y ys ++ [z+1] ++ zs)
         where y = x + 9
               (z:zs) = drop y ys
     
    graficas :: [Int] -> FilePath -> IO ()
    graficas ns f = plotLists [PNG f, Key Nothing] ([zip [-9..] (distribucionDDCpi x) | x <- ns]::[[(Int,Int)]])

Escribe tu solución

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