[commit: ghc] wip/rae: Use CoercionN and friends in TyCoRep (6092dcb)

git at git.haskell.org git at git.haskell.org
Mon Feb 15 15:38:48 UTC 2016


Repository : ssh://git@git.haskell.org/ghc

On branch  : wip/rae
Link       : http://ghc.haskell.org/trac/ghc/changeset/6092dcbe6cb6dacbf117f2bd50555eb61183a307/ghc

>---------------------------------------------------------------

commit 6092dcbe6cb6dacbf117f2bd50555eb61183a307
Author: Richard Eisenberg <eir at cis.upenn.edu>
Date:   Wed Feb 10 08:03:56 2016 -0500

    Use CoercionN and friends in TyCoRep


>---------------------------------------------------------------

6092dcbe6cb6dacbf117f2bd50555eb61183a307
 compiler/types/Coercion.hs |  7 -------
 compiler/types/TyCoRep.hs  | 34 +++++++++++++++++++++-------------
 2 files changed, 21 insertions(+), 20 deletions(-)

diff --git a/compiler/types/Coercion.hs b/compiler/types/Coercion.hs
index 2989bce..6546288 100644
--- a/compiler/types/Coercion.hs
+++ b/compiler/types/Coercion.hs
@@ -127,13 +127,6 @@ import Control.Monad (foldM)
 import Control.Arrow ( first )
 import Data.Function ( on )
 
------------------------------------------------------------------
--- These synonyms are very useful as documentation
-
-type CoercionN = Coercion   -- nominal coercion
-type CoercionR = Coercion   -- representational coercion
-type CoercionP = Coercion   -- phantom coercion
-
 {-
 %************************************************************************
 %*                                                                      *
diff --git a/compiler/types/TyCoRep.hs b/compiler/types/TyCoRep.hs
index 6a13213..b359ba2 100644
--- a/compiler/types/TyCoRep.hs
+++ b/compiler/types/TyCoRep.hs
@@ -33,6 +33,7 @@ module TyCoRep (
         -- Coercions
         Coercion(..), LeftOrRight(..),
         UnivCoProvenance(..), CoercionHole(..),
+        CoercionN, CoercionR, CoercionP, KindCoercion,
 
         -- Functions over types
         mkTyConTy, mkTyVarTy, mkTyVarTys,
@@ -213,10 +214,10 @@ data Type
 
   | CastTy
         Type
-        Coercion    -- ^ A kind cast. The coercion is always nominal.
-                    -- INVARIANT: The cast is never refl.
-                    -- INVARIANT: The cast is "pushed down" as far as it
-                    -- can go. See Note [Pushing down casts]
+        KindCoercion  -- ^ A kind cast. The coercion is always nominal.
+                      -- INVARIANT: The cast is never refl.
+                      -- INVARIANT: The cast is "pushed down" as far as it
+                      -- can go. See Note [Pushing down casts]
 
   | CoercionTy
         Coercion    -- ^ Injection of a Coercion into a type
@@ -592,11 +593,11 @@ data Coercion
                -- we expand synonyms eagerly
                -- But it can be a type function
 
-  | AppCo Coercion Coercion             -- lift AppTy
+  | AppCo Coercion CoercionN             -- lift AppTy
           -- AppCo :: e -> N -> e
 
   -- See Note [Forall coercions]
-  | ForAllCo TyVar Coercion Coercion
+  | ForAllCo TyVar KindCoercion Coercion
          -- ForAllCo :: _ -> N -> e -> e
 
   -- These are special
@@ -626,15 +627,15 @@ data Coercion
     -- Using NthCo on a ForAllCo gives an N coercion always
     -- See Note [NthCo and newtypes]
 
-  | LRCo   LeftOrRight Coercion     -- Decomposes (t_left t_right)
+  | LRCo   LeftOrRight CoercionN     -- Decomposes (t_left t_right)
     -- :: _ -> N -> N
-  | InstCo Coercion Coercion
+  | InstCo Coercion CoercionN
     -- :: e -> N -> e
     -- See Note [InstCo roles]
 
   -- Coherence applies a coercion to the left-hand type of another coercion
   -- See Note [Coherence]
-  | CoherenceCo Coercion Coercion
+  | CoherenceCo Coercion KindCoercion
      -- :: e -> N -> e
 
   -- Extract a kind coercion from a (heterogeneous) type coercion
@@ -642,11 +643,16 @@ data Coercion
   | KindCo Coercion
      -- :: e -> N
 
-  | SubCo Coercion                  -- Turns a ~N into a ~R
+  | SubCo CoercionN                  -- Turns a ~N into a ~R
     -- :: N -> R
 
   deriving (Data.Data, Data.Typeable)
 
+type CoercionN = Coercion       -- always nominal
+type CoercionR = Coercion       -- always representational
+type CoercionP = Coercion       -- always phantom
+type KindCoercion = CoercionN   -- always nominal
+
 -- If you edit this type, you may need to update the GHC formalism
 -- See Note [GHC Formalism] in coreSyn/CoreLint.hs
 data LeftOrRight = CLeft | CRight
@@ -1002,10 +1008,12 @@ role and kind, which is done in the UnivCo constructor.
 data UnivCoProvenance
   = UnsafeCoerceProv   -- ^ From @unsafeCoerce#@. These are unsound.
 
-  | PhantomProv Coercion -- ^ See Note [Phantom coercions]
+  | PhantomProv KindCoercion -- ^ See Note [Phantom coercions]. Only in Phantom
+                             -- roled coercions
 
-  | ProofIrrelProv Coercion  -- ^ From the fact that any two coercions are
-                             --   considered equivalent. See Note [ProofIrrelProv]
+  | ProofIrrelProv KindCoercion  -- ^ From the fact that any two coercions are
+                                 --   considered equivalent. See Note [ProofIrrelProv].
+                                 -- Can be used in Nominal or Representational coercions
 
   | PluginProv String  -- ^ From a plugin, which asserts that this coercion
                        --   is sound. The string is for the use of the plugin.



More information about the ghc-commits mailing list