[commit: ghc] master: Add a caveat to the GHC.Generics examples about :+: nesting (88f20bd)
git at git.haskell.org
git at git.haskell.org
Mon Jul 24 15:55:25 UTC 2017
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/88f20bdb60fb9469fa8ae953f7c2509d1913fdf7/ghc
>---------------------------------------------------------------
commit 88f20bdb60fb9469fa8ae953f7c2509d1913fdf7
Author: Ryan Scott <ryan.gl.scott at gmail.com>
Date: Mon Jul 24 11:54:37 2017 -0400
Add a caveat to the GHC.Generics examples about :+: nesting
Summary:
GHC's choice in how it nests `:+:` can sometimes affect the
implementaiton of `GHC.Generics`-related code, so we should make a note of
this in the examples we provide. Fixes #9453.
Test Plan: Read it, like it, build it, ship it
Reviewers: bgamari, austin, hvr
Reviewed By: bgamari
Subscribers: rwbarton, thomie
GHC Trac Issues: #9453
Differential Revision: https://phabricator.haskell.org/D3782
>---------------------------------------------------------------
88f20bdb60fb9469fa8ae953f7c2509d1913fdf7
docs/users_guide/glasgow_exts.rst | 15 +++++++++--
libraries/base/GHC/Generics.hs | 52 ++++++++++++++++++++++-----------------
2 files changed, 43 insertions(+), 24 deletions(-)
diff --git a/docs/users_guide/glasgow_exts.rst b/docs/users_guide/glasgow_exts.rst
index fddf993..eb99959 100644
--- a/docs/users_guide/glasgow_exts.rst
+++ b/docs/users_guide/glasgow_exts.rst
@@ -14025,8 +14025,19 @@ we show generic serialization: ::
instance (Serialize a) => GSerialize (K1 i a) where
gput (K1 x) = put x
-Typically this class will not be exported, as it only makes sense to
-have instances for the representation types.
+A caveat: this encoding strategy may not be reliable across different versions
+of GHC. When deriving a ``Generic`` instance is free to choose any nesting of
+``:+:`` and ``:*:`` it chooses, so if GHC chooses ``(a :+: b) :+: c``, then the
+encoding for ``a`` would be ``[O, O]``, ``b`` would be ``[O, I]``, and ``c``
+would be ``[I]``. However, if GHC chooses ``a :+: (b :+: c)``, then the
+encoding for ``a`` would be ``[O]``, ``b`` would be ``[I, O]``, and ``c`` would
+be ``[I, I]``. (In practice, the current implementation tries to produce a
+more-or-less balanced nesting of ``:+:`` and ``:*:`` so that the traversal of
+the structure of the datatype from the root to a particular component can be
+performed in logarithmic rather than linear time.)
+
+Typically this ``GSerialize`` class will not be exported, as it only makes
+sense to have instances for the representation types.
Unlifted representation types
-----------------------------
diff --git a/libraries/base/GHC/Generics.hs b/libraries/base/GHC/Generics.hs
index cc85a1d..14184c2 100644
--- a/libraries/base/GHC/Generics.hs
+++ b/libraries/base/GHC/Generics.hs
@@ -1,23 +1,23 @@
-{-# LANGUAGE CPP #-}
-{-# LANGUAGE DataKinds #-}
-{-# LANGUAGE DeriveFunctor #-}
+{-# LANGUAGE CPP #-}
+{-# LANGUAGE DataKinds #-}
+{-# LANGUAGE DeriveFunctor #-}
+{-# LANGUAGE DeriveGeneric #-}
+{-# LANGUAGE FlexibleContexts #-}
+{-# LANGUAGE FlexibleInstances #-}
+{-# LANGUAGE GADTs #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
-{-# LANGUAGE DeriveGeneric #-}
-{-# LANGUAGE FlexibleContexts #-}
-{-# LANGUAGE FlexibleInstances #-}
-{-# LANGUAGE GADTs #-}
-{-# LANGUAGE KindSignatures #-}
-{-# LANGUAGE MagicHash #-}
-{-# LANGUAGE NoImplicitPrelude #-}
-{-# LANGUAGE PolyKinds #-}
-{-# LANGUAGE ScopedTypeVariables #-}
-{-# LANGUAGE StandaloneDeriving #-}
-{-# LANGUAGE Trustworthy #-}
-{-# LANGUAGE TypeFamilies #-}
-{-# LANGUAGE TypeInType #-}
-{-# LANGUAGE TypeOperators #-}
-{-# LANGUAGE TypeSynonymInstances #-}
-{-# LANGUAGE UndecidableInstances #-}
+{-# LANGUAGE KindSignatures #-}
+{-# LANGUAGE MagicHash #-}
+{-# LANGUAGE NoImplicitPrelude #-}
+{-# LANGUAGE PolyKinds #-}
+{-# LANGUAGE ScopedTypeVariables #-}
+{-# LANGUAGE StandaloneDeriving #-}
+{-# LANGUAGE Trustworthy #-}
+{-# LANGUAGE TypeFamilies #-}
+{-# LANGUAGE TypeInType #-}
+{-# LANGUAGE TypeOperators #-}
+{-# LANGUAGE TypeSynonymInstances #-}
+{-# LANGUAGE UndecidableInstances #-}
-----------------------------------------------------------------------------
-- |
@@ -256,9 +256,9 @@ module GHC.Generics (
-- all the constructors and fields as needed. However, users /should not rely on
-- a specific nesting strategy/ for ':+:' and ':*:' being used. The compiler is
-- free to choose any nesting it prefers. (In practice, the current implementation
--- tries to produce a more or less balanced nesting, so that the traversal of the
--- structure of the datatype from the root to a particular component can be performed
--- in logarithmic rather than linear time.)
+-- tries to produce a more-or-less balanced nesting, so that the traversal of
+-- the structure of the datatype from the root to a particular component can be
+-- performed in logarithmic rather than linear time.)
-- ** Defining datatype-generic functions
--
@@ -351,6 +351,14 @@ module GHC.Generics (
-- encode' ('R1' x) = True : encode' x
-- @
--
+-- (Note that this encoding strategy may not be reliable across different
+-- versions of GHC. Recall that the compiler is free to choose any nesting
+-- of ':+:' it chooses, so if GHC chooses @(a ':+:' b) ':+:' c@, then the
+-- encoding for @a@ would be @[False, False]@, @b@ would be @[False, True]@,
+-- and @c@ would be @[True]@. However, if GHC chooses @a ':+:' (b ':+:' c)@,
+-- then the encoding for @a@ would be @[False]@, @b@ would be @[True, False]@,
+-- and @c@ would be @[True, True]@.)
+--
-- In the case for ':*:', we append the encodings of the two subcomponents:
--
-- @
More information about the ghc-commits
mailing list