Menu Close

El problema de las N torres

El problema de las N torres consiste en colocar N torres en un tablero con N filas y N columnas de forma que no haya dos torres en la misma fila ni en la misma columna.

Cada solución del problema de puede representar mediante una matriz con ceros y unos donde los unos representan las posiciones ocupadas por las torres y los ceros las posiciones libres. Por ejemplo,

   ( 0 1 0 )
   ( 1 0 0 )
   ( 0 0 1 )

representa una solución del problema de las 3 torres.

Definir las funciones

   torres  :: Int -> [Matrix Int]
   nTorres :: Int -> Integer

tales que
+ (torres n) es la lista de las soluciones del problema de las n torres. Por ejemplo,

      λ> torres 3
      [( 1 0 0 )
       ( 0 1 0 )
       ( 0 0 1 )
      ,( 1 0 0 )
       ( 0 0 1 )
       ( 0 1 0 )
      ,( 0 1 0 )
       ( 1 0 0 )
       ( 0 0 1 )
      ,( 0 1 0 )
       ( 0 0 1 )
       ( 1 0 0 )
      ,( 0 0 1 )
       ( 1 0 0 )
       ( 0 1 0 )
      ,( 0 0 1 )
       ( 0 1 0 )
       ( 1 0 0 )
      ]
  • (nTorres n) es el número de soluciones del problema de las n torres. Por ejemplo,
      λ> nTorres 3
      6
      λ> length (show (nTorres (10^4)))
      35660

Soluciones

import Data.List (genericLength, sort, permutations)
import Data.Matrix 
 
-- 1ª definición de torres
-- =======================
 
torres1 :: Int -> [Matrix Int]
torres1 n = 
    [permutacionAmatriz n p | p <- sort (permutations [1..n])]
 
permutacionAmatriz :: Int -> [Int] -> Matrix Int
permutacionAmatriz n p =
    matrix n n f
    where f (i,j) | (i,j) `elem` posiciones = 1
                  | otherwise               = 0
          posiciones = zip [1..n] p    
 
-- 2ª definición de torres
-- =======================
 
torres2 :: Int -> [Matrix Int]
torres2 = map fromLists . permutations . toLists . identity
 
-- El cálculo con la definición anterior es:
--    λ> identity 3
--    ( 1 0 0 )
--    ( 0 1 0 )
--    ( 0 0 1 )
--    
--    λ> toLists it
--    [[1,0,0],[0,1,0],[0,0,1]]
--    λ> permutations it
--    [[[1,0,0],[0,1,0],[0,0,1]],
--     [[0,1,0],[1,0,0],[0,0,1]],
--     [[0,0,1],[0,1,0],[1,0,0]],
--     [[0,1,0],[0,0,1],[1,0,0]],
--     [[0,0,1],[1,0,0],[0,1,0]],
--     [[1,0,0],[0,0,1],[0,1,0]]]
--    λ> map fromLists it
--    [( 1 0 0 )
--     ( 0 1 0 )
--     ( 0 0 1 )
--    ,( 0 1 0 )
--     ( 1 0 0 )
--     ( 0 0 1 )
--    ,( 0 0 1 )
--     ( 0 1 0 )
--     ( 1 0 0 )
--    ,( 0 1 0 )
--     ( 0 0 1 )
--     ( 1 0 0 )
--    ,( 0 0 1 )
--     ( 1 0 0 )
--     ( 0 1 0 )
--    ,( 1 0 0 )
--     ( 0 0 1 )
--     ( 0 1 0 )
--    ]
 
-- 1ª definición de nTorres
-- ========================
 
nTorres1 :: Int -> Integer
nTorres1 = genericLength . torres1
 
-- 2ª definición de nTorres
-- ========================
 
nTorres2 :: Int -> Integer
nTorres2 n = product [1..fromIntegral n]
 
-- Comparación de eficiencia
-- =========================
 
--    λ> nTorres1 9
--    362880
--    (4.22 secs, 693,596,128 bytes)
--    λ> nTorres2 9
--    362880
--    (0.00 secs, 0 bytes)
Posted in Avanzado

5 Comments

  1. marjimcom
    import Data.List (permutations)
    import Data.Matrix 
     
    torres  :: Int -> [Matrix Int]
    torres n = map (matriz n) (lista n)
     
    lista :: Int -> [[(Int,Int)]]
    lista n = map (zip [1..n]) (permutations [1..n])
     
    matriz :: Int -> [(Int,Int)] -> Matrix Int
    matriz n xs = matrix n n ((i,j)-> f i j)
      where f i j | (i,j) `elem` xs = 1
                  | otherwise       = 0
     
    nTorres :: Int -> Integer
    nTorres n = product [1..(fromIntegral n)]
  2. enrnarbej
    import Data.Matrix 
     
    torres :: Int -> [Matrix Int]
    torres n =
      foldl (*) (identity n) . map (uncurry (permMatrix n)) <$> permutaciones [1..n]
     
    permutaciones :: [Int] -> [[(Int,Int)]]
    permutaciones [] = [[]]
    permutaciones p@(x:xs) =
      pxs ++ concat [map ((x,y):) pxs | y <- xs]
      where pxs = permutaciones xs
     
    nTorres :: Int -> Integer
    nTorres n = product [1..toInteger n]
  3. enrnarbej

    Una pequeña modificación de la solución de marjimcom que mejora ligeramente la eficacia.

    import Data.List (permutations)
    import Data.Matrix 
     
    torres :: Int -> [Matrix Int]
    torres n = aux n <$> permutations [1..n]
     
    aux :: Int -> [Int] -> Matrix Int
    aux n xs =  foldl (+) z [setElem 1 x z | x <- zip [1..n] xs]
      where z = zero n n
     
    --    *Main> length (torres2 11)
    --    39916800
    --    (4.32 secs, 18,843,026,656 bytes)
    --    *Main> length (torres 11)
    --    39916800
    --    (3.68 secs, 15,330,346,728 bytes)
  4. albcercid
     
    torres  :: Int -> [Matrix Int]
    torres n = map (creaMatriz n) (permutations [1..n])
         where creaMatriz a xs = matrix a a f        
                  where f x | elem x t = 1
                            | otherwise = 0
                        t = zip xs [1..a]
    nTorres :: Int -> Integer
    nTorres x = product [1..fromIntegral x]
  5. Juanjo Ortega (juaorture)
    import Data.Matrix
    import Data.List
     
    colocaTorres :: Matrix Int -> [Matrix Int]
    colocaTorres p = [ setElem 1 (i,j) p | i <- [1..nrows p]
                                         , j <- [1..ncols p]
                                         , all (==0) (getCol j p)
                                         , all (==0) (getRow i p)]
     
    torres :: Int -> [Matrix Int]
    torres n = nub (aux n (zero n n))
           where aux :: Int -> Matrix Int -> [Matrix Int]
                 aux 0 p = [p]
                 aux x p = concatMap (aux (x-1)) (colocaTorres p)
     
    nTorres :: Int -> Integer
    nTorres = genericLength . torres
     
    nTorres' :: Int -> Integer
    nTorres' n = product [1..fromIntegral n]

Escribe tu solución

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