···11+ghc-settings-edit is a small tool for changing certain fields in the settings
22+file that is part of every GHC installation (usually located at
33+lib/ghc-$version/lib/settings or lib/ghc-$version/settings). This is sometimes
44+necessary because GHC's build process leaks the tools used at build time into
55+the final settings file. This is fine, as long as the build and host platform
66+of the GHC build is the same since it will be possible to execute the tools
77+used at build time at run time. In case we are cross compiling GHC itself,
88+the settings file needs to be changed so that the correct tools are used in the
99+final installation. The GHC build system itself doesn't allow for this due to
1010+its somewhat peculiar bootstrapping mechanism.
1111+1212+This tool was originally written by sternenseemann and is licensed under the MIT
1313+license (as is nixpkgs) as well as the BSD 3 Clause license since it incorporates
1414+some code from GHC. It is primarily intended for use in nixpkgs, so it should be
1515+considered unstable: No guarantees about the stability of its command line
1616+interface are made at this time.
1717+1818+> -- SPDX-License-Identifier: MIT AND BSD-3-Clause
1919+> {-# LANGUAGE LambdaCase #-}
2020+> module Main where
2121+2222+ghc-settings-edit requires no additional dependencies to the ones already
2323+required to bootstrap GHC. This means that it only depends on GHC and core
2424+libraries shipped with the compiler (base and containers). This property should
2525+be preserved going forward as to not needlessly complicate bootstrapping GHC
2626+in nixpkgs. Additionally, a wide range of library versions and thus GHC versions
2727+should be supported (via CPP if necessary).
2828+2929+> import Control.Monad (foldM)
3030+> import qualified Data.Map.Lazy as Map
3131+> import System.Environment (getArgs, getProgName)
3232+> import Text.Read (readEither)
3333+3434+Note that the containers dependency is needed to represent the contents of the
3535+settings file. In theory, [(String, String)] (think lookup) would suffice, but
3636+base doesn't provide any facilities for updating such lists. To avoid needlessly
3737+reinventing the wheel here, we depend on an extra core library.
3838+3939+> type SettingsMap = Map.Map String String
4040+4141+ghc-settings-edit accepts the following arguments:
4242+4343+- The path to the settings file which is edited in place.
4444+- For every field in the settings file to be updated, two arguments need to be
4545+ passed: the name of the field and its new value. Any number of these pairs
4646+ may be provided. If a field is missing from the given settings file,
4747+ it won't be added (see also below).
4848+4949+> usage :: String -> String
5050+> usage name = "Usage: " ++ name ++ " FILE [KEY NEWVAL [KEY2 NEWVAL2 ...]]"
5151+5252+The arguments and the contents of the settings file are fed into the performEdits
5353+function which implements the main logic of ghc-settings-edit (except IO).
5454+5555+> performEdits :: [String] -> String -> Either String String
5656+> performEdits editArgs settingsString = do
5757+5858+First, the settings file is parsed and read into the SettingsMap structure. For
5959+parsing, we can simply rely read, as GHC uses the familiar Read/Show format
6060+(plus some formatting) for storing its settings. This is the main reason
6161+ghc-settings-edit is written in Haskell: We don't need to roll our own parser.
6262+6363+> settingsMap <- Map.fromList <$> readEither settingsString
6464+6565+We also need to parse the remaining command line arguments (after the path)
6666+which means splitting them into pairs of arguments describing the individual
6767+edits. We use the chunkList utility function from GHC for this which is vendored
6868+below. Since it doesn't guarantee that all sublists have the exact length given,
6969+we'll have to check the length of the returned “pairs” later.
7070+7171+> let edits = chunkList 2 editArgs
7272+7373+Since each edit is a transformation of the SettingsMap, we use a fold to go
7474+through the edits. The Either monad allows us to bail out if one is malformed.
7575+The use of Map.adjust ensures that fields that aren't present in the original
7676+settings file aren't added since the corresponding GHC installation wouldn't
7777+understand them. Note that this is done silently which may be suboptimal:
7878+It could be better to fail.
7979+8080+> show . Map.toList <$> foldM applyEdit settingsMap edits
8181+> where
8282+> applyEdit :: SettingsMap -> [String] -> Either String SettingsMap
8383+> applyEdit m [key, newValue] = Right $ Map.adjust (const newValue) key m
8484+> applyEdit _ _ = Left "Uneven number of edit arguments provided"
8585+8686+main just wraps performEdits and takes care of reading from and writing to the
8787+given file.
8888+8989+> main :: IO ()
9090+> main =
9191+> getArgs >>= \case
9292+> (settingsFile:edits) -> do
9393+> orig <- readFile settingsFile
9494+> case performEdits edits orig of
9595+> Right edited -> writeFile settingsFile edited
9696+> Left errorMsg -> error errorMsg
9797+> _ -> do
9898+> name <- getProgName
9999+> error $ usage name
100100+101101+As mentioned, chunkList is taken from GHC, specifically GHC.Utils.Misc of GHC
102102+verson 9.8.2. We don't depend on the ghc library directly (which would be
103103+possible in theory) since there are no stability guarantees or deprecation
104104+windows for the ghc's public library.
105105+106106+> -- | Split a list into chunks of /n/ elements
107107+> chunkList :: Int -> [a] -> [[a]]
108108+> chunkList _ [] = []
109109+> chunkList n xs = as : chunkList n bs where (as,bs) = splitAt n xs