-- Copyright (c) 2020, Shayne Fletcher. All rights reserved.
-- SPDX-License-Identifier: BSD-3-Clause.

{-# OPTIONS_GHC -Wno-missing-fields #-}
{-# LANGUAGE CPP #-}
#include "ghclib_api.h"

module Language.Haskell.GhclibParserEx.GHC.Settings.Config(
    fakeSettings
  , fakeLlvmConfig
  )
where

#if defined (GHCLIB_API_HEAD) || defined(GHCLIB_API_902) || defined (GHCLIB_API_900)
import GHC.Settings.Config
import GHC.Driver.Session
import GHC.Utils.Fingerprint
import GHC.Platform
import GHC.Settings
#elif defined (GHCLIB_API_810)
import Config
import DynFlags
import Fingerprint
import GHC.Platform
import ToolSettings
#else
import Config
import DynFlags
import Fingerprint
import Platform
#endif

fakeSettings :: Settings
fakeSettings :: Settings
fakeSettings = Settings :: GhcNameVersion
-> FileSettings
-> Platform
-> ToolSettings
-> PlatformMisc
-> PlatformConstants
-> [(String, String)]
-> Settings
Settings
#if defined (GHCLIB_API_HEAD) || defined(GHCLIB_API_902) || defined (GHCLIB_API_900)|| defined (GHCLIB_API_810)
  { sGhcNameVersion :: GhcNameVersion
sGhcNameVersion=GhcNameVersion
ghcNameVersion
  , sFileSettings :: FileSettings
sFileSettings=FileSettings
fileSettings
  , sTargetPlatform :: Platform
sTargetPlatform=Platform
platform
  , sPlatformMisc :: PlatformMisc
sPlatformMisc=PlatformMisc
platformMisc
#  if !defined(GHCLIB_API_HEAD)
  , sPlatformConstants :: PlatformConstants
sPlatformConstants=PlatformConstants
platformConstants
#  endif
  , sToolSettings :: ToolSettings
sToolSettings=ToolSettings
toolSettings
  }
#else
  { sTargetPlatform=platform
  , sPlatformConstants=platformConstants
  , sProjectVersion=cProjectVersion
  , sProgramName="ghc"
  , sOpt_P_fingerprint=fingerprint0
  }
#endif
  where
#if defined (GHCLIB_API_HEAD) || defined(GHCLIB_API_902) || defined (GHCLIB_API_900)|| defined (GHCLIB_API_810)
    toolSettings :: ToolSettings
toolSettings = ToolSettings :: Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> String
-> (String, [Option])
-> String
-> String
-> (String, [Option])
-> (String, [Option])
-> (String, [Option])
-> (String, [Option])
-> String
-> String
-> String
-> String
-> String
-> (String, [Option])
-> (String, [Option])
-> (String, [Option])
-> String
-> [String]
-> [String]
-> Fingerprint
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> ToolSettings
ToolSettings {
      toolSettings_opt_P_fingerprint :: Fingerprint
toolSettings_opt_P_fingerprint=Fingerprint
fingerprint0
      }
    fileSettings :: FileSettings
fileSettings = FileSettings :: String
-> String
-> Maybe String
-> String
-> String
-> String
-> FileSettings
FileSettings {}
    platformMisc :: PlatformMisc
platformMisc = PlatformMisc :: String
-> String
-> IntegerLibrary
-> Bool
-> Bool
-> Bool
-> String
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> String
-> PlatformMisc
PlatformMisc {}
    ghcNameVersion :: GhcNameVersion
ghcNameVersion =
      GhcNameVersion :: String -> String -> GhcNameVersion
GhcNameVersion{ghcNameVersion_programName :: String
ghcNameVersion_programName=String
"ghc"
                    ,ghcNameVersion_projectVersion :: String
ghcNameVersion_projectVersion=String
cProjectVersion
                    }
#endif
    platform :: Platform
platform =
      Platform :: PlatformMini
-> PlatformWordSize
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Platform
Platform{
#if defined (GHCLIB_API_HEAD) || defined(GHCLIB_API_902) || defined (GHCLIB_API_900)
    -- It doesn't matter what values we write here as these fields are
    -- not referenced for our purposes. However the fields are strict
    -- so we must say something.
        platformByteOrder=LittleEndian
      , platformHasGnuNonexecStack=True
      , platformHasIdentDirective=False
      , platformHasSubsectionsViaSymbols=False
      , platformIsCrossCompiling=False
      , platformLeadingUnderscore=False
      , platformTablesNextToCode=False
#if defined (GHCLIB_API_HEAD)
      , platform_constants = Nothing
#endif
#if !defined(GHCLIB_API_HEAD) && !defined (GHCLIB_API_900)
      , platformConstants=platformConstants
#endif
      ,
#endif
#if defined (GHCLIB_API_HEAD) || defined(GHCLIB_API_902)
        platformWordSize=PW8
      , platformArchOS=ArchOS {archOS_arch=ArchUnknown, archOS_OS=OSUnknown}
#elif defined (GHCLIB_API_810) || defined (GHCLIB_API_900)
        platformWordSize :: PlatformWordSize
platformWordSize=PlatformWordSize
PW8
      , platformMini :: PlatformMini
platformMini=PlatformMini :: Arch -> OS -> PlatformMini
PlatformMini {platformMini_arch :: Arch
platformMini_arch=Arch
ArchUnknown, platformMini_os :: OS
platformMini_os=OS
OSUnknown}
#else
        platformWordSize=8
      , platformOS=OSUnknown
#endif
      , platformUnregisterised :: Bool
platformUnregisterised=Bool
True
      }
#if !defined(GHCLIB_API_HEAD)
    platformConstants :: PlatformConstants
platformConstants =
      PlatformConstants :: Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Bool
-> Bool
-> Int
-> Integer
-> Integer
-> Integer
-> PlatformConstants
PlatformConstants{pc_DYNAMIC_BY_DEFAULT :: Bool
pc_DYNAMIC_BY_DEFAULT=Bool
False,pc_WORD_SIZE :: Int
pc_WORD_SIZE=Int
8}
#endif

#if defined (GHCLIB_API_HEAD) || defined(GHCLIB_API_902) || defined (GHCLIB_API_900)|| defined (GHCLIB_API_810)
fakeLlvmConfig :: LlvmConfig
fakeLlvmConfig :: LlvmConfig
fakeLlvmConfig = [(String, LlvmTarget)] -> [(Int, String)] -> LlvmConfig
LlvmConfig [] []
#else
fakeLlvmConfig :: (LlvmTargets, LlvmPasses)
fakeLlvmConfig = ([], [])
#endif