Re: [Haskell-cafe] Help understanding Haskell runtime costs

2011-08-11 Thread Henning Thielemann

On 09.08.2011 01:43, Thiago Negri wrote:

Hello all,

I'm relatively new to Haskell and trying to solve some online judge's
problems in it.
One of the problems is to say if a given sentence is a tautogram or not.
A tautogram is just a sentence with all the words starting with the same letter.

My first try (solution is ok) was to do it as haskeller as possible,
trying to overcome my imperative mind.
But it did bad at performance (0.30 secs of runtime, 4.6 mb of memory):

-- code start
import Data.Char (toLower)

main = getContents=  mapM_ (putStrLn . toStr . isTautogram . words)
. takeWhile (/= *) . lines


That's still imperative! :-)

How about 'interact' and using 'unlines' instead of 'putStrLn' ?



toStr :: Bool -  [Char]


You may want to write String instead of [Char] for clarity.


toStr True = Y
toStr False = N

isTautogram :: [[Char]] -  Bool
isTautogram (x:[]) = True


I assume this case is not necessary, since  all [] == True  anyway.


isTautogram (x:xs) = all ((== firstChar) . toLower . head) xs
 where firstChar = toLower . head $ x


It is maybe more elegant, not to compare all words with the first one, 
but to compare adjacent words in the list:


all (zipWith (...) xs (drop 1 xs))



Note that the only thing that changed between the two tries was the main-loop.
The second version runs faster (got 0.11 secs) and with less memory (3.6 mb)

Can someone explain to me what is really going on?
Maybe pointing out how I can achieve these optimizations using
profiling information...


Interesting observation. I do not see a problem quickly.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Help understanding Haskell runtime costs

2011-08-11 Thread Thiago Negri
So, thanks to Henning Thielemann I was able to make a code a little
more functional.
I did find ByteString module that really speed things up.

I got 0.04 seconds with the following snippet:

-- code start
import qualified Data.ByteString.Char8 as BS
import Data.Char (toLower)

main :: IO ()
main = interact' $ unlines' . solveAll . takeWhile ((/= '*') . head') . lines'

solveAll :: [String'] - [String']
solveAll = map $ toStr . solve

toStr :: Bool - String'
toStr True = makeString' Y
toStr False = makeString' N

solve :: String' - Bool
solve = isTautogram . words'

isTautogram :: [String'] - Bool
isTautogram (x:xs) = all ((== firstChar) . normalizeHead) xs
where firstChar = normalizeHead x

normalizeHead :: String' - Char
normalizeHead = toLower . head'

-- optimizations
type String' = BS.ByteString
interact' = BS.interact
unlines' = BS.unlines
lines' = BS.lines
head' = BS.head
words' = BS.words
makeString' = BS.pack
-- code end

Thanks all,
Thiago.

2011/8/11 Henning Thielemann schlepp...@henning-thielemann.de:
 On 09.08.2011 01:43, Thiago Negri wrote:

 Hello all,

 I'm relatively new to Haskell and trying to solve some online judge's
 problems in it.
 One of the problems is to say if a given sentence is a tautogram or not.
 A tautogram is just a sentence with all the words starting with the same
 letter.

 My first try (solution is ok) was to do it as haskeller as possible,
 trying to overcome my imperative mind.
 But it did bad at performance (0.30 secs of runtime, 4.6 mb of memory):

 -- code start
 import Data.Char (toLower)

 main = getContents=  mapM_ (putStrLn . toStr . isTautogram . words)
 . takeWhile (/= *) . lines

 That's still imperative! :-)

 How about 'interact' and using 'unlines' instead of 'putStrLn' ?


 toStr :: Bool -  [Char]

 You may want to write String instead of [Char] for clarity.

 toStr True = Y
 toStr False = N

 isTautogram :: [[Char]] -  Bool
 isTautogram (x:[]) = True

 I assume this case is not necessary, since  all [] == True  anyway.

 isTautogram (x:xs) = all ((== firstChar) . toLower . head) xs
     where firstChar = toLower . head $ x

 It is maybe more elegant, not to compare all words with the first one, but
 to compare adjacent words in the list:

 all (zipWith (...) xs (drop 1 xs))


 Note that the only thing that changed between the two tries was the
 main-loop.
 The second version runs faster (got 0.11 secs) and with less memory (3.6
 mb)

 Can someone explain to me what is really going on?
 Maybe pointing out how I can achieve these optimizations using
 profiling information...

 Interesting observation. I do not see a problem quickly.

 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Help understanding Haskell runtime costs

2011-08-08 Thread Thiago Negri
Hello all,

I'm relatively new to Haskell and trying to solve some online judge's
problems in it.
One of the problems is to say if a given sentence is a tautogram or not.
A tautogram is just a sentence with all the words starting with the same letter.

My first try (solution is ok) was to do it as haskeller as possible,
trying to overcome my imperative mind.
But it did bad at performance (0.30 secs of runtime, 4.6 mb of memory):

-- code start
import Data.Char (toLower)

main = getContents =  mapM_ (putStrLn . toStr . isTautogram . words)
. takeWhile (/= *) . lines

toStr :: Bool - [Char]
toStr True = Y
toStr False = N

isTautogram :: [[Char]] - Bool
isTautogram (x:[]) = True
isTautogram (x:xs) = all ((== firstChar) . toLower . head) xs
where firstChar = toLower . head $ x
-- code end

I tried to profile the code, but didn't find anything useful.
My bet is that all this words . lines is consuming more memory than
necessary, maybe saving space for the lines already processed.
Then I tried a some-what tail-call function, consuming one line at
each iteration:

-- code start
import Data.Char (toLower)

main :: IO ()
main = getLine = mainLoop

mainLoop :: [Char] - IO ()
mainLoop s | (head s) == '*' = return ()
   | otherwise   = (putStrLn . toStr . isTautogram . words
$ s)  main

toStr :: Bool - [Char]
toStr True = Y
toStr False = N

isTautogram :: [[Char]] - Bool
isTautogram (x:[]) = True
isTautogram (x:xs) = all ((== firstChar) . toLower . head) xs
where firstChar = toLower . head $ x
-- code end

Note that the only thing that changed between the two tries was the main-loop.
The second version runs faster (got 0.11 secs) and with less memory (3.6 mb)

Can someone explain to me what is really going on?
Maybe pointing out how I can achieve these optimizations using
profiling information...

Thanks,
Thiago.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe