DiffArray Performance

Adrian Hey ahey at iee.org
Mon Oct 27 11:25:11 EST 2003


Hello,

I've been trying to optimise the following code..

-- Search Tree data type
newtype STree = STree (Array Int (STree,[Match]))
-- Initial value for Search Tree
sTree0 :: STree
sTree0 = STree (array (0,9) [(n,(sTree0,[]))| n <- [0..9]])

-- Make the search tree from a list of words
makeSTree :: [String] -> STree
makeSTree ws = foldl' putWord sTree0 pairs where
  pairs = [let ps = packString w in ps `seq` (word2keys w, MatchW ps) | w<-ws]
  word2keys cs = [getKey (toUpper c) | c <- cs, c /= '"' , c /= '-' ]
  putWord stree (keys,m) = put keys stree
    where put []     _         = error "makeSTree: empty Keys"
          put [k]    (STree a) = let (t,ms) = a ! k
                                 in STree (a // [(k,(t,m:ms))])
          put (k:ks) (STree a) = let (t,ms) = a ! k
                                     t'     = put ks t 
                                 in t' `seq` STree (a // [(k,(t',ms))])

This seems to be taking about 4.8 seconds (of 5.1 seconds total
program execution time) for the input I'm using. I thought using
DiffArrays might be faster, but no such luck. Execution time rose
to 9.5 *minutes*.

Is this what I should expect to see?

I'm using ghc 6.0, BTW.

Thanks
--
Adrian Hey








More information about the Glasgow-haskell-users mailing list