
There exists a small but measurable performance hit for at least one
test case (using Int as keys, obviously). Perhaps the bias would be
the other way if we were comparing EnumMap to an IntMap wrapped with
to/from Enum.
Thomas
-- Using Data.IntMap
[tommd@Mavlo Test]$ ghc --make -O2 im.hs
[1 of 1] Compiling Main ( im.hs, im.o )
Linking im ...
[tommd@Mavlo Test]$ ./im
buildMap: 0.625563s
lookupMap: 0.176478s
[tommd@Mavlo Test]$ ./im
buildMap: 0.613668s
lookupMap: 0.174151s
[tommd@Mavlo Test]$ ./im
buildMap: 0.607961s
lookupMap: 0.175584s
-- Using Data.EnumMap
[tommd@Mavlo Test]$ vi im.hs
[tommd@Mavlo Test]$ ghc --make -O2 im.hs
[1 of 1] Compiling Main ( im.hs, im.o )
Linking im ...
[tommd@Mavlo Test]$ ./im
buildMap: 0.705458s
lookupMap: 0.229307s
[tommd@Mavlo Test]$ ./im
buildMap: 0.71757s
lookupMap: 0.231273s
[tommd@Mavlo Test]$ ./im
buildMap: 0.685333s
lookupMap: 0.23883s
Code (sorry, its ugly I know)
{-# LANGUAGE BangPatterns #-}
module Main where
import Data.Time
import qualified Data.EnumMap as E
type IntMap = E.EnumMap Int
-- import qualified Data.IntMap as E
-- type IntMap = E.IntMap
main = do
bench "buildMap" buildMap
!e <- buildMap
bench "lookupMap" (lookupMap e)
bench str func = do
start <- getCurrentTime
!x <- func
finish <- getCurrentTime
let diff = diffUTCTime finish start
putStrLn $ str ++ ":\t" ++ (show diff)
keys = [0..1000000]
buildMap :: IO (IntMap Int)
buildMap = do
return $ go keys keys E.empty
where
go [] _ !m = m
go _ [] !m = m
go (k:ks) (e:es) m = go ks es (E.insert k e m)
lookupMap m = do
check keys m
where
check [] _ = return ()
check (k:ks) m =
if (E.lookup k m /= Just k)
then error "blah"
else check ks m
On Sat, Aug 8, 2009 at 4:02 PM, John Van Enk
What if we say that Enum a generalization, rather than a wrapper, of Int?
If the benchmarks are even, is there a reason to use the more specific structure rather than the general one? I don't know if Enum being "more complex" outweighs the benefits of it being "more general" (if the EnumMap matches IntMap for speed).
Thoughts?
On Sat, Aug 8, 2009 at 6:11 PM, Henning Thielemann
wrote: On Sat, 8 Aug 2009, John Van Enk wrote:
That's originally how I was thinking about doing it, but I think that requires one to re-implement all the functions available in Data.IntMap as simple wrappers that do the toEnum/fromEnum conversion. I think making it into its own module is a little cleaner. The conversion from EnumMap to IntMap is substantially cleaner than from IntMap to EnumMap:
type IntMap v = EnumMap Int v
Can you implement EnumMap in terms of the Enum methods, without many conversions to Int? I mean, if you often convert to Int and back then you could achieve the same on top of IntMap. Generally I prefer the strategy "from simple to complex". I consider Enum to be a "wrapper" around Int. http://haskell.org/haskellwiki/Simple_to_complex
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe