INLINE pragma bogus

Simon Peyton-Jones simonpj at microsoft.com
Fri Sep 24 03:28:18 EDT 2010


In Data.Map we see

mapKeysMonotonic :: (k1->k2) -> Map k1 a -> Map k2 a
mapKeysMonotonic _ Tip = Tip
mapKeysMonotonic f (Bin sz k x l r) =
    Bin sz (f k) x (mapKeysMonotonic f l) (mapKeysMonotonic f r)
{-# INLINE mapKeysMonotonic #-}


But mapKeysMonotonic is recursive, so it isn't going to get inlined. Lint bleats about this.

Remove the pragma?

Same for Data.IntMap.submapCmp, which is again recursive.

Incidentally submapCmp  is a MASSIVE function to put an INLINE pragma on!  Do you really need this much inlining?

Simon
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/libraries/attachments/20100924/09e34482/attachment.html


More information about the Libraries mailing list