[Haskell-cafe] Beginner's speed problem
Don Stewart
dons at galois.com
Wed Dec 2 16:44:01 EST 2009
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.
More information about the Haskell-Cafe
mailing list