module GHC.Settings.Utils where

import Prelude -- See Note [Why do we import Prelude here?]

import Data.Char (isSpace)
import Data.Map (Map)
import qualified Data.Map as Map

import GHC.BaseDir
import GHC.Platform.ArchOS
import System.FilePath

import GHC.Toolchain.Target

maybeRead :: Read a => String -> Maybe a
maybeRead :: forall a. Read a => [Char] -> Maybe a
maybeRead [Char]
str = case ReadS a
forall a. Read a => ReadS a
reads [Char]
str of
  [(a
x, [Char]
"")] -> a -> Maybe a
forall a. a -> Maybe a
Just a
x
  [(a, [Char])]
_ -> Maybe a
forall a. Maybe a
Nothing

maybeReadFuzzy :: Read a => String -> Maybe a
maybeReadFuzzy :: forall a. Read a => [Char] -> Maybe a
maybeReadFuzzy [Char]
str = case ReadS a
forall a. Read a => ReadS a
reads [Char]
str of
  [(a
x, [Char]
s)] | (Char -> Bool) -> [Char] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all Char -> Bool
isSpace [Char]
s -> a -> Maybe a
forall a. a -> Maybe a
Just a
x
  [(a, [Char])]
_ -> Maybe a
forall a. Maybe a
Nothing


-- Note [Settings file]
-- ~~~~~~~~~~~~~~~~~~~~
--
-- GHC has a file, `${top_dir}/settings`, which is the main source of run-time
-- configuration. ghc-pkg needs just a little bit of it: the target platform CPU
-- arch and OS. It uses that to figure out what subdirectory of `~/.ghc` is
-- associated with the current version/target platform.
--
-- This module has just enough code to read key value pairs from the settings
-- file, and read the target platform from those pairs.

type RawSettings = Map String String

-- | Read target Arch/OS from the settings
getTargetArchOS
  :: Target -- ^ The 'Target' from which to read the 'ArchOS'
  -> ArchOS
getTargetArchOS :: Target -> ArchOS
getTargetArchOS Target
target = Target -> ArchOS
tgtArchOs Target
target

getGlobalPackageDb :: FilePath -> RawSettings -> Either String FilePath
getGlobalPackageDb :: [Char] -> RawSettings -> Either [Char] [Char]
getGlobalPackageDb [Char]
settingsFile RawSettings
settings = do
  rel_db <- [Char] -> RawSettings -> [Char] -> Either [Char] [Char]
getRawSetting [Char]
settingsFile RawSettings
settings [Char]
"Relative Global Package DB"
  return (dropFileName settingsFile </> rel_db)

--------------------------------------------------------------------------------
-- lib/settings

getRawSetting
  :: FilePath -> RawSettings -> String -> Either String String
getRawSetting :: [Char] -> RawSettings -> [Char] -> Either [Char] [Char]
getRawSetting [Char]
settingsFile RawSettings
settings [Char]
key = case [Char] -> RawSettings -> Maybe [Char]
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup [Char]
key RawSettings
settings of
  Just [Char]
xs -> [Char] -> Either [Char] [Char]
forall a b. b -> Either a b
Right [Char]
xs
  Maybe [Char]
Nothing -> [Char] -> Either [Char] [Char]
forall a b. a -> Either a b
Left ([Char] -> Either [Char] [Char]) -> [Char] -> Either [Char] [Char]
forall a b. (a -> b) -> a -> b
$ [Char]
"No entry for " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char] -> [Char]
forall a. Show a => a -> [Char]
show [Char]
key [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" in " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char] -> [Char]
forall a. Show a => a -> [Char]
show [Char]
settingsFile

getRawFilePathSetting
  :: FilePath -> FilePath -> RawSettings -> String -> Either String String
getRawFilePathSetting :: [Char] -> [Char] -> RawSettings -> [Char] -> Either [Char] [Char]
getRawFilePathSetting [Char]
top_dir [Char]
settingsFile RawSettings
settings [Char]
key =
  [Char] -> [Char] -> [Char]
expandTopDir [Char]
top_dir ([Char] -> [Char]) -> Either [Char] [Char] -> Either [Char] [Char]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Char] -> RawSettings -> [Char] -> Either [Char] [Char]
getRawSetting [Char]
settingsFile RawSettings
settings [Char]
key

getRawBooleanSetting
  :: FilePath -> RawSettings -> String -> Either String Bool
getRawBooleanSetting :: [Char] -> RawSettings -> [Char] -> Either [Char] Bool
getRawBooleanSetting [Char]
settingsFile RawSettings
settings [Char]
key = do
  rawValue <- [Char] -> RawSettings -> [Char] -> Either [Char] [Char]
getRawSetting [Char]
settingsFile RawSettings
settings [Char]
key
  case rawValue of
    [Char]
"YES" -> Bool -> Either [Char] Bool
forall a b. b -> Either a b
Right Bool
True
    [Char]
"NO" -> Bool -> Either [Char] Bool
forall a b. b -> Either a b
Right Bool
False
    [Char]
xs -> [Char] -> Either [Char] Bool
forall a b. a -> Either a b
Left ([Char] -> Either [Char] Bool) -> [Char] -> Either [Char] Bool
forall a b. (a -> b) -> a -> b
$ [Char]
"Bad value for " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char] -> [Char]
forall a. Show a => a -> [Char]
show [Char]
key [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
": " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char] -> [Char]
forall a. Show a => a -> [Char]
show [Char]
xs