
Bang patterns are easy: they make a part of the pattern strict by seq'ing it.
f (x, !y) = ...
~
f (x, y) = y `seq` ...
2009/8/30 Steve
On Sun, 2009-08-30 at 16:34 +0400, Eugene Kirpichov wrote:
Here's my version that works in 0.7s for me for a file with 10^7 "999999999"'s but for some reason gets a 'wrong answer' at SPOJ :)
{-# LANGUAGE BangPatterns #-} module Main where
import qualified Data.ByteString.Lazy as B import Data.Word
answer :: Int -> B.ByteString -> Int answer k = fst . B.foldl' f (0, 0) where f :: (Int,Int) -> Word8 -> (Int,Int) f (!countSoFar, !x) 10 | x`mod`k==0 = (countSoFar+1, 0) | otherwise = (countSoFar, 0) f (!countSoFar, !x) c = (countSoFar, 10*x+(fromIntegral c)-48)
readInt :: B.ByteString -> Int readInt = B.foldl' (\x c -> 10*x+fromIntegral c-48) 0
main = do (line, rest) <- B.break (==10) `fmap` B.getContents let [n, k] = map readInt . B.split 32 $ line putStrLn . show $ answer k rest - 1
Eugene, I ran your code on one of my test files and it gave the same answer as my code. So I submitted it and it was accepted. Its fast - twice as fast as my solution, using much less memory. Overall its the 4th fastest Haskell solution. (but its still 10 * slower than C/C++) I'll have to read up on BangPatterns to try to understand what its doing!
I submitted it as:
{-# LANGUAGE BangPatterns #-} module Main where
import qualified Data.ByteString.Lazy as B import qualified Data.Word as DW
answer :: Int -> B.ByteString -> Int answer k = fst . B.foldl' f (0, 0) where f :: (Int,Int) -> DW.Word8 -> (Int,Int) f (!countSoFar, !x) 10 | x`mod`k==0 = (countSoFar+1, 0) | otherwise = (countSoFar, 0) f (!countSoFar, !x) c = (countSoFar, 10*x+(fromIntegral c)-48)
readInt :: B.ByteString -> Int readInt = B.foldl' (\x c -> 10*x+fromIntegral c-48) 0
main :: IO () main = do (line, rest) <- B.break (==10) `fmap` B.getContents let [_, k] = map readInt . B.split 32 $ line putStrLn . show $ answer k rest - 1
-- Eugene Kirpichov Web IR developer, market.yandex.ru