Skip to content

Commit

Permalink
Add benchmarks with DMap (#14)
Browse files Browse the repository at this point in the history
* Add benchmarks with DMap

* Fix CI for 8.0.2
  • Loading branch information
vrom911 authored and chshersh committed Jul 7, 2018
1 parent 71aa479 commit e64c000
Show file tree
Hide file tree
Showing 4 changed files with 101 additions and 4 deletions.
3 changes: 1 addition & 2 deletions benchmark/CacheMap.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,6 @@
{-# LANGUAGE ExplicitNamespaces #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
Expand All @@ -25,7 +24,7 @@ import Data.Proxy (Proxy (..))
import Data.Typeable (Typeable)
import GHC.TypeLits

import Data.TypeRep.Map (TF (..), TypeRepMap (..), fromList, lookup)
import Data.TypeRep.CacheMap (TF (..), TypeRepMap (..), fromList, lookup)

benchCacheMap :: Benchmark
benchCacheMap = bgroup "vector optimal cache"
Expand Down
85 changes: 85 additions & 0 deletions benchmark/DMap.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,85 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE ExplicitNamespaces #-}
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE ViewPatterns #-}

{-# OPTIONS_GHC -fplugin GHC.TypeLits.KnownNat.Solver -fno-warn-orphans #-}

module DMap
( benchDMap
, prepareBenchDMap
) where

import Criterion.Main (Benchmark, bench, bgroup, nf)

import Prelude hiding (lookup)

import Control.DeepSeq (rnf)
import Control.Exception
import Data.Functor.Identity (Identity (..))
import Data.Maybe (fromJust)
import Data.Proxy (Proxy (..))
import Data.Type.Equality ((:~:) (..))
import GHC.TypeLits
import Type.Reflection (TypeRep, Typeable, typeRep)
import Type.Reflection.Unsafe (typeRepFingerprint)
import Unsafe.Coerce (unsafeCoerce)

import Data.Dependent.Map (DMap, empty, insert, keys, lookup)
import Data.GADT.Compare (GCompare (..), GEq (..), GOrdering (..))
import Data.Some (Some (This))

benchDMap :: Benchmark
benchDMap = bgroup "dependent map"
[ bench "lookup" $ nf tenLookups bigMap
-- , bench "insert new" $ whnf (\x -> rknf $ insert x bigMap) (Proxy :: Proxy 9999999999)
-- , bench "update old" $ whnf (\x -> rknf $ insert x bigMap) (Proxy :: Proxy 1)
]

tenLookups :: DMap TypeRep Identity
-> ( Proxy 10, Proxy 20, Proxy 30, Proxy 40
, Proxy 50, Proxy 60, Proxy 70, Proxy 80
)
tenLookups tmap = (lp, lp, lp, lp, lp, lp, lp, lp)
where
lp :: forall (a :: Nat) . Typeable a => Proxy a
lp = runIdentity $ fromJust $ lookup (typeRep @(Proxy a)) tmap

-- TypeRepMap of 10000 elements
bigMap :: DMap TypeRep Identity
bigMap = buildBigMap 10000 (Proxy :: Proxy 0) empty

buildBigMap :: forall a . (KnownNat a)
=> Int
-> Proxy (a :: Nat)
-> DMap TypeRep Identity
-> DMap TypeRep Identity
buildBigMap 1 x = insert (typeRep @(Proxy a)) $ Identity x
buildBigMap n x = insert (typeRep @(Proxy a)) (Identity x)
. buildBigMap (n - 1) (Proxy @(a + 1))

rknf :: DMap TypeRep f -> ()
rknf = rnf . map (\(This t) -> typeRepFingerprint t) . keys

prepareBenchDMap :: IO ()
prepareBenchDMap = evaluate (rknf bigMap)

instance GEq TypeRep where
geq :: TypeRep a -> TypeRep b -> Maybe (a :~: b)
geq (typeRepFingerprint -> a) (typeRepFingerprint -> b) =
if a == b
then Just $ unsafeCoerce Refl
else Nothing

instance GCompare TypeRep where
gcompare :: TypeRep a -> TypeRep b -> GOrdering a b
gcompare (typeRepFingerprint -> a) (typeRepFingerprint -> b) =
case compare a b of
EQ -> unsafeCoerce GEQ
LT -> GLT
GT -> GGT
11 changes: 11 additions & 0 deletions benchmark/Main.hs
Original file line number Diff line number Diff line change
@@ -1,9 +1,14 @@
{-# LANGUAGE CPP #-}

module Main where

import Criterion.Main (defaultMain)

import CacheMap (benchCacheMap, prepareBenchCacheMap)
import CMap (benchMap, prepareBenchMap)
#if ( __GLASGOW_HASKELL__ >= 802 )
import DMap (benchDMap, prepareBenchDMap)
#endif
import OptimalVector (benchVectorOpt, prepareBenchVectorOpt)
--import Vector (benchVector, prepareBenchVector)

Expand All @@ -13,9 +18,15 @@ main = do
prepareBenchCacheMap
--prepareBenchVector
prepareBenchVectorOpt
#if ( __GLASGOW_HASKELL__ >= 802 )
prepareBenchDMap
#endif
defaultMain
[ benchMap
-- , benchVector
, benchCacheMap
, benchVectorOpt
#if ( __GLASGOW_HASKELL__ >= 802 )
, benchDMap
#endif
]
6 changes: 4 additions & 2 deletions typerep-map.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -76,15 +76,17 @@ benchmark typerep-map-benchmark
, OptimalVector
build-depends: base
, criterion
, typerep-map
, typerep-map-internal
, deepseq
, dependent-map
, dependent-sum
, ghc-typelits-knownnat
default-extensions: OverloadedStrings
RecordWildCards
ScopedTypeVariables
TypeApplications

if impl(ghc >= 8.2.2)
other-modules: DMap

source-repository head
type: git
Expand Down

0 comments on commit e64c000

Please sign in to comment.