summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorSylvain Henry <sylvain@haskus.fr>2021-04-09 14:39:27 +0200
committerMarge Bot <ben+marge-bot@smart-cactus.org>2021-04-10 05:31:14 -0400
commitb699c4fb0d23616a20d160f04a893f514fc7e38c (patch)
treed26e8dd39d908ec1c35945c613c48b39eba84b09
parent2cdc95f9c068421a55c634933ab2d8596eb992fb (diff)
downloadhaskell-b699c4fb0d23616a20d160f04a893f514fc7e38c.tar.gz
Constants: add a note and fix minor doc glitches
-rw-r--r--compiler/GHC/Platform.hs62
-rw-r--r--compiler/GHC/Unit/State.hs40
-rw-r--r--includes/Cmm.h4
-rw-r--r--includes/rts/Constants.h2
4 files changed, 79 insertions, 29 deletions
diff --git a/compiler/GHC/Platform.hs b/compiler/GHC/Platform.hs
index 5ce843046b..b3ab1b4020 100644
--- a/compiler/GHC/Platform.hs
+++ b/compiler/GHC/Platform.hs
@@ -1,11 +1,10 @@
{-# LANGUAGE ScopedTypeVariables #-}
+{-# LANGUAGE LambdaCase #-}
-- | Platform description
module GHC.Platform
( Platform (..)
- , platformConstants
, PlatformWordSize(..)
- , PlatformConstants(..)
, platformArch
, platformOS
, ArchOS(..)
@@ -33,6 +32,10 @@ module GHC.Platform
, PlatformMisc(..)
, SseVersion (..)
, BmiVersion (..)
+ -- * Platform constants
+ , PlatformConstants(..)
+ , lookupPlatformConstants
+ , platformConstants
-- * Shared libraries
, platformSOName
, platformHsSOName
@@ -51,6 +54,7 @@ import GHC.Utils.Panic.Plain
import Data.Word
import Data.Int
import System.FilePath
+import System.Directory
-- | Platform description
--
@@ -249,3 +253,57 @@ platformSOExt platform
OSDarwin -> "dylib"
OSMinGW32 -> "dll"
_ -> "so"
+
+-- Note [Platform constants]
+-- ~~~~~~~~~~~~~~~~~~~~~~~~~
+--
+-- The RTS is partly written in C, hence we use an external C compiler to build
+-- it. Thus GHC must somehow retrieve some information about the produced code
+-- (sizes of types, offsets of struct fields, etc.) to produce compatible code.
+--
+-- This is the role of utils/deriveConstants utility: it produces a C
+-- source, compiles it with the same toolchain that will be used to build the
+-- RTS, and finally retrieves the constants from the built artefact. We can't
+-- directly run the produced program because we may be cross-compiling.
+--
+-- These constants are then stored in DerivedConstants.h header file that is
+-- bundled with the RTS unit. This file is directly imported by Cmm codes and it
+-- is also read by GHC. deriveConstants also produces the Haskell definition of
+-- the PlatformConstants datatype and the Haskell parser for the
+-- DerivedConstants.h file.
+--
+-- For quite some time, constants used by GHC were globally installed in
+-- ${libdir}/platformConstants but now GHC reads the DerivedConstants.h header
+-- bundled with the RTS unit. GHC detects when it builds the RTS unit itself and
+-- in this case it loads the header from the include-dirs passed on the
+-- command-line.
+--
+-- Note that GHC doesn't parse every "#define SOME_CONSTANT 123" individually.
+-- Instead there is a single #define that contains all the constants useful to
+-- GHC in a comma separated list:
+--
+-- #define HS_CONSTANTS "123,45,..."
+--
+-- Note that GHC mustn't directly import DerivedConstants.h as these constants
+-- are only valid for a specific target platform and we want GHC to be target
+-- agnostic.
+--
+
+
+-- | Try to locate "DerivedConstants.h" file in the given dirs and to parse the
+-- PlatformConstants from it.
+--
+-- See Note [Platform constants]
+lookupPlatformConstants :: [FilePath] -> IO (Maybe PlatformConstants)
+lookupPlatformConstants include_dirs = find_constants include_dirs
+ where
+ try_parse d = do
+ let p = d </> "DerivedConstants.h"
+ doesFileExist p >>= \case
+ True -> Just <$> parseConstantsHeader p
+ False -> return Nothing
+
+ find_constants [] = return Nothing
+ find_constants (x:xs) = try_parse x >>= \case
+ Nothing -> find_constants xs
+ Just c -> return (Just c)
diff --git a/compiler/GHC/Unit/State.hs b/compiler/GHC/Unit/State.hs
index 4a1cd29b25..fe4796d1fc 100644
--- a/compiler/GHC/Unit/State.hs
+++ b/compiler/GHC/Unit/State.hs
@@ -77,7 +77,6 @@ import GHC.Driver.Session
import GHC.Platform
import GHC.Platform.Ways
-import GHC.Platform.Constants
import GHC.Unit.Database
import GHC.Unit.Info
@@ -596,29 +595,22 @@ initUnits logger dflags cached_dbs = do
(homeUnitInstanceOf_ dflags)
(homeUnitInstantiations_ dflags)
- -- try to find platform constants
- mconstants <- do
- let
- try_parse d = do
- let p = d </> "DerivedConstants.h"
- doesFileExist p >>= \case
- True -> Just <$> parseConstantsHeader p
- False -> return Nothing
-
- find_constants [] = return Nothing
- find_constants (x:xs) = try_parse x >>= \case
- Nothing -> find_constants xs
- Just c -> return (Just c)
-
- if homeUnitId_ dflags == rtsUnitId
- then do
- -- we're building the RTS! Try to find the header in its includes
- find_constants (includePathsGlobal (includePaths dflags))
- else
- -- try to find the platform constants in the RTS unit
- case lookupUnitId unit_state rtsUnitId of
- Nothing -> return Nothing
- Just info -> find_constants (fmap ST.unpack (unitIncludeDirs info))
+ -- Try to find platform constants
+ --
+ -- See Note [Platform constants] in GHC.Platform
+ mconstants <- if homeUnitId_ dflags == rtsUnitId
+ then do
+ -- we're building the RTS! Lookup DerivedConstants.h in the include paths
+ lookupPlatformConstants (includePathsGlobal (includePaths dflags))
+ else
+ -- lookup the DerivedConstants.h header bundled with the RTS unit. We
+ -- don't fail if we can't find the RTS unit as it can be a valid (but
+ -- uncommon) case, e.g. building a C utility program (not depending on the
+ -- RTS) before building the RTS. In any case, we will fail later on if we
+ -- really need to use the platform constants but they have not been loaded.
+ case lookupUnitId unit_state rtsUnitId of
+ Nothing -> return Nothing
+ Just info -> lookupPlatformConstants (fmap ST.unpack (unitIncludeDirs info))
return (dbs,unit_state,home_unit,mconstants)
diff --git a/includes/Cmm.h b/includes/Cmm.h
index 84c6fca125..b1b8680e99 100644
--- a/includes/Cmm.h
+++ b/includes/Cmm.h
@@ -20,8 +20,8 @@
* StgTSO_what_next(CurrentTSO) = x
*
* where the StgTSO_what_next() macro is automatically generated by
- * mkDerivedConstants.c. If you need to access a field that doesn't
- * already have a macro, edit that file (it's pretty self-explanatory).
+ * utils/deriveConstants. If you need to access a field that doesn't
+ * already have a macro, edit that program (it's pretty self-explanatory).
*
* -------------------------------------------------------------------------- */
diff --git a/includes/rts/Constants.h b/includes/rts/Constants.h
index 043099bd1a..9cbe47752e 100644
--- a/includes/rts/Constants.h
+++ b/includes/rts/Constants.h
@@ -10,7 +10,7 @@
*
* Constants which are derived automatically from other definitions in
* the system (eg. structure sizes) are generated into the file
- * DerivedConstants.h by a C program (mkDerivedConstantsHdr).
+ * DerivedConstants.h by a C program (utils/deriveConstants).
*
* To understand the structure of the RTS headers, see the wiki:
* https://gitlab.haskell.org/ghc/ghc/wikis/commentary/source-tree/includes