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 representa 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)
Ejercicio

7 soluciones de “El problema de las N torres

  1. carmengar
    import Data.List
    import Data.Matrix as M
     
     
    torres :: Int -> [Matrix Int]
    torres n = map f (permutations [1..n])
             where f xs = matrix n n ((i,j) -> if j /= xs!!(i-1) then 0
                                                else 1) 
     
    factorial :: Integer -> Integer
    factorial 0 = 1
    factorial n = factorial (n-1) * n
     
    nTorres :: Int -> Integer
    nTorres = factorial . toInteger
  2. erisan
    import Data.List
    import Data.Matrix 
     
     
    torres  :: Int -> [Matrix Int]
    torres n = [matrix n n ((i,j) -> if j /= ys!!(i-1) then 0 else 1) | ys  <- permutations [1..n]]
     
    nTorres :: Int -> Integer
    nTorres n = factoriales !! n
     
     
    factoriales :: [Integer]
    factoriales = map snd aux
        where aux = iterate f (1,1) where f (x,y) = (x+1,x*y)
  3. Chema Cortés
    import Data.Matrix
    import Data.List (permutations)
     
    torres  :: Int -> [Matrix Int]
    torres n = [ fromLists xs | xs <- (permutations . toLists) i ]
        where i = identity n
     
    nTorres :: Int -> Integer
    nTorres n = product [1..fromIntegral n]
    • carmengar

      Tu definición de torres se puede simplificar:

      torres :: Int -> [Matrix Int]
      torres = map fromLists . permutations . toLists . identity
  4. fracruzam
    import Data.List
    import Data.Matrix
     
    torres  :: Int -> [Matrix Int]
    torres n = map setTablero (permutations [1..n])
      where setTablero :: [Int] -> Matrix Int
            setTablero xs = foldr (p -> setElem 1 p) (zero n n) (zip [1..] xs)
     
    nTorres :: Int -> Integer
    nTorres n = product [1..fromIntegral n]
  5. abrdelrod

    Mediante búsqueda en espacios de estados (en esta ocasión no resulta ser el método más eficiente):

    import I1M.BusquedaEnEspaciosDeEstados
    import Data.Matrix
    import Data.List
     
    torres :: Int -> [Matrix Int]
    torres n = 
        map ((x,_,_) -> x) (buscaEE sucesores esFinal (zero n n,1,[]))
        where esFinal (_,m,_)    = m == n+1
              sucesores (p,m,xs) = [(setElem 1 (i,m) p,m+1,i:xs) | i <- [1..n] \ xs]
  6. alvalvdom1
    import Data.List
    import Data.Matrix
     
    torres  :: Int -> [Matrix Int]
    torres n = map fromLists [map (fila n) xs | xs <- permutations [1..n]]
             where fila :: Int -> Int -> [Int]
                   fila n m = replicate (m-1) 0 ++ [1] ++ replicate (n-m) 0
     
    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.