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

-- | The 'FinderCache' maps modules to the result of
-- searching for that module. It records the results of searching for
-- modules along the search path. On @:load@, we flush the entire
-- contents of this cache.
--
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)

-- | The result of searching for an imported module.
--
-- NB: FindResult manages both user source-import lookups
-- (which can result in 'Module') as well as direct imports
-- for interfaces (which always result in 'InstalledModule').
data FindResult
  = Found ModLocation Module
        -- ^ The module was found
  | NoPackage Unit
        -- ^ The requested unit was not found
  | FoundMultiple [(Module, ModuleOrigin)]
        -- ^ _Error_: both in multiple packages

        -- | Not found
  | NotFound
      { FindResult -> [FilePath]
fr_paths       :: [FilePath]       -- ^ Places where I looked

      , FindResult -> Maybe Unit
fr_pkg         :: Maybe Unit       -- ^ Just p => module is in this unit's
                                           --   manifest, but couldn't find the
                                           --   .hi file

      , FindResult -> [Unit]
fr_mods_hidden :: [Unit]           -- ^ Module is in these units,
                                           --   but the *module* is hidden

      , FindResult -> [Unit]
fr_pkgs_hidden :: [Unit]           -- ^ Module is in these units,
                                           --   but the *unit* is hidden

        -- | Module is in these units, but it is unusable
      , FindResult -> [(Unit, UnusableUnitReason)]
fr_unusables   :: [(Unit, UnusableUnitReason)]

      , FindResult -> [ModuleSuggestion]
fr_suggestions :: [ModuleSuggestion] -- ^ Possible mis-spelled modules
      }

-- | Locations and information the finder cares about.
--
-- Should be taken from 'DynFlags' via 'initFinderOpts'.
data FinderOpts = FinderOpts
  { FinderOpts -> [FilePath]
finder_importPaths :: [FilePath]
      -- ^ Where are we allowed to look for Modules and Source files
  , FinderOpts -> Bool
finder_lookupHomeInterfaces :: Bool
      -- ^ When looking up a home module:
      --
      --    * 'True':  search interface files (e.g. in '-c' mode)
      --    * 'False': search source files (e.g. in '--make' mode)

  , FinderOpts -> Bool
finder_bypassHiFileCheck :: Bool
      -- ^ Don't check that an imported interface file actually exists
      -- if it can only be at one location. The interface will be reported
      -- as `InstalledFound` even if the file doesn't exist, so this is
      -- only useful in specific cases (e.g. to generate dependencies
      -- with `ghc -M`)
  , FinderOpts -> Ways
finder_ways :: Ways
  , FinderOpts -> Bool
finder_enableSuggestions :: Bool
      -- ^ If we encounter unknown modules, should we suggest modules
      -- that have a similar name.
  , 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