Beginner's speed problem

Hi, I am trying to solve this problem: https://www.spoj.pl/problems/LASTDIG/ It is very simple. Given a and b, return the last digit of a^b. b could be large, so I used logarithmic exponentiation and wrote/submitted the code below for this problem: ---------------------------------------------------------------------- lastdigit :: Int -> Int -> Int -> Int lastdigit 0 0 _ = 1 lastdigit a b c | even b = lastdigit ( (a*a) `rem` 10 ) (b `quot` 2) c | b == 1 = (a*c) `rem` 10 | otherwise = lastdigit ( (a*a) `rem` 10 ) (b `quot` 2) (a*c) doit :: [Char] -> Int doit line = lastdigit (read $ head $ words line) (read $ last $ words line) 1 main = do n <- getLine inputs <- sequence $ take (read n) $ repeat getLine let slist = map doit inputs mapM_ (putStrLn.show) slist ------------------------------------------------------------------- As n in main is at most 30, I thought this would easily run in 1 second, but I get a time limit exceeded error on the site. Can someone tell me where my code is taking too much time? Thanks in advance! -- Aditya Manthramurthy

aditya87:
Hi,
I am trying to solve this problem: https://www.spoj.pl/problems/LASTDIG/ It is very simple. Given a and b, return the last digit of a^b. b could be large, so I used logarithmic exponentiation and wrote/submitted the code below for this problem:
---------------------------------------------------------------------- lastdigit :: Int -> Int -> Int -> Int lastdigit 0 0 _ = 1 lastdigit a b c | even b = lastdigit ( (a*a) `rem` 10 ) (b `quot` 2) c | b == 1 = (a*c) `rem` 10 | otherwise = lastdigit ( (a*a) `rem` 10 ) (b `quot` 2) (a*c)
doit :: [Char] -> Int doit line = lastdigit (read $ head $ words line) (read $ last $ words line) 1
main = do n <- getLine inputs <- sequence $ take (read n) $ repeat getLine let slist = map doit inputs mapM_ (putStrLn.show) slist -------------------------------------------------------------------
I notice an unnec. lazy 'c' argument to lastdigit, {-# LANGUAGE BangPatterns #-} lastdigit :: Int -> Int -> Int -> Int lastdigit 0 0 _ = 1 lastdigit a b !c | even b = lastdigit ( (a*a) `rem` 10 ) (b `quot` 2) c | b == 1 = (a*c) `rem` 10 | otherwise = lastdigit ( (a*a) `rem` 10 ) (b `quot` 2) (a*c) doit :: [Char] -> Int doit line = lastdigit (read $ head $ words line) (read $ last $ words line) 1 main = do n <- getLine inputs <- sequence $ take (read n) $ repeat getLine let slist = map doit inputs mapM_ (putStrLn.show) slist Would generate better code for lastdigit.

Am Mittwoch 02 Dezember 2009 22:44:01 schrieb Don Stewart:
aditya87:
Hi,
I am trying to solve this problem: https://www.spoj.pl/problems/LASTDIG/ It is very simple. Given a and b, return the last digit of a^b. b could be large, so I used logarithmic exponentiation and
Just to mention it, you can do something much much faster for this problem. Something in the microsecond range (if IO is fast enough, millisecond otherwise).
wrote/submitted the code below for this problem:
---------------------------------------------------------------------- lastdigit :: Int -> Int -> Int -> Int lastdigit 0 0 _ = 1 lastdigit a b c | even b = lastdigit ( (a*a) `rem` 10 ) (b `quot` 2) c
| b == 1 = (a*c) `rem` 10 | otherwise = lastdigit ( (a*a) `rem` 10 ) (b `quot` 2) | (a*c)
doit :: [Char] -> Int doit line = lastdigit (read $ head $ words line) (read $ last $ words line) 1
main = do n <- getLine inputs <- sequence $ take (read n) $ repeat getLine let slist = map doit inputs mapM_ (putStrLn.show) slist -------------------------------------------------------------------
I notice an unnec. lazy 'c' argument to lastdigit,
Though for <= 30 inputs and exponents < 2^31, the laziness shouldn't do too much harm, I think. Shouldn't push it over one second, now they've at last replaced 6.6.1.
{-# LANGUAGE BangPatterns #-}
lastdigit :: Int -> Int -> Int -> Int lastdigit 0 0 _ = 1 lastdigit a b !c | even b = lastdigit ( (a*a) `rem` 10 ) (b `quot` 2) c
| b == 1 = (a*c) `rem` 10
However, | otherwise = lastdigit ( (a*a) `rem` 10 ) (b `quot` 2) (a*c) is problematic. The (a*c), to be exact. The exponent may be close to 2^31, so up to 30 bits may be set. You then have a multiplication of up to 30 factors, the first is (< 20), the others (< 10), but it may easily overflow Int range, and then the last digit need not be correct. You need ((a*c) `rem` 10) there.
doit :: [Char] -> Int doit line = lastdigit (read $ head $ words line) (read $ last $ words line) 1
main = do n <- getLine inputs <- sequence $ take (read n) $ repeat getLine let slist = map doit inputs mapM_ (putStrLn.show) slist
I'd prefer main = do lns <- fmap lines getContents mapM_ (print . doit) $ tail lns or main = fmap lines getContents >>= mapM_ (print . doit) . tail
Would generate better code for lastdigit.

Hello
Thanks for all the help!
I only have a couple of questions.
On Thu, Dec 3, 2009 at 03:45, Daniel Fischer
Am Mittwoch 02 Dezember 2009 22:44:01 schrieb Don Stewart:
aditya87:
Hi,
I am trying to solve this problem: https://www.spoj.pl/problems/LASTDIG/ It is very simple. Given a and b, return the last digit of a^b. b could be large, so I used logarithmic exponentiation and
Just to mention it, you can do something much much faster for this problem. Something in the microsecond range (if IO is fast enough, millisecond otherwise).
I guess you mean that we can find the cycle that the last digits follow while multiplying repeatedly by a, and then use that. I'll try that next in Haskell!
{-# LANGUAGE BangPatterns #-}
lastdigit :: Int -> Int -> Int -> Int lastdigit 0 0 _ = 1 lastdigit a b !c | even b = lastdigit ( (a*a) `rem` 10 ) (b `quot` 2) c
| b == 1 = (a*c) `rem` 10
However,
| otherwise = lastdigit ( (a*a) `rem` 10 ) (b `quot` 2) (a*c)
This bang pattern (!c) is giving me pattern match errors. Is its only effect evaluating c instead of plain substitution? -- Aditya Manthramurthy

Am Donnerstag 03 Dezember 2009 06:52:01 schrieb Aditya M:
Hello
Thanks for all the help!
I only have a couple of questions.
On Thu, Dec 3, 2009 at 03:45, Daniel Fischer
wrote: Am Mittwoch 02 Dezember 2009 22:44:01 schrieb Don Stewart:
aditya87:
Hi,
I am trying to solve this problem: https://www.spoj.pl/problems/LASTDIG/ It is very simple. Given a and b, return the last digit of a^b. b could be large, so I used logarithmic exponentiation and
Just to mention it, you can do something much much faster for this problem. Something in the microsecond range (if IO is fast enough, millisecond otherwise).
I guess you mean that we can find the cycle that the last digits follow while multiplying repeatedly by a, and then use that.
Yes. Except there's not much finding to be done, you can pretty much write it down immediately. But I underestimated the slowness of String IO, so it's not gaining you terribly much unless you resort to ByteString IO. As an indication, for files containing 20.9 million, 2.85 million, 25942 (a,b) pairs respectively: ByteString + shortcut: 4.6 seconds, 0.66 seconds, 0.00 seconds ByteString + modular exponentiation: 49.2 seconds, 6.74 seconds, 0.06 seconds String + shortcut: 262 seconds, 35.04 seconds, 0.33 seconds String + modular exponentiation: 303 seconds, 40.73 seconds, 0.38 seconds (Note: I have tweaked the String IO, using main = fmap lines getContents >>= putStr . unlines . (map doit) . tail and modified doit (returns a String now, is a little stricter, calls words line only once; also read - for the base, I use (digitToInt . last), it's much faster than read) 1. With "replicateM n getLine" or "sequence $ take n $ repeat getLine", the entire input must be read in before processing can start. Firstly that's slower and secondly it needs a lot of memory - more than I have, for the larger files. 2. (putStr . unlines) is faster than mapM_ putStrLn. It could be tweaked more, but that wouldn't gain nearly as much as switching to ByteString.) So with String IO, in either method the overwhelming part of the time is used for IO (and read), in comparison, the algorithmic difference pales. With ByteString IO, the algorithmic difference stands out.
I'll try that next in Haskell!
{-# LANGUAGE BangPatterns #-}
lastdigit :: Int -> Int -> Int -> Int lastdigit 0 0 _ = 1 lastdigit a b !c | even b = lastdigit ( (a*a) `rem` 10 ) (b `quot` 2) c
| b == 1 = (a*c) `rem` 10
However,
| otherwise = lastdigit ( (a*a) `rem` 10 ) (b `quot` 2) (a*c)
This bang pattern (!c) is giving me pattern match errors.
??? without the LANGUAGE pragma, it would give a parse error, so you can't have forgotten that. But in lastdigit :: Int -> Int -> Int -> Int lastdigit 0 0 _ = 1 lastdigit a b !c | even b = lastdigit ( (a*a) `rem` 10 ) (b `quot` 2) c | b == 1 = (a*c) `rem` 10 | otherwise = lastdigit ( (a*a) `rem` 10 ) (b `quot` 2) ((a*c) `rem` 10) there is simply no possibility for a pattern match error (other than having one argument bottom). I'm flabbergasted.
Is its only effect evaluating c instead of plain substitution?
Yes, it keeps c evaluated instead of building a thunk. You can get pretty much the same effect by having lastdigit :: Int -> Int -> Int -> Int lastdigit 0 0 _ = 1 lastdigit a b c | even b = lastdigit ( (a*a) `rem` 10 ) (b `quot` 2) c | b == 1 = (a*c) `rem` 10 | otherwise = lastdigit ( (a*a) `rem` 10 ) (b `quot` 2) $! ((a*c) `rem` 10) using strict application on the last argument when it is modified.
participants (3)
-
Aditya M
-
Daniel Fischer
-
Don Stewart