diff --git a/compiler/basicTypes/Literal.hs b/compiler/basicTypes/Literal.hs
index 8dd6708edaa8de233a538b628071c5518e2509c9..abf74a7cbd28e61b7c3962e86c4830315d8f43de 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 d30bd4c0f78713dcf23d2a1dfcae33bd91ad4cb9..95f5a41a23e65f55e187a3f251eee49bb1a6253a 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 be96fba7e9f14ecc06df96430fbf2e1d044e30cf..04b3d70f54cc617a2689a406e671bdc0cb2e9878 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 078390638d52be1fcc88d0f7dd292c9ef6cbfc65..4e6a9d293a25edab8a3d790799e849c573ef773b 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 c374e9fd8119c12a8dc1c3edb3aa7ba5baae6520..16ab6ed587699c1049196ef3a73472805a09f5e8 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 e837d297835bcaa58a5f69d8b4fbd8eff6bc8f11..ed8b386238c46c2b44a6738d9277126fcc918ce8 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 20d12bb40193bf4a858dda525efda7a4abd04f55..f83fb6b00006df02cacd910d21892224f45f6917 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 7f7c1118482e6fa325a53a53f3a6893f6a7bacfe..2f481c272a03f4b7deddfadaa06974d3ba7650c5 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 427de3bb3de5b5467bd2c0ad34935d1b009ed654..528337c57e0a73eb635aa69edb3d2ac1dffa5f3e 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 26d0a6fd9a8d75f9b91fcee634ea5bc2b6fd4c1b..409cd0fbf225a1883307f93f4c23bd81bb4fabaf 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 e57c409a049e993705f04b5c6de3492fec4be459..f68496879533bff5677784091b736da0a33d370b 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 8cd9c3e497a230dd8a5ca384ea25d673f7d9b7f9..57d5354cca76a3daf3f9780301eaae375b318f28 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 9d9a0cf2d115a54aab17e7249bbf25a292f7b3ec..bc216758a00618cdc7c0e8527c6fb3d01be3f5ae 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 258896ff1ac68a745ae3cd96f7fbb087097a1eb8..67a9776eacae28b08b3fd7c2aa9cc0040c44c7a0 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 2d56bf41d553bec03d8b08e24ac87683d17d1b81..c3f9d5a2795b72dba7d9b36c30a03616a3f48ddf 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 e49ffb5973678e1299a5103a7eba2ff0d1917d54..98bffd37770ba6775ebe184d5dcf2ad96fb323b4 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 8e298adf6a6d9ae13905de62e81d2f2b905d3fb0..5204d5e9f6088a037fa1d3de4bff96263913fe5c 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 dd0cc4860a4cd2184d5e7a86da80e4b4d02e4aca..3ecd9bfead4f38029994cfeb3958bf03ee369ef6 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 d380d96707a7e4b990efc3c5cefd178740469840..1a235c40087f0d9954ba7f1bf5ee0485ee63155f 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 fb38ca1c02bc60c016e5f7638ec157820607f2b2..aa556e774fdcb05de916de52cc798eb2b0669d4a 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 33ae172d713222a3c6517897ebd034e2941016c5..8b23e08003de6c13c61302de1205b71e7c99460a 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 e26dcce1ee61aa8657f01bc1ee45a673c1549fe9..bd74d36c5684e8636ec953f0040775084ad92884 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 e365a8edd476323a0798916af5891c3088e43cdb..e1ca00e8a80ed0a860a208dda8ba6a3d05ea4c2a 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 ab9695778c88cd92483668426784eff9bf46f3a0..b47bf6aff6859bebb3965d4c09b7110ac9584136 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 28f38d09ec55a9ef8eade138ced340df59b10305..bdf6a2642f27213a39bbb44c7203fd88643a73ad 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 3651a88cc6529043d9540fb4e491c7619b72f503..70a04e6bc95aec630812e858771b4419229596f0 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 fe03cf21e97b8d324d454e261a45f654dba83585..114951946c6a88314d9a7f031aaaa879cb683e8e 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 d4392c4c375dac36aa656861fc8eda513e0ccacb..5c88faf895584fcd90adbb7f71fed52d91a0dab1 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 ffc11980e249349d61a3c48249adfbd5686d27f1..f77927f8e5626d08623651341d68cafc50b74c67 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 76b5be6573eba79ee28b856b2653ca63b182922c..7a6bca627744d5cab45826646d1c213f2fb06307 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 823fd228549e3f561f623384cd55bf7fb311eb72..bed4ae2fd1091e7000436e55f1703c84d4209368 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 d89ccf8dea4a0e73f46b3f0eeb7d67760ec05d0e..41e59850c00ef8b41d619b3deabb9e04913820b1 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 196019335848c95f3b85766b2f94fdc03fa8cdf2..d7658ad2aa7a0558e5ec5ae2c37321934939ccaf 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 2749073ff15a643b18452716e3aafb3ebe58eff0..0fa9ffa6649fad585e83d0fe63fb9009e5ca15e5 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 64e012c57fdbe35e464f1ecaff1913dc2f9be3d2..ec63308b83f41a6a673f10bd2bbb014539125ce9 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 b8285340cf51234c73242bf75f38d5756e3d1063..e9e09711ba36f91515f210bb95be8c701ae4fe3e 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 47547fca5b4339de15362624246a2964687c5bcd..9f327c90d9be3bee47b2ef23db2c13231b18f300 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 6db3f3243d66f28783fb91fe73b6aeac7fe63410..5ab880513295118f1d08f6d7aeaa055360cb3814 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 149d3a678ad2a7c39292799d16942e928d177060..c930389c95479fcff839d458a55f0d7414332f47 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 9aa9002c2369401b9bec0939e682b1ed0ffc2ff1..e61846d4e6f87b8b639214df569dbd091d977bda 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 1747d50be1e159d23af38d8a904aceb1103c60db..10e1102304cf433f6a7ad6f588548333ae2832f3 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 ed0c57e1e2521497f95c39526f2c13c4e1417f18..6e9450fd8574aac5b045b43b40ed778123f6ea34 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 0e645a2a560e753b0c0a61a3d55a76903b7ba436..b64b4efc338ce7f0fa87c0aa6a5281683eb1cffe 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 687a4f818f6903aa412f80fb9a37bf80a828ec6d..01b85c47bcaa3bc78d129a018cb1aab7509e3ed5 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 57ff0b2478084b9fec4a5e94571fdaf00d9a294c..01253544e6d1a3fbfb55379f2c07f730bedc2c13 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 0bd99fbee8807e5d5fd60dd9a5db47d5918fd3fb..4f18a45c16b0b5788ffdf80be7bb89886d44a672 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 69113e8ea5f0e5c217f9c56d68caefb0fe9046c7..9c57a0292f24c2fb3ab79c02636ddcde8cc6f265 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 03e8e42d9ae48da1dfb9bd7c8fda66c94065e063..516cda0eb3c243d11434b34d26324267139148f0 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 3bf19f2dc653e06c9200ca418337ea0733484a35..b17ea32f01aa9d2b1e0e4334a2a9e808317b6ba1 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 be6402e57a1b4ab50debbc6e071d2ad147f9169b..4254f23122649cbbaa11ee70832635177233e527 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 8ba2ead926de6ea5ff4fbf0c2fd5f293dfd24fcb..5b7ac208b6cc41ea2e125ea9b076ff7b205ca382 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 80f3e6179b3f4e0cefaba79018f0a9f79928eedf..48e9e26ae44994cc670b83729530b94e0883a09b 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 c7875cfaeae6e53631040b9f78fbe339b6ccb0fb..df97de1c629e02cc16ce504c89b617955322acd1 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 bc26a663a54fd4ac085b2f995ffbf124bcb05b33..eccc83eb48045c8f2f587625ccbf8560f57a3d18 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 50001d7334599e2b332153600dc68d96c99c8617..6d7b377d68b8f4015e18963fcb36bb47b0d84c7d 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 b62c44fa812b39bd84cd5562aaae0d1a59cd4e0f..9c6e24d320799199c6011845196e1ff82e1f0321 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 8db80ef064778ab12c48658f102a1e30c1d90400..5d4fd418c3504aae3f7e8f0d749fe47f6b505302 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 b4e79432d811050f85c8e91e14fb122c223a4d59..5a4f1c65a85a84c594d038093f6ee4895d194a09 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 a9337b00441d272818290ef0c12c605f25907ff4..cdaf738d6861ebca7aaf20caa5b44d2f558991fd 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 24577c446cdd9dd2773598577b3f350d666be381..1239380ba2a7bc562c2bb95755fd5c67d5185de8 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 09003cf0a3a148182565da0017fd9f66b64c9615..5528a3872792572522e759a613a68434b5b1a828 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 b8af046d825aea868e71d02ca684fad97764e9af..e7f8cb4a635713307d75d95af0783f101c9ff054 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 3a6e3407a768dc81210aff5256b37662f42be54a..44a3bbb306e89e2475204f118a4c6c8838585281 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 3ad01c6d7c112e10b4fc1ded1b34f7898d5027e2..bbb7976a753ffacc7ef832a3417509aaf263ccd6 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 ea81219c6965613a398bd1f9543d19f2a6e2b113..30a4d6979b0008c3b81afcfe28fbe55328d553e8 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 039bb6496cf3bb6bea83e0653e5154f241dfee6d..e64af0c44e20b1a77bb25e852472eb9177ebcc5c 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 3f78ac51d772edd85221d17c41969013c4dc2eee..f57b6fafb5cb02493565e53a370637b1da13a525 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 0619956f394e381b27ee9ccaefc38010c5ebe03c..fc67f7754197521a2f728ac98cbaef5b48b8a24d 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 6800b9043b637b231b25858e4a7d898602508825..da39b635b246ecc1e78c3f3c2b781e347888c0c4 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 21e18ee6fd49256a37a3ed97ad5130142407bc20..73cfb28d461678915f63a32fb76e8e8c90d583be 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 0e69d421a3c889f59935c021d84d40166607fd32..6e5d656beb3885854aed0f3d27d1dedca24b14dd 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 bf28d29be9356f64bc955da82962aa667a0ea80c..095d9eba7c5426c1f3818e3c92bc6bb6ce087b36 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 24823e398597b0c981b1ece3721828f952fbbf44..19056be4fa252822bf39ac5bd54a99f123122fa0 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 37e99c5a71e5bc996bb36911e2953def9ff27dc1..2d9fd88c8e33a61c1def480d77eae2adba79009e 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 6b93df5494ee745fd67c6d02d6cb685dded98cc3..8a1876506dc32da871dc2f3e763ed890c0f1431d 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 4922c15d3f5291c2acf57b82f02e0f9af2dfab57..2372e3ed27f437509d6637d6d4a39983ca36cad1 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 61c35e7e5da1aa3323d654d539dafab8dd6e2e2a..ace0cddb668daf3aa8cc4955f6cb4a5626c70f31 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 36fb7ef6cb1dfd5911a199f258dc1ab5b056af02..bb19dc2ba34c0f79356f6d559fb42549a42c66dc 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 ee857a817ea00267f5e0e0e5668fb339d987a63e..a5306faaa4684dc018f1d6d4914794bb67901c43 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 3bb9bbceb5b3aaf854e2b7f469f7847507500992..0878f9ff5a2991ce2d2d379f5ae4b160d00126fd 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 5f7d939f0de90b5844c9a712d9f205c5e125476e..8344778ea9d91259dadb7f918faf6ec42ff3ac28 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 97872c15f78c59f80a8e12d83920c26f3e65fc0e..15721b1489a9d69b8cf3b67abfdfbbeafa7abc5d 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 1197dc60fe6f32bc23fdc1e81deb677e1c895fb7..40088aa734a400d23ca89a2868b6e8b6d66d985f 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