[Haskell] Re: performance tuning Data.FiniteMap

S. Alexander Jacobson alex at i2x.com
Mon Mar 1 22:08:15 EST 2004


On Fri, 27 Feb 2004 oleg at pobox.com wrote:
> 	If indeed the read performance is at premium and updates are
> infrequent, by bother with ternary etc. trees -- why not to use just a
> single, one-level array. Given a reasonable hash function

Because updates are not so infrequent that I want
to pay the cost of replicating the entire array
every update (or every ten!).  I'm willing to
exchange *some* read time for faster update. Also,
because small array copies may be sufficiently
faster than tree traversals that I may pay very
little extra for faster reads.

FYI, my current code looks like this:

  type HTArray base elt = Array base (HT base elt)
  data HT base elt = HT (Maybe (HTArray base elt)) (Maybe elt)
  data MyMap base key elt = ArrMap (HTArray base elt) (key->[base]) (HT base elt)

  newMap minBase maxBase toBase = ArrMap proto toBase emptyHT
	where
	proto= array (minBase,maxBase) [(x,emptyHT) | x<- [minBase..maxBase]]
	emptyHT=HT Nothing Nothing

  lookup (ArrMap _ toBase ht) key = lookup' ht $ toBase key
  lookup' (HT x y) [] = y
  lookup' (HT Nothing _) _ = Nothing
  lookup' (HT (Just ar) _) (k:ey) = lookup' (ar!k) ey

  insert (ArrMap proto toBase ht) key elt = ArrMap proto toBase newHT
     where newHT= insert' proto ht (toBase key) elt
  insert' _ (HT x _) [] = HT x
  insert' proto (HT Nothing y) key = insert' proto (HT (Just proto) y) key
  insert' p (HT (Just ar) y) (k:ey) = \val -> HT (Just $ newArray val) y
	where newArray val = ar//[(k,insert' p (ar!k) ey val)]

  -----

  testMap=newMap (chr 0) (chr 255) id
  main = do print $ lookup (insert testMap "abc" (Just "def")) "abc"

Make the difference between in minBase and
maxBase larger in the call to newMap to prefer
reads more.

Note: This format seems awkward.  I feel like I
want to have the user to define an enumeration
type e.g.

  data UpToFive = One | Two | Three | Four | Five
  instance Ix UpToFive where....

and have

  newMap::(Bounded base,Ix base)=>(key->[base]) -> MyMap base key elt

But I can't figure out a nice way to auto-generate
arbitrary size enumerations and manually doing so
is too wearisome to contemplate.

If you can generate these enumeration classes,
then it would seem you could auto-derive functions
that translate from an arbitrary key into [base].

-Alex-

_________________________________________________________________
S. Alexander Jacobson                  mailto:me at alexjacobson.com
tel:917-770-6565                       http://alexjacobson.com


More information about the Haskell mailing list