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. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe