Send Beginners mailing list submissions to
        beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
        http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
        beginners-requ...@haskell.org

You can reach the person managing the list at
        beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than "Re: Contents of Beginners digest..."


Today's Topics:

   1. Re:  CSES programming problems at https://cses.fi/problemset/
      (Irfon-Kim Ahmad)
   2. Re:  CSES programming problems at https://cses.fi/problemset/
      (Julian Ong)
   3. Re:  CSES programming problems at https://cses.fi/problemset/
      (Julian Ong)


----------------------------------------------------------------------

Message: 1
Date: Sun, 28 Jun 2020 12:48:12 -0400
From: Irfon-Kim Ahmad <ir...@ambienautica.com>
To: beginners@haskell.org
Subject: Re: [Haskell-beginners] CSES programming problems at
        https://cses.fi/problemset/
Message-ID: <0bcd69e9-10d4-3f41-274f-8e860692a...@ambienautica.com>
Content-Type: text/plain; charset="utf-8"; Format="flowed"

On 2020-06-28 11:26 a.m., Doug McIlroy wrote:
>> I'm currently stuck on the Two Knights problem.
> Having placed one knight on the board, in how many
> places can you put the other?

If you check the website indicated, it's a slight variation on that:

"Your task is to count for k=1,2,…,nthe number of ways two knights can 
be placed on a k×kchessboard so that they do not attack each other."

The input is n (an integer that can range from 1 to 10000), the output 
is a single integer for each value from 1 to n, one per line, the memory 
limit is 512MB, and the maximum runtime is 1.00 seconds.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://mail.haskell.org/pipermail/beginners/attachments/20200628/60d748f0/attachment-0001.html>

------------------------------

Message: 2
Date: Sun, 28 Jun 2020 23:27:07 +0000 (UTC)
From: Julian Ong <julian_...@yahoo.com>
To: beginners@haskell.org
Subject: Re: [Haskell-beginners] CSES programming problems at
        https://cses.fi/problemset/
Message-ID: <1817199903.471182.1593386827...@mail.yahoo.com>
Content-Type: text/plain; charset="utf-8"

 I realized I did not answer the question Doug posed, but the algorithm as 
originally presented works correctly and calculates correctly the number of 
possible knight pairings for each k x k board and generates the correct output 
requested by the problem.
The issue is still that, as I have implemented it in Haskell, it doesn't run 
fast enough to pass the automated CSES testing for n=10000. I am very curious 
whether it's possible to pass the speed testing for this problem using Haskell 
and if so how.
    On Sunday, June 28, 2020, 09:49:02 AM PDT, Irfon-Kim Ahmad 
<ir...@ambienautica.com> wrote:  
 
  On 2020-06-28 11:26 a.m., Doug McIlroy wrote:
  
  
 I'm currently stuck on the Two Knights problem.
 
 Having placed one knight on the board, in how many
places can you put the other?
 
 
If you check the website indicated, it's a slight variation on that: 
 
 
"Your task is to count for k=1,2,…,n the number of ways two knights can be 
placed on a k×k chessboard so that they do not attack each other."
 
 
The input is n (an integer that can range from 1 to 10000), the output is a 
single integer for each value from 1 to n, one per line, the memory limit is 
512MB, and the maximum runtime is 1.00 seconds. 

  

 
 _______________________________________________
Beginners mailing list
Beginners@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
  
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://mail.haskell.org/pipermail/beginners/attachments/20200628/5ead1b1b/attachment-0001.html>

------------------------------

Message: 3
Date: Sun, 28 Jun 2020 23:45:18 +0000 (UTC)
From: Julian Ong <julian_...@yahoo.com>
To: beginners@haskell.org
Subject: Re: [Haskell-beginners] CSES programming problems at
        https://cses.fi/problemset/
Message-ID: <1581505561.464885.1593387918...@mail.yahoo.com>
Content-Type: text/plain; charset="utf-8"

 I've simplified and optimized it slightly (no need to use a monad for 
moveKnightUR) but overall it's still not fast enough to pass the CSES test. I'm 
wondering if the recursion is somehow inefficient because of two instances of 
solveK (k-1)...?---- main :: IO ()main = do    line <- getLine    let n = read 
line :: Integer    putStr $ unlines $ map show $ reverse $ solveK n

solveK :: Integer -> [Integer]solveK k    | k == 1 = [0]    | otherwise = 
(solveFrameK k + head (solveK (k-1))) : solveK (k-1)
-- Returns list of knight moves in the upper right (k-1) x (k-1) portion of the 
board excluding the first column and first rowmoveKnightUR :: Integer -> 
(Integer, Integer) -> [(Integer, Integer)]moveKnightUR k (c, r) = filter (\(c', 
r') -> c' `elem` [2..k] && r' `elem` [2..k]) [(c-1, r+2), (c+1, r+2), (c+2, 
r+1), (c+2, r-1), (c+1, r-2), (c-2, r+1)]    -- Returns list of left and bottom 
border squares for k x k board in (col, row) format with (1, 1) being the lower 
left squaregenBorder :: Integer -> [(Integer, Integer)]genBorder k = [(1, a) | 
a <- [1..k]] ++ [(a, 1) | a <- [2..k]]
-- Formula for combinations C(n, r)combinations :: Integer -> Integer -> 
Integercombinations n r = product [1..n] `div` (product [1..(n-r)] * product 
[1..r])
-- Calculates additional number of two knight placements along the left and 
bottom border and from that border into the upper right (k-1) x (k-1) 
regionsolveFrameK :: Integer -> IntegersolveFrameK k    | k == 1 = 0    | k == 
2 = 6    | otherwise = ((combinations (2*k-1) 2) - 2) + (k-1) * (k-1) * (2*k-1) 
- sum (map (toInteger . length) (map (moveKnightUR k) (genBorder k)))----
Julian
    On Sunday, June 28, 2020, 04:27:07 PM PDT, Julian Ong 
<julian_...@yahoo.com> wrote:  
 
  I realized I did not answer the question Doug posed, but the algorithm as 
originally presented works correctly and calculates correctly the number of 
possible knight pairings for each k x k board and generates the correct output 
requested by the problem.
The issue is still that, as I have implemented it in Haskell, it doesn't run 
fast enough to pass the automated CSES testing for n=10000. I am very curious 
whether it's possible to pass the speed testing for this problem using Haskell 
and if so how.
    On Sunday, June 28, 2020, 09:49:02 AM PDT, Irfon-Kim Ahmad 
<ir...@ambienautica.com> wrote:  
 
  On 2020-06-28 11:26 a.m., Doug McIlroy wrote:
  
  
 I'm currently stuck on the Two Knights problem.
 
 Having placed one knight on the board, in how many
places can you put the other?
 
 
If you check the website indicated, it's a slight variation on that: 
 
 
"Your task is to count for k=1,2,…,n the number of ways two knights can be 
placed on a k×k chessboard so that they do not attack each other."
 
 
The input is n (an integer that can range from 1 to 10000), the output is a 
single integer for each value from 1 to n, one per line, the memory limit is 
512MB, and the maximum runtime is 1.00 seconds. 

  

 
 _______________________________________________
Beginners mailing list
Beginners@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
    
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://mail.haskell.org/pipermail/beginners/attachments/20200628/a32cbec0/attachment.html>

------------------------------

Subject: Digest Footer

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners


------------------------------

End of Beginners Digest, Vol 144, Issue 7
*****************************************

Reply via email to