[Haskell-cafe] Stack overflow with my Trie implementation

Adrian Hey ahey at iee.org
Thu Apr 26 15:37:53 EDT 2007


Adrian Hey wrote:
> Pete Kazmier wrote:
>> I've modified my Norvig spelling corrector to use a trie instead of
>> Data.Map in the hopes of improving performance.  Plus, this is fun and
>> a great learning exercise for me.  Unfortunately, when I load my trie
>> with a large amount of data, I get a stack overflow.  It's unclear to
>> me why this is happening.  I specifically use foldl' to avoid this
>> situation when building my trie.  Could someone shed some light on the
>> situation for me?
>>
>> Here is the code:
>>
>>> module Main where
>>> import Data.List (foldl')
>>> import Data.Maybe (maybe, fromMaybe)
>>> import Prelude hiding (lookup)
>>> import qualified Data.Map as M
>>>
>>> data Trie a = T (Maybe a) (M.Map Char (Trie a)) deriving (Show)
> 
> Try making it strict in the Map field..
> 
>  > data Trie a = T (Maybe a) !(M.Map Char (Trie a)) deriving (Show)

Hmm, strictness is a slippery thing, so I think you'll also
need to use strict insertion for the Map. I believe such a thing
was added a while back, but with your code you could use

 >insertWith fn (k:ks) v (T mv m) = newtrie `seq` T mv (M.insert k 
newtrie m)
 >     where
 >       oldtrie = M.findWithDefault empty k m
 >       newtrie = insertWith fn ks v oldtrie

BTW, if you use strict insertion function (insertWith') it shouldn't
be necessary to do a lookup first.

Regards
--
Adrian Hey







More information about the Haskell-Cafe mailing list