{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE RankNTypes #-}
module Distribution.Simple.Program.GHC (
    GhcOptions(..),
    GhcMode(..),
    GhcOptimisation(..),
    GhcDynLinkMode(..),
    GhcProfAuto(..),
    ghcInvocation,
    renderGhcOptions,
    runGHC,
    packageDbArgsDb,
  ) where
import Prelude ()
import Distribution.Compat.Prelude
import Distribution.Backpack
import Distribution.Simple.GHC.ImplInfo
import Distribution.PackageDescription hiding (Flag)
import Distribution.ModuleName
import Distribution.Simple.Compiler hiding (Flag)
import qualified Distribution.Simple.Compiler as Compiler (Flag)
import Distribution.Simple.Setup
import Distribution.Simple.Program.Types
import Distribution.Simple.Program.Run
import Distribution.System
import Distribution.Text
import Distribution.Types.ComponentId
import Distribution.Verbosity
import Distribution.Utils.NubList
import Language.Haskell.Extension
import qualified Data.Map as Map
data GhcOptions = GhcOptions {
  
  ghcOptMode          :: Flag GhcMode,
  
  
  ghcOptExtra         :: NubListR String,
  
  
  ghcOptExtraDefault  :: NubListR String,
  
  
  
  ghcOptInputFiles    :: NubListR FilePath,
  
  ghcOptInputModules  :: NubListR ModuleName,
  
  ghcOptOutputFile    :: Flag FilePath,
  
  
  ghcOptOutputDynFile :: Flag FilePath,
  
  
  ghcOptSourcePathClear :: Flag Bool,
  
  ghcOptSourcePath    :: NubListR FilePath,
  
  
  
  
  
  
  
  ghcOptThisUnitId   :: Flag String,
  
  
  
  
  ghcOptThisComponentId :: Flag ComponentId,
  
  
  
  
  ghcOptInstantiatedWith :: [(ModuleName, OpenModule)],
  
  ghcOptNoCode :: Flag Bool,
  
  ghcOptPackageDBs    :: PackageDBStack,
  
  
  ghcOptPackages      ::
    NubListR (OpenUnitId, ModuleRenaming),
  
  ghcOptHideAllPackages :: Flag Bool,
  
  ghcOptWarnMissingHomeModules :: Flag Bool,
  
  
  ghcOptNoAutoLinkPackages :: Flag Bool,
  
  
  
  ghcOptLinkLibs      :: NubListR FilePath,
  
  ghcOptLinkLibPath  :: NubListR FilePath,
  
  ghcOptLinkOptions   :: NubListR String,
  
  ghcOptLinkFrameworks :: NubListR String,
  
  
  ghcOptLinkFrameworkDirs :: NubListR String,
  
  ghcOptNoLink :: Flag Bool,
  
  
  ghcOptLinkNoHsMain :: Flag Bool,
  
  ghcOptLinkModDefFiles :: NubListR FilePath,
  
  
  
  ghcOptCcOptions     :: NubListR String,
  
  ghcOptCxxOptions     :: NubListR String,
  
  ghcOptCppOptions    :: NubListR String,
  
  ghcOptCppIncludePath :: NubListR FilePath,
  
  ghcOptCppIncludes    :: NubListR FilePath,
  
  ghcOptFfiIncludes    :: NubListR FilePath,
  
  
  
  ghcOptLanguage      :: Flag Language,
  
  ghcOptExtensions    :: NubListR Extension,
  
  
  ghcOptExtensionMap    :: Map Extension (Maybe Compiler.Flag),
  
  
  
  ghcOptOptimisation  :: Flag GhcOptimisation,
    
  ghcOptDebugInfo     :: Flag DebugInfoLevel,
  
  ghcOptProfilingMode :: Flag Bool,
  
  ghcOptProfilingAuto :: Flag GhcProfAuto,
  
  ghcOptSplitSections :: Flag Bool,
  
  ghcOptSplitObjs     :: Flag Bool,
  
  ghcOptNumJobs       :: Flag (Maybe Int),
  
  ghcOptHPCDir        :: Flag FilePath,
  
  
  
  ghcOptGHCiScripts    :: NubListR FilePath,
  
  
  ghcOptHiSuffix      :: Flag String,
  ghcOptObjSuffix     :: Flag String,
  ghcOptDynHiSuffix   :: Flag String,   
  ghcOptDynObjSuffix  :: Flag String,   
  ghcOptHiDir         :: Flag FilePath,
  ghcOptObjDir        :: Flag FilePath,
  ghcOptOutputDir     :: Flag FilePath,
  ghcOptStubDir       :: Flag FilePath,
  
  
  ghcOptDynLinkMode   :: Flag GhcDynLinkMode,
  ghcOptStaticLib     :: Flag Bool,
  ghcOptShared        :: Flag Bool,
  ghcOptFPic          :: Flag Bool,
  ghcOptDylibName     :: Flag String,
  ghcOptRPaths        :: NubListR FilePath,
  
  
  
  ghcOptVerbosity     :: Flag Verbosity,
  
  
  ghcOptExtraPath     :: NubListR FilePath,
  
  
  ghcOptCabal         :: Flag Bool
} deriving (Show, Generic)
data GhcMode = GhcModeCompile     
             | GhcModeLink        
             | GhcModeMake        
             | GhcModeInteractive 
             | GhcModeAbiHash     
 deriving (Show, Eq)
data GhcOptimisation = GhcNoOptimisation             
                     | GhcNormalOptimisation         
                     | GhcMaximumOptimisation        
                     | GhcSpecialOptimisation String 
 deriving (Show, Eq)
data GhcDynLinkMode = GhcStaticOnly       
                    | GhcDynamicOnly      
                    | GhcStaticAndDynamic 
 deriving (Show, Eq)
data GhcProfAuto = GhcProfAutoAll       
                 | GhcProfAutoToplevel  
                 | GhcProfAutoExported  
 deriving (Show, Eq)
runGHC :: Verbosity -> ConfiguredProgram -> Compiler -> Platform  -> GhcOptions
       -> IO ()
runGHC verbosity ghcProg comp platform opts = do
  runProgramInvocation verbosity (ghcInvocation ghcProg comp platform opts)
ghcInvocation :: ConfiguredProgram -> Compiler -> Platform -> GhcOptions
              -> ProgramInvocation
ghcInvocation prog comp platform opts =
    (programInvocation prog (renderGhcOptions comp platform opts)) {
        progInvokePathEnv = fromNubListR (ghcOptExtraPath opts)
    }
renderGhcOptions :: Compiler -> Platform -> GhcOptions -> [String]
renderGhcOptions comp _platform@(Platform _arch os) opts
  | compilerFlavor comp `notElem` [GHC, GHCJS] =
    error $ "Distribution.Simple.Program.GHC.renderGhcOptions: "
    ++ "compiler flavor must be 'GHC' or 'GHCJS'!"
  | otherwise =
  concat
  [ case flagToMaybe (ghcOptMode opts) of
       Nothing                 -> []
       Just GhcModeCompile     -> ["-c"]
       Just GhcModeLink        -> []
       Just GhcModeMake        -> ["--make"]
       Just GhcModeInteractive -> ["--interactive"]
       Just GhcModeAbiHash     -> ["--abi-hash"]
  , flags ghcOptExtraDefault
  , [ "-no-link" | flagBool ghcOptNoLink ]
  
  
  , maybe [] verbosityOpts (flagToMaybe (ghcOptVerbosity opts))
  , [ "-fbuilding-cabal-package" | flagBool ghcOptCabal ]
  
  
  , case flagToMaybe (ghcOptOptimisation opts) of
      Nothing                         -> []
      Just GhcNoOptimisation          -> ["-O0"]
      Just GhcNormalOptimisation      -> ["-O"]
      Just GhcMaximumOptimisation     -> ["-O2"]
      Just (GhcSpecialOptimisation s) -> ["-O" ++ s] 
  , case flagToMaybe (ghcOptDebugInfo opts) of
      Nothing                                -> []
      Just NoDebugInfo                       -> []
      Just MinimalDebugInfo                  -> ["-g1"]
      Just NormalDebugInfo                   -> ["-g2"]
      Just MaximalDebugInfo                  -> ["-g3"]
  , [ "-prof" | flagBool ghcOptProfilingMode ]
  , case flagToMaybe (ghcOptProfilingAuto opts) of
      _ | not (flagBool ghcOptProfilingMode)
                                -> []
      Nothing                   -> []
      Just GhcProfAutoAll
        | flagProfAuto implInfo -> ["-fprof-auto"]
        | otherwise             -> ["-auto-all"] 
      Just GhcProfAutoToplevel
        | flagProfAuto implInfo -> ["-fprof-auto-top"]
        | otherwise             -> ["-auto-all"]
      Just GhcProfAutoExported
        | flagProfAuto implInfo -> ["-fprof-auto-exported"]
        | otherwise             -> ["-auto"]
  , [ "-split-sections" | flagBool ghcOptSplitSections ]
  , [ "-split-objs" | flagBool ghcOptSplitObjs ]
  , case flagToMaybe (ghcOptHPCDir opts) of
      Nothing -> []
      Just hpcdir -> ["-fhpc", "-hpcdir", hpcdir]
  , if parmakeSupported comp
    then case ghcOptNumJobs opts of
      NoFlag  -> []
      Flag n  -> ["-j" ++ maybe "" show n]
    else []
  
  
  , [ "-staticlib" | flagBool ghcOptStaticLib ]
  , [ "-shared"    | flagBool ghcOptShared    ]
  , case flagToMaybe (ghcOptDynLinkMode opts) of
      Nothing                  -> []
      Just GhcStaticOnly       -> ["-static"]
      Just GhcDynamicOnly      -> ["-dynamic"]
      Just GhcStaticAndDynamic -> ["-static", "-dynamic-too"]
  , [ "-fPIC"    | flagBool ghcOptFPic ]
  , concat [ ["-dylib-install-name", libname] | libname <- flag ghcOptDylibName ]
  
  
  , concat [ ["-osuf",    suf] | suf <- flag ghcOptObjSuffix ]
  , concat [ ["-hisuf",   suf] | suf <- flag ghcOptHiSuffix  ]
  , concat [ ["-dynosuf", suf] | suf <- flag ghcOptDynObjSuffix ]
  , concat [ ["-dynhisuf",suf] | suf <- flag ghcOptDynHiSuffix  ]
  , concat [ ["-outputdir", dir] | dir <- flag ghcOptOutputDir ]
  , concat [ ["-odir",    dir] | dir <- flag ghcOptObjDir ]
  , concat [ ["-hidir",   dir] | dir <- flag ghcOptHiDir  ]
  , concat [ ["-stubdir", dir] | dir <- flag ghcOptStubDir ]
  
  
  , [ "-i"        | flagBool ghcOptSourcePathClear ]
  , [ "-i" ++ dir | dir <- flags ghcOptSourcePath ]
  
  
  
  , [ "-I"    ++ dir | dir <- flags ghcOptCppIncludePath ]
  , [ "-optP" ++ opt | opt <- flags ghcOptCppOptions ]
  , concat [ [ "-optP-include", "-optP" ++ inc]
           | inc <- flags ghcOptCppIncludes ]
  , [ "-optc" ++ opt | opt <- flags ghcOptCcOptions ]
  , [ "-optc" ++ opt | opt <- flags ghcOptCxxOptions ]
  
  
  , [ "-optl" ++ opt | opt <- flags ghcOptLinkOptions ]
  , ["-l" ++ lib     | lib <- flags ghcOptLinkLibs ]
  , ["-L" ++ dir     | dir <- flags ghcOptLinkLibPath ]
  , if isOSX
    then concat [ ["-framework", fmwk]
                | fmwk <- flags ghcOptLinkFrameworks ]
    else []
  , if isOSX
    then concat [ ["-framework-path", path]
                | path <- flags ghcOptLinkFrameworkDirs ]
    else []
  , [ "-no-hs-main"  | flagBool ghcOptLinkNoHsMain ]
  , [ "-dynload deploy" | not (null (flags ghcOptRPaths)) ]
  , concat [ [ "-optl-Wl,-rpath," ++ dir]
           | dir <- flags ghcOptRPaths ]
  , [ modDefFile | modDefFile <- flags ghcOptLinkModDefFiles ]
  
  
  , concat [ [ case () of
                _ | unitIdSupported comp     -> "-this-unit-id"
                  | packageKeySupported comp -> "-this-package-key"
                  | otherwise                -> "-package-name"
             , this_arg ]
             | this_arg <- flag ghcOptThisUnitId ]
  , concat [ ["-this-component-id", display this_cid ]
           | this_cid <- flag ghcOptThisComponentId ]
  , if null (ghcOptInstantiatedWith opts)
        then []
        else "-instantiated-with"
             : intercalate "," (map (\(n,m) -> display n ++ "="
                                            ++ display m)
                                    (ghcOptInstantiatedWith opts))
             : []
  , concat [ ["-fno-code", "-fwrite-interface"] | flagBool ghcOptNoCode ]
  , [ "-hide-all-packages"     | flagBool ghcOptHideAllPackages ]
  , [ "-Wmissing-home-modules" | flagBool ghcOptWarnMissingHomeModules ]
  , [ "-no-auto-link-packages" | flagBool ghcOptNoAutoLinkPackages ]
  , packageDbArgs implInfo (ghcOptPackageDBs opts)
  , concat $ let space "" = ""
                 space xs = ' ' : xs
             in [ ["-package-id", display ipkgid ++ space (display rns)]
                | (ipkgid,rns) <- flags ghcOptPackages ]
  
  
  , if supportsHaskell2010 implInfo
    then [ "-X" ++ display lang | lang <- flag ghcOptLanguage ]
    else []
  , [ ext'
    | ext  <- flags ghcOptExtensions
    , ext' <- case Map.lookup ext (ghcOptExtensionMap opts) of
        Just (Just arg) -> [arg]
        Just Nothing    -> []
        Nothing         ->
            error $ "Distribution.Simple.Program.GHC.renderGhcOptions: "
                  ++ display ext ++ " not present in ghcOptExtensionMap."
    ]
  
  
  , concat [ [ "-ghci-script", script ] | script <- flags  ghcOptGHCiScripts
                                        , flagGhciScript implInfo ]
  
  
  , [ display modu | modu <- flags ghcOptInputModules ]
  , flags ghcOptInputFiles
  , concat [ [ "-o",    out] | out <- flag ghcOptOutputFile ]
  , concat [ [ "-dyno", out] | out <- flag ghcOptOutputDynFile ]
  
  
  , flags ghcOptExtra
  ]
  where
    implInfo     = getImplInfo comp
    isOSX        = os == OSX
    flag     flg = flagToList (flg opts)
    flags    flg = fromNubListR . flg $ opts
    flagBool flg = fromFlagOrDefault False (flg opts)
verbosityOpts :: Verbosity -> [String]
verbosityOpts verbosity
  | verbosity >= deafening = ["-v"]
  | verbosity >= normal    = []
  | otherwise              = ["-w", "-v0"]
packageDbArgsConf :: PackageDBStack -> [String]
packageDbArgsConf dbstack = case dbstack of
  (GlobalPackageDB:UserPackageDB:dbs) -> concatMap specific dbs
  (GlobalPackageDB:dbs)               -> ("-no-user-package-conf")
                                       : concatMap specific dbs
  _ -> ierror
  where
    specific (SpecificPackageDB db) = [ "-package-conf", db ]
    specific _                      = ierror
    ierror = error $ "internal error: unexpected package db stack: "
                  ++ show dbstack
packageDbArgsDb :: PackageDBStack -> [String]
packageDbArgsDb dbstack = case dbstack of
  (GlobalPackageDB:UserPackageDB:dbs)
    | all isSpecific dbs              -> concatMap single dbs
  (GlobalPackageDB:dbs)
    | all isSpecific dbs              -> "-no-user-package-db"
                                       : concatMap single dbs
  dbs                                 -> "-clear-package-db"
                                       : concatMap single dbs
 where
   single (SpecificPackageDB db) = [ "-package-db", db ]
   single GlobalPackageDB        = [ "-global-package-db" ]
   single UserPackageDB          = [ "-user-package-db" ]
   isSpecific (SpecificPackageDB _) = True
   isSpecific _                     = False
packageDbArgs :: GhcImplInfo -> PackageDBStack -> [String]
packageDbArgs implInfo
  | flagPackageConf implInfo = packageDbArgsConf
  | otherwise                = packageDbArgsDb
instance Monoid GhcOptions where
  mempty = gmempty
  mappend = (<>)
instance Semigroup GhcOptions where
  (<>) = gmappend