[commit: ghc] wip/branchedness: Make BranchFlag a new kind, resolving an old TODO comment (1634c3c)

git at git.haskell.org git at git.haskell.org
Sun Aug 2 17:44:44 UTC 2015


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

On branch  : wip/branchedness
Link       : http://ghc.haskell.org/trac/ghc/changeset/1634c3c6cf7b1410bd1a939d795c7afa66e94254/ghc

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

commit 1634c3c6cf7b1410bd1a939d795c7afa66e94254
Author: Gabor Greif <ggreif at gmail.com>
Date:   Sat Aug 1 10:52:39 2015 +0200

    Make BranchFlag a new kind, resolving an old TODO comment


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

1634c3c6cf7b1410bd1a939d795c7afa66e94254
 compiler/types/CoAxiom.hs | 20 ++++++++------------
 1 file changed, 8 insertions(+), 12 deletions(-)

diff --git a/compiler/types/CoAxiom.hs b/compiler/types/CoAxiom.hs
index cd8607a..36d9a67 100644
--- a/compiler/types/CoAxiom.hs
+++ b/compiler/types/CoAxiom.hs
@@ -1,6 +1,6 @@
 -- (c) The University of Glasgow 2012
 
-{-# LANGUAGE CPP, DeriveDataTypeable, GADTs, ScopedTypeVariables #-}
+{-# LANGUAGE CPP, DataKinds, DeriveDataTypeable, GADTs, KindSignatures, ScopedTypeVariables, StandaloneDeriving #-}
 
 -- | Module for coercion axioms, used to represent type family instances
 -- and newtypes
@@ -108,13 +108,6 @@ declaring whether it is known to be a singleton or not. The list of branches
 is stored using a special form of list, declared below, that ensures that the
 type variable is accurate.
 
-As of this writing (Dec 2012), it would not be appropriate to use a promoted
-type as the phantom type, so we use empty datatypes. We wish to have GHC
-remain compilable with GHC 7.2.1. If you are revising this code and GHC no
-longer needs to remain compatible with GHC 7.2.x, then please update this
-code to use promoted types.
-
-
 ************************************************************************
 *                                                                      *
                     Branch lists
@@ -125,11 +118,14 @@ code to use promoted types.
 type BranchIndex = Int  -- The index of the branch in the list of branches
                         -- Counting from zero
 
--- the phantom type labels
-data Unbranched deriving Typeable
-data Branched deriving Typeable
+-- promoted data type
+data BranchFlag = Branched | Unbranched
+type Branched = 'Branched
+deriving instance Typeable 'Branched
+type Unbranched = 'Unbranched
+deriving instance Typeable 'Unbranched
 
-data BranchList a br where
+data BranchList a (br :: BranchFlag) where
   FirstBranch :: a -> BranchList a br
   NextBranch :: a -> BranchList a br -> BranchList a Branched
 



More information about the ghc-commits mailing list