[commit: packages/base] master: Add new module Data.Type.Bool, defining &&, || and Not. (2cf7397)

git at git.haskell.org git at git.haskell.org
Thu Oct 31 18:30:53 UTC 2013


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/2cf7397a1c1627b328d48b78495ee58e4ce84f7a/base

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

commit 2cf7397a1c1627b328d48b78495ee58e4ce84f7a
Author: Richard Eisenberg <eir at cis.upenn.edu>
Date:   Wed Oct 30 16:32:06 2013 -0400

    Add new module Data.Type.Bool, defining &&, || and Not.
    
    This change was necessary given the instances for (==) in
    Data.Type.Equality. These need conjunction, and a local
    definition of conjunction doesn't work if a client is reasoning
    about equality. Both the client and the library need the
    same conjunction, so that is what Data.Type.Bool provides.


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

2cf7397a1c1627b328d48b78495ee58e4ce84f7a
 Data/Either.hs        |    2 +-
 Data/Type/Bool.hs     |   56 +++++++++++++++++++++++++++++++++++++++++++++++++
 Data/Type/Equality.hs |   10 +--------
 base.cabal            |    1 +
 4 files changed, 59 insertions(+), 10 deletions(-)

diff --git a/Data/Either.hs b/Data/Either.hs
index c0574d5..cf45e79 100644
--- a/Data/Either.hs
+++ b/Data/Either.hs
@@ -1,7 +1,7 @@
 {-# LANGUAGE Trustworthy #-}
 {-# LANGUAGE NoImplicitPrelude #-}
 {-# LANGUAGE DeriveDataTypeable, StandaloneDeriving #-}
-{-# LANGUAGE DataKinds, TypeFamilies, TypeOperators, UndecidableInstances #-}
+{-# LANGUAGE PolyKinds, DataKinds, TypeFamilies, TypeOperators, UndecidableInstances #-}
 
 -----------------------------------------------------------------------------
 -- |
diff --git a/Data/Type/Bool.hs b/Data/Type/Bool.hs
new file mode 100644
index 0000000..705db9e
--- /dev/null
+++ b/Data/Type/Bool.hs
@@ -0,0 +1,56 @@
+{-# LANGUAGE TypeFamilies, TypeOperators, DataKinds, NoImplicitPrelude,
+             PolyKinds #-}
+
+-----------------------------------------------------------------------------
+-- |
+-- Module      :  Data.Type.Bool
+-- License     :  BSD-style (see the LICENSE file in the distribution)
+--
+-- Maintainer  :  libraries at haskell.org
+-- Stability   :  experimental
+-- Portability :  not portable
+--
+-- Basic operations on type-level Booleans.
+--
+-- /Since: 4.7.0.0/
+-----------------------------------------------------------------------------
+
+module Data.Type.Bool (
+  If, type (&&), type (||), Not
+  ) where
+
+import Data.Bool
+
+-- This needs to be in base because (&&) is used in Data.Type.Equality.
+-- The other functions do not need to be in base, but seemed to be appropriate
+-- here.
+
+-- | Type-level "If". @If True a b@ ==> @a@; @If False a b@ ==> @b@
+type family If cond tru fls where
+  If True  tru fls = tru
+  If False tru fls = fls
+
+-- | Type-level "and"
+type family a && b where
+  False && a     = False
+  True  && a     = a
+  a     && False = False
+  a     && True  = a
+  a     && a     = a
+infixr 3 &&
+
+-- | Type-level "or"
+type family a || b where
+  False || a     = a
+  True  || a     = True
+  a     || False = a
+  a     || True  = True
+  a     || a     = a
+infixr 2 ||
+
+-- | Type-level "not"
+type family Not a where
+  Not False = True
+  Not True  = False
+
+  
\ No newline at end of file
diff --git a/Data/Type/Equality.hs b/Data/Type/Equality.hs
index c0b145b..464f7d2 100644
--- a/Data/Type/Equality.hs
+++ b/Data/Type/Equality.hs
@@ -47,6 +47,7 @@ import GHC.Enum
 import GHC.Show
 import GHC.Read
 import GHC.Base
+import Data.Type.Bool
 
 infix 4 :~:
 
@@ -150,15 +151,6 @@ type family EqOrdering a b where
 
 type EqUnit (a :: ()) (b :: ()) = True
 
--- more complicated types need a type-level And:
-type family a && b where
-  False && x = False
-  True  && x = x
-  x && False = False
-  x && True  = x
-  x && x     = x
-infixr 3 &&
-
 type family EqList a b where
   EqList '[]        '[]        = True
   EqList (h1 ': t1) (h2 ': t2) = (h1 == h2) && (t1 == t2)
diff --git a/base.cabal b/base.cabal
index 3c9fad8..8192f58 100644
--- a/base.cabal
+++ b/base.cabal
@@ -143,6 +143,7 @@ Library
         Data.String
         Data.Traversable
         Data.Tuple
+        Data.Type.Bool
         Data.Type.Coercion
         Data.Type.Equality
         Data.Typeable



More information about the ghc-commits mailing list