RFC: Should Data.IntMap.Strict be value-strict in the function arguments or the map itself

Edward Z. Yang ezyang at MIT.EDU
Thu Oct 27 19:17:04 CEST 2011


Here's the definition of Tip.

    data IntMap a = Bin {-# UNPACK #-} !Prefix {-# UNPACK #-} !Mask !(IntMap a) !(IntMap a)
                  | Tip {-# UNPACK #-} !Key a
                  | Nil

So we effectively have:

     insert :: Key -> a -> IntMap a -> IntMap a
     insert k x t =
       case t of
         Bin p m l r
           | nomatch k p m -> join k (Tip k x) p t
           | zero k m -> Bin p m (insert k x l) r
           | otherwise -> Bin p m l (insert k x r)
         Tip ky _
           | k==ky -> Tip k x
           | otherwise -> join k (Tip k x) ky t
         Nil -> k `seq` Tip k x

So it does not terminate in this case.

Edward

Excerpts from Johan Tibell's message of Thu Oct 27 13:13:56 -0400 2011:
> On Thu, Oct 27, 2011 at 10:03 AM, Edward Z. Yang <ezyang at mit.edu> wrote:
> 
> > I'd like to remark that the situation with keys is not /quite/ comparable.
> > Even if we don't need to look at the key for inserting into an empty map,
> > it will get forced anyway because IntMaps are spine-strict (in particular,
> > they
> > are strict in their keys.)
> 
> 
> I'm not quite sure if I follow. Here's Data.IntMap.insert:
> 
>     insert :: Key -> a -> IntMap a -> IntMap a
>     insert k x t = k `seq`
>       case t of
>         Bin p m l r
>           | nomatch k p m -> join k (Tip k x) p t
>           | zero k m -> Bin p m (insert k x l) r
>           | otherwise -> Bin p m l (insert k x r)
>         Tip ky _
>           | k==ky -> Tip k x
>           | otherwise -> join k (Tip k x) ky t
>         Nil -> Tip k x
> 
> Without the explicit `seq`
> 
>     insert undefined 1 Nil
> 
> terminates but with the `seq` it's _|_.
> 
> Are you saying it will eventually get force if someone e.g. does a lookup
> after the insert?
> 
> -- Johan



More information about the Libraries mailing list