module GHC.Unit.Finder.Types
( FinderCache (..)
, FinderCacheState
, FindResult (..)
, InstalledFindResult (..)
, FinderOpts(..)
)
where
import GHC.Prelude
import GHC.Unit
import qualified Data.Map as M
import GHC.Fingerprint
import GHC.Platform.Ways
import Data.IORef
import GHC.Data.FastString
import qualified Data.Set as Set
type FinderCacheState = InstalledModuleEnv InstalledFindResult
type FileCacheState = M.Map FilePath Fingerprint
data FinderCache = FinderCache { FinderCache -> IORef FinderCacheState
fcModuleCache :: (IORef FinderCacheState)
, FinderCache -> IORef FileCacheState
fcFileCache :: (IORef FileCacheState)
}
data InstalledFindResult
= InstalledFound ModLocation InstalledModule
| InstalledNoPackage UnitId
| InstalledNotFound [FilePath] (Maybe UnitId)
data FindResult
= Found ModLocation Module
| NoPackage Unit
| FoundMultiple [(Module, ModuleOrigin)]
| NotFound
{ FindResult -> [FilePath]
fr_paths :: [FilePath]
, FindResult -> Maybe Unit
fr_pkg :: Maybe Unit
, FindResult -> [Unit]
fr_mods_hidden :: [Unit]
, FindResult -> [Unit]
fr_pkgs_hidden :: [Unit]
, FindResult -> [(Unit, UnusableUnitReason)]
fr_unusables :: [(Unit, UnusableUnitReason)]
, FindResult -> [ModuleSuggestion]
fr_suggestions :: [ModuleSuggestion]
}
data FinderOpts = FinderOpts
{ FinderOpts -> [FilePath]
finder_importPaths :: [FilePath]
, FinderOpts -> Bool
finder_lookupHomeInterfaces :: Bool
, FinderOpts -> Bool
finder_bypassHiFileCheck :: Bool
, FinderOpts -> Ways
finder_ways :: Ways
, FinderOpts -> Bool
finder_enableSuggestions :: Bool
, FinderOpts -> Maybe FilePath
finder_workingDirectory :: Maybe FilePath
, FinderOpts -> Maybe FastString
finder_thisPackageName :: Maybe FastString
, FinderOpts -> Set ModuleName
finder_hiddenModules :: Set.Set ModuleName
, FinderOpts -> Set ModuleName
finder_reexportedModules :: Set.Set ModuleName
, FinderOpts -> Maybe FilePath
finder_hieDir :: Maybe FilePath
, FinderOpts -> FilePath
finder_hieSuf :: String
, FinderOpts -> Maybe FilePath
finder_hiDir :: Maybe FilePath
, FinderOpts -> FilePath
finder_hiSuf :: String
, FinderOpts -> FilePath
finder_dynHiSuf :: String
, FinderOpts -> Maybe FilePath
finder_objectDir :: Maybe FilePath
, FinderOpts -> FilePath
finder_objectSuf :: String
, FinderOpts -> FilePath
finder_dynObjectSuf :: String
, FinderOpts -> Maybe FilePath
finder_stubDir :: Maybe FilePath
} deriving Int -> FinderOpts -> ShowS
[FinderOpts] -> ShowS
FinderOpts -> FilePath
(Int -> FinderOpts -> ShowS)
-> (FinderOpts -> FilePath)
-> ([FinderOpts] -> ShowS)
-> Show FinderOpts
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FinderOpts -> ShowS
showsPrec :: Int -> FinderOpts -> ShowS
$cshow :: FinderOpts -> FilePath
show :: FinderOpts -> FilePath
$cshowList :: [FinderOpts] -> ShowS
showList :: [FinderOpts] -> ShowS
Show