-- Copyright (c) 2019 The DAML Authors. All rights reserved.
-- SPDX-License-Identifier: Apache-2.0

{-# LANGUAGE CPP                      #-}
{-# LANGUAGE NondecreasingIndentation #-}

-----------------------------------------------------------------------------
--
-- GHC Driver
--
-- (c) The University of Glasgow 2005
--
-----------------------------------------------------------------------------

module Development.IDE.GHC.CPP(doCpp, addOptP)
where

import           Development.IDE.GHC.Compat      as Compat
import           Development.IDE.GHC.Compat.Util
import           GHC

-- See Note [Guidelines For Using CPP In GHCIDE Import Statements]

import           GHC.Settings

#if !MIN_VERSION_ghc(9,3,0)
import qualified GHC.Driver.Pipeline             as Pipeline
#endif

#if MIN_VERSION_ghc(9,3,0) && !MIN_VERSION_ghc(9,5,0)
import qualified GHC.Driver.Pipeline.Execute     as Pipeline
#endif

#if MIN_VERSION_ghc(9,5,0)
import qualified GHC.SysTools.Cpp                as Pipeline
#endif

addOptP :: String -> DynFlags -> DynFlags
addOptP :: String -> DynFlags -> DynFlags
addOptP String
f = (ToolSettings -> ToolSettings) -> DynFlags -> DynFlags
alterToolSettings ((ToolSettings -> ToolSettings) -> DynFlags -> DynFlags)
-> (ToolSettings -> ToolSettings) -> DynFlags -> DynFlags
forall a b. (a -> b) -> a -> b
$ \ToolSettings
s -> ToolSettings
s
          { toolSettings_opt_P             = f : toolSettings_opt_P s
          , toolSettings_opt_P_fingerprint = fingerprintStrings (f : toolSettings_opt_P s)
          }
  where
    fingerprintStrings :: [String] -> Fingerprint
fingerprintStrings [String]
ss = [Fingerprint] -> Fingerprint
fingerprintFingerprints ([Fingerprint] -> Fingerprint) -> [Fingerprint] -> Fingerprint
forall a b. (a -> b) -> a -> b
$ (String -> Fingerprint) -> [String] -> [Fingerprint]
forall a b. (a -> b) -> [a] -> [b]
map String -> Fingerprint
fingerprintString [String]
ss
    alterToolSettings :: (ToolSettings -> ToolSettings) -> DynFlags -> DynFlags
alterToolSettings ToolSettings -> ToolSettings
g DynFlags
dynFlags = DynFlags
dynFlags { toolSettings = g (toolSettings dynFlags) }

doCpp :: HscEnv -> FilePath -> FilePath -> IO ()
doCpp :: HscEnv -> String -> String -> IO ()
doCpp HscEnv
env String
input_fn String
output_fn =
        -- See GHC commit a2f53ac8d968723417baadfab5be36a020ea6850
        -- this function/Pipeline.doCpp previously had a raw parameter
        -- always set to True that corresponded to these settings

#if MIN_VERSION_ghc(9,5,0)
    let cpp_opts :: CppOpts
cpp_opts = Pipeline.CppOpts
                 { cppLinePragmas :: Bool
cppLinePragmas = Bool
True
# if MIN_VERSION_ghc(9,9,0)
                 , useHsCpp = True
# else
                 , cppUseCc :: Bool
cppUseCc = Bool
False
# endif
                 } in
#else
    let cpp_opts = True in
#endif

    Logger
-> TmpFs
-> DynFlags
-> UnitEnv
-> CppOpts
-> String
-> String
-> IO ()
Pipeline.doCpp (HscEnv -> Logger
hsc_logger HscEnv
env) (HscEnv -> TmpFs
hsc_tmpfs HscEnv
env) (HscEnv -> DynFlags
hsc_dflags HscEnv
env) (HscEnv -> UnitEnv
hsc_unit_env HscEnv
env) CppOpts
cpp_opts String
input_fn String
output_fn