summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorBen Gamari <ben@smart-cactus.org>2019-12-29 23:46:52 -0500
committerMarge Bot <ben+marge-bot@smart-cactus.org>2020-02-20 21:56:13 -0500
commit89cb4cc4cc76f834b0bcc53fb551db706ef143b7 (patch)
treec1d16f85237abfa8ed866a17853a74367f065fca
parentc5ec996583373025488c090fb2c89f7bda38c1cb (diff)
downloadhaskell-89cb4cc4cc76f834b0bcc53fb551db706ef143b7.tar.gz
Use Type instead of * in GHC
-rw-r--r--compiler/GHC/Cmm/Dataflow.hs3
-rw-r--r--compiler/GHC/Cmm/Dataflow/Graph.hs6
-rw-r--r--compiler/GHC/Hs/Expr.hs3
-rw-r--r--compiler/GHC/Hs/Expr.hs-boot13
-rw-r--r--compiler/GHC/Hs/Pat.hs-boot3
-rw-r--r--compiler/parser/RdrHsSyn.hs5
-rw-r--r--compiler/utils/TrieMap.hs3
7 files changed, 22 insertions, 14 deletions
diff --git a/compiler/GHC/Cmm/Dataflow.hs b/compiler/GHC/Cmm/Dataflow.hs
index fcabb1df0f..4f900c32ac 100644
--- a/compiler/GHC/Cmm/Dataflow.hs
+++ b/compiler/GHC/Cmm/Dataflow.hs
@@ -43,13 +43,14 @@ import Data.Array
import Data.Maybe
import Data.IntSet (IntSet)
import qualified Data.IntSet as IntSet
+import Data.Kind (Type)
import GHC.Cmm.Dataflow.Block
import GHC.Cmm.Dataflow.Graph
import GHC.Cmm.Dataflow.Collections
import GHC.Cmm.Dataflow.Label
-type family Fact (x :: Extensibility) f :: *
+type family Fact (x :: Extensibility) f :: Type
type instance Fact C f = FactBase f
type instance Fact O f = f
diff --git a/compiler/GHC/Cmm/Dataflow/Graph.hs b/compiler/GHC/Cmm/Dataflow/Graph.hs
index 3f361de0fb..de146c6a35 100644
--- a/compiler/GHC/Cmm/Dataflow/Graph.hs
+++ b/compiler/GHC/Cmm/Dataflow/Graph.hs
@@ -27,11 +27,13 @@ import GHC.Cmm.Dataflow.Label
import GHC.Cmm.Dataflow.Block
import GHC.Cmm.Dataflow.Collections
+import Data.Kind
+
-- | A (possibly empty) collection of closed/closed blocks
type Body n = LabelMap (Block n C C)
-- | @Body@ abstracted over @block@
-type Body' block (n :: Extensibility -> Extensibility -> *) = LabelMap (block n C C)
+type Body' block (n :: Extensibility -> Extensibility -> Type) = LabelMap (block n C C)
-------------------------------
-- | Gives access to the anchor points for
@@ -76,7 +78,7 @@ type Graph = Graph' Block
-- | @Graph'@ is abstracted over the block type, so that we can build
-- graphs of annotated blocks for example (Compiler.Hoopl.Dataflow
-- needs this).
-data Graph' block (n :: Extensibility -> Extensibility -> *) e x where
+data Graph' block (n :: Extensibility -> Extensibility -> Type) e x where
GNil :: Graph' block n O O
GUnit :: block n O O -> Graph' block n O O
GMany :: MaybeO e (block n O C)
diff --git a/compiler/GHC/Hs/Expr.hs b/compiler/GHC/Hs/Expr.hs
index 9f97fc9ff7..a84bc1b240 100644
--- a/compiler/GHC/Hs/Expr.hs
+++ b/compiler/GHC/Hs/Expr.hs
@@ -54,6 +54,7 @@ import {-# SOURCE #-} TcRnTypes (TcLclEnv)
-- libraries:
import Data.Data hiding (Fixity(..))
import qualified Data.Data as Data (Fixity(..))
+import qualified Data.Kind
import Data.Maybe (isNothing)
import GHCi.RemoteTypes ( ForeignRef )
@@ -129,7 +130,7 @@ type family SyntaxExpr p
-- noSyntaxExpr would be ambiguous.
type instance SyntaxExpr (GhcPass p) = SyntaxExprGhc p
-type family SyntaxExprGhc (p :: Pass) = (r :: *) | r -> p where
+type family SyntaxExprGhc (p :: Pass) = (r :: Data.Kind.Type) | r -> p where
SyntaxExprGhc 'Parsed = NoExtField
SyntaxExprGhc 'Renamed = SyntaxExprRn
SyntaxExprGhc 'Typechecked = SyntaxExprTc
diff --git a/compiler/GHC/Hs/Expr.hs-boot b/compiler/GHC/Hs/Expr.hs-boot
index 7ea4633760..0fdbf773b2 100644
--- a/compiler/GHC/Hs/Expr.hs-boot
+++ b/compiler/GHC/Hs/Expr.hs-boot
@@ -15,18 +15,19 @@ import Outputable ( SDoc, Outputable )
import {-# SOURCE #-} GHC.Hs.Pat ( LPat )
import BasicTypes ( SpliceExplicitFlag(..))
import GHC.Hs.Extension ( OutputableBndrId, GhcPass )
+import Data.Kind ( Type )
type role HsExpr nominal
type role HsCmd nominal
type role MatchGroup nominal nominal
type role GRHSs nominal nominal
type role HsSplice nominal
-data HsExpr (i :: *)
-data HsCmd (i :: *)
-data HsSplice (i :: *)
-data MatchGroup (a :: *) (body :: *)
-data GRHSs (a :: *) (body :: *)
-type family SyntaxExpr (i :: *)
+data HsExpr (i :: Type)
+data HsCmd (i :: Type)
+data HsSplice (i :: Type)
+data MatchGroup (a :: Type) (body :: Type)
+data GRHSs (a :: Type) (body :: Type)
+type family SyntaxExpr (i :: Type)
instance OutputableBndrId p => Outputable (HsExpr (GhcPass p))
instance OutputableBndrId p => Outputable (HsCmd (GhcPass p))
diff --git a/compiler/GHC/Hs/Pat.hs-boot b/compiler/GHC/Hs/Pat.hs-boot
index 1a1e6c4a2c..c7ff0a892e 100644
--- a/compiler/GHC/Hs/Pat.hs-boot
+++ b/compiler/GHC/Hs/Pat.hs-boot
@@ -11,9 +11,10 @@ module GHC.Hs.Pat where
import Outputable
import GHC.Hs.Extension ( OutputableBndrId, GhcPass, XRec )
+import Data.Kind
type role Pat nominal
-data Pat (i :: *)
+data Pat (i :: Type)
type LPat i = XRec i Pat
instance OutputableBndrId p => Outputable (Pat (GhcPass p))
diff --git a/compiler/parser/RdrHsSyn.hs b/compiler/parser/RdrHsSyn.hs
index a4ca9aaf76..ef64ce25e6 100644
--- a/compiler/parser/RdrHsSyn.hs
+++ b/compiler/parser/RdrHsSyn.hs
@@ -138,6 +138,7 @@ import Text.ParserCombinators.ReadP as ReadP
import Data.Char
import qualified Data.Monoid as Monoid
import Data.Data ( dataTypeOf, fromConstr, dataTypeConstrs )
+import Data.Kind ( Type )
#include "HsVersions.h"
@@ -1733,7 +1734,7 @@ instance DisambInfixOp RdrName where
-- See Note [Ambiguous syntactic categories]
class b ~ (Body b) GhcPs => DisambECP b where
-- | See Note [Body in DisambECP]
- type Body b :: * -> *
+ type Body b :: Type -> Type
-- | Return a command without ambiguity, or fail in a non-command context.
ecpFromCmd' :: LHsCmd GhcPs -> PV (Located b)
-- | Return an expression without ambiguity, or fail in a non-expression context.
@@ -1843,7 +1844,7 @@ even when -XUndecidableSuperClasses are not required.
{- Note [Body in DisambECP]
~~~~~~~~~~~~~~~~~~~~~~~~~~~
There are helper functions (mkBodyStmt, mkBindStmt, unguardedRHS, etc) that
-require their argument to take a form of (body GhcPs) for some (body :: * ->
+require their argument to take a form of (body GhcPs) for some (body :: Type ->
*). To satisfy this requirement, we say that (b ~ Body b GhcPs) in the
superclass constraints of DisambECP.
diff --git a/compiler/utils/TrieMap.hs b/compiler/utils/TrieMap.hs
index 917e3b21f6..f4106437a1 100644
--- a/compiler/utils/TrieMap.hs
+++ b/compiler/utils/TrieMap.hs
@@ -39,6 +39,7 @@ import qualified Data.Map as Map
import qualified Data.IntMap as IntMap
import Outputable
import Control.Monad( (>=>) )
+import Data.Kind( Type )
{-
This module implements TrieMaps, which are finite mappings
@@ -65,7 +66,7 @@ type XT a = Maybe a -> Maybe a -- How to alter a non-existent elt (Nothing)
-- or an existing elt (Just)
class TrieMap m where
- type Key m :: *
+ type Key m :: Type
emptyTM :: m a
lookupTM :: forall b. Key m -> m b -> Maybe b
alterTM :: forall b. Key m -> XT b -> m b -> m b