From bff2f24ba9104275c665b6a0cf30a8dd18407392 Mon Sep 17 00:00:00 2001
From: John Ericson <John.Ericson@Obsidian.Systems>
Date: Thu, 30 May 2019 20:06:24 -0400
Subject: [PATCH] Move 'Platform' to ghc-boot

ghc-pkg needs to be aware of platforms so it can figure out which
subdire within the user package db to use. This is admittedly
roundabout, but maybe Cabal could use the same notion of a platform as
GHC to good affect too.
---
 compiler/basicTypes/Literal.hs                         | 2 +-
 compiler/cmm/CLabel.hs                                 | 2 +-
 compiler/cmm/CmmBuildInfoTables.hs                     | 2 +-
 compiler/cmm/CmmCallConv.hs                            | 2 +-
 compiler/cmm/CmmInfo.hs                                | 2 +-
 compiler/cmm/CmmOpt.hs                                 | 2 +-
 compiler/cmm/CmmParse.y                                | 2 +-
 compiler/cmm/CmmPipeline.hs                            | 2 +-
 compiler/cmm/CmmProcPoint.hs                           | 2 +-
 compiler/cmm/CmmSink.hs                                | 2 +-
 compiler/cmm/PprC.hs                                   | 2 +-
 compiler/cmm/SMRep.hs                                  | 2 +-
 compiler/codeGen/CodeGen/Platform.hs                   | 2 +-
 compiler/codeGen/StgCmmCon.hs                          | 2 +-
 compiler/codeGen/StgCmmPrim.hs                         | 2 +-
 compiler/coreSyn/CorePrep.hs                           | 2 +-
 compiler/coreSyn/CoreUtils.hs                          | 2 +-
 compiler/deSugar/DsForeign.hs                          | 2 +-
 compiler/ghc.cabal.in                                  | 1 -
 compiler/ghci/ByteCodeAsm.hs                           | 2 +-
 compiler/ghci/ByteCodeGen.hs                           | 2 +-
 compiler/ghci/Linker.hs                                | 2 +-
 compiler/iface/BinIface.hs                             | 2 +-
 compiler/llvmGen/LlvmCodeGen/Base.hs                   | 2 +-
 compiler/llvmGen/LlvmCodeGen/CodeGen.hs                | 2 +-
 compiler/llvmGen/LlvmCodeGen/Data.hs                   | 2 +-
 compiler/llvmGen/LlvmMangler.hs                        | 2 +-
 compiler/main/DriverPhases.hs                          | 2 +-
 compiler/main/DriverPipeline.hs                        | 2 +-
 compiler/main/DynFlags.hs                              | 2 +-
 compiler/main/DynFlags.hs-boot                         | 2 +-
 compiler/main/GHC.hs                                   | 2 +-
 compiler/main/HscMain.hs                               | 2 +-
 compiler/main/HscTypes.hs                              | 2 +-
 compiler/main/Packages.hs                              | 2 +-
 compiler/main/Settings.hs                              | 2 +-
 compiler/main/StaticPtrTable.hs                        | 2 +-
 compiler/main/SysTools.hs                              | 2 +-
 compiler/main/SysTools/ExtraObj.hs                     | 2 +-
 compiler/main/SysTools/Info.hs                         | 2 +-
 compiler/main/SysTools/Tasks.hs                        | 2 +-
 compiler/nativeGen/AsmCodeGen.hs                       | 2 +-
 compiler/nativeGen/Dwarf.hs                            | 2 +-
 compiler/nativeGen/Dwarf/Constants.hs                  | 2 +-
 compiler/nativeGen/Dwarf/Types.hs                      | 2 +-
 compiler/nativeGen/Instruction.hs                      | 2 +-
 compiler/nativeGen/PIC.hs                              | 2 +-
 compiler/nativeGen/PPC/CodeGen.hs                      | 2 +-
 compiler/nativeGen/PPC/Instr.hs                        | 2 +-
 compiler/nativeGen/PPC/Ppr.hs                          | 2 +-
 compiler/nativeGen/PPC/Regs.hs                         | 2 +-
 compiler/nativeGen/PprBase.hs                          | 2 +-
 compiler/nativeGen/RegAlloc/Graph/Main.hs              | 2 +-
 compiler/nativeGen/RegAlloc/Graph/Spill.hs             | 2 +-
 compiler/nativeGen/RegAlloc/Graph/SpillClean.hs        | 2 +-
 compiler/nativeGen/RegAlloc/Graph/SpillCost.hs         | 2 +-
 compiler/nativeGen/RegAlloc/Graph/TrivColorable.hs     | 2 +-
 compiler/nativeGen/RegAlloc/Linear/FreeRegs.hs         | 2 +-
 compiler/nativeGen/RegAlloc/Linear/Main.hs             | 2 +-
 compiler/nativeGen/RegAlloc/Linear/PPC/FreeRegs.hs     | 2 +-
 compiler/nativeGen/RegAlloc/Linear/SPARC/FreeRegs.hs   | 2 +-
 compiler/nativeGen/RegAlloc/Linear/X86/FreeRegs.hs     | 2 +-
 compiler/nativeGen/RegAlloc/Linear/X86_64/FreeRegs.hs  | 2 +-
 compiler/nativeGen/RegAlloc/Liveness.hs                | 2 +-
 compiler/nativeGen/SPARC/CodeGen.hs                    | 2 +-
 compiler/nativeGen/SPARC/CodeGen/Base.hs               | 2 +-
 compiler/nativeGen/SPARC/Instr.hs                      | 2 +-
 compiler/nativeGen/SPARC/Ppr.hs                        | 2 +-
 compiler/nativeGen/TargetReg.hs                        | 2 +-
 compiler/nativeGen/X86/CodeGen.hs                      | 2 +-
 compiler/nativeGen/X86/Instr.hs                        | 2 +-
 compiler/nativeGen/X86/Ppr.hs                          | 2 +-
 compiler/nativeGen/X86/RegInfo.hs                      | 2 +-
 compiler/nativeGen/X86/Regs.hs                         | 2 +-
 compiler/prelude/PrelRules.hs                          | 2 +-
 compiler/stgSyn/StgSyn.hs                              | 2 +-
 compiler/typecheck/TcForeign.hs                        | 2 +-
 compiler/utils/AsmUtils.hs                             | 2 +-
 compiler/utils/Outputable.hs                           | 2 +-
 ghc/GHCi/Leak.hs                                       | 2 +-
 {compiler/utils => libraries/ghc-boot/GHC}/Platform.hs | 4 ++--
 libraries/ghc-boot/ghc-boot.cabal.in                   | 1 +
 testsuite/tests/codeGen/should_run/T13825-unit.hs      | 2 +-
 83 files changed, 83 insertions(+), 83 deletions(-)
 rename {compiler/utils => libraries/ghc-boot/GHC}/Platform.hs (98%)

diff --git a/compiler/basicTypes/Literal.hs b/compiler/basicTypes/Literal.hs
index 8dd6708edaa8..abf74a7cbd28 100644
--- a/compiler/basicTypes/Literal.hs
+++ b/compiler/basicTypes/Literal.hs
@@ -61,7 +61,7 @@ import BasicTypes
 import Binary
 import Constants
 import DynFlags
-import Platform
+import GHC.Platform
 import UniqFM
 import Util
 
diff --git a/compiler/cmm/CLabel.hs b/compiler/cmm/CLabel.hs
index d30bd4c0f787..95f5a41a23e6 100644
--- a/compiler/cmm/CLabel.hs
+++ b/compiler/cmm/CLabel.hs
@@ -124,7 +124,7 @@ import CostCentre
 import Outputable
 import FastString
 import DynFlags
-import Platform
+import GHC.Platform
 import UniqSet
 import Util
 import PprCore ( {- instances -} )
diff --git a/compiler/cmm/CmmBuildInfoTables.hs b/compiler/cmm/CmmBuildInfoTables.hs
index be96fba7e9f1..04b3d70f54cc 100644
--- a/compiler/cmm/CmmBuildInfoTables.hs
+++ b/compiler/cmm/CmmBuildInfoTables.hs
@@ -16,7 +16,7 @@ import Hoopl.Label
 import Hoopl.Collections
 import Hoopl.Dataflow
 import Module
-import Platform
+import GHC.Platform
 import Digraph
 import CLabel
 import PprCmmDecl ()
diff --git a/compiler/cmm/CmmCallConv.hs b/compiler/cmm/CmmCallConv.hs
index 078390638d52..4e6a9d293a25 100644
--- a/compiler/cmm/CmmCallConv.hs
+++ b/compiler/cmm/CmmCallConv.hs
@@ -13,7 +13,7 @@ import Cmm (Convention(..))
 import PprCmm ()
 
 import DynFlags
-import Platform
+import GHC.Platform
 import Outputable
 
 -- Calculate the 'GlobalReg' or stack locations for function call
diff --git a/compiler/cmm/CmmInfo.hs b/compiler/cmm/CmmInfo.hs
index c374e9fd8119..16ab6ed58769 100644
--- a/compiler/cmm/CmmInfo.hs
+++ b/compiler/cmm/CmmInfo.hs
@@ -45,7 +45,7 @@ import Stream (Stream)
 import qualified Stream
 import Hoopl.Collections
 
-import Platform
+import GHC.Platform
 import Maybes
 import DynFlags
 import Panic
diff --git a/compiler/cmm/CmmOpt.hs b/compiler/cmm/CmmOpt.hs
index e837d297835b..ed8b386238c4 100644
--- a/compiler/cmm/CmmOpt.hs
+++ b/compiler/cmm/CmmOpt.hs
@@ -25,7 +25,7 @@ import DynFlags
 import Util
 
 import Outputable
-import Platform
+import GHC.Platform
 
 import Data.Bits
 import Data.Maybe
diff --git a/compiler/cmm/CmmParse.y b/compiler/cmm/CmmParse.y
index 20d12bb40193..f83fb6b00006 100644
--- a/compiler/cmm/CmmParse.y
+++ b/compiler/cmm/CmmParse.y
@@ -237,7 +237,7 @@ import CmmMonad
 import CostCentre
 import ForeignCall
 import Module
-import Platform
+import GHC.Platform
 import Literal
 import Unique
 import UniqFM
diff --git a/compiler/cmm/CmmPipeline.hs b/compiler/cmm/CmmPipeline.hs
index 7f7c1118482e..2f481c272a03 100644
--- a/compiler/cmm/CmmPipeline.hs
+++ b/compiler/cmm/CmmPipeline.hs
@@ -26,7 +26,7 @@ import ErrUtils
 import HscTypes
 import Control.Monad
 import Outputable
-import Platform
+import GHC.Platform
 
 -----------------------------------------------------------------------------
 -- | Top level driver for C-- pipeline
diff --git a/compiler/cmm/CmmProcPoint.hs b/compiler/cmm/CmmProcPoint.hs
index 427de3bb3de5..528337c57e0a 100644
--- a/compiler/cmm/CmmProcPoint.hs
+++ b/compiler/cmm/CmmProcPoint.hs
@@ -23,7 +23,7 @@ import Data.List (sortBy)
 import Maybes
 import Control.Monad
 import Outputable
-import Platform
+import GHC.Platform
 import UniqSupply
 import Hoopl.Block
 import Hoopl.Collections
diff --git a/compiler/cmm/CmmSink.hs b/compiler/cmm/CmmSink.hs
index 26d0a6fd9a8d..409cd0fbf225 100644
--- a/compiler/cmm/CmmSink.hs
+++ b/compiler/cmm/CmmSink.hs
@@ -14,7 +14,7 @@ import Hoopl.Label
 import Hoopl.Collections
 import Hoopl.Graph
 import CodeGen.Platform
-import Platform (isARM, platformArch)
+import GHC.Platform (isARM, platformArch)
 
 import DynFlags
 import Unique
diff --git a/compiler/cmm/PprC.hs b/compiler/cmm/PprC.hs
index e57c409a049e..f68496879533 100644
--- a/compiler/cmm/PprC.hs
+++ b/compiler/cmm/PprC.hs
@@ -44,7 +44,7 @@ import CPrim
 import DynFlags
 import FastString
 import Outputable
-import Platform
+import GHC.Platform
 import UniqSet
 import UniqFM
 import Unique
diff --git a/compiler/cmm/SMRep.hs b/compiler/cmm/SMRep.hs
index 8cd9c3e497a2..57d5354cca76 100644
--- a/compiler/cmm/SMRep.hs
+++ b/compiler/cmm/SMRep.hs
@@ -49,7 +49,7 @@ import GhcPrelude
 import BasicTypes( ConTagZ )
 import DynFlags
 import Outputable
-import Platform
+import GHC.Platform
 import FastString
 
 import Data.Word
diff --git a/compiler/codeGen/CodeGen/Platform.hs b/compiler/codeGen/CodeGen/Platform.hs
index 9d9a0cf2d115..bc216758a006 100644
--- a/compiler/codeGen/CodeGen/Platform.hs
+++ b/compiler/codeGen/CodeGen/Platform.hs
@@ -6,7 +6,7 @@ module CodeGen.Platform
 import GhcPrelude
 
 import CmmExpr
-import Platform
+import GHC.Platform
 import Reg
 
 import qualified CodeGen.Platform.ARM        as ARM
diff --git a/compiler/codeGen/StgCmmCon.hs b/compiler/codeGen/StgCmmCon.hs
index 258896ff1ac6..67a9776eacae 100644
--- a/compiler/codeGen/StgCmmCon.hs
+++ b/compiler/codeGen/StgCmmCon.hs
@@ -44,7 +44,7 @@ import RepType (countConRepArgs)
 import Literal
 import PrelInfo
 import Outputable
-import Platform
+import GHC.Platform
 import Util
 import MonadUtils (mapMaybeM)
 
diff --git a/compiler/codeGen/StgCmmPrim.hs b/compiler/codeGen/StgCmmPrim.hs
index 2d56bf41d553..c3f9d5a2795b 100644
--- a/compiler/codeGen/StgCmmPrim.hs
+++ b/compiler/codeGen/StgCmmPrim.hs
@@ -31,7 +31,7 @@ import StgCmmHeap
 import StgCmmProf ( costCentreFrom )
 
 import DynFlags
-import Platform
+import GHC.Platform
 import BasicTypes
 import BlockId
 import MkGraph
diff --git a/compiler/coreSyn/CorePrep.hs b/compiler/coreSyn/CorePrep.hs
index e49ffb597367..98bffd37770b 100644
--- a/compiler/coreSyn/CorePrep.hs
+++ b/compiler/coreSyn/CorePrep.hs
@@ -53,7 +53,7 @@ import DynFlags
 import Util
 import Pair
 import Outputable
-import Platform
+import GHC.Platform
 import FastString
 import Name             ( NamedThing(..), nameSrcSpan )
 import SrcLoc           ( SrcSpan(..), realSrcLocSpan, mkRealSrcLoc )
diff --git a/compiler/coreSyn/CoreUtils.hs b/compiler/coreSyn/CoreUtils.hs
index 8e298adf6a6d..5204d5e9f608 100644
--- a/compiler/coreSyn/CoreUtils.hs
+++ b/compiler/coreSyn/CoreUtils.hs
@@ -88,7 +88,7 @@ import FastString
 import Maybes
 import ListSetOps       ( minusList )
 import BasicTypes       ( Arity, isConLike )
-import Platform
+import GHC.Platform
 import Util
 import Pair
 import Data.ByteString     ( ByteString )
diff --git a/compiler/deSugar/DsForeign.hs b/compiler/deSugar/DsForeign.hs
index dd0cc4860a4c..3ecd9bfead4f 100644
--- a/compiler/deSugar/DsForeign.hs
+++ b/compiler/deSugar/DsForeign.hs
@@ -49,7 +49,7 @@ import SrcLoc
 import Outputable
 import FastString
 import DynFlags
-import Platform
+import GHC.Platform
 import OrdList
 import Pair
 import Util
diff --git a/compiler/ghc.cabal.in b/compiler/ghc.cabal.in
index d380d96707a7..1a235c40087f 100644
--- a/compiler/ghc.cabal.in
+++ b/compiler/ghc.cabal.in
@@ -607,7 +607,6 @@ Library
             Reg
             RegClass
             PIC
-            Platform
             CPrim
             X86.Regs
             X86.RegInfo
diff --git a/compiler/ghci/ByteCodeAsm.hs b/compiler/ghci/ByteCodeAsm.hs
index fb38ca1c02bc..aa556e774fdc 100644
--- a/compiler/ghci/ByteCodeAsm.hs
+++ b/compiler/ghci/ByteCodeAsm.hs
@@ -33,7 +33,7 @@ import StgCmmLayout     ( ArgRep(..) )
 import SMRep
 import DynFlags
 import Outputable
-import Platform
+import GHC.Platform
 import Util
 import Unique
 import UniqDSet
diff --git a/compiler/ghci/ByteCodeGen.hs b/compiler/ghci/ByteCodeGen.hs
index 33ae172d7132..8b23e08003de 100644
--- a/compiler/ghci/ByteCodeGen.hs
+++ b/compiler/ghci/ByteCodeGen.hs
@@ -23,7 +23,7 @@ import GHCi.RemoteTypes
 import BasicTypes
 import DynFlags
 import Outputable
-import Platform
+import GHC.Platform
 import Name
 import MkId
 import Id
diff --git a/compiler/ghci/Linker.hs b/compiler/ghci/Linker.hs
index e26dcce1ee61..bd74d36c5684 100644
--- a/compiler/ghci/Linker.hs
+++ b/compiler/ghci/Linker.hs
@@ -50,7 +50,7 @@ import SrcLoc
 import qualified Maybes
 import UniqDSet
 import FastString
-import Platform
+import GHC.Platform
 import SysTools
 import FileCleanup
 
diff --git a/compiler/iface/BinIface.hs b/compiler/iface/BinIface.hs
index e365a8edd476..e1ca00e8a80e 100644
--- a/compiler/iface/BinIface.hs
+++ b/compiler/iface/BinIface.hs
@@ -42,7 +42,7 @@ import FastMutInt
 import Unique
 import Outputable
 import NameCache
-import Platform
+import GHC.Platform
 import FastString
 import Constants
 import Util
diff --git a/compiler/llvmGen/LlvmCodeGen/Base.hs b/compiler/llvmGen/LlvmCodeGen/Base.hs
index ab9695778c88..b47bf6aff685 100644
--- a/compiler/llvmGen/LlvmCodeGen/Base.hs
+++ b/compiler/llvmGen/LlvmCodeGen/Base.hs
@@ -49,7 +49,7 @@ import DynFlags
 import FastString
 import Cmm              hiding ( succ )
 import Outputable as Outp
-import Platform
+import GHC.Platform
 import UniqFM
 import Unique
 import BufWrite   ( BufHandle )
diff --git a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs
index 28f38d09ec55..bdf6a2642f27 100644
--- a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs
+++ b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs
@@ -29,7 +29,7 @@ import FastString
 import ForeignCall
 import Outputable hiding (panic, pprPanic)
 import qualified Outputable
-import Platform
+import GHC.Platform
 import OrdList
 import UniqSupply
 import Unique
diff --git a/compiler/llvmGen/LlvmCodeGen/Data.hs b/compiler/llvmGen/LlvmCodeGen/Data.hs
index 3651a88cc652..70a04e6bc95a 100644
--- a/compiler/llvmGen/LlvmCodeGen/Data.hs
+++ b/compiler/llvmGen/LlvmCodeGen/Data.hs
@@ -18,7 +18,7 @@ import BlockId
 import CLabel
 import Cmm
 import DynFlags
-import Platform
+import GHC.Platform
 
 import FastString
 import Outputable
diff --git a/compiler/llvmGen/LlvmMangler.hs b/compiler/llvmGen/LlvmMangler.hs
index fe03cf21e97b..114951946c6a 100644
--- a/compiler/llvmGen/LlvmMangler.hs
+++ b/compiler/llvmGen/LlvmMangler.hs
@@ -14,7 +14,7 @@ module LlvmMangler ( llvmFixupAsm ) where
 import GhcPrelude
 
 import DynFlags ( DynFlags, targetPlatform )
-import Platform ( platformArch, Arch(..) )
+import GHC.Platform ( platformArch, Arch(..) )
 import ErrUtils ( withTiming )
 import Outputable ( text )
 
diff --git a/compiler/main/DriverPhases.hs b/compiler/main/DriverPhases.hs
index d4392c4c375d..5c88faf89558 100644
--- a/compiler/main/DriverPhases.hs
+++ b/compiler/main/DriverPhases.hs
@@ -44,7 +44,7 @@ import GhcPrelude
 
 import {-# SOURCE #-} DynFlags
 import Outputable
-import Platform
+import GHC.Platform
 import System.FilePath
 import Binary
 import Util
diff --git a/compiler/main/DriverPipeline.hs b/compiler/main/DriverPipeline.hs
index ffc11980e249..f77927f8e562 100644
--- a/compiler/main/DriverPipeline.hs
+++ b/compiler/main/DriverPipeline.hs
@@ -58,7 +58,7 @@ import Maybes           ( expectJust )
 import SrcLoc
 import LlvmCodeGen      ( llvmFixupAsm )
 import MonadUtils
-import Platform
+import GHC.Platform
 import TcRnTypes
 import ToolSettings
 import Hooks
diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs
index 76b5be6573eb..7a6bca627744 100644
--- a/compiler/main/DynFlags.hs
+++ b/compiler/main/DynFlags.hs
@@ -248,7 +248,7 @@ module DynFlags (
 
 import GhcPrelude
 
-import Platform
+import GHC.Platform
 import PlatformConstants
 import Module
 import PackageConfig
diff --git a/compiler/main/DynFlags.hs-boot b/compiler/main/DynFlags.hs-boot
index 823fd228549e..bed4ae2fd109 100644
--- a/compiler/main/DynFlags.hs-boot
+++ b/compiler/main/DynFlags.hs-boot
@@ -1,7 +1,7 @@
 module DynFlags where
 
 import GhcPrelude
-import Platform
+import GHC.Platform
 
 data DynFlags
 data DumpFlag
diff --git a/compiler/main/GHC.hs b/compiler/main/GHC.hs
index d89ccf8dea4a..41e59850c00e 100644
--- a/compiler/main/GHC.hs
+++ b/compiler/main/GHC.hs
@@ -338,7 +338,7 @@ import SysTools.BaseDir
 import Annotations
 import Module
 import Panic
-import Platform
+import GHC.Platform
 import Bag              ( listToBag )
 import ErrUtils
 import MonadUtils
diff --git a/compiler/main/HscMain.hs b/compiler/main/HscMain.hs
index 196019335848..d7658ad2aa7a 100644
--- a/compiler/main/HscMain.hs
+++ b/compiler/main/HscMain.hs
@@ -149,7 +149,7 @@ import DynamicLoading   ( initializePlugins )
 
 import DynFlags
 import ErrUtils
-import Platform ( platformOS, osSubsectionsViaSymbols )
+import GHC.Platform ( platformOS, osSubsectionsViaSymbols )
 
 import Outputable
 import NameEnv
diff --git a/compiler/main/HscTypes.hs b/compiler/main/HscTypes.hs
index 2749073ff15a..0fa9ffa6649f 100644
--- a/compiler/main/HscTypes.hs
+++ b/compiler/main/HscTypes.hs
@@ -201,7 +201,7 @@ import Bag
 import Binary
 import ErrUtils
 import NameCache
-import Platform
+import GHC.Platform
 import Util
 import UniqDSet
 import GHC.Serialized   ( Serialized )
diff --git a/compiler/main/Packages.hs b/compiler/main/Packages.hs
index 64e012c57fdb..ec63308b83f4 100644
--- a/compiler/main/Packages.hs
+++ b/compiler/main/Packages.hs
@@ -77,7 +77,7 @@ import UniqSet
 import Module
 import Util
 import Panic
-import Platform
+import GHC.Platform
 import Outputable
 import Maybes
 
diff --git a/compiler/main/Settings.hs b/compiler/main/Settings.hs
index b8285340cf51..e9e09711ba36 100644
--- a/compiler/main/Settings.hs
+++ b/compiler/main/Settings.hs
@@ -64,7 +64,7 @@ import CliOption
 import Fingerprint
 import FileSettings
 import GhcNameVersion
-import Platform
+import GHC.Platform
 import PlatformConstants
 import ToolSettings
 
diff --git a/compiler/main/StaticPtrTable.hs b/compiler/main/StaticPtrTable.hs
index 47547fca5b43..9f327c90d9be 100644
--- a/compiler/main/StaticPtrTable.hs
+++ b/compiler/main/StaticPtrTable.hs
@@ -135,7 +135,7 @@ import MkCore (mkStringExprFSWith)
 import Module
 import Name
 import Outputable
-import Platform
+import GHC.Platform
 import PrelNames
 import TcEnv (lookupGlobal)
 import Type
diff --git a/compiler/main/SysTools.hs b/compiler/main/SysTools.hs
index 6db3f3243d66..5ab880513295 100644
--- a/compiler/main/SysTools.hs
+++ b/compiler/main/SysTools.hs
@@ -45,7 +45,7 @@ import Packages
 import Config
 import Outputable
 import ErrUtils
-import Platform
+import GHC.Platform
 import Util
 import DynFlags
 import Fingerprint
diff --git a/compiler/main/SysTools/ExtraObj.hs b/compiler/main/SysTools/ExtraObj.hs
index 149d3a678ad2..c930389c9547 100644
--- a/compiler/main/SysTools/ExtraObj.hs
+++ b/compiler/main/SysTools/ExtraObj.hs
@@ -17,7 +17,7 @@ import AsmUtils
 import ErrUtils
 import DynFlags
 import Packages
-import Platform
+import GHC.Platform
 import Outputable
 import SrcLoc           ( noSrcSpan )
 import Module
diff --git a/compiler/main/SysTools/Info.hs b/compiler/main/SysTools/Info.hs
index 9aa9002c2369..e61846d4e6f8 100644
--- a/compiler/main/SysTools/Info.hs
+++ b/compiler/main/SysTools/Info.hs
@@ -19,7 +19,7 @@ import Data.IORef
 
 import System.IO
 
-import Platform
+import GHC.Platform
 import GhcPrelude
 
 import SysTools.Process
diff --git a/compiler/main/SysTools/Tasks.hs b/compiler/main/SysTools/Tasks.hs
index 1747d50be1e1..10e1102304cf 100644
--- a/compiler/main/SysTools/Tasks.hs
+++ b/compiler/main/SysTools/Tasks.hs
@@ -13,7 +13,7 @@ import ErrUtils
 import HscTypes
 import DynFlags
 import Outputable
-import Platform
+import GHC.Platform
 import Util
 
 import Data.Char
diff --git a/compiler/nativeGen/AsmCodeGen.hs b/compiler/nativeGen/AsmCodeGen.hs
index ed0c57e1e252..6e9450fd8574 100644
--- a/compiler/nativeGen/AsmCodeGen.hs
+++ b/compiler/nativeGen/AsmCodeGen.hs
@@ -60,7 +60,7 @@ import qualified RegAlloc.Graph.TrivColorable   as Color
 
 import AsmUtils
 import TargetReg
-import Platform
+import GHC.Platform
 import BlockLayout
 import Config
 import Instruction
diff --git a/compiler/nativeGen/Dwarf.hs b/compiler/nativeGen/Dwarf.hs
index 0e645a2a560e..b64b4efc338c 100644
--- a/compiler/nativeGen/Dwarf.hs
+++ b/compiler/nativeGen/Dwarf.hs
@@ -12,7 +12,7 @@ import Debug
 import DynFlags
 import Module
 import Outputable
-import Platform
+import GHC.Platform
 import Unique
 import UniqSupply
 
diff --git a/compiler/nativeGen/Dwarf/Constants.hs b/compiler/nativeGen/Dwarf/Constants.hs
index 687a4f818f69..01b85c47bcaa 100644
--- a/compiler/nativeGen/Dwarf/Constants.hs
+++ b/compiler/nativeGen/Dwarf/Constants.hs
@@ -7,7 +7,7 @@ import GhcPrelude
 
 import AsmUtils
 import FastString
-import Platform
+import GHC.Platform
 import Outputable
 
 import Reg
diff --git a/compiler/nativeGen/Dwarf/Types.hs b/compiler/nativeGen/Dwarf/Types.hs
index 57ff0b247808..01253544e6d1 100644
--- a/compiler/nativeGen/Dwarf/Types.hs
+++ b/compiler/nativeGen/Dwarf/Types.hs
@@ -30,7 +30,7 @@ import CmmExpr         ( GlobalReg(..) )
 import Encoding
 import FastString
 import Outputable
-import Platform
+import GHC.Platform
 import Unique
 import Reg
 import SrcLoc
diff --git a/compiler/nativeGen/Instruction.hs b/compiler/nativeGen/Instruction.hs
index 0bd99fbee880..4f18a45c16b0 100644
--- a/compiler/nativeGen/Instruction.hs
+++ b/compiler/nativeGen/Instruction.hs
@@ -23,7 +23,7 @@ import Hoopl.Collections
 import Hoopl.Label
 import DynFlags
 import Cmm hiding (topInfoTable)
-import Platform
+import GHC.Platform
 
 -- | Holds a list of source and destination registers used by a
 --      particular instruction.
diff --git a/compiler/nativeGen/PIC.hs b/compiler/nativeGen/PIC.hs
index 69113e8ea5f0..9c57a0292f24 100644
--- a/compiler/nativeGen/PIC.hs
+++ b/compiler/nativeGen/PIC.hs
@@ -54,7 +54,7 @@ import qualified PPC.Regs       as PPC
 
 import qualified X86.Instr      as X86
 
-import Platform
+import GHC.Platform
 import Instruction
 import Reg
 import NCGMonad
diff --git a/compiler/nativeGen/PPC/CodeGen.hs b/compiler/nativeGen/PPC/CodeGen.hs
index 03e8e42d9ae4..516cda0eb3c2 100644
--- a/compiler/nativeGen/PPC/CodeGen.hs
+++ b/compiler/nativeGen/PPC/CodeGen.hs
@@ -41,7 +41,7 @@ import Format
 import RegClass
 import Reg
 import TargetReg
-import Platform
+import GHC.Platform
 
 -- Our intermediate code:
 import BlockId
diff --git a/compiler/nativeGen/PPC/Instr.hs b/compiler/nativeGen/PPC/Instr.hs
index 3bf19f2dc653..b17ea32f01aa 100644
--- a/compiler/nativeGen/PPC/Instr.hs
+++ b/compiler/nativeGen/PPC/Instr.hs
@@ -43,7 +43,7 @@ import CmmInfo
 import FastString
 import CLabel
 import Outputable
-import Platform
+import GHC.Platform
 import UniqFM (listToUFM, lookupUFM)
 import UniqSupply
 
diff --git a/compiler/nativeGen/PPC/Ppr.hs b/compiler/nativeGen/PPC/Ppr.hs
index be6402e57a1b..4254f2312264 100644
--- a/compiler/nativeGen/PPC/Ppr.hs
+++ b/compiler/nativeGen/PPC/Ppr.hs
@@ -30,7 +30,7 @@ import CLabel
 import PprCmmExpr ()
 
 import Unique                ( pprUniqueAlways, getUnique )
-import Platform
+import GHC.Platform
 import FastString
 import Outputable
 import DynFlags
diff --git a/compiler/nativeGen/PPC/Regs.hs b/compiler/nativeGen/PPC/Regs.hs
index 8ba2ead926de..5b7ac208b6cc 100644
--- a/compiler/nativeGen/PPC/Regs.hs
+++ b/compiler/nativeGen/PPC/Regs.hs
@@ -63,7 +63,7 @@ import Unique
 import CodeGen.Platform
 import DynFlags
 import Outputable
-import Platform
+import GHC.Platform
 
 import Data.Word        ( Word8, Word16, Word32, Word64 )
 import Data.Int         ( Int8, Int16, Int32, Int64 )
diff --git a/compiler/nativeGen/PprBase.hs b/compiler/nativeGen/PprBase.hs
index 80f3e6179b3f..48e9e26ae449 100644
--- a/compiler/nativeGen/PprBase.hs
+++ b/compiler/nativeGen/PprBase.hs
@@ -28,7 +28,7 @@ import Cmm
 import DynFlags
 import FastString
 import Outputable
-import Platform
+import GHC.Platform
 import FileCleanup
 
 import qualified Data.Array.Unsafe as U ( castSTUArray )
diff --git a/compiler/nativeGen/RegAlloc/Graph/Main.hs b/compiler/nativeGen/RegAlloc/Graph/Main.hs
index c7875cfaeae6..df97de1c629e 100644
--- a/compiler/nativeGen/RegAlloc/Graph/Main.hs
+++ b/compiler/nativeGen/RegAlloc/Graph/Main.hs
@@ -21,7 +21,7 @@ import Reg
 import Bag
 import DynFlags
 import Outputable
-import Platform
+import GHC.Platform
 import UniqFM
 import UniqSet
 import UniqSupply
diff --git a/compiler/nativeGen/RegAlloc/Graph/Spill.hs b/compiler/nativeGen/RegAlloc/Graph/Spill.hs
index bc26a663a54f..eccc83eb4804 100644
--- a/compiler/nativeGen/RegAlloc/Graph/Spill.hs
+++ b/compiler/nativeGen/RegAlloc/Graph/Spill.hs
@@ -23,7 +23,7 @@ import UniqFM
 import UniqSet
 import UniqSupply
 import Outputable
-import Platform
+import GHC.Platform
 
 import Data.List
 import Data.Maybe
diff --git a/compiler/nativeGen/RegAlloc/Graph/SpillClean.hs b/compiler/nativeGen/RegAlloc/Graph/SpillClean.hs
index 50001d733459..6d7b377d68b8 100644
--- a/compiler/nativeGen/RegAlloc/Graph/SpillClean.hs
+++ b/compiler/nativeGen/RegAlloc/Graph/SpillClean.hs
@@ -41,7 +41,7 @@ import UniqFM
 import Unique
 import State
 import Outputable
-import Platform
+import GHC.Platform
 import Hoopl.Collections
 
 import Data.List
diff --git a/compiler/nativeGen/RegAlloc/Graph/SpillCost.hs b/compiler/nativeGen/RegAlloc/Graph/SpillCost.hs
index b62c44fa812b..9c6e24d32079 100644
--- a/compiler/nativeGen/RegAlloc/Graph/SpillCost.hs
+++ b/compiler/nativeGen/RegAlloc/Graph/SpillCost.hs
@@ -28,7 +28,7 @@ import UniqFM
 import UniqSet
 import Digraph          (flattenSCCs)
 import Outputable
-import Platform
+import GHC.Platform
 import State
 import CFG
 
diff --git a/compiler/nativeGen/RegAlloc/Graph/TrivColorable.hs b/compiler/nativeGen/RegAlloc/Graph/TrivColorable.hs
index 8db80ef06477..5d4fd418c350 100644
--- a/compiler/nativeGen/RegAlloc/Graph/TrivColorable.hs
+++ b/compiler/nativeGen/RegAlloc/Graph/TrivColorable.hs
@@ -16,7 +16,7 @@ import Reg
 import GraphBase
 
 import UniqSet
-import Platform
+import GHC.Platform
 import Panic
 
 -- trivColorable ---------------------------------------------------------------
diff --git a/compiler/nativeGen/RegAlloc/Linear/FreeRegs.hs b/compiler/nativeGen/RegAlloc/Linear/FreeRegs.hs
index b4e79432d811..5a4f1c65a85a 100644
--- a/compiler/nativeGen/RegAlloc/Linear/FreeRegs.hs
+++ b/compiler/nativeGen/RegAlloc/Linear/FreeRegs.hs
@@ -16,7 +16,7 @@ import RegClass
 
 import DynFlags
 import Panic
-import Platform
+import GHC.Platform
 
 -- -----------------------------------------------------------------------------
 -- The free register set
diff --git a/compiler/nativeGen/RegAlloc/Linear/Main.hs b/compiler/nativeGen/RegAlloc/Linear/Main.hs
index a9337b00441d..cdaf738d6861 100644
--- a/compiler/nativeGen/RegAlloc/Linear/Main.hs
+++ b/compiler/nativeGen/RegAlloc/Linear/Main.hs
@@ -130,7 +130,7 @@ import UniqSet
 import UniqFM
 import UniqSupply
 import Outputable
-import Platform
+import GHC.Platform
 
 import Data.Maybe
 import Data.List
diff --git a/compiler/nativeGen/RegAlloc/Linear/PPC/FreeRegs.hs b/compiler/nativeGen/RegAlloc/Linear/PPC/FreeRegs.hs
index 24577c446cdd..1239380ba2a7 100644
--- a/compiler/nativeGen/RegAlloc/Linear/PPC/FreeRegs.hs
+++ b/compiler/nativeGen/RegAlloc/Linear/PPC/FreeRegs.hs
@@ -9,7 +9,7 @@ import RegClass
 import Reg
 
 import Outputable
-import Platform
+import GHC.Platform
 
 import Data.Word
 import Data.Bits
diff --git a/compiler/nativeGen/RegAlloc/Linear/SPARC/FreeRegs.hs b/compiler/nativeGen/RegAlloc/Linear/SPARC/FreeRegs.hs
index 09003cf0a3a1..5528a3872792 100644
--- a/compiler/nativeGen/RegAlloc/Linear/SPARC/FreeRegs.hs
+++ b/compiler/nativeGen/RegAlloc/Linear/SPARC/FreeRegs.hs
@@ -11,7 +11,7 @@ import Reg
 
 import CodeGen.Platform
 import Outputable
-import Platform
+import GHC.Platform
 
 import Data.Word
 import Data.Bits
diff --git a/compiler/nativeGen/RegAlloc/Linear/X86/FreeRegs.hs b/compiler/nativeGen/RegAlloc/Linear/X86/FreeRegs.hs
index b8af046d825a..e7f8cb4a6357 100644
--- a/compiler/nativeGen/RegAlloc/Linear/X86/FreeRegs.hs
+++ b/compiler/nativeGen/RegAlloc/Linear/X86/FreeRegs.hs
@@ -9,7 +9,7 @@ import X86.Regs
 import RegClass
 import Reg
 import Panic
-import Platform
+import GHC.Platform
 
 import Data.Word
 import Data.Bits
diff --git a/compiler/nativeGen/RegAlloc/Linear/X86_64/FreeRegs.hs b/compiler/nativeGen/RegAlloc/Linear/X86_64/FreeRegs.hs
index 3a6e3407a768..44a3bbb306e8 100644
--- a/compiler/nativeGen/RegAlloc/Linear/X86_64/FreeRegs.hs
+++ b/compiler/nativeGen/RegAlloc/Linear/X86_64/FreeRegs.hs
@@ -9,7 +9,7 @@ import X86.Regs
 import RegClass
 import Reg
 import Panic
-import Platform
+import GHC.Platform
 
 import Data.Word
 import Data.Bits
diff --git a/compiler/nativeGen/RegAlloc/Liveness.hs b/compiler/nativeGen/RegAlloc/Liveness.hs
index 3ad01c6d7c11..bbb7976a753f 100644
--- a/compiler/nativeGen/RegAlloc/Liveness.hs
+++ b/compiler/nativeGen/RegAlloc/Liveness.hs
@@ -51,7 +51,7 @@ import Digraph
 import DynFlags
 import MonadUtils
 import Outputable
-import Platform
+import GHC.Platform
 import UniqSet
 import UniqFM
 import UniqSupply
diff --git a/compiler/nativeGen/SPARC/CodeGen.hs b/compiler/nativeGen/SPARC/CodeGen.hs
index ea81219c6965..30a4d6979b00 100644
--- a/compiler/nativeGen/SPARC/CodeGen.hs
+++ b/compiler/nativeGen/SPARC/CodeGen.hs
@@ -59,7 +59,7 @@ import DynFlags
 import FastString
 import OrdList
 import Outputable
-import Platform
+import GHC.Platform
 
 import Control.Monad    ( mapAndUnzipM )
 
diff --git a/compiler/nativeGen/SPARC/CodeGen/Base.hs b/compiler/nativeGen/SPARC/CodeGen/Base.hs
index 039bb6496cf3..e64af0c44e20 100644
--- a/compiler/nativeGen/SPARC/CodeGen/Base.hs
+++ b/compiler/nativeGen/SPARC/CodeGen/Base.hs
@@ -26,7 +26,7 @@ import CodeGen.Platform
 import DynFlags
 import Cmm
 import PprCmmExpr ()
-import Platform
+import GHC.Platform
 
 import Outputable
 import OrdList
diff --git a/compiler/nativeGen/SPARC/Instr.hs b/compiler/nativeGen/SPARC/Instr.hs
index 3f78ac51d772..f57b6fafb5cb 100644
--- a/compiler/nativeGen/SPARC/Instr.hs
+++ b/compiler/nativeGen/SPARC/Instr.hs
@@ -46,7 +46,7 @@ import DynFlags
 import Cmm
 import FastString
 import Outputable
-import Platform
+import GHC.Platform
 
 
 -- | Register or immediate
diff --git a/compiler/nativeGen/SPARC/Ppr.hs b/compiler/nativeGen/SPARC/Ppr.hs
index 0619956f394e..fc67f7754197 100644
--- a/compiler/nativeGen/SPARC/Ppr.hs
+++ b/compiler/nativeGen/SPARC/Ppr.hs
@@ -47,7 +47,7 @@ import Hoopl.Collections
 
 import Unique           ( pprUniqueAlways )
 import Outputable
-import Platform
+import GHC.Platform
 import FastString
 
 -- -----------------------------------------------------------------------------
diff --git a/compiler/nativeGen/TargetReg.hs b/compiler/nativeGen/TargetReg.hs
index 6800b9043b63..da39b635b246 100644
--- a/compiler/nativeGen/TargetReg.hs
+++ b/compiler/nativeGen/TargetReg.hs
@@ -29,7 +29,7 @@ import Format
 
 import Outputable
 import Unique
-import Platform
+import GHC.Platform
 
 import qualified X86.Regs       as X86
 import qualified X86.RegInfo    as X86
diff --git a/compiler/nativeGen/X86/CodeGen.hs b/compiler/nativeGen/X86/CodeGen.hs
index 21e18ee6fd49..73cfb28d4616 100644
--- a/compiler/nativeGen/X86/CodeGen.hs
+++ b/compiler/nativeGen/X86/CodeGen.hs
@@ -54,7 +54,7 @@ import NCGMonad   ( NatM, getNewRegNat, getNewLabelNat, setDeltaNat
 import CFG
 import Format
 import Reg
-import Platform
+import GHC.Platform
 
 -- Our intermediate code:
 import BasicTypes
diff --git a/compiler/nativeGen/X86/Instr.hs b/compiler/nativeGen/X86/Instr.hs
index 0e69d421a3c8..6e5d656beb38 100644
--- a/compiler/nativeGen/X86/Instr.hs
+++ b/compiler/nativeGen/X86/Instr.hs
@@ -34,7 +34,7 @@ import CodeGen.Platform
 import Cmm
 import FastString
 import Outputable
-import Platform
+import GHC.Platform
 
 import BasicTypes       (Alignment)
 import CLabel
diff --git a/compiler/nativeGen/X86/Ppr.hs b/compiler/nativeGen/X86/Ppr.hs
index bf28d29be935..095d9eba7c54 100644
--- a/compiler/nativeGen/X86/Ppr.hs
+++ b/compiler/nativeGen/X86/Ppr.hs
@@ -42,7 +42,7 @@ import Cmm              hiding (topInfoTable)
 import BlockId
 import CLabel
 import Unique           ( pprUniqueAlways )
-import Platform
+import GHC.Platform
 import FastString
 import Outputable
 
diff --git a/compiler/nativeGen/X86/RegInfo.hs b/compiler/nativeGen/X86/RegInfo.hs
index 24823e398597..19056be4fa25 100644
--- a/compiler/nativeGen/X86/RegInfo.hs
+++ b/compiler/nativeGen/X86/RegInfo.hs
@@ -15,7 +15,7 @@ import Format
 import Reg
 
 import Outputable
-import Platform
+import GHC.Platform
 import Unique
 
 import UniqFM
diff --git a/compiler/nativeGen/X86/Regs.hs b/compiler/nativeGen/X86/Regs.hs
index 37e99c5a71e5..2d9fd88c8e33 100644
--- a/compiler/nativeGen/X86/Regs.hs
+++ b/compiler/nativeGen/X86/Regs.hs
@@ -60,7 +60,7 @@ import Cmm
 import CLabel           ( CLabel )
 import DynFlags
 import Outputable
-import Platform
+import GHC.Platform
 
 import qualified Data.Array as A
 
diff --git a/compiler/prelude/PrelRules.hs b/compiler/prelude/PrelRules.hs
index 6b93df5494ee..8a1876506dc3 100644
--- a/compiler/prelude/PrelRules.hs
+++ b/compiler/prelude/PrelRules.hs
@@ -53,7 +53,7 @@ import Outputable
 import FastString
 import BasicTypes
 import DynFlags
-import Platform
+import GHC.Platform
 import Util
 import Coercion     (mkUnbranchedAxInstCo,mkSymCo,Role(..))
 
diff --git a/compiler/stgSyn/StgSyn.hs b/compiler/stgSyn/StgSyn.hs
index 4922c15d3f52..2372e3ed27f4 100644
--- a/compiler/stgSyn/StgSyn.hs
+++ b/compiler/stgSyn/StgSyn.hs
@@ -76,7 +76,7 @@ import Literal     ( Literal, literalType )
 import Module      ( Module )
 import Outputable
 import Packages    ( isDllName )
-import Platform
+import GHC.Platform
 import PprCore     ( {- instances -} )
 import PrimOp      ( PrimOp, PrimCall )
 import TyCon       ( PrimRep(..), TyCon )
diff --git a/compiler/typecheck/TcForeign.hs b/compiler/typecheck/TcForeign.hs
index 61c35e7e5da1..ace0cddb668d 100644
--- a/compiler/typecheck/TcForeign.hs
+++ b/compiler/typecheck/TcForeign.hs
@@ -57,7 +57,7 @@ import TcType
 import PrelNames
 import DynFlags
 import Outputable
-import Platform
+import GHC.Platform
 import SrcLoc
 import Bag
 import Hooks
diff --git a/compiler/utils/AsmUtils.hs b/compiler/utils/AsmUtils.hs
index 36fb7ef6cb1d..bb19dc2ba34c 100644
--- a/compiler/utils/AsmUtils.hs
+++ b/compiler/utils/AsmUtils.hs
@@ -8,7 +8,7 @@ module AsmUtils
 
 import GhcPrelude
 
-import Platform
+import GHC.Platform
 import Outputable
 
 -- | Generate a section type (e.g. @\@progbits@). See #13937.
diff --git a/compiler/utils/Outputable.hs b/compiler/utils/Outputable.hs
index ee857a817ea0..a5306faaa468 100644
--- a/compiler/utils/Outputable.hs
+++ b/compiler/utils/Outputable.hs
@@ -101,7 +101,7 @@ import BufWrite (BufHandle)
 import FastString
 import qualified Pretty
 import Util
-import Platform
+import GHC.Platform
 import qualified PprColour as Col
 import Pretty           ( Doc, Mode(..) )
 import Panic
diff --git a/ghc/GHCi/Leak.hs b/ghc/GHCi/Leak.hs
index 3bb9bbceb5b3..0878f9ff5a29 100644
--- a/ghc/GHCi/Leak.hs
+++ b/ghc/GHCi/Leak.hs
@@ -13,7 +13,7 @@ import GHC.Ptr (Ptr (..))
 import GHCi.Util
 import HscTypes
 import Outputable
-import Platform (target32Bit)
+import GHC.Platform (target32Bit)
 import Prelude
 import System.Mem
 import System.Mem.Weak
diff --git a/compiler/utils/Platform.hs b/libraries/ghc-boot/GHC/Platform.hs
similarity index 98%
rename from compiler/utils/Platform.hs
rename to libraries/ghc-boot/GHC/Platform.hs
index 5f7d939f0de9..8344778ea9d9 100644
--- a/compiler/utils/Platform.hs
+++ b/libraries/ghc-boot/GHC/Platform.hs
@@ -1,7 +1,7 @@
 
 -- | A description of the platform we're compiling for.
 --
-module Platform (
+module GHC.Platform (
         Platform(..),
         Arch(..),
         OS(..),
@@ -23,7 +23,7 @@ module Platform (
 
 where
 
-import GhcPrelude
+import Prelude -- See Note [Why do we import Prelude here?]
 
 -- | Contains enough information for the native code generator to emit
 --      code for this platform.
diff --git a/libraries/ghc-boot/ghc-boot.cabal.in b/libraries/ghc-boot/ghc-boot.cabal.in
index 97872c15f78c..15721b1489a9 100644
--- a/libraries/ghc-boot/ghc-boot.cabal.in
+++ b/libraries/ghc-boot/ghc-boot.cabal.in
@@ -43,6 +43,7 @@ Library
             GHC.Serialized
             GHC.ForeignSrcLang
             GHC.HandleEncoding
+            GHC.Platform
 
     build-depends: base       >= 4.7 && < 4.14,
                    binary     == 0.8.*,
diff --git a/testsuite/tests/codeGen/should_run/T13825-unit.hs b/testsuite/tests/codeGen/should_run/T13825-unit.hs
index 1197dc60fe6f..40088aa734a4 100644
--- a/testsuite/tests/codeGen/should_run/T13825-unit.hs
+++ b/testsuite/tests/codeGen/should_run/T13825-unit.hs
@@ -8,7 +8,7 @@ import StgCmmClosure
 import GHC
 import GhcMonad
 import System.Environment
-import Platform
+import GHC.Platform
 
 main :: IO ()
 main = do
-- 
GitLab