[commit: ghc] wip/ttypeable: Documentation (2e96c20)

git at git.haskell.org git at git.haskell.org
Mon Feb 13 15:17:00 UTC 2017


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

On branch  : wip/ttypeable
Link       : http://ghc.haskell.org/trac/ghc/changeset/2e96c2008eb2396738f46f0d25893d219101687b/ghc

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

commit 2e96c2008eb2396738f46f0d25893d219101687b
Author: Ben Gamari <ben at smart-cactus.org>
Date:   Sun Feb 12 20:22:33 2017 -0500

    Documentation


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

2e96c2008eb2396738f46f0d25893d219101687b
 libraries/base/Data/Type/Equality.hs |  2 ++
 libraries/base/Type/Reflection.hs    | 26 ++++++++++++++++++++++++++
 libraries/base/changelog.md          |  9 +++++++++
 3 files changed, 37 insertions(+)

diff --git a/libraries/base/Data/Type/Equality.hs b/libraries/base/Data/Type/Equality.hs
index 503a3f0..73f8407 100644
--- a/libraries/base/Data/Type/Equality.hs
+++ b/libraries/base/Data/Type/Equality.hs
@@ -140,6 +140,8 @@ deriving instance a ~ b => Bounded (a :~: b)
 
 -- | Kind heterogeneous propositional equality. Like '(:~:)', @a :~~: b@ is
 -- inhabited by a terminating value if and only if @a@ is the same type as @b at .
+--
+-- @since 4.10.0.0
 data (a :: k1) :~~: (b :: k2) where
    HRefl :: a :~~: a
 
diff --git a/libraries/base/Type/Reflection.hs b/libraries/base/Type/Reflection.hs
index 75352df..37efcba 100644
--- a/libraries/base/Type/Reflection.hs
+++ b/libraries/base/Type/Reflection.hs
@@ -2,6 +2,29 @@
 {-# LANGUAGE NoImplicitPrelude #-}
 {-# LANGUAGE PatternSynonyms #-}
 
+-----------------------------------------------------------------------------
+-- |
+-- Module      :  Type.Reflection
+-- Copyright   :  (c) The University of Glasgow, CWI 2001--2017
+-- License     :  BSD-style (see the file libraries/base/LICENSE)
+--
+-- Maintainer  :  libraries at haskell.org
+-- Stability   :  experimental
+-- Portability :  non-portable (requires GADTs and compiler support)
+--
+-- This provides a type-indexed type representation mechanism, similar to that
+-- described by,
+--
+-- * Simon Peyton-Jones, Stephanie Weirich, Richard Eisenberg,
+-- Dimitrios Vytiniotis. "A reflection on types." /Proc. Philip Wadler's 60th
+-- birthday Festschrift/, Edinburgh (April 2016).
+--
+-- The interface provides 'TypeRep', a type representation which can
+-- be safely decomposed and composed. See "Data.Dynamic" for an example of this.
+--
+-- @since 4.10.0.0
+--
+-----------------------------------------------------------------------------
 module Type.Reflection
     ( -- * The Typeable class
       I.Typeable
@@ -24,6 +47,9 @@ module Type.Reflection
     , I.typeRepKind
 
       -- ** Quantified
+      --
+      -- "Data.Typeable" exports a variant of this interface (named differently
+      -- for backwards compatibility).
     , I.SomeTypeRep(..)
     , I.typeRepXTyCon
     , I.rnfSomeTypeRep
diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md
index aa7302d..fd8f188 100644
--- a/libraries/base/changelog.md
+++ b/libraries/base/changelog.md
@@ -56,6 +56,15 @@
     imported from `Control.Applicative`. It is likely to be added to the
     `Prelude` in the future. (#13191)
 
+  * A new module exposing GHC's new type-indexed type representation
+    mechanism, `Type.Reflection`, is now provided.
+
+  * `Data.Dynamic` now exports the `Dyn` data constructor, enabled by the new
+    type-indexed type representation mechanism.
+
+  * `Data.Type.Equality` now provides a kind heterogeneous type equality type,
+    `(:~~:)`.
+
 ## 4.9.0.0  *May 2016*
 
   * Bundled with GHC 8.0



More information about the ghc-commits mailing list