never executed always true always false
    1 module GHC.Unit.Finder.Types
    2    ( FinderCache (..)
    3    , FinderCacheState
    4    , FindResult (..)
    5    , InstalledFindResult (..)
    6    , FinderOpts(..)
    7    )
    8 where
    9 
   10 import GHC.Prelude
   11 import GHC.Unit
   12 import qualified Data.Map as M
   13 import GHC.Fingerprint
   14 import GHC.Platform.Ways
   15 
   16 import Data.IORef
   17 
   18 -- | The 'FinderCache' maps modules to the result of
   19 -- searching for that module. It records the results of searching for
   20 -- modules along the search path. On @:load@, we flush the entire
   21 -- contents of this cache.
   22 --
   23 type FinderCacheState = InstalledModuleEnv InstalledFindResult
   24 type FileCacheState   = M.Map FilePath Fingerprint
   25 data FinderCache = FinderCache { fcModuleCache :: (IORef FinderCacheState)
   26                                , fcFileCache   :: (IORef FileCacheState)
   27                                }
   28 
   29 data InstalledFindResult
   30   = InstalledFound ModLocation InstalledModule
   31   | InstalledNoPackage UnitId
   32   | InstalledNotFound [FilePath] (Maybe UnitId)
   33 
   34 -- | The result of searching for an imported module.
   35 --
   36 -- NB: FindResult manages both user source-import lookups
   37 -- (which can result in 'Module') as well as direct imports
   38 -- for interfaces (which always result in 'InstalledModule').
   39 data FindResult
   40   = Found ModLocation Module
   41         -- ^ The module was found
   42   | NoPackage Unit
   43         -- ^ The requested unit was not found
   44   | FoundMultiple [(Module, ModuleOrigin)]
   45         -- ^ _Error_: both in multiple packages
   46 
   47         -- | Not found
   48   | NotFound
   49       { fr_paths       :: [FilePath]       -- ^ Places where I looked
   50 
   51       , fr_pkg         :: Maybe Unit       -- ^ Just p => module is in this unit's
   52                                            --   manifest, but couldn't find the
   53                                            --   .hi file
   54 
   55       , fr_mods_hidden :: [Unit]           -- ^ Module is in these units,
   56                                            --   but the *module* is hidden
   57 
   58       , fr_pkgs_hidden :: [Unit]           -- ^ Module is in these units,
   59                                            --   but the *unit* is hidden
   60 
   61         -- | Module is in these units, but it is unusable
   62       , fr_unusables   :: [(Unit, UnusableUnitReason)]
   63 
   64       , fr_suggestions :: [ModuleSuggestion] -- ^ Possible mis-spelled modules
   65       }
   66 
   67 -- | Locations and information the finder cares about.
   68 --
   69 -- Should be taken from 'DynFlags' via 'initFinderOpts'.
   70 data FinderOpts = FinderOpts
   71   { finder_importPaths :: [FilePath]
   72       -- ^ Where are we allowed to look for Modules and Source files
   73   , finder_lookupHomeInterfaces :: Bool
   74       -- ^ When looking up a home module:
   75       --
   76       --    * 'True':  search interface files (e.g. in '-c' mode)
   77       --    * 'False': search source files (e.g. in '--make' mode)
   78 
   79   , finder_bypassHiFileCheck :: Bool
   80       -- ^ Don't check that an imported interface file actually exists
   81       -- if it can only be at one location. The interface will be reported
   82       -- as `InstalledFound` even if the file doesn't exist, so this is
   83       -- only useful in specific cases (e.g. to generate dependencies
   84       -- with `ghc -M`)
   85   , finder_ways :: Ways
   86   , finder_enableSuggestions :: Bool
   87       -- ^ If we encounter unknown modules, should we suggest modules
   88       -- that have a similar name.
   89   , finder_hieDir :: Maybe FilePath
   90   , finder_hieSuf :: String
   91   , finder_hiDir :: Maybe FilePath
   92   , finder_hiSuf :: String
   93   , finder_dynHiSuf :: String
   94   , finder_objectDir :: Maybe FilePath
   95   , finder_objectSuf :: String
   96   , finder_dynObjectSuf :: String
   97   , finder_stubDir :: Maybe FilePath
   98   }