summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorSylvain Henry <sylvain@haskus.fr>2020-02-24 20:59:43 +0100
committerMarge Bot <ben+marge-bot@smart-cactus.org>2020-02-26 15:10:58 -0500
commit817f93eac4d13f680e8e3e7a25eb403b1864f82e (patch)
treef7014721e49627f15d76f44a5bf663043e35fafc
parentb2b49a0aad353201678970c76d8305a5dcb1bfab (diff)
downloadhaskell-817f93eac4d13f680e8e3e7a25eb403b1864f82e.tar.gz
Modules: Core (#13009)
Update haddock submodule
-rw-r--r--compiler/GHC.hs6
-rw-r--r--compiler/GHC/ByteCode/Instr.hs4
-rw-r--r--compiler/GHC/Cmm/CLabel.hs2
-rw-r--r--compiler/GHC/Cmm/CommonBlockElim.hs2
-rw-r--r--compiler/GHC/Cmm/DebugBlock.hs2
-rw-r--r--compiler/GHC/Cmm/Node.hs2
-rw-r--r--compiler/GHC/Cmm/Parser.y2
-rw-r--r--compiler/GHC/CmmToAsm/Dwarf.hs2
-rw-r--r--compiler/GHC/CmmToAsm/X86/CodeGen.hs2
-rw-r--r--compiler/GHC/Core.hs (renamed from compiler/coreSyn/CoreSyn.hs)133
-rw-r--r--compiler/GHC/Core/Arity.hs (renamed from compiler/coreSyn/CoreArity.hs)31
-rw-r--r--compiler/GHC/Core/FVs.hs (renamed from compiler/coreSyn/CoreFVs.hs)4
-rw-r--r--compiler/GHC/Core/Lint.hs (renamed from compiler/coreSyn/CoreLint.hs)66
-rw-r--r--compiler/GHC/Core/Make.hs (renamed from compiler/coreSyn/MkCore.hs)22
-rw-r--r--compiler/GHC/Core/Map.hs (renamed from compiler/coreSyn/CoreMap.hs)6
-rw-r--r--compiler/GHC/Core/Op/Tidy.hs (renamed from compiler/coreSyn/CoreTidy.hs)6
-rw-r--r--compiler/GHC/Core/Ppr.hs (renamed from compiler/coreSyn/PprCore.hs)8
-rw-r--r--compiler/GHC/Core/Ppr/TyThing.hs (renamed from compiler/main/PprTyThing.hs)2
-rw-r--r--compiler/GHC/Core/Rules.hs (renamed from compiler/specialise/Rules.hs)28
-rw-r--r--compiler/GHC/Core/Seq.hs (renamed from compiler/coreSyn/CoreSeq.hs)4
-rw-r--r--compiler/GHC/Core/SimpleOpt.hs (renamed from compiler/coreSyn/CoreOpt.hs)42
-rw-r--r--compiler/GHC/Core/Stats.hs (renamed from compiler/coreSyn/CoreStats.hs)4
-rw-r--r--compiler/GHC/Core/Subst.hs (renamed from compiler/coreSyn/CoreSubst.hs)12
-rw-r--r--compiler/GHC/Core/Unfold.hs (renamed from compiler/coreSyn/CoreUnfold.hs)18
-rw-r--r--compiler/GHC/Core/Unfold.hs-boot (renamed from compiler/coreSyn/CoreUnfold.hs-boot)4
-rw-r--r--compiler/GHC/Core/Utils.hs (renamed from compiler/coreSyn/CoreUtils.hs)41
-rw-r--r--compiler/GHC/CoreToByteCode.hs20
-rw-r--r--compiler/GHC/CoreToIface.hs4
-rw-r--r--compiler/GHC/CoreToStg.hs10
-rw-r--r--compiler/GHC/CoreToStg/Prep.hs22
-rw-r--r--compiler/GHC/Driver/Hooks.hs2
-rw-r--r--compiler/GHC/Driver/Main.hs15
-rw-r--r--compiler/GHC/Driver/Session.hs2
-rw-r--r--compiler/GHC/Driver/Types.hs4
-rw-r--r--compiler/GHC/Hs/Binds.hs2
-rw-r--r--compiler/GHC/Hs/Expr.hs2
-rw-r--r--compiler/GHC/Hs/Pat.hs2
-rw-r--r--compiler/GHC/HsToCore.hs20
-rw-r--r--compiler/GHC/HsToCore/Arrows.hs8
-rw-r--r--compiler/GHC/HsToCore/Binds.hs22
-rw-r--r--compiler/GHC/HsToCore/Binds.hs-boot4
-rw-r--r--compiler/GHC/HsToCore/Coverage.hs2
-rw-r--r--compiler/GHC/HsToCore/Expr.hs12
-rw-r--r--compiler/GHC/HsToCore/Expr.hs-boot2
-rw-r--r--compiler/GHC/HsToCore/Foreign/Call.hs6
-rw-r--r--compiler/GHC/HsToCore/Foreign/Decl.hs4
-rw-r--r--compiler/GHC/HsToCore/GuardedRHSs.hs6
-rw-r--r--compiler/GHC/HsToCore/ListComp.hs6
-rw-r--r--compiler/GHC/HsToCore/Match.hs8
-rw-r--r--compiler/GHC/HsToCore/Match.hs-boot2
-rw-r--r--compiler/GHC/HsToCore/Match/Constructor.hs2
-rw-r--r--compiler/GHC/HsToCore/Match/Literal.hs4
-rw-r--r--compiler/GHC/HsToCore/Monad.hs6
-rw-r--r--compiler/GHC/HsToCore/PmCheck.hs2
-rw-r--r--compiler/GHC/HsToCore/PmCheck/Oracle.hs12
-rw-r--r--compiler/GHC/HsToCore/PmCheck/Types.hs8
-rw-r--r--compiler/GHC/HsToCore/Quote.hs6
-rw-r--r--compiler/GHC/HsToCore/Utils.hs16
-rw-r--r--compiler/GHC/Iface/Ext/Ast.hs2
-rw-r--r--compiler/GHC/Iface/Ext/Utils.hs4
-rw-r--r--compiler/GHC/Iface/Load.hs2
-rw-r--r--compiler/GHC/Iface/Syntax.hs14
-rw-r--r--compiler/GHC/Iface/Tidy.hs26
-rw-r--r--compiler/GHC/Iface/Type.hs4
-rw-r--r--compiler/GHC/Iface/Utils.hs2
-rw-r--r--compiler/GHC/IfaceToCore.hs12
-rw-r--r--compiler/GHC/IfaceToCore.hs-boot19
-rw-r--r--compiler/GHC/Plugins.hs24
-rw-r--r--compiler/GHC/Runtime/Debugger.hs2
-rw-r--r--compiler/GHC/Runtime/Eval.hs2
-rw-r--r--compiler/GHC/Stg/CSE.hs6
-rw-r--r--compiler/GHC/Stg/FVs.hs2
-rw-r--r--compiler/GHC/Stg/Lint.hs4
-rw-r--r--compiler/GHC/Stg/Subst.hs2
-rw-r--r--compiler/GHC/Stg/Syntax.hs14
-rw-r--r--compiler/GHC/Stg/Unarise.hs6
-rw-r--r--compiler/GHC/StgToCmm/Bind.hs2
-rw-r--r--compiler/GHC/StgToCmm/DataCon.hs2
-rw-r--r--compiler/GHC/StgToCmm/Expr.hs8
-rw-r--r--compiler/basicTypes/BasicTypes.hs6
-rw-r--r--compiler/basicTypes/DataCon.hs2
-rw-r--r--compiler/basicTypes/Id.hs8
-rw-r--r--compiler/basicTypes/IdInfo.hs8
-rw-r--r--compiler/basicTypes/Literal.hs4
-rw-r--r--compiler/basicTypes/MkId.hs20
-rw-r--r--compiler/ghc.cabal.in33
-rw-r--r--compiler/main/StaticPtrTable.hs6
-rw-r--r--compiler/main/UpdateCafInfos.hs2
-rw-r--r--compiler/prelude/PrelRules.hs23
-rw-r--r--compiler/prelude/PrimOp.hs8
-rw-r--r--compiler/prelude/TysPrim.hs2
-rw-r--r--compiler/prelude/TysWiredIn.hs6
-rw-r--r--compiler/simplCore/CSE.hs16
-rw-r--r--compiler/simplCore/CallArity.hs8
-rw-r--r--compiler/simplCore/CoreMonad.hs2
-rw-r--r--compiler/simplCore/Exitify.hs6
-rw-r--r--compiler/simplCore/FloatIn.hs10
-rw-r--r--compiler/simplCore/FloatOut.hs10
-rw-r--r--compiler/simplCore/LiberateCase.hs4
-rw-r--r--compiler/simplCore/OccurAnal.hs14
-rw-r--r--compiler/simplCore/SAT.hs4
-rw-r--r--compiler/simplCore/SetLevels.hs24
-rw-r--r--compiler/simplCore/SimplCore.hs18
-rw-r--r--compiler/simplCore/SimplEnv.hs16
-rw-r--r--compiler/simplCore/SimplMonad.hs4
-rw-r--r--compiler/simplCore/SimplUtils.hs44
-rw-r--r--compiler/simplCore/Simplify.hs46
-rw-r--r--compiler/specialise/SpecConstr.hs26
-rw-r--r--compiler/specialise/Specialise.hs44
-rw-r--r--compiler/stranal/CprAnal.hs6
-rw-r--r--compiler/stranal/DmdAnal.hs14
-rw-r--r--compiler/stranal/WorkWrap.hs18
-rw-r--r--compiler/stranal/WwLib.hs6
-rw-r--r--compiler/typecheck/ClsInst.hs2
-rw-r--r--compiler/typecheck/Constraint.hs2
-rw-r--r--compiler/typecheck/FamInst.hs2
-rw-r--r--compiler/typecheck/Inst.hs4
-rw-r--r--compiler/typecheck/TcBinds.hs2
-rw-r--r--compiler/typecheck/TcCanonical.hs2
-rw-r--r--compiler/typecheck/TcEvTerm.hs6
-rw-r--r--compiler/typecheck/TcEvidence.hs6
-rw-r--r--compiler/typecheck/TcExpr.hs4
-rw-r--r--compiler/typecheck/TcHsSyn.hs4
-rw-r--r--compiler/typecheck/TcInstDcls.hs8
-rw-r--r--compiler/typecheck/TcInteract.hs2
-rw-r--r--compiler/typecheck/TcMatches.hs2
-rw-r--r--compiler/typecheck/TcPat.hs2
-rw-r--r--compiler/typecheck/TcRnDriver.hs4
-rw-r--r--compiler/typecheck/TcSMonad.hs2
-rw-r--r--compiler/typecheck/TcTyClsDecls.hs2
-rw-r--r--compiler/typecheck/TcTyDecls.hs2
-rw-r--r--compiler/typecheck/TcType.hs2
-rw-r--r--compiler/typecheck/TcTypeable.hs2
-rw-r--r--compiler/types/CoAxiom.hs2
-rw-r--r--compiler/types/Coercion.hs4
-rw-r--r--compiler/types/FamInstEnv.hs4
-rw-r--r--compiler/types/InstEnv.hs2
-rw-r--r--compiler/types/OptCoercion.hs2
-rw-r--r--compiler/types/TyCoPpr.hs2
-rw-r--r--compiler/types/TyCoRep.hs6
-rw-r--r--compiler/types/TyCoSubst.hs2
-rw-r--r--compiler/types/TyCon.hs4
-rw-r--r--compiler/types/Type.hs8
-rw-r--r--compiler/utils/Outputable.hs2
-rw-r--r--compiler/utils/TrieMap.hs4
-rw-r--r--ghc/GHCi/UI.hs2
-rw-r--r--ghc/GHCi/UI/Info.hs4
-rw-r--r--rts/RtsStartup.c2
-rw-r--r--testsuite/tests/callarity/unittest/CallArity1.hs10
-rw-r--r--testsuite/tests/typecheck/should_compile/T3409.hs2
m---------utils/haddock0
151 files changed, 726 insertions, 723 deletions
diff --git a/compiler/GHC.hs b/compiler/GHC.hs
index 392d695997..f973507dee 100644
--- a/compiler/GHC.hs
+++ b/compiler/GHC.hs
@@ -301,7 +301,7 @@ import GHC.Runtime.Eval.Types
import GHC.Runtime.Interpreter
import GHCi.RemoteTypes
-import PprTyThing ( pprFamInst )
+import GHC.Core.Ppr.TyThing ( pprFamInst )
import GHC.Driver.Main
import GHC.Driver.Make
import GHC.Driver.Pipeline ( compileOne' )
@@ -327,7 +327,7 @@ import Avail
import InstEnv
import FamInstEnv ( FamInst )
import SrcLoc
-import CoreSyn
+import GHC.Core
import GHC.Iface.Tidy
import GHC.Driver.Phases ( Phase(..), isHaskellSrcFilename )
import GHC.Driver.Finder
@@ -353,7 +353,7 @@ import Lexer
import ApiAnnotation
import qualified GHC.LanguageExtensions as LangExt
import NameEnv
-import CoreFVs ( orphNamesOfFamInst )
+import GHC.Core.FVs ( orphNamesOfFamInst )
import FamInstEnv ( famInstEnvElts )
import TcRnDriver
import Inst
diff --git a/compiler/GHC/ByteCode/Instr.hs b/compiler/GHC/ByteCode/Instr.hs
index d6c9cd5391..bff6bb5df0 100644
--- a/compiler/GHC/ByteCode/Instr.hs
+++ b/compiler/GHC/ByteCode/Instr.hs
@@ -17,13 +17,13 @@ import GHC.ByteCode.Types
import GHCi.RemoteTypes
import GHCi.FFI (C_ffi_cif)
import GHC.StgToCmm.Layout ( ArgRep(..) )
-import PprCore
+import GHC.Core.Ppr
import Outputable
import FastString
import Name
import Unique
import Id
-import CoreSyn
+import GHC.Core
import Literal
import DataCon
import VarSet
diff --git a/compiler/GHC/Cmm/CLabel.hs b/compiler/GHC/Cmm/CLabel.hs
index f3cf8019d0..ef53715617 100644
--- a/compiler/GHC/Cmm/CLabel.hs
+++ b/compiler/GHC/Cmm/CLabel.hs
@@ -130,7 +130,7 @@ import GHC.Driver.Session
import GHC.Platform
import UniqSet
import Util
-import PprCore ( {- instances -} )
+import GHC.Core.Ppr ( {- instances -} )
-- -----------------------------------------------------------------------------
-- The CLabel type
diff --git a/compiler/GHC/Cmm/CommonBlockElim.hs b/compiler/GHC/Cmm/CommonBlockElim.hs
index 86ea0e94e2..29f019fa15 100644
--- a/compiler/GHC/Cmm/CommonBlockElim.hs
+++ b/compiler/GHC/Cmm/CommonBlockElim.hs
@@ -300,7 +300,7 @@ copyTicks env g
foldr blockCons code (map CmmTick ticks)
-- Group by [Label]
--- See Note [Compressed TrieMap] in coreSyn/TrieMap about the usage of GenMap.
+-- See Note [Compressed TrieMap] in GHC.Core.Map about the usage of GenMap.
groupByLabel :: [(Key, DistinctBlocks)] -> [(Key, [DistinctBlocks])]
groupByLabel =
go (TM.emptyTM :: TM.ListMap (TM.GenMap LabelMap) (Key, [DistinctBlocks]))
diff --git a/compiler/GHC/Cmm/DebugBlock.hs b/compiler/GHC/Cmm/DebugBlock.hs
index ae86788d9c..23da957f9e 100644
--- a/compiler/GHC/Cmm/DebugBlock.hs
+++ b/compiler/GHC/Cmm/DebugBlock.hs
@@ -31,7 +31,7 @@ import GHC.Cmm.BlockId
import GHC.Cmm.CLabel
import GHC.Cmm
import GHC.Cmm.Utils
-import CoreSyn
+import GHC.Core
import FastString ( nilFS, mkFastString )
import Module
import Outputable
diff --git a/compiler/GHC/Cmm/Node.hs b/compiler/GHC/Cmm/Node.hs
index f26fb2c9d9..c809a99136 100644
--- a/compiler/GHC/Cmm/Node.hs
+++ b/compiler/GHC/Cmm/Node.hs
@@ -36,7 +36,7 @@ import FastString
import ForeignCall
import Outputable
import GHC.Runtime.Heap.Layout
-import CoreSyn (Tickish)
+import GHC.Core (Tickish)
import qualified Unique as U
import GHC.Cmm.Dataflow.Block
diff --git a/compiler/GHC/Cmm/Parser.y b/compiler/GHC/Cmm/Parser.y
index 69a2a9347e..fd875aa8e8 100644
--- a/compiler/GHC/Cmm/Parser.y
+++ b/compiler/GHC/Cmm/Parser.y
@@ -219,7 +219,7 @@ import GHC.StgToCmm.Closure
import GHC.StgToCmm.Layout hiding (ArgRep(..))
import GHC.StgToCmm.Ticky
import GHC.StgToCmm.Bind ( emitBlackHoleCode, emitUpdateFrame )
-import CoreSyn ( Tickish(SourceNote) )
+import GHC.Core ( Tickish(SourceNote) )
import GHC.Cmm.Opt
import GHC.Cmm.Graph
diff --git a/compiler/GHC/CmmToAsm/Dwarf.hs b/compiler/GHC/CmmToAsm/Dwarf.hs
index 8cacd19023..cdbbb9885a 100644
--- a/compiler/GHC/CmmToAsm/Dwarf.hs
+++ b/compiler/GHC/CmmToAsm/Dwarf.hs
@@ -7,7 +7,7 @@ import GhcPrelude
import GHC.Cmm.CLabel
import GHC.Cmm.Expr ( GlobalReg(..) )
import Config ( cProjectName, cProjectVersion )
-import CoreSyn ( Tickish(..) )
+import GHC.Core ( Tickish(..) )
import GHC.Cmm.DebugBlock
import GHC.Driver.Session
import Module
diff --git a/compiler/GHC/CmmToAsm/X86/CodeGen.hs b/compiler/GHC/CmmToAsm/X86/CodeGen.hs
index f3b20c19e1..4b1dd31cf1 100644
--- a/compiler/GHC/CmmToAsm/X86/CodeGen.hs
+++ b/compiler/GHC/CmmToAsm/X86/CodeGen.hs
@@ -75,7 +75,7 @@ import GHC.Cmm.Dataflow.Collections
import GHC.Cmm.Dataflow.Graph
import GHC.Cmm.Dataflow.Label
import GHC.Cmm.CLabel
-import CoreSyn ( Tickish(..) )
+import GHC.Core ( Tickish(..) )
import SrcLoc ( srcSpanFile, srcSpanStartLine, srcSpanStartCol )
-- The rest:
diff --git a/compiler/coreSyn/CoreSyn.hs b/compiler/GHC/Core.hs
index 2d4dd98cee..59556fccc2 100644
--- a/compiler/coreSyn/CoreSyn.hs
+++ b/compiler/GHC/Core.hs
@@ -9,8 +9,8 @@
{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-}
{-# OPTIONS_GHC -Wno-incomplete-record-updates #-}
--- | CoreSyn holds all the main data types for use by for the Glasgow Haskell Compiler midsection
-module CoreSyn (
+-- | GHC.Core holds all the main data types for use by for the Glasgow Haskell Compiler midsection
+module GHC.Core (
-- * Main data types
Expr(..), Alt, Bind(..), AltCon(..), Arg,
Tickish(..), TickishScoping(..), TickishPlacement(..),
@@ -180,7 +180,7 @@ These data types are the heart of the compiler
-- * Primitive literals
--
-- * Applications: note that the argument may be a 'Type'.
--- See Note [CoreSyn let/app invariant]
+-- See Note [Core let/app invariant]
-- See Note [Levity polymorphism invariants]
--
-- * Lambda abstraction
@@ -190,10 +190,10 @@ These data types are the heart of the compiler
-- this corresponds to allocating a thunk for the things
-- bound and then executing the sub-expression.
--
--- See Note [CoreSyn letrec invariant]
--- See Note [CoreSyn let/app invariant]
+-- See Note [Core letrec invariant]
+-- See Note [Core let/app invariant]
-- See Note [Levity polymorphism invariants]
--- See Note [CoreSyn type and coercion invariant]
+-- See Note [Core type and coercion invariant]
--
-- * Case expression. Operationally this corresponds to evaluating
-- the scrutinee (expression examined) to weak head normal form
@@ -239,7 +239,7 @@ is better for at least three reasons:
Then exprType of the RHS is (S a), but we cannot make that be
the 'ty' in the Case constructor because 'a' is simply not in
scope there. Instead we must expand the synonym to Int before
- putting it in the Case constructor. See CoreUtils.mkSingleAltCase.
+ putting it in the Case constructor. See GHC.Core.Utils.mkSingleAltCase.
So we'd have to do synonym expansion in exprType which would
be inefficient.
@@ -252,7 +252,7 @@ is better for at least three reasons:
-}
-- If you edit this type, you may need to update the GHC formalism
--- See Note [GHC Formalism] in coreSyn/CoreLint.hs
+-- See Note [GHC Formalism] in GHC.Core.Lint
data Expr b
= Var Id
| Lit Literal
@@ -276,13 +276,13 @@ type Arg b = Expr b
-- The default alternative is @(DEFAULT, [], rhs)@
-- If you edit this type, you may need to update the GHC formalism
--- See Note [GHC Formalism] in coreSyn/CoreLint.hs
+-- See Note [GHC Formalism] in GHC.Core.Lint
type Alt b = (AltCon, [b], Expr b)
-- | A case alternative constructor (i.e. pattern match)
-- If you edit this type, you may need to update the GHC formalism
--- See Note [GHC Formalism] in coreSyn/CoreLint.hs
+-- See Note [GHC Formalism] in GHC.Core.Lint
data AltCon
= DataAlt DataCon -- ^ A plain data constructor: @case e of { Foo x -> ... }@.
-- Invariant: the 'DataCon' is always from a @data@ type, and never from a @newtype@
@@ -297,7 +297,7 @@ data AltCon
-- This instance is a bit shady. It can only be used to compare AltCons for
-- a single type constructor. Fortunately, it seems quite unlikely that we'll
-- ever need to compare AltCons for different type constructors.
--- The instance adheres to the order described in [CoreSyn case invariants]
+-- The instance adheres to the order described in [Core case invariants]
instance Ord AltCon where
compare (DataAlt con1) (DataAlt con2) =
ASSERT( dataConTyCon con1 == dataConTyCon con2 )
@@ -312,7 +312,7 @@ instance Ord AltCon where
-- | Binding, used for top level bindings in a module and local bindings in a @let@.
-- If you edit this type, you may need to update the GHC formalism
--- See Note [GHC Formalism] in coreSyn/CoreLint.hs
+-- See Note [GHC Formalism] in GHC.Core.Lint
data Bind b = NonRec b (Expr b)
| Rec [(b, (Expr b))]
deriving Data
@@ -356,7 +356,7 @@ Also, we do not permit case analysis with literal patterns on floating-point
types. See #9238 and Note [Rules for floating-point comparisons] in
PrelRules for the rationale for this restriction.
--------------------------- CoreSyn INVARIANTS ---------------------------
+-------------------------- GHC.Core INVARIANTS ---------------------------
Note [Variable occurrences in Core]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
@@ -368,18 +368,18 @@ For example
Here 'c' is a CoVar, which is lambda-bound, but it /occurs/ in
a Coercion, (sym c).
-Note [CoreSyn letrec invariant]
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+Note [Core letrec invariant]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~
The right hand sides of all top-level and recursive @let@s
/must/ be of lifted type (see "Type#type_classification" for
the meaning of /lifted/ vs. /unlifted/).
There is one exception to this rule, top-level @let@s are
allowed to bind primitive string literals: see
-Note [CoreSyn top-level string literals].
+Note [Core top-level string literals].
-Note [CoreSyn top-level string literals]
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+Note [Core top-level string literals]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
As an exception to the usual rule that top-level binders must be lifted,
we allow binding primitive string literals (of type Addr#) of type Addr# at the
top level. This allows us to share string literals earlier in the pipeline and
@@ -413,7 +413,7 @@ parts of the compilation pipeline.
at the top level.
* In Core, we have a special rule that permits top-level Addr# bindings. See
- Note [CoreSyn top-level string literals]. Core-to-core passes may introduce
+ Note [Core top-level string literals]. Core-to-core passes may introduce
new top-level string literals.
* In STG, top-level string literals are explicitly represented in the syntax
@@ -423,8 +423,8 @@ parts of the compilation pipeline.
in the object file, the content of the exported literal is given a label with
the _bytes suffix.
-Note [CoreSyn let/app invariant]
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+Note [Core let/app invariant]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
The let/app invariant
the right hand side of a non-recursive 'Let', and
the argument of an 'App',
@@ -443,12 +443,12 @@ expression is floated out:
y::Int# = fac 4#
In this situation you should use @case@ rather than a @let@. The function
-'CoreUtils.needsCaseBinding' can help you determine which to generate, or
-alternatively use 'MkCore.mkCoreLet' rather than this constructor directly,
+'GHC.Core.Utils.needsCaseBinding' can help you determine which to generate, or
+alternatively use 'GHC.Core.Make.mkCoreLet' rather than this constructor directly,
which will generate a @case@ if necessary
The let/app invariant is initially enforced by mkCoreLet and mkCoreApp in
-coreSyn/MkCore.
+GHC.Core.Make.
For discussion of some implications of the let/app invariant primops see
Note [Checking versus non-checking primops] in PrimOp.
@@ -463,13 +463,13 @@ checked by Core Lint.
See Note [Empty case alternatives]
2. The 'DEFAULT' case alternative must be first in the list,
- if it occurs at all. Checked in CoreLint.checkCaseAlts.
+ if it occurs at all. Checked in GHC.Core.Lint.checkCaseAlts.
3. The remaining cases are in order of (strictly) increasing
tag (for 'DataAlts') or
lit (for 'LitAlts').
This makes finding the relevant constructor easy, and makes
- comparison easier too. Checked in CoreLint.checkCaseAlts.
+ comparison easier too. Checked in GHC.Core.Lint.checkCaseAlts.
4. The list of alternatives must be exhaustive. An /exhaustive/ case
does not necessarily mention all constructors:
@@ -504,7 +504,7 @@ checked by Core Lint.
Blue (since, if the case is exhaustive, that's all that
remains). Of course, if it's not Blue and we start fetching
fields that should be in a Blue constructor, we may die
- horribly. See also Note [Core Lint guarantee] in CoreLint.
+ horribly. See also Note [Core Lint guarantee] in GHC.Core.Lint.
5. Floating-point values must not be scrutinised against literals.
See #9238 and Note [Rules for floating-point comparisons]
@@ -518,8 +518,8 @@ checked by Core Lint.
7. The type of the scrutinee must be the same as the type
of the case binder, obviously. Checked in lintCaseExpr.
-Note [CoreSyn type and coercion invariant]
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+Note [Core type and coercion invariant]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
We allow a /non-recursive/, /non-top-level/ let to bind type and
coercion variables. These can be very convenient for postponing type
substitutions until the next run of the simplifier.
@@ -539,8 +539,8 @@ substitutions until the next run of the simplifier.
Note [Equality superclasses in quantified constraints]
in TcCanonical
-Note [CoreSyn case invariants]
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+Note [Core case invariants]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~
See Note [Case expression invariants]
Note [Levity polymorphism invariants]
@@ -563,8 +563,8 @@ is illegal because x's type has kind (TYPE r), which has 'r' free.
See Note [Levity polymorphism checking] in GHC.HsToCore.Monad to see where these
invariants are established for user-written code.
-Note [CoreSyn let goal]
-~~~~~~~~~~~~~~~~~~~~~~~
+Note [Core let goal]
+~~~~~~~~~~~~~~~~~~~~
* The simplifier tries to ensure that if the RHS of a let is a constructor
application, its arguments are trivial, so that the constructor can be
inlined vigorously.
@@ -580,7 +580,7 @@ this exhaustive list can be empty!
* A case expression can have empty alternatives if (and only if) the
scrutinee is bound to raise an exception or diverge. When do we know
- this? See Note [Bottoming expressions] in CoreUtils.
+ this? See Note [Bottoming expressions] in GHC.Core.Utils.
* The possibility of empty alternatives is one reason we need a type on
the case expression: if the alternatives are empty we can't get the
@@ -614,8 +614,8 @@ this exhaustive list can be empty!
unboxed type.
* We treat a case expression with empty alternatives as trivial iff
- its scrutinee is (see CoreUtils.exprIsTrivial). This is actually
- important; see Note [Empty case is trivial] in CoreUtils
+ its scrutinee is (see GHC.Core.Utils.exprIsTrivial). This is actually
+ important; see Note [Empty case is trivial] in GHC.Core.Utils
* An empty case is replaced by its scrutinee during the CoreToStg
conversion; remember STG is un-typed, so there is no need for
@@ -677,7 +677,7 @@ Join points must follow these invariants:
See Note [Join points are less general than the paper]
2. For join arity n, the right-hand side must begin with at least n lambdas.
- No ticks, no casts, just lambdas! C.f. CoreUtils.joinRhsArity.
+ No ticks, no casts, just lambdas! C.f. GHC.Core.Utils.joinRhsArity.
2a. Moreover, this same constraint applies to any unfolding of
the binder. Reason: if we want to push a continuation into
@@ -795,7 +795,7 @@ and join points] in Simplify):
The body of the join point now returns a Bool, so the label `j` has to have its
type updated accordingly. Inconvenient though this may be, it has the advantage
-that 'CoreUtils.exprType' can still return a type for any expression, including
+that 'GHC.Core.Utils.exprType' can still return a type for any expression, including
a jump.
This differs from the paper (see Note [Invariants on join points]). In the
@@ -931,7 +931,7 @@ type MOutCoercion = MCoercion
-- | Allows attaching extra information to points in expressions
-- If you edit this type, you may need to update the GHC formalism
--- See Note [GHC Formalism] in coreSyn/CoreLint.hs
+-- See Note [GHC Formalism] in GHC.Core.Lint
data Tickish id =
-- | An @{-# SCC #-}@ profiling annotation, either automatically
-- added by the desugarer as a result of -auto-all, or added by
@@ -963,7 +963,7 @@ data Tickish id =
-- appropriate entry in GHC.Driver.Types.ModBreaks.
--
-- Careful about substitution! See
- -- Note [substTickish] in CoreSubst.
+ -- Note [substTickish] in GHC.Core.Subst.
}
-- | A source note.
@@ -1295,8 +1295,9 @@ Orphan-hood is computed
* *
************************************************************************
-The CoreRule type and its friends are dealt with mainly in CoreRules,
-but CoreFVs, Subst, PprCore, CoreTidy also inspect the representation.
+The CoreRule type and its friends are dealt with mainly in GHC.Core.Rules, but
+GHC.Core.FVs, GHC.Core.Subst, GHC.Core.Ppr, GHC.Core.Op.Tidy also inspect the
+representation.
-}
-- | Gathers a collection of 'CoreRule's. Maps (the name of) an 'Id' to its rules
@@ -1381,7 +1382,7 @@ data CoreRule
-- arguments, it simply discards them; the returned 'CoreExpr'
-- is just the rewrite of 'ru_fn' applied to the first 'ru_nargs' args
}
- -- See Note [Extra args in rule matching] in Rules.hs
+ -- See Note [Extra args in rule matching] in GHC.Core.Rules
type RuleFun = DynFlags -> InScopeEnv -> Id -> [CoreExpr] -> Maybe CoreExpr
type InScopeEnv = (InScopeSet, IdUnfoldingFun)
@@ -1439,7 +1440,7 @@ The @Unfolding@ type is declared here to avoid numerous loops
-- | Records the /unfolding/ of an identifier, which is approximately the form the
-- identifier would have if we substituted its definition in for the identifier.
--- This type should be treated as abstract everywhere except in "CoreUnfold"
+-- This type should be treated as abstract everywhere except in GHC.Core.Unfold
data Unfolding
= NoUnfolding -- ^ We have no information about the unfolding.
@@ -1540,7 +1541,7 @@ data UnfoldingGuidance
= UnfWhen { -- Inline without thinking about the *size* of the uf_tmpl
-- Used (a) for small *and* cheap unfoldings
-- (b) for INLINE functions
- -- See Note [INLINE for small functions] in CoreUnfold
+ -- See Note [INLINE for small functions] in GHC.Core.Unfold
ug_arity :: Arity, -- Number of value arguments expected
ug_unsat_ok :: Bool, -- True <=> ok to inline even if unsaturated
@@ -1701,7 +1702,7 @@ isExpandableUnfolding _ = False
expandUnfolding_maybe :: Unfolding -> Maybe CoreExpr
-- Expand an expandable unfolding; this is used in rule matching
--- See Note [Expanding variables] in Rules.hs
+-- See Note [Expanding variables] in GHC.Core.Rules
-- The key point here is that CONLIKE things can be expanded
expandUnfolding_maybe (CoreUnfolding { uf_expandable = True, uf_tmpl = rhs }) = Just rhs
expandUnfolding_maybe _ = Nothing
@@ -1786,7 +1787,7 @@ on the left, thus
it'd only inline when applied to three arguments. This slightly-experimental
change was requested by Roman, but it seems to make sense.
-See also Note [Inlining an InlineRule] in CoreUnfold.
+See also Note [Inlining an InlineRule] in GHC.Core.Unfold.
Note [OccInfo in unfoldings and rules]
@@ -1869,7 +1870,7 @@ a list of CoreBind
-}
-- If you edit this type, you may need to update the GHC formalism
--- See Note [GHC Formalism] in coreSyn/CoreLint.hs
+-- See Note [GHC Formalism] in GHC.Core.Lint
type CoreProgram = [CoreBind] -- See Note [CoreProgram]
-- | The common case for the type of binders and variables when
@@ -1931,7 +1932,7 @@ deTagAlt (con, bndrs, rhs) = (con, [b | TB b _ <- bndrs], deTagExpr rhs)
-}
-- | Apply a list of argument expressions to a function expression in a nested fashion. Prefer to
--- use 'MkCore.mkCoreApps' if possible
+-- use 'GHC.Core.Make.mkCoreApps' if possible
mkApps :: Expr b -> [Arg b] -> Expr b
-- | Apply a list of type argument expressions to a function expression in a nested fashion
mkTyApps :: Expr b -> [Type] -> Expr b
@@ -1940,7 +1941,7 @@ mkCoApps :: Expr b -> [Coercion] -> Expr b
-- | Apply a list of type or value variables to a function expression in a nested fashion
mkVarApps :: Expr b -> [Var] -> Expr b
-- | Apply a list of argument expressions to a data constructor in a nested fashion. Prefer to
--- use 'MkCore.mkCoreConApps' if possible
+-- use 'GHC.Core.Make.mkCoreConApps' if possible
mkConApp :: DataCon -> [Arg b] -> Expr b
mkApps f args = foldl' App f args
@@ -1961,20 +1962,20 @@ mkTyArg ty
| otherwise = Type ty
-- | Create a machine integer literal expression of type @Int#@ from an @Integer@.
--- If you want an expression of type @Int@ use 'MkCore.mkIntExpr'
+-- If you want an expression of type @Int@ use 'GHC.Core.Make.mkIntExpr'
mkIntLit :: DynFlags -> Integer -> Expr b
-- | Create a machine integer literal expression of type @Int#@ from an @Int@.
--- If you want an expression of type @Int@ use 'MkCore.mkIntExpr'
+-- If you want an expression of type @Int@ use 'GHC.Core.Make.mkIntExpr'
mkIntLitInt :: DynFlags -> Int -> Expr b
mkIntLit dflags n = Lit (mkLitInt dflags n)
mkIntLitInt dflags n = Lit (mkLitInt dflags (toInteger n))
-- | Create a machine word literal expression of type @Word#@ from an @Integer@.
--- If you want an expression of type @Word@ use 'MkCore.mkWordExpr'
+-- If you want an expression of type @Word@ use 'GHC.Core.Make.mkWordExpr'
mkWordLit :: DynFlags -> Integer -> Expr b
-- | Create a machine word literal expression of type @Word#@ from a @Word@.
--- If you want an expression of type @Word@ use 'MkCore.mkWordExpr'
+-- If you want an expression of type @Word@ use 'GHC.Core.Make.mkWordExpr'
mkWordLitWord :: DynFlags -> Word -> Expr b
mkWordLit dflags w = Lit (mkLitWord dflags w)
@@ -1987,41 +1988,41 @@ mkInt64LitInt64 :: Int64 -> Expr b
mkInt64LitInt64 w = Lit (mkLitInt64 (toInteger w))
-- | Create a machine character literal expression of type @Char#@.
--- If you want an expression of type @Char@ use 'MkCore.mkCharExpr'
+-- If you want an expression of type @Char@ use 'GHC.Core.Make.mkCharExpr'
mkCharLit :: Char -> Expr b
-- | Create a machine string literal expression of type @Addr#@.
--- If you want an expression of type @String@ use 'MkCore.mkStringExpr'
+-- If you want an expression of type @String@ use 'GHC.Core.Make.mkStringExpr'
mkStringLit :: String -> Expr b
mkCharLit c = Lit (mkLitChar c)
mkStringLit s = Lit (mkLitString s)
-- | Create a machine single precision literal expression of type @Float#@ from a @Rational@.
--- If you want an expression of type @Float@ use 'MkCore.mkFloatExpr'
+-- If you want an expression of type @Float@ use 'GHC.Core.Make.mkFloatExpr'
mkFloatLit :: Rational -> Expr b
-- | Create a machine single precision literal expression of type @Float#@ from a @Float@.
--- If you want an expression of type @Float@ use 'MkCore.mkFloatExpr'
+-- If you want an expression of type @Float@ use 'GHC.Core.Make.mkFloatExpr'
mkFloatLitFloat :: Float -> Expr b
mkFloatLit f = Lit (mkLitFloat f)
mkFloatLitFloat f = Lit (mkLitFloat (toRational f))
-- | Create a machine double precision literal expression of type @Double#@ from a @Rational@.
--- If you want an expression of type @Double@ use 'MkCore.mkDoubleExpr'
+-- If you want an expression of type @Double@ use 'GHC.Core.Make.mkDoubleExpr'
mkDoubleLit :: Rational -> Expr b
-- | Create a machine double precision literal expression of type @Double#@ from a @Double@.
--- If you want an expression of type @Double@ use 'MkCore.mkDoubleExpr'
+-- If you want an expression of type @Double@ use 'GHC.Core.Make.mkDoubleExpr'
mkDoubleLitDouble :: Double -> Expr b
mkDoubleLit d = Lit (mkLitDouble d)
mkDoubleLitDouble d = Lit (mkLitDouble (toRational d))
-- | Bind all supplied binding groups over an expression in a nested let expression. Assumes
--- that the rhs satisfies the let/app invariant. Prefer to use 'MkCore.mkCoreLets' if
+-- that the rhs satisfies the let/app invariant. Prefer to use 'GHC.Core.Make.mkCoreLets' if
-- possible, which does guarantee the invariant
mkLets :: [Bind b] -> Expr b -> Expr b
-- | Bind all supplied binders over an expression in a nested lambda expression. Prefer to
--- use 'MkCore.mkCoreLams' if possible
+-- use 'GHC.Core.Make.mkCoreLams' if possible
mkLams :: [b] -> Expr b -> Expr b
mkLams binders body = foldr Lam body binders
@@ -2043,12 +2044,12 @@ mkLetRec :: [(b, Expr b)] -> Expr b -> Expr b
mkLetRec [] body = body
mkLetRec bs body = Let (Rec bs) body
--- | Create a binding group where a type variable is bound to a type. Per "CoreSyn#type_let",
+-- | Create a binding group where a type variable is bound to a type. Per "GHC.Core#type_let",
-- this can only be used to bind something in a non-recursive @let@ expression
mkTyBind :: TyVar -> Type -> CoreBind
mkTyBind tv ty = NonRec tv (Type ty)
--- | Create a binding group where a type variable is bound to a type. Per "CoreSyn#type_let",
+-- | Create a binding group where a type variable is bound to a type. Per "GHC.Core#type_let",
-- this can only be used to bind something in a non-recursive @let@ expression
mkCoBind :: CoVar -> Coercion -> CoreBind
mkCoBind cv co = NonRec cv (Coercion co)
@@ -2069,7 +2070,7 @@ varsToCoreExprs vs = map varToCoreExpr vs
* *
************************************************************************
-These are defined here to avoid a module loop between CoreUtils and CoreFVs
+These are defined here to avoid a module loop between GHC.Core.Utils and GHC.Core.FVs
-}
@@ -2100,7 +2101,7 @@ exprToCoercion_maybe _ = Nothing
-- | Extract every variable by this group
bindersOf :: Bind b -> [b]
-- If you edit this function, you may need to update the GHC formalism
--- See Note [GHC Formalism] in coreSyn/CoreLint.hs
+-- See Note [GHC Formalism] in GHC.Core.Lint
bindersOf (NonRec binder _) = [binder]
bindersOf (Rec pairs) = [binder | (binder, _) <- pairs]
diff --git a/compiler/coreSyn/CoreArity.hs b/compiler/GHC/Core/Arity.hs
index abf6642633..73122bef30 100644
--- a/compiler/coreSyn/CoreArity.hs
+++ b/compiler/GHC/Core/Arity.hs
@@ -11,21 +11,22 @@
{-# OPTIONS_GHC -Wno-incomplete-record-updates #-}
-- | Arity and eta expansion
-module CoreArity (
- manifestArity, joinRhsArity, exprArity, typeArity,
- exprEtaExpandArity, findRhsArity, etaExpand,
- etaExpandToJoinPoint, etaExpandToJoinPointRule,
- exprBotStrictness_maybe
- ) where
+module GHC.Core.Arity
+ ( manifestArity, joinRhsArity, exprArity, typeArity
+ , exprEtaExpandArity, findRhsArity, etaExpand
+ , etaExpandToJoinPoint, etaExpandToJoinPointRule
+ , exprBotStrictness_maybe
+ )
+where
#include "HsVersions.h"
import GhcPrelude
-import CoreSyn
-import CoreFVs
-import CoreUtils
-import CoreSubst
+import GHC.Core
+import GHC.Core.FVs
+import GHC.Core.Utils
+import GHC.Core.Subst
import Demand
import Var
import VarEnv
@@ -992,19 +993,19 @@ etaInfoApp :: Subst -> CoreExpr -> [EtaInfo] -> CoreExpr
-- ((substExpr s e) `appliedto` eis)
etaInfoApp subst (Lam v1 e) (EtaVar v2 : eis)
- = etaInfoApp (CoreSubst.extendSubstWithVar subst v1 v2) e eis
+ = etaInfoApp (GHC.Core.Subst.extendSubstWithVar subst v1 v2) e eis
etaInfoApp subst (Cast e co1) eis
= etaInfoApp subst e (pushCoercion co' eis)
where
- co' = CoreSubst.substCo subst co1
+ co' = GHC.Core.Subst.substCo subst co1
etaInfoApp subst (Case e b ty alts) eis
= Case (subst_expr subst e) b1 ty' alts'
where
(subst1, b1) = substBndr subst b
alts' = map subst_alt alts
- ty' = etaInfoAppTy (CoreSubst.substTy subst ty) eis
+ ty' = etaInfoAppTy (GHC.Core.Subst.substTy subst ty) eis
subst_alt (con, bs, rhs) = (con, bs', etaInfoApp subst2 rhs eis)
where
(subst2,bs') = substBndrs subst1 bs
@@ -1095,7 +1096,7 @@ mkEtaWW orig_n ppr_orig_expr in_scope orig_ty
----------- Function types (t1 -> t2)
| Just (arg_ty, res_ty) <- splitFunTy_maybe ty
, not (isTypeLevPoly arg_ty)
- -- See Note [Levity polymorphism invariants] in CoreSyn
+ -- See Note [Levity polymorphism invariants] in GHC.Core
-- See also test case typecheck/should_run/EtaExpandLevPoly
, let (subst', eta_id') = freshEtaId n subst arg_ty
@@ -1135,7 +1136,7 @@ mkEtaWW orig_n ppr_orig_expr in_scope orig_ty
-- TODO Check if we actually *are* changing any join points' types
subst_expr :: Subst -> CoreExpr -> CoreExpr
-subst_expr = substExpr (text "CoreArity:substExpr")
+subst_expr = substExpr (text "GHC.Core.Arity:substExpr")
--------------
diff --git a/compiler/coreSyn/CoreFVs.hs b/compiler/GHC/Core/FVs.hs
index b249f50c29..00c2bbfe9f 100644
--- a/compiler/coreSyn/CoreFVs.hs
+++ b/compiler/GHC/Core/FVs.hs
@@ -8,7 +8,7 @@ Taken quite directly from the Peyton Jones/Lester paper.
{-# LANGUAGE CPP #-}
-- | A module concerned with finding the free variables of an expression.
-module CoreFVs (
+module GHC.Core.FVs (
-- * Free variables of expressions and binding groups
exprFreeVars,
exprFreeVarsDSet,
@@ -61,7 +61,7 @@ module CoreFVs (
import GhcPrelude
-import CoreSyn
+import GHC.Core
import Id
import IdInfo
import NameSet
diff --git a/compiler/coreSyn/CoreLint.hs b/compiler/GHC/Core/Lint.hs
index bca567cff5..dc4119dea8 100644
--- a/compiler/coreSyn/CoreLint.hs
+++ b/compiler/GHC/Core/Lint.hs
@@ -10,7 +10,7 @@ See Note [Core Lint guarantee].
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveFunctor #-}
-module CoreLint (
+module GHC.Core.Lint (
lintCoreBindings, lintUnfolding,
lintPassResult, lintInteractiveExpr, lintExpr,
lintAnnots, lintTypes,
@@ -18,17 +18,17 @@ module CoreLint (
-- ** Debug output
endPass, endPassIO,
dumpPassResult,
- CoreLint.dumpIfSet,
+ GHC.Core.Lint.dumpIfSet,
) where
#include "HsVersions.h"
import GhcPrelude
-import CoreSyn
-import CoreFVs
-import CoreUtils
-import CoreStats ( coreBindsStats )
+import GHC.Core
+import GHC.Core.FVs
+import GHC.Core.Utils
+import GHC.Core.Stats ( coreBindsStats )
import CoreMonad
import Bag
import Literal
@@ -42,7 +42,7 @@ import VarSet
import Name
import Id
import IdInfo
-import PprCore
+import GHC.Core.Ppr
import ErrUtils
import Coercion
import SrcLoc
@@ -63,7 +63,7 @@ import FastString
import Util
import InstEnv ( instanceDFunId )
import OptCoercion ( checkAxInstCo )
-import CoreArity ( typeArity )
+import GHC.Core.Arity ( typeArity )
import Demand ( splitStrictSig, isBotDiv )
import GHC.Driver.Types
@@ -92,7 +92,7 @@ then running the compiled program will not seg-fault, assuming no bugs downstrea
to decouple the safety of the resulting program from the type inference algorithm.
However, do note point (4) above. Core Lint does not check for incomplete case-matches;
-see Note [Case expression invariants] in CoreSyn, invariant (4). As explained there,
+see Note [Case expression invariants] in GHC.Core, invariant (4). As explained there,
an incomplete case-match might slip by Core Lint and cause trouble at runtime.
Note [GHC Formalism]
@@ -162,7 +162,7 @@ Note [Linting type lets]
~~~~~~~~~~~~~~~~~~~~~~~~
In the desugarer, it's very very convenient to be able to say (in effect)
let a = Type Int in <body>
-That is, use a type let. See Note [Type let] in CoreSyn.
+That is, use a type let. See Note [Type let] in GHC.Core.
However, when linting <body> we need to remember that a=Int, else we might
reject a correct program. So we carry a type substitution (in this example
@@ -197,7 +197,7 @@ different types, called bad coercions. Following coercions are forbidden:
Note [Join points]
~~~~~~~~~~~~~~~~~~
-We check the rules listed in Note [Invariants on join points] in CoreSyn. The
+We check the rules listed in Note [Invariants on join points] in GHC.Core. The
only one that causes any difficulty is the first: All occurrences must be tail
calls. To this end, along with the in-scope set, we remember in le_joins the
subset of in-scope Ids that are valid join ids. For example:
@@ -549,7 +549,7 @@ lintSingleBinding top_lvl_flag rec_flag (binder,rhs)
; ensureEqTys binder_ty ty (mkRhsMsg binder (text "RHS") ty)
-- If the binding is for a CoVar, the RHS should be (Coercion co)
- -- See Note [CoreSyn type and coercion invariant] in CoreSyn
+ -- See Note [Core type and coercion invariant] in GHC.Core
; checkL (not (isCoVar binder) || isCoArg rhs)
(mkLetErr binder rhs)
@@ -561,7 +561,7 @@ lintSingleBinding top_lvl_flag rec_flag (binder,rhs)
(badBndrTyMsg binder (text "levity-polymorphic"))
-- Check the let/app invariant
- -- See Note [CoreSyn let/app invariant] in CoreSyn
+ -- See Note [Core let/app invariant] in GHC.Core
; checkL ( isJoinId binder
|| not (isUnliftedType binder_ty)
|| (isNonRec rec_flag && exprOkForSpeculation rhs)
@@ -570,7 +570,7 @@ lintSingleBinding top_lvl_flag rec_flag (binder,rhs)
-- Check that if the binder is top-level or recursive, it's not
-- demanded. Primitive string literals are exempt as there is no
- -- computation to perform, see Note [CoreSyn top-level string literals].
+ -- computation to perform, see Note [Core top-level string literals].
; checkL (not (isStrictId binder)
|| (isNonRec rec_flag && not (isTopLevel top_lvl_flag))
|| exprIsTickedString rhs)
@@ -578,7 +578,7 @@ lintSingleBinding top_lvl_flag rec_flag (binder,rhs)
-- Check that if the binder is at the top level and has type Addr#,
-- that it is a string literal, see
- -- Note [CoreSyn top-level string literals].
+ -- Note [Core top-level string literals].
; checkL (not (isTopLevel top_lvl_flag && binder_ty `eqType` addrPrimTy)
|| exprIsTickedString rhs)
(mkTopNonLitStrMsg binder)
@@ -687,7 +687,7 @@ lintIdUnfolding bndr bndr_ty uf
; ensureEqTys bndr_ty ty (mkRhsMsg bndr (text "unfolding") ty) }
lintIdUnfolding _ _ _
= return () -- Do not Lint unstable unfoldings, because that leads
- -- to exponential behaviour; c.f. CoreFVs.idUnfoldingVars
+ -- to exponential behaviour; c.f. GHC.Core.FVs.idUnfoldingVars
{-
Note [Checking for INLINE loop breakers]
@@ -702,7 +702,7 @@ the desugarer.
Note [Checking for levity polymorphism]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
We ordinarily want to check for bad levity polymorphism. See
-Note [Levity polymorphism invariants] in CoreSyn. However, we do *not*
+Note [Levity polymorphism invariants] in GHC.Core. However, we do *not*
want to do this in a compulsory unfolding. Compulsory unfoldings arise
only internally, for things like newtype wrappers, dictionaries, and
(notably) unsafeCoerce#. These might legitimately be levity-polymorphic;
@@ -838,7 +838,7 @@ lintVarOcc :: Var -> Int -- Number of arguments (type or value) being passed
lintVarOcc var nargs
= do { checkL (isNonCoVarId var)
(text "Non term variable" <+> ppr var)
- -- See CoreSyn Note [Variable occurrences in Core]
+ -- See GHC.Core Note [Variable occurrences in Core]
-- Cneck that the type of the occurrence is the same
-- as the type of the binding site
@@ -971,7 +971,7 @@ Consider:
This is clearly ill-typed, since the jump is inside both an application and a
lambda, either of which is enough to disqualify it as a tail call (see Note
-[Invariants on join points] in CoreSyn). However, strictly from a
+[Invariants on join points] in GHC.Core). However, strictly from a
lambda-calculus perspective, the term doesn't go wrong---after the two beta
reductions, the jump *is* a tail call and everything is fine.
@@ -981,10 +981,10 @@ rules: naively reducing the above example using lets will capture any free
occurrence of y in e2. More fundamentally, type lets are tricky; many passes,
such as Float Out, tacitly assume that the incoming program's type lets have
all been dealt with by the simplifier. Thus we don't want to let-bind any types
-in, say, CoreSubst.simpleOptPgm, which in some circumstances can run immediately
+in, say, GHC.Core.Subst.simpleOptPgm, which in some circumstances can run immediately
before Float Out.
-All that said, currently CoreSubst.simpleOptPgm is the only thing using this
+All that said, currently GHC.Core.Subst.simpleOptPgm is the only thing using this
loophole, doing so to avoid re-traversing large functions (beta-reducing a type
lambda without introducing a type let requires a substitution). TODO: Improve
simpleOptPgm so that we can forget all this ever happened.
@@ -1013,7 +1013,7 @@ lintCoreArg fun_ty (Type arg_ty)
lintCoreArg fun_ty arg
= do { arg_ty <- markAllJoinsBad $ lintCoreExpr arg
- -- See Note [Levity polymorphism invariants] in CoreSyn
+ -- See Note [Levity polymorphism invariants] in GHC.Core
; flags <- getLintFlags
; lintL (not (lf_check_levity_poly flags) || not (isTypeLevPoly arg_ty))
(text "Levity-polymorphic argument:" <+>
@@ -1094,7 +1094,7 @@ lintCaseExpr scrut var alt_ty alts =
-- Check the scrutinee
; scrut_ty <- markAllJoinsBad $ lintCoreExpr scrut
-- See Note [Join points are less general than the paper]
- -- in CoreSyn
+ -- in GHC.Core
; (alt_ty, _) <- addLoc (CaseTy scrut) $
lintInTy alt_ty
@@ -1107,7 +1107,7 @@ lintCaseExpr scrut var alt_ty alts =
-- Check that the scrutinee is not a floating-point type
-- if there are any literal alternatives
- -- See CoreSyn Note [Case expression invariants] item (5)
+ -- See GHC.Core Note [Case expression invariants] item (5)
-- See Note [Rules for floating-point comparisons] in PrelRules
; let isLitPat (LitAlt _, _ , _) = True
isLitPat _ = False
@@ -1133,7 +1133,7 @@ lintCaseExpr scrut var alt_ty alts =
; subst <- getTCvSubst
; ensureEqTys var_ty scrut_ty (mkScrutMsg var var_ty scrut_ty subst)
- -- See CoreSyn Note [Case expression invariants] item (7)
+ -- See GHC.Core Note [Case expression invariants] item (7)
; lintBinder CaseBind var $ \_ ->
do { -- Check the alternatives
@@ -1152,14 +1152,14 @@ checkCaseAlts :: CoreExpr -> OutType -> [CoreAlt] -> LintM ()
checkCaseAlts e ty alts =
do { checkL (all non_deflt con_alts) (mkNonDefltMsg e)
- -- See CoreSyn Note [Case expression invariants] item (2)
+ -- See GHC.Core Note [Case expression invariants] item (2)
; checkL (increasing_tag con_alts) (mkNonIncreasingAltsMsg e)
- -- See CoreSyn Note [Case expression invariants] item (3)
+ -- See GHC.Core Note [Case expression invariants] item (3)
-- For types Int#, Word# with an infinite (well, large!) number of
-- possible values, there should usually be a DEFAULT case
- -- But (see Note [Empty case alternatives] in CoreSyn) it's ok to
+ -- But (see Note [Empty case alternatives] in GHC.Core) it's ok to
-- have *no* case alternatives.
-- In effect, this is a kind of partial test. I suppose it's possible
-- that we might *know* that 'x' was 1 or 2, in which case
@@ -1185,7 +1185,7 @@ lintAltExpr :: CoreExpr -> OutType -> LintM ()
lintAltExpr expr ann_ty
= do { actual_ty <- lintCoreExpr expr
; ensureEqTys actual_ty ann_ty (mkCaseAltMsg expr actual_ty ann_ty) }
- -- See CoreSyn Note [Case expression invariants] item (6)
+ -- See GHC.Core Note [Case expression invariants] item (6)
lintCoreAlt :: OutType -- Type of scrutinee
-> OutType -- Type of the alternative
@@ -1299,7 +1299,7 @@ lintIdBndr top_lvl bind_site id linterF
; (ty, k) <- addLoc (IdTy id) $
lintInTy (idType id)
- -- See Note [Levity polymorphism invariants] in CoreSyn
+ -- See Note [Levity polymorphism invariants] in GHC.Core
; lintL (isJoinId id || not (lf_check_levity_poly flags) || not (isKindLevPoly k))
(text "Levity-polymorphic binder:" <+>
(ppr id <+> dcolon <+> parens (ppr ty <+> dcolon <+> ppr k)))
@@ -1455,7 +1455,7 @@ Here 'cls' appears free in b's kind, which would usually be illegal
#in this case (Alg cls *) = *, so all is well. Currently we allow
this, and make Lint expand synonyms where necessary to make it so.
-c.f. TcUnify.occCheckExpand and CoreUtils.coreAltsType which deal
+c.f. TcUnify.occCheckExpand and GHC.Core.Utils.coreAltsType which deal
with the same problem. A single systematic solution eludes me.
-}
@@ -1612,7 +1612,7 @@ lintCoreRule fun fun_ty rule@(Rule { ru_name = name, ru_bndrs = bndrs
rhs_fvs = exprFreeVars rhs
is_bad_bndr :: Var -> Bool
- -- See Note [Unbound RULE binders] in Rules
+ -- See Note [Unbound RULE binders] in GHC.Core.Rules
is_bad_bndr bndr = not (bndr `elemVarSet` lhs_fvs)
&& bndr `elemVarSet` rhs_fvs
&& isNothing (isReflCoVar_maybe bndr)
@@ -1659,7 +1659,7 @@ argument to be made for allowing a situation like this:
Applying this rule can't turn a well-typed program into an ill-typed one, so
conceivably we could allow it. But we can always eta-expand such an
-"undersaturated" rule (see 'CoreArity.etaExpandToJoinPointRule'), and in fact
+"undersaturated" rule (see 'GHC.Core.Arity.etaExpandToJoinPointRule'), and in fact
the simplifier would have to in order to deal with the RHS. So we take a
conservative view and don't allow undersaturated rules for join points. See
Note [Rules and join points] in OccurAnal for further discussion.
diff --git a/compiler/coreSyn/MkCore.hs b/compiler/GHC/Core/Make.hs
index d8b3b7a75d..540ecfbe56 100644
--- a/compiler/coreSyn/MkCore.hs
+++ b/compiler/GHC/Core/Make.hs
@@ -3,7 +3,7 @@
{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-}
-- | Handy functions for creating much Core syntax
-module MkCore (
+module GHC.Core.Make (
-- * Constructing normal syntax
mkCoreLet, mkCoreLets,
mkCoreApp, mkCoreApps, mkCoreConApps,
@@ -59,8 +59,8 @@ import GhcPrelude
import Id
import Var ( EvVar, setTyVarUnique )
-import CoreSyn
-import CoreUtils ( exprType, needsCaseBinding, mkSingleAltCase, bindNonRec )
+import GHC.Core
+import GHC.Core.Utils ( exprType, needsCaseBinding, mkSingleAltCase, bindNonRec )
import Literal
import GHC.Driver.Types
@@ -92,7 +92,7 @@ infixl 4 `mkCoreApp`, `mkCoreApps`
{-
************************************************************************
* *
-\subsection{Basic CoreSyn construction}
+\subsection{Basic GHC.Core construction}
* *
************************************************************************
-}
@@ -108,9 +108,9 @@ sortQuantVars vs = sorted_tcvs ++ ids
sorted_tcvs = scopedSort tcvs
-- | Bind a binding group over an expression, using a @let@ or @case@ as
--- appropriate (see "CoreSyn#let_app_invariant")
+-- appropriate (see "GHC.Core#let_app_invariant")
mkCoreLet :: CoreBind -> CoreExpr -> CoreExpr
-mkCoreLet (NonRec bndr rhs) body -- See Note [CoreSyn let/app invariant]
+mkCoreLet (NonRec bndr rhs) body -- See Note [Core let/app invariant]
= bindNonRec bndr rhs body
mkCoreLet bind body
= Let bind body
@@ -135,7 +135,7 @@ mkCoreConApps con args = mkCoreApps (Var (dataConWorkId con)) args
-- | Construct an expression which represents the application of a number of
-- expressions to another. The leftmost expression in the list is applied first
-- Respects the let/app invariant by building a case expression where necessary
--- See CoreSyn Note [CoreSyn let/app invariant]
+-- See Note [Core let/app invariant] in GHC.Core
mkCoreApps :: CoreExpr -> [CoreExpr] -> CoreExpr
mkCoreApps fun args
= fst $
@@ -147,7 +147,7 @@ mkCoreApps fun args
-- | Construct an expression which represents the application of one expression
-- to the other
-- Respects the let/app invariant by building a case expression where necessary
--- See CoreSyn Note [CoreSyn let/app invariant]
+-- See Note [Core let/app invariant] in GHC.Core
mkCoreApp :: SDoc -> CoreExpr -> CoreExpr -> CoreExpr
mkCoreApp s fun arg
= fst $ mkCoreAppTyped s (fun, exprType fun) arg
@@ -157,7 +157,7 @@ mkCoreApp s fun arg
-- function is not exported and used in the definition of 'mkCoreApp' and
-- 'mkCoreApps'.
-- Respects the let/app invariant by building a case expression where necessary
--- See CoreSyn Note [CoreSyn let/app invariant]
+-- See Note [Core let/app invariant] in GHC.Core
mkCoreAppTyped :: SDoc -> (CoreExpr, Type) -> CoreExpr -> (CoreExpr, Type)
mkCoreAppTyped _ (fun, fun_ty) (Type ty)
= (App fun (Type ty), piResultTy fun_ty ty)
@@ -173,7 +173,7 @@ mkValApp :: CoreExpr -> CoreExpr -> Type -> Type -> CoreExpr
-- Build an application (e1 e2),
-- or a strict binding (case e2 of x -> e1 x)
-- using the latter when necessary to respect the let/app invariant
--- See Note [CoreSyn let/app invariant]
+-- See Note [Core let/app invariant] in GHC.Core
mkValApp fun arg arg_ty res_ty
| not (needsCaseBinding arg_ty arg)
= App fun arg -- The vastly common case
@@ -234,7 +234,7 @@ mkIfThenElse guard then_expr else_expr
castBottomExpr :: CoreExpr -> Type -> CoreExpr
-- (castBottomExpr e ty), assuming that 'e' diverges,
-- return an expression of type 'ty'
--- See Note [Empty case alternatives] in CoreSyn
+-- See Note [Empty case alternatives] in GHC.Core
castBottomExpr e res_ty
| e_ty `eqType` res_ty = e
| otherwise = Case e (mkWildValBinder e_ty) res_ty []
diff --git a/compiler/coreSyn/CoreMap.hs b/compiler/GHC/Core/Map.hs
index d50dcbf1bc..ee12bdd8a3 100644
--- a/compiler/coreSyn/CoreMap.hs
+++ b/compiler/GHC/Core/Map.hs
@@ -11,7 +11,7 @@
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE UndecidableInstances #-}
-module CoreMap(
+module GHC.Core.Map (
-- * Maps over Core expressions
CoreMap, emptyCoreMap, extendCoreMap, lookupCoreMap, foldCoreMap,
-- * Maps over 'Type's
@@ -40,7 +40,7 @@ module CoreMap(
import GhcPrelude
import TrieMap
-import CoreSyn
+import GHC.Core
import Coercion
import Name
import Type
@@ -139,7 +139,7 @@ We could compare the return type regardless, but the wildly common case
is that it's unnecessary, so we have two fields (cm_case and cm_ecase)
for the two possibilities. Only cm_ecase looks at the type.
-See also Note [Empty case alternatives] in CoreSyn.
+See also Note [Empty case alternatives] in GHC.Core.
-}
-- | @CoreMap a@ is a map from 'CoreExpr' to @a@. If you are a client, this
diff --git a/compiler/coreSyn/CoreTidy.hs b/compiler/GHC/Core/Op/Tidy.hs
index 9c19f3667b..8ddd3708c3 100644
--- a/compiler/coreSyn/CoreTidy.hs
+++ b/compiler/GHC/Core/Op/Tidy.hs
@@ -9,7 +9,7 @@ The code for *top-level* bindings is in GHC.Iface.Tidy.
{-# LANGUAGE CPP #-}
{-# OPTIONS_GHC -Wno-incomplete-record-updates #-}
-module CoreTidy (
+module GHC.Core.Op.Tidy (
tidyExpr, tidyRules, tidyUnfolding
) where
@@ -17,8 +17,8 @@ module CoreTidy (
import GhcPrelude
-import CoreSyn
-import CoreSeq ( seqUnfolding )
+import GHC.Core
+import GHC.Core.Seq ( seqUnfolding )
import Id
import IdInfo
import Demand ( zapUsageEnvSig )
diff --git a/compiler/coreSyn/PprCore.hs b/compiler/GHC/Core/Ppr.hs
index 760c325d2b..bd2b968ef4 100644
--- a/compiler/coreSyn/PprCore.hs
+++ b/compiler/GHC/Core/Ppr.hs
@@ -10,7 +10,7 @@ Printing of Core syntax
{-# LANGUAGE LambdaCase #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
-module PprCore (
+module GHC.Core.Ppr (
pprCoreExpr, pprParendExpr,
pprCoreBinding, pprCoreBindings, pprCoreAlt,
pprCoreBindingWithSize, pprCoreBindingsWithSize,
@@ -19,8 +19,8 @@ module PprCore (
import GhcPrelude
-import CoreSyn
-import CoreStats (exprStats)
+import GHC.Core
+import GHC.Core.Stats (exprStats)
import Literal( pprLiteral )
import Name( pprInfixName, pprPrefixName )
import Var
@@ -517,7 +517,7 @@ ppIdInfo id info
, (not (null rules), text "RULES:" <+> vcat (map pprRule rules))
] -- Inline pragma, occ, demand, one-shot info
-- printed out with all binders (when debug is on);
- -- see PprCore.pprIdBndr
+ -- see GHC.Core.Ppr.pprIdBndr
where
pp_scope | isGlobalId id = text "GblId"
| isExportedId id = text "LclIdX"
diff --git a/compiler/main/PprTyThing.hs b/compiler/GHC/Core/Ppr/TyThing.hs
index 11288618ef..b11cd6edb2 100644
--- a/compiler/main/PprTyThing.hs
+++ b/compiler/GHC/Core/Ppr/TyThing.hs
@@ -7,7 +7,7 @@
-----------------------------------------------------------------------------
{-# LANGUAGE CPP #-}
-module PprTyThing (
+module GHC.Core.Ppr.TyThing (
pprTyThing,
pprTyThingInContext,
pprTyThingLoc,
diff --git a/compiler/specialise/Rules.hs b/compiler/GHC/Core/Rules.hs
index 6b96877067..9d2a209993 100644
--- a/compiler/specialise/Rules.hs
+++ b/compiler/GHC/Core/Rules.hs
@@ -8,7 +8,7 @@
-- | Functions for collecting together and applying rewrite rules to a module.
-- The 'CoreRule' datatype itself is declared elsewhere.
-module Rules (
+module GHC.Core.Rules (
-- ** Constructing
emptyRuleBase, mkRuleBase, extendRuleBaseList,
unionRuleBase, pprRuleBase,
@@ -30,22 +30,22 @@ module Rules (
import GhcPrelude
-import CoreSyn -- All of it
+import GHC.Core -- All of it
import Module ( Module, ModuleSet, elemModuleSet )
-import CoreSubst
-import CoreOpt ( exprIsLambda_maybe )
-import CoreFVs ( exprFreeVars, exprsFreeVars, bindFreeVars
+import GHC.Core.Subst
+import GHC.Core.SimpleOpt ( exprIsLambda_maybe )
+import GHC.Core.FVs ( exprFreeVars, exprsFreeVars, bindFreeVars
, rulesFreeVarsDSet, exprsOrphNames, exprFreeVarsList )
-import CoreUtils ( exprType, eqExpr, mkTick, mkTicks,
- stripTicksTopT, stripTicksTopE,
- isJoinBind )
-import PprCore ( pprRules )
+import GHC.Core.Utils ( exprType, eqExpr, mkTick, mkTicks
+ , stripTicksTopT, stripTicksTopE
+ , isJoinBind )
+import GHC.Core.Ppr ( pprRules )
import Type ( Type, TCvSubst, extendTvSubst, extendCvSubst
, mkEmptyTCvSubst, substTy )
import TcType ( tcSplitTyConApp_maybe )
import TysWiredIn ( anyTypeOfKind )
import Coercion
-import CoreTidy ( tidyRules )
+import GHC.Core.Op.Tidy ( tidyRules )
import Id
import IdInfo ( RuleInfo( RuleInfo ) )
import Var
@@ -171,7 +171,7 @@ where pi' :: Lift Int# is the specialised version of pi.
mkRule :: Module -> Bool -> Bool -> RuleName -> Activation
-> Name -> [CoreBndr] -> [CoreExpr] -> CoreExpr -> CoreRule
-- ^ Used to make 'CoreRule' for an 'Id' defined in the module being
--- compiled. See also 'CoreSyn.CoreRule'
+-- compiled. See also 'GHC.Core.CoreRule'
mkRule this_mod is_auto is_local name act fn bndrs args rhs
= Rule { ru_name = name, ru_fn = fn, ru_act = act,
ru_bndrs = bndrs, ru_args = args,
@@ -262,7 +262,7 @@ pprRulesForUser :: DynFlags -> [CoreRule] -> SDoc
-- (b) sort them into order based on the rule name
-- (c) suppress uniques (unless -dppr-debug is on)
-- This combination makes the output stable so we can use in testing
--- It's here rather than in PprCore because it calls tidyRules
+-- It's here rather than in GHC.Core.Ppr because it calls tidyRules
pprRulesForUser dflags rules
= withPprStyle (defaultUserStyle dflags) $
pprRules $
@@ -341,7 +341,7 @@ but that isn't quite right:
************************************************************************
-}
--- RuleBase itself is defined in CoreSyn, along with CoreRule
+-- RuleBase itself is defined in GHC.Core, along with CoreRule
emptyRuleBase :: RuleBase
emptyRuleBase = emptyNameEnv
@@ -1066,7 +1066,7 @@ Our cunning plan is this:
check that does not mention any locally bound (lambda, case)
variables. If so we fail
- * We use CoreSubst.substBind to freshen the binding, using an
+ * We use GHC.Core.Subst.substBind to freshen the binding, using an
in-scope set that is the original in-scope variables plus the
rs_bndrs (currently floated let-bindings). So in (a) above
we'll freshen the 'v' binding; in (b) above we'll freshen
diff --git a/compiler/coreSyn/CoreSeq.hs b/compiler/GHC/Core/Seq.hs
index aa94a24215..5c600296e0 100644
--- a/compiler/coreSyn/CoreSeq.hs
+++ b/compiler/GHC/Core/Seq.hs
@@ -4,7 +4,7 @@
-- It can often be useful to force various parts of the AST. This module
-- provides a number of @seq@-like functions to accomplish this.
-module CoreSeq (
+module GHC.Core.Seq (
-- * Utilities for forcing Core structures
seqExpr, seqExprs, seqUnfolding, seqRules,
megaSeqIdInfo, seqRuleInfo, seqBinds,
@@ -12,7 +12,7 @@ module CoreSeq (
import GhcPrelude
-import CoreSyn
+import GHC.Core
import IdInfo
import Demand( seqDemand, seqStrictSig )
import Cpr( seqCprSig )
diff --git a/compiler/coreSyn/CoreOpt.hs b/compiler/GHC/Core/SimpleOpt.hs
index 7bb83db8b7..f9665140b1 100644
--- a/compiler/coreSyn/CoreOpt.hs
+++ b/compiler/GHC/Core/SimpleOpt.hs
@@ -4,7 +4,7 @@
-}
{-# LANGUAGE CPP #-}
-module CoreOpt (
+module GHC.Core.SimpleOpt (
-- ** Simple expression optimiser
simpleOptPgm, simpleOptExpr, simpleOptExprWith,
@@ -22,15 +22,15 @@ module CoreOpt (
import GhcPrelude
-import CoreArity( etaExpandToJoinPoint )
+import GHC.Core.Arity( etaExpandToJoinPoint )
-import CoreSyn
-import CoreSubst
-import CoreUtils
-import CoreFVs
-import {-# SOURCE #-} CoreUnfold ( mkUnfolding )
-import MkCore ( FloatBind(..) )
-import PprCore ( pprCoreBindings, pprRules )
+import GHC.Core
+import GHC.Core.Subst
+import GHC.Core.Utils
+import GHC.Core.FVs
+import {-# SOURCE #-} GHC.Core.Unfold( mkUnfolding )
+import GHC.Core.Make ( FloatBind(..) )
+import GHC.Core.Ppr ( pprCoreBindings, pprRules )
import OccurAnal( occurAnalyseExpr, occurAnalysePgm )
import Literal ( Literal(LitString) )
import Id
@@ -384,7 +384,7 @@ simple_bind_pair env@(SOE { soe_inl = inl_env, soe_subst = subst })
| ASSERT2( isNonCoVarId in_bndr, ppr in_bndr )
-- The previous two guards got rid of tyvars and coercions
- -- See Note [CoreSyn type and coercion invariant] in CoreSyn
+ -- See Note [Core type and coercion invariant] in GHC.Core
pre_inline_unconditionally
= (env { soe_inl = extendVarEnv inl_env in_bndr clo }, Nothing)
@@ -452,7 +452,7 @@ simple_out_bind_pair env in_bndr mb_out_bndr out_rhs
occ_info active stable_unf top_level
| ASSERT2( isNonCoVarId in_bndr, ppr in_bndr )
-- Type and coercion bindings are caught earlier
- -- See Note [CoreSyn type and coercion invariant]
+ -- See Note [Core type and coercion invariant]
post_inline_unconditionally
= ( env' { soe_subst = extendIdSubst (soe_subst env) in_bndr out_rhs }
, Nothing)
@@ -530,7 +530,7 @@ But not for join points! For two reasons:
Lint may reject. I say "may" because this is /explicitly/
allowed in the "Compiling without Continuations" paper
(Section 3, "Managing \Delta"). But GHC currently does not
- allow this slightly-more-flexible form. See CoreSyn
+ allow this slightly-more-flexible form. See GHC.Core
Note [Join points are less general than the paper].
The simple thing to do is to disable this transformation
@@ -576,7 +576,7 @@ subst_opt_id_bndr :: SimpleOptEnv -> InId -> (SimpleOptEnv, OutId)
--
-- Rather like SimplEnv.substIdBndr
--
--- It's important to zap fragile OccInfo (which CoreSubst.substIdBndr
+-- It's important to zap fragile OccInfo (which GHC.Core.Subst.substIdBndr
-- carefully does not do) because simplOptExpr invalidates it
subst_opt_id_bndr env@(SOE { soe_subst = subst, soe_inl = inl }) old_id
@@ -820,7 +820,7 @@ Note [exprIsConApp_maybe on literal strings]
See #9400 and #13317.
Conceptually, a string literal "abc" is just ('a':'b':'c':[]), but in Core
-they are represented as unpackCString# "abc"# by MkCore.mkStringExprFS, or
+they are represented as unpackCString# "abc"# by GHC.Core.Make.mkStringExprFS, or
unpackCStringUtf8# when the literal contains multi-byte UTF8 characters.
For optimizations we want to be able to treat it as a list, so they can be
@@ -872,7 +872,7 @@ Here's how exprIsConApp_maybe achieves this:
0. Start with scrutinee = $WMkT e
1. Inline $WMkT on-the-fly. That's why data-constructor wrappers are marked
- as expandable. (See CoreUtils.isExpandableApp.) Now we have
+ as expandable. (See GHC.Core.Utils.isExpandableApp.) Now we have
scrutinee = (\n. case n of n' -> MkT n') e
2. Beta-reduce the application, generating a floated 'let'.
@@ -1076,10 +1076,10 @@ exprIsConApp_maybe (in_scope, id_unf) expr
; return (in_scope, floats, con, tys, args) }
----------------------------
- -- Operations on the (Either InScopeSet CoreSubst)
+ -- Operations on the (Either InScopeSet GHC.Core.Subst)
-- The Left case is wildly dominant
subst_co (Left {}) co = co
- subst_co (Right s) co = CoreSubst.substCo s co
+ subst_co (Right s) co = GHC.Core.Subst.substCo s co
subst_expr (Left {}) e = e
subst_expr (Right s) e = substExpr (text "exprIsConApp2") s e
@@ -1102,7 +1102,7 @@ exprIsConApp_maybe (in_scope, id_unf) expr
dealWithStringLiteral :: Var -> BS.ByteString -> Coercion
-> Maybe (DataCon, [Type], [CoreExpr])
--- This is not possible with user-supplied empty literals, MkCore.mkStringExprFS
+-- This is not possible with user-supplied empty literals, GHC.Core.Make.mkStringExprFS
-- turns those into [] automatically, but just in case something else in GHC
-- generates a string literal directly.
dealWithStringLiteral _ str co
@@ -1140,7 +1140,7 @@ Note [DFun arity check]
~~~~~~~~~~~~~~~~~~~~~~~
Here we check that the total number of supplied arguments (including
type args) matches what the dfun is expecting. This may be *less*
-than the ordinary arity of the dfun: see Note [DFun unfoldings] in CoreSyn
+than the ordinary arity of the dfun: see Note [DFun unfoldings] in GHC.Core
-}
exprIsLiteral_maybe :: InScopeEnv -> CoreExpr -> Maybe Literal
@@ -1164,7 +1164,7 @@ exprIsLambda_maybe will, given an expression `e`, try to turn it into the form
casts (using the Push rule), and it unfolds function calls if the unfolding
has a greater arity than arguments are present.
-Currently, it is used in Rules.match, and is required to make
+Currently, it is used in GHC.Core.Rules.match, and is required to make
"map coerce = coerce" match.
-}
@@ -1288,7 +1288,7 @@ pushCoTyArg co ty
-- co1 :: k2 ~N k1
-- Note that NthCo can extract a Nominal equality between the
-- kinds of the types related by a coercion between forall-types.
- -- See the NthCo case in CoreLint.
+ -- See the NthCo case in GHC.Core.Lint.
co2 = mkInstCo co (mkGReflLeftCo Nominal ty co1)
-- co2 :: ty1[ (ty|>co1)/a1 ] ~ ty2[ ty/a2 ]
diff --git a/compiler/coreSyn/CoreStats.hs b/compiler/GHC/Core/Stats.hs
index fde107b372..fe288f5348 100644
--- a/compiler/coreSyn/CoreStats.hs
+++ b/compiler/GHC/Core/Stats.hs
@@ -5,7 +5,7 @@
-- | Functions to computing the statistics reflective of the "size"
-- of a Core expression
-module CoreStats (
+module GHC.Core.Stats (
-- * Expression and bindings size
coreBindsSize, exprSize,
CoreStats(..), coreBindsStats, exprStats,
@@ -14,7 +14,7 @@ module CoreStats (
import GhcPrelude
import BasicTypes
-import CoreSyn
+import GHC.Core
import Outputable
import Coercion
import Var
diff --git a/compiler/coreSyn/CoreSubst.hs b/compiler/GHC/Core/Subst.hs
index ec55f688a9..e61088a277 100644
--- a/compiler/coreSyn/CoreSubst.hs
+++ b/compiler/GHC/Core/Subst.hs
@@ -8,7 +8,7 @@ Utility functions on @Core@ syntax
{-# LANGUAGE CPP #-}
{-# OPTIONS_GHC -Wno-incomplete-record-updates #-}
-module CoreSubst (
+module GHC.Core.Subst (
-- * Main data types
Subst(..), -- Implementation exported for supercompiler's Renaming.hs only
TvSubstEnv, IdSubstEnv, InScopeSet,
@@ -39,10 +39,10 @@ module CoreSubst (
import GhcPrelude
-import CoreSyn
-import CoreFVs
-import CoreSeq
-import CoreUtils
+import GHC.Core
+import GHC.Core.FVs
+import GHC.Core.Seq
+import GHC.Core.Utils
import qualified Type
import qualified Coercion
@@ -251,7 +251,7 @@ lookupIdSubst doc (Subst in_scope ids _ _) v
| Just e <- lookupVarEnv ids v = e
| Just v' <- lookupInScope in_scope v = Var v'
-- Vital! See Note [Extending the Subst]
- | otherwise = WARN( True, text "CoreSubst.lookupIdSubst" <+> doc <+> ppr v
+ | otherwise = WARN( True, text "GHC.Core.Subst.lookupIdSubst" <+> doc <+> ppr v
$$ ppr in_scope)
Var v
diff --git a/compiler/coreSyn/CoreUnfold.hs b/compiler/GHC/Core/Unfold.hs
index 70f8715db3..a895df36c0 100644
--- a/compiler/coreSyn/CoreUnfold.hs
+++ b/compiler/GHC/Core/Unfold.hs
@@ -19,7 +19,7 @@ find, unsurprisingly, a Core expression.
{-# OPTIONS_GHC -Wno-incomplete-record-updates #-}
-module CoreUnfold (
+module GHC.Core.Unfold (
Unfolding, UnfoldingGuidance, -- Abstract types
noUnfolding, mkImplicitUnfolding,
@@ -37,7 +37,7 @@ module CoreUnfold (
callSiteInline, CallCtxt(..),
- -- Reexport from CoreSubst (it only live there so it can be used
+ -- Reexport from GHC.Core.Subst (it only live there so it can be used
-- by the Very Simple Optimiser)
exprIsConApp_maybe, exprIsLiteral_maybe
) where
@@ -47,11 +47,11 @@ module CoreUnfold (
import GhcPrelude
import GHC.Driver.Session
-import CoreSyn
-import OccurAnal ( occurAnalyseExpr_NoBinderSwap )
-import CoreOpt
-import CoreArity ( manifestArity )
-import CoreUtils
+import GHC.Core
+import OccurAnal ( occurAnalyseExpr_NoBinderSwap )
+import GHC.Core.SimpleOpt
+import GHC.Core.Arity ( manifestArity )
+import GHC.Core.Utils
import Id
import Demand ( isBottomingSig )
import DataCon
@@ -828,7 +828,7 @@ sizeExpr dflags bOMB_OUT_SIZE top_args expr
-- | Finds a nominal size of a string literal.
litSize :: Literal -> Int
--- Used by CoreUnfold.sizeExpr
+-- Used by GHC.Core.Unfold.sizeExpr
litSize (LitNumber LitNumInteger _ _) = 100 -- Note [Size of literal integers]
litSize (LitNumber LitNumNatural _ _) = 100
litSize (LitString str) = 10 + 10 * ((BS.length str + 3) `div` 4)
@@ -1534,7 +1534,7 @@ because the latter is strict.
f = \x -> ...(error s)...
Fundamentally such contexts should not encourage inlining because, provided
-the RHS is "expandable" (see Note [exprIsExpandable] in CoreUtils) the
+the RHS is "expandable" (see Note [exprIsExpandable] in GHC.Core.Utils) the
context can ``see'' the unfolding of the variable (e.g. case or a
RULE) so there's no gain.
diff --git a/compiler/coreSyn/CoreUnfold.hs-boot b/compiler/GHC/Core/Unfold.hs-boot
index cee6658df2..54895ae8b1 100644
--- a/compiler/coreSyn/CoreUnfold.hs-boot
+++ b/compiler/GHC/Core/Unfold.hs-boot
@@ -1,9 +1,9 @@
-module CoreUnfold (
+module GHC.Core.Unfold (
mkUnfolding, mkInlineUnfolding
) where
import GhcPrelude
-import CoreSyn
+import GHC.Core
import GHC.Driver.Session
mkInlineUnfolding :: CoreExpr -> Unfolding
diff --git a/compiler/coreSyn/CoreUtils.hs b/compiler/GHC/Core/Utils.hs
index 7133567068..67ff7823e4 100644
--- a/compiler/coreSyn/CoreUtils.hs
+++ b/compiler/GHC/Core/Utils.hs
@@ -9,7 +9,7 @@ Utility functions on @Core@ syntax
{-# LANGUAGE CPP #-}
-- | Commonly useful utilities for manipulating the Core language
-module CoreUtils (
+module GHC.Core.Utils (
-- * Constructing expressions
mkCast,
mkTick, mkTicks, mkTickNoHNF, tickHNFArgs,
@@ -64,10 +64,10 @@ module CoreUtils (
import GhcPrelude
-import CoreSyn
+import GHC.Core
import PrelNames ( makeStaticName )
-import PprCore
-import CoreFVs( exprFreeVars )
+import GHC.Core.Ppr
+import GHC.Core.FVs( exprFreeVars )
import Var
import SrcLoc
import VarEnv
@@ -112,7 +112,7 @@ import UniqSet
exprType :: CoreExpr -> Type
-- ^ Recover the type of a well-typed Core expression. Fails when
--- applied to the actual 'CoreSyn.Type' expression as it cannot
+-- applied to the actual 'GHC.Core.Type' expression as it cannot
-- really be said to have a type
exprType (Var var) = idType var
exprType (Lit lit) = literalType lit
@@ -222,7 +222,7 @@ Various possibilities suggest themselves:
Note that there might be existentially quantified coercion variables, too.
-}
--- Not defined with applyTypeToArg because you can't print from CoreSyn.
+-- Not defined with applyTypeToArg because you can't print from GHC.Core.
applyTypeToArgs :: CoreExpr -> Type -> [CoreExpr] -> Type
-- ^ A more efficient version of 'applyTypeToArg' when we have several arguments.
-- The first argument is just for debugging, and gives some context
@@ -482,7 +482,7 @@ bindNonRec :: Id -> CoreExpr -> CoreExpr -> CoreExpr
-- It's used by the desugarer to avoid building bindings
-- that give Core Lint a heart attack, although actually
-- the simplifier deals with them perfectly well. See
--- also 'MkCore.mkCoreLet'
+-- also 'GHC.Core.Make.mkCoreLet'
bindNonRec bndr rhs body
| isTyVar bndr = let_bind
| isCoVar bndr = if isCoArg rhs then let_bind
@@ -495,7 +495,7 @@ bindNonRec bndr rhs body
let_bind = Let (NonRec bndr rhs) body
-- | Tests whether we have to use a @case@ rather than @let@ binding for this expression
--- as per the invariants of 'CoreExpr': see "CoreSyn#let_app_invariant"
+-- as per the invariants of 'CoreExpr': see "GHC.Core#let_app_invariant"
needsCaseBinding :: Type -> CoreExpr -> Bool
needsCaseBinding ty rhs = isUnliftedType ty && not (exprOkForSpeculation rhs)
-- Make a case expression instead of a let
@@ -555,7 +555,7 @@ can be eliminated by expanding the synonym.
Note [Binding coercions]
~~~~~~~~~~~~~~~~~~~~~~~~
Consider binding a CoVar, c = e. Then, we must satisfy
-Note [CoreSyn type and coercion invariant] in CoreSyn,
+Note [Core type and coercion invariant] in GHC.Core,
which allows only (Coercion co) on the RHS.
************************************************************************
@@ -979,7 +979,7 @@ Note [Empty case is trivial]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~
The expression (case (x::Int) Bool of {}) is just a type-changing
case used when we are sure that 'x' will not return. See
-Note [Empty case alternatives] in CoreSyn.
+Note [Empty case alternatives] in GHC.Core.
If the scrutinee is trivial, then so is the whole expression; and the
CoreToSTG pass in fact drops the case expression leaving only the
@@ -1048,7 +1048,7 @@ getIdFromTrivialExpr_maybe e
{-
exprIsBottom is a very cheap and cheerful function; it may return
False for bottoming expressions, but it never costs much to ask. See
-also CoreArity.exprBotStrictness_maybe, but that's a bit more
+also GHC.Core.Arity.exprBotStrictness_maybe, but that's a bit more
expensive.
-}
@@ -1068,7 +1068,7 @@ exprIsBottom e
go n (Let _ e) = go n e
go n (Lam v e) | isTyVar v = go n e
go _ (Case _ _ _ alts) = null alts
- -- See Note [Empty case alternatives] in CoreSyn
+ -- See Note [Empty case alternatives] in GHC.Core
go _ _ = False
{- Note [Bottoming expressions]
@@ -1193,8 +1193,11 @@ the moment we go for the slightly more aggressive version which treats
Moreover it improves arities of overloaded functions where
there is only dictionary selection (no construction) involved
-Note [exprIsCheap] See also Note [Interaction of exprIsCheap and lone variables]
-~~~~~~~~~~~~~~~~~~ in CoreUnfold.hs
+Note [exprIsCheap]
+~~~~~~~~~~~~~~~~~~
+
+See also Note [Interaction of exprIsCheap and lone variables] in GHC.Core.Unfold
+
@exprIsCheap@ looks at a Core expression and returns \tr{True} if
it is obviously in weak head normal form, or is cheap to get to WHNF.
[Note that that's not the same as exprIsDupable; an expression might be
@@ -1296,7 +1299,7 @@ so might make a RULE or case-of-constructor fire. Consider
y = build g
in ....(case x of (p,q) -> rhs)....(foldr k z y)....
-We don't inline 'x' or 'y' (see Note [Lone variables] in CoreUnfold),
+We don't inline 'x' or 'y' (see Note [Lone variables] in GHC.Core.Unfold),
but we do want
* the case-expression to simplify
@@ -1835,7 +1838,7 @@ it doesn't have the trickiness of the let/app invariant to worry about.
-- > C (f x :: Int#)
--
-- Suppose @f x@ diverges; then @C (f x)@ is not a value. However this can't
--- happen: see "CoreSyn#let_app_invariant". This invariant states that arguments of
+-- happen: see "GHC.Core#let_app_invariant". This invariant states that arguments of
-- unboxed type must be ok-for-speculation (or trivial).
exprIsHNF :: CoreExpr -> Bool -- True => Value-lambda, constructor, PAP
exprIsHNF = exprIsHNFlike isDataConWorkId isEvaldUnfolding
@@ -1894,7 +1897,7 @@ exprIsHNFlike is_con is_con_unf = is_hnf_like
id_app_is_value id n_val_args
= is_con id
|| idArity id > n_val_args
- || id `hasKey` absentErrorIdKey -- See Note [aBSENT_ERROR_ID] in MkCore
+ || id `hasKey` absentErrorIdKey -- See Note [aBSENT_ERROR_ID] in GHC.Core.Make
-- absentError behaves like an honorary data constructor
@@ -1915,10 +1918,10 @@ don't want to discard a seq on it.
-- | Can we bind this 'CoreExpr' at the top level?
exprIsTopLevelBindable :: CoreExpr -> Type -> Bool
--- See Note [CoreSyn top-level string literals]
+-- See Note [Core top-level string literals]
-- Precondition: exprType expr = ty
-- Top-level literal strings can't even be wrapped in ticks
--- see Note [CoreSyn top-level string literals] in CoreSyn
+-- see Note [Core top-level string literals] in GHC.Core
exprIsTopLevelBindable expr ty
= not (mightBeUnliftedType ty)
-- Note that 'expr' may be levity polymorphic here consequently we must use
diff --git a/compiler/GHC/CoreToByteCode.hs b/compiler/GHC/CoreToByteCode.hs
index a2b18601ca..6b5a40f4a8 100644
--- a/compiler/GHC/CoreToByteCode.hs
+++ b/compiler/GHC/CoreToByteCode.hs
@@ -31,12 +31,12 @@ import Id
import Var ( updateVarType )
import ForeignCall
import GHC.Driver.Types
-import CoreUtils
-import CoreSyn
-import PprCore
+import GHC.Core.Utils
+import GHC.Core
+import GHC.Core.Ppr
import Literal
import PrimOp
-import CoreFVs
+import GHC.Core.FVs
import Type
import GHC.Types.RepType
import DataCon
@@ -718,10 +718,10 @@ Note [Not-necessarily-lifted join points]
A join point variable is essentially a goto-label: it is, for example,
never used as an argument to another function, and it is called only
in tail position. See Note [Join points] and Note [Invariants on join points],
-both in CoreSyn. Because join points do not compile to true, red-blooded
+both in GHC.Core. Because join points do not compile to true, red-blooded
variables (with, e.g., registers allocated to them), they are allowed
to be levity-polymorphic. (See invariant #6 in Note [Invariants on join points]
-in CoreSyn.)
+in GHC.Core.)
However, in this byte-code generator, join points *are* treated just as
ordinary variables. There is no check whether a binding is for a join point
@@ -731,7 +731,7 @@ opportunity here, but that is beyond the scope of my (Richard E's) Thursday.)
We thus must have *some* strategy for dealing with levity-polymorphic and
unlifted join points. Levity-polymorphic variables are generally not allowed
(though levity-polymorphic join points *are*; see Note [Invariants on join points]
-in CoreSyn, point 6), and we don't wish to evaluate unlifted join points eagerly.
+in GHC.Core, point 6), and we don't wish to evaluate unlifted join points eagerly.
The questionable join points are *not-necessarily-lifted join points*
(NNLJPs). (Not having such a strategy led to #16509, which panicked in the
isUnliftedType check in the AnnVar case of schemeE.) Here is the strategy:
@@ -1545,8 +1545,8 @@ pushAtom d p e
pushAtom _ _ (AnnCoercion {}) -- Coercions are zero-width things,
= return (nilOL, 0) -- treated just like a variable V
--- See Note [Empty case alternatives] in coreSyn/CoreSyn.hs
--- and Note [Bottoming expressions] in coreSyn/CoreUtils.hs:
+-- See Note [Empty case alternatives] in GHC.Core
+-- and Note [Bottoming expressions] in GHC.Core.Utils:
-- The scrutinee of an empty case evaluates to bottom
pushAtom d p (AnnCase (_, a) _ _ []) -- trac #12128
= pushAtom d p a
@@ -1922,7 +1922,7 @@ atomPrimRep (AnnLit l) = typePrimRep1 (literalType l)
-- #12128:
-- A case expression can be an atom because empty cases evaluate to bottom.
--- See Note [Empty case alternatives] in coreSyn/CoreSyn.hs
+-- See Note [Empty case alternatives] in GHC.Core
atomPrimRep (AnnCase _ _ ty _) =
ASSERT(case typePrimRep ty of [LiftedRep] -> True; _ -> False) LiftedRep
atomPrimRep (AnnCoercion {}) = VoidRep
diff --git a/compiler/GHC/CoreToIface.hs b/compiler/GHC/CoreToIface.hs
index 277656d134..370a569d98 100644
--- a/compiler/GHC/CoreToIface.hs
+++ b/compiler/GHC/CoreToIface.hs
@@ -51,7 +51,7 @@ import GHC.Iface.Syntax
import DataCon
import Id
import IdInfo
-import CoreSyn
+import GHC.Core
import TyCon hiding ( pprPromotionQuote )
import CoAxiom
import TysPrim ( eqPrimTyCon, eqReprPrimTyCon )
@@ -422,7 +422,7 @@ toIfaceLetBndr id = IfLetBndr (occNameFS (getOccName id))
(toIfaceType (idType id))
(toIfaceIdInfo (idInfo id))
(toIfaceJoinInfo (isJoinId_maybe id))
- -- Put into the interface file any IdInfo that CoreTidy.tidyLetBndr
+ -- Put into the interface file any IdInfo that GHC.Core.Op.Tidy.tidyLetBndr
-- has left on the Id. See Note [IdInfo on nested let-bindings] in GHC.Iface.Syntax
toIfaceIdDetails :: IdDetails -> IfaceIdDetails
diff --git a/compiler/GHC/CoreToStg.hs b/compiler/GHC/CoreToStg.hs
index a450f342b0..bfda490b85 100644
--- a/compiler/GHC/CoreToStg.hs
+++ b/compiler/GHC/CoreToStg.hs
@@ -17,10 +17,10 @@ module GHC.CoreToStg ( coreToStg ) where
import GhcPrelude
-import CoreSyn
-import CoreUtils ( exprType, findDefault, isJoinBind
+import GHC.Core
+import GHC.Core.Utils ( exprType, findDefault, isJoinBind
, exprIsTickedString_maybe )
-import CoreArity ( manifestArity )
+import GHC.Core.Arity ( manifestArity )
import GHC.Stg.Syntax
import Type
@@ -271,7 +271,7 @@ coreTopBindToStg
coreTopBindToStg _ _ env ccs (NonRec id e)
| Just str <- exprIsTickedString_maybe e
-- top-level string literal
- -- See Note [CoreSyn top-level string literals] in CoreSyn
+ -- See Note [Core top-level string literals] in GHC.Core
= let
env' = extendVarEnv env id how_bound
how_bound = LetBound TopLet 0
@@ -417,7 +417,7 @@ coreToStgExpr (Cast expr _)
coreToStgExpr (Case scrut _ _ [])
= coreToStgExpr scrut
- -- See Note [Empty case alternatives] in CoreSyn If the case
+ -- See Note [Empty case alternatives] in GHC.Core If the case
-- alternatives are empty, the scrutinee must diverge or raise an
-- exception, so we can just dive into it.
--
diff --git a/compiler/GHC/CoreToStg/Prep.hs b/compiler/GHC/CoreToStg/Prep.hs
index 300c95f6df..3e7e5f3f55 100644
--- a/compiler/GHC/CoreToStg/Prep.hs
+++ b/compiler/GHC/CoreToStg/Prep.hs
@@ -24,13 +24,13 @@ import OccurAnal
import GHC.Driver.Types
import PrelNames
import MkId ( realWorldPrimId )
-import CoreUtils
-import CoreArity
-import CoreFVs
+import GHC.Core.Utils
+import GHC.Core.Arity
+import GHC.Core.FVs
import CoreMonad ( CoreToDo(..) )
-import CoreLint ( endPassIO )
-import CoreSyn
-import MkCore hiding( FloatBind(..) ) -- We use our own FloatBind here
+import GHC.Core.Lint ( endPassIO )
+import GHC.Core
+import GHC.Core.Make hiding( FloatBind(..) ) -- We use our own FloatBind here
import Type
import Literal
import Coercion
@@ -1094,7 +1094,7 @@ maybeSaturate fn expr n_args
{-
************************************************************************
* *
- Simple CoreSyn operations
+ Simple GHC.Core operations
* *
************************************************************************
-}
@@ -1137,7 +1137,7 @@ After ANFing we get
and now we do NOT want eta expansion to give
f = /\a -> \ y -> (let s = h 3 in g s) y
-Instead CoreArity.etaExpand gives
+Instead GHC.Core.Arity.etaExpand gives
f = /\a -> \y -> let s = h 3 in g s y
-}
@@ -1161,7 +1161,7 @@ get to a partial application:
-}
-- When updating this function, make sure it lines up with
--- CoreUtils.tryEtaReduce!
+-- GHC.Core.Utils.tryEtaReduce!
tryEtaReducePrep :: [CoreBndr] -> CoreExpr -> Maybe CoreExpr
tryEtaReducePrep bndrs expr@(App _ _)
| ok_to_eta_reduce f
@@ -1564,7 +1564,7 @@ cpCloneBndr env bndr
-- Drop (now-useless) rules/unfoldings
-- See Note [Drop unfoldings and rules]
- -- and Note [Preserve evaluatedness] in CoreTidy
+ -- and Note [Preserve evaluatedness] in GHC.Core.Op.Tidy
; let unfolding' = zapUnfolding (realIdUnfolding bndr)
-- Simplifier will set the Id's unfolding
@@ -1597,7 +1597,7 @@ We want to drop the unfolding/rules on every Id:
we'd have to substitute in them
HOWEVER, we want to preserve evaluated-ness;
-see Note [Preserve evaluatedness] in CoreTidy.
+see Note [Preserve evaluatedness] in GHC.Core.Op.Tidy.
-}
------------------------------------------------------------------------------
diff --git a/compiler/GHC/Driver/Hooks.hs b/compiler/GHC/Driver/Hooks.hs
index 027d8831b7..81552a46f6 100644
--- a/compiler/GHC/Driver/Hooks.hs
+++ b/compiler/GHC/Driver/Hooks.hs
@@ -42,7 +42,7 @@ import Bag
import RdrName
import Name
import Id
-import CoreSyn
+import GHC.Core
import GHCi.RemoteTypes
import SrcLoc
import Type
diff --git a/compiler/GHC/Driver/Main.hs b/compiler/GHC/Driver/Main.hs
index e5c030f741..0e4c5addb9 100644
--- a/compiler/GHC/Driver/Main.hs
+++ b/compiler/GHC/Driver/Main.hs
@@ -90,14 +90,13 @@ import Data.Data hiding (Fixity, TyCon)
import Data.Maybe ( fromJust )
import Id
import GHC.Runtime.Interpreter ( addSptEntry )
-import GHCi.RemoteTypes ( ForeignHValue )
-import GHC.CoreToByteCode ( byteCodeGen, coreExprToBCOs )
+import GHCi.RemoteTypes ( ForeignHValue )
+import GHC.CoreToByteCode ( byteCodeGen, coreExprToBCOs )
import GHC.Runtime.Linker
-import CoreTidy ( tidyExpr )
-import Type ( Type )
-import {- Kind parts of -} Type ( Kind )
-import CoreLint ( lintInteractiveExpr )
-import VarEnv ( emptyTidyEnv )
+import GHC.Core.Op.Tidy ( tidyExpr )
+import Type ( Type, Kind )
+import GHC.Core.Lint ( lintInteractiveExpr )
+import VarEnv ( emptyTidyEnv )
import Panic
import ConLike
import Control.Concurrent
@@ -108,7 +107,7 @@ import GHC.Driver.Packages
import RdrName
import GHC.Hs
import GHC.Hs.Dump
-import CoreSyn
+import GHC.Core
import StringBuffer
import Parser
import Lexer
diff --git a/compiler/GHC/Driver/Session.hs b/compiler/GHC/Driver/Session.hs
index f20a899086..7bad61c93d 100644
--- a/compiler/GHC/Driver/Session.hs
+++ b/compiler/GHC/Driver/Session.hs
@@ -1211,7 +1211,7 @@ data DynFlags = DynFlags {
extensionFlags :: EnumSet LangExt.Extension,
-- Unfolding control
- -- See Note [Discounts and thresholds] in CoreUnfold
+ -- See Note [Discounts and thresholds] in GHC.Core.Unfold
ufCreationThreshold :: Int,
ufUseThreshold :: Int,
ufFunAppDiscount :: Int,
diff --git a/compiler/GHC/Driver/Types.hs b/compiler/GHC/Driver/Types.hs
index 7fd8fe73c3..9e7b175a1c 100644
--- a/compiler/GHC/Driver/Types.hs
+++ b/compiler/GHC/Driver/Types.hs
@@ -168,7 +168,7 @@ import Avail
import Module
import InstEnv ( InstEnv, ClsInst, identicalClsInstHead )
import FamInstEnv
-import CoreSyn ( CoreProgram, RuleBase, CoreRule )
+import GHC.Core ( CoreProgram, RuleBase, CoreRule )
import Name
import NameEnv
import VarSet
@@ -1409,7 +1409,7 @@ data ModGuts
-- ^ Family instances declared in this module
mg_patsyns :: ![PatSyn], -- ^ Pattern synonyms declared in this module
mg_rules :: ![CoreRule], -- ^ Before the core pipeline starts, contains
- -- See Note [Overall plumbing for rules] in Rules.hs
+ -- See Note [Overall plumbing for rules] in GHC.Core.Rules
mg_binds :: !CoreProgram, -- ^ Bindings for this module
mg_foreign :: !ForeignStubs, -- ^ Foreign exports declared in this module
mg_foreign_files :: ![(ForeignSrcLang, FilePath)],
diff --git a/compiler/GHC/Hs/Binds.hs b/compiler/GHC/Hs/Binds.hs
index 483a952e62..6fabd4e748 100644
--- a/compiler/GHC/Hs/Binds.hs
+++ b/compiler/GHC/Hs/Binds.hs
@@ -32,7 +32,7 @@ import {-# SOURCE #-} GHC.Hs.Pat ( LPat )
import GHC.Hs.Extension
import GHC.Hs.Types
-import CoreSyn
+import GHC.Core
import TcEvidence
import Type
import NameSet
diff --git a/compiler/GHC/Hs/Expr.hs b/compiler/GHC/Hs/Expr.hs
index f6f0541097..1f51dccf3d 100644
--- a/compiler/GHC/Hs/Expr.hs
+++ b/compiler/GHC/Hs/Expr.hs
@@ -37,7 +37,7 @@ import GHC.Hs.Binds
-- others:
import TcEvidence
-import CoreSyn
+import GHC.Core
import Name
import NameSet
import BasicTypes
diff --git a/compiler/GHC/Hs/Pat.hs b/compiler/GHC/Hs/Pat.hs
index 3e78ec4fb9..76735b2f97 100644
--- a/compiler/GHC/Hs/Pat.hs
+++ b/compiler/GHC/Hs/Pat.hs
@@ -57,7 +57,7 @@ import GHC.Hs.Types
import TcEvidence
import BasicTypes
-- others:
-import PprCore ( {- instance OutputableBndr TyVar -} )
+import GHC.Core.Ppr ( {- instance OutputableBndr TyVar -} )
import TysWiredIn
import Var
import RdrName ( RdrName )
diff --git a/compiler/GHC/HsToCore.hs b/compiler/GHC/HsToCore.hs
index ec888766a7..7b4659edba 100644
--- a/compiler/GHC/HsToCore.hs
+++ b/compiler/GHC/HsToCore.hs
@@ -33,12 +33,12 @@ import Name
import Type
import TyCon ( tyConDataCons )
import Avail
-import CoreSyn
-import CoreFVs ( exprsSomeFreeVarsList )
-import CoreOpt ( simpleOptPgm, simpleOptExpr )
-import CoreUtils
-import CoreUnfold
-import PprCore
+import GHC.Core
+import GHC.Core.FVs ( exprsSomeFreeVarsList )
+import GHC.Core.SimpleOpt ( simpleOptPgm, simpleOptExpr )
+import GHC.Core.Utils
+import GHC.Core.Unfold
+import GHC.Core.Ppr
import GHC.HsToCore.Monad
import GHC.HsToCore.Expr
import GHC.HsToCore.Binds
@@ -48,14 +48,14 @@ import TysPrim
import Coercion
import TysWiredIn
import DataCon ( dataConWrapId )
-import MkCore
+import GHC.Core.Make
import Module
import NameSet
import NameEnv
-import Rules
+import GHC.Core.Rules
import BasicTypes
import CoreMonad ( CoreToDo(..) )
-import CoreLint ( endPassIO )
+import GHC.Core.Lint ( endPassIO )
import VarSet
import FastString
import ErrUtils
@@ -511,7 +511,7 @@ For that we replace any forall'ed `c :: Coercible a b` value in a RULE by
corresponding `co :: a ~#R b` and wrap the LHS and the RHS in
`let c = MkCoercible co in ...`. This is later simplified to the desired form
by simpleOptExpr (for the LHS) resp. the simplifiers (for the RHS).
-See also Note [Getting the map/coerce RULE to work] in CoreOpt.
+See also Note [Getting the map/coerce RULE to work] in GHC.Core.SimpleOpt.
Note [Rules and inlining/other rules]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
diff --git a/compiler/GHC/HsToCore/Arrows.hs b/compiler/GHC/HsToCore/Arrows.hs
index 450c879b90..24a7f89fb1 100644
--- a/compiler/GHC/HsToCore/Arrows.hs
+++ b/compiler/GHC/HsToCore/Arrows.hs
@@ -39,10 +39,10 @@ import {-# SOURCE #-} GHC.HsToCore.Expr ( dsExpr, dsLExpr, dsLExprNoLP, dsLocalB
import TcType
import Type ( splitPiTy )
import TcEvidence
-import CoreSyn
-import CoreFVs
-import CoreUtils
-import MkCore
+import GHC.Core
+import GHC.Core.FVs
+import GHC.Core.Utils
+import GHC.Core.Make
import GHC.HsToCore.Binds (dsHsWrapper)
import Id
diff --git a/compiler/GHC/HsToCore/Binds.hs b/compiler/GHC/HsToCore/Binds.hs
index 124427578d..86d309c73d 100644
--- a/compiler/GHC/HsToCore/Binds.hs
+++ b/compiler/GHC/HsToCore/Binds.hs
@@ -35,15 +35,15 @@ import GHC.HsToCore.GuardedRHSs
import GHC.HsToCore.Utils
import GHC.HsToCore.PmCheck ( needToRunPmCheck, addTyCsDs, checkGuardMatches )
-import GHC.Hs -- lots of things
-import CoreSyn -- lots of things
-import CoreOpt ( simpleOptExpr )
-import OccurAnal ( occurAnalyseExpr )
-import MkCore
-import CoreUtils
-import CoreArity ( etaExpand )
-import CoreUnfold
-import CoreFVs
+import GHC.Hs -- lots of things
+import GHC.Core -- lots of things
+import GHC.Core.SimpleOpt ( simpleOptExpr )
+import OccurAnal ( occurAnalyseExpr )
+import GHC.Core.Make
+import GHC.Core.Utils
+import GHC.Core.Arity ( etaExpand )
+import GHC.Core.Unfold
+import GHC.Core.FVs
import Digraph
import Predicate
@@ -58,7 +58,7 @@ import Id
import MkId(proxyHashId)
import Name
import VarSet
-import Rules
+import GHC.Core.Rules
import VarEnv
import Var( EvVar )
import Outputable
@@ -1160,7 +1160,7 @@ dsEvBinds bs
mk_ev_binds :: Bag (Id,CoreExpr) -> [CoreBind]
-- We do SCC analysis of the evidence bindings, /after/ desugaring
--- them. This is convenient: it means we can use the CoreSyn
+-- them. This is convenient: it means we can use the GHC.Core
-- free-variable functions rather than having to do accurate free vars
-- for EvTerm.
mk_ev_binds ds_binds
diff --git a/compiler/GHC/HsToCore/Binds.hs-boot b/compiler/GHC/HsToCore/Binds.hs-boot
index 36e158b279..aa3134ac72 100644
--- a/compiler/GHC/HsToCore/Binds.hs-boot
+++ b/compiler/GHC/HsToCore/Binds.hs-boot
@@ -1,6 +1,6 @@
module GHC.HsToCore.Binds where
import GHC.HsToCore.Monad ( DsM )
-import CoreSyn ( CoreExpr )
-import TcEvidence (HsWrapper)
+import GHC.Core ( CoreExpr )
+import TcEvidence (HsWrapper)
dsHsWrapper :: HsWrapper -> DsM (CoreExpr -> CoreExpr)
diff --git a/compiler/GHC/HsToCore/Coverage.hs b/compiler/GHC/HsToCore/Coverage.hs
index b93f04b3fa..960b2840fa 100644
--- a/compiler/GHC/HsToCore/Coverage.hs
+++ b/compiler/GHC/HsToCore/Coverage.hs
@@ -33,7 +33,7 @@ import Name
import Bag
import CostCentre
import CostCentreState
-import CoreSyn
+import GHC.Core
import Id
import VarSet
import Data.List
diff --git a/compiler/GHC/HsToCore/Expr.hs b/compiler/GHC/HsToCore/Expr.hs
index b627d6e841..53922768b6 100644
--- a/compiler/GHC/HsToCore/Expr.hs
+++ b/compiler/GHC/HsToCore/Expr.hs
@@ -45,9 +45,9 @@ import TcType
import TcEvidence
import TcRnMonad
import Type
-import CoreSyn
-import CoreUtils
-import MkCore
+import GHC.Core
+import GHC.Core.Utils
+import GHC.Core.Make
import GHC.Driver.Session
import CostCentre
@@ -251,7 +251,7 @@ dsLExpr (L loc e)
-- polymorphic. This should be used when the resulting expression will
-- be an argument to some other function.
-- See Note [Levity polymorphism checking] in GHC.HsToCore.Monad
--- See Note [Levity polymorphism invariants] in CoreSyn
+-- See Note [Levity polymorphism invariants] in GHC.Core
dsLExprNoLP :: LHsExpr GhcTc -> DsM CoreExpr
dsLExprNoLP (L loc e)
= putSrcSpanDs loc $
@@ -401,7 +401,7 @@ dsExpr (ExplicitTuple _ tup_args boxity)
-- The reverse is because foldM goes left-to-right
(\(lam_vars, args) -> mkCoreLams lam_vars $
mkCoreTupBoxity boxity args) }
- -- See Note [Don't flatten tuples from HsSyn] in MkCore
+ -- See Note [Don't flatten tuples from HsSyn] in GHC.Core.Make
dsExpr (ExplicitSum types alt arity expr)
= do { dsWhenNoErrs (dsLExprNoLP expr)
@@ -1112,7 +1112,7 @@ badMonadBind rhs elt_ty
Note [Detecting forced eta expansion]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
We cannot have levity polymorphic function arguments. See
-Note [Levity polymorphism invariants] in CoreSyn. But we *can* have
+Note [Levity polymorphism invariants] in GHC.Core. But we *can* have
functions that take levity polymorphic arguments, as long as these
functions are eta-reduced. (See #12708 for an example.)
diff --git a/compiler/GHC/HsToCore/Expr.hs-boot b/compiler/GHC/HsToCore/Expr.hs-boot
index b717c1bee8..e742ac5156 100644
--- a/compiler/GHC/HsToCore/Expr.hs-boot
+++ b/compiler/GHC/HsToCore/Expr.hs-boot
@@ -1,7 +1,7 @@
module GHC.HsToCore.Expr where
import GHC.Hs ( HsExpr, LHsExpr, LHsLocalBinds, LPat, SyntaxExpr )
import GHC.HsToCore.Monad ( DsM, MatchResult )
-import CoreSyn ( CoreExpr )
+import GHC.Core ( CoreExpr )
import GHC.Hs.Extension ( GhcTc)
dsExpr :: HsExpr GhcTc -> DsM CoreExpr
diff --git a/compiler/GHC/HsToCore/Foreign/Call.hs b/compiler/GHC/HsToCore/Foreign/Call.hs
index bebb677772..72b3d996f0 100644
--- a/compiler/GHC/HsToCore/Foreign/Call.hs
+++ b/compiler/GHC/HsToCore/Foreign/Call.hs
@@ -24,11 +24,11 @@ where
import GhcPrelude
-import CoreSyn
+import GHC.Core
import GHC.HsToCore.Monad
-import CoreUtils
-import MkCore
+import GHC.Core.Utils
+import GHC.Core.Make
import MkId
import ForeignCall
import DataCon
diff --git a/compiler/GHC/HsToCore/Foreign/Decl.hs b/compiler/GHC/HsToCore/Foreign/Decl.hs
index dc569bdbfa..686380ee39 100644
--- a/compiler/GHC/HsToCore/Foreign/Decl.hs
+++ b/compiler/GHC/HsToCore/Foreign/Decl.hs
@@ -20,14 +20,14 @@ import GhcPrelude
import TcRnMonad -- temp
-import CoreSyn
+import GHC.Core
import GHC.HsToCore.Foreign.Call
import GHC.HsToCore.Monad
import GHC.Hs
import DataCon
-import CoreUnfold
+import GHC.Core.Unfold
import Id
import Literal
import Module
diff --git a/compiler/GHC/HsToCore/GuardedRHSs.hs b/compiler/GHC/HsToCore/GuardedRHSs.hs
index 37a7cd591b..ef055b0caa 100644
--- a/compiler/GHC/HsToCore/GuardedRHSs.hs
+++ b/compiler/GHC/HsToCore/GuardedRHSs.hs
@@ -19,9 +19,9 @@ import {-# SOURCE #-} GHC.HsToCore.Expr ( dsLExpr, dsLocalBinds )
import {-# SOURCE #-} GHC.HsToCore.Match ( matchSinglePatVar )
import GHC.Hs
-import MkCore
-import CoreSyn
-import CoreUtils (bindNonRec)
+import GHC.Core.Make
+import GHC.Core
+import GHC.Core.Utils (bindNonRec)
import BasicTypes (Origin(FromSource))
import GHC.Driver.Session
diff --git a/compiler/GHC/HsToCore/ListComp.hs b/compiler/GHC/HsToCore/ListComp.hs
index 0411542d78..6c58be3a47 100644
--- a/compiler/GHC/HsToCore/ListComp.hs
+++ b/compiler/GHC/HsToCore/ListComp.hs
@@ -20,14 +20,14 @@ import {-# SOURCE #-} GHC.HsToCore.Expr ( dsHandleMonadicFailure, dsExpr, dsLExp
import GHC.Hs
import TcHsSyn
-import CoreSyn
-import MkCore
+import GHC.Core
+import GHC.Core.Make
import GHC.HsToCore.Monad -- the monadery used in the desugarer
import GHC.HsToCore.Utils
import GHC.Driver.Session
-import CoreUtils
+import GHC.Core.Utils
import Id
import Type
import TysWiredIn
diff --git a/compiler/GHC/HsToCore/Match.hs b/compiler/GHC/HsToCore/Match.hs
index 0542fd5e7e..bb7134b428 100644
--- a/compiler/GHC/HsToCore/Match.hs
+++ b/compiler/GHC/HsToCore/Match.hs
@@ -34,10 +34,10 @@ import TcHsSyn
import TcEvidence
import TcRnMonad
import GHC.HsToCore.PmCheck
-import CoreSyn
+import GHC.Core
import Literal
-import CoreUtils
-import MkCore
+import GHC.Core.Utils
+import GHC.Core.Make
import GHC.HsToCore.Monad
import GHC.HsToCore.Binds
import GHC.HsToCore.GuardedRHSs
@@ -331,7 +331,7 @@ In that situation we desugar to
The *desugarer* isn't certain whether there really should be no
alternatives, so it adds a default case, as it always does. A later
pass may remove it if it's inaccessible. (See also Note [Empty case
-alternatives] in CoreSyn.)
+alternatives] in GHC.Core.)
We do *not* desugar simply to
error "empty case"
diff --git a/compiler/GHC/HsToCore/Match.hs-boot b/compiler/GHC/HsToCore/Match.hs-boot
index dbed65dd0d..6dd7729935 100644
--- a/compiler/GHC/HsToCore/Match.hs-boot
+++ b/compiler/GHC/HsToCore/Match.hs-boot
@@ -4,7 +4,7 @@ import GhcPrelude
import Var ( Id )
import TcType ( Type )
import GHC.HsToCore.Monad ( DsM, EquationInfo, MatchResult )
-import CoreSyn ( CoreExpr )
+import GHC.Core ( CoreExpr )
import GHC.Hs ( LPat, HsMatchContext, MatchGroup, LHsExpr )
import GHC.Hs.Extension ( GhcRn, GhcTc )
diff --git a/compiler/GHC/HsToCore/Match/Constructor.hs b/compiler/GHC/HsToCore/Match/Constructor.hs
index 37a9f753a6..ab662a2f0e 100644
--- a/compiler/GHC/HsToCore/Match/Constructor.hs
+++ b/compiler/GHC/HsToCore/Match/Constructor.hs
@@ -27,7 +27,7 @@ import BasicTypes ( Origin(..) )
import TcType
import GHC.HsToCore.Monad
import GHC.HsToCore.Utils
-import MkCore ( mkCoreLets )
+import GHC.Core.Make ( mkCoreLets )
import Util
import Id
import NameEnv
diff --git a/compiler/GHC/HsToCore/Match/Literal.hs b/compiler/GHC/HsToCore/Match/Literal.hs
index 2fdb1a3dd5..6c3a2d7a7e 100644
--- a/compiler/GHC/HsToCore/Match/Literal.hs
+++ b/compiler/GHC/HsToCore/Match/Literal.hs
@@ -34,8 +34,8 @@ import GHC.HsToCore.Utils
import GHC.Hs
import Id
-import CoreSyn
-import MkCore
+import GHC.Core
+import GHC.Core.Make
import TyCon
import DataCon
import TcHsSyn ( shortCutLit )
diff --git a/compiler/GHC/HsToCore/Monad.hs b/compiler/GHC/HsToCore/Monad.hs
index b13a7f3304..6c4e2f61d5 100644
--- a/compiler/GHC/HsToCore/Monad.hs
+++ b/compiler/GHC/HsToCore/Monad.hs
@@ -56,9 +56,9 @@ import GhcPrelude
import TcRnMonad
import FamInstEnv
-import CoreSyn
-import MkCore ( unitExpr )
-import CoreUtils ( exprType, isExprLevPoly )
+import GHC.Core
+import GHC.Core.Make ( unitExpr )
+import GHC.Core.Utils ( exprType, isExprLevPoly )
import GHC.Hs
import GHC.IfaceToCore
import TcMType ( checkForLevPolyX, formatLevPolyErr )
diff --git a/compiler/GHC/HsToCore/PmCheck.hs b/compiler/GHC/HsToCore/PmCheck.hs
index 2a7d70abd2..78672a6443 100644
--- a/compiler/GHC/HsToCore/PmCheck.hs
+++ b/compiler/GHC/HsToCore/PmCheck.hs
@@ -28,7 +28,7 @@ import GHC.HsToCore.PmCheck.Types
import GHC.HsToCore.PmCheck.Oracle
import GHC.HsToCore.PmCheck.Ppr
import BasicTypes (Origin, isGenerated)
-import CoreSyn (CoreExpr, Expr(Var,App))
+import GHC.Core (CoreExpr, Expr(Var,App))
import FastString (unpackFS, lengthFS)
import GHC.Driver.Session
import GHC.Hs
diff --git a/compiler/GHC/HsToCore/PmCheck/Oracle.hs b/compiler/GHC/HsToCore/PmCheck/Oracle.hs
index c0722249d8..f538b82a13 100644
--- a/compiler/GHC/HsToCore/PmCheck/Oracle.hs
+++ b/compiler/GHC/HsToCore/PmCheck/Oracle.hs
@@ -42,12 +42,12 @@ import VarEnv
import UniqDFM
import Var (EvVar)
import Name
-import CoreSyn
-import CoreFVs ( exprFreeVars )
-import CoreMap
-import CoreOpt (simpleOptExpr, exprIsConApp_maybe)
-import CoreUtils (exprType)
-import MkCore (mkListExpr, mkCharExpr)
+import GHC.Core
+import GHC.Core.FVs (exprFreeVars)
+import GHC.Core.Map
+import GHC.Core.SimpleOpt (simpleOptExpr, exprIsConApp_maybe)
+import GHC.Core.Utils (exprType)
+import GHC.Core.Make (mkListExpr, mkCharExpr)
import UniqSupply
import FastString
import SrcLoc
diff --git a/compiler/GHC/HsToCore/PmCheck/Types.hs b/compiler/GHC/HsToCore/PmCheck/Types.hs
index 26e6ffc67e..4f3456908f 100644
--- a/compiler/GHC/HsToCore/PmCheck/Types.hs
+++ b/compiler/GHC/HsToCore/PmCheck/Types.hs
@@ -52,9 +52,9 @@ import Maybes
import Type
import TyCon
import Literal
-import CoreSyn
-import CoreMap
-import CoreUtils (exprType)
+import GHC.Core
+import GHC.Core.Map
+import GHC.Core.Utils (exprType)
import PrelNames
import TysWiredIn
import TysPrim
@@ -146,7 +146,7 @@ eqConLike (PatSynCon psc1) (PatSynCon psc2)
eqConLike _ _ = PossiblyOverlap
-- | Represents the head of a match against a 'ConLike' or literal.
--- Really similar to 'CoreSyn.AltCon'.
+-- Really similar to 'GHC.Core.AltCon'.
data PmAltCon = PmAltConLike ConLike
| PmAltLit PmLit
diff --git a/compiler/GHC/HsToCore/Quote.hs b/compiler/GHC/HsToCore/Quote.hs
index d6525f83f2..fe06404b22 100644
--- a/compiler/GHC/HsToCore/Quote.hs
+++ b/compiler/GHC/HsToCore/Quote.hs
@@ -51,9 +51,9 @@ import NameEnv
import TcType
import TyCon
import TysWiredIn
-import CoreSyn
-import MkCore
-import CoreUtils
+import GHC.Core
+import GHC.Core.Make
+import GHC.Core.Utils
import SrcLoc
import Unique
import BasicTypes
diff --git a/compiler/GHC/HsToCore/Utils.hs b/compiler/GHC/HsToCore/Utils.hs
index 953225e912..d11e59a0c8 100644
--- a/compiler/GHC/HsToCore/Utils.hs
+++ b/compiler/GHC/HsToCore/Utils.hs
@@ -52,11 +52,11 @@ import {-# SOURCE #-} GHC.HsToCore.Expr ( dsLExpr )
import GHC.Hs
import TcHsSyn
import TcType( tcSplitTyConApp )
-import CoreSyn
+import GHC.Core
import GHC.HsToCore.Monad
-import CoreUtils
-import MkCore
+import GHC.Core.Utils
+import GHC.Core.Make
import MkId
import Id
import Literal
@@ -168,7 +168,7 @@ will propagate that Name to all the occurrence sites, as well as
un-shadowing it, so we'll get
M.a{r8} = case e of (v:_) ->
case v of Just a{s77} -> a{s77}
-In fact, even CoreSubst.simplOptExpr will do this, and simpleOptExpr
+In fact, even GHC.Core.Subst.simplOptExpr will do this, and simpleOptExpr
runs on the output of the desugarer, so all is well by the end of
the desugaring pass.
@@ -418,7 +418,7 @@ There are a few subtleties in the desugaring of `seq`:
Consider,
f x y = x `seq` (y `seq` (# x,y #))
- The [CoreSyn let/app invariant] means that, other things being equal, because
+ The [Core let/app invariant] means that, other things being equal, because
the argument to the outer 'seq' has an unlifted type, we'll use call-by-value thus:
f x y = case (y `seq` (# x,y #)) of v -> x `seq` v
@@ -490,21 +490,21 @@ mkCoreAppDs _ (Var f `App` Type _r `App` Type ty1 `App` Type ty2 `App` arg1) arg
-> v1 -- Note [Desugaring seq], points (2) and (3)
_ -> mkWildValBinder ty1
-mkCoreAppDs s fun arg = mkCoreApp s fun arg -- The rest is done in MkCore
+mkCoreAppDs s fun arg = mkCoreApp s fun arg -- The rest is done in GHC.Core.Make
-- NB: No argument can be levity polymorphic
mkCoreAppsDs :: SDoc -> CoreExpr -> [CoreExpr] -> CoreExpr
mkCoreAppsDs s fun args = foldl' (mkCoreAppDs s) fun args
mkCastDs :: CoreExpr -> Coercion -> CoreExpr
--- We define a desugarer-specific version of CoreUtils.mkCast,
+-- We define a desugarer-specific version of GHC.Core.Utils.mkCast,
-- because in the immediate output of the desugarer, we can have
-- apparently-mis-matched coercions: E.g.
-- let a = b
-- in (x :: a) |> (co :: b ~ Int)
-- Lint know about type-bindings for let and does not complain
-- So here we do not make the assertion checks that we make in
--- CoreUtils.mkCast; and we do less peephole optimisation too
+-- GHC.Core.Utils.mkCast; and we do less peephole optimisation too
mkCastDs e co | isReflCo co = e
| otherwise = Cast e co
diff --git a/compiler/GHC/Iface/Ext/Ast.hs b/compiler/GHC/Iface/Ext/Ast.hs
index edeeaf651e..d6386357ca 100644
--- a/compiler/GHC/Iface/Ext/Ast.hs
+++ b/compiler/GHC/Iface/Ext/Ast.hs
@@ -23,7 +23,7 @@ import Bag ( Bag, bagToList )
import BasicTypes
import BooleanFormula
import Class ( FunDep )
-import CoreUtils ( exprType )
+import GHC.Core.Utils ( exprType )
import ConLike ( conLikeName )
import GHC.HsToCore ( deSugarExpr )
import FieldLabel
diff --git a/compiler/GHC/Iface/Ext/Utils.hs b/compiler/GHC/Iface/Ext/Utils.hs
index 007634bae6..1e0a241384 100644
--- a/compiler/GHC/Iface/Ext/Utils.hs
+++ b/compiler/GHC/Iface/Ext/Utils.hs
@@ -6,8 +6,8 @@ module GHC.Iface.Ext.Utils where
import GhcPrelude
-import CoreMap
-import GHC.Driver.Session ( DynFlags )
+import GHC.Core.Map
+import GHC.Driver.Session ( DynFlags )
import FastString ( FastString, mkFastString )
import GHC.Iface.Type
import Name hiding (varName)
diff --git a/compiler/GHC/Iface/Load.hs b/compiler/GHC/Iface/Load.hs
index cde0e8c9e2..c812968b0a 100644
--- a/compiler/GHC/Iface/Load.hs
+++ b/compiler/GHC/Iface/Load.hs
@@ -54,7 +54,7 @@ import PrelInfo
import PrimOp ( allThePrimOps, primOpFixity, primOpOcc )
import MkId ( seqId )
import TysPrim ( funTyConName )
-import Rules
+import GHC.Core.Rules
import TyCon
import Annotations
import InstEnv
diff --git a/compiler/GHC/Iface/Syntax.hs b/compiler/GHC/Iface/Syntax.hs
index cea861de27..5067204b8b 100644
--- a/compiler/GHC/Iface/Syntax.hs
+++ b/compiler/GHC/Iface/Syntax.hs
@@ -46,7 +46,7 @@ import GhcPrelude
import GHC.Iface.Type
import BinFingerprint
-import CoreSyn( IsOrphan, isOrphan )
+import GHC.Core( IsOrphan, isOrphan )
import Demand
import Cpr
import Class
@@ -188,7 +188,7 @@ data IfaceTyConParent
| IfDataInstance
IfExtName -- Axiom name
IfaceTyCon -- Family TyCon (pretty-printing only, not used in GHC.IfaceToCore)
- -- see Note [Pretty printing via Iface syntax] in PprTyThing
+ -- see Note [Pretty printing via Iface syntax] in GHC.Core.Ppr.TyThing
IfaceAppArgs -- Arguments of the family TyCon
data IfaceFamTyConFlav
@@ -197,7 +197,7 @@ data IfaceFamTyConFlav
| IfaceClosedSynFamilyTyCon (Maybe (IfExtName, [IfaceAxBranch]))
-- ^ Name of associated axiom and branches for pretty printing purposes,
-- or 'Nothing' for an empty closed family without an axiom
- -- See Note [Pretty printing via Iface syntax] in PprTyThing
+ -- See Note [Pretty printing via Iface syntax] in GHC.Core.Ppr.TyThing
| IfaceAbstractClosedSynFamilyTyCon
| IfaceBuiltInSynFamTyCon -- for pretty printing purposes only
@@ -533,7 +533,7 @@ Note [Empty case alternatives]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
In Iface syntax an IfaceCase does not record the types of the alternatives,
unlike Core syntax Case. But we need this type if the alternatives are empty.
-Hence IfaceECase. See Note [Empty case alternatives] in CoreSyn.
+Hence IfaceECase. See Note [Empty case alternatives] in GHC.Core.
Note [Expose recursive functions]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
@@ -549,7 +549,7 @@ that came up was a NOINLINE pragma on a let-binding inside an INLINE
function. The user (Duncan Coutts) really wanted the NOINLINE control
to cross the separate compilation boundary.
-In general we retain all info that is left by CoreTidy.tidyLetBndr, since
+In general we retain all info that is left by GHC.Core.Op.Tidy.tidyLetBndr, since
that is what is seen by importing module with --make
Note [Displaying axiom incompatibilities]
@@ -676,7 +676,7 @@ Note [Printing IfaceDecl binders]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
The binders in an IfaceDecl are just OccNames, so we don't know what module they
come from. But when we pretty-print a TyThing by converting to an IfaceDecl
-(see PprTyThing), the TyThing may come from some other module so we really need
+(see GHC.Core.Ppr.TyThing), the TyThing may come from some other module so we really need
the module qualifier. We solve this by passing in a pretty-printer for the
binders.
@@ -746,7 +746,7 @@ constraintIfaceKind =
pprIfaceDecl :: ShowSub -> IfaceDecl -> SDoc
-- NB: pprIfaceDecl is also used for pretty-printing TyThings in GHCi
--- See Note [Pretty-printing TyThings] in PprTyThing
+-- See Note [Pretty-printing TyThings] in GHC.Core.Ppr.TyThing
pprIfaceDecl ss (IfaceData { ifName = tycon, ifCType = ctype,
ifCtxt = context, ifResKind = kind,
ifRoles = roles, ifCons = condecls,
diff --git a/compiler/GHC/Iface/Tidy.hs b/compiler/GHC/Iface/Tidy.hs
index 49a5a29856..d764b92edb 100644
--- a/compiler/GHC/Iface/Tidy.hs
+++ b/compiler/GHC/Iface/Tidy.hs
@@ -18,18 +18,18 @@ import GhcPrelude
import TcRnTypes
import GHC.Driver.Session
-import CoreSyn
-import CoreUnfold
-import CoreFVs
-import CoreTidy
+import GHC.Core
+import GHC.Core.Unfold
+import GHC.Core.FVs
+import GHC.Core.Op.Tidy
import CoreMonad
-import CoreStats (coreBindsStats, CoreStats(..))
-import CoreSeq (seqBinds)
-import CoreLint
-import Rules
+import GHC.Core.Stats (coreBindsStats, CoreStats(..))
+import GHC.Core.Seq (seqBinds)
+import GHC.Core.Lint
+import GHC.Core.Rules
import PatSyn
import ConLike
-import CoreArity ( exprArity, exprBotStrictness_maybe )
+import GHC.Core.Arity ( exprArity, exprBotStrictness_maybe )
import StaticPtrTable
import VarEnv
import VarSet
@@ -505,14 +505,14 @@ of exceptions, and finally I gave up the battle:
Note [Injecting implicit bindings]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-We inject the implicit bindings right at the end, in CoreTidy.
+We inject the implicit bindings right at the end, in GHC.Core.Op.Tidy.
Some of these bindings, notably record selectors, are not
constructed in an optimised form. E.g. record selector for
data T = MkT { x :: {-# UNPACK #-} !Int }
Then the unfolding looks like
x = \t. case t of MkT x1 -> let x = I# x1 in x
This generates bad code unless it's first simplified a bit. That is
-why CoreUnfold.mkImplicitUnfolding uses simpleOptExpr to do a bit of
+why GHC.Core.Unfold.mkImplicitUnfolding uses simpleOptExpr to do a bit of
optimisation first. (Only matters when the selector is used curried;
eg map x ys.) See #2070.
@@ -1155,12 +1155,12 @@ tidyTopIdInfo dflags rhs_tidy_env name orig_rhs tidy_rhs idinfo show_unfold
| not is_external -- For internal Ids (not externally visible)
= vanillaIdInfo -- we only need enough info for code generation
-- Arity and strictness info are enough;
- -- c.f. CoreTidy.tidyLetBndr
+ -- c.f. GHC.Core.Op.Tidy.tidyLetBndr
`setArityInfo` arity
`setStrictnessInfo` final_sig
`setCprInfo` final_cpr
`setUnfoldingInfo` minimal_unfold_info -- See note [Preserve evaluatedness]
- -- in CoreTidy
+ -- in GHC.Core.Op.Tidy
| otherwise -- Externally-visible Ids get the whole lot
= vanillaIdInfo
diff --git a/compiler/GHC/Iface/Type.hs b/compiler/GHC/Iface/Type.hs
index 3c08262ed8..4f8c6571f7 100644
--- a/compiler/GHC/Iface/Type.hs
+++ b/compiler/GHC/Iface/Type.hs
@@ -137,7 +137,7 @@ type IfaceKind = IfaceType
-- | A kind of universal type, used for types and kinds.
--
-- Any time a 'Type' is pretty-printed, it is first converted to an 'IfaceType'
--- before being printed. See Note [Pretty printing via Iface syntax] in PprTyThing
+-- before being printed. See Note [Pretty printing via Iface syntax] in GHC.Core.Ppr.TyThing
data IfaceType
= IfaceFreeTyVar TyVar -- See Note [Free tyvars in IfaceType]
| IfaceTyVar IfLclName -- Type/coercion variable only, not tycon
@@ -248,7 +248,7 @@ instance Outputable IfaceTyConSort where
Nowadays (since Nov 16, 2016) we pretty-print a Type by converting to
an IfaceType and pretty printing that. This eliminates a lot of
pretty-print duplication, and it matches what we do with pretty-
-printing TyThings. See Note [Pretty printing via Iface syntax] in PprTyThing.
+printing TyThings. See Note [Pretty printing via Iface syntax] in GHC.Core.Ppr.TyThing.
It works fine for closed types, but when printing debug traces (e.g.
when using -ddump-tc-trace) we print a lot of /open/ types. These
diff --git a/compiler/GHC/Iface/Utils.hs b/compiler/GHC/Iface/Utils.hs
index 83f46bd774..927897edf8 100644
--- a/compiler/GHC/Iface/Utils.hs
+++ b/compiler/GHC/Iface/Utils.hs
@@ -71,7 +71,7 @@ import FlagChecker
import GHC.HsToCore.Usage ( mkUsageInfo, mkUsedNames, mkDependencies )
import Id
import Annotations
-import CoreSyn
+import GHC.Core
import Class
import TyCon
import CoAxiom
diff --git a/compiler/GHC/IfaceToCore.hs b/compiler/GHC/IfaceToCore.hs
index 589843e404..a6fa7408b2 100644
--- a/compiler/GHC/IfaceToCore.hs
+++ b/compiler/GHC/IfaceToCore.hs
@@ -42,11 +42,11 @@ import GHC.Driver.Types
import Annotations
import InstEnv
import FamInstEnv
-import CoreSyn
-import CoreUtils
-import CoreUnfold
-import CoreLint
-import MkCore
+import GHC.Core
+import GHC.Core.Utils
+import GHC.Core.Unfold
+import GHC.Core.Lint
+import GHC.Core.Make
import Id
import MkId
import IdInfo
@@ -1546,7 +1546,7 @@ an unfolding that isn't going to be looked at.
-}
tcPragExpr :: Bool -- Is this unfolding compulsory?
- -- See Note [Checking for levity polymorphism] in CoreLint
+ -- See Note [Checking for levity polymorphism] in GHC.Core.Lint
-> TopLevelFlag -> Name -> IfaceExpr -> IfL (Maybe CoreExpr)
tcPragExpr is_compulsory toplvl name expr
= forkM_maybe doc $ do
diff --git a/compiler/GHC/IfaceToCore.hs-boot b/compiler/GHC/IfaceToCore.hs-boot
index 521a32d93f..aea03c8d5d 100644
--- a/compiler/GHC/IfaceToCore.hs-boot
+++ b/compiler/GHC/IfaceToCore.hs-boot
@@ -1,16 +1,15 @@
module GHC.IfaceToCore where
import GhcPrelude
-import GHC.Iface.Syntax
- ( IfaceDecl, IfaceClsInst, IfaceFamInst, IfaceRule
- , IfaceAnnotation, IfaceCompleteMatch )
-import TyCoRep ( TyThing )
-import TcRnTypes ( IfL )
-import InstEnv ( ClsInst )
-import FamInstEnv ( FamInst )
-import CoreSyn ( CoreRule )
-import GHC.Driver.Types ( CompleteMatch )
-import Annotations ( Annotation )
+import GHC.Iface.Syntax ( IfaceDecl, IfaceClsInst, IfaceFamInst, IfaceRule
+ , IfaceAnnotation, IfaceCompleteMatch )
+import TyCoRep ( TyThing )
+import TcRnTypes ( IfL )
+import InstEnv ( ClsInst )
+import FamInstEnv ( FamInst )
+import GHC.Core ( CoreRule )
+import GHC.Driver.Types ( CompleteMatch )
+import Annotations ( Annotation )
tcIfaceDecl :: Bool -> IfaceDecl -> IfL TyThing
tcIfaceRules :: Bool -> [IfaceRule] -> IfL [CoreRule]
diff --git a/compiler/GHC/Plugins.hs b/compiler/GHC/Plugins.hs
index 6b3115bbcc..3de7a1b045 100644
--- a/compiler/GHC/Plugins.hs
+++ b/compiler/GHC/Plugins.hs
@@ -6,13 +6,13 @@
-- with saying "import GHC.Plugins".
--
-- Particularly interesting modules for plugin writers include
--- "CoreSyn" and "CoreMonad".
+-- "GHC.Core" and "CoreMonad".
module GHC.Plugins(
module GHC.Driver.Plugins,
module RdrName, module OccName, module Name, module Var, module Id, module IdInfo,
- module CoreMonad, module CoreSyn, module Literal, module DataCon,
- module CoreUtils, module MkCore, module CoreFVs, module CoreSubst,
- module Rules, module Annotations,
+ module CoreMonad, module GHC.Core, module Literal, module DataCon,
+ module GHC.Core.Utils, module GHC.Core.Make, module GHC.Core.FVs,
+ module GHC.Core.Subst, module GHC.Core.Rules, module Annotations,
module GHC.Driver.Session, module GHC.Driver.Packages,
module Module, module Type, module TyCon, module Coercion,
module TysWiredIn, module GHC.Driver.Types, module BasicTypes,
@@ -38,17 +38,17 @@ import IdInfo
-- Core
import CoreMonad
-import CoreSyn
+import GHC.Core
import Literal
import DataCon
-import CoreUtils
-import MkCore
-import CoreFVs
-import CoreSubst hiding( substTyVarBndr, substCoVarBndr, extendCvSubst )
+import GHC.Core.Utils
+import GHC.Core.Make
+import GHC.Core.FVs
+import GHC.Core.Subst hiding( substTyVarBndr, substCoVarBndr, extendCvSubst )
-- These names are also exported by Type
-- Core "extras"
-import Rules
+import GHC.Core.Rules
import Annotations
-- Pipeline-related stuff
@@ -57,9 +57,9 @@ import GHC.Driver.Packages
-- Important GHC types
import Module
-import Type hiding {- conflict with CoreSubst -}
+import Type hiding {- conflict with GHC.Core.Subst -}
( substTy, extendTvSubst, extendTvSubstList, isInScope )
-import Coercion hiding {- conflict with CoreSubst -}
+import Coercion hiding {- conflict with GHC.Core.Subst -}
( substCo )
import TyCon
import TysWiredIn
diff --git a/compiler/GHC/Runtime/Debugger.hs b/compiler/GHC/Runtime/Debugger.hs
index 177a83ea8b..0b2ce71122 100644
--- a/compiler/GHC/Runtime/Debugger.hs
+++ b/compiler/GHC/Runtime/Debugger.hs
@@ -33,7 +33,7 @@ import UniqSet
import Type
import GHC
import Outputable
-import PprTyThing
+import GHC.Core.Ppr.TyThing
import ErrUtils
import MonadUtils
import GHC.Driver.Session
diff --git a/compiler/GHC/Runtime/Eval.hs b/compiler/GHC/Runtime/Eval.hs
index c960b1c8c6..8890192d92 100644
--- a/compiler/GHC/Runtime/Eval.hs
+++ b/compiler/GHC/Runtime/Eval.hs
@@ -60,7 +60,7 @@ import GHC.Driver.Types
import InstEnv
import GHC.Iface.Env ( newInteractiveBinder )
import FamInstEnv ( FamInst )
-import CoreFVs ( orphNamesOfFamInst )
+import GHC.Core.FVs ( orphNamesOfFamInst )
import TyCon
import Type hiding( typeKind )
import GHC.Types.RepType
diff --git a/compiler/GHC/Stg/CSE.hs b/compiler/GHC/Stg/CSE.hs
index 66f5004b49..ec497a8a59 100644
--- a/compiler/GHC/Stg/CSE.hs
+++ b/compiler/GHC/Stg/CSE.hs
@@ -93,10 +93,10 @@ import Id
import GHC.Stg.Syntax
import Outputable
import VarEnv
-import CoreSyn (AltCon(..))
+import GHC.Core (AltCon(..))
import Data.List (mapAccumL)
import Data.Maybe (fromMaybe)
-import CoreMap
+import GHC.Core.Map
import NameEnv
import Control.Monad( (>=>) )
@@ -232,7 +232,7 @@ substVar env id = fromMaybe id $ lookupVarEnv (ce_subst env) id
-- Functions to enter binders
--- This is much simpler than the equivalent code in CoreSubst:
+-- This is much simpler than the equivalent code in GHC.Core.Subst:
-- * We do not substitute type variables, and
-- * There is nothing relevant in IdInfo at this stage
-- that needs substitutions.
diff --git a/compiler/GHC/Stg/FVs.hs b/compiler/GHC/Stg/FVs.hs
index f878124a18..6bd219d7a3 100644
--- a/compiler/GHC/Stg/FVs.hs
+++ b/compiler/GHC/Stg/FVs.hs
@@ -47,7 +47,7 @@ import GhcPrelude
import GHC.Stg.Syntax
import Id
import VarSet
-import CoreSyn ( Tickish(Breakpoint) )
+import GHC.Core ( Tickish(Breakpoint) )
import Outputable
import Util
diff --git a/compiler/GHC/Stg/Lint.hs b/compiler/GHC/Stg/Lint.hs
index 48d77d0903..471bbf763e 100644
--- a/compiler/GHC/Stg/Lint.hs
+++ b/compiler/GHC/Stg/Lint.hs
@@ -6,7 +6,7 @@ A lint pass to check basic STG invariants:
- Variables should be defined before used.
- Let bindings should not have unboxed types (unboxed bindings should only
- appear in case), except when they're join points (see Note [CoreSyn let/app
+ appear in case), except when they're join points (see Note [Core let/app
invariant] and #14117).
- If linting after unarisation, invariants listed in Note [Post-unarisation
@@ -48,7 +48,7 @@ import CostCentre ( isCurrentCCS )
import Id ( Id, idType, isJoinId, idName )
import VarSet
import DataCon
-import CoreSyn ( AltCon(..) )
+import GHC.Core ( AltCon(..) )
import Name ( getSrcLoc, nameIsLocalOrFrom )
import ErrUtils ( MsgDoc, Severity(..), mkLocMessage )
import Type
diff --git a/compiler/GHC/Stg/Subst.hs b/compiler/GHC/Stg/Subst.hs
index 84b9f29c3c..aa07c48b36 100644
--- a/compiler/GHC/Stg/Subst.hs
+++ b/compiler/GHC/Stg/Subst.hs
@@ -13,7 +13,7 @@ import Outputable
import Util
-- | A renaming substitution from 'Id's to 'Id's. Like 'RnEnv2', but not
--- maintaining pairs of substitutions. Like @"CoreSubst".'CoreSubst.Subst'@, but
+-- maintaining pairs of substitutions. Like 'GHC.Core.Subst.Subst', but
-- with the domain being 'Id's instead of entire 'CoreExpr'.
data Subst = Subst InScopeSet IdSubstEnv
diff --git a/compiler/GHC/Stg/Syntax.hs b/compiler/GHC/Stg/Syntax.hs
index eee0e6c6b2..46e70d477e 100644
--- a/compiler/GHC/Stg/Syntax.hs
+++ b/compiler/GHC/Stg/Syntax.hs
@@ -5,7 +5,7 @@ Shared term graph (STG) syntax for spineless-tagless code generation
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
This data type represents programs just before code generation (conversion to
-@Cmm@): basically, what we have is a stylised form of @CoreSyntax@, the style
+@Cmm@): basically, what we have is a stylised form of Core syntax, the style
being one that happens to be ideally suited to spineless tagless code
generation.
-}
@@ -63,7 +63,7 @@ module GHC.Stg.Syntax (
import GhcPrelude
-import CoreSyn ( AltCon, Tickish )
+import GHC.Core ( AltCon, Tickish )
import CostCentre ( CostCentreStack )
import Data.ByteString ( ByteString )
import Data.Data ( Data )
@@ -78,7 +78,7 @@ import Module ( Module )
import Outputable
import GHC.Driver.Packages ( isDllName )
import GHC.Platform
-import PprCore ( {- instances -} )
+import GHC.Core.Ppr( {- instances -} )
import PrimOp ( PrimOp, PrimCall )
import TyCon ( PrimRep(..), TyCon )
import Type ( Type )
@@ -96,12 +96,12 @@ GenStgBinding
As usual, expressions are interesting; other things are boring. Here are the
boring things (except note the @GenStgRhs@), parameterised with respect to
-binder and occurrence information (just as in @CoreSyn@):
+binder and occurrence information (just as in @GHC.Core@):
-}
-- | A top-level binding.
data GenStgTopBinding pass
--- See Note [CoreSyn top-level string literals]
+-- See Note [Core top-level string literals]
= StgTopLifted (GenStgBinding pass)
| StgTopStringLit Id ByteString
@@ -483,7 +483,7 @@ STG case alternatives
* *
************************************************************************
-Very like in @CoreSyntax@ (except no type-world stuff).
+Very like in Core syntax (except no type-world stuff).
The type constructor is guaranteed not to be abstract; that is, we can see its
representation. This is important because the code generator uses it to
@@ -537,7 +537,7 @@ type CgStgAlt = GenStgAlt 'CodeGen
{- Many passes apply a substitution, and it's very handy to have type
synonyms to remind us whether or not the substitution has been applied.
- See CoreSyn for precedence in Core land
+ See GHC.Core for precedence in Core land
-}
type InStgTopBinding = StgTopBinding
diff --git a/compiler/GHC/Stg/Unarise.hs b/compiler/GHC/Stg/Unarise.hs
index 4ed88255c1..cf47d204af 100644
--- a/compiler/GHC/Stg/Unarise.hs
+++ b/compiler/GHC/Stg/Unarise.hs
@@ -203,12 +203,12 @@ module GHC.Stg.Unarise (unarise) where
import GhcPrelude
import BasicTypes
-import CoreSyn
+import GHC.Core
import DataCon
import FastString (FastString, mkFastString)
import Id
import Literal
-import MkCore (aBSENT_SUM_FIELD_ERROR_ID)
+import GHC.Core.Make (aBSENT_SUM_FIELD_ERROR_ID)
import MkId (voidPrimId, voidArgId)
import MonadUtils (mapAccumLM)
import Outputable
@@ -581,7 +581,7 @@ mkUbxSum dc ty_args args0
slotRubbishArg :: SlotTy -> StgArg
slotRubbishArg PtrSlot = StgVarArg aBSENT_SUM_FIELD_ERROR_ID
- -- See Note [aBSENT_SUM_FIELD_ERROR_ID] in MkCore
+ -- See Note [aBSENT_SUM_FIELD_ERROR_ID] in GHC.Core.Make
slotRubbishArg WordSlot = StgLitArg (LitNumber LitNumWord 0 wordPrimTy)
slotRubbishArg Word64Slot = StgLitArg (LitNumber LitNumWord64 0 word64PrimTy)
slotRubbishArg FloatSlot = StgLitArg (LitFloat 0)
diff --git a/compiler/GHC/StgToCmm/Bind.hs b/compiler/GHC/StgToCmm/Bind.hs
index eb0d01ba62..5116cc1a30 100644
--- a/compiler/GHC/StgToCmm/Bind.hs
+++ b/compiler/GHC/StgToCmm/Bind.hs
@@ -29,7 +29,7 @@ import GHC.StgToCmm.Closure
import GHC.StgToCmm.Foreign (emitPrimCall)
import GHC.Cmm.Graph
-import CoreSyn ( AltCon(..), tickishIsCode )
+import GHC.Core ( AltCon(..), tickishIsCode )
import GHC.Cmm.BlockId
import GHC.Runtime.Heap.Layout
import GHC.Cmm
diff --git a/compiler/GHC/StgToCmm/DataCon.hs b/compiler/GHC/StgToCmm/DataCon.hs
index 2f7e350d83..199417ad34 100644
--- a/compiler/GHC/StgToCmm/DataCon.hs
+++ b/compiler/GHC/StgToCmm/DataCon.hs
@@ -20,7 +20,7 @@ module GHC.StgToCmm.DataCon (
import GhcPrelude
import GHC.Stg.Syntax
-import CoreSyn ( AltCon(..) )
+import GHC.Core ( AltCon(..) )
import GHC.StgToCmm.Monad
import GHC.StgToCmm.Env
diff --git a/compiler/GHC/StgToCmm/Expr.hs b/compiler/GHC/StgToCmm/Expr.hs
index 589cb770d6..cf0d4be8bc 100644
--- a/compiler/GHC/StgToCmm/Expr.hs
+++ b/compiler/GHC/StgToCmm/Expr.hs
@@ -36,7 +36,7 @@ import GHC.Cmm.Graph
import GHC.Cmm.BlockId
import GHC.Cmm hiding ( succ )
import GHC.Cmm.Info
-import CoreSyn
+import GHC.Core
import DataCon
import GHC.Driver.Session ( mAX_PTR_TAG )
import ForeignCall
@@ -324,8 +324,8 @@ calls to nonVoidIds in various places. So we must not look up
Note [Dead-binder optimisation]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
A case-binder, or data-constructor argument, may be marked as dead,
-because we preserve occurrence-info on binders in CoreTidy (see
-CoreTidy.tidyIdBndr).
+because we preserve occurrence-info on binders in GHC.Core.Op.Tidy (see
+GHC.Core.Op.Tidy.tidyIdBndr).
If the binder is dead, we can sometimes eliminate a load. While
CmmSink will eliminate that load, it's very easy to kill it at source
@@ -336,7 +336,7 @@ to keep it for -O0. See also Phab:D5358.
This probably also was the reason for occurrence hack in Phab:D5339 to
exist, perhaps because the occurrence information preserved by
-'CoreTidy.tidyIdBndr' was insufficient. But now that CmmSink does the
+'GHC.Core.Op.Tidy.tidyIdBndr' was insufficient. But now that CmmSink does the
job we deleted the hacks.
-}
diff --git a/compiler/basicTypes/BasicTypes.hs b/compiler/basicTypes/BasicTypes.hs
index 83ebb67c5c..9bae45365e 100644
--- a/compiler/basicTypes/BasicTypes.hs
+++ b/compiler/basicTypes/BasicTypes.hs
@@ -154,7 +154,7 @@ instance Outputable LeftOrRight where
-- "real work". So:
-- fib 100 has arity 0
-- \x -> fib x has arity 1
--- See also Note [Definition of arity] in CoreArity
+-- See also Note [Definition of arity] in GHC.Core.Arity
type Arity = Int
-- | Representation Arity
@@ -1377,13 +1377,13 @@ The main effects of CONLIKE are:
- The occurrence analyser (OccAnal) and simplifier (Simplify) treat
CONLIKE thing like constructors, by ANF-ing them
- - New function CoreUtils.exprIsExpandable is like exprIsCheap, but
+ - New function GHC.Core.Utils.exprIsExpandable is like exprIsCheap, but
additionally spots applications of CONLIKE functions
- A CoreUnfolding has a field that caches exprIsExpandable
- The rule matcher consults this field. See
- Note [Expanding variables] in Rules.hs.
+ Note [Expanding variables] in GHC.Core.Rules.
-}
isConLike :: RuleMatchInfo -> Bool
diff --git a/compiler/basicTypes/DataCon.hs b/compiler/basicTypes/DataCon.hs
index c89dab3349..7db26f1c94 100644
--- a/compiler/basicTypes/DataCon.hs
+++ b/compiler/basicTypes/DataCon.hs
@@ -461,7 +461,7 @@ data DataCon
-- It's convenient to apply the rep-type of MkT to 't', to get
-- forall x y. (t~(x,y), x~y, Ord x) => x -> y -> T t
-- and use that to check the pattern. Mind you, this is really only
- -- used in CoreLint.
+ -- used in GHC.Core.Lint.
dcInfix :: Bool, -- True <=> declared infix
diff --git a/compiler/basicTypes/Id.hs b/compiler/basicTypes/Id.hs
index dddc23da10..cc693e2f44 100644
--- a/compiler/basicTypes/Id.hs
+++ b/compiler/basicTypes/Id.hs
@@ -120,7 +120,7 @@ module Id (
import GhcPrelude
import GHC.Driver.Session
-import CoreSyn ( CoreRule, isStableUnfolding, evaldUnfolding,
+import GHC.Core ( CoreRule, isStableUnfolding, evaldUnfolding,
isCompulsoryUnfolding, Unfolding( NoUnfolding ) )
import IdInfo
@@ -374,7 +374,7 @@ It's very important that they are *LocalIds*, not GlobalIds, for lots
of reasons:
* We want to treat them as free variables for the purpose of
- dependency analysis (e.g. CoreFVs.exprFreeVars).
+ dependency analysis (e.g. GHC.Core.FVs.exprFreeVars).
* Look them up in the current substitution when we come across
occurrences of them (in Subst.lookupIdSubst). Lacking this we
@@ -778,7 +778,7 @@ idOneShotInfo :: Id -> OneShotInfo
idOneShotInfo id = oneShotInfo (idInfo id)
-- | Like 'idOneShotInfo', but taking the Horrible State Hack in to account
--- See Note [The state-transformer hack] in CoreArity
+-- See Note [The state-transformer hack] in GHC.Core.Arity
idStateHackOneShotInfo :: Id -> OneShotInfo
idStateHackOneShotInfo id
| isStateHackType (idType id) = stateHackOneShot
@@ -788,7 +788,7 @@ idStateHackOneShotInfo id
-- This one is the "business end", called externally.
-- It works on type variables as well as Ids, returning True
-- Its main purpose is to encapsulate the Horrible State Hack
--- See Note [The state-transformer hack] in CoreArity
+-- See Note [The state-transformer hack] in GHC.Core.Arity
isOneShotBndr :: Var -> Bool
isOneShotBndr var
| isTyVar var = True
diff --git a/compiler/basicTypes/IdInfo.hs b/compiler/basicTypes/IdInfo.hs
index d3c5abdea0..ea778ca87e 100644
--- a/compiler/basicTypes/IdInfo.hs
+++ b/compiler/basicTypes/IdInfo.hs
@@ -86,7 +86,7 @@ module IdInfo (
import GhcPrelude
-import CoreSyn
+import GHC.Core
import Class
import {-# SOURCE #-} PrimOp (PrimOp)
@@ -165,7 +165,7 @@ data IdDetails
-- This only covers /un-lifted/ coercions, of type
-- (t1 ~# t2) or (t1 ~R# t2), not their lifted variants
| JoinId JoinArity -- ^ An 'Id' for a join point taking n arguments
- -- Note [Join points] in CoreSyn
+ -- Note [Join points] in GHC.Core
-- | Recursive Selector Parent
data RecSelParent = RecSelData TyCon | RecSelPatSyn PatSyn deriving Eq
@@ -242,7 +242,7 @@ pprIdDetails other = brackets (pp other)
data IdInfo
= IdInfo {
arityInfo :: !ArityInfo,
- -- ^ 'Id' arity, as computed by 'CoreArity'. Specifies how many
+ -- ^ 'Id' arity, as computed by 'GHC.Core.Arity'. Specifies how many
-- arguments this 'Id' has to be applied to before it doesn any
-- meaningful work.
ruleInfo :: RuleInfo,
@@ -617,7 +617,7 @@ Ids store whether or not they can be levity-polymorphic at any amount
of saturation. This is helpful in optimizing the levity-polymorphism check
done in the desugarer, where we can usually learn that something is not
levity-polymorphic without actually figuring out its type. See
-isExprLevPoly in CoreUtils for where this info is used. Storing
+isExprLevPoly in GHC.Core.Utils for where this info is used. Storing
this is required to prevent perf/compiler/T5631 from blowing up.
-}
diff --git a/compiler/basicTypes/Literal.hs b/compiler/basicTypes/Literal.hs
index 708a85bb2f..035ba3b4b9 100644
--- a/compiler/basicTypes/Literal.hs
+++ b/compiler/basicTypes/Literal.hs
@@ -599,7 +599,7 @@ rubbishLit = LitRubbish
-- structured, ensuring that the compiler can't inline in ways that will break
-- user code. One approach to this is described in #8472.
litIsTrivial :: Literal -> Bool
--- c.f. CoreUtils.exprIsTrivial
+-- c.f. GHC.Core.Utils.exprIsTrivial
litIsTrivial (LitString _) = False
litIsTrivial (LitNumber nt _ _) = case nt of
LitNumInteger -> False
@@ -612,7 +612,7 @@ litIsTrivial _ = True
-- | True if code space does not go bad if we duplicate this literal
litIsDupable :: DynFlags -> Literal -> Bool
--- c.f. CoreUtils.exprIsDupable
+-- c.f. GHC.Core.Utils.exprIsDupable
litIsDupable _ (LitString _) = False
litIsDupable dflags (LitNumber nt i _) = case nt of
LitNumInteger -> inIntRange dflags i
diff --git a/compiler/basicTypes/MkId.hs b/compiler/basicTypes/MkId.hs
index 683d136b99..499b0347e1 100644
--- a/compiler/basicTypes/MkId.hs
+++ b/compiler/basicTypes/MkId.hs
@@ -42,7 +42,7 @@ module MkId (
import GhcPrelude
-import Rules
+import GHC.Core.Rules
import TysPrim
import TysWiredIn
import PrelRules
@@ -51,9 +51,9 @@ import TyCoRep
import FamInstEnv
import Coercion
import TcType
-import MkCore
-import CoreUtils ( mkCast, mkDefaultCase )
-import CoreUnfold
+import GHC.Core.Make
+import GHC.Core.Utils ( mkCast, mkDefaultCase )
+import GHC.Core.Unfold
import Literal
import TyCon
import Class
@@ -66,7 +66,7 @@ import Id
import IdInfo
import Demand
import Cpr
-import CoreSyn
+import GHC.Core
import Unique
import UniqSupply
import PrelNames
@@ -100,7 +100,7 @@ There are several reasons why an Id might appear in the wiredInIds:
* magicIds: see Note [magicIds]
-* errorIds, defined in coreSyn/MkCore.hs.
+* errorIds, defined in GHC.Core.Make.
These error functions (e.g. rUNTIME_ERROR_ID) are wired in
because the desugarer generates code that mentions them directly
@@ -144,7 +144,7 @@ wiredInIds :: [Id]
wiredInIds
= magicIds
++ ghcPrimIds
- ++ errorIds -- Defined in MkCore
+ ++ errorIds -- Defined in GHC.Core.Make
magicIds :: [Id] -- See Note [magicIds]
magicIds = [lazyId, oneShotId, noinlineId]
@@ -352,7 +352,7 @@ With -XUnliftedNewtypes, this is allowed -- even though MkN is levity-
polymorphic. It's OK because MkN evaporates in the compiled code, becoming
just a cast. That is, it has a compulsory unfolding. As long as its
argument is not levity-polymorphic (which it can't be, according to
-Note [Levity polymorphism invariants] in CoreSyn), and it's saturated,
+Note [Levity polymorphism invariants] in GHC.Core), and it's saturated,
no levity-polymorphic code ends up in the code generator. The saturation
condition is effectively checked by Note [Detecting forced eta expansion]
in GHC.HsToCore.Expr.
@@ -1387,7 +1387,7 @@ seqId = pcMiscPrelId seqName ty info
= alwaysInlinePragma `setInlinePragmaActivation` ActiveAfter
NoSourceText 0
-- Make 'seq' not inline-always, so that simpleOptExpr
- -- (see CoreSubst.simple_app) won't inline 'seq' on the
+ -- (see GHC.Core.Subst.simple_app) won't inline 'seq' on the
-- LHS of rules. That way we can have rules for 'seq';
-- see Note [seqId magic]
@@ -1611,7 +1611,7 @@ which is what we want.
It is only effective if the one-shot info survives as long as possible; in
particular it must make it into the interface in unfoldings. See Note [Preserve
-OneShotInfo] in CoreTidy.
+OneShotInfo] in GHC.Core.Op.Tidy.
Also see https://gitlab.haskell.org/ghc/ghc/wikis/one-shot.
diff --git a/compiler/ghc.cabal.in b/compiler/ghc.cabal.in
index f42fc72d4e..a9903b9ded 100644
--- a/compiler/ghc.cabal.in
+++ b/compiler/ghc.cabal.in
@@ -162,7 +162,6 @@ Library
.
basicTypes
cmm
- coreSyn
iface
main
parser
@@ -301,21 +300,21 @@ Library
GHC.StgToCmm.Utils
GHC.StgToCmm.ExtCode
GHC.Runtime.Heap.Layout
- CoreArity
- CoreFVs
- CoreLint
- CoreSubst
- CoreOpt
- CoreSyn
+ GHC.Core.Arity
+ GHC.Core.FVs
+ GHC.Core.Lint
+ GHC.Core.Subst
+ GHC.Core.SimpleOpt
+ GHC.Core
TrieMap
- CoreTidy
- CoreUnfold
- CoreUtils
- CoreMap
- CoreSeq
- CoreStats
- MkCore
- PprCore
+ GHC.Core.Op.Tidy
+ GHC.Core.Unfold
+ GHC.Core.Utils
+ GHC.Core.Map
+ GHC.Core.Seq
+ GHC.Core.Stats
+ GHC.Core.Make
+ GHC.Core.Ppr
GHC.HsToCore.PmCheck.Oracle
GHC.HsToCore.PmCheck.Ppr
GHC.HsToCore.PmCheck.Types
@@ -388,7 +387,7 @@ Library
PlatformConstants
GHC.Driver.Plugins
TcPluginM
- PprTyThing
+ GHC.Core.Ppr.TyThing
Settings
StaticPtrTable
SysTools
@@ -460,7 +459,7 @@ Library
GHC.CoreToStg
GHC.CoreToStg.Prep
GHC.Types.RepType
- Rules
+ GHC.Core.Rules
SpecConstr
Specialise
CallArity
diff --git a/compiler/main/StaticPtrTable.hs b/compiler/main/StaticPtrTable.hs
index 985e91e29c..1a87cf8d1d 100644
--- a/compiler/main/StaticPtrTable.hs
+++ b/compiler/main/StaticPtrTable.hs
@@ -125,13 +125,13 @@ Here is a running example:
import GhcPrelude
import GHC.Cmm.CLabel
-import CoreSyn
-import CoreUtils (collectMakeStaticArgs)
+import GHC.Core
+import GHC.Core.Utils (collectMakeStaticArgs)
import DataCon
import GHC.Driver.Session
import GHC.Driver.Types
import Id
-import MkCore (mkStringExprFSWith)
+import GHC.Core.Make (mkStringExprFSWith)
import Module
import Name
import Outputable
diff --git a/compiler/main/UpdateCafInfos.hs b/compiler/main/UpdateCafInfos.hs
index 600dc62207..46d3aee676 100644
--- a/compiler/main/UpdateCafInfos.hs
+++ b/compiler/main/UpdateCafInfos.hs
@@ -6,7 +6,7 @@ module UpdateCafInfos
import GhcPrelude
-import CoreSyn
+import GHC.Core
import GHC.Driver.Types
import Id
import IdInfo
diff --git a/compiler/prelude/PrelRules.hs b/compiler/prelude/PrelRules.hs
index 201bd037f3..a83dd54a94 100644
--- a/compiler/prelude/PrelRules.hs
+++ b/compiler/prelude/PrelRules.hs
@@ -29,20 +29,21 @@ import GhcPrelude
import {-# SOURCE #-} MkId ( mkPrimOpId, magicDictId )
-import CoreSyn
-import MkCore
+import GHC.Core
+import GHC.Core.Make
import Id
import Literal
-import CoreOpt ( exprIsLiteral_maybe )
-import PrimOp ( PrimOp(..), tagToEnumKey )
+import GHC.Core.SimpleOpt ( exprIsLiteral_maybe )
+import PrimOp ( PrimOp(..), tagToEnumKey )
import TysWiredIn
import TysPrim
import TyCon ( tyConDataCons_maybe, isAlgTyCon, isEnumerationTyCon
, isNewTyCon, unwrapNewTyCon_maybe, tyConDataCons
, tyConFamilySize )
import DataCon ( dataConTagZ, dataConTyCon, dataConWrapId, dataConWorkId )
-import CoreUtils ( cheapEqExpr, cheapEqExpr', exprIsHNF, exprType, stripTicksTop, stripTicksTopT, mkTicks )
-import CoreUnfold ( exprIsConApp_maybe )
+import GHC.Core.Utils ( cheapEqExpr, cheapEqExpr', exprIsHNF, exprType
+ , stripTicksTop, stripTicksTopT, mkTicks )
+import GHC.Core.Unfold ( exprIsConApp_maybe )
import Type
import OccName ( occNameFS )
import PrelNames
@@ -739,7 +740,7 @@ as follows:
in ...
This was originally done in the fix to #16449 but this breaks the let/app
-invariant (see Note [CoreSyn let/app invariant] in CoreSyn) as noted in #16742.
+invariant (see Note [Core let/app invariant] in GHC.Core) as noted in #16742.
For the reasons discussed in Note [Checking versus non-checking primops] (in
the PrimOp module) there is no safe way rewrite the argument of I# such that
it bottoms.
@@ -1103,12 +1104,12 @@ Only `SeqOp` shares that property. (Other primops do not do anything
as fancy as argument evaluation.) The special handling for dataToTag#
is:
-* CoreUtils.exprOkForSpeculation has a special case for DataToTagOp,
+* GHC.Core.Utils.exprOkForSpeculation has a special case for DataToTagOp,
(actually in app_ok). Most primops with lifted arguments do not
evaluate those arguments, but DataToTagOp and SeqOp are two
exceptions. We say that they are /never/ ok-for-speculation,
regardless of the evaluated-ness of their argument.
- See CoreUtils Note [exprOkForSpeculation and SeqOp/DataToTagOp]
+ See GHC.Core.Utils Note [exprOkForSpeculation and SeqOp/DataToTagOp]
* There is a special case for DataToTagOp in GHC.StgToCmm.Expr.cgExpr,
that evaluates its argument and then extracts the tag from
@@ -1200,8 +1201,8 @@ Implementing seq#. The compiler has magic for SeqOp in
- GHC.StgToCmm.Expr.cgExpr, and cgCase: special case for seq#
-- CoreUtils.exprOkForSpeculation;
- see Note [exprOkForSpeculation and SeqOp/DataToTagOp] in CoreUtils
+- GHC.Core.Utils.exprOkForSpeculation;
+ see Note [exprOkForSpeculation and SeqOp/DataToTagOp] in GHC.Core.Utils
- Simplify.addEvals records evaluated-ness for the result; see
Note [Adding evaluatedness info to pattern-bound variables]
diff --git a/compiler/prelude/PrimOp.hs b/compiler/prelude/PrimOp.hs
index 81d643fc66..ecce2e791f 100644
--- a/compiler/prelude/PrimOp.hs
+++ b/compiler/prelude/PrimOp.hs
@@ -323,7 +323,7 @@ Note [Checking versus non-checking primops]
It is important that a non-checking primop never be transformed in a way that
would cause it to bottom. Doing so would violate Core's let/app invariant
- (see Note [CoreSyn let/app invariant] in CoreSyn) which is critical to
+ (see Note [Core let/app invariant] in GHC.Core) which is critical to
the simplifier's ability to float without fear of changing program meaning.
@@ -483,7 +483,7 @@ primOpCanFail :: PrimOp -> Bool
primOpOkForSpeculation :: PrimOp -> Bool
-- See Note [PrimOp can_fail and has_side_effects]
- -- See comments with CoreUtils.exprOkForSpeculation
+ -- See comments with GHC.Core.Utils.exprOkForSpeculation
-- primOpOkForSpeculation => primOpOkForSideEffects
primOpOkForSpeculation op
= primOpOkForSideEffects op
@@ -535,7 +535,7 @@ primOpIsCheap op = primOpOkForSpeculation op
primOpCodeSize
~~~~~~~~~~~~~~
Gives an indication of the code size of a primop, for the purposes of
-calculating unfolding sizes; see CoreUnfold.sizeExpr.
+calculating unfolding sizes; see GHC.Core.Unfold.sizeExpr.
-}
primOpCodeSize :: PrimOp -> Int
@@ -543,7 +543,7 @@ primOpCodeSize :: PrimOp -> Int
primOpCodeSizeDefault :: Int
primOpCodeSizeDefault = 1
- -- CoreUnfold.primOpSize already takes into account primOpOutOfLine
+ -- GHC.Core.Unfold.primOpSize already takes into account primOpOutOfLine
-- and adds some further costs for the args in that case.
primOpCodeSizeForeignCall :: Int
diff --git a/compiler/prelude/TysPrim.hs b/compiler/prelude/TysPrim.hs
index e50030b0f6..7a3a8df8ae 100644
--- a/compiler/prelude/TysPrim.hs
+++ b/compiler/prelude/TysPrim.hs
@@ -511,7 +511,7 @@ tYPETyCon = mkKindTyCon tYPETyConName
-- ... and now their names
-- If you edit these, you may need to update the GHC formalism
--- See Note [GHC Formalism] in coreSyn/CoreLint.hs
+-- See Note [GHC Formalism] in GHC.Core.Lint
tYPETyConName = mkPrimTyConName (fsLit "TYPE") tYPETyConKey tYPETyCon
mkPrimTyConName :: FastString -> Unique -> TyCon -> Name
diff --git a/compiler/prelude/TysWiredIn.hs b/compiler/prelude/TysWiredIn.hs
index 0ea3ec2dd7..ff28acce8d 100644
--- a/compiler/prelude/TysWiredIn.hs
+++ b/compiler/prelude/TysWiredIn.hs
@@ -733,8 +733,8 @@ Note that there is *not* a unary constraint tuple, unlike for other forms of
tuples. See [Ignore unary constraint tuples] in TcHsType for more
details.
-See also Note [Flattening one-tuples] in MkCore and
-Note [Don't flatten tuples from HsSyn] in MkCore.
+See also Note [Flattening one-tuples] in GHC.Core.Make and
+Note [Don't flatten tuples from HsSyn] in GHC.Core.Make.
-}
@@ -1604,7 +1604,7 @@ mkTupleTy boxity tys = mkTupleTy1 boxity tys
-- | Make a tuple type. The list of types should /not/ include any
-- RuntimeRep specifications. Boxed 1-tuples are *not* flattened.
-- See Note [One-tuples] and Note [Don't flatten tuples from HsSyn]
--- in MkCore
+-- in GHC.Core.Make
mkTupleTy1 :: Boxity -> [Type] -> Type
mkTupleTy1 Boxed tys = mkTyConApp (tupleTyCon Boxed (length tys)) tys
mkTupleTy1 Unboxed tys = mkTyConApp (tupleTyCon Unboxed (length tys))
diff --git a/compiler/simplCore/CSE.hs b/compiler/simplCore/CSE.hs
index 9a0945e290..8fe56f0965 100644
--- a/compiler/simplCore/CSE.hs
+++ b/compiler/simplCore/CSE.hs
@@ -15,22 +15,22 @@ module CSE (cseProgram, cseOneExpr) where
import GhcPrelude
-import CoreSubst
+import GHC.Core.Subst
import Var ( Var )
import VarEnv ( elemInScopeSet, mkInScopeSet )
import Id ( Id, idType, isDeadBinder, idHasRules
, idInlineActivation, setInlineActivation
, zapIdOccInfo, zapIdUsageInfo, idInlinePragma
, isJoinId, isJoinId_maybe )
-import CoreUtils ( mkAltExpr, eqExpr
+import GHC.Core.Utils ( mkAltExpr, eqExpr
, exprIsTickedString
, stripTicksE, stripTicksT, mkTicks )
-import CoreFVs ( exprFreeVars )
+import GHC.Core.FVs ( exprFreeVars )
import Type ( tyConAppArgs )
-import CoreSyn
+import GHC.Core
import Outputable
import BasicTypes
-import CoreMap
+import GHC.Core.Map
import Util ( filterOut )
import Data.List ( mapAccumL )
@@ -271,7 +271,7 @@ We must not be naive about join points in CSE:
join j = e in
if b then jump j else 1 + e
The expression (1 + jump j) is not good (see Note [Invariants on join points] in
-CoreSyn). This seems to come up quite seldom, but it happens (first seen
+GHC.Core). This seems to come up quite seldom, but it happens (first seen
compiling ppHtml in Haddock.Backends.Xhtml).
We could try and be careful by tracking which join points are still valid at
@@ -416,7 +416,7 @@ addBinding :: CSEnv -- Includes InId->OutId cloning
-- unless we can instead just substitute [in-id -> rhs]
--
-- It's possible for the binder to be a type variable (see
--- Note [Type-let] in CoreSyn), in which case we can just substitute.
+-- Note [Type-let] in GHC.Core), in which case we can just substitute.
addBinding env in_id out_id rhs'
| not (isId in_id) = (extendCSSubst env in_id rhs', out_id)
| noCSE in_id = (env, out_id)
@@ -469,7 +469,7 @@ We would normally turn this into:
But this breaks an invariant of Core, namely that the RHS of a top-level binding
of type Addr# must be a string literal, not another variable. See Note
-[CoreSyn top-level string literals] in CoreSyn.
+[Core top-level string literals] in GHC.Core.
For this reason, we special case top-level bindings to literal strings and leave
the original RHS unmodified. This produces:
diff --git a/compiler/simplCore/CallArity.hs b/compiler/simplCore/CallArity.hs
index 36f80c149c..84d62e4ad9 100644
--- a/compiler/simplCore/CallArity.hs
+++ b/compiler/simplCore/CallArity.hs
@@ -14,10 +14,10 @@ import VarEnv
import GHC.Driver.Session ( DynFlags )
import BasicTypes
-import CoreSyn
+import GHC.Core
import Id
-import CoreArity ( typeArity )
-import CoreUtils ( exprIsCheap, exprIsTrivial )
+import GHC.Core.Arity ( typeArity )
+import GHC.Core.Utils ( exprIsCheap, exprIsTrivial )
import UnVarGraph
import Demand
import Util
@@ -384,7 +384,7 @@ the case for Core!
1. We need to ensure the invariant
callArity e <= typeArity (exprType e)
for the same reasons that exprArity needs this invariant (see Note
- [exprArity invariant] in CoreArity).
+ [exprArity invariant] in GHC.Core.Arity).
If we are not doing that, a too-high arity annotation will be stored with
the id, confusing the simplifier later on.
diff --git a/compiler/simplCore/CoreMonad.hs b/compiler/simplCore/CoreMonad.hs
index 84860d56e5..7da11f9062 100644
--- a/compiler/simplCore/CoreMonad.hs
+++ b/compiler/simplCore/CoreMonad.hs
@@ -51,7 +51,7 @@ module CoreMonad (
import GhcPrelude hiding ( read )
-import CoreSyn
+import GHC.Core
import GHC.Driver.Types
import Module
import GHC.Driver.Session
diff --git a/compiler/simplCore/Exitify.hs b/compiler/simplCore/Exitify.hs
index f8266fc154..cbb7469e4f 100644
--- a/compiler/simplCore/Exitify.hs
+++ b/compiler/simplCore/Exitify.hs
@@ -39,13 +39,13 @@ import GhcPrelude
import Var
import Id
import IdInfo
-import CoreSyn
-import CoreUtils
+import GHC.Core
+import GHC.Core.Utils
import State
import Unique
import VarSet
import VarEnv
-import CoreFVs
+import GHC.Core.FVs
import FastString
import Type
import Util( mapSnd )
diff --git a/compiler/simplCore/FloatIn.hs b/compiler/simplCore/FloatIn.hs
index 47cbb87912..4a690ccfc4 100644
--- a/compiler/simplCore/FloatIn.hs
+++ b/compiler/simplCore/FloatIn.hs
@@ -22,11 +22,11 @@ module FloatIn ( floatInwards ) where
import GhcPrelude
-import CoreSyn
-import MkCore hiding ( wrapFloats )
-import GHC.Driver.Types ( ModGuts(..) )
-import CoreUtils
-import CoreFVs
+import GHC.Core
+import GHC.Core.Make hiding ( wrapFloats )
+import GHC.Driver.Types ( ModGuts(..) )
+import GHC.Core.Utils
+import GHC.Core.FVs
import CoreMonad ( CoreM )
import Id ( isOneShotBndr, idType, isJoinId, isJoinId_maybe )
import Var
diff --git a/compiler/simplCore/FloatOut.hs b/compiler/simplCore/FloatOut.hs
index 18d48d4f12..b8736085dd 100644
--- a/compiler/simplCore/FloatOut.hs
+++ b/compiler/simplCore/FloatOut.hs
@@ -12,10 +12,10 @@ module FloatOut ( floatOutwards ) where
import GhcPrelude
-import CoreSyn
-import CoreUtils
-import MkCore
-import CoreArity ( etaExpand )
+import GHC.Core
+import GHC.Core.Utils
+import GHC.Core.Make
+import GHC.Core.Arity ( etaExpand )
import CoreMonad ( FloatOutSwitches(..) )
import GHC.Driver.Session
@@ -111,7 +111,7 @@ Well, maybe. We don't do this at the moment.
Note [Join points]
~~~~~~~~~~~~~~~~~~
Every occurrence of a join point must be a tail call (see Note [Invariants on
-join points] in CoreSyn), so we must be careful with how far we float them. The
+join points] in GHC.Core), so we must be careful with how far we float them. The
mechanism for doing so is the *join ceiling*, detailed in Note [Join ceiling]
in SetLevels. For us, the significance is that a binder might be marked to be
dropped at the nearest boundary between tail calls and non-tail calls. For
diff --git a/compiler/simplCore/LiberateCase.hs b/compiler/simplCore/LiberateCase.hs
index 8bea7dbfdb..1347cf37bf 100644
--- a/compiler/simplCore/LiberateCase.hs
+++ b/compiler/simplCore/LiberateCase.hs
@@ -12,8 +12,8 @@ module LiberateCase ( liberateCase ) where
import GhcPrelude
import GHC.Driver.Session
-import CoreSyn
-import CoreUnfold ( couldBeSmallEnoughToInline )
+import GHC.Core
+import GHC.Core.Unfold ( couldBeSmallEnoughToInline )
import TysWiredIn ( unitDataConId )
import Id
import VarEnv
diff --git a/compiler/simplCore/OccurAnal.hs b/compiler/simplCore/OccurAnal.hs
index 47460178f1..161d1a9010 100644
--- a/compiler/simplCore/OccurAnal.hs
+++ b/compiler/simplCore/OccurAnal.hs
@@ -23,11 +23,11 @@ module OccurAnal (
import GhcPrelude
-import CoreSyn
-import CoreFVs
-import CoreUtils ( exprIsTrivial, isDefaultAlt, isExpandableApp,
+import GHC.Core
+import GHC.Core.FVs
+import GHC.Core.Utils ( exprIsTrivial, isDefaultAlt, isExpandableApp,
stripTicksTopE, mkTicks )
-import CoreArity ( joinRhsArity )
+import GHC.Core.Arity ( joinRhsArity )
import Id
import IdInfo
import Name( localiseName )
@@ -2762,7 +2762,7 @@ setBinderOcc occ_info bndr
-- the decision about another binding 'g' might be invalidated if (say)
-- 'f' tail-calls 'g'.
--
--- See Note [Invariants on join points] in CoreSyn.
+-- See Note [Invariants on join points] in GHC.Core.
decideJoinPointHood :: TopLevelFlag -> UsageDetails
-> [CoreBndr]
-> Bool
@@ -2835,7 +2835,7 @@ unfolding captured by the INLINE pragma has arity 1. If we try to
convert g to be a join point, its unfolding will still have arity 1
(since it is stable, and we don't meddle with stable unfoldings), and
Lint will complain (see Note [Invariants on join points], (2a), in
-CoreSyn. #13413.
+GHC.Core. #13413.
Moreover, since g is going to be inlined anyway, there is no benefit
from making it a join point.
@@ -2847,7 +2847,7 @@ TcInstDcls) we mark recursive things as INLINE but the recursion
unravels; so ignoring INLINE pragmas on recursive things isn't good
either.
-See Invariant 2a of Note [Invariants on join points] in CoreSyn
+See Invariant 2a of Note [Invariants on join points] in GHC.Core
************************************************************************
diff --git a/compiler/simplCore/SAT.hs b/compiler/simplCore/SAT.hs
index 23e2b601d3..626c4d06b2 100644
--- a/compiler/simplCore/SAT.hs
+++ b/compiler/simplCore/SAT.hs
@@ -54,8 +54,8 @@ module SAT ( doStaticArgs ) where
import GhcPrelude
import Var
-import CoreSyn
-import CoreUtils
+import GHC.Core
+import GHC.Core.Utils
import Type
import Coercion
import Id
diff --git a/compiler/simplCore/SetLevels.hs b/compiler/simplCore/SetLevels.hs
index 60cc676503..e645005b7d 100644
--- a/compiler/simplCore/SetLevels.hs
+++ b/compiler/simplCore/SetLevels.hs
@@ -66,18 +66,18 @@ module SetLevels (
import GhcPrelude
-import CoreSyn
+import GHC.Core
import CoreMonad ( FloatOutSwitches(..) )
-import CoreUtils ( exprType, exprIsHNF
+import GHC.Core.Utils ( exprType, exprIsHNF
, exprOkForSpeculation
, exprIsTopLevelBindable
, isExprLevPoly
, collectMakeStaticArgs
)
-import CoreArity ( exprBotStrictness_maybe )
-import CoreFVs -- all of it
-import CoreSubst
-import MkCore ( sortQuantVars )
+import GHC.Core.Arity ( exprBotStrictness_maybe )
+import GHC.Core.FVs -- all of it
+import GHC.Core.Subst
+import GHC.Core.Make ( sortQuantVars )
import Id
import IdInfo
@@ -340,7 +340,7 @@ don't want @lvlExpr@ to turn the scrutinee of the @case@ into an MFE
If there were another lambda in @r@'s rhs, it would get level-2 as well.
-}
-lvlExpr env (_, AnnType ty) = return (Type (CoreSubst.substTy (le_subst env) ty))
+lvlExpr env (_, AnnType ty) = return (Type (GHC.Core.Subst.substTy (le_subst env) ty))
lvlExpr env (_, AnnCoercion co) = return (Coercion (substCo (le_subst env) co))
lvlExpr env (_, AnnVar v) = return (lookupVar env v)
lvlExpr _ (_, AnnLit lit) = return (Lit lit)
@@ -522,7 +522,7 @@ Things to note:
- exrpIsHNF catches the key case of an evaluated variable
- exprOkForSpeculation is /false/ of an evaluated variable;
- See Note [exprOkForSpeculation and evaluated variables] in CoreUtils
+ See Note [exprOkForSpeculation and evaluated variables] in GHC.Core.Utils
So we'd actually miss the key case!
- Nothing is gained from the extra generality of exprOkForSpeculation
@@ -602,7 +602,7 @@ lvlMFE :: LevelEnv -- Level of in-scope names/tyvars
-- the expression, so that it can itself be floated.
lvlMFE env _ (_, AnnType ty)
- = return (Type (CoreSubst.substTy (le_subst env) ty))
+ = return (Type (GHC.Core.Subst.substTy (le_subst env) ty))
-- No point in floating out an expression wrapped in a coercion or note
-- If we do we'll transform lvl = e |> co
@@ -628,7 +628,7 @@ lvlMFE env strict_ctxt ann_expr
-- See Note [Free join points]
|| isExprLevPoly expr
-- We can't let-bind levity polymorphic expressions
- -- See Note [Levity polymorphism invariants] in CoreSyn
+ -- See Note [Levity polymorphism invariants] in GHC.Core
|| notWorthFloating expr abs_vars
|| not float_me
= -- Don't float it out
@@ -1331,7 +1331,7 @@ substAndLvlBndrs is_rec env lvl bndrs
(subst_env, subst_bndrs) = substBndrsSL is_rec env bndrs
substBndrsSL :: RecFlag -> LevelEnv -> [InVar] -> (LevelEnv, [OutVar])
--- So named only to avoid the name clash with CoreSubst.substBndrs
+-- So named only to avoid the name clash with GHC.Core.Subst.substBndrs
substBndrsSL is_rec env@(LE { le_subst = subst, le_env = id_env }) bndrs
= ( env { le_subst = subst'
, le_env = foldl' add_id id_env (bndrs `zip` bndrs') }
@@ -1672,7 +1672,7 @@ newPolyBndrs dest_lvl
mkSysLocal (mkFastString str) uniq poly_ty
where
str = "poly_" ++ occNameString (getOccName bndr)
- poly_ty = mkLamTypes abs_vars (CoreSubst.substTy subst (idType bndr))
+ poly_ty = mkLamTypes abs_vars (GHC.Core.Subst.substTy subst (idType bndr))
-- If we are floating a join point to top level, it stops being
-- a join point. Otherwise it continues to be a join point,
diff --git a/compiler/simplCore/SimplCore.hs b/compiler/simplCore/SimplCore.hs
index 1acedf2b44..e34e390a9a 100644
--- a/compiler/simplCore/SimplCore.hs
+++ b/compiler/simplCore/SimplCore.hs
@@ -13,18 +13,18 @@ module SimplCore ( core2core, simplifyExpr ) where
import GhcPrelude
import GHC.Driver.Session
-import CoreSyn
+import GHC.Core
import GHC.Driver.Types
import CSE ( cseProgram )
-import Rules ( mkRuleBase, unionRuleBase,
+import GHC.Core.Rules ( mkRuleBase, unionRuleBase,
extendRuleBaseList, ruleCheckProgram, addRuleInfo,
getRules )
-import PprCore ( pprCoreBindings, pprCoreExpr )
+import GHC.Core.Ppr ( pprCoreBindings, pprCoreExpr )
import OccurAnal ( occurAnalysePgm, occurAnalyseExpr )
import IdInfo
-import CoreStats ( coreBindsSize, coreBindsStats, exprSize )
-import CoreUtils ( mkTicks, stripTicksTop )
-import CoreLint ( endPass, lintPassResult, dumpPassResult,
+import GHC.Core.Stats ( coreBindsSize, coreBindsStats, exprSize )
+import GHC.Core.Utils ( mkTicks, stripTicksTop )
+import GHC.Core.Lint ( endPass, lintPassResult, dumpPassResult,
lintAnnots )
import Simplify ( simplTopBinds, simplExpr, simplRules )
import SimplUtils ( simplEnvForGHCi, activeRule, activeUnfolding )
@@ -52,8 +52,8 @@ import WorkWrap ( wwTopBinds )
import SrcLoc
import Util
import Module
-import GHC.Driver.Plugins ( withPlugins, installCoreToDos )
-import GHC.Runtime.Loader -- ( initializePlugins )
+import GHC.Driver.Plugins ( withPlugins, installCoreToDos )
+import GHC.Runtime.Loader -- ( initializePlugins )
import UniqSupply ( UniqSupply, mkSplitUniqSupply, splitUniqSupply )
import UniqFM
@@ -701,7 +701,7 @@ simplifyPgmIO pass@(CoreDoSimplify max_iterations mode)
(pprCoreBindings tagged_binds);
-- Get any new rules, and extend the rule base
- -- See Note [Overall plumbing for rules] in Rules.hs
+ -- See Note [Overall plumbing for rules] in GHC.Core.Rules
-- We need to do this regularly, because simplification can
-- poke on IdInfo thunks, which in turn brings in new rules
-- behind the scenes. Otherwise there's a danger we'll simply
diff --git a/compiler/simplCore/SimplEnv.hs b/compiler/simplCore/SimplEnv.hs
index 020607abe6..9e91d2ea5a 100644
--- a/compiler/simplCore/SimplEnv.hs
+++ b/compiler/simplCore/SimplEnv.hs
@@ -49,15 +49,15 @@ import GhcPrelude
import SimplMonad
import CoreMonad ( SimplMode(..) )
-import CoreSyn
-import CoreUtils
+import GHC.Core
+import GHC.Core.Utils
import Var
import VarEnv
import VarSet
import OrdList
import Id
-import MkCore ( mkWildValBinder )
-import GHC.Driver.Session ( DynFlags )
+import GHC.Core.Make ( mkWildValBinder )
+import GHC.Driver.Session ( DynFlags )
import TysWiredIn
import qualified Type
import Type hiding ( substTy, substTyVar, substTyVarBndr )
@@ -149,7 +149,7 @@ pprSimplEnv env
| otherwise = ppr v
type SimplIdSubst = IdEnv SimplSR -- IdId |--> OutExpr
- -- See Note [Extending the Subst] in CoreSubst
+ -- See Note [Extending the Subst] in GHC.Core.Subst
-- | A substitution result.
data SimplSR
@@ -290,7 +290,7 @@ way to do that is to start of with a representative
Id in the in-scope set
There can be *occurrences* of wild-id. For example,
-MkCore.mkCoreApp transforms
+GHC.Core.Make.mkCoreApp transforms
e (a /# b) --> case (a /# b) of wild { DEFAULT -> e wild }
This is ok provided 'wild' isn't free in 'e', and that's the delicate
thing. Generally, you want to run the simplifier to get rid of the
@@ -498,7 +498,7 @@ unitLetFloat bind = ASSERT(all (not . isJoinId) (bindersOf bind))
| not (isStrictId bndr) = FltLifted
| exprIsTickedString rhs = FltLifted
-- String literals can be floated freely.
- -- See Note [CoreSyn top-level string literals] in CoreSyn.
+ -- See Note [Core top-level string literals] in GHC.Core.
| exprOkForSpeculation rhs = FltOkSpec -- Unlifted, and lifted but ok-for-spec (eg HNF)
| otherwise = ASSERT2( not (isUnliftedType (idType bndr)), ppr bndr )
FltCareful
@@ -805,7 +805,7 @@ substNonCoVarIdBndr
-- Augment the substitution if the unique changed
-- Extend the in-scope set with the new Id
--
--- Similar to CoreSubst.substIdBndr, except that
+-- Similar to GHC.Core.Subst.substIdBndr, except that
-- the type of id_subst differs
-- all fragile info is zapped
substNonCoVarIdBndr new_res_ty
diff --git a/compiler/simplCore/SimplMonad.hs b/compiler/simplCore/SimplMonad.hs
index ed0889d1b1..c1045f7875 100644
--- a/compiler/simplCore/SimplMonad.hs
+++ b/compiler/simplCore/SimplMonad.hs
@@ -28,7 +28,7 @@ import Id ( Id, mkSysLocalOrCoVar )
import IdInfo ( IdDetails(..), vanillaIdInfo, setArityInfo )
import Type ( Type, mkLamTypes )
import FamInstEnv ( FamInstEnv )
-import CoreSyn ( RuleEnv(..) )
+import GHC.Core ( RuleEnv(..) )
import UniqSupply
import GHC.Driver.Session
import CoreMonad
@@ -189,7 +189,7 @@ newJoinId bndrs body_ty
; let name = mkSystemVarName uniq (fsLit "$j")
join_id_ty = mkLamTypes bndrs body_ty -- Note [Funky mkLamTypes]
arity = count isId bndrs
- -- arity: See Note [Invariants on join points] invariant 2b, in CoreSyn
+ -- arity: See Note [Invariants on join points] invariant 2b, in GHC.Core
join_arity = length bndrs
details = JoinId join_arity
id_info = vanillaIdInfo `setArityInfo` arity
diff --git a/compiler/simplCore/SimplUtils.hs b/compiler/simplCore/SimplUtils.hs
index 9528a73d90..6f46ded027 100644
--- a/compiler/simplCore/SimplUtils.hs
+++ b/compiler/simplCore/SimplUtils.hs
@@ -43,14 +43,14 @@ import GhcPrelude
import SimplEnv
import CoreMonad ( SimplMode(..), Tick(..) )
import GHC.Driver.Session
-import CoreSyn
-import qualified CoreSubst
-import PprCore
+import GHC.Core
+import qualified GHC.Core.Subst
+import GHC.Core.Ppr
import TyCoPpr ( pprParendType )
-import CoreFVs
-import CoreUtils
-import CoreArity
-import CoreUnfold
+import GHC.Core.FVs
+import GHC.Core.Utils
+import GHC.Core.Arity
+import GHC.Core.Unfold
import Name
import Id
import IdInfo
@@ -353,7 +353,7 @@ mkFunRules rs = Just (n_required, rs)
mkBoringStop :: OutType -> SimplCont
mkBoringStop ty = Stop ty BoringCtxt
-mkRhsStop :: OutType -> SimplCont -- See Note [RHS of lets] in CoreUnfold
+mkRhsStop :: OutType -> SimplCont -- See Note [RHS of lets] in GHC.Core.Unfold
mkRhsStop ty = Stop ty RhsCtxt
mkLazyArgStop :: OutType -> CallCtxt -> SimplCont
@@ -432,7 +432,7 @@ contArgs cont
| lone cont = (True, [], cont)
| otherwise = go [] cont
where
- lone (ApplyToTy {}) = False -- See Note [Lone variables] in CoreUnfold
+ lone (ApplyToTy {}) = False -- See Note [Lone variables] in GHC.Core.Unfold
lone (ApplyToVal {}) = False
lone (CastIt {}) = False
lone _ = True
@@ -632,7 +632,7 @@ interestingCallContext env cont
-- Can happen if we have (f Int |> co) y
-- If f has an INLINE prag we need to give it some
-- motivation to inline. See Note [Cast then apply]
- -- in CoreUnfold
+ -- in GHC.Core.Unfold
interesting (StrictArg { sc_cci = cci }) = cci
interesting (StrictBind {}) = BoringCtxt
@@ -1135,7 +1135,7 @@ preInlineUnconditionally
-> InExpr -> StaticEnv -- These two go together
-> Maybe SimplEnv -- Returned env has extended substitution
-- Precondition: rhs satisfies the let/app invariant
--- See Note [CoreSyn let/app invariant] in CoreSyn
+-- See Note [Core let/app invariant] in GHC.Core
-- Reason: we don't want to inline single uses, or discard dead bindings,
-- for unlifted, side-effect-ful bindings
preInlineUnconditionally env top_lvl bndr rhs rhs_env
@@ -1259,7 +1259,7 @@ postInlineUnconditionally
-> OutExpr
-> Bool
-- Precondition: rhs satisfies the let/app invariant
--- See Note [CoreSyn let/app invariant] in CoreSyn
+-- See Note [Core let/app invariant] in GHC.Core
-- Reason: we don't want to inline single uses, or discard dead bindings,
-- for unlifted, side-effect-ful bindings
postInlineUnconditionally env top_lvl bndr occ_info rhs
@@ -1517,7 +1517,7 @@ tryEtaExpandRhs mode bndr rhs
-- Note [Do not eta-expand join points]
-- But do return the correct arity and bottom-ness, because
-- these are used to set the bndr's IdInfo (#15517)
- -- Note [Invariants on join points] invariant 2b, in CoreSyn
+ -- Note [Invariants on join points] invariant 2b, in GHC.Core
| otherwise
= do { (new_arity, is_bot, new_rhs) <- try_expand
@@ -1553,7 +1553,7 @@ Note [Eta-expanding at let bindings]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
We now eta expand at let-bindings, which is where the payoff comes.
The most significant thing is that we can do a simple arity analysis
-(in CoreArity.findRhsArity), which we can't do for free-floating lambdas
+(in GHC.Core.Arity.findRhsArity), which we can't do for free-floating lambdas
One useful consequence of not eta-expanding lambdas is this example:
genMap :: C a => ...
@@ -1747,21 +1747,21 @@ abstractFloats dflags top_lvl main_tvs floats body
= ASSERT( notNull body_floats )
ASSERT( isNilOL (sfJoinFloats floats) )
do { (subst, float_binds) <- mapAccumLM abstract empty_subst body_floats
- ; return (float_binds, CoreSubst.substExpr (text "abstract_floats1") subst body) }
+ ; return (float_binds, GHC.Core.Subst.substExpr (text "abstract_floats1") subst body) }
where
is_top_lvl = isTopLevel top_lvl
main_tv_set = mkVarSet main_tvs
body_floats = letFloatBinds (sfLetFloats floats)
- empty_subst = CoreSubst.mkEmptySubst (sfInScope floats)
+ empty_subst = GHC.Core.Subst.mkEmptySubst (sfInScope floats)
- abstract :: CoreSubst.Subst -> OutBind -> SimplM (CoreSubst.Subst, OutBind)
+ abstract :: GHC.Core.Subst.Subst -> OutBind -> SimplM (GHC.Core.Subst.Subst, OutBind)
abstract subst (NonRec id rhs)
= do { (poly_id1, poly_app) <- mk_poly1 tvs_here id
; let (poly_id2, poly_rhs) = mk_poly2 poly_id1 tvs_here rhs'
- subst' = CoreSubst.extendIdSubst subst id poly_app
+ subst' = GHC.Core.Subst.extendIdSubst subst id poly_app
; return (subst', NonRec poly_id2 poly_rhs) }
where
- rhs' = CoreSubst.substExpr (text "abstract_floats2") subst rhs
+ rhs' = GHC.Core.Subst.substExpr (text "abstract_floats2") subst rhs
-- tvs_here: see Note [Which type variables to abstract over]
tvs_here = scopedSort $
@@ -1771,10 +1771,10 @@ abstractFloats dflags top_lvl main_tvs floats body
abstract subst (Rec prs)
= do { (poly_ids, poly_apps) <- mapAndUnzipM (mk_poly1 tvs_here) ids
- ; let subst' = CoreSubst.extendSubstList subst (ids `zip` poly_apps)
+ ; let subst' = GHC.Core.Subst.extendSubstList subst (ids `zip` poly_apps)
poly_pairs = [ mk_poly2 poly_id tvs_here rhs'
| (poly_id, rhs) <- poly_ids `zip` rhss
- , let rhs' = CoreSubst.substExpr (text "abstract_floats")
+ , let rhs' = GHC.Core.Subst.substExpr (text "abstract_floats")
subst' rhs ]
; return (subst', Rec poly_pairs) }
where
@@ -2207,7 +2207,7 @@ mkCase2 dflags scrut bndr alts_ty alts
re_sort :: [CoreAlt] -> [CoreAlt]
-- Sort the alternatives to re-establish
- -- CoreSyn Note [Case expression invariants]
+ -- GHC.Core Note [Case expression invariants]
re_sort alts = sortBy cmpAlt alts
add_default :: [CoreAlt] -> [CoreAlt]
diff --git a/compiler/simplCore/Simplify.hs b/compiler/simplCore/Simplify.hs
index 0c3e0f788b..ad8557b0a4 100644
--- a/compiler/simplCore/Simplify.hs
+++ b/compiler/simplCore/Simplify.hs
@@ -23,8 +23,8 @@ import FamInstEnv ( FamInstEnv )
import Literal ( litIsLifted ) --, mkLitInt ) -- temporalily commented out. See #8326
import Id
import MkId ( seqId )
-import MkCore ( FloatBind, mkImpossibleExpr, castBottomExpr )
-import qualified MkCore as MkCore
+import GHC.Core.Make ( FloatBind, mkImpossibleExpr, castBottomExpr )
+import qualified GHC.Core.Make
import IdInfo
import Name ( mkSystemVarName, isExternalName, getOccFS )
import Coercion hiding ( substCo, substCoVar )
@@ -34,16 +34,16 @@ import DataCon ( DataCon, dataConWorkId, dataConRepStrictness
, dataConRepArgTys, isUnboxedTupleCon
, StrictnessMark (..) )
import CoreMonad ( Tick(..), SimplMode(..) )
-import CoreSyn
+import GHC.Core
import Demand ( StrictSig(..), dmdTypeDepth, isStrictDmd
, mkClosedStrictSig, topDmd, botDiv )
import Cpr ( mkCprSig, botCpr )
-import PprCore ( pprCoreExpr )
-import CoreUnfold
-import CoreUtils
-import CoreOpt ( pushCoTyArg, pushCoValArg
- , joinPointBinding_maybe, joinPointBindings_maybe )
-import Rules ( mkRuleInfo, lookupRule, getRules )
+import GHC.Core.Ppr ( pprCoreExpr )
+import GHC.Core.Unfold
+import GHC.Core.Utils
+import GHC.Core.SimpleOpt ( pushCoTyArg, pushCoValArg
+ , joinPointBinding_maybe, joinPointBindings_maybe )
+import GHC.Core.Rules ( mkRuleInfo, lookupRule, getRules )
import BasicTypes ( TopLevelFlag(..), isNotTopLevel, isTopLevel,
RecFlag(..), Arity )
import MonadUtils ( mapAccumLM, liftIO )
@@ -386,7 +386,7 @@ completeNonRecX :: TopLevelFlag -> SimplEnv
-> OutExpr -- Simplified RHS
-> SimplM (SimplFloats, SimplEnv) -- The new binding is in the floats
-- Precondition: rhs satisfies the let/app invariant
--- See Note [CoreSyn let/app invariant] in CoreSyn
+-- See Note [Core let/app invariant] in GHC.Core
completeNonRecX top_lvl env is_strict old_bndr new_bndr new_rhs
= ASSERT2( not (isJoinId new_bndr), ppr new_bndr )
@@ -634,7 +634,7 @@ We want to turn this into:
foo1 = "blob"#
foo = Ptr foo1
-See Note [CoreSyn top-level string literals] in CoreSyn.
+See Note [Core top-level string literals] in GHC.Core.
************************************************************************
* *
@@ -782,7 +782,7 @@ propagate the info that x's RHS is bottom to x's IdInfo as rapidly as
possible.
We use tryEtaExpandRhs on every binding, and it turns ou that the
-arity computation it performs (via CoreArity.findRhsArity) already
+arity computation it performs (via GHC.Core.Arity.findRhsArity) already
does a simple bottoming-expression analysis. So all we need to do
is propagate that info to the binder's IdInfo.
@@ -1173,7 +1173,7 @@ simplTick env tickish expr cont
splitCont other = (mkBoringStop (contHoleType other), other)
getDoneId (DoneId id) = id
- getDoneId (DoneEx e _) = getIdFromTrivialExpr e -- Note [substTickish] in CoreSubst
+ getDoneId (DoneEx e _) = getIdFromTrivialExpr e -- Note [substTickish] in GHC.Core.Subst
getDoneId other = pprPanic "getDoneId" (ppr other)
-- Note [case-of-scc-of-case]
@@ -1326,7 +1326,7 @@ simplCast env body co0 cont0
| Just (co1, m_co2) <- pushCoValArg co
, let new_ty = coercionRKind co1
, not (isTypeLevPoly new_ty) -- Without this check, we get a lev-poly arg
- -- See Note [Levity polymorphism invariants] in CoreSyn
+ -- See Note [Levity polymorphism invariants] in GHC.Core
-- test: typecheck/should_run/EtaExpandLevPoly
= {-#SCC "addCoerce-pushCoValArg" #-}
do { tail' <- addCoerceM m_co2 tail
@@ -1457,7 +1457,7 @@ simplNonRecE :: SimplEnv
-- which may abort the whole process
--
-- Precondition: rhs satisfies the let/app invariant
--- Note [CoreSyn let/app invariant] in CoreSyn
+-- Note [Core let/app invariant] in GHC.Core
--
-- The "body" of the binding comes as a pair of ([InId],InExpr)
-- representing a lambda; so we recurse back to simplLam
@@ -2314,7 +2314,7 @@ We treat the unlifted and lifted cases separately:
we won't build a thunk because the let is strict.
See also Note [Case-to-let for strictly-used binders]
- NB: absentError satisfies exprIsHNF: see Note [aBSENT_ERROR_ID] in MkCore.
+ NB: absentError satisfies exprIsHNF: see Note [aBSENT_ERROR_ID] in GHC.Core.Make.
We want to turn
case (absentError "foo") of r -> ...MkT r...
into
@@ -2346,7 +2346,7 @@ this transformation. If you want to fix the evaluation order, use
'pseq'. See #8900 for an example where the loss of this
transformation bit us in practice.
-See also Note [Empty case alternatives] in CoreSyn.
+See also Note [Empty case alternatives] in GHC.Core.
Historical notes
@@ -2377,7 +2377,7 @@ There have been various earlier versions of this patch:
case_bndr_evald_next _ = False
This patch was part of fixing #7542. See also
- Note [Eta reduction of an eval'd function] in CoreUtils.)
+ Note [Eta reduction of an eval'd function] in GHC.Core.Utils.)
Further notes about case elimination
@@ -2491,7 +2491,7 @@ rebuildCase env scrut case_bndr alts cont
_ -> return
-- See Note [FloatBinds from constructor wrappers]
( emptyFloats env,
- MkCore.wrapFloats wfloats $
+ GHC.Core.Make.wrapFloats wfloats $
wrapFloats (floats1 `addFloats` floats2) expr' )}
@@ -2551,8 +2551,8 @@ doCaseToLet :: OutExpr -- Scrutinee
-- The situation is case scrut of b { DEFAULT -> body }
-- Can we transform thus? let { b = scrut } in body
doCaseToLet scrut case_bndr
- | isTyCoVar case_bndr -- Respect CoreSyn
- = isTyCoArg scrut -- Note [CoreSyn type and coercion invariant]
+ | isTyCoVar case_bndr -- Respect GHC.Core
+ = isTyCoArg scrut -- Note [Core type and coercion invariant]
| isUnliftedType (idType case_bndr)
= exprOkForSpeculation scrut
@@ -2936,7 +2936,7 @@ knownCon env scrut dc_floats dc dc_ty_args dc_args bndr bs rhs cont
_ ->
return ( emptyFloats env
-- See Note [FloatBinds from constructor wrappers]
- , MkCore.wrapFloats dc_floats $
+ , GHC.Core.Make.wrapFloats dc_floats $
wrapFloats (floats1 `addFloats` floats2 `addFloats` floats3) expr') }
where
zap_occ = zapBndrOccInfo (isDeadBinder bndr) -- bndr is an InId
@@ -3556,7 +3556,7 @@ simplStableUnfolding env top_lvl mb_cont id unf rhs_ty
-- But retain a previous boring_ok of True; e.g. see
-- the way it is set in calcUnfoldingGuidanceWithArity
in return (mkCoreUnfolding src is_top_lvl expr' guide')
- -- See Note [Top-level flag on inline rules] in CoreUnfold
+ -- See Note [Top-level flag on inline rules] in GHC.Core.Unfold
_other -- Happens for INLINABLE things
-> mkLetUnfolding dflags top_lvl src id expr' }
diff --git a/compiler/specialise/SpecConstr.hs b/compiler/specialise/SpecConstr.hs
index f477aed400..b681adfee1 100644
--- a/compiler/specialise/SpecConstr.hs
+++ b/compiler/specialise/SpecConstr.hs
@@ -23,29 +23,29 @@ module SpecConstr(
import GhcPrelude
-import CoreSyn
-import CoreSubst
-import CoreUtils
-import CoreUnfold ( couldBeSmallEnoughToInline )
-import CoreFVs ( exprsFreeVarsList )
+import GHC.Core
+import GHC.Core.Subst
+import GHC.Core.Utils
+import GHC.Core.Unfold ( couldBeSmallEnoughToInline )
+import GHC.Core.FVs ( exprsFreeVarsList )
import CoreMonad
import Literal ( litIsLifted )
-import GHC.Driver.Types ( ModGuts(..) )
+import GHC.Driver.Types ( ModGuts(..) )
import WwLib ( isWorkerSmallEnough, mkWorkerArgs )
import DataCon
import Coercion hiding( substCo )
-import Rules
+import GHC.Core.Rules
import Type hiding ( substTy )
import TyCon ( tyConName )
import Id
-import PprCore ( pprParendExpr )
-import MkCore ( mkImpossibleExpr )
+import GHC.Core.Ppr ( pprParendExpr )
+import GHC.Core.Make ( mkImpossibleExpr )
import VarEnv
import VarSet
import Name
import BasicTypes
-import GHC.Driver.Session ( DynFlags(..), GeneralFlag( Opt_SpecConstrKeen )
- , gopt, hasPprDebug )
+import GHC.Driver.Session ( DynFlags(..), GeneralFlag( Opt_SpecConstrKeen )
+ , gopt, hasPprDebug )
import Maybes ( orElse, catMaybes, isJust, isNothing )
import Demand
import Cpr
@@ -2154,7 +2154,7 @@ argToPat env in_scope val_env (Tick _ arg) arg_occ
-- Ignore Notes. In particular, we want to ignore any InlineMe notes
-- Perhaps we should not ignore profiling notes, but I'm going to
-- ride roughshod over them all for now.
- --- See Note [Notes in RULE matching] in Rules
+ --- See Note [Notes in RULE matching] in GHC.Core.Rules
argToPat env in_scope val_env (Let _ arg) arg_occ
= argToPat env in_scope val_env arg arg_occ
@@ -2241,7 +2241,7 @@ argToPat env in_scope val_env (Var v) arg_occ
-- And by not wild-carding we tend to get forall'd
-- variables that are in scope, which in turn can
-- expose the weakness in let-matching
--- See Note [Matching lets] in Rules
+-- See Note [Matching lets] in GHC.Core.Rules
-- Check for a variable bound inside the function.
-- Don't make a wild-card, because we may usefully share
diff --git a/compiler/specialise/Specialise.hs b/compiler/specialise/Specialise.hs
index 60bb890461..6ef320f8af 100644
--- a/compiler/specialise/Specialise.hs
+++ b/compiler/specialise/Specialise.hs
@@ -22,17 +22,17 @@ import Predicate
import Module( Module, HasModule(..) )
import Coercion( Coercion )
import CoreMonad
-import qualified CoreSubst
-import CoreUnfold
+import qualified GHC.Core.Subst
+import GHC.Core.Unfold
import Var ( isLocalVar )
import VarSet
import VarEnv
-import CoreSyn
-import Rules
-import CoreOpt ( collectBindersPushingCo )
-import CoreUtils ( exprIsTrivial, mkCast, exprType )
-import CoreFVs
-import CoreArity ( etaExpandToJoinPointRule )
+import GHC.Core
+import GHC.Core.Rules
+import GHC.Core.SimpleOpt ( collectBindersPushingCo )
+import GHC.Core.Utils ( exprIsTrivial, mkCast, exprType )
+import GHC.Core.FVs
+import GHC.Core.Arity ( etaExpandToJoinPointRule )
import UniqSupply
import Name
import MkId ( voidArgId, voidPrimId )
@@ -607,7 +607,7 @@ specProgram guts@(ModGuts { mg_module = this_mod
-- accidentally re-use a unique that's already in use
-- Easiest thing is to do it all at once, as if all the top-level
-- decls were mutually recursive
- top_env = SE { se_subst = CoreSubst.mkEmptySubst $ mkInScopeSet $ mkVarSet $
+ top_env = SE { se_subst = GHC.Core.Subst.mkEmptySubst $ mkInScopeSet $ mkVarSet $
bindersOfBinds binds
, se_interesting = emptyVarSet }
@@ -1036,7 +1036,7 @@ Avoiding this recursive specialisation loop is the reason for the
-}
data SpecEnv
- = SE { se_subst :: CoreSubst.Subst
+ = SE { se_subst :: GHC.Core.Subst.Subst
-- We carry a substitution down:
-- a) we must clone any binding that might float outwards,
-- to avoid name clashes
@@ -1051,7 +1051,7 @@ data SpecEnv
}
specVar :: SpecEnv -> Id -> CoreExpr
-specVar env v = CoreSubst.lookupIdSubst (text "specVar") (se_subst env) v
+specVar env v = GHC.Core.Subst.lookupIdSubst (text "specVar") (se_subst env) v
specExpr :: SpecEnv -> CoreExpr -> SpecM (CoreExpr, UsageDetails)
@@ -1144,7 +1144,7 @@ specCase env scrut' case_bndr [(con, args, rhs)]
subst_prs = (case_bndr, Var case_bndr_flt)
: [ (arg, Var sc_flt)
| (arg, Just sc_flt) <- args `zip` mb_sc_flts ]
- env_rhs' = env_rhs { se_subst = CoreSubst.extendIdSubstList (se_subst env_rhs) subst_prs
+ env_rhs' = env_rhs { se_subst = GHC.Core.Subst.extendIdSubstList (se_subst env_rhs) subst_prs
, se_interesting = se_interesting env_rhs `extendVarSetList`
(case_bndr_flt : sc_args_flt) }
@@ -1402,7 +1402,7 @@ specCalls mb_mod env existing_rules calls_for_me fn rhs
-- See Note [Account for casts in binding]
rhs_tyvars = filter isTyVar rhs_bndrs
- in_scope = CoreSubst.substInScope (se_subst env)
+ in_scope = GHC.Core.Subst.substInScope (se_subst env)
already_covered :: DynFlags -> [CoreRule] -> [CoreExpr] -> Bool
already_covered dflags new_rules args -- Note [Specialisations already covered]
@@ -1691,9 +1691,9 @@ bindAuxiliaryDicts env@(SE { se_subst = subst, se_interesting = interesting })
= (env', dx_binds, spec_dict_args)
where
(dx_binds, spec_dict_args) = go call_ds inst_dict_ids
- env' = env { se_subst = subst `CoreSubst.extendSubstList`
+ env' = env { se_subst = subst `GHC.Core.Subst.extendSubstList`
(orig_dict_ids `zip` spec_dict_args)
- `CoreSubst.extendInScopeList` dx_ids
+ `GHC.Core.Subst.extendInScopeList` dx_ids
, se_interesting = interesting `unionVarSet` interesting_dicts }
dx_ids = [dx_id | (NonRec dx_id _, _) <- dx_binds]
@@ -2595,20 +2595,20 @@ mapAndCombineSM f (x:xs) = do (y, uds1) <- f x
extendTvSubstList :: SpecEnv -> [(TyVar,Type)] -> SpecEnv
extendTvSubstList env tv_binds
- = env { se_subst = CoreSubst.extendTvSubstList (se_subst env) tv_binds }
+ = env { se_subst = GHC.Core.Subst.extendTvSubstList (se_subst env) tv_binds }
substTy :: SpecEnv -> Type -> Type
-substTy env ty = CoreSubst.substTy (se_subst env) ty
+substTy env ty = GHC.Core.Subst.substTy (se_subst env) ty
substCo :: SpecEnv -> Coercion -> Coercion
-substCo env co = CoreSubst.substCo (se_subst env) co
+substCo env co = GHC.Core.Subst.substCo (se_subst env) co
substBndr :: SpecEnv -> CoreBndr -> (SpecEnv, CoreBndr)
-substBndr env bs = case CoreSubst.substBndr (se_subst env) bs of
+substBndr env bs = case GHC.Core.Subst.substBndr (se_subst env) bs of
(subst', bs') -> (env { se_subst = subst' }, bs')
substBndrs :: SpecEnv -> [CoreBndr] -> (SpecEnv, [CoreBndr])
-substBndrs env bs = case CoreSubst.substBndrs (se_subst env) bs of
+substBndrs env bs = case GHC.Core.Subst.substBndrs (se_subst env) bs of
(subst', bs') -> (env { se_subst = subst' }, bs')
cloneBindSM :: SpecEnv -> CoreBind -> SpecM (SpecEnv, SpecEnv, CoreBind)
@@ -2616,7 +2616,7 @@ cloneBindSM :: SpecEnv -> CoreBind -> SpecM (SpecEnv, SpecEnv, CoreBind)
-- Return the substitution to use for RHSs, and the one to use for the body
cloneBindSM env@(SE { se_subst = subst, se_interesting = interesting }) (NonRec bndr rhs)
= do { us <- getUniqueSupplyM
- ; let (subst', bndr') = CoreSubst.cloneIdBndr subst us bndr
+ ; let (subst', bndr') = GHC.Core.Subst.cloneIdBndr subst us bndr
interesting' | interestingDict env rhs
= interesting `extendVarSet` bndr'
| otherwise = interesting
@@ -2625,7 +2625,7 @@ cloneBindSM env@(SE { se_subst = subst, se_interesting = interesting }) (NonRec
cloneBindSM env@(SE { se_subst = subst, se_interesting = interesting }) (Rec pairs)
= do { us <- getUniqueSupplyM
- ; let (subst', bndrs') = CoreSubst.cloneRecIdBndrs subst us (map fst pairs)
+ ; let (subst', bndrs') = GHC.Core.Subst.cloneRecIdBndrs subst us (map fst pairs)
env' = env { se_subst = subst'
, se_interesting = interesting `extendVarSetList`
[ v | (v,r) <- pairs, interestingDict env r ] }
diff --git a/compiler/stranal/CprAnal.hs b/compiler/stranal/CprAnal.hs
index 3691b213b8..1f244d7a0e 100644
--- a/compiler/stranal/CprAnal.hs
+++ b/compiler/stranal/CprAnal.hs
@@ -17,8 +17,8 @@ import WwLib ( deepSplitProductType_maybe )
import GHC.Driver.Session
import Demand
import Cpr
-import CoreSyn
-import CoreSeq
+import GHC.Core
+import GHC.Core.Seq
import Outputable
import VarEnv
import BasicTypes
@@ -26,7 +26,7 @@ import Data.List
import DataCon
import Id
import IdInfo
-import CoreUtils ( exprIsHNF, dumpIdInfoOfProgram )
+import GHC.Core.Utils ( exprIsHNF, dumpIdInfoOfProgram )
import TyCon
import Type
import FamInstEnv
diff --git a/compiler/stranal/DmdAnal.hs b/compiler/stranal/DmdAnal.hs
index da771e4412..5c5181da12 100644
--- a/compiler/stranal/DmdAnal.hs
+++ b/compiler/stranal/DmdAnal.hs
@@ -18,8 +18,8 @@ import GhcPrelude
import GHC.Driver.Session
import WwLib ( findTypeShape )
import Demand -- All of it
-import CoreSyn
-import CoreSeq ( seqBinds )
+import GHC.Core
+import GHC.Core.Seq ( seqBinds )
import Outputable
import VarEnv
import BasicTypes
@@ -27,7 +27,7 @@ import Data.List ( mapAccumL )
import DataCon
import Id
import IdInfo
-import CoreUtils
+import GHC.Core.Utils
import TyCon
import Type
import Coercion ( Coercion, coVarsOfCo )
@@ -590,7 +590,7 @@ dmdAnalRhsLetDown rec_flag env let_dmd id rhs
rhs_arity = idArity id
rhs_dmd
-- See Note [Demand analysis for join points]
- -- See Note [Invariants on join points] invariant 2b, in CoreSyn
+ -- See Note [Invariants on join points] invariant 2b, in GHC.Core
-- rhs_arity matches the join arity of the join point
| isJoinId id
= mkCallDmds rhs_arity let_dmd
@@ -768,7 +768,7 @@ complexity.
Note [idArity varies independently of dmdTypeDepth]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-We used to check in CoreLint that dmdTypeDepth <= idArity for a let-bound
+We used to check in GHC.Core.Lint that dmdTypeDepth <= idArity for a let-bound
identifier. But that means we would have to zap demand signatures every time we
reset or decrease arity. That's an unnecessary dependency, because
@@ -852,9 +852,9 @@ we want plusInt's strictness to propagate to foo! But because it has
no manifest lambdas, it won't do so automatically, and indeed 'co' might
have type (Int->Int->Int) ~ T.
-Fortunately, CoreArity gives 'foo' arity 2, which is enough for LetDown to
+Fortunately, GHC.Core.Arity gives 'foo' arity 2, which is enough for LetDown to
forward plusInt's demand signature, and all is well (see Note [Newtype arity] in
-CoreArity)! A small example is the test case NewtypeArity.
+GHC.Core.Arity)! A small example is the test case NewtypeArity.
Note [Product demands for function body]
diff --git a/compiler/stranal/WorkWrap.hs b/compiler/stranal/WorkWrap.hs
index 4e579d67b8..070b2f9046 100644
--- a/compiler/stranal/WorkWrap.hs
+++ b/compiler/stranal/WorkWrap.hs
@@ -9,11 +9,11 @@ module WorkWrap ( wwTopBinds ) where
import GhcPrelude
-import CoreArity ( manifestArity )
-import CoreSyn
-import CoreUnfold ( certainlyWillInline, mkWwInlineRule, mkWorkerUnfolding )
-import CoreUtils ( exprType, exprIsHNF )
-import CoreFVs ( exprFreeVars )
+import GHC.Core.Arity ( manifestArity )
+import GHC.Core
+import GHC.Core.Unfold ( certainlyWillInline, mkWwInlineRule, mkWorkerUnfolding )
+import GHC.Core.Utils ( exprType, exprIsHNF )
+import GHC.Core.FVs ( exprFreeVars )
import Var
import Id
import IdInfo
@@ -201,7 +201,7 @@ unfolding to the *worker*. So we will get something like this:
fw d x y' = let y = I# y' in ...f...
How do we "transfer the unfolding"? Easy: by using the old one, wrapped
-in work_fn! See CoreUnfold.mkWorkerUnfolding.
+in work_fn! See GHC.Core.Unfold.mkWorkerUnfolding.
Note [Worker-wrapper for NOINLINE functions]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
@@ -534,12 +534,12 @@ Note [Zapping DmdEnv after Demand Analyzer] above.
Note [Don't eta expand in w/w]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
A binding where the manifestArity of the RHS is less than idArity of the binder
-means CoreArity didn't eta expand that binding. When this happens, it does so
-for a reason (see Note [exprArity invariant] in CoreArity) and we probably have
+means GHC.Core.Arity didn't eta expand that binding. When this happens, it does so
+for a reason (see Note [exprArity invariant] in GHC.Core.Arity) and we probably have
a PAP, cast or trivial expression as RHS.
Performing the worker/wrapper split will implicitly eta-expand the binding to
-idArity, overriding CoreArity's decision. Other than playing fast and loose with
+idArity, overriding GHC.Core.Arity's decision. Other than playing fast and loose with
divergence, it's also broken for newtypes:
f = (\xy.blah) |> co
diff --git a/compiler/stranal/WwLib.hs b/compiler/stranal/WwLib.hs
index 8163792b5b..5d4325766b 100644
--- a/compiler/stranal/WwLib.hs
+++ b/compiler/stranal/WwLib.hs
@@ -15,14 +15,14 @@ module WwLib ( mkWwBodies, mkWWstr, mkWorkerArgs
import GhcPrelude
-import CoreSyn
-import CoreUtils ( exprType, mkCast, mkDefaultCase, mkSingleAltCase )
+import GHC.Core
+import GHC.Core.Utils ( exprType, mkCast, mkDefaultCase, mkSingleAltCase )
import Id
import IdInfo ( JoinArity )
import DataCon
import Demand
import Cpr
-import MkCore ( mkAbsentErrorApp, mkCoreUbxTup
+import GHC.Core.Make ( mkAbsentErrorApp, mkCoreUbxTup
, mkCoreApp, mkCoreLet )
import MkId ( voidArgId, voidPrimId )
import TysWiredIn ( tupleDataCon )
diff --git a/compiler/typecheck/ClsInst.hs b/compiler/typecheck/ClsInst.hs
index 41874f1807..b112bff74a 100644
--- a/compiler/typecheck/ClsInst.hs
+++ b/compiler/typecheck/ClsInst.hs
@@ -32,7 +32,7 @@ import PrelNames
import Id
import Type
-import MkCore ( mkStringExprFS, mkNaturalExpr )
+import GHC.Core.Make ( mkStringExprFS, mkNaturalExpr )
import Name ( Name, pprDefinedAt )
import VarEnv ( VarEnv )
diff --git a/compiler/typecheck/Constraint.hs b/compiler/typecheck/Constraint.hs
index 9bd18504b1..40fc8fdedb 100644
--- a/compiler/typecheck/Constraint.hs
+++ b/compiler/typecheck/Constraint.hs
@@ -92,7 +92,7 @@ import TcType
import TcEvidence
import TcOrigin
-import CoreSyn
+import GHC.Core
import TyCoPpr
import OccName
diff --git a/compiler/typecheck/FamInst.hs b/compiler/typecheck/FamInst.hs
index 748e9fd8bf..eb86ec0284 100644
--- a/compiler/typecheck/FamInst.hs
+++ b/compiler/typecheck/FamInst.hs
@@ -19,7 +19,7 @@ import GHC.Driver.Types
import FamInstEnv
import InstEnv( roughMatchTcs )
import Coercion
-import CoreLint
+import GHC.Core.Lint
import TcEvidence
import GHC.Iface.Load
import TcRnMonad
diff --git a/compiler/typecheck/Inst.hs b/compiler/typecheck/Inst.hs
index 525fa7ebf3..96b387b7ec 100644
--- a/compiler/typecheck/Inst.hs
+++ b/compiler/typecheck/Inst.hs
@@ -52,7 +52,7 @@ import TcEnv
import TcEvidence
import InstEnv
import TysWiredIn ( heqDataCon, eqDataCon )
-import CoreSyn ( isOrphan )
+import GHC.Core ( isOrphan )
import FunDeps
import TcMType
import Type
@@ -62,7 +62,7 @@ import TcType
import GHC.Driver.Types
import Class( Class )
import MkId( mkDictFunId )
-import CoreSyn( Expr(..) ) -- For the Coercion constructor
+import GHC.Core( Expr(..) ) -- For the Coercion constructor
import Id
import Name
import Var ( EvVar, tyVarName, VarBndr(..) )
diff --git a/compiler/typecheck/TcBinds.hs b/compiler/typecheck/TcBinds.hs
index f597d6daf9..cc2ee8ec84 100644
--- a/compiler/typecheck/TcBinds.hs
+++ b/compiler/typecheck/TcBinds.hs
@@ -20,7 +20,7 @@ import GhcPrelude
import {-# SOURCE #-} TcMatches ( tcGRHSsPat, tcMatchesFun )
import {-# SOURCE #-} TcExpr ( tcMonoExpr )
import {-# SOURCE #-} TcPatSyn ( tcPatSynDecl, tcPatSynBuilderBind )
-import CoreSyn (Tickish (..))
+import GHC.Core (Tickish (..))
import CostCentre (mkUserCC, CCFlavour(DeclCC))
import GHC.Driver.Session
import FastString
diff --git a/compiler/typecheck/TcCanonical.hs b/compiler/typecheck/TcCanonical.hs
index 9b79002311..7bbaa1ec99 100644
--- a/compiler/typecheck/TcCanonical.hs
+++ b/compiler/typecheck/TcCanonical.hs
@@ -27,7 +27,7 @@ import Class
import TyCon
import TyCoRep -- cleverly decomposes types, good for completeness checking
import Coercion
-import CoreSyn
+import GHC.Core
import Id( idType, mkTemplateLocals )
import FamInstEnv ( FamInstEnvs )
import FamInst ( tcTopNormaliseNewTypeTF_maybe )
diff --git a/compiler/typecheck/TcEvTerm.hs b/compiler/typecheck/TcEvTerm.hs
index 7812339d15..39e03180b7 100644
--- a/compiler/typecheck/TcEvTerm.hs
+++ b/compiler/typecheck/TcEvTerm.hs
@@ -8,15 +8,15 @@ import GhcPrelude
import FastString
import Type
-import CoreSyn
-import MkCore
+import GHC.Core
+import GHC.Core.Make
import Literal ( Literal(..) )
import TcEvidence
import GHC.Driver.Types
import GHC.Driver.Session
import Name
import Module
-import CoreUtils
+import GHC.Core.Utils
import PrelNames
import SrcLoc
diff --git a/compiler/typecheck/TcEvidence.hs b/compiler/typecheck/TcEvidence.hs
index 0794157ed0..89bf4149b7 100644
--- a/compiler/typecheck/TcEvidence.hs
+++ b/compiler/typecheck/TcEvidence.hs
@@ -58,7 +58,7 @@ import GhcPrelude
import Var
import CoAxiom
import Coercion
-import PprCore () -- Instance OutputableBndr TyVar
+import GHC.Core.Ppr () -- Instance OutputableBndr TyVar
import TcType
import Type
import TyCon
@@ -71,9 +71,9 @@ import Predicate
import Name
import Pair
-import CoreSyn
+import GHC.Core
import Class ( classSCSelId )
-import CoreFVs ( exprSomeFreeVars )
+import GHC.Core.FVs ( exprSomeFreeVars )
import Util
import Bag
diff --git a/compiler/typecheck/TcExpr.hs b/compiler/typecheck/TcExpr.hs
index 16b0f26ed1..f5e92ffe7d 100644
--- a/compiler/typecheck/TcExpr.hs
+++ b/compiler/typecheck/TcExpr.hs
@@ -440,7 +440,7 @@ tcExpr expr@(ExplicitTuple x tup_args boxity) res_ty
= do { let arity = length tup_args
tup_tc = tupleTyCon boxity arity
-- NB: tupleTyCon doesn't flatten 1-tuples
- -- See Note [Don't flatten tuples from HsSyn] in MkCore
+ -- See Note [Don't flatten tuples from HsSyn] in GHC.Core.Make
; res_ty <- expTypeToType res_ty
; (coi, arg_tys) <- matchExpectedTyConApp tup_tc res_ty
-- Unboxed tuples have RuntimeRep vars, which we
@@ -461,7 +461,7 @@ tcExpr expr@(ExplicitTuple x tup_args boxity) res_ty
; let actual_res_ty
= mkVisFunTys [ty | (ty, (L _ (Missing _))) <- arg_tys `zip` tup_args]
(mkTupleTy1 boxity arg_tys)
- -- See Note [Don't flatten tuples from HsSyn] in MkCore
+ -- See Note [Don't flatten tuples from HsSyn] in GHC.Core.Make
; wrap <- tcSubTypeHR (Shouldn'tHappenOrigin "ExpTuple")
(Just expr)
diff --git a/compiler/typecheck/TcHsSyn.hs b/compiler/typecheck/TcHsSyn.hs
index 7dfb3ff1ab..1ccd8aced2 100644
--- a/compiler/typecheck/TcHsSyn.hs
+++ b/compiler/typecheck/TcHsSyn.hs
@@ -83,7 +83,7 @@ import Bag
import Outputable
import Util
import UniqFM
-import CoreSyn
+import GHC.Core
import {-# SOURCE #-} TcSplice (runTopSplice)
@@ -115,7 +115,7 @@ hsPatType (ViewPat ty _ _) = ty
hsPatType (ListPat (ListPatTc ty Nothing) _) = mkListTy ty
hsPatType (ListPat (ListPatTc _ (Just (ty,_))) _) = ty
hsPatType (TuplePat tys _ bx) = mkTupleTy1 bx tys
- -- See Note [Don't flatten tuples from HsSyn] in MkCore
+ -- See Note [Don't flatten tuples from HsSyn] in GHC.Core.Make
hsPatType (SumPat tys _ _ _ ) = mkSumTy tys
hsPatType (ConPatOut { pat_con = lcon
, pat_arg_tys = tys })
diff --git a/compiler/typecheck/TcInstDcls.hs b/compiler/typecheck/TcInstDcls.hs
index 09720f57ca..68ed568e05 100644
--- a/compiler/typecheck/TcInstDcls.hs
+++ b/compiler/typecheck/TcInstDcls.hs
@@ -44,9 +44,9 @@ import TcDeriv
import TcEnv
import TcHsType
import TcUnify
-import CoreSyn ( Expr(..), mkApps, mkVarApps, mkLams )
-import MkCore ( nO_METHOD_BINDING_ERROR_ID )
-import CoreUnfold ( mkInlineUnfoldingWithArity, mkDFunUnfolding )
+import GHC.Core ( Expr(..), mkApps, mkVarApps, mkLams )
+import GHC.Core.Make ( nO_METHOD_BINDING_ERROR_ID )
+import GHC.Core.Unfold ( mkInlineUnfoldingWithArity, mkDFunUnfolding )
import Type
import TcEvidence
import TyCon
@@ -189,7 +189,7 @@ Instead we use a cunning trick.
* We give 'df' a magical unfolding (DFunUnfolding [$cop1, $cop2, ..])
that lists its methods.
- * We make CoreUnfold.exprIsConApp_maybe spot a DFunUnfolding and return
+ * We make GHC.Core.Unfold.exprIsConApp_maybe spot a DFunUnfolding and return
a suitable constructor application -- inlining df "on the fly" as it
were.
diff --git a/compiler/typecheck/TcInteract.hs b/compiler/typecheck/TcInteract.hs
index 90cc412318..ce3cc9ffaf 100644
--- a/compiler/typecheck/TcInteract.hs
+++ b/compiler/typecheck/TcInteract.hs
@@ -45,7 +45,7 @@ import TcSMonad
import Bag
import MonadUtils ( concatMapM, foldlM )
-import CoreSyn
+import GHC.Core
import Data.List( partition, deleteFirstsBy )
import SrcLoc
import VarEnv
diff --git a/compiler/typecheck/TcMatches.hs b/compiler/typecheck/TcMatches.hs
index 8088602972..262e7ccf2c 100644
--- a/compiler/typecheck/TcMatches.hs
+++ b/compiler/typecheck/TcMatches.hs
@@ -48,7 +48,7 @@ import Util
import SrcLoc
-- Create chunkified tuple tybes for monad comprehensions
-import MkCore
+import GHC.Core.Make
import Control.Monad
import Control.Arrow ( second )
diff --git a/compiler/typecheck/TcPat.hs b/compiler/typecheck/TcPat.hs
index 8a3b154fe6..9f298bfdad 100644
--- a/compiler/typecheck/TcPat.hs
+++ b/compiler/typecheck/TcPat.hs
@@ -451,7 +451,7 @@ tc_pat penv (TuplePat _ pats boxity) pat_ty thing_inside
= do { let arity = length pats
tc = tupleTyCon boxity arity
-- NB: tupleTyCon does not flatten 1-tuples
- -- See Note [Don't flatten tuples from HsSyn] in MkCore
+ -- See Note [Don't flatten tuples from HsSyn] in GHC.Core.Make
; (coi, arg_tys) <- matchExpectedPatTy (matchExpectedTyConApp tc)
penv pat_ty
-- Unboxed tuples have RuntimeRep vars, which we discard:
diff --git a/compiler/typecheck/TcRnDriver.hs b/compiler/typecheck/TcRnDriver.hs
index 8f87554349..930dc3c15a 100644
--- a/compiler/typecheck/TcRnDriver.hs
+++ b/compiler/typecheck/TcRnDriver.hs
@@ -80,8 +80,8 @@ import TcEvidence
import Constraint
import TcOrigin
import qualified BooleanFormula as BF
-import PprTyThing( pprTyThingInContext )
-import CoreFVs( orphNamesOfFamInst )
+import GHC.Core.Ppr.TyThing ( pprTyThingInContext )
+import GHC.Core.FVs ( orphNamesOfFamInst )
import FamInst
import InstEnv
import FamInstEnv( FamInst, pprFamInst, famInstsRepTyCons
diff --git a/compiler/typecheck/TcSMonad.hs b/compiler/typecheck/TcSMonad.hs
index ab838be5fa..737ac7da8c 100644
--- a/compiler/typecheck/TcSMonad.hs
+++ b/compiler/typecheck/TcSMonad.hs
@@ -175,7 +175,7 @@ import UniqFM
import UniqDFM
import Maybes
-import CoreMap
+import GHC.Core.Map
import Control.Monad
import qualified Control.Monad.Fail as MonadFail
import MonadUtils
diff --git a/compiler/typecheck/TcTyClsDecls.hs b/compiler/typecheck/TcTyClsDecls.hs
index 05112757c9..e712f79e1d 100644
--- a/compiler/typecheck/TcTyClsDecls.hs
+++ b/compiler/typecheck/TcTyClsDecls.hs
@@ -4332,7 +4332,7 @@ checkRoleAnnot tv (L _ (Just r1)) r2
-- -dcore-lint is enabled. See Note [Role inference] in TcTyDecls
checkValidRoles :: TyCon -> TcM ()
-- If you edit this function, you may need to update the GHC formalism
--- See Note [GHC Formalism] in CoreLint
+-- See Note [GHC Formalism] in GHC.Core.Lint
checkValidRoles tc
| isAlgTyCon tc
-- tyConDataCons returns an empty list for data families
diff --git a/compiler/typecheck/TcTyDecls.hs b/compiler/typecheck/TcTyDecls.hs
index bf18c06729..b9b51e11f7 100644
--- a/compiler/typecheck/TcTyDecls.hs
+++ b/compiler/typecheck/TcTyDecls.hs
@@ -40,7 +40,7 @@ import TyCoRep( Type(..), Coercion(..), MCoercion(..), UnivCoProvenance(..) )
import TcType
import Predicate
import TysWiredIn( unitTy )
-import MkCore( rEC_SEL_ERROR_ID )
+import GHC.Core.Make( rEC_SEL_ERROR_ID )
import GHC.Hs
import Class
import Type
diff --git a/compiler/typecheck/TcType.hs b/compiler/typecheck/TcType.hs
index 27fd90f6c6..ba4efcf35d 100644
--- a/compiler/typecheck/TcType.hs
+++ b/compiler/typecheck/TcType.hs
@@ -209,7 +209,7 @@ import TyCon
-- others:
import GHC.Driver.Session
-import CoreFVs
+import GHC.Core.FVs
import Name -- hiding (varName)
-- We use this to make dictionaries for type literals.
-- Perhaps there's a better way to do this?
diff --git a/compiler/typecheck/TcTypeable.hs b/compiler/typecheck/TcTypeable.hs
index b13d70f1dd..19d695f6d1 100644
--- a/compiler/typecheck/TcTypeable.hs
+++ b/compiler/typecheck/TcTypeable.hs
@@ -37,7 +37,7 @@ import GHC.Hs
import GHC.Driver.Session
import Bag
import Var ( VarBndr(..) )
-import CoreMap
+import GHC.Core.Map
import Constants
import Fingerprint(Fingerprint(..), fingerprintString, fingerprintFingerprints)
import Outputable
diff --git a/compiler/types/CoAxiom.hs b/compiler/types/CoAxiom.hs
index 7d824f6c10..066daefaed 100644
--- a/compiler/types/CoAxiom.hs
+++ b/compiler/types/CoAxiom.hs
@@ -203,7 +203,7 @@ of the branches.
-- | A 'CoAxiom' is a \"coercion constructor\", i.e. a named equality axiom.
-- If you edit this type, you may need to update the GHC formalism
--- See Note [GHC Formalism] in coreSyn/CoreLint.hs
+-- See Note [GHC Formalism] in GHC.Core.Lint
data CoAxiom br
= CoAxiom -- Type equality axiom.
{ co_ax_unique :: Unique -- Unique identifier
diff --git a/compiler/types/Coercion.hs b/compiler/types/Coercion.hs
index eba05f8386..858b7d8f61 100644
--- a/compiler/types/Coercion.hs
+++ b/compiler/types/Coercion.hs
@@ -6,7 +6,7 @@
ScopedTypeVariables #-}
-- | Module for (a) type kinds and (b) type coercions,
--- as used in System FC. See 'CoreSyn.Expr' for
+-- as used in System FC. See 'GHC.Core.Expr' for
-- more on System FC and how coercions fit into it.
--
module Coercion (
@@ -847,7 +847,7 @@ mkCoVarCos = map mkCoVarCo
{- Note [mkCoVarCo]
~~~~~~~~~~~~~~~~~~~
In the past, mkCoVarCo optimised (c :: t~t) to (Refl t). That is
-valid (although see Note [Unbound RULE binders] in Rules), but
+valid (although see Note [Unbound RULE binders] in GHC.Core.Rules), but
it's a relatively expensive test and perhaps better done in
optCoercion. Not a big deal either way.
-}
diff --git a/compiler/types/FamInstEnv.hs b/compiler/types/FamInstEnv.hs
index 56183e1495..de3e867944 100644
--- a/compiler/types/FamInstEnv.hs
+++ b/compiler/types/FamInstEnv.hs
@@ -55,7 +55,7 @@ import Name
import UniqDFM
import Outputable
import Maybes
-import CoreMap
+import GHC.Core.Map
import Unique
import Util
import Var
@@ -220,7 +220,7 @@ instance Outputable FamInst where
pprFamInst :: FamInst -> SDoc
-- Prints the FamInst as a family instance declaration
-- NB: This function, FamInstEnv.pprFamInst, is used only for internal,
--- debug printing. See PprTyThing.pprFamInst for printing for the user
+-- debug printing. See GHC.Core.Ppr.TyThing.pprFamInst for printing for the user
pprFamInst (FamInst { fi_flavor = flavor, fi_axiom = ax
, fi_tvs = tvs, fi_tys = tys, fi_rhs = rhs })
= hang (ppr_tc_sort <+> text "instance"
diff --git a/compiler/types/InstEnv.hs b/compiler/types/InstEnv.hs
index 94cabfb724..67325558b6 100644
--- a/compiler/types/InstEnv.hs
+++ b/compiler/types/InstEnv.hs
@@ -35,7 +35,7 @@ import GhcPrelude
import TcType -- InstEnv is really part of the type checker,
-- and depends on TcType in many ways
-import CoreSyn ( IsOrphan(..), isOrphan, chooseOrphanAnchor )
+import GHC.Core ( IsOrphan(..), isOrphan, chooseOrphanAnchor )
import Module
import Class
import Var
diff --git a/compiler/types/OptCoercion.hs b/compiler/types/OptCoercion.hs
index f73af0edf5..9819e210ab 100644
--- a/compiler/types/OptCoercion.hs
+++ b/compiler/types/OptCoercion.hs
@@ -967,7 +967,7 @@ The problem described here was first found in dependent/should_compile/dynamic-p
checkAxInstCo :: Coercion -> Maybe CoAxBranch
-- defined here to avoid dependencies in Coercion
-- If you edit this function, you may need to update the GHC formalism
--- See Note [GHC Formalism] in CoreLint
+-- See Note [GHC Formalism] in GHC.Core.Lint
checkAxInstCo (AxiomInstCo ax ind cos)
= let branch = coAxiomNthBranch ax ind
tvs = coAxBranchTyVars branch
diff --git a/compiler/types/TyCoPpr.hs b/compiler/types/TyCoPpr.hs
index e3581ba02a..f1a36feca9 100644
--- a/compiler/types/TyCoPpr.hs
+++ b/compiler/types/TyCoPpr.hs
@@ -76,7 +76,7 @@ See Note [Precedence in types] in BasicTypes.
--------------------------------------------------------
-- When pretty-printing types, we convert to IfaceType,
-- and pretty-print that.
--- See Note [Pretty printing via Iface syntax] in PprTyThing
+-- See Note [Pretty printing via Iface syntax] in GHC.Core.Ppr.TyThing
--------------------------------------------------------
pprType, pprParendType, pprTidiedType :: Type -> SDoc
diff --git a/compiler/types/TyCoRep.hs b/compiler/types/TyCoRep.hs
index 36744cbc19..75a031b799 100644
--- a/compiler/types/TyCoRep.hs
+++ b/compiler/types/TyCoRep.hs
@@ -139,7 +139,7 @@ instance NamedThing TyThing where -- Can't put this with the type
getName (AConLike cl) = conLikeName cl
pprShortTyThing :: TyThing -> SDoc
--- c.f. PprTyThing.pprTyThing, which prints all the details
+-- c.f. GHC.Core.Ppr.TyThing.pprTyThing, which prints all the details
pprShortTyThing thing
= pprTyThingCategory thing <+> quotes (ppr (getName thing))
@@ -170,7 +170,7 @@ type KindOrType = Type -- See Note [Arguments to type constructors]
type Kind = Type
-- If you edit this type, you may need to update the GHC formalism
--- See Note [GHC Formalism] in coreSyn/CoreLint.hs
+-- See Note [GHC Formalism] in GHC.Core.Lint
data Type
-- See Note [Non-trivial definitional equality]
= TyVarTy Var -- ^ Vanilla type or kind variable (*never* a coercion variable)
@@ -963,7 +963,7 @@ mkTyConTy tycon = TyConApp tycon []
-- of two types.
-- If you edit this type, you may need to update the GHC formalism
--- See Note [GHC Formalism] in coreSyn/CoreLint.hs
+-- See Note [GHC Formalism] in GHC.Core.Lint
data Coercion
-- Each constructor has a "role signature", indicating the way roles are
-- propagated through coercions.
diff --git a/compiler/types/TyCoSubst.hs b/compiler/types/TyCoSubst.hs
index 8a471eb40d..7248713219 100644
--- a/compiler/types/TyCoSubst.hs
+++ b/compiler/types/TyCoSubst.hs
@@ -135,7 +135,7 @@ the in-scope set in the substitution is a superset of both:
(SIa) The free vars of the range of the substitution
(SIb) The free vars of ty minus the domain of the substitution
-The same rules apply to other substitutions (notably CoreSubst.Subst)
+The same rules apply to other substitutions (notably GHC.Core.Subst.Subst)
* Reason for (SIa). Consider
substTy [a :-> Maybe b] (forall b. b->a)
diff --git a/compiler/types/TyCon.hs b/compiler/types/TyCon.hs
index d4bfe16a75..7f5fde2847 100644
--- a/compiler/types/TyCon.hs
+++ b/compiler/types/TyCon.hs
@@ -689,7 +689,7 @@ instance Binary TyConBndrVis where
-- such as those for function and tuple types.
-- If you edit this type, you may need to update the GHC formalism
--- See Note [GHC Formalism] in coreSyn/CoreLint.hs
+-- See Note [GHC Formalism] in GHC.Core.Lint
data TyCon
= -- | The function type constructor, @(->)@
FunTyCon {
@@ -1469,7 +1469,7 @@ isGcPtrRep UnliftedRep = True
isGcPtrRep _ = False
-- A PrimRep is compatible with another iff one can be coerced to the other.
--- See Note [bad unsafe coercion] in CoreLint for when are two types coercible.
+-- See Note [bad unsafe coercion] in GHC.Core.Lint for when are two types coercible.
primRepCompatible :: DynFlags -> PrimRep -> PrimRep -> Bool
primRepCompatible dflags rep1 rep2 =
(isUnboxed rep1 == isUnboxed rep2) &&
diff --git a/compiler/types/Type.hs b/compiler/types/Type.hs
index fbd2f55568..71a0622787 100644
--- a/compiler/types/Type.hs
+++ b/compiler/types/Type.hs
@@ -1088,7 +1088,7 @@ piResultTy_maybe ty arg
-- there are more type args than foralls in 'undefined's type.
-- If you edit this function, you may need to update the GHC formalism
--- See Note [GHC Formalism] in coreSyn/CoreLint.hs
+-- See Note [GHC Formalism] in GHC.Core.Lint
-- This is a heavily used function (e.g. from typeKind),
-- so we pay attention to efficiency, especially in the special case
@@ -2085,7 +2085,7 @@ isPrimitiveType ty = case splitTyConApp_maybe ty of
-- in its return type, since given
-- join j @a @b x y z = e1 in e2,
-- the types of e1 and e2 must be the same, and a and b are not in scope for e2.
--- (See Note [The polymorphism rule of join points] in CoreSyn.) Returns False
+-- (See Note [The polymorphism rule of join points] in GHC.Core.) Returns False
-- also if the type simply doesn't have enough arguments.
--
-- Note that we need to know how many arguments (type *and* value) the putative
@@ -2113,7 +2113,7 @@ isValidJoinPointType arity ty
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
In principle, if a function would be a join point except that it fails
the polymorphism rule (see Note [The polymorphism rule of join points] in
-CoreSyn), it can still be made a join point with some effort. This is because
+GHC.Core), it can still be made a join point with some effort. This is because
all tail calls must return the same type (they return to the same context!), and
thus if the return type depends on an argument, that argument must always be the
same.
@@ -2643,7 +2643,7 @@ occCheckExpand :: [Var] -> Type -> Maybe Type
-- free of the variable, then the same type is returned.
occCheckExpand vs_to_avoid ty
| null vs_to_avoid -- Efficient shortcut
- = Just ty -- Can happen, eg. CoreUtils.mkSingleAltCase
+ = Just ty -- Can happen, eg. GHC.Core.Utils.mkSingleAltCase
| otherwise
= go (mkVarSet vs_to_avoid, emptyVarEnv) ty
diff --git a/compiler/utils/Outputable.hs b/compiler/utils/Outputable.hs
index b9e3993cb9..7133951d67 100644
--- a/compiler/utils/Outputable.hs
+++ b/compiler/utils/Outputable.hs
@@ -962,7 +962,7 @@ instance Outputable Extension where
-- | 'BindingSite' is used to tell the thing that prints binder what
-- language construct is binding the identifier. This can be used
-- to decide how much info to print.
--- Also see Note [Binding-site specific printing] in PprCore
+-- Also see Note [Binding-site specific printing] in GHC.Core.Ppr
data BindingSite
= LambdaBind -- ^ The x in (\x. e)
| CaseBind -- ^ The x in case scrut of x { (y,z) -> ... }
diff --git a/compiler/utils/TrieMap.hs b/compiler/utils/TrieMap.hs
index f4106437a1..53bb06c4f9 100644
--- a/compiler/utils/TrieMap.hs
+++ b/compiler/utils/TrieMap.hs
@@ -47,7 +47,7 @@ whose key is a structured value like a CoreExpr or Type.
This file implements tries over general data structures.
Implementation for tries over Core Expressions/Types are
-available in coreSyn/TrieMap.
+available in GHC.Core.Map.
The regular pattern for handling TrieMaps on data structures was first
described (to my knowledge) in Connelly and Morris's 1995 paper "A
@@ -333,7 +333,7 @@ just use SingletonMap.
nothing in the map, don't bother building out the (possibly infinite) recursive
TrieMap structure!
-Compressed triemaps are heavily used by CoreMap. So we have to mark some things
+Compressed triemaps are heavily used by GHC.Core.Map. So we have to mark some things
as INLINEABLE to permit specialization.
-}
diff --git a/ghc/GHCi/UI.hs b/ghc/GHCi/UI.hs
index ef78dca036..31243edfc1 100644
--- a/ghc/GHCi/UI.hs
+++ b/ghc/GHCi/UI.hs
@@ -59,7 +59,7 @@ import Name
import GHC.Driver.Packages ( trusted, getPackageDetails, getInstalledPackageDetails,
listVisibleModuleNames, pprFlag )
import GHC.Iface.Syntax ( showToHeader )
-import PprTyThing
+import GHC.Core.Ppr.TyThing
import PrelNames
import RdrName ( getGRE_NameQualifier_maybes, getRdrName )
import SrcLoc
diff --git a/ghc/GHCi/UI/Info.hs b/ghc/GHCi/UI/Info.hs
index 7f65cf11c9..5ec1ca76a4 100644
--- a/ghc/GHCi/UI/Info.hs
+++ b/ghc/GHCi/UI/Info.hs
@@ -31,7 +31,7 @@ import Data.Time
import Prelude hiding (mod,(<>))
import System.Directory
-import qualified CoreUtils
+import qualified GHC.Core.Utils
import GHC.HsToCore
import GHC.Driver.Session (HasDynFlags(..))
import FastString
@@ -334,7 +334,7 @@ processAllTypeCheckedModule tcm = do
getTypeLHsExpr e = do
hs_env <- getSession
(_,mbe) <- liftIO $ deSugarExpr hs_env e
- return $ fmap (\expr -> (mid, getLoc e, CoreUtils.exprType expr)) mbe
+ return $ fmap (\expr -> (mid, getLoc e, GHC.Core.Utils.exprType expr)) mbe
where
mid :: Maybe Id
mid | HsVar _ (L _ i) <- unwrapVar (unLoc e) = Just i
diff --git a/rts/RtsStartup.c b/rts/RtsStartup.c
index d0d08a2495..6e8bed1255 100644
--- a/rts/RtsStartup.c
+++ b/rts/RtsStartup.c
@@ -277,7 +277,7 @@ hs_init_ghc(int *argc, char **argv[], RtsConfig rts_config)
getStablePtr((StgPtr)nestedAtomically_closure);
getStablePtr((StgPtr)absentSumFieldError_closure);
// `Id` for this closure is marked as non-CAFFY,
- // see Note [aBSENT_SUM_FIELD_ERROR_ID] in MkCore.
+ // see Note [aBSENT_SUM_FIELD_ERROR_ID] in GHC.Core.Make.
getStablePtr((StgPtr)runSparks_closure);
getStablePtr((StgPtr)ensureIOManagerIsRunning_closure);
diff --git a/testsuite/tests/callarity/unittest/CallArity1.hs b/testsuite/tests/callarity/unittest/CallArity1.hs
index 8a1cacc4e0..cbc07dbecd 100644
--- a/testsuite/tests/callarity/unittest/CallArity1.hs
+++ b/testsuite/tests/callarity/unittest/CallArity1.hs
@@ -1,9 +1,9 @@
{-# LANGUAGE TupleSections #-}
-import CoreSyn
-import CoreUtils
+import GHC.Core
+import GHC.Core.Utils
import Id
import Type
-import MkCore
+import GHC.Core.Make
import CallArity (callArityRHS)
import MkId
import SysTools
@@ -17,10 +17,10 @@ import Control.Monad
import Control.Monad.IO.Class
import System.Environment( getArgs )
import VarSet
-import PprCore
+import GHC.Core.Ppr
import Unique
import UniqSet
-import CoreLint
+import GHC.Core.Lint
import FastString
-- Build IDs. use mkTemplateLocal, more predictable than proper uniques
diff --git a/testsuite/tests/typecheck/should_compile/T3409.hs b/testsuite/tests/typecheck/should_compile/T3409.hs
index b584fe1f1f..dd6c935a1d 100644
--- a/testsuite/tests/typecheck/should_compile/T3409.hs
+++ b/testsuite/tests/typecheck/should_compile/T3409.hs
@@ -5,7 +5,7 @@
-- because of a type synonym that discards one of its arguments
--
-- See Note [Existential variables and silly type synonyms]
--- in CoreUtils
+-- in GHC.Core.Utils
-- In GHC 6.10, both tests below (independently) give Lint errors
diff --git a/utils/haddock b/utils/haddock
-Subproject 844c0c47a223e2e1bb3767afc05639269dad8ee
+Subproject 78d0e033a2f8ce5dc1f5e2e4eb8b823ee4d1d1b