[commit: ghc] master: Document the list data type (60b547b)

git at git.haskell.org git at git.haskell.org
Thu Oct 4 15:39:02 UTC 2018


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

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

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

commit 60b547b583f27f436912acd70e674cd9f34d72b2
Author: Alec Theriault <alec.theriault at gmail.com>
Date:   Thu Oct 4 11:18:32 2018 -0400

    Document the list data type
    
    Summary: Also qualified some identifier hyperlinks along the way.
    
    Reviewers: bgamari
    
    Reviewed By: bgamari
    
    Subscribers: rwbarton, carter
    
    GHC Trac Issues: #4861
    
    Differential Revision: https://phabricator.haskell.org/D5158


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

60b547b583f27f436912acd70e674cd9f34d72b2
 libraries/ghc-prim/GHC/Magic.hs | 18 +++++++++---------
 libraries/ghc-prim/GHC/Types.hs | 28 ++++++++++++++++++++++++----
 2 files changed, 33 insertions(+), 13 deletions(-)

diff --git a/libraries/ghc-prim/GHC/Magic.hs b/libraries/ghc-prim/GHC/Magic.hs
index ae95bfc..8bc8852 100644
--- a/libraries/ghc-prim/GHC/Magic.hs
+++ b/libraries/ghc-prim/GHC/Magic.hs
@@ -34,16 +34,16 @@ import GHC.Prim
 import GHC.CString ()
 import GHC.Types (RuntimeRep, TYPE)
 
--- | The call @inline f@ arranges that 'f' is inlined, regardless of
+-- | The call @inline f@ arranges that @f@ is inlined, regardless of
 -- its size. More precisely, the call @inline f@ rewrites to the
 -- right-hand side of @f@'s definition. This allows the programmer to
 -- control inlining from a particular call site rather than the
--- definition site of the function (c.f. 'INLINE' pragmas).
+-- definition site of the function (c.f. @INLINE@ pragmas).
 --
 -- This inlining occurs regardless of the argument to the call or the
 -- size of @f@'s definition; it is unconditional. The main caveat is
 -- that @f@'s definition must be visible to the compiler; it is
--- therefore recommended to mark the function with an 'INLINABLE'
+-- therefore recommended to mark the function with an @INLINABLE@
 -- pragma at its definition so that GHC guarantees to record its
 -- unfolding regardless of size.
 --
@@ -53,7 +53,7 @@ import GHC.Types (RuntimeRep, TYPE)
 inline :: a -> a
 inline x = x
 
--- | The call @noinline f@ arranges that 'f' will not be inlined.
+-- | The call @noinline f@ arranges that @f@ will not be inlined.
 -- It is removed during CorePrep so that its use imposes no overhead
 -- (besides the fact that it blocks inlining.)
 {-# NOINLINE noinline #-}
@@ -61,7 +61,7 @@ noinline :: a -> a
 noinline x = x
 
 -- | The 'lazy' function restrains strictness analysis a little. The
--- call @lazy e@ means the same as 'e', but 'lazy' has a magical
+-- call @lazy e@ means the same as @e@, but 'lazy' has a magical
 -- property so far as strictness analysis is concerned: it is lazy in
 -- its first argument, even though its semantics is strict. After
 -- strictness analysis has run, calls to 'lazy' are inlined to be the
@@ -74,8 +74,8 @@ noinline x = x
 -- > par :: a -> b -> b
 -- > par x y = case (par# x) of _ -> lazy y
 --
--- If 'lazy' were not lazy, 'par' would look strict in 'y' which
--- would defeat the whole purpose of 'par'.
+-- If 'lazy' were not lazy, 'Control.Parallel.par' would look strict in
+-- @y@ which would defeat the whole purpose of 'Control.Parallel.par'.
 --
 -- Like 'seq', the argument of 'lazy' can have an unboxed type.
 lazy :: a -> a
@@ -105,8 +105,8 @@ oneShot f = f
 -- Implementation note: This is wired in in MkId.hs, so the code here is
 -- mostly there to have a place for the documentation.
 
--- | Apply a function to a 'State# RealWorld' token. When manually applying
--- a function to `realWorld#`, it is necessary to use `NOINLINE` to prevent
+-- | Apply a function to a @'State#' 'RealWorld'@ token. When manually applying
+-- a function to `realWorld#`, it is necessary to use @NOINLINE@ to prevent
 -- semantically undesirable floating. `runRW#` is inlined, but only very late
 -- in compilation after all floating is complete.
 
diff --git a/libraries/ghc-prim/GHC/Types.hs b/libraries/ghc-prim/GHC/Types.hs
index 3275d57..d06c0be 100644
--- a/libraries/ghc-prim/GHC/Types.hs
+++ b/libraries/ghc-prim/GHC/Types.hs
@@ -97,6 +97,22 @@ type family Any :: k where { }
 *                                                                      *
 ********************************************************************* -}
 
+-- | The builtin list type, usually written in its non-prefix form @[a]@.
+--
+-- ==== __Examples__
+--
+-- Unless the OverloadedLists extension is enabled, list literals are
+-- syntatic sugar for repeated applications of @:@ and @[]@.
+--
+-- >>> 1:2:3:4:[] == [1,2,3,4]
+-- True
+--
+-- Similarly, unless the OverloadedStrings extension is enabled, string
+-- literals are syntactic sugar for a lists of characters.
+--
+-- >>> ['h','e','l','l','o'] == "hello"
+-- True
+--
 data [] a = [] | a : [a]
 
 
@@ -124,7 +140,8 @@ Haskell has type 'Char'.
 
 To convert a 'Char' to or from the corresponding 'Int' value defined
 by Unicode, use 'Prelude.toEnum' and 'Prelude.fromEnum' from the
-'Prelude.Enum' class respectively (or equivalently 'ord' and 'chr').
+'Prelude.Enum' class respectively (or equivalently 'Data.Char.ord' and
+'Data.Char.chr').
 -}
 data {-# CTYPE "HsChar" #-} Char = C# Char#
 
@@ -164,7 +181,8 @@ function, unless that function is itself in the 'IO' monad and called
 at some point, directly or indirectly, from @Main.main at .
 
 'IO' is a monad, so 'IO' actions can be combined using either the do-notation
-or the '>>' and '>>=' operations from the 'Monad' class.
+or the 'Prelude.>>' and 'Prelude.>>=' operations from the 'Prelude.Monad'
+class.
 -}
 newtype IO a = IO (State# RealWorld -> (# State# RealWorld, a #))
 type role IO representational
@@ -213,7 +231,7 @@ class a ~~ b
 
 -- | Lifted, homogeneous equality. By lifted, we mean that it
 -- can be bogus (deferred type error). By homogeneous, the two
--- types @a@ and @b@ must have the sme kinds.
+-- types @a@ and @b@ must have the same kinds.
 class a ~ b
   -- See also Note [The equality types story] in TysPrim
 
@@ -450,7 +468,9 @@ type KindBndr = Int
 #endif
 
 -- | The representation produced by GHC for conjuring up the kind of a
--- 'TypeRep'.  See Note [Representing TyCon kinds: KindRep] in TcTypeable.
+-- 'Data.Typeable.TypeRep'.
+
+-- See Note [Representing TyCon kinds: KindRep] in TcTypeable.
 data KindRep = KindRepTyConApp TyCon [KindRep]
              | KindRepVar !KindBndr
              | KindRepApp KindRep KindRep



More information about the ghc-commits mailing list