summaryrefslogtreecommitdiff
path: root/compiler/GHC/Core
diff options
context:
space:
mode:
Diffstat (limited to 'compiler/GHC/Core')
-rw-r--r--compiler/GHC/Core/Coercion.hs8
-rw-r--r--compiler/GHC/Core/Coercion/Axiom.hs11
-rw-r--r--compiler/GHC/Core/FamInstEnv.hs12
-rw-r--r--compiler/GHC/Core/Lint.hs16
-rw-r--r--compiler/GHC/Core/Map.hs17
-rw-r--r--compiler/GHC/Core/Multiplicity.hs3
-rw-r--r--compiler/GHC/Core/Opt/Exitify.hs2
-rw-r--r--compiler/GHC/Core/Opt/OccurAnal.hs9
-rw-r--r--compiler/GHC/Core/Opt/SetLevels.hs13
-rw-r--r--compiler/GHC/Core/Opt/Simplify/Utils.hs3
-rw-r--r--compiler/GHC/Core/Opt/Specialise.hs10
-rw-r--r--compiler/GHC/Core/Opt/StaticArgs.hs3
-rw-r--r--compiler/GHC/Core/Opt/WorkWrap/Utils.hs6
-rw-r--r--compiler/GHC/Core/Ppr.hs7
-rw-r--r--compiler/GHC/Core/TyCo/Rep.hs8
-rw-r--r--compiler/GHC/Core/TyCon.hs7
-rw-r--r--compiler/GHC/Core/Unfold.hs3
-rw-r--r--compiler/GHC/Core/UsageEnv.hs19
18 files changed, 88 insertions, 69 deletions
diff --git a/compiler/GHC/Core/Coercion.hs b/compiler/GHC/Core/Coercion.hs
index 381e80d07a..401eed8edb 100644
--- a/compiler/GHC/Core/Coercion.hs
+++ b/compiler/GHC/Core/Coercion.hs
@@ -1,10 +1,12 @@
+{-# LANGUAGE CPP #-}
+{-# LANGUAGE FlexibleContexts #-}
+{-# LANGUAGE RankNTypes #-}
+{-# LANGUAGE ScopedTypeVariables #-}
+
{-
(c) The University of Glasgow 2006
-}
-{-# LANGUAGE RankNTypes, CPP, MultiWayIf, FlexibleContexts, BangPatterns,
- ScopedTypeVariables #-}
-
-- | Module for (a) type kinds and (b) type coercions,
-- as used in System FC. See 'GHC.Core.Expr' for
-- more on System FC and how coercions fit into it.
diff --git a/compiler/GHC/Core/Coercion/Axiom.hs b/compiler/GHC/Core/Coercion/Axiom.hs
index 2bf31f8cc1..3221eab4b2 100644
--- a/compiler/GHC/Core/Coercion/Axiom.hs
+++ b/compiler/GHC/Core/Coercion/Axiom.hs
@@ -1,7 +1,12 @@
--- (c) The University of Glasgow 2012
+{-# LANGUAGE CPP #-}
+{-# LANGUAGE DataKinds #-}
+{-# LANGUAGE DeriveDataTypeable #-}
+{-# LANGUAGE GADTs #-}
+{-# LANGUAGE KindSignatures #-}
+{-# LANGUAGE RoleAnnotations #-}
+{-# LANGUAGE ScopedTypeVariables #-}
-{-# LANGUAGE CPP, DataKinds, DeriveDataTypeable, GADTs, KindSignatures,
- ScopedTypeVariables, StandaloneDeriving, RoleAnnotations #-}
+-- (c) The University of Glasgow 2012
-- | Module for coercion axioms, used to represent type family instances
-- and newtypes
diff --git a/compiler/GHC/Core/FamInstEnv.hs b/compiler/GHC/Core/FamInstEnv.hs
index 75ad0a5574..8b9af440cc 100644
--- a/compiler/GHC/Core/FamInstEnv.hs
+++ b/compiler/GHC/Core/FamInstEnv.hs
@@ -1,12 +1,14 @@
+{-# LANGUAGE CPP #-}
+{-# LANGUAGE DeriveFunctor #-}
+{-# LANGUAGE GADTs #-}
+{-# LANGUAGE ScopedTypeVariables #-}
+{-# LANGUAGE TupleSections #-}
+
+{-# OPTIONS_GHC -Wno-incomplete-record-updates #-}
-- (c) The University of Glasgow 2006
--
-- FamInstEnv: Type checked family instance declarations
-{-# LANGUAGE CPP, GADTs, ScopedTypeVariables, BangPatterns, TupleSections,
- DeriveFunctor #-}
-
-{-# OPTIONS_GHC -Wno-incomplete-record-updates #-}
-
module GHC.Core.FamInstEnv (
FamInst(..), FamFlavor(..), famInstAxiom, famInstTyCon, famInstRHS,
famInstsRepTyCons, famInstRepTyCon_maybe, dataFamInstRepTyCon,
diff --git a/compiler/GHC/Core/Lint.hs b/compiler/GHC/Core/Lint.hs
index 7f8fb351e0..0a1d5d0ddb 100644
--- a/compiler/GHC/Core/Lint.hs
+++ b/compiler/GHC/Core/Lint.hs
@@ -1,3 +1,8 @@
+{-# LANGUAGE CPP #-}
+{-# LANGUAGE DeriveFunctor #-}
+{-# LANGUAGE MultiWayIf #-}
+{-# LANGUAGE ScopedTypeVariables #-}
+
{-
(c) The University of Glasgow 2006
(c) The GRASP/AQUA Project, Glasgow University, 1993-1998
@@ -7,9 +12,6 @@ A ``lint'' pass to check for Core correctness.
See Note [Core Lint guarantee].
-}
-{-# LANGUAGE CPP #-}
-{-# LANGUAGE ViewPatterns, ScopedTypeVariables, DeriveFunctor, MultiWayIf #-}
-
module GHC.Core.Lint (
lintCoreBindings, lintUnfolding,
lintPassResult, lintInteractiveExpr, lintExpr,
@@ -1864,14 +1866,14 @@ lintCoreRule fun fun_ty rule@(Rule { ru_name = name, ru_bndrs = bndrs
~~~~~~~~~~~~~~~~~~~~~~~
It's very bad if simplifying a rule means that one of the template
variables (ru_bndrs) that /is/ mentioned on the RHS becomes
-not-mentioned in the LHS (ru_args). How can that happen? Well, in
-#10602, SpecConstr stupidly constructed a rule like
+not-mentioned in the LHS (ru_args). How can that happen? Well, in #10602,
+SpecConstr stupidly constructed a rule like
forall x,c1,c2.
f (x |> c1 |> c2) = ....
-But simplExpr collapses those coercions into one. (Indeed in
-#10602, it collapsed to the identity and was removed altogether.)
+But simplExpr collapses those coercions into one. (Indeed in #10602,
+it collapsed to the identity and was removed altogether.)
We don't have a great story for what to do here, but at least
this check will nail it.
diff --git a/compiler/GHC/Core/Map.hs b/compiler/GHC/Core/Map.hs
index ad5cd6fd53..d053aecb82 100644
--- a/compiler/GHC/Core/Map.hs
+++ b/compiler/GHC/Core/Map.hs
@@ -1,16 +1,15 @@
-{-
-(c) The University of Glasgow 2006
-(c) The GRASP/AQUA Project, Glasgow University, 1992-1998
--}
-
{-# LANGUAGE CPP #-}
-{-# LANGUAGE RankNTypes #-}
-{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE FlexibleContexts #-}
-{-# LANGUAGE TypeSynonymInstances #-}
{-# LANGUAGE FlexibleInstances #-}
-{-# LANGUAGE UndecidableInstances #-}
+{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
+{-# LANGUAGE TypeFamilies #-}
+{-# LANGUAGE UndecidableInstances #-}
+
+{-
+(c) The University of Glasgow 2006
+(c) The GRASP/AQUA Project, Glasgow University, 1992-1998
+-}
module GHC.Core.Map (
-- * Maps over Core expressions
diff --git a/compiler/GHC/Core/Multiplicity.hs b/compiler/GHC/Core/Multiplicity.hs
index 73535a3e15..881966f8ff 100644
--- a/compiler/GHC/Core/Multiplicity.hs
+++ b/compiler/GHC/Core/Multiplicity.hs
@@ -1,5 +1,4 @@
-{-# LANGUAGE DeriveDataTypeable #-}
-{-# LANGUAGE PatternSynonyms, ViewPatterns #-}
+{-# LANGUAGE PatternSynonyms #-}
{-|
This module defines the semi-ring of multiplicities, and associated functions.
diff --git a/compiler/GHC/Core/Opt/Exitify.hs b/compiler/GHC/Core/Opt/Exitify.hs
index e489cf298f..60b1e7a61c 100644
--- a/compiler/GHC/Core/Opt/Exitify.hs
+++ b/compiler/GHC/Core/Opt/Exitify.hs
@@ -1,5 +1,3 @@
-{-# LANGUAGE PatternSynonyms #-}
-
module GHC.Core.Opt.Exitify ( exitifyProgram ) where
{-
diff --git a/compiler/GHC/Core/Opt/OccurAnal.hs b/compiler/GHC/Core/Opt/OccurAnal.hs
index e352910cfb..97d38c8bd1 100644
--- a/compiler/GHC/Core/Opt/OccurAnal.hs
+++ b/compiler/GHC/Core/Opt/OccurAnal.hs
@@ -1,3 +1,9 @@
+{-# LANGUAGE BangPatterns #-}
+{-# LANGUAGE CPP #-}
+{-# LANGUAGE ViewPatterns #-}
+
+{-# OPTIONS_GHC -Wno-incomplete-record-updates #-}
+
{-
(c) The GRASP/AQUA Project, Glasgow University, 1992-1998
@@ -11,9 +17,6 @@ The occurrence analyser re-typechecks a core expression, returning a new
core expression with (hopefully) improved usage information.
-}
-{-# LANGUAGE CPP, BangPatterns, MultiWayIf, ViewPatterns #-}
-
-{-# OPTIONS_GHC -Wno-incomplete-record-updates #-}
module GHC.Core.Opt.OccurAnal ( occurAnalysePgm, occurAnalyseExpr ) where
#include "HsVersions.h"
diff --git a/compiler/GHC/Core/Opt/SetLevels.hs b/compiler/GHC/Core/Opt/SetLevels.hs
index f678433568..0a4d4541f4 100644
--- a/compiler/GHC/Core/Opt/SetLevels.hs
+++ b/compiler/GHC/Core/Opt/SetLevels.hs
@@ -1,3 +1,8 @@
+{-# LANGUAGE CPP #-}
+{-# LANGUAGE PatternSynonyms #-}
+
+{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-}
+
{-
(c) The GRASP/AQUA Project, Glasgow University, 1992-1998
@@ -60,9 +65,6 @@
identity.
-}
-{-# LANGUAGE CPP, MultiWayIf, PatternSynonyms #-}
-
-{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-}
module GHC.Core.Opt.SetLevels (
setLevels,
@@ -882,9 +884,8 @@ float a boxed version
and replace the original (f x) with
case (case y of I# r -> r) of r -> blah
-Being able to float unboxed expressions is sometimes important; see
-#12603. I'm not sure how /often/ it is important, but it's
-not hard to achieve.
+Being able to float unboxed expressions is sometimes important; see #12603.
+I'm not sure how /often/ it is important, but it's not hard to achieve.
We only do it for a fixed collection of types for which we have a
convenient boxing constructor (see boxingDataCon_maybe). In
diff --git a/compiler/GHC/Core/Opt/Simplify/Utils.hs b/compiler/GHC/Core/Opt/Simplify/Utils.hs
index 420d406eed..41ef2291e0 100644
--- a/compiler/GHC/Core/Opt/Simplify/Utils.hs
+++ b/compiler/GHC/Core/Opt/Simplify/Utils.hs
@@ -1207,8 +1207,7 @@ Here f occurs just once, in the RHS of fInt. But if we inline it there
it might make fInt look big, and we'll lose the opportunity to inline f
at each of fInt's call sites. The INLINE pragma will only inline when
the application is saturated for exactly this reason; and we don't
-want PreInlineUnconditionally to second-guess it. A live example is
-#3736.
+want PreInlineUnconditionally to second-guess it. A live example is #3736.
c.f. Note [Stable unfoldings and postInlineUnconditionally]
NB: if the pragma is INLINEABLE, then we don't want to behave in
diff --git a/compiler/GHC/Core/Opt/Specialise.hs b/compiler/GHC/Core/Opt/Specialise.hs
index 30e9689619..57c49cd5c9 100644
--- a/compiler/GHC/Core/Opt/Specialise.hs
+++ b/compiler/GHC/Core/Opt/Specialise.hs
@@ -1,15 +1,13 @@
+{-# LANGUAGE CPP #-}
+
+{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-}
+
{-
(c) The GRASP/AQUA Project, Glasgow University, 1993-1998
\section[Specialise]{Stamping out overloading, and (optionally) polymorphism}
-}
-{-# LANGUAGE CPP #-}
-{-# LANGUAGE PatternSynonyms #-}
-{-# LANGUAGE DeriveFunctor #-}
-{-# LANGUAGE ViewPatterns #-}
-
-{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-}
module GHC.Core.Opt.Specialise ( specProgram, specUnfolding ) where
#include "HsVersions.h"
diff --git a/compiler/GHC/Core/Opt/StaticArgs.hs b/compiler/GHC/Core/Opt/StaticArgs.hs
index 91c8646f19..04b21b588e 100644
--- a/compiler/GHC/Core/Opt/StaticArgs.hs
+++ b/compiler/GHC/Core/Opt/StaticArgs.hs
@@ -1,3 +1,5 @@
+{-# LANGUAGE CPP #-}
+
{-
(c) The GRASP/AQUA Project, Glasgow University, 1992-1998
@@ -48,7 +50,6 @@ The previous patch, to fix polymorphic floatout demand signatures, is
essential to make this work well!
-}
-{-# LANGUAGE CPP, PatternSynonyms #-}
module GHC.Core.Opt.StaticArgs ( doStaticArgs ) where
import GHC.Prelude
diff --git a/compiler/GHC/Core/Opt/WorkWrap/Utils.hs b/compiler/GHC/Core/Opt/WorkWrap/Utils.hs
index 231faa0d44..490ca1a189 100644
--- a/compiler/GHC/Core/Opt/WorkWrap/Utils.hs
+++ b/compiler/GHC/Core/Opt/WorkWrap/Utils.hs
@@ -924,15 +924,13 @@ which can still be specialised by the type-class specialiser, something like
BUT if f is strict in the Ord dictionary, we might unpack it, to get
fw :: (a->a->Bool) -> [a] -> Int# -> a
-and the type-class specialiser can't specialise that. An example is
-#6056.
+and the type-class specialiser can't specialise that. An example is #6056.
But in any other situation a dictionary is just an ordinary value,
and can be unpacked. So we track the INLINABLE pragma, and switch
off the unpacking in mkWWstr_one (see the isClassPred test).
-Historical note: #14955 describes how I got this fix wrong
-the first time.
+Historical note: #14955 describes how I got this fix wrong the first time.
-}
-- | Context for a 'DataCon' application with a hole for every field, including
diff --git a/compiler/GHC/Core/Ppr.hs b/compiler/GHC/Core/Ppr.hs
index 79c5acae23..37e5afc963 100644
--- a/compiler/GHC/Core/Ppr.hs
+++ b/compiler/GHC/Core/Ppr.hs
@@ -1,3 +1,6 @@
+{-# LANGUAGE LambdaCase #-}
+{-# OPTIONS_GHC -fno-warn-orphans #-}
+
{-
(c) The University of Glasgow 2006
(c) The AQUA Project, Glasgow University, 1996-1998
@@ -6,10 +9,6 @@
Printing of Core syntax
-}
-{-# LANGUAGE MultiWayIf #-}
-{-# LANGUAGE LambdaCase #-}
-{-# OPTIONS_GHC -fno-warn-orphans #-}
-
module GHC.Core.Ppr (
pprCoreExpr, pprParendExpr,
pprCoreBinding, pprCoreBindings, pprCoreAlt,
diff --git a/compiler/GHC/Core/TyCo/Rep.hs b/compiler/GHC/Core/TyCo/Rep.hs
index 87cd0ed6bb..9503ba4ccf 100644
--- a/compiler/GHC/Core/TyCo/Rep.hs
+++ b/compiler/GHC/Core/TyCo/Rep.hs
@@ -1,3 +1,8 @@
+{-# LANGUAGE CPP #-}
+{-# LANGUAGE DeriveDataTypeable #-}
+
+{-# OPTIONS_HADDOCK not-home #-}
+
{-
(c) The University of Glasgow 2006
(c) The GRASP/AQUA Project, Glasgow University, 1998
@@ -18,9 +23,6 @@ Note [The Type-related module hierarchy]
-}
-- We expose the relevant stuff from this module via the Type module
-{-# OPTIONS_HADDOCK not-home #-}
-{-# LANGUAGE CPP, MultiWayIf, PatternSynonyms, BangPatterns, DeriveDataTypeable #-}
-
module GHC.Core.TyCo.Rep (
TyThing(..), tyThingCategory, pprTyThingCategory, pprShortTyThing,
diff --git a/compiler/GHC/Core/TyCon.hs b/compiler/GHC/Core/TyCon.hs
index 919407376e..ad455779b7 100644
--- a/compiler/GHC/Core/TyCon.hs
+++ b/compiler/GHC/Core/TyCon.hs
@@ -1,3 +1,7 @@
+{-# LANGUAGE CPP #-}
+{-# LANGUAGE FlexibleInstances #-}
+{-# LANGUAGE LambdaCase #-}
+
{-
(c) The University of Glasgow 2006
(c) The GRASP/AQUA Project, Glasgow University, 1992-1998
@@ -6,9 +10,6 @@
The @TyCon@ datatype
-}
-{-# LANGUAGE CPP, FlexibleInstances #-}
-{-# LANGUAGE LambdaCase #-}
-
module GHC.Core.TyCon(
-- * Main TyCon data types
TyCon,
diff --git a/compiler/GHC/Core/Unfold.hs b/compiler/GHC/Core/Unfold.hs
index 89e4580351..a410bac6e1 100644
--- a/compiler/GHC/Core/Unfold.hs
+++ b/compiler/GHC/Core/Unfold.hs
@@ -713,8 +713,7 @@ Historical note 2: Much longer ago, Simon M tried a MUCH bigger
discount: (10 * (10 + n_val_args)), and said it was an "unambiguous
win", but its terribly dangerous because a function with many many
case branches, each finishing with a constructor, can have an
-arbitrarily large discount. This led to terrible code bloat: see
-#6099.
+arbitrarily large discount. This led to terrible code bloat: see #6099.
Note [Unboxed tuple size and result discount]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
diff --git a/compiler/GHC/Core/UsageEnv.hs b/compiler/GHC/Core/UsageEnv.hs
index e88b55560d..5c2f613247 100644
--- a/compiler/GHC/Core/UsageEnv.hs
+++ b/compiler/GHC/Core/UsageEnv.hs
@@ -1,7 +1,18 @@
-{-# LANGUAGE ViewPatterns #-}
-module GHC.Core.UsageEnv (UsageEnv, addUsage, scaleUsage, zeroUE,
- lookupUE, scaleUE, deleteUE, addUE, Usage(..), unitUE,
- bottomUE, supUE, supUEs) where
+module GHC.Core.UsageEnv
+ ( Usage(..)
+ , UsageEnv
+ , addUE
+ , addUsage
+ , bottomUE
+ , deleteUE
+ , lookupUE
+ , scaleUE
+ , scaleUsage
+ , supUE
+ , supUEs
+ , unitUE
+ , zeroUE
+ ) where
import Data.Foldable
import GHC.Prelude