[Haskell-beginners] Diagnosing : Large memory usage + low CPU

Hugo Ferreira hmf at inescporto.pt
Tue Nov 29 12:20:19 CET 2011


Hello,

I am testing a simple algorithm and find that during part of the
execution this is fast and uses acceptable memory. However, when
it gets to a certain point the memory climbs to 75-80 % of the
OS's memory and CPU plummets to a mere 5% at most.

In the part of the application that executes ok I have calls as
follows:

   let r9' = evalTagger'' (tagFun suffixCapsFreq) $ test
   let a9' = tagginAccuracy r9'
   putStrLn ("Suffix(3) + Caps + Freq tag result done = "  ++ (show a9'))


The slow one has:

   let r12' = evalTagger'' ruleSuffixCapsFreq $ test
   let a12' = tagginAccuracy r12'
   putStrLn ("Rules + Suffix(3) + Caps + Freq tag result done = " ++ 
(show a12'))


The difference lies in the following functions:

ruleApplication :: TransformationRule -> POSTags -> Maybe Tag
ruleApplication (NextTagRule (Replacement old new) next) z = do
   (_, _, proposed)     <- Z.safeCursor z
   (_, _, nextProposed) <- rightCursor z
   if proposed == old && nextProposed == next then Just new else Nothing
....

updateState :: (TransformationRule,Int) -> POSTags -> POSTags
updateState r = Z.fromList . reverse . Z.foldlz' (update r) []
     where update (r,_) !xs z =
               case ruleApplication r z of
                 Just tag -> (token, correct, tag):xs
                 Nothing  -> e:xs
               where e@(token, correct, _proposed) = Z.cursor z

rulesT :: [(TransformationRule, Int)] -> POSTags -> POSTags
rulesT rs state = L.foldl' tag state rs
   where
     tag !s rule = updateState rule s

(.>) :: (POSTags -> Tag) -> (POSTags -> Tag) -> POSTags -> Tag
f .> g = \ x ->
            case (g x) of
              "" -> f x
              t -> t

(|>) :: (POSTags -> POSTags) -> (POSTags -> Tag) -> POSTags -> POSTags
f |> g = \ x -> f $ tagFun g x

let ruleT = rulesT top10Rules

let suffixCapsFreq = suffixT .> capitalizeT .> freqT
let ruleSuffixCapsFreq = ruleT |> suffixCapsFreq

where top10Rules is a list. Note that suffixCapsFreq and tagFun
are common to both calls.

I have placed bangs in many places and used eager evaluation in the
folds. However nothing seems to help. Can anyone tell me how I should
diagnose this problem. Any suggestions are welcome.

TIA,
Hugo F.






More information about the Beginners mailing list