[commit: ghc] master: Add Data.Void to base (re #9814) (a97f90c)

git at git.haskell.org git at git.haskell.org
Fri Nov 21 17:34:08 UTC 2014


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/a97f90cecb6351a6db5a62c1551fcbf079b0acdd/ghc

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

commit a97f90cecb6351a6db5a62c1551fcbf079b0acdd
Author: Herbert Valerio Riedel <hvr at gnu.org>
Date:   Fri Nov 21 18:30:14 2014 +0100

    Add Data.Void to base (re #9814)
    
    This adds the module `Data.Void` (formerly provided by Edward Kmett's `void`
    package) to `base`.
    
    The original Haskell98 compatible implementation has been modified to use
    modern GHC features (among others this makes use of `EmptyCase` as
    motivated by #2431), and `vacuousM` was dropped since it's redundant now
    with the AMP in place.  Instances for classes not part of `base` had to be
    dropped as well.
    
    TODO: Documentation could be improved
    
    Reviewed By: ekmett, austin
    
    Differential Revision: https://phabricator.haskell.org/D506


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

a97f90cecb6351a6db5a62c1551fcbf079b0acdd
 libraries/base/Data/Void.hs | 74 +++++++++++++++++++++++++++++++++++++++++++++
 libraries/base/base.cabal   |  1 +
 libraries/base/changelog.md |  3 ++
 3 files changed, 78 insertions(+)

diff --git a/libraries/base/Data/Void.hs b/libraries/base/Data/Void.hs
new file mode 100644
index 0000000..a4f8778
--- /dev/null
+++ b/libraries/base/Data/Void.hs
@@ -0,0 +1,74 @@
+{-# LANGUAGE AutoDeriveTypeable #-}
+{-# LANGUAGE DeriveDataTypeable #-}
+{-# LANGUAGE DeriveGeneric #-}
+{-# LANGUAGE EmptyCase #-}
+{-# LANGUAGE Safe #-}
+{-# LANGUAGE StandaloneDeriving #-}
+
+-----------------------------------------------------------------------------
+-- |
+-- Copyright   :  (C) 2008-2014 Edward Kmett
+-- License     :  BSD-style (see the file libraries/base/LICENSE)
+--
+-- Maintainer  :  Edward Kmett <ekmett at gmail.com>
+-- Stability   :  provisional
+-- Portability :  portable
+--
+-- A logically uninhabited data type, used to indicate that a given
+-- term should not exist.
+--
+-- /Since: 4.8.0.0/
+----------------------------------------------------------------------------
+module Data.Void
+    ( Void
+    , absurd
+    , vacuous
+    ) where
+
+import Control.Exception
+import Data.Data
+import Data.Ix
+import GHC.Generics
+
+-- | Uninhabited data type
+--
+-- /Since: 4.8.0.0/
+data Void deriving (Generic)
+
+deriving instance Data Void
+
+instance Eq Void where
+    _ == _ = True
+
+instance Ord Void where
+    compare _ _ = EQ
+
+-- | Reading a 'Void' value is always a parse error, considering
+-- 'Void' as a data type with no constructors.
+instance Read Void where
+    readsPrec _ _ = []
+
+instance Show Void where
+    showsPrec _ = absurd
+
+instance Ix Void where
+    range _     = []
+    index _     = absurd
+    inRange _   = absurd
+    rangeSize _ = 0
+
+instance Exception Void
+
+-- | Since 'Void' values logically don't exist, this witnesses the
+-- logical reasoning tool of \"ex falso quodlibet\".
+--
+-- /Since: 4.8.0.0/
+absurd :: Void -> a
+absurd a = case a of {}
+
+-- | If 'Void' is uninhabited then any 'Functor' that holds only
+-- values of type 'Void' is holding no values.
+--
+-- /Since: 4.8.0.0/
+vacuous :: Functor f => f Void -> f a
+vacuous = fmap absurd
diff --git a/libraries/base/base.cabal b/libraries/base/base.cabal
index ca619ca..bde2a29 100644
--- a/libraries/base/base.cabal
+++ b/libraries/base/base.cabal
@@ -170,6 +170,7 @@ Library
         Data.Typeable.Internal
         Data.Unique
         Data.Version
+        Data.Void
         Data.Word
         Debug.Trace
         Foreign
diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md
index 56bfc31..7825c97 100644
--- a/libraries/base/changelog.md
+++ b/libraries/base/changelog.md
@@ -83,6 +83,9 @@
   * New module `Data.Bifunctor` providing the `Bifunctor(bimap,first,second)`
     class (previously defined in `bifunctors` package) (#9682)
 
+  * New module `Data.Void` providing the canonical uninhabited type `Void`
+    (previously defined in `void` package) (#9814)
+
   * Update Unicode class definitions to Unicode version 7.0
 
   * Add `Alt`, an `Alternative` wrapper, to `Data.Monoid`. (#9759)



More information about the ghc-commits mailing list