1ghc-settings-edit is a small tool for changing certain fields in the settings
2file that is part of every GHC installation (usually located at
3lib/ghc-$version/lib/settings or lib/ghc-$version/settings). This is sometimes
4necessary because GHC's build process leaks the tools used at build time into
5the final settings file. This is fine, as long as the build and host platform
6of the GHC build is the same since it will be possible to execute the tools
7used at build time at run time. In case we are cross compiling GHC itself,
8the settings file needs to be changed so that the correct tools are used in the
9final installation. The GHC build system itself doesn't allow for this due to
10its somewhat peculiar bootstrapping mechanism.
11
12This tool was originally written by sternenseemann and is licensed under the MIT
13license (as is nixpkgs) as well as the BSD 3 Clause license since it incorporates
14some code from GHC. It is primarily intended for use in nixpkgs, so it should be
15considered unstable: No guarantees about the stability of its command line
16interface are made at this time.
17
18> -- SPDX-License-Identifier: MIT AND BSD-3-Clause
19> {-# LANGUAGE LambdaCase #-}
20> module Main where
21
22ghc-settings-edit requires no additional dependencies to the ones already
23required to bootstrap GHC. This means that it only depends on GHC and core
24libraries shipped with the compiler (base and containers). This property should
25be preserved going forward as to not needlessly complicate bootstrapping GHC
26in nixpkgs. Additionally, a wide range of library versions and thus GHC versions
27should be supported (via CPP if necessary).
28
29> import Control.Monad (foldM)
30> import qualified Data.Map.Lazy as Map
31> import System.Environment (getArgs, getProgName)
32> import Text.Read (readEither)
33
34Note that the containers dependency is needed to represent the contents of the
35settings file. In theory, [(String, String)] (think lookup) would suffice, but
36base doesn't provide any facilities for updating such lists. To avoid needlessly
37reinventing the wheel here, we depend on an extra core library.
38
39> type SettingsMap = Map.Map String String
40
41ghc-settings-edit accepts the following arguments:
42
43- The path to the settings file which is edited in place.
44- For every field in the settings file to be updated, two arguments need to be
45 passed: the name of the field and its new value. Any number of these pairs
46 may be provided. If a field is missing from the given settings file,
47 it won't be added (see also below).
48
49> usage :: String -> String
50> usage name = "Usage: " ++ name ++ " FILE [KEY NEWVAL [KEY2 NEWVAL2 ...]]"
51
52The arguments and the contents of the settings file are fed into the performEdits
53function which implements the main logic of ghc-settings-edit (except IO).
54
55> performEdits :: [String] -> String -> Either String String
56> performEdits editArgs settingsString = do
57
58First, the settings file is parsed and read into the SettingsMap structure. For
59parsing, we can simply rely read, as GHC uses the familiar Read/Show format
60(plus some formatting) for storing its settings. This is the main reason
61ghc-settings-edit is written in Haskell: We don't need to roll our own parser.
62
63> settingsMap <- Map.fromList <$> readEither settingsString
64
65We also need to parse the remaining command line arguments (after the path)
66which means splitting them into pairs of arguments describing the individual
67edits. We use the chunkList utility function from GHC for this which is vendored
68below. Since it doesn't guarantee that all sublists have the exact length given,
69we'll have to check the length of the returned “pairs” later.
70
71> let edits = chunkList 2 editArgs
72
73Since each edit is a transformation of the SettingsMap, we use a fold to go
74through the edits. The Either monad allows us to bail out if one is malformed.
75The use of Map.adjust ensures that fields that aren't present in the original
76settings file aren't added since the corresponding GHC installation wouldn't
77understand them. Note that this is done silently which may be suboptimal:
78It could be better to fail.
79
80> show . Map.toList <$> foldM applyEdit settingsMap edits
81> where
82> applyEdit :: SettingsMap -> [String] -> Either String SettingsMap
83> applyEdit m [key, newValue] = Right $ Map.adjust (const newValue) key m
84> applyEdit _ _ = Left "Uneven number of edit arguments provided"
85
86main just wraps performEdits and takes care of reading from and writing to the
87given file.
88
89> main :: IO ()
90> main =
91> getArgs >>= \case
92> (settingsFile:edits) -> do
93> orig <- readFile settingsFile
94> case performEdits edits orig of
95> Right edited -> writeFile settingsFile edited
96> Left errorMsg -> error errorMsg
97> _ -> do
98> name <- getProgName
99> error $ usage name
100
101As mentioned, chunkList is taken from GHC, specifically GHC.Utils.Misc of GHC
102verson 9.8.2. We don't depend on the ghc library directly (which would be
103possible in theory) since there are no stability guarantees or deprecation
104windows for the ghc's public library.
105
106> -- | Split a list into chunks of /n/ elements
107> chunkList :: Int -> [a] -> [[a]]
108> chunkList _ [] = []
109> chunkList n xs = as : chunkList n bs where (as,bs) = splitAt n xs