Skip to content

Commit 22af858

Browse files
authored
[#90] Check more ghc warnings through ghc-options (#91)
* [#90] Check more ghc warnings through ghc-options Resolves #90 * Clean up LANGUAGE extensions
1 parent 497e182 commit 22af858

File tree

14 files changed

+321
-277
lines changed

14 files changed

+321
-277
lines changed

benchmark/CMap.hs

Lines changed: 46 additions & 39 deletions
Original file line numberDiff line numberDiff line change
@@ -1,70 +1,77 @@
1+
{-# OPTIONS_GHC -fplugin GHC.TypeLits.KnownNat.Solver #-}
2+
13
{-# LANGUAGE DataKinds #-}
2-
{-# LANGUAGE ExplicitNamespaces #-}
3-
{-# LANGUAGE KindSignatures #-}
44
{-# LANGUAGE PolyKinds #-}
55
{-# LANGUAGE TypeFamilies #-}
66
{-# LANGUAGE TypeOperators #-}
77
{-# LANGUAGE UndecidableInstances #-}
88

9-
{-# OPTIONS_GHC -fplugin GHC.TypeLits.KnownNat.Solver #-}
10-
119
module CMap
12-
( spec
13-
) where
14-
15-
import Criterion.Main (bench, nf, env, whnf)
10+
( spec
11+
) where
1612

1713
import Prelude hiding (lookup)
1814

19-
import Spec
15+
import Criterion.Main (bench, env, nf, whnf)
16+
import Data.Kind (Type)
2017
import Data.Maybe (fromJust)
2118
import Data.Proxy (Proxy (..))
2219
import Data.Typeable (Typeable)
23-
import GHC.TypeLits
20+
import GHC.TypeLits (type (+), KnownNat, Nat)
2421

2522
import Data.TypeRep.CMap (TypeRepMap (..), empty, insert, lookup)
2623

24+
import Spec (BenchSpec (..))
25+
26+
2727
spec :: BenchSpec
2828
spec = BenchSpec
29-
{ benchLookup = Just $ \name ->
30-
env (mkMap 10000) $ \ ~bigMap ->
31-
bench name $ nf tenLookups bigMap
32-
, benchInsertSmall = Just $ \name ->
33-
bench name $ whnf (inserts empty 10) (Proxy @ 99999)
34-
, benchInsertBig = Just $ \name ->
35-
env (mkMap 10000) $ \ ~(bigMap) ->
36-
bench name $ whnf (inserts bigMap 1) (Proxy @ 99999)
37-
, benchUpdateSmall = Just $ \name ->
38-
env (mkMap 10) $ \ ~(smallMap) ->
39-
bench name $ whnf (inserts smallMap 10) (Proxy @ 0)
40-
, benchUpdateBig = Just $ \name ->
41-
env (mkMap 10000) $ \ ~(bigMap) ->
42-
bench name $ whnf (inserts bigMap 10) (Proxy @ 0)
43-
}
29+
{ benchLookup = Just $ \name ->
30+
env (mkMap 10000) $ \ ~bigMap ->
31+
bench name $ nf tenLookups bigMap
32+
, benchInsertSmall = Just $ \name ->
33+
bench name $ whnf (inserts empty 10) (Proxy @ 99999)
34+
, benchInsertBig = Just $ \name ->
35+
env (mkMap 10000) $ \ ~bigMap ->
36+
bench name $ whnf (inserts bigMap 1) (Proxy @ 99999)
37+
, benchUpdateSmall = Just $ \name ->
38+
env (mkMap 10) $ \ ~smallMap ->
39+
bench name $ whnf (inserts smallMap 10) (Proxy @ 0)
40+
, benchUpdateBig = Just $ \name ->
41+
env (mkMap 10000) $ \ ~bigMap ->
42+
bench name $ whnf (inserts bigMap 10) (Proxy @ 0)
43+
}
4444

45-
tenLookups :: TypeRepMap (Proxy :: Nat -> *)
46-
-> ( Proxy 10, Proxy 20, Proxy 30, Proxy 40
47-
, Proxy 50, Proxy 60, Proxy 70, Proxy 80
48-
)
45+
tenLookups
46+
:: TypeRepMap (Proxy :: Nat -> Type)
47+
-> ( Proxy 10, Proxy 20, Proxy 30, Proxy 40
48+
, Proxy 50, Proxy 60, Proxy 70, Proxy 80
49+
)
4950
tenLookups tmap = (lp, lp, lp, lp, lp, lp, lp, lp)
5051
where
5152
lp :: forall (a::Nat). Typeable a => Proxy a
5253
lp = fromJust $ lookup tmap
5354

54-
inserts :: forall a . (KnownNat a)
55-
=> TypeRepMap (Proxy :: Nat -> *)
56-
-> Int
57-
-> Proxy (a :: Nat)
58-
-> TypeRepMap (Proxy :: Nat -> *)
55+
inserts
56+
:: forall a . (KnownNat a)
57+
=> TypeRepMap (Proxy :: Nat -> Type)
58+
-> Int
59+
-> Proxy (a :: Nat)
60+
-> TypeRepMap (Proxy :: Nat -> Type)
5961
inserts !c 0 _ = c
6062
inserts !c n x = inserts
61-
(insert x c)
62-
(n-1)
63-
(Proxy :: Proxy (a+1))
63+
(insert x c)
64+
(n-1)
65+
(Proxy :: Proxy (a+1))
6466

65-
mkMap :: Int -> IO (TypeRepMap (Proxy :: Nat -> *))
67+
mkMap :: Int -> IO (TypeRepMap (Proxy :: Nat -> Type))
6668
mkMap n = pure $ buildBigMap n (Proxy :: Proxy 0) empty
6769

68-
buildBigMap :: forall a . (KnownNat a) => Int -> Proxy (a :: Nat) -> TypeRepMap (Proxy :: Nat -> *) -> TypeRepMap (Proxy :: Nat -> *)
70+
buildBigMap
71+
:: forall a . (KnownNat a)
72+
=> Int
73+
-> Proxy (a :: Nat)
74+
-> TypeRepMap (Proxy :: Nat -> Type)
75+
-> TypeRepMap (Proxy :: Nat -> Type)
6976
buildBigMap 1 x = insert x
7077
buildBigMap n x = insert x . buildBigMap (n - 1) (Proxy :: Proxy (a + 1))

benchmark/CacheMap.hs

Lines changed: 48 additions & 45 deletions
Original file line numberDiff line numberDiff line change
@@ -1,76 +1,79 @@
1+
{-# OPTIONS_GHC -fplugin GHC.TypeLits.KnownNat.Solver #-}
2+
13
{-# LANGUAGE DataKinds #-}
2-
{-# LANGUAGE ExplicitNamespaces #-}
3-
{-# LANGUAGE KindSignatures #-}
44
{-# LANGUAGE PolyKinds #-}
55
{-# LANGUAGE TypeFamilies #-}
66
{-# LANGUAGE TypeOperators #-}
77
{-# LANGUAGE UndecidableInstances #-}
88

9-
{-# OPTIONS_GHC -fplugin GHC.TypeLits.KnownNat.Solver #-}
10-
119
module CacheMap
12-
( spec
13-
) where
14-
15-
import Criterion.Main (bench, nf, whnf, env)
16-
import Spec
10+
( spec
11+
) where
1712

1813
import Prelude hiding (lookup)
1914

15+
import Criterion.Main (bench, env, nf, whnf)
16+
import Data.Kind (Type)
2017
import Data.Maybe (fromJust)
2118
import Data.Proxy (Proxy (..))
2219
import Data.Typeable (Typeable)
2320
import GHC.Exts (fromList)
24-
import GHC.TypeLits
21+
import GHC.TypeLits (type (+), KnownNat, Nat)
22+
23+
import Data.TypeRepMap.Internal (TypeRepMap (..), WrapTypeable (..), empty, insert, lookup)
24+
25+
import Spec (BenchSpec (..))
2526

26-
import Data.TypeRepMap.Internal (TypeRepMap (..), WrapTypeable (..), lookup, insert, empty)
2727

2828
spec :: BenchSpec
2929
spec = BenchSpec
30-
{ benchLookup = Just $ \name ->
31-
env (mkMap 10000) $ \ ~bigMap ->
32-
bench name $ nf tenLookups bigMap
33-
, benchInsertSmall = Just $ \name ->
34-
bench name $ whnf (inserts empty 10) (Proxy @ 99999)
35-
, benchInsertBig = Just $ \name ->
36-
env (mkMap 10000) $ \ ~(bigMap) ->
37-
bench name $ whnf (inserts bigMap 1) (Proxy @ 99999)
38-
, benchUpdateSmall = Just $ \name ->
39-
env (mkMap 10) $ \ ~(smallMap) ->
40-
bench name $ whnf (inserts smallMap 10) (Proxy @ 0)
41-
, benchUpdateBig = Just $ \name ->
42-
env (mkMap 10000) $ \ ~(bigMap) ->
43-
bench name $ whnf (inserts bigMap 10) (Proxy @ 0)
44-
}
30+
{ benchLookup = Just $ \name ->
31+
env (mkMap 10000) $ \ ~bigMap ->
32+
bench name $ nf tenLookups bigMap
33+
, benchInsertSmall = Just $ \name ->
34+
bench name $ whnf (inserts empty 10) (Proxy @ 99999)
35+
, benchInsertBig = Just $ \name ->
36+
env (mkMap 10000) $ \ ~bigMap ->
37+
bench name $ whnf (inserts bigMap 1) (Proxy @ 99999)
38+
, benchUpdateSmall = Just $ \name ->
39+
env (mkMap 10) $ \ ~smallMap ->
40+
bench name $ whnf (inserts smallMap 10) (Proxy @ 0)
41+
, benchUpdateBig = Just $ \name ->
42+
env (mkMap 10000) $ \ ~bigMap ->
43+
bench name $ whnf (inserts bigMap 10) (Proxy @ 0)
44+
}
4545

46-
tenLookups :: TypeRepMap (Proxy :: Nat -> *)
47-
-> ( Proxy 10, Proxy 20, Proxy 30, Proxy 40
48-
, Proxy 50, Proxy 60, Proxy 70, Proxy 80
49-
)
46+
tenLookups
47+
:: TypeRepMap (Proxy :: Nat -> Type)
48+
-> ( Proxy 10, Proxy 20, Proxy 30, Proxy 40
49+
, Proxy 50, Proxy 60, Proxy 70, Proxy 80
50+
)
5051
tenLookups tmap = (lp, lp, lp, lp, lp, lp, lp, lp)
5152
where
52-
lp :: forall (a::Nat). Typeable a => Proxy a
53+
lp :: forall (a :: Nat) . Typeable a => Proxy a
5354
lp = fromJust $ lookup tmap
5455

55-
inserts :: forall a . (KnownNat a)
56-
=> TypeRepMap (Proxy :: Nat -> *)
57-
-> Int
58-
-> Proxy (a :: Nat)
59-
-> TypeRepMap (Proxy :: Nat -> *)
56+
inserts
57+
:: forall a . (KnownNat a)
58+
=> TypeRepMap (Proxy :: Nat -> Type)
59+
-> Int
60+
-> Proxy (a :: Nat)
61+
-> TypeRepMap (Proxy :: Nat -> Type)
6062
inserts !c 0 _ = c
6163
inserts !c n x = inserts
62-
(insert x c)
63-
(n-1)
64-
(Proxy :: Proxy (a+1))
64+
(insert x c)
65+
(n-1)
66+
(Proxy :: Proxy (a + 1))
6567

66-
mkMap :: Int -> IO (TypeRepMap (Proxy :: Nat -> *))
68+
mkMap :: Int -> IO (TypeRepMap (Proxy :: Nat -> Type))
6769
mkMap n = pure $ fromList $ buildBigMap n (Proxy :: Proxy 0) []
6870

6971

70-
buildBigMap :: forall a . (KnownNat a)
71-
=> Int
72-
-> Proxy (a :: Nat)
73-
-> [WrapTypeable (Proxy :: Nat -> *)]
74-
-> [WrapTypeable (Proxy :: Nat -> *)]
72+
buildBigMap
73+
:: forall a . (KnownNat a)
74+
=> Int
75+
-> Proxy (a :: Nat)
76+
-> [WrapTypeable (Proxy :: Nat -> Type)]
77+
-> [WrapTypeable (Proxy :: Nat -> Type)]
7578
buildBigMap 1 x = (WrapTypeable x :)
7679
buildBigMap n x = (WrapTypeable x :) . buildBigMap (n - 1) (Proxy :: Proxy (a + 1))

benchmark/DMap.hs

Lines changed: 45 additions & 42 deletions
Original file line numberDiff line numberDiff line change
@@ -1,79 +1,81 @@
1+
{-# OPTIONS_GHC -fplugin GHC.TypeLits.KnownNat.Solver #-}
2+
13
{-# LANGUAGE DataKinds #-}
2-
{-# LANGUAGE ExplicitNamespaces #-}
34
{-# LANGUAGE InstanceSigs #-}
4-
{-# LANGUAGE KindSignatures #-}
55
{-# LANGUAGE PolyKinds #-}
66
{-# LANGUAGE TypeFamilies #-}
77
{-# LANGUAGE TypeOperators #-}
88
{-# LANGUAGE UndecidableInstances #-}
99

10-
{-# OPTIONS_GHC -fplugin GHC.TypeLits.KnownNat.Solver #-}
11-
1210
module DMap
13-
( spec
14-
) where
15-
16-
import Criterion.Main (bench, env, nf, whnf)
11+
( spec
12+
) where
1713

1814
import Prelude hiding (lookup)
1915

2016
import Control.DeepSeq (NFData (..))
17+
import Criterion.Main (bench, env, nf, whnf)
18+
import Data.Kind (Type)
2119
import Data.Maybe (fromJust)
2220
import Data.Proxy (Proxy (..))
23-
import GHC.TypeLits
24-
import Spec
21+
import GHC.TypeLits (type (+), KnownNat, Nat)
2522
import Type.Reflection (TypeRep, Typeable, typeRep)
2623
import Type.Reflection.Unsafe (typeRepFingerprint)
2724

2825
import Data.Dependent.Map (DMap, empty, insert, keys, lookup)
2926
import Data.Some (Some (Some))
3027

31-
type TypeRepMap = DMap TypeRep
28+
import Spec (BenchSpec (..))
3229

3330

31+
type TypeRepMap = DMap TypeRep
32+
3433
spec :: BenchSpec
3534
spec = BenchSpec
36-
{ benchLookup = Just $ \name ->
37-
env mkBigMap $ \ ~(DMapNF bigMap) ->
38-
bench name $ nf tenLookups bigMap
39-
, benchInsertSmall = Just $ \name ->
40-
bench name $ whnf (inserts empty 10) (Proxy @ 99999)
41-
, benchInsertBig = Just $ \name ->
42-
env mkBigMap $ \ ~(DMapNF bigMap) ->
43-
bench name $ whnf (inserts bigMap 1) (Proxy @ 99999)
44-
, benchUpdateSmall = Nothing -- Not implemented
45-
, benchUpdateBig = Nothing -- Not implemented
46-
}
35+
{ benchLookup = Just $ \name ->
36+
env mkBigMap $ \ ~(DMapNF bigMap) ->
37+
bench name $ nf tenLookups bigMap
38+
, benchInsertSmall = Just $ \name ->
39+
bench name $ whnf (inserts empty 10) (Proxy @ 99999)
40+
, benchInsertBig = Just $ \name ->
41+
env mkBigMap $ \ ~(DMapNF bigMap) ->
42+
bench name $ whnf (inserts bigMap 1) (Proxy @ 99999)
43+
, benchUpdateSmall = Nothing -- Not implemented
44+
, benchUpdateBig = Nothing -- Not implemented
45+
}
4746

48-
tenLookups :: TypeRepMap (Proxy :: Nat -> *)
49-
-> ( Proxy 10, Proxy 20, Proxy 30, Proxy 40
50-
, Proxy 50, Proxy 60, Proxy 70, Proxy 80
51-
)
47+
tenLookups
48+
:: TypeRepMap (Proxy :: Nat -> Type)
49+
-> ( Proxy 10, Proxy 20, Proxy 30, Proxy 40
50+
, Proxy 50, Proxy 60, Proxy 70, Proxy 80
51+
)
5252
tenLookups tmap = (lp, lp, lp, lp, lp, lp, lp, lp)
5353
where
5454
lp :: forall (a :: Nat) . Typeable a => Proxy a
5555
lp = fromJust $ lookup (typeRep @a) tmap
5656

57-
inserts :: forall a . (KnownNat a)
58-
=> TypeRepMap (Proxy :: Nat -> *)
59-
-> Int
60-
-> Proxy (a :: Nat)
61-
-> TypeRepMap (Proxy :: Nat -> *)
57+
inserts
58+
:: forall a . (KnownNat a)
59+
=> TypeRepMap (Proxy :: Nat -> Type)
60+
-> Int
61+
-> Proxy (a :: Nat)
62+
-> TypeRepMap (Proxy :: Nat -> Type)
6263
inserts !c 0 _ = c
6364
inserts !c n x = inserts
64-
(insert (typeRep @ a) x c)
65-
(n-1)
66-
(Proxy :: Proxy (a+1))
65+
(insert (typeRep @ a) x c)
66+
(n-1)
67+
(Proxy :: Proxy (a+1))
6768

6869
-- TypeRepMap of 10000 elements
69-
mkBigMap :: IO (DMapNF (Proxy :: Nat -> *))
70+
mkBigMap :: IO (DMapNF (Proxy :: Nat -> Type))
7071
mkBigMap = pure . DMapNF $ buildBigMap 10000 (Proxy :: Proxy 0) empty
7172

72-
buildBigMap :: forall a . (KnownNat a)
73-
=> Int
74-
-> Proxy (a :: Nat)
75-
-> TypeRepMap (Proxy :: Nat -> *)
76-
-> TypeRepMap (Proxy :: Nat -> *)
73+
buildBigMap
74+
:: forall a . (KnownNat a)
75+
=> Int
76+
-> Proxy (a :: Nat)
77+
-> TypeRepMap (Proxy :: Nat -> Type)
78+
-> TypeRepMap (Proxy :: Nat -> Type)
7779
buildBigMap 1 x = insert (typeRep @a) x
7880
buildBigMap n x = insert (typeRep @a) x
7981
. buildBigMap (n - 1) (Proxy @(a + 1))
@@ -82,5 +84,6 @@ buildBigMap n x = insert (typeRep @a) x
8284
newtype DMapNF f = DMapNF (TypeRepMap f)
8385

8486
instance NFData (DMapNF f) where
85-
rnf (DMapNF x) =
86-
rnf . map (\(Some t) -> typeRepFingerprint t) $ keys x
87+
rnf :: DMapNF f -> ()
88+
rnf (DMapNF x) =
89+
rnf . map (\(Some t) -> typeRepFingerprint t) $ keys x

0 commit comments

Comments
 (0)