{-# LANGUAGE FlexibleContexts #-}
module GHC.Iface.Errors
( badIfaceFile
, hiModuleNameMismatchWarn
, homeModError
, cannotFindInterface
, cantFindInstalledErr
, cannotFindModule
, cantFindErr
, mayShowLocations
) where
import GHC.Platform.Profile
import GHC.Platform.Ways
import GHC.Utils.Panic.Plain
import GHC.Driver.Session
import GHC.Driver.Env
import GHC.Driver.Errors.Types
import GHC.Data.Maybe
import GHC.Prelude
import GHC.Unit
import GHC.Unit.Env
import GHC.Unit.Finder.Types
import GHC.Utils.Outputable as Outputable
badIfaceFile :: String -> SDoc -> SDoc
badIfaceFile :: String -> SDoc -> SDoc
badIfaceFile String
file SDoc
err
= [SDoc] -> SDoc
forall doc. IsDoc doc => [doc] -> doc
vcat [String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"Bad interface file:" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> String -> SDoc
forall doc. IsLine doc => String -> doc
text String
file,
Int -> SDoc -> SDoc
nest Int
4 SDoc
err]
hiModuleNameMismatchWarn :: Module -> Module -> SDoc
hiModuleNameMismatchWarn :: GenModule Unit -> GenModule Unit -> SDoc
hiModuleNameMismatchWarn GenModule Unit
requested_mod GenModule Unit
read_mod
| GenModule Unit -> Unit
forall unit. GenModule unit -> unit
moduleUnit GenModule Unit
requested_mod Unit -> Unit -> Bool
forall a. Eq a => a -> a -> Bool
== GenModule Unit -> Unit
forall unit. GenModule unit -> unit
moduleUnit GenModule Unit
read_mod =
[SDoc] -> SDoc
forall doc. IsLine doc => [doc] -> doc
sep [String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"Interface file contains module" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> SDoc -> SDoc
quotes (GenModule Unit -> SDoc
forall a. Outputable a => a -> SDoc
ppr GenModule Unit
read_mod) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> SDoc
forall doc. IsLine doc => doc
comma,
String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"but we were expecting module" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> SDoc -> SDoc
quotes (GenModule Unit -> SDoc
forall a. Outputable a => a -> SDoc
ppr GenModule Unit
requested_mod),
[SDoc] -> SDoc
forall doc. IsLine doc => [doc] -> doc
sep [String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"Probable cause: the source code which generated interface file",
String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"has an incompatible module name"
]
]
| Bool
otherwise =
PprStyle -> SDoc -> SDoc
withPprStyle (NamePprCtx -> Depth -> PprStyle
mkUserStyle NamePprCtx
alwaysQualify Depth
AllTheWay) (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$
[SDoc] -> SDoc
forall doc. IsLine doc => [doc] -> doc
hsep [ String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"Something is amiss; requested module "
, GenModule Unit -> SDoc
forall a. Outputable a => a -> SDoc
ppr GenModule Unit
requested_mod
, String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"differs from name found in the interface file"
, GenModule Unit -> SDoc
forall a. Outputable a => a -> SDoc
ppr GenModule Unit
read_mod
, SDoc -> SDoc
forall doc. IsLine doc => doc -> doc
parens (String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"if these names look the same, try again with -dppr-debug")
]
homeModError :: InstalledModule -> ModLocation -> SDoc
homeModError :: InstalledModule -> ModLocation -> SDoc
homeModError InstalledModule
mod ModLocation
location
= String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"attempting to use module " SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> SDoc -> SDoc
quotes (InstalledModule -> SDoc
forall a. Outputable a => a -> SDoc
ppr InstalledModule
mod)
SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> (case ModLocation -> Maybe String
ml_hs_file ModLocation
location of
Just String
file -> SDoc
forall doc. IsLine doc => doc
space SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc
parens (String -> SDoc
forall doc. IsLine doc => String -> doc
text String
file)
Maybe String
Nothing -> SDoc
forall doc. IsOutput doc => doc
Outputable.empty)
SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"which is not loaded"
cannotFindInterface :: UnitState -> Maybe HomeUnit -> Profile -> ([FilePath] -> SDoc) -> ModuleName -> InstalledFindResult -> SDoc
cannotFindInterface :: UnitState
-> Maybe HomeUnit
-> Profile
-> ([String] -> SDoc)
-> ModuleName
-> InstalledFindResult
-> SDoc
cannotFindInterface = SDoc
-> SDoc
-> UnitState
-> Maybe HomeUnit
-> Profile
-> ([String] -> SDoc)
-> ModuleName
-> InstalledFindResult
-> SDoc
cantFindInstalledErr (String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"Failed to load interface for")
(String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"Ambiguous interface for")
cantFindInstalledErr
:: SDoc
-> SDoc
-> UnitState
-> Maybe HomeUnit
-> Profile
-> ([FilePath] -> SDoc)
-> ModuleName
-> InstalledFindResult
-> SDoc
cantFindInstalledErr :: SDoc
-> SDoc
-> UnitState
-> Maybe HomeUnit
-> Profile
-> ([String] -> SDoc)
-> ModuleName
-> InstalledFindResult
-> SDoc
cantFindInstalledErr SDoc
cannot_find SDoc
_ UnitState
unit_state Maybe HomeUnit
mhome_unit Profile
profile [String] -> SDoc
tried_these ModuleName
mod_name InstalledFindResult
find_result
= SDoc
cannot_find SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> SDoc -> SDoc
quotes (ModuleName -> SDoc
forall a. Outputable a => a -> SDoc
ppr ModuleName
mod_name)
SDoc -> SDoc -> SDoc
forall doc. IsDoc doc => doc -> doc -> doc
$$ SDoc
more_info
where
build_tag :: String
build_tag = Ways -> String
waysBuildTag (Profile -> Ways
profileWays Profile
profile)
more_info :: SDoc
more_info
= case InstalledFindResult
find_result of
InstalledNoPackage UnitId
pkg
-> String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"no unit id matching" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> SDoc -> SDoc
quotes (UnitId -> SDoc
forall a. Outputable a => a -> SDoc
ppr UnitId
pkg) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+>
String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"was found" SDoc -> SDoc -> SDoc
forall doc. IsDoc doc => doc -> doc -> doc
$$ UnitId -> SDoc
looks_like_srcpkgid UnitId
pkg
InstalledNotFound [String]
files Maybe UnitId
mb_pkg
| Just UnitId
pkg <- Maybe UnitId
mb_pkg
, Maybe HomeUnit -> UnitId -> Bool
forall u. Maybe (GenHomeUnit u) -> UnitId -> Bool
notHomeUnitId Maybe HomeUnit
mhome_unit UnitId
pkg
-> UnitId -> [String] -> SDoc
not_found_in_package UnitId
pkg [String]
files
| [String] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [String]
files
-> String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"It is not a module in the current program, or in any known package."
| Bool
otherwise
-> [String] -> SDoc
tried_these [String]
files
InstalledFindResult
_ -> String -> SDoc
forall a. HasCallStack => String -> a
panic String
"cantFindInstalledErr"
looks_like_srcpkgid :: UnitId -> SDoc
looks_like_srcpkgid :: UnitId -> SDoc
looks_like_srcpkgid UnitId
pk
| (UnitInfo
pkg:[UnitInfo]
pkgs) <- UnitState -> PackageId -> [UnitInfo]
searchPackageId UnitState
unit_state (FastString -> PackageId
PackageId (UnitId -> FastString
unitIdFS UnitId
pk))
= SDoc -> SDoc
forall doc. IsLine doc => doc -> doc
parens (String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"This unit ID looks like the source package ID;" SDoc -> SDoc -> SDoc
forall doc. IsDoc doc => doc -> doc -> doc
$$
String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"the real unit ID is" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> SDoc -> SDoc
quotes (FastString -> SDoc
forall doc. IsLine doc => FastString -> doc
ftext (UnitId -> FastString
unitIdFS (UnitInfo -> UnitId
forall srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo srcpkgid srcpkgname uid modulename mod -> uid
unitId UnitInfo
pkg))) SDoc -> SDoc -> SDoc
forall doc. IsDoc doc => doc -> doc -> doc
$$
(if [UnitInfo] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [UnitInfo]
pkgs then SDoc
forall doc. IsOutput doc => doc
Outputable.empty
else String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"and" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Int -> SDoc
forall doc. IsLine doc => Int -> doc
int ([UnitInfo] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [UnitInfo]
pkgs) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"other candidates"))
| Bool
otherwise = SDoc
forall doc. IsOutput doc => doc
Outputable.empty
not_found_in_package :: UnitId -> [String] -> SDoc
not_found_in_package UnitId
pkg [String]
files
| String
build_tag String -> String -> Bool
forall a. Eq a => a -> a -> Bool
/= String
""
= let
build :: String
build = if String
build_tag String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"p" then String
"profiling"
else String
"\"" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
build_tag String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"\""
in
String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"Perhaps you haven't installed the " SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> String -> SDoc
forall doc. IsLine doc => String -> doc
text String
build SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<>
String -> SDoc
forall doc. IsLine doc => String -> doc
text String
" libraries for package " SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> SDoc -> SDoc
quotes (UnitId -> SDoc
forall a. Outputable a => a -> SDoc
ppr UnitId
pkg) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> Char -> SDoc
forall doc. IsLine doc => Char -> doc
char Char
'?' SDoc -> SDoc -> SDoc
forall doc. IsDoc doc => doc -> doc -> doc
$$
[String] -> SDoc
tried_these [String]
files
| Bool
otherwise
= String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"There are files missing in the " SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> SDoc -> SDoc
quotes (UnitId -> SDoc
forall a. Outputable a => a -> SDoc
ppr UnitId
pkg) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<>
String -> SDoc
forall doc. IsLine doc => String -> doc
text String
" package," SDoc -> SDoc -> SDoc
forall doc. IsDoc doc => doc -> doc -> doc
$$
String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"try running 'ghc-pkg check'." SDoc -> SDoc -> SDoc
forall doc. IsDoc doc => doc -> doc -> doc
$$
[String] -> SDoc
tried_these [String]
files
mayShowLocations :: DynFlags -> [FilePath] -> SDoc
mayShowLocations :: DynFlags -> [String] -> SDoc
mayShowLocations DynFlags
dflags [String]
files
| [String] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [String]
files = SDoc
forall doc. IsOutput doc => doc
Outputable.empty
| DynFlags -> Int
verbosity DynFlags
dflags Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
3 =
String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"Use -v (or `:set -v` in ghci) " SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<>
String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"to see a list of the files searched for."
| Bool
otherwise =
SDoc -> Int -> SDoc -> SDoc
hang (String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"Locations searched:") Int
2 (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$ [SDoc] -> SDoc
forall doc. IsDoc doc => [doc] -> doc
vcat ((String -> SDoc) -> [String] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map String -> SDoc
forall doc. IsLine doc => String -> doc
text [String]
files)
cannotFindModule :: HscEnv -> ModuleName -> FindResult -> SDoc
cannotFindModule :: HscEnv -> ModuleName -> FindResult -> SDoc
cannotFindModule HscEnv
hsc_env = DynFlags -> UnitEnv -> Profile -> ModuleName -> FindResult -> SDoc
cannotFindModule'
(HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env)
(HscEnv -> UnitEnv
hsc_unit_env HscEnv
hsc_env)
(DynFlags -> Profile
targetProfile (HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env))
cannotFindModule' :: DynFlags -> UnitEnv -> Profile -> ModuleName -> FindResult -> SDoc
cannotFindModule' :: DynFlags -> UnitEnv -> Profile -> ModuleName -> FindResult -> SDoc
cannotFindModule' DynFlags
dflags UnitEnv
unit_env Profile
profile ModuleName
mod FindResult
res = UnitState -> SDoc -> SDoc
pprWithUnitState ((() :: Constraint) => UnitEnv -> UnitState
UnitEnv -> UnitState
ue_units UnitEnv
unit_env) (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$
BuildingCabalPackage
-> SDoc
-> SDoc
-> UnitEnv
-> Profile
-> ([String] -> SDoc)
-> ModuleName
-> FindResult
-> SDoc
cantFindErr (DynFlags -> BuildingCabalPackage
checkBuildingCabalPackage DynFlags
dflags)
SDoc
cannotFindMsg
(String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"Ambiguous module name")
UnitEnv
unit_env
Profile
profile
(DynFlags -> [String] -> SDoc
mayShowLocations DynFlags
dflags)
ModuleName
mod
FindResult
res
where
cannotFindMsg :: SDoc
cannotFindMsg =
case FindResult
res of
NotFound { fr_mods_hidden :: FindResult -> [Unit]
fr_mods_hidden = [Unit]
hidden_mods
, fr_pkgs_hidden :: FindResult -> [Unit]
fr_pkgs_hidden = [Unit]
hidden_pkgs
, fr_unusables :: FindResult -> [(Unit, UnusableUnitReason)]
fr_unusables = [(Unit, UnusableUnitReason)]
unusables }
| Bool -> Bool
not ([Unit] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Unit]
hidden_mods Bool -> Bool -> Bool
&& [Unit] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Unit]
hidden_pkgs Bool -> Bool -> Bool
&& [(Unit, UnusableUnitReason)] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [(Unit, UnusableUnitReason)]
unusables)
-> String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"Could not load module"
FindResult
_ -> String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"Could not find module"
cantFindErr
:: BuildingCabalPackage
-> SDoc
-> SDoc
-> UnitEnv
-> Profile
-> ([FilePath] -> SDoc)
-> ModuleName
-> FindResult
-> SDoc
cantFindErr :: BuildingCabalPackage
-> SDoc
-> SDoc
-> UnitEnv
-> Profile
-> ([String] -> SDoc)
-> ModuleName
-> FindResult
-> SDoc
cantFindErr BuildingCabalPackage
_ SDoc
_ SDoc
multiple_found UnitEnv
_ Profile
_ [String] -> SDoc
_ ModuleName
mod_name (FoundMultiple [(GenModule Unit, ModuleOrigin)]
mods)
| Just [Unit]
pkgs <- Maybe [Unit]
unambiguousPackages
= SDoc -> Int -> SDoc -> SDoc
hang (SDoc
multiple_found SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> SDoc -> SDoc
quotes (ModuleName -> SDoc
forall a. Outputable a => a -> SDoc
ppr ModuleName
mod_name) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> SDoc
forall doc. IsLine doc => doc
colon) Int
2 (
[SDoc] -> SDoc
forall doc. IsLine doc => [doc] -> doc
sep [String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"it was found in multiple packages:",
[SDoc] -> SDoc
forall doc. IsLine doc => [doc] -> doc
hsep ((Unit -> SDoc) -> [Unit] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map Unit -> SDoc
forall a. Outputable a => a -> SDoc
ppr [Unit]
pkgs) ]
)
| Bool
otherwise
= SDoc -> Int -> SDoc -> SDoc
hang (SDoc
multiple_found SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> SDoc -> SDoc
quotes (ModuleName -> SDoc
forall a. Outputable a => a -> SDoc
ppr ModuleName
mod_name) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> SDoc
forall doc. IsLine doc => doc
colon) Int
2 (
[SDoc] -> SDoc
forall doc. IsDoc doc => [doc] -> doc
vcat (((GenModule Unit, ModuleOrigin) -> SDoc)
-> [(GenModule Unit, ModuleOrigin)] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map (GenModule Unit, ModuleOrigin) -> SDoc
forall {a}.
(Outputable a, Outputable (GenModule a)) =>
(GenModule a, ModuleOrigin) -> SDoc
pprMod [(GenModule Unit, ModuleOrigin)]
mods)
)
where
unambiguousPackages :: Maybe [Unit]
unambiguousPackages = (Maybe [Unit] -> (GenModule Unit, ModuleOrigin) -> Maybe [Unit])
-> Maybe [Unit] -> [(GenModule Unit, ModuleOrigin)] -> Maybe [Unit]
forall b a. (b -> a -> b) -> b -> [a] -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' Maybe [Unit] -> (GenModule Unit, ModuleOrigin) -> Maybe [Unit]
forall {a}. Maybe [a] -> (GenModule a, ModuleOrigin) -> Maybe [a]
unambiguousPackage ([Unit] -> Maybe [Unit]
forall a. a -> Maybe a
Just []) [(GenModule Unit, ModuleOrigin)]
mods
unambiguousPackage :: Maybe [a] -> (GenModule a, ModuleOrigin) -> Maybe [a]
unambiguousPackage (Just [a]
xs) (GenModule a
m, ModOrigin (Just Bool
_) [UnitInfo]
_ [UnitInfo]
_ Bool
_)
= [a] -> Maybe [a]
forall a. a -> Maybe a
Just (GenModule a -> a
forall unit. GenModule unit -> unit
moduleUnit GenModule a
m a -> [a] -> [a]
forall a. a -> [a] -> [a]
: [a]
xs)
unambiguousPackage Maybe [a]
_ (GenModule a, ModuleOrigin)
_ = Maybe [a]
forall a. Maybe a
Nothing
pprMod :: (GenModule a, ModuleOrigin) -> SDoc
pprMod (GenModule a
m, ModuleOrigin
o) = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"it is bound as" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> GenModule a -> SDoc
forall a. Outputable a => a -> SDoc
ppr GenModule a
m SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+>
String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"by" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> GenModule a -> ModuleOrigin -> SDoc
forall {a}. Outputable a => GenModule a -> ModuleOrigin -> SDoc
pprOrigin GenModule a
m ModuleOrigin
o
pprOrigin :: GenModule a -> ModuleOrigin -> SDoc
pprOrigin GenModule a
_ ModuleOrigin
ModHidden = String -> SDoc
forall a. HasCallStack => String -> a
panic String
"cantFindErr: bound by mod hidden"
pprOrigin GenModule a
_ (ModUnusable UnusableUnitReason
_) = String -> SDoc
forall a. HasCallStack => String -> a
panic String
"cantFindErr: bound by mod unusable"
pprOrigin GenModule a
m (ModOrigin Maybe Bool
e [UnitInfo]
res [UnitInfo]
_ Bool
f) = [SDoc] -> SDoc
forall doc. IsLine doc => [doc] -> doc
sep ([SDoc] -> SDoc) -> [SDoc] -> SDoc
forall a b. (a -> b) -> a -> b
$ SDoc -> [SDoc] -> [SDoc]
forall doc. IsLine doc => doc -> [doc] -> [doc]
punctuate SDoc
forall doc. IsLine doc => doc
comma (
if Maybe Bool
e Maybe Bool -> Maybe Bool -> Bool
forall a. Eq a => a -> a -> Bool
== Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
True
then [String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"package" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> a -> SDoc
forall a. Outputable a => a -> SDoc
ppr (GenModule a -> a
forall unit. GenModule unit -> unit
moduleUnit GenModule a
m)]
else [] [SDoc] -> [SDoc] -> [SDoc]
forall a. [a] -> [a] -> [a]
++
(UnitInfo -> SDoc) -> [UnitInfo] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map ((String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"a reexport in package" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+>)
(SDoc -> SDoc) -> (UnitInfo -> SDoc) -> UnitInfo -> SDoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
.Unit -> SDoc
forall a. Outputable a => a -> SDoc
ppr(Unit -> SDoc) -> (UnitInfo -> Unit) -> UnitInfo -> SDoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
.UnitInfo -> Unit
mkUnit) [UnitInfo]
res [SDoc] -> [SDoc] -> [SDoc]
forall a. [a] -> [a] -> [a]
++
if Bool
f then [String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"a package flag"] else []
)
cantFindErr BuildingCabalPackage
using_cabal SDoc
cannot_find SDoc
_ UnitEnv
unit_env Profile
profile [String] -> SDoc
tried_these ModuleName
mod_name FindResult
find_result
= SDoc
cannot_find SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> SDoc -> SDoc
quotes (ModuleName -> SDoc
forall a. Outputable a => a -> SDoc
ppr ModuleName
mod_name)
SDoc -> SDoc -> SDoc
forall doc. IsDoc doc => doc -> doc -> doc
$$ SDoc
more_info
where
mhome_unit :: Maybe HomeUnit
mhome_unit = UnitEnv -> Maybe HomeUnit
ue_homeUnit UnitEnv
unit_env
more_info :: SDoc
more_info
= case FindResult
find_result of
NoPackage Unit
pkg
-> String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"no unit id matching" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> SDoc -> SDoc
quotes (Unit -> SDoc
forall a. Outputable a => a -> SDoc
ppr Unit
pkg) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+>
String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"was found"
NotFound { fr_paths :: FindResult -> [String]
fr_paths = [String]
files, fr_pkg :: FindResult -> Maybe Unit
fr_pkg = Maybe Unit
mb_pkg
, fr_mods_hidden :: FindResult -> [Unit]
fr_mods_hidden = [Unit]
mod_hiddens, fr_pkgs_hidden :: FindResult -> [Unit]
fr_pkgs_hidden = [Unit]
pkg_hiddens
, fr_unusables :: FindResult -> [(Unit, UnusableUnitReason)]
fr_unusables = [(Unit, UnusableUnitReason)]
unusables, fr_suggestions :: FindResult -> [ModuleSuggestion]
fr_suggestions = [ModuleSuggestion]
suggest }
| Just Unit
pkg <- Maybe Unit
mb_pkg
, Maybe HomeUnit
Nothing <- Maybe HomeUnit
mhome_unit
-> Unit -> [String] -> SDoc
not_found_in_package Unit
pkg [String]
files
| Just Unit
pkg <- Maybe Unit
mb_pkg
, Just HomeUnit
home_unit <- Maybe HomeUnit
mhome_unit
, Bool -> Bool
not (HomeUnit -> Unit -> Bool
isHomeUnit HomeUnit
home_unit Unit
pkg)
-> Unit -> [String] -> SDoc
not_found_in_package Unit
pkg [String]
files
| Bool -> Bool
not ([ModuleSuggestion] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [ModuleSuggestion]
suggest)
-> [ModuleSuggestion] -> SDoc
pp_suggestions [ModuleSuggestion]
suggest SDoc -> SDoc -> SDoc
forall doc. IsDoc doc => doc -> doc -> doc
$$ [String] -> SDoc
tried_these [String]
files
| [String] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [String]
files Bool -> Bool -> Bool
&& [Unit] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Unit]
mod_hiddens Bool -> Bool -> Bool
&&
[Unit] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Unit]
pkg_hiddens Bool -> Bool -> Bool
&& [(Unit, UnusableUnitReason)] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [(Unit, UnusableUnitReason)]
unusables
-> String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"It is not a module in the current program, or in any known package."
| Bool
otherwise
-> [SDoc] -> SDoc
forall doc. IsDoc doc => [doc] -> doc
vcat ((Unit -> SDoc) -> [Unit] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map Unit -> SDoc
pkg_hidden [Unit]
pkg_hiddens) SDoc -> SDoc -> SDoc
forall doc. IsDoc doc => doc -> doc -> doc
$$
[SDoc] -> SDoc
forall doc. IsDoc doc => [doc] -> doc
vcat ((Unit -> SDoc) -> [Unit] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map Unit -> SDoc
forall a. Outputable a => a -> SDoc
mod_hidden [Unit]
mod_hiddens) SDoc -> SDoc -> SDoc
forall doc. IsDoc doc => doc -> doc -> doc
$$
[SDoc] -> SDoc
forall doc. IsDoc doc => [doc] -> doc
vcat (((Unit, UnusableUnitReason) -> SDoc)
-> [(Unit, UnusableUnitReason)] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map (Unit, UnusableUnitReason) -> SDoc
forall {a}. Outputable a => (a, UnusableUnitReason) -> SDoc
unusable [(Unit, UnusableUnitReason)]
unusables) SDoc -> SDoc -> SDoc
forall doc. IsDoc doc => doc -> doc -> doc
$$
[String] -> SDoc
tried_these [String]
files
FindResult
_ -> String -> SDoc
forall a. HasCallStack => String -> a
panic String
"cantFindErr"
build_tag :: String
build_tag = Ways -> String
waysBuildTag (Profile -> Ways
profileWays Profile
profile)
not_found_in_package :: Unit -> [String] -> SDoc
not_found_in_package Unit
pkg [String]
files
| String
build_tag String -> String -> Bool
forall a. Eq a => a -> a -> Bool
/= String
""
= let
build :: String
build = if String
build_tag String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"p" then String
"profiling"
else String
"\"" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
build_tag String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"\""
in
String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"Perhaps you haven't installed the " SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> String -> SDoc
forall doc. IsLine doc => String -> doc
text String
build SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<>
String -> SDoc
forall doc. IsLine doc => String -> doc
text String
" libraries for package " SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> SDoc -> SDoc
quotes (Unit -> SDoc
forall a. Outputable a => a -> SDoc
ppr Unit
pkg) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> Char -> SDoc
forall doc. IsLine doc => Char -> doc
char Char
'?' SDoc -> SDoc -> SDoc
forall doc. IsDoc doc => doc -> doc -> doc
$$
[String] -> SDoc
tried_these [String]
files
| Bool
otherwise
= String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"There are files missing in the " SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> SDoc -> SDoc
quotes (Unit -> SDoc
forall a. Outputable a => a -> SDoc
ppr Unit
pkg) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<>
String -> SDoc
forall doc. IsLine doc => String -> doc
text String
" package," SDoc -> SDoc -> SDoc
forall doc. IsDoc doc => doc -> doc -> doc
$$
String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"try running 'ghc-pkg check'." SDoc -> SDoc -> SDoc
forall doc. IsDoc doc => doc -> doc -> doc
$$
[String] -> SDoc
tried_these [String]
files
pkg_hidden :: Unit -> SDoc
pkg_hidden :: Unit -> SDoc
pkg_hidden Unit
uid =
String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"It is a member of the hidden package"
SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> SDoc -> SDoc
quotes (Unit -> SDoc
forall a. Outputable a => a -> SDoc
ppr Unit
uid)
SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> SDoc
forall doc. IsLine doc => doc
dot SDoc -> SDoc -> SDoc
forall doc. IsDoc doc => doc -> doc -> doc
$$ Unit -> SDoc
pkg_hidden_hint Unit
uid
pkg_hidden_hint :: Unit -> SDoc
pkg_hidden_hint Unit
uid
| BuildingCabalPackage
using_cabal BuildingCabalPackage -> BuildingCabalPackage -> Bool
forall a. Eq a => a -> a -> Bool
== BuildingCabalPackage
YesBuildingCabalPackage
= let pkg :: UnitInfo
pkg = String -> Maybe UnitInfo -> UnitInfo
forall a. HasCallStack => String -> Maybe a -> a
expectJust String
"pkg_hidden" (UnitState -> Unit -> Maybe UnitInfo
lookupUnit ((() :: Constraint) => UnitEnv -> UnitState
UnitEnv -> UnitState
ue_units UnitEnv
unit_env) Unit
uid)
in String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"Perhaps you need to add" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+>
SDoc -> SDoc
quotes (PackageName -> SDoc
forall a. Outputable a => a -> SDoc
ppr (UnitInfo -> PackageName
forall srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo srcpkgid srcpkgname uid modulename mod
-> srcpkgname
unitPackageName UnitInfo
pkg)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+>
String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"to the build-depends in your .cabal file."
| Just UnitInfo
pkg <- UnitState -> Unit -> Maybe UnitInfo
lookupUnit ((() :: Constraint) => UnitEnv -> UnitState
UnitEnv -> UnitState
ue_units UnitEnv
unit_env) Unit
uid
= String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"You can run" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+>
SDoc -> SDoc
quotes (String -> SDoc
forall doc. IsLine doc => String -> doc
text String
":set -package " SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> PackageName -> SDoc
forall a. Outputable a => a -> SDoc
ppr (UnitInfo -> PackageName
forall srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo srcpkgid srcpkgname uid modulename mod
-> srcpkgname
unitPackageName UnitInfo
pkg)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+>
String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"to expose it." SDoc -> SDoc -> SDoc
forall doc. IsDoc doc => doc -> doc -> doc
$$
String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"(Note: this unloads all the modules in the current scope.)"
| Bool
otherwise = SDoc
forall doc. IsOutput doc => doc
Outputable.empty
mod_hidden :: a -> SDoc
mod_hidden a
pkg =
String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"it is a hidden module in the package" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> SDoc -> SDoc
quotes (a -> SDoc
forall a. Outputable a => a -> SDoc
ppr a
pkg)
unusable :: (a, UnusableUnitReason) -> SDoc
unusable (a
pkg, UnusableUnitReason
reason)
= String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"It is a member of the package"
SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> SDoc -> SDoc
quotes (a -> SDoc
forall a. Outputable a => a -> SDoc
ppr a
pkg)
SDoc -> SDoc -> SDoc
forall doc. IsDoc doc => doc -> doc -> doc
$$ SDoc -> UnusableUnitReason -> SDoc
pprReason (String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"which is") UnusableUnitReason
reason
pp_suggestions :: [ModuleSuggestion] -> SDoc
pp_suggestions :: [ModuleSuggestion] -> SDoc
pp_suggestions [ModuleSuggestion]
sugs
| [ModuleSuggestion] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [ModuleSuggestion]
sugs = SDoc
forall doc. IsOutput doc => doc
Outputable.empty
| Bool
otherwise = SDoc -> Int -> SDoc -> SDoc
hang (String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"Perhaps you meant")
Int
2 ([SDoc] -> SDoc
forall doc. IsDoc doc => [doc] -> doc
vcat ((ModuleSuggestion -> SDoc) -> [ModuleSuggestion] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map ModuleSuggestion -> SDoc
pp_sugg [ModuleSuggestion]
sugs))
pp_sugg :: ModuleSuggestion -> SDoc
pp_sugg (SuggestVisible ModuleName
m GenModule Unit
mod ModuleOrigin
o) = ModuleName -> SDoc
forall a. Outputable a => a -> SDoc
ppr ModuleName
m SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> ModuleOrigin -> SDoc
provenance ModuleOrigin
o
where provenance :: ModuleOrigin -> SDoc
provenance ModuleOrigin
ModHidden = SDoc
forall doc. IsOutput doc => doc
Outputable.empty
provenance (ModUnusable UnusableUnitReason
_) = SDoc
forall doc. IsOutput doc => doc
Outputable.empty
provenance (ModOrigin{ fromOrigUnit :: ModuleOrigin -> Maybe Bool
fromOrigUnit = Maybe Bool
e,
fromExposedReexport :: ModuleOrigin -> [UnitInfo]
fromExposedReexport = [UnitInfo]
res,
fromPackageFlag :: ModuleOrigin -> Bool
fromPackageFlag = Bool
f })
| Just Bool
True <- Maybe Bool
e
= SDoc -> SDoc
forall doc. IsLine doc => doc -> doc
parens (String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"from" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Unit -> SDoc
forall a. Outputable a => a -> SDoc
ppr (GenModule Unit -> Unit
forall unit. GenModule unit -> unit
moduleUnit GenModule Unit
mod))
| Bool
f Bool -> Bool -> Bool
&& GenModule Unit -> ModuleName
forall unit. GenModule unit -> ModuleName
moduleName GenModule Unit
mod ModuleName -> ModuleName -> Bool
forall a. Eq a => a -> a -> Bool
== ModuleName
m
= SDoc -> SDoc
forall doc. IsLine doc => doc -> doc
parens (String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"from" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Unit -> SDoc
forall a. Outputable a => a -> SDoc
ppr (GenModule Unit -> Unit
forall unit. GenModule unit -> unit
moduleUnit GenModule Unit
mod))
| (UnitInfo
pkg:[UnitInfo]
_) <- [UnitInfo]
res
= SDoc -> SDoc
forall doc. IsLine doc => doc -> doc
parens (String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"from" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Unit -> SDoc
forall a. Outputable a => a -> SDoc
ppr (UnitInfo -> Unit
mkUnit UnitInfo
pkg)
SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> SDoc
forall doc. IsLine doc => doc
comma SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"reexporting" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> GenModule Unit -> SDoc
forall a. Outputable a => a -> SDoc
ppr GenModule Unit
mod)
| Bool
f
= SDoc -> SDoc
forall doc. IsLine doc => doc -> doc
parens (String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"defined via package flags to be"
SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> GenModule Unit -> SDoc
forall a. Outputable a => a -> SDoc
ppr GenModule Unit
mod)
| Bool
otherwise = SDoc
forall doc. IsOutput doc => doc
Outputable.empty
pp_sugg (SuggestHidden ModuleName
m GenModule Unit
mod ModuleOrigin
o) = ModuleName -> SDoc
forall a. Outputable a => a -> SDoc
ppr ModuleName
m SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> ModuleOrigin -> SDoc
provenance ModuleOrigin
o
where provenance :: ModuleOrigin -> SDoc
provenance ModuleOrigin
ModHidden = SDoc
forall doc. IsOutput doc => doc
Outputable.empty
provenance (ModUnusable UnusableUnitReason
_) = SDoc
forall doc. IsOutput doc => doc
Outputable.empty
provenance (ModOrigin{ fromOrigUnit :: ModuleOrigin -> Maybe Bool
fromOrigUnit = Maybe Bool
e,
fromHiddenReexport :: ModuleOrigin -> [UnitInfo]
fromHiddenReexport = [UnitInfo]
rhs })
| Just Bool
False <- Maybe Bool
e
= SDoc -> SDoc
forall doc. IsLine doc => doc -> doc
parens (String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"needs flag -package-id"
SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Unit -> SDoc
forall a. Outputable a => a -> SDoc
ppr (GenModule Unit -> Unit
forall unit. GenModule unit -> unit
moduleUnit GenModule Unit
mod))
| (UnitInfo
pkg:[UnitInfo]
_) <- [UnitInfo]
rhs
= SDoc -> SDoc
forall doc. IsLine doc => doc -> doc
parens (String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"needs flag -package-id"
SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Unit -> SDoc
forall a. Outputable a => a -> SDoc
ppr (UnitInfo -> Unit
mkUnit UnitInfo
pkg))
| Bool
otherwise = SDoc
forall doc. IsOutput doc => doc
Outputable.empty