module GHC.Driver.Config.Finder (
    FinderOpts(..),
    initFinderOpts
  ) where

import GHC.Prelude

import GHC.Driver.Session
import GHC.Unit.Finder.Types
import GHC.Data.FastString


-- | Create a new 'FinderOpts' from DynFlags.
initFinderOpts :: DynFlags -> FinderOpts
initFinderOpts :: DynFlags -> FinderOpts
initFinderOpts DynFlags
flags = FinderOpts
  { finder_importPaths :: [FilePath]
finder_importPaths = DynFlags -> [FilePath]
importPaths DynFlags
flags
  , finder_lookupHomeInterfaces :: Bool
finder_lookupHomeInterfaces = GhcMode -> Bool
isOneShot (DynFlags -> GhcMode
ghcMode DynFlags
flags)
  , finder_bypassHiFileCheck :: Bool
finder_bypassHiFileCheck = GhcMode
MkDepend GhcMode -> GhcMode -> Bool
forall a. Eq a => a -> a -> Bool
== (DynFlags -> GhcMode
ghcMode DynFlags
flags)
  , finder_ways :: Ways
finder_ways = DynFlags -> Ways
ways DynFlags
flags
  , finder_enableSuggestions :: Bool
finder_enableSuggestions = GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_HelpfulErrors DynFlags
flags
  , finder_workingDirectory :: Maybe FilePath
finder_workingDirectory = DynFlags -> Maybe FilePath
workingDirectory DynFlags
flags
  , finder_thisPackageName :: Maybe FastString
finder_thisPackageName  = FilePath -> FastString
mkFastString (FilePath -> FastString) -> Maybe FilePath -> Maybe FastString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> DynFlags -> Maybe FilePath
thisPackageName DynFlags
flags
  , finder_hiddenModules :: Set ModuleName
finder_hiddenModules = DynFlags -> Set ModuleName
hiddenModules DynFlags
flags
  , finder_reexportedModules :: Set ModuleName
finder_reexportedModules = DynFlags -> Set ModuleName
reexportedModules DynFlags
flags
  , finder_hieDir :: Maybe FilePath
finder_hieDir = DynFlags -> Maybe FilePath
hieDir DynFlags
flags
  , finder_hieSuf :: FilePath
finder_hieSuf = DynFlags -> FilePath
hieSuf DynFlags
flags
  , finder_hiDir :: Maybe FilePath
finder_hiDir = DynFlags -> Maybe FilePath
hiDir DynFlags
flags
  , finder_hiSuf :: FilePath
finder_hiSuf = DynFlags -> FilePath
hiSuf_ DynFlags
flags
  , finder_dynHiSuf :: FilePath
finder_dynHiSuf = DynFlags -> FilePath
dynHiSuf_ DynFlags
flags
  , finder_objectDir :: Maybe FilePath
finder_objectDir = DynFlags -> Maybe FilePath
objectDir DynFlags
flags
  , finder_objectSuf :: FilePath
finder_objectSuf = DynFlags -> FilePath
objectSuf_ DynFlags
flags
  , finder_dynObjectSuf :: FilePath
finder_dynObjectSuf = DynFlags -> FilePath
dynObjectSuf_ DynFlags
flags
  , finder_stubDir :: Maybe FilePath
finder_stubDir = DynFlags -> Maybe FilePath
stubDir DynFlags
flags
  }