[Git][ghc/ghc][ghc-8.8] 3 commits: users-guide: Drop old release notes
Ben Gamari
gitlab at gitlab.haskell.org
Tue Apr 30 14:04:14 UTC 2019
Ben Gamari pushed to branch ghc-8.8 at Glasgow Haskell Compiler / GHC
Commits:
e1c3aa5b by Ben Gamari at 2019-04-25T23:03:31Z
users-guide: Drop old release notes
- - - - -
f175c306 by Ben Gamari at 2019-04-25T23:13:57Z
users-guide: Mention profiling break on 32-bit Windows
Due to #15934.
- - - - -
c56dad01 by Ben Gamari at 2019-04-26T17:53:21Z
gitlab-ci: Reintroduce DWARF-enabled bindists
It seems that this was inadvertently dropped in
1285d6b95fbae7858abbc4722bc2301d7fe40425.
- - - - -
5 changed files:
- .gitlab-ci.yml
- − docs/users_guide/8.2.1-notes.rst
- − docs/users_guide/8.6.1-notes.rst
- docs/users_guide/index.rst
- docs/users_guide/profiling.rst
Changes:
=====================================
.gitlab-ci.yml
=====================================
@@ -394,6 +394,21 @@ validate-x86_64-linux-deb9-unreg:
CONFIGURE_ARGS: --enable-unregisterised
TEST_ENV: "x86_64-linux-deb9-unreg"
+release-x86_64-linux-deb9-dwarf:
+ extends: .validate-linux
+ stage: build
+ image: "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb9:$DOCKER_REV"
+ allow_failure: true
+ variables:
+ CONFIGURE_ARGS: "--enable-dwarf-unwind"
+ BUILD_FLAVOUR: dwarf
+ TEST_ENV: "x86_64-linux-deb9"
+ artifacts:
+ when: always
+ expire_in: 2 week
+ cache:
+ key: linux-x86_64-deb9
+
#################################
# x86_64-linux-deb8
=====================================
docs/users_guide/8.2.1-notes.rst deleted
=====================================
@@ -1,527 +0,0 @@
-.. _release-8-2-1:
-
-Release notes for version 8.2.1
-===============================
-
-The significant changes to the various parts of the compiler are listed
-in the following sections. There have also been numerous bug fixes and
-performance improvements over the 8.0 branch.
-
-Highlights
-----------
-
-The highlights since the 8.0 release include:
-
-- A new, more expressive ``Typeable`` mechanism, ``Type.Reflection``
-
-- Colorful error messages with caret diagnostics
-
-- SCC annotations can now be used for declarations.
-
-- Heap overflow throws an exception in certain circumstances.
-
-- Improved code generation of join points
-
-- Deriving strategies
-
-- Compact regions support, allowing efficient garbage collection of large heaps
-
-- More reliable DWARF debug information
-
-Full details
-------------
-
-Package system
-~~~~~~~~~~~~~~
-
-- The long awaited Backpack module system is now fully usable. See
- :ghc-wiki:`the GHC Wiki <Backpack>` for details.
-
-Language
-~~~~~~~~
-
-- Pattern synonym signatures can now be applied to multiple patterns, just like
- value-level binding signatures. See :ref:`patsyn-typing` for details.
-
-- It is now possible to explicitly pick a strategy to use when deriving a
- class instance using the :ghc-flag:`-XDerivingStrategies` language extension
- (see :ref:`deriving-strategies`).
-
-- The new :ghc-flag:`-XUnboxedSums` extension allows more efficient representation
- of sum data. Some future GHC release will have support for worker/wrapper
- transformation of sum arguments and constructor unpacking.
-
-- Support for overloaded record fields via a new ``HasField`` class and
- associated compiler logic (see :ref:`record-field-selector-polymorphism`)
-
-- GHC now recognizes the ``COMPLETE`` language pragma, allowing the user to
- specify sets of patterns (including pattern synonyms) which constitute a
- complete pattern match. See :ref:`complete-pragma` for details.
-
-Compiler
-~~~~~~~~
-
-- GHC will now use ``ld.gold`` or ``ld.lld`` instead of the system's default
- ``ld``, if available. Linker availability will be evaluated at ``configure``
- time. The user can manually override which linker to use by passing the ``LD``
- variable to ``configure``. You can revert to the old behavior of using the
- system's default ``ld`` by passing the ``--disable-ld-override`` flag to
- ``configure``.
-
-- GHC now uses section splitting (i.e. :ghc-flag:`-split-sections`) instead of
- object splitting (i.e. :ghc-flag:`-split-objs`) as the default mechanism for
- linker-based dead code removal. While the effect is the same, split sections
- tends to produce significantly smaller objects than split objects and more
- closely mirrors the approach used by other compilers. Split objects will
- be deprecated and eventually removed in a future GHC release.
-
- Note that some versions of the ubiquitous BFD linker exhibit performance
- trouble with large libraries with section splitting enabled (see
- :ghc-ticket:`13739`). It is recommended that you use either the ``gold`` or
- ``lld`` linker if you observe this. This will require that you install one of
- these compilers, rerun ``configure``, and reinstall GHC.
-
- Split sections is enabled by default in the official binary distributions for
- platforms that support it.
-
-- Old profiling flags ``-auto-all``, ``-auto``, and ``-caf-all`` are deprecated
- and their usage provokes a compile-time warning.
-
-- Support for adding cost centres to declarations is added. The same ``SCC``
- syntax can be used, in addition to a new form for specifying the cost centre
- name. See :ref:`scc-pragma` for examples.
-
-- GHC is now much more particular about :ghc-flag:`-XDefaultSignatures`. The
- type signature for a default method of a type class must now be the same as
- the corresponding main method's type signature modulo differences in the
- signatures' contexts. Otherwise, the typechecker will reject that class's
- definition. See :ref:`class-default-signatures` for further details.
-
-- :ghc-flag:`-XDeriveAnyClass` is no longer limited to type classes whose
- argument is of kind ``*`` or ``* -> *``.
-
-- The means by which :ghc-flag:`-XDeriveAnyClass` infers instance contexts has
- been completely overhauled. The instance context is now inferred using the
- type signatures (and default type signatures) of the derived class's methods
- instead of using the datatype's definition, which often led to
- over-constrained instances or instances that didn't typecheck (or worse,
- triggered GHC panics). See the section on
- :ref:`DeriveAnyClass <derive-any-class>` for more details.
-
-- GHC now allows standalone deriving using :ghc-flag:`-XDeriveAnyClass` on
- any data type, even if its data constructors are not in scope. This is
- consistent with the fact that this code (in the presence of
- :ghc-flag:`-XDeriveAnyClass`): ::
-
- deriving instance C T
-
- is exactly equivalent to: ::
-
- instance C T
-
- and the latter code has no restrictions about whether the data constructors
- of ``T`` are in scope.
-
-- :ghc-flag:`-XGeneralizedNewtypeDeriving` now supports deriving type classes
- with associated type families. See the section on
- :ref:`GeneralizedNewtypeDeriving and associated type families
- <gnd-and-associated-types>`.
-
-- :ghc-flag:`-XGeneralizedNewtypeDeriving` will no longer infer constraints
- when deriving a class with no methods. That is, this code: ::
-
- class Throws e
- newtype Id a = MkId a
- deriving Throws
-
- will now generate this instance: ::
-
- instance Throws (Id a)
-
- instead of this instance: ::
-
- instance Throws a => Throws (Id a)
-
- This change was motivated by the fact that the latter code has a strictly
- redundant ``Throws a`` constraint, so it would emit a warning when compiled
- with :ghc-flag:`-Wredundant-constraints`. The latter instance could still
- be derived if so desired using :ghc-flag:`-XStandaloneDeriving`: ::
-
- deriving instance Throws a => Throws (Id a)
-
-- Add warning flag :ghc-flag:`-Wcpp-undef` which passes ``-Wundef`` to the C
- pre-processor causing the pre-processor to warn on uses of the ``#if``
- directive on undefined identifiers.
-
-- GHC will no longer automatically infer the kind of higher-rank type synonyms;
- you must explicitly annotate the synonym with a kind signature.
- For example, given::
-
- data T :: (forall k. k -> Type) -> Type
-
- to define a synonym of ``T``, you must write::
-
- type TSyn = (T :: (forall k. k -> Type) -> Type)
-
-- The Mingw-w64 toolchain for the Windows version of GHC has been updated. GHC now uses
- `GCC 6.2.0` and `binutils 2.27`.
-
-- Previously, :ghc-flag:`-Wmissing-methods` would not warn whenever a type
- class method beginning with an underscore was not implemented in an instance.
- For instance, this code would compile without any warnings: ::
-
- class Foo a where
- _Bar :: a -> Int
-
- instance Foo Int
-
- :ghc-flag:`-Wmissing-methods` will now warn that ``_Bar`` is not implemented
- in the ``Foo Int`` instance.
-
-- A new flag :ghc-flag:`-ddump-json` has been added. This flag dumps compiler
- output as JSON documents. It is experimental and will be refined depending
- on feedback from tooling authors for the next release.
-
-- GHC is now able to better optimize polymorphic expressions by using known
- superclass dictionaries where possible. Some examples: ::
-
- -- uses of `Monad IO` or `Applicative IO` here are improved
- foo :: MonadBaseControl IO m => ...
-
- -- uses of `Monoid MyMonoid` here are improved
- bar :: MonadWriter MyMonoid m => ...
-
-- GHC now derives the definition of ``<$`` when using :ghc-flag:`-XDeriveFunctor`
- rather than using the default definition. This prevents unnecessary
- allocation and a potential space leak when deriving ``Functor`` for
- a recursive type.
-
-- The :ghc-flag:`-XExtendedDefaultRules` extension now defaults multi-parameter
- typeclasses. See :ghc-ticket:`12923`.
-
-- GHC now ignores ``RULES`` for data constructors (:ghc-ticket:`13290`).
- Previously, it accepted::
-
- {-# RULES "NotAllowed" forall x. Just x = e #-}
-
- That rule will no longer take effect, and a warning will be issued. ``RULES``
- may still mention data constructors, but not in the outermost position::
-
- {-# RULES "StillWorks" forall x. f (Just x) = e #-}
-
-- Type synonyms can no longer appear in the class position of an instance.
- This means something like this is no longer allowed: ::
-
- type ReadShow a = (Read a, Show a)
- instance Read Foo
- instance Show Foo
- instance ReadShow Foo -- illegal
-
- See :ghc-ticket:`13267`.
-
-- Validity checking for associated type family instances has tightened
- somewhat. Before, this would be accepted: ::
-
- class Foo a where
- type Bar a
-
- instance Foo (Either a b) where
- type Bar (Either c d) = d -> c
-
- This is now disallowed, as the type variables used in the `Bar` instance do
- not match those in the instance head. This instance can be fixed by changing
- it to: ::
-
- instance Foo (Either a b) where
- type Bar (Either a b) = b -> a
-
- See the section on :ref:`associated type family instances <assoc-data-inst>`
- for more information.
-
-- A bug involving the interaction between :ghc-flag:`-XMonoLocalBinds` and
- :ghc-flag:`-XPolyKinds` has been fixed. This can cause some programs to fail
- to typecheck in case explicit kind signatures are not provided. See
- :ref:`kind-generalisation` for an example.
-
-GHCi
-~~~~
-
-- Added :ghc-flag:`-flocal-ghci-history` which uses current directory for `.ghci-history`.
-
-- Added support for :ghc-flag:`-XStaticPointers` in interpreted modules. Note, however,
- that ``static`` expressions are still not allowed in expressions evaluated in the REPL.
-
-- Added support for :ghci-cmd:`:type +d` and :ghci-cmd:`:type +v`. (:ghc-ticket:`11975`)
-
-Template Haskell
-~~~~~~~~~~~~~~~~
-
-- Reifying types that contain unboxed tuples now works correctly. (Previously,
- Template Haskell reified unboxed tuples as boxed tuples with twice their
- appropriate arity.)
-
-- Splicing singleton unboxed tuple types (e.g., ``(# Int #)``) now works
- correctly. Previously, Template Haskell would implicitly remove the
- parentheses when splicing, which would turn ``(# Int #)`` into ``Int``.
-
-- Add support for type signatures in patterns. (:ghc-ticket:`12164`)
-
-- Make quoting and reification return the same types. (:ghc-ticket:`11629`)
-
-- More kind annotations appear in the left-hand sides of reified closed
- type family equations, in order to disambiguate types that would otherwise
- be ambiguous in the presence of :ghc-flag:`-XPolyKinds`.
- (:ghc-ticket:`12646`)
-
-- Quoted type signatures are more accurate with respect to implicitly
- quantified type variables. Before, if you quoted this: ::
-
- [d| id :: a -> a
- id x = x
- |]
-
- then the code that Template Haskell would give back to you would actually be
- this instead: ::
-
- id :: forall a. a -> a
- id x = x
-
- That is, quoting would explicitly quantify all type variables, even ones
- that were implicitly quantified in the source. This could be especially
- harmful if a kind variable was implicitly quantified. For example, if
- you took this quoted declaration: ::
-
- [d| idProxy :: forall proxy (b :: k). proxy b -> proxy b
- idProxy x = x
- |]
-
- and tried to splice it back in, you'd get this instead: ::
-
- idProxy :: forall k proxy (b :: k). proxy b -> proxy b
- idProxy x = x
-
- Now ``k`` is explicitly quantified, and that requires turning on
- :ghc-flag:`-XTypeInType`, whereas the original declaration did not!
-
- Template Haskell quoting now respects implicit quantification in type
- signatures, so the quoted declarations above now correctly leave the
- type variables ``a`` and ``k`` as implicitly quantified.
- (:ghc-ticket:`13018` and :ghc-ticket:`13123`)
-
-- Looking up type constructors with symbol names (e.g., ``+``) now works
- as expected (:ghc-ticket:`11046`)
-
-
-Runtime system
-~~~~~~~~~~~~~~
-
-- Heap overflow throws a catchable exception, provided that it was detected
- by the RTS during a GC cycle due to the program exceeding a limit set by
- ``+RTS -M`` (see :rts-flag:`-M ⟨size⟩`), and not due to an allocation being refused
- by the operating system. This exception is thrown to the same thread that
- receives ``UserInterrupt`` exceptions, and may be caught by user programs.
-
-- Added support for *Compact Regions*, which offer a way to manually
- move long-lived data outside of the heap so that the garbage
- collector does not have to trace it repeatedly. Compacted data can
- also be serialized, stored, and deserialized again later by the same
- program. For more details see the :ghc-compact-ref:`GHC.Compact.` module.
- Moreover, see the ``compact`` library on `Hackage
- <https://hackage.haskell.org/package/compact>`_ for a high-level interface.
-
-- There is new support for improving performance on machines with a
- Non-Uniform Memory Architecture (NUMA). See :rts-flag:`--numa`.
- This is supported on Linux and Windows systems.
-
-- The garbage collector can be told to use fewer threads than the
- global number of capabilities set by :rts-flag:`-N ⟨x⟩`. By default, the garbage
- collector will use a number of threads equal to the lesser of the global number
- of capabilities or the number of physical cores. See :rts-flag:`-qn ⟨x⟩`, and a
- `blog post <http://simonmar.github.io/posts/2016-12-08-Haskell-in-the-datacentre.html>`_
- that describes this.
-
-- The :ref:`heap profiler <prof-heap>` can now emit heap census data to the GHC
- event log, allowing heap profiles to be correlated with other tracing events
- (see :ghc-ticket:`11094`).
-
-- Some bugs have been fixed in the stack-trace implementation in the
- profiler that sometimes resulted in incorrect stack traces and
- costs attributed to the wrong cost centre stack (see :ghc-ticket:`5654`).
-
-- Added processor group support for Windows. This allows the runtime to allocate
- threads to all cores in systems which have multiple processor groups.
- (e.g. > 64 cores, see :ghc-ticket:`11054`)
-
-- Output of :ref:`Event log <rts-eventlog>` data can now be configured,
- enabling external tools to collect and analyze the event log data while the
- application is still running.
-
-- ``advapi32``, ``shell32`` and ``user32`` are now automatically loaded in GHCi.
- ``libGCC`` is also loaded when a dependency requires it. See
- :ghc-ticket:`13189`.
-
-hsc2hs
-~~~~~~
-
-- Version number 0.68.2
-
-Libraries
----------
-
-array
-~~~~~
-
-- Version number 0.5.2.0 (was 0.5.0.0)
-
-.. _lib-base:
-
-base
-~~~~
-
-See ``changelog.md`` in the ``base`` package for full release notes.
-
-- Version number 4.10.0.0 (was 4.9.0.0)
-
-- ``Data.Either`` now provides ``fromLeft`` and ``fromRight``
-
-- ``Data.Type.Coercion`` now provides ``gcoerceWith``, which is analogous to
- ``gcastWith`` from ``Data.Type.Equality``.
-
-- The ``Read1`` and ``Read2`` classes in ``Data.Functor.Classes`` have new
- methods, ``liftReadList(2)`` and ``liftReadListPrec(2)``, that are defined in
- terms of ``ReadPrec`` instead of ``ReadS``. This matches the interface
- provided in GHC's version of the ``Read`` class, and allows users to write
- more efficient ``Read1`` and ``Read2`` instances.
-
-- Add ``type family AppendSymbol (m :: Symbol) (n :: Symbol) :: Symbol`` to
- ``GHC.TypeLits``
-
-- Add ``GHC.TypeNats`` module with ``Natural``-based ``KnownNat``. The ``Nat``
- operations in ``GHC.TypeLits`` are a thin compatibility layer on top.
- Note: the ``KnownNat`` evidence is changed from an ``Integer`` to a ``Natural``.
-
-- ``liftA2`` is now a method of the ``Applicative`` class. ``Traversable``
- deriving has been modified to use ``liftA2`` for the first two elements
- traversed in each constructor. ``liftA2`` is not yet in the ``Prelude``,
- and must currently be imported from ``Control.Applicative``. It is likely
- to be added to the ``Prelude`` in the future.
-
-binary
-~~~~~~
-
-- Version number 0.8.5.1 (was 0.7.1.0)
-
-bytestring
-~~~~~~~~~~
-
-- Version number 0.10.8.2 (was 0.10.4.0)
-
-Cabal
-~~~~~
-
-- Version number 2.0.0.0 (was 1.24.2.0)
-
-containers
-~~~~~~~~~~
-
-- Version number 0.5.10.2 (was 0.5.4.0)
-
-deepseq
-~~~~~~~
-
-- Version number 1.4.3.0 (was 1.3.0.2)
-
-directory
-~~~~~~~~~
-
-- Version number 1.3.0.2 (was 1.2.0.2)
-
-filepath
-~~~~~~~~
-
-- Version number 1.4.1.2 (was 1.3.0.2)
-
-ghc
-~~~
-
-- Version number 8.2.1
-
-ghc-boot
-~~~~~~~~
-
-- This is an internal package. Use with caution.
-
-ghc-compact
-~~~~~~~~~~~
-
-The ``ghc-compact`` library provides an experimental API for placing immutable
-data structures into a contiguous memory region. Data in these regions is not
-traced during garbage collection and can be serialized to disk or over the
-network.
-
-- Version number 0.1.0.0 (newly added)
-
-ghc-prim
-~~~~~~~~
-
-- Version number 0.5.1.0 (was 0.3.1.0)
-
-- Added new ``isByteArrayPinned#`` and ``isMutableByteArrayPinned#`` operation.
-
-- New function ``noinline`` in ``GHC.Magic`` lets you mark that a function
- should not be inlined. It is optimized away after the simplifier runs.
-
-hoopl
-~~~~~
-
-- Version number 3.10.2.2 (was 3.10.2.1)
-
-hpc
-~~~
-
-- Version number 0.6.0.3 (was 0.6.0.2)
-
-integer-gmp
-~~~~~~~~~~~
-
-- Version number 1.0.0.1 (was 1.0.0.1)
-
-process
-~~~~~~~
-
-- Version number 1.6.1.0 (was 1.4.3.0)
-
-template-haskell
-~~~~~~~~~~~~~~~~
-
-- Version 2.12.0.0 (was 2.11.1.0)
-
-- Added support for unboxed sums :ghc-ticket:`12478`.
-
-- Added support for visible type applications :ghc-ticket:`12530`.
-
-time
-~~~~
-
-- Version number 1.8.0.1 (was 1.6.0.1)
-
-unix
-~~~~
-
-- Version number 2.7.2.2 (was 2.7.2.1)
-
-Win32
-~~~~~
-
-- Version number 2.5.4.1 (was 2.3.1.1)
-
-Known bugs
-----------
-
-- At least one known program regresses in compile time significantly over 8.0.
- See :ghc-ticket:`13535`.
-
-- Some uses of type applications may cause GHC to panic. See :ghc-ticket:`13819`.
-
-- The compiler may loop during typechecking on some modules using
- :ghc-flag:`-XUndecidableInstances`. See :ghc-ticket:`13943`.
=====================================
docs/users_guide/8.6.1-notes.rst deleted
=====================================
@@ -1,292 +0,0 @@
-.. _release-8-6-1:
-
-Release notes for version 8.6.1
-===============================
-
-The significant changes to the various parts of the compiler are listed in the
-following sections. There have also been numerous bug fixes and performance
-improvements over the 8.4.1 release.
-
-
-Highlights
-----------
-
-The highlights, since the 8.4.1 release, are:
-
-- Programs are no longer constrained by the Windows ``MAX_PATH`` file path
- length limit. The file path limit is now approximately 32,767 characters. Note
- that GHC itself is still somewhat limited due to GCC not supporting file
- namespaced paths. Paths that are passed directly to the compiler, linker or
- other GNU tools are currently still constrained. See :ref:`windows-file-paths`
- for details.
-
-- Many, many bug fixes.
-
-
-Full details
-------------
-
-Language
-~~~~~~~~
-
-- Use of quantified type variables in constraints is now allowed via the
- :extension:`QuantifiedConstraints` language extension. This long-awaited feature
- enables users to encode significantly more precision in their types. For instance,
- the common ``MonadTrans`` typeclass could now make the expectation that an
- applied transformer is must be a ``Monad`` ::
-
- class (forall m. Monad m => Monad (t m)) => MonadTrans t where {- ... -}
-
- Additionally, quantification can enable terminating instance resolution
- where this previously was not possible. See :ref:`quantified-constraints` for
- details.
-
-- A new :extension:`DerivingVia` language extension has been added which allows
- the use of the ``via`` deriving strategy. For instance: ::
-
- newtype T = MkT Int
- deriving Monoid via (Sum Int)
-
- See :ref:`deriving-via` for more information.
-
-- A new :extension:`StarIsType` language extension has been added which controls
- whether ``*`` is parsed as ``Data.Kind.Type`` or a regular type operator.
- :extension:`StarIsType` is enabled by default.
-
-- GHC now permits the use of a wildcard type as the context of a standalone
- ``deriving`` declaration with the use of the
- :extension:`PartialTypeSignatures` language extension. For instance, this
- declaration: ::
-
- deriving instance _ => Eq (Foo a)
-
- Denotes a derived ``Eq (Foo a)`` instance, where the context is inferred in
- much the same way as ordinary ``deriving`` clauses do.
- See :ref:`partial-type-signatures`.
-
-- Data declarations with empty ``where`` clauses are no longer valid without the
- extension :extension:`GADTSyntax` enabled. For instance, consider the
- following, ::
-
- data T where
-
- The grammar is invalid in Haskell2010. Previously it could be compiled successfully
- without ``GADTs``. As of GHC 8.6.1, this is a parse error.
-
-- Incomplete patterns warning :ghc-flag:`-Wincomplete-patterns` is extended to
- guards in pattern bindings and ``if`` alternatives of :extension:`MultiWayIf`.
- For instance, consider the following, ::
-
- foo :: Bool -> Int
- foo b = if | b -> 1
-
- In GHC 8.6.1, it will raise the warning: ::
-
- <interactive>:2:12: warning: [-Wincomplete-patterns]
- Pattern match(es) are non-exhaustive
- In a multi-way if alternative:
- Guards do not cover entire pattern space
-
- See :ghc-ticket:`14773`.
-
-- Scoped type variables now work in default methods of class declarations
- and in pattern synonyms in Template Haskell. See :ghc-ticket:`14885`.
-
-- ``do`` expressions, lambda expressions, etc. to be directly used as
- a function argument, enabled with :extension:`BlockArguments`.
- See :ref:`More liberal syntax for function arguments <block-arguments>`
- for the full details.
-
-- Underscores in numeric literals (e.g. ``1_000_000``), enabled with
- :extension:`NumericUnderscores`.
- See :ref:`Numeric underscores <numeric-underscores>`
- for the full details.
-
-- CUSKs now require all kind variables to be explicitly quantified. This was
- already the case with :extension:`TypeInType`, but now :extension:`PolyKinds`
- also exhibits this behavior. This means that the following example is no
- longer considered to have a CUSK::
-
- data T1 :: k -> Type -- No CUSK: `k` is not explicitly quantified
-
-- Functionality of :extension:`TypeInType` has been subsumed by
- :extension:`PolyKinds`, and it is now merely a shorthand for
- :extension:`PolyKinds`, :extension:`DataKinds`, and :extension:`NoStarIsType`.
- The users are advised to avoid :extension:`TypeInType` due to its misleading
- name: the ``Type :: Type`` axiom holds regardless of whether it is enabled.
-
-- GHC has become more diligent about catching illegal uses of kind polymorphism.
- For instance, GHC 8.4 would accept the following without the use of
- :extension:`PolyKinds`::
-
- f :: forall k (a :: k). Proxy a
- f = Proxy
-
- This is now an error unless :extension:`PolyKinds` is enabled.
-
-- The plugin mechanism has been extended to allow plugins to run between frontend
- phases. Of particular note are the parser and typechecker plugins which run
- after parsing and typechecking have completed. Collectively, these new extension
- points are called :ref:`source plugins <source-plugins>`.
-
-- Type literals now could be used in type class instances without the extension
- :extension:`FlexibleInstances`.
-
- See :ghc-ticket:`13833`.
-
-- :extension:`MonadFailDesugaring` is now enabled by default. See
- `MonadFail Proposal (MFP)
- <https://prime.haskell.org/wiki/Libraries/Proposals/MonadFail>`__
- for more details.
-
-Compiler
-~~~~~~~~
-
-- GHC now no longer adds the current file's directory as a general include path
- calling the C compiler. Instead we use :ghc-flag:`-iquote` to only add it as
- an include path for `#include ""`. See :ghc-ticket:`14312`.
-
-- GHC now supports British spelling of :extension:`GeneralizedNewtypeDeriving`.
-
-- GHC now does significantly more constant folding in its core-to-core optimiser.
- This will result in significantly better code being generated for some
- programs. See :ghc-ticket:`9136`.
-
-- GHC now offers significantly more information about typed holes such as valid
- hole fits and refinement hole fits. See :ref:`Valid Hole Fits <typed-hole-valid-hole-fits>`
- for more information.
-
-- The code-generation effects of :ghc-flag:`-dynamic` can now be
- enabled independently by the flag
- :ghc-flag:`-fexternal-dynamic-refs`. If you don't know why you might
- need this, you don't need it.
-
-- :ghc-flag:`-Wcompat` now includes :ghc-flag:`-Wimplicit-kind-vars` to
- provide early detection of breakage that will be caused by implementation of
- `GHC proposal #24
- <https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0024-no-kind-vars.rst>`__
- in a future release.
-
-Plugins
-~~~~~~~
-
-- GHC's plugin mechanism now offers plugin authors control over their plugin's
- effect on recompilation checking. Specifically the ``Plugin`` record name has
- a new field ::
-
- data Plugin = Plugin {
- pluginRecompile :: [CommandLineOption] -> IO PluginRecompile
- , {- ... -}
- }
-
- data PluginRecompile = ForceRecompile | NoForceRecompile | MaybeRecompile Fingerprint
-
- Plugin based on ``defaultPlugin`` will have their previous recompilation
- behavior (``ForceRecompile``) preserved. However, plugins that are "pure" are
- encouraged to override this to either ``NoForceRecompile`` or ``MaybeRecompile``.
- See :ref:`plugin_recompilation` for details.
-
-- GHC now provides a class of new plugins: source plugins. These plugins can
- inspect and modify a variety of intermediate representations used by the
- compiler's frontend. These include:
-
- * The ability to modify the parser output
- * The ability to inspect the renamer output
- * The ability to modify the typechecked AST
- * The ability to modify Template Haskell splices
- * The ability to modify interface files as they are loaded
-
- See :ref:`source-plugins` for details.
-
-GHCi
-~~~~
-
-- Added an experimental :ghci-cmd:`:doc` command that displays the
- documentation for a declaration.
-
-Runtime system
-~~~~~~~~~~~~~~
-
-- The GHC runtime linker now prefers user shared libraries above system ones.
- When extra search directories are specified these are searched before anything
- else. This fixes ``iuuc`` on Windows given the proper search directories (e.g
- ``-L/mingw64/lib``).
-
-- The GHC runtime linker now uses ``LIBRARY_PATH`` and the runtime loader now also
- searches ``LD_LIBRARY_PATH``.
-
-- The GHC runtime on Windows is no longer constrained by the ``MAX_PATH`` file path
- length limitation. See :ref:`windows-file-paths`.
-
-- The runtime now allows use of the :rts-flag:`-hT` profiling variety on
- programs built with :ghc-flag:`-prof`.
-
-- The STM assertions mechanism (namely the ``always`` and ``alwaysSucceeds``
- functions) has been removed. This happened a bit earlier than proposed in the
- deprecation pragma included in GHC 8.4, but due to community feedback we
- decided to move ahead with the early removal.
-
-Template Haskell
-~~~~~~~~~~~~~~~~
-
-``ghc`` library
-~~~~~~~~~~~~~~~
-
-
-``base`` library
-~~~~~~~~~~~~~~~~
-
-- ``($!)`` is now representation-polymorphic like ``($)``.
-
-- The module ``Data.Functor.Contravariant`` has been moved from the
- ``contravariant`` package into ``base``. All the other modules in
- ``contravariant`` (``Data.Functor.Contravariant.Divisible``, etc.)
- have not been moved to ``base``, and they still reside in ``contravariant``.
-
-``ghc-prim`` library
-~~~~~~~~~~~~~~~~~~~~
-
-- Version number 0.5.2.1 (was 0.5.2.0)
-
-- Added new ``addWordC#`` operation for unsigned addition with carry.
-
-Build system
-~~~~~~~~~~~~
-
-
-Included libraries
-------------------
-
-The package database provided with this distribution also contains a number of
-packages other than GHC itself. See the changelogs provided with these packages
-for further change information.
-
-.. ghc-package-list::
-
- libraries/array/array.cabal: Dependency of ``ghc`` library
- libraries/base/base.cabal: Core library
- libraries/binary/binary.cabal: Dependency of ``ghc`` library
- libraries/bytestring/bytestring.cabal: Dependency of ``ghc`` library
- libraries/Cabal/Cabal/Cabal.cabal: Dependency of ``ghc-pkg`` utility
- libraries/containers/containers.cabal: Dependency of ``ghc`` library
- libraries/deepseq/deepseq.cabal: Dependency of ``ghc`` library
- libraries/directory/directory.cabal: Dependency of ``ghc`` library
- libraries/filepath/filepath.cabal: Dependency of ``ghc`` library
- compiler/ghc.cabal: The compiler itself
- libraries/ghci/ghci.cabal: The REPL interface
- libraries/ghc-boot/ghc-boot.cabal: Internal compiler library
- libraries/ghc-compact/ghc-compact.cabal: Core library
- libraries/ghc-prim/ghc-prim.cabal: Core library
- libraries/haskeline/haskeline.cabal: Dependency of ``ghci`` executable
- libraries/hpc/hpc.cabal: Dependency of ``hpc`` executable
- libraries/integer-gmp/integer-gmp.cabal: Core library
- libraries/mtl/mtl.cabal: Dependency of ``Cabal`` library
- libraries/parsec/parsec.cabal: Dependency of ``Cabal`` library
- libraries/process/process.cabal: Dependency of ``ghc`` library
- libraries/template-haskell/template-haskell.cabal: Core library
- libraries/text/text.cabal: Dependency of ``Cabal`` library
- libraries/time/time.cabal: Dependency of ``ghc`` library
- libraries/transformers/transformers.cabal: Dependency of ``ghc`` library
- libraries/unix/unix.cabal: Dependency of ``ghc`` library
- libraries/Win32/Win32.cabal: Dependency of ``ghc`` library
- libraries/xhtml/xhtml.cabal: Dependency of ``haddock`` executable
=====================================
docs/users_guide/index.rst
=====================================
@@ -12,7 +12,6 @@ Contents:
license
intro
- 8.6.1-notes
8.8.1-notes
ghci
runghc
=====================================
docs/users_guide/profiling.rst
=====================================
@@ -318,7 +318,12 @@ Compiler options for profiling
put in your source will spring to life.
Without a :ghc-flag:`-prof` option, your ``SCC``\ s are ignored; so you can
- compile ``SCC``-laden code without changing it.
+ compile :pragma:`SCC`-laden code without changing it.
+
+.. warning::
+
+ Due to platform limitations, GHC may fail to produce profiled
+ object files on 32-bit Windows (see :ghc-ticket:`15934`).
There are a few other profiling-related compilation options. Use them
*in addition to* :ghc-flag:`-prof`. These do not have to be used consistently
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/compare/2ffe559c7fef3b324e72aa2e947d5b4394ff2791...c56dad0132275841f92a02b79da7d3612ef85025
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/compare/2ffe559c7fef3b324e72aa2e947d5b4394ff2791...c56dad0132275841f92a02b79da7d3612ef85025
You're receiving this email because of your account on gitlab.haskell.org.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20190430/add1d1c4/attachment-0001.html>
More information about the ghc-commits
mailing list