Send Beginners mailing list submissions to
        beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
        http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
        beginners-requ...@haskell.org

You can reach the person managing the list at
        beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than "Re: Contents of Beginners digest..."


Today's Topics:

   1.  Performance problem (Jefferson Andrade)
   2.   Performance problem (Rados?aw Szymczyszyn)


----------------------------------------------------------------------

Message: 1
Date: Wed, 30 May 2012 02:03:32 -0300
From: Jefferson Andrade <joandr...@gmail.com>
Subject: [Haskell-beginners] Performance problem
To: beginners@haskell.org
Message-ID:
        <ca+u7k5gg7vr5_+we1hwonbjjpslcakb0snxtsr7qu51-utn...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

Hi!

I have a basic knowledge about Haskell and I am trying to put this
knowledge to work with a few exercises. The one I am trying now is
basically the following.

1. I must read from the standard input a series of text lines. Each line
represents a command that must be performed. The possible commands are:
add <id> <first-name> <last-name> <birth-date> <phone-number>
del <id>
info <id>
query (key:value)+

2. Each command may or may not generate an output on the standard output
according to a series of conditions (if an entry with the same ID already
exists, if the id of a del does not exists, if the id of an info does not
exists). Also, the info and query command also generate output on the
normal working.

3. The program is working, I suppose, but when I submit it for testing and
ranking on spoj.pl I get a timeout. The maximum allowed time for this
problem is 6s.

My code is the following:

===== Begin of source code =====

-- Problem id: HASHADQI

import qualified Data.List as List
import qualified Data.IntMap as Map
import Data.Maybe

type Person = (String,String,String,String)
type IntPersonMap = Map.IntMap Person

main = do
  input <- getContents
  seqAction Map.empty $ lines input

seqAction :: IntPersonMap -> [String] -> IO IntPersonMap
seqAction m [] = return m
seqAction m (l:ls) = do
  m' <- doAction m l
  seqAction m' ls

doAction :: IntPersonMap -> String -> IO IntPersonMap
doAction m cmd = do
  case cmd of
    'a':cs -> doInsert m (words cmd)
    'd':cs -> doDelete m (words cmd)
    'i':cs -> doInfo m (words cmd)
    'q':cs -> doQuery m (words cmd)
    [] -> return m

doInsert :: IntPersonMap -> [String] -> IO IntPersonMap
doInsert m [_, idText, fn, ln, bd, pn] = do
  let id = read idText :: Int
  if Map.member id m
    then do putStrLn $ "ID " ++ show id ++ " ja cadastrado."
            return m
    else return (Map.insert id (fn, ln, bd, pn) m)

doDelete :: IntPersonMap -> [String] -> IO IntPersonMap
doDelete m [_, idText] = do
  let id = read idText :: Int
  if Map.member id m
    then return (Map.delete id m)
    else do putStrLn $ "ID " ++ show id ++ " nao existente."
            return m

doInfo :: IntPersonMap -> [String] -> IO IntPersonMap
doInfo m [_, idText] = do
  let id = read idText :: Int
  case Map.lookup id m of
    Just (fn, ln, bd, pn) -> do putStrLn $ unwords [fn, ln, bd, pn]
                                return m
    Nothing -> do putStrLn $ "ID " ++ show id ++ " nao existente."
                  return m

doQuery :: IntPersonMap -> [String] -> IO IntPersonMap
doQuery m (_:qs) = do
  let test = (\x -> foldl (&&) True $ map ($x) $ makePredicate qs)
      result = Map.filter test m
  putStrLn $ unwords . map show $ Map.keys result
  return m

makePredicate :: [String] -> [(Person -> Bool)]
makePredicate [] = []
makePredicate (q:qs) =
  case List.break (==':') q of
    ("fn", ':':x) -> (\(fn,_,_,_) -> fn == x) : (makePredicate qs)
    ("ln", ':':x) -> (\(_,ln,_,_) -> ln == x) : (makePredicate qs)
    ("bd", ':':x) -> (\(_,_,bd,_) -> bd == x) : (makePredicate qs)
    ("pn", ':':x) -> (\(_,_,_,pn) -> pn == x) : (makePredicate qs)

===== End of source code =====

Can any one explain where is the source(s) of inefficiency and suggest how
to make this program more efficient?

Thanks in advance,
Jeff.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20120530/80fe29f1/attachment-0001.htm>

------------------------------

Message: 2
Date: Wed, 30 May 2012 11:07:22 +0200
From: Rados?aw Szymczyszyn <lav...@gmail.com>
Subject: [Haskell-beginners]  Performance problem
To: beginners@haskell.org
Message-ID:
        <CAG=dco2ff0z83+g+tvhjrpw1uwu066zr4pa0y5-ga+ordvr...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

Hello!

I've had a similar problem with text processing discussed on the list
some time ago (a topic about implementing a spellchecker). To keep
things short'n'simple: built-in Haskell Strings are inefficient as
they're simply lists of Chars, i.e. a String is in fact just a [Char].

The usually suggested solution to this problem is using the ByteString
type which comes from bytestring package. It's probably all nice when
you only need ASCII/Latin encodings, but it bite me when processing
Unicode (e.g. Data.ByteString.UTF8 doesn't have a words function,
though Data.ByteString has one). However, the performance is good.

The best solution as far as I have researched is the text package and
type Text. It ought to support Unicode as far as I remember and has
got all the useful list-like functions. As I hadn't yet had an
occasion to play with it before, I took your code and adapted it to
use Text and Text.IO. Let me know what are the results, as I haven't
got any test set to compare the speed before and after the
modifications.

=== CODE

-- Problem id: HASHADQI

import qualified Data.List as List
import qualified Data.IntMap as Map
import Data.Maybe

import Data.Text (Text)
import qualified Data.Text ? ?as T
import qualified Data.Text.IO as T

type Person = (Text,Text,Text,Text)
type IntPersonMap = Map.IntMap Person

main = do
?input <- T.getContents
?seqAction Map.empty $ T.lines input

seqAction :: IntPersonMap -> [Text] -> IO IntPersonMap
seqAction m [] = return m
seqAction m (l:ls) = do
?m' <- doAction m l
?seqAction m' ls

doAction :: IntPersonMap -> Text -> IO IntPersonMap
doAction m cmd = do
?case T.unpack (T.take 1 cmd) of
? ?"a" -> doInsert m $ T.words cmd
? ?"d" -> doDelete m $ T.words cmd
? ?"i" -> doInfo m $ T.words cmd
? ?"q" -> doQuery m $ T.words cmd
? ?[] -> return m

doInsert :: IntPersonMap -> [Text] -> IO IntPersonMap
doInsert m [_, idText, fn, ln, bd, pn] = do
?let id = read (T.unpack idText) :: Int
?if Map.member id m
? ?then do putStrLn $ "ID " ++ show id ++ " ja cadastrado."
? ? ? ? ? ?return m
? ?else return (Map.insert id (fn, ln, bd, pn) m)

doDelete :: IntPersonMap -> [Text] -> IO IntPersonMap
doDelete m [_, idText] = do
?let id = read (T.unpack idText) :: Int
?if Map.member id m
? ?then return (Map.delete id m)
? ?else do putStrLn $ "ID " ++ show id ++ " nao existente."
? ? ? ? ? ?return m

doInfo :: IntPersonMap -> [Text] -> IO IntPersonMap
doInfo m [_, idText] = do
?let id = read (T.unpack idText) :: Int
?case Map.lookup id m of
? ?Just (fn, ln, bd, pn) -> do putStrLn . show $ T.unwords [fn, ln, bd, pn]
? ? ? ? ? ? ? ? ? ? ? ? ? ? ? ?return m
? ?Nothing -> do putStrLn $ "ID " ++ show id ++ " nao existente."
? ? ? ? ? ? ? ? ?return m

doQuery :: IntPersonMap -> [Text] -> IO IntPersonMap
doQuery m (_:qs) = do
?let test = (\x -> foldl (&&) True $ map ($x) $ makePredicate qs)
? ? ?result = Map.filter test m
?putStrLn $ unwords . map show $ Map.keys result
?return m

makePredicate :: [Text] -> [(Person -> Bool)]
makePredicate [] = []
makePredicate (q:qs) =
?case (\(a,b) -> (T.unpack a, b)) (T.break (==':') q) of
? ?("fn", x) -> (\(fn,_,_,_) -> fn == (T.drop 1 x)) : (makePredicate qs)
? ?("ln", x) -> (\(_,ln,_,_) -> ln == (T.drop 1 x)) : (makePredicate qs)
? ?("bd", x) -> (\(_,_,bd,_) -> bd == (T.drop 1 x)) : (makePredicate qs)
? ?("pn", x) -> (\(_,_,_,pn) -> pn == (T.drop 1 x)) : (makePredicate qs)

=== END CODE

Regards,
Radek Szymczyszyn



------------------------------

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 47, Issue 29
*****************************************

Reply via email to