{-# LANGUAGE NoImplicitPrelude          #-}
{-# LANGUAGE DataKinds                  #-}
{-# LANGUAGE OverloadedStrings          #-}

module Stack.Types.Build.Exception
  ( BuildException (..)
  , BuildPrettyException (..)
  , pprintTargetParseErrors
  , ConstructPlanException (..)
  , LatestApplicableVersion
  , BadDependency (..)
  ) where

import qualified Data.ByteString as S
import           Data.Char ( isSpace )
import           Data.List as L
import qualified Data.Map as Map
import qualified Data.Map.Strict as M
import           Data.Monoid.Map ( MonoidMap (..) )
import qualified Data.Set as Set
import qualified Data.Text as T
import           Distribution.System ( Arch )
import qualified Distribution.Text as C
import           Distribution.Types.PackageName ( mkPackageName )
import           Distribution.Types.TestSuiteInterface ( TestSuiteInterface )
import qualified Distribution.Version as C
import           RIO.Process ( showProcessArgDebug )
import           Stack.Constants
                   ( defaultUserConfigPath, wiredInPackages )
import           Stack.Prelude
import           Stack.Types.Compiler ( ActualCompiler, compilerVersionString )
import           Stack.Types.CompilerBuild
                   ( CompilerBuild, compilerBuildSuffix )
import           Stack.Types.DumpPackage ( DumpPackage )
import           Stack.Types.UnusedFlags ( FlagSource (..), UnusedFlags (..) )
import           Stack.Types.GHCVariant ( GHCVariant, ghcVariantSuffix )
import           Stack.Types.NamedComponent
                   ( NamedComponent, renderPkgComponent )
import           Stack.Types.Package ( Package (..), packageIdentifier )
import           Stack.Types.ParentMap ( ParentMap )
import           Stack.Types.Version ( VersionCheck (..), VersionRange )

-- | Type representing exceptions thrown by functions exported by modules with

-- names beginning @Stack.Build@.

data BuildException
  = Couldn'tFindPkgId PackageName
  | CompilerVersionMismatch
      (Maybe (ActualCompiler, Arch)) -- found

      (WantedCompiler, Arch) -- expected

      GHCVariant -- expected

      CompilerBuild -- expected

      VersionCheck
      (Maybe (Path Abs File)) -- Path to the stack.yaml file

      Text -- recommended resolution

  | Couldn'tParseTargets [Text]
  | UnknownTargets
      (Set PackageName) -- no known version

      (Map PackageName Version) -- not in snapshot, here's the most recent

                                -- version in the index

      (Path Abs File) -- stack.yaml

  | TestSuiteFailure
      PackageIdentifier
      (Map Text (Maybe ExitCode))
      (Maybe (Path Abs File))
      S.ByteString
  | TestSuiteTypeUnsupported TestSuiteInterface
  | LocalPackageDoesn'tMatchTarget
      PackageName
      Version -- local version

      Version -- version specified on command line

  | NoSetupHsFound (Path Abs Dir)
  | InvalidGhcOptionsSpecification [PackageName]
  | TestSuiteExeMissing Bool String String String
  | CabalCopyFailed Bool String
  | LocalPackagesPresent [PackageIdentifier]
  | CouldNotLockDistDir !(Path Abs File)
  | TaskCycleBug PackageIdentifier
  | PackageIdMissingBug PackageIdentifier
  | AllInOneBuildBug
  | MultipleResultsBug PackageName [DumpPackage]
  | TemplateHaskellNotFoundBug
  | HaddockIndexNotFound
  | ShowBuildErrorBug
  deriving (Int -> BuildException -> ShowS
[BuildException] -> ShowS
BuildException -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BuildException] -> ShowS
$cshowList :: [BuildException] -> ShowS
show :: BuildException -> String
$cshow :: BuildException -> String
showsPrec :: Int -> BuildException -> ShowS
$cshowsPrec :: Int -> BuildException -> ShowS
Show, Typeable)

instance Exception BuildException where
  displayException :: BuildException -> String
displayException (Couldn'tFindPkgId PackageName
name) = String -> ShowS
bugReport String
"[S-7178]" forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
    [ String
"After installing "
    , PackageName -> String
packageNameString PackageName
name
    ,String
", the package id couldn't be found (via ghc-pkg describe "
    , PackageName -> String
packageNameString PackageName
name
    , String
")."
    ]
  displayException (CompilerVersionMismatch Maybe (ActualCompiler, Arch)
mactual (WantedCompiler
expected, Arch
eArch) GHCVariant
ghcVariant CompilerBuild
ghcBuild VersionCheck
check Maybe (Path Abs File)
mstack Text
resolution) = forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
    [ String
"Error: [S-6362]\n"
    , case Maybe (ActualCompiler, Arch)
mactual of
        Maybe (ActualCompiler, Arch)
Nothing -> String
"No compiler found, expected "
        Just (ActualCompiler
actual, Arch
arch) -> forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
          [ String
"Compiler version mismatched, found "
          , ActualCompiler -> String
compilerVersionString ActualCompiler
actual
          , String
" ("
          , forall a. Pretty a => a -> String
C.display Arch
arch
          , String
")"
          , String
", but expected "
          ]
    , case VersionCheck
check of
        VersionCheck
MatchMinor -> String
"minor version match with "
        VersionCheck
MatchExact -> String
"exact version "
        VersionCheck
NewerMinor -> String
"minor version match or newer with "
    , Text -> String
T.unpack forall a b. (a -> b) -> a -> b
$ Utf8Builder -> Text
utf8BuilderToText forall a b. (a -> b) -> a -> b
$ forall a. Display a => a -> Utf8Builder
display WantedCompiler
expected
    , String
" ("
    , forall a. Pretty a => a -> String
C.display Arch
eArch
    , GHCVariant -> String
ghcVariantSuffix GHCVariant
ghcVariant
    , CompilerBuild -> String
compilerBuildSuffix CompilerBuild
ghcBuild
    , String
") (based on "
    , case Maybe (Path Abs File)
mstack of
        Maybe (Path Abs File)
Nothing -> String
"command line arguments"
        Just Path Abs File
stack -> String
"resolver setting in " forall a. [a] -> [a] -> [a]
++ forall b t. Path b t -> String
toFilePath Path Abs File
stack
    , String
").\n"
    , Text -> String
T.unpack Text
resolution
    ]
  displayException (Couldn'tParseTargets [Text]
targets) = [String] -> String
unlines
    forall a b. (a -> b) -> a -> b
$ String
"Error: [S-3127]"
    forall a. a -> [a] -> [a]
: String
"The following targets could not be parsed as package names or \
      \directories:"
    forall a. a -> [a] -> [a]
: forall a b. (a -> b) -> [a] -> [b]
map Text -> String
T.unpack [Text]
targets
  displayException (UnknownTargets Set PackageName
noKnown Map PackageName Version
notInSnapshot Path Abs File
stackYaml) = [String] -> String
unlines
    forall a b. (a -> b) -> a -> b
$ String
"Error: [S-2154]"
    forall a. a -> [a] -> [a]
: ([String]
noKnown' forall a. [a] -> [a] -> [a]
++ [String]
notInSnapshot')
   where
    noKnown' :: [String]
noKnown'
      | forall a. Set a -> Bool
Set.null Set PackageName
noKnown = []
      | Bool
otherwise = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$
          String
"The following target packages were not found: " forall a. [a] -> [a] -> [a]
++
          forall a. [a] -> [[a]] -> [a]
intercalate String
", " (forall a b. (a -> b) -> [a] -> [b]
map PackageName -> String
packageNameString forall a b. (a -> b) -> a -> b
$ forall a. Set a -> [a]
Set.toList Set PackageName
noKnown) forall a. [a] -> [a] -> [a]
++
          String
"\nSee https://docs.haskellstack.org/en/stable/build_command/#target-syntax for details."
    notInSnapshot' :: [String]
notInSnapshot'
      | forall k a. Map k a -> Bool
Map.null Map PackageName Version
notInSnapshot = []
      | Bool
otherwise =
            String
"The following packages are not in your snapshot, but exist"
          forall a. a -> [a] -> [a]
: String
"in your package index. Recommended action: add them to your"
          forall a. a -> [a] -> [a]
: (String
"extra-deps in " forall a. [a] -> [a] -> [a]
++ forall b t. Path b t -> String
toFilePath Path Abs File
stackYaml)
          forall a. a -> [a] -> [a]
: String
"(Note: these are the most recent versions,"
          forall a. a -> [a] -> [a]
: String
"but there's no guarantee that they'll build together)."
          forall a. a -> [a] -> [a]
: String
""
          forall a. a -> [a] -> [a]
: forall a b. (a -> b) -> [a] -> [b]
map
              (\(PackageName
name, Version
version') -> String
"- " forall a. [a] -> [a] -> [a]
++ PackageIdentifier -> String
packageIdentifierString
                  (PackageName -> Version -> PackageIdentifier
PackageIdentifier PackageName
name Version
version'))
              (forall k a. Map k a -> [(k, a)]
Map.toList Map PackageName Version
notInSnapshot)
  displayException (TestSuiteFailure PackageIdentifier
ident Map Text (Maybe ExitCode)
codes Maybe (Path Abs File)
mlogFile ByteString
bs) = [String] -> String
unlines
    forall a b. (a -> b) -> a -> b
$ String
"Error: [S-1995]"
    forall a. a -> [a] -> [a]
: forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
        [ [String
"Test suite failure for package " forall a. [a] -> [a] -> [a]
++ PackageIdentifier -> String
packageIdentifierString PackageIdentifier
ident]
        , forall a b c. (a -> b -> c) -> b -> a -> c
flip forall a b. (a -> b) -> [a] -> [b]
map (forall k a. Map k a -> [(k, a)]
Map.toList Map Text (Maybe ExitCode)
codes) forall a b. (a -> b) -> a -> b
$ \(Text
name, Maybe ExitCode
mcode) -> forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
            [ String
"    "
            , Text -> String
T.unpack Text
name
            , String
": "
            , case Maybe ExitCode
mcode of
                Maybe ExitCode
Nothing -> String
" executable not found"
                Just ExitCode
ec -> String
" exited with: " forall a. [a] -> [a] -> [a]
++ forall e. Exception e => e -> String
displayException ExitCode
ec
            ]
        , forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ case Maybe (Path Abs File)
mlogFile of
            Maybe (Path Abs File)
Nothing -> String
"Logs printed to console"
            -- TODO Should we load up the full error output and print it here?

            Just Path Abs File
logFile -> String
"Full log available at " forall a. [a] -> [a] -> [a]
++ forall b t. Path b t -> String
toFilePath Path Abs File
logFile
        , if ByteString -> Bool
S.null ByteString
bs
            then []
            else
              [ String
""
              , String
""
              , ShowS
doubleIndent forall a b. (a -> b) -> a -> b
$ Text -> String
T.unpack forall a b. (a -> b) -> a -> b
$ OnDecodeError -> ByteString -> Text
decodeUtf8With OnDecodeError
lenientDecode ByteString
bs
              ]
        ]
   where
    indent' :: ShowS
indent' = forall a. (a -> Bool) -> [a] -> [a]
dropWhileEnd Char -> Bool
isSpace forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> String
unlines forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (String
"  " ++) forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [String]
lines
    doubleIndent :: ShowS
doubleIndent = ShowS
indent' forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShowS
indent'
  displayException (TestSuiteTypeUnsupported TestSuiteInterface
interface) = forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
    [ String
"Error: [S-3819]\n"
    , String
"Unsupported test suite type: "
    , forall a. Show a => a -> String
show TestSuiteInterface
interface
    ]
     -- Suppressing duplicate output

  displayException (LocalPackageDoesn'tMatchTarget PackageName
name Version
localV Version
requestedV) = forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
    [ String
"Error: [S-5797]\n"
    , String
"Version for local package "
    , PackageName -> String
packageNameString PackageName
name
    , String
" is "
    , Version -> String
versionString Version
localV
    , String
", but you asked for "
    , Version -> String
versionString Version
requestedV
    , String
" on the command line"
    ]
  displayException (NoSetupHsFound Path Abs Dir
dir) = forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
    [ String
"Error: [S-3118]\n"
    , String
"No Setup.hs or Setup.lhs file found in "
    , forall b t. Path b t -> String
toFilePath Path Abs Dir
dir
    ]
  displayException (InvalidGhcOptionsSpecification [PackageName]
unused) = [String] -> String
unlines
    forall a b. (a -> b) -> a -> b
$ String
"Error: [S-4925]"
    forall a. a -> [a] -> [a]
: String
"Invalid GHC options specification:"
    forall a. a -> [a] -> [a]
: forall a b. (a -> b) -> [a] -> [b]
map PackageName -> String
showGhcOptionSrc [PackageName]
unused
   where
    showGhcOptionSrc :: PackageName -> String
showGhcOptionSrc PackageName
name = forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
      [ String
"- Package '"
      , PackageName -> String
packageNameString PackageName
name
      , String
"' not found"
      ]
  displayException (TestSuiteExeMissing Bool
isSimpleBuildType String
exeName String
pkgName' String
testName) =
    String -> Bool -> ShowS
missingExeError String
"[S-7987]"
      Bool
isSimpleBuildType forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
        [ String
"Test suite executable \""
        , String
exeName
        , String
" not found for "
        , String
pkgName'
        , String
":test:"
        , String
testName
        ]
  displayException (CabalCopyFailed Bool
isSimpleBuildType String
innerMsg) =
    String -> Bool -> ShowS
missingExeError String
"[S-8027]"
      Bool
isSimpleBuildType forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
        [ String
"'cabal copy' failed.  Error message:\n"
        , String
innerMsg
        , String
"\n"
        ]
  displayException (LocalPackagesPresent [PackageIdentifier]
locals) = [String] -> String
unlines
    forall a b. (a -> b) -> a -> b
$ String
"Error: [S-5510]"
    forall a. a -> [a] -> [a]
: String
"Local packages are not allowed when using the 'script' command. \
      \Packages found:"
    forall a. a -> [a] -> [a]
: forall a b. (a -> b) -> [a] -> [b]
map (\PackageIdentifier
ident -> String
"- " forall a. [a] -> [a] -> [a]
++ PackageIdentifier -> String
packageIdentifierString PackageIdentifier
ident) [PackageIdentifier]
locals
  displayException (CouldNotLockDistDir Path Abs File
lockFile) = [String] -> String
unlines
    [ String
"Error: [S-7168]"
    , String
"Locking the dist directory failed, try to lock file:"
    , String
"  " forall a. [a] -> [a] -> [a]
++ forall b t. Path b t -> String
toFilePath Path Abs File
lockFile
    , String
"Maybe you're running another copy of Stack?"
    ]
  displayException (TaskCycleBug PackageIdentifier
pid) = String -> ShowS
bugReport String
"[S-7868]" forall a b. (a -> b) -> a -> b
$
    String
"Unexpected task cycle for "
    forall a. [a] -> [a] -> [a]
++ PackageName -> String
packageNameString (PackageIdentifier -> PackageName
pkgName PackageIdentifier
pid)
  displayException (PackageIdMissingBug PackageIdentifier
ident) = String -> ShowS
bugReport String
"[S-8923]" forall a b. (a -> b) -> a -> b
$
    String
"singleBuild: missing package ID missing: "
    forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show PackageIdentifier
ident
  displayException BuildException
AllInOneBuildBug = String -> ShowS
bugReport String
"[S-7371]"
    String
"Cannot have an all-in-one build that also has a final build step."
  displayException (MultipleResultsBug PackageName
name [DumpPackage]
dps) = String -> ShowS
bugReport String
"[S-6739]" forall a b. (a -> b) -> a -> b
$
    String
"singleBuild: multiple results when describing installed package "
    forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show (PackageName
name, [DumpPackage]
dps)
  displayException BuildException
TemplateHaskellNotFoundBug = String -> ShowS
bugReport String
"[S-3121]"
    String
"template-haskell is a wired-in GHC boot library but it wasn't found."
  displayException BuildException
HaddockIndexNotFound =
    String
"Error: [S-6901]\n"
    forall a. [a] -> [a] -> [a]
++ String
"No local or snapshot doc index found to open."
  displayException BuildException
ShowBuildErrorBug = String -> ShowS
bugReport String
"[S-5452]"
    String
"Unexpected case in showBuildError."

data BuildPrettyException
  = ConstructPlanFailed
      [ConstructPlanException]
      (Path Abs File)
      (Path Abs Dir)
      ParentMap
      (Set PackageName)
      (Map PackageName [PackageName])
  | ExecutionFailure [SomeException]
  | CabalExitedUnsuccessfully
      ExitCode
      PackageIdentifier
      (Path Abs File)  -- cabal Executable

      [String]         -- cabal arguments

      (Maybe (Path Abs File)) -- logfiles location

      [Text]     -- log contents

  | SetupHsBuildFailure
      ExitCode
      (Maybe PackageIdentifier) -- which package's custom setup, is simple setup

                                -- if Nothing

      (Path Abs File)  -- ghc Executable

      [String]         -- ghc arguments

      (Maybe (Path Abs File)) -- logfiles location

      [Text]     -- log contents

  | TargetParseException [StyleDoc]
  | SomeTargetsNotBuildable [(PackageName, NamedComponent)]
  | InvalidFlagSpecification (Set UnusedFlags)
  | GHCProfOptionInvalid
  deriving (Int -> BuildPrettyException -> ShowS
[BuildPrettyException] -> ShowS
BuildPrettyException -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BuildPrettyException] -> ShowS
$cshowList :: [BuildPrettyException] -> ShowS
show :: BuildPrettyException -> String
$cshow :: BuildPrettyException -> String
showsPrec :: Int -> BuildPrettyException -> ShowS
$cshowsPrec :: Int -> BuildPrettyException -> ShowS
Show, Typeable)

instance Pretty BuildPrettyException where
  pretty :: BuildPrettyException -> StyleDoc
pretty ( ConstructPlanFailed [ConstructPlanException]
errs Path Abs File
stackYaml Path Abs Dir
stackRoot ParentMap
parents Set PackageName
wanted Map PackageName [PackageName]
prunedGlobalDeps ) =
    StyleDoc
"[S-4804]"
    forall a. Semigroup a => a -> a -> a
<> StyleDoc
line
    forall a. Semigroup a => a -> a -> a
<> String -> StyleDoc
flow String
"Stack failed to construct a build plan."
    forall a. Semigroup a => a -> a -> a
<> StyleDoc
blankLine
    forall a. Semigroup a => a -> a -> a
<> [ConstructPlanException]
-> Path Abs File
-> Path Abs Dir
-> ParentMap
-> Set PackageName
-> Map PackageName [PackageName]
-> StyleDoc
pprintExceptions
           [ConstructPlanException]
errs Path Abs File
stackYaml Path Abs Dir
stackRoot ParentMap
parents Set PackageName
wanted Map PackageName [PackageName]
prunedGlobalDeps
  pretty (ExecutionFailure [SomeException]
es) =
    StyleDoc
"[S-7282]"
    forall a. Semigroup a => a -> a -> a
<> StyleDoc
line
    forall a. Semigroup a => a -> a -> a
<> String -> StyleDoc
flow String
"Stack failed to execute the build plan."
    forall a. Semigroup a => a -> a -> a
<> StyleDoc
blankLine
    forall a. Semigroup a => a -> a -> a
<> [StyleDoc] -> StyleDoc
fillSep
         [ String -> StyleDoc
flow String
"While executing the build plan, Stack encountered the"
         , case [SomeException]
es of
             [SomeException
_] -> StyleDoc
"error:"
             [SomeException]
_ -> String -> StyleDoc
flow String
"following errors:"
         ]
    forall a. Semigroup a => a -> a -> a
<> StyleDoc
blankLine
    forall a. Semigroup a => a -> a -> a
<> [StyleDoc] -> StyleDoc
hcat (forall a. a -> [a] -> [a]
L.intersperse StyleDoc
blankLine (forall a b. (a -> b) -> [a] -> [b]
map SomeException -> StyleDoc
ppException [SomeException]
es))
  pretty (CabalExitedUnsuccessfully ExitCode
exitCode PackageIdentifier
taskProvides' Path Abs File
execName [String]
fullArgs Maybe (Path Abs File)
logFiles [Text]
bss) =
    String
-> Bool
-> ExitCode
-> Maybe PackageIdentifier
-> Path Abs File
-> [String]
-> Maybe (Path Abs File)
-> [Text]
-> StyleDoc
showBuildError String
"[S-7011]"
      Bool
False ExitCode
exitCode (forall a. a -> Maybe a
Just PackageIdentifier
taskProvides') Path Abs File
execName [String]
fullArgs Maybe (Path Abs File)
logFiles [Text]
bss
  pretty (SetupHsBuildFailure ExitCode
exitCode Maybe PackageIdentifier
mtaskProvides Path Abs File
execName [String]
fullArgs Maybe (Path Abs File)
logFiles [Text]
bss) =
    String
-> Bool
-> ExitCode
-> Maybe PackageIdentifier
-> Path Abs File
-> [String]
-> Maybe (Path Abs File)
-> [Text]
-> StyleDoc
showBuildError String
"[S-6374]"
      Bool
True ExitCode
exitCode Maybe PackageIdentifier
mtaskProvides Path Abs File
execName [String]
fullArgs Maybe (Path Abs File)
logFiles [Text]
bss
  pretty (TargetParseException [StyleDoc]
errs) =
    StyleDoc
"[S-8506]"
    forall a. Semigroup a => a -> a -> a
<> [StyleDoc] -> StyleDoc
pprintTargetParseErrors [StyleDoc]
errs
  pretty (SomeTargetsNotBuildable [(PackageName, NamedComponent)]
xs) =
    StyleDoc
"[S-7086]"
    forall a. Semigroup a => a -> a -> a
<> StyleDoc
line
    forall a. Semigroup a => a -> a -> a
<> [StyleDoc] -> StyleDoc
fillSep
         (  [ String -> StyleDoc
flow String
"The following components have"
            , Style -> StyleDoc -> StyleDoc
style Style
Shell (String -> StyleDoc
flow String
"buildable: False")
            , String -> StyleDoc
flow String
"set in the Cabal configuration, and so cannot be targets:"
            ]
         forall a. Semigroup a => a -> a -> a
<> forall a. Pretty a => Maybe Style -> Bool -> [a] -> [StyleDoc]
mkNarrativeList (forall a. a -> Maybe a
Just Style
Target) Bool
False
              (forall a b. (a -> b) -> [a] -> [b]
map (forall a. IsString a => String -> a
fromString forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
T.unpack forall b c a. (b -> c) -> (a -> b) -> a -> c
. (PackageName, NamedComponent) -> Text
renderPkgComponent) [(PackageName, NamedComponent)]
xs :: [StyleDoc])
         )
    forall a. Semigroup a => a -> a -> a
<> StyleDoc
blankLine
    forall a. Semigroup a => a -> a -> a
<> String -> StyleDoc
flow String
"To resolve this, either provide flags such that these components \
            \are buildable, or only specify buildable targets."
  pretty (InvalidFlagSpecification Set UnusedFlags
unused) =
    StyleDoc
"[S-8664]"
    forall a. Semigroup a => a -> a -> a
<> StyleDoc
line
    forall a. Semigroup a => a -> a -> a
<> String -> StyleDoc
flow String
"Invalid flag specification:"
    forall a. Semigroup a => a -> a -> a
<> StyleDoc
line
    forall a. Semigroup a => a -> a -> a
<> [StyleDoc] -> StyleDoc
bulletedList (forall a b. (a -> b) -> [a] -> [b]
map UnusedFlags -> StyleDoc
go (forall a. Set a -> [a]
Set.toList Set UnusedFlags
unused))
   where
    showFlagSrc :: FlagSource -> StyleDoc
    showFlagSrc :: FlagSource -> StyleDoc
showFlagSrc FlagSource
FSCommandLine = String -> StyleDoc
flow String
"(specified on the command line)"
    showFlagSrc FlagSource
FSStackYaml =
      String -> StyleDoc
flow String
"(specified in the project-level configuration (e.g. stack.yaml))"

    go :: UnusedFlags -> StyleDoc
    go :: UnusedFlags -> StyleDoc
go (UFNoPackage FlagSource
src PackageName
name) = [StyleDoc] -> StyleDoc
fillSep
      [ StyleDoc
"Package"
      , Style -> StyleDoc -> StyleDoc
style Style
Error (forall a. IsString a => String -> a
fromString forall a b. (a -> b) -> a -> b
$ PackageName -> String
packageNameString PackageName
name)
      , String -> StyleDoc
flow String
"not found"
      , FlagSource -> StyleDoc
showFlagSrc FlagSource
src
      ]
    go (UFFlagsNotDefined FlagSource
src PackageName
pname Set FlagName
pkgFlags Set FlagName
flags) =
         [StyleDoc] -> StyleDoc
fillSep
           ( StyleDoc
"Package"
           forall a. a -> [a] -> [a]
: Style -> StyleDoc -> StyleDoc
style Style
Current (forall a. IsString a => String -> a
fromString String
name)
           forall a. a -> [a] -> [a]
: String -> StyleDoc
flow String
"does not define the following flags"
           forall a. a -> [a] -> [a]
: FlagSource -> StyleDoc
showFlagSrc FlagSource
src forall a. Semigroup a => a -> a -> a
<> StyleDoc
":"
           forall a. a -> [a] -> [a]
: forall a. Pretty a => Maybe Style -> Bool -> [a] -> [StyleDoc]
mkNarrativeList (forall a. a -> Maybe a
Just Style
Error) Bool
False
               (forall a b. (a -> b) -> [a] -> [b]
map (forall a. IsString a => String -> a
fromString forall b c a. (b -> c) -> (a -> b) -> a -> c
. FlagName -> String
flagNameString) (forall a. Set a -> [a]
Set.toList Set FlagName
flags) :: [StyleDoc])
           )
      forall a. Semigroup a => a -> a -> a
<> StyleDoc
line
      forall a. Semigroup a => a -> a -> a
<> if forall a. Set a -> Bool
Set.null Set FlagName
pkgFlags
           then [StyleDoc] -> StyleDoc
fillSep
             [ String -> StyleDoc
flow String
"No flags are defined by package"
             , Style -> StyleDoc -> StyleDoc
style Style
Current (forall a. IsString a => String -> a
fromString String
name) forall a. Semigroup a => a -> a -> a
<> StyleDoc
"."
             ]
           else [StyleDoc] -> StyleDoc
fillSep
           ( String -> StyleDoc
flow String
"Flags defined by package"
           forall a. a -> [a] -> [a]
: Style -> StyleDoc -> StyleDoc
style Style
Current (forall a. IsString a => String -> a
fromString String
name)
           forall a. a -> [a] -> [a]
: StyleDoc
"are:"
           forall a. a -> [a] -> [a]
: forall a. Pretty a => Maybe Style -> Bool -> [a] -> [StyleDoc]
mkNarrativeList (forall a. a -> Maybe a
Just Style
Good) Bool
False
               (forall a b. (a -> b) -> [a] -> [b]
map (forall a. IsString a => String -> a
fromString forall b c a. (b -> c) -> (a -> b) -> a -> c
. FlagName -> String
flagNameString) (forall a. Set a -> [a]
Set.toList Set FlagName
pkgFlags) :: [StyleDoc])
           )
     where
      name :: String
name = PackageName -> String
packageNameString PackageName
pname
    go (UFSnapshot PackageName
name) = [StyleDoc] -> StyleDoc
fillSep
      [ String -> StyleDoc
flow String
"Attempted to set flag on snapshot package"
      , Style -> StyleDoc -> StyleDoc
style Style
Current (forall a. IsString a => String -> a
fromString forall a b. (a -> b) -> a -> b
$ PackageName -> String
packageNameString PackageName
name) forall a. Semigroup a => a -> a -> a
<> StyleDoc
","
      , String -> StyleDoc
flow String
"please add the package to"
      , Style -> StyleDoc -> StyleDoc
style Style
Shell StyleDoc
"extra-deps" forall a. Semigroup a => a -> a -> a
<> StyleDoc
"."
      ]
  pretty BuildPrettyException
GHCProfOptionInvalid =
    StyleDoc
"[S-8100]"
    forall a. Semigroup a => a -> a -> a
<> StyleDoc
line
    forall a. Semigroup a => a -> a -> a
<> [StyleDoc] -> StyleDoc
fillSep
         [ String -> StyleDoc
flow String
"When building with Stack, you should not use GHC's"
         , Style -> StyleDoc -> StyleDoc
style Style
Shell StyleDoc
"-prof"
         , String -> StyleDoc
flow String
"option. Instead, please use Stack's"
         , Style -> StyleDoc -> StyleDoc
style Style
Shell StyleDoc
"--library-profiling"
         , StyleDoc
"and"
         , Style -> StyleDoc -> StyleDoc
style Style
Shell StyleDoc
"--executable-profiling"
         , String -> StyleDoc
flow String
"flags. See:"
         , Style -> StyleDoc -> StyleDoc
style Style
Url StyleDoc
"https://github.com/commercialhaskell/stack/issues/1015" forall a. Semigroup a => a -> a -> a
<> StyleDoc
"."
         ]

instance Exception BuildPrettyException

-- | Helper function to pretty print an error message for target parse errors.

pprintTargetParseErrors :: [StyleDoc] -> StyleDoc
pprintTargetParseErrors :: [StyleDoc] -> StyleDoc
pprintTargetParseErrors [StyleDoc]
errs =
     StyleDoc
line
  forall a. Semigroup a => a -> a -> a
<> String -> StyleDoc
flow String
"Stack failed to parse the target(s)."
  forall a. Semigroup a => a -> a -> a
<> StyleDoc
blankLine
  forall a. Semigroup a => a -> a -> a
<> [StyleDoc] -> StyleDoc
fillSep
       [ String -> StyleDoc
flow String
"While parsing, Stack encountered the"
       , case [StyleDoc]
errs of
           [StyleDoc
err] ->
                  StyleDoc
"error:"
               forall a. Semigroup a => a -> a -> a
<> StyleDoc
blankLine
               forall a. Semigroup a => a -> a -> a
<> Int -> StyleDoc -> StyleDoc
indent Int
4 StyleDoc
err
           [StyleDoc]
_ ->
                  String -> StyleDoc
flow String
"following errors:"
               forall a. Semigroup a => a -> a -> a
<> StyleDoc
blankLine
               forall a. Semigroup a => a -> a -> a
<> [StyleDoc] -> StyleDoc
bulletedList [StyleDoc]
errs
       ]
  forall a. Semigroup a => a -> a -> a
<> StyleDoc
blankLine
  forall a. Semigroup a => a -> a -> a
<> [StyleDoc] -> StyleDoc
fillSep
       [ String -> StyleDoc
flow String
"Stack expects a target to be a package name (e.g."
       , Style -> StyleDoc -> StyleDoc
style Style
Shell StyleDoc
"my-package" forall a. Semigroup a => a -> a -> a
<> StyleDoc
"),"
       , String -> StyleDoc
flow String
"a package identifier (e.g."
       , Style -> StyleDoc -> StyleDoc
style Style
Shell StyleDoc
"my-package-0.1.2.3" forall a. Semigroup a => a -> a -> a
<> StyleDoc
"),"
       , String -> StyleDoc
flow String
"a package component (e.g."
       , Style -> StyleDoc -> StyleDoc
style Style
Shell StyleDoc
"my-package:test:my-test-suite" forall a. Semigroup a => a -> a -> a
<> StyleDoc
"),"
       , String -> StyleDoc
flow String
"or, failing that, a relative path to a directory that is a \
              \local package directory or a parent directory of one or more \
              \local package directories."
       ]

pprintExceptions ::
     [ConstructPlanException]
  -> Path Abs File
  -> Path Abs Dir
  -> ParentMap
  -> Set PackageName
  -> Map PackageName [PackageName]
  -> StyleDoc
pprintExceptions :: [ConstructPlanException]
-> Path Abs File
-> Path Abs Dir
-> ParentMap
-> Set PackageName
-> Map PackageName [PackageName]
-> StyleDoc
pprintExceptions [ConstructPlanException]
exceptions Path Abs File
stackYaml Path Abs Dir
stackRoot ParentMap
parentMap Set PackageName
wanted' Map PackageName [PackageName]
prunedGlobalDeps =
  forall a. Monoid a => [a] -> a
mconcat forall a b. (a -> b) -> a -> b
$
    [ String -> StyleDoc
flow String
"While constructing the build plan, Stack encountered the \
           \following errors:"
    , StyleDoc
blankLine
    , forall a. Monoid a => [a] -> a
mconcat (forall a. a -> [a] -> [a]
L.intersperse StyleDoc
blankLine (forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe ConstructPlanException -> Maybe StyleDoc
pprintException [ConstructPlanException]
exceptions'))
    ] forall a. [a] -> [a] -> [a]
++ if forall (t :: * -> *) a. Foldable t => t a -> Bool
L.null [StyleDoc]
recommendations
           then []
           else
             [ StyleDoc
blankLine
             , String -> StyleDoc
flow String
"Some different approaches to resolving this:"
             , StyleDoc
blankLine
             ] forall a. [a] -> [a] -> [a]
++ [StyleDoc]
recommendations

 where
  exceptions' :: [ConstructPlanException]
exceptions' = {- should we dedupe these somehow? nubOrd -} [ConstructPlanException]
exceptions

  recommendations :: [StyleDoc]
recommendations =
    if Bool -> Bool
not Bool
onlyHasDependencyMismatches
      then []
      else
        [ StyleDoc
"  *" StyleDoc -> StyleDoc -> StyleDoc
<+> StyleDoc -> StyleDoc
align ([StyleDoc] -> StyleDoc
fillSep
            [ StyleDoc
"Set"
            , Style -> StyleDoc -> StyleDoc
style Style
Shell (String -> StyleDoc
flow String
"allow-newer: true")
            , StyleDoc
"in"
            , forall a. Pretty a => a -> StyleDoc
pretty (Path Abs Dir -> Path Abs File
defaultUserConfigPath Path Abs Dir
stackRoot)
            , String -> StyleDoc
flow String
"to ignore all version constraints and build anyway."
            ])
        , StyleDoc
blankLine
        ]
    forall a. [a] -> [a] -> [a]
++ [StyleDoc]
addExtraDepsRecommendations

  addExtraDepsRecommendations :: [StyleDoc]
addExtraDepsRecommendations
    | forall k a. Map k a -> Bool
Map.null Map PackageName (Version, BlobKey)
extras = []
    | (Just (Version, BlobKey)
_) <- forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup (String -> PackageName
mkPackageName String
"base") Map PackageName (Version, BlobKey)
extras =
        [ StyleDoc
"  *" StyleDoc -> StyleDoc -> StyleDoc
<+> StyleDoc -> StyleDoc
align ([StyleDoc] -> StyleDoc
fillSep
            [ String -> StyleDoc
flow String
"Build requires unattainable version of the"
            , Style -> StyleDoc -> StyleDoc
style Style
Current StyleDoc
"base"
            , String -> StyleDoc
flow String
"package. Since"
            , Style -> StyleDoc -> StyleDoc
style Style
Current StyleDoc
"base"
            , String -> StyleDoc
flow String
"is a part of GHC, you most likely need to use a \
                   \different GHC version with the matching"
            , Style -> StyleDoc -> StyleDoc
style Style
Current StyleDoc
"base"forall a. Semigroup a => a -> a -> a
<> StyleDoc
"."
            ])
         , StyleDoc
line
        ]
    | Bool
otherwise =
       [ StyleDoc
"  *" StyleDoc -> StyleDoc -> StyleDoc
<+> StyleDoc -> StyleDoc
align ([StyleDoc] -> StyleDoc
fillSep
         [ Style -> StyleDoc -> StyleDoc
style Style
Recommendation (String -> StyleDoc
flow String
"Recommended action:")
         , String -> StyleDoc
flow String
"try adding the following to your"
         , Style -> StyleDoc -> StyleDoc
style Style
Shell StyleDoc
"extra-deps"
         , StyleDoc
"in"
         , forall a. Pretty a => a -> StyleDoc
pretty Path Abs File
stackYaml forall a. Semigroup a => a -> a -> a
<> StyleDoc
":"
         ])
       , StyleDoc
blankLine
       , [StyleDoc] -> StyleDoc
vsep (forall a b. (a -> b) -> [a] -> [b]
map forall {a}. IsString a => (PackageName, (Version, BlobKey)) -> a
pprintExtra (forall k a. Map k a -> [(k, a)]
Map.toList Map PackageName (Version, BlobKey)
extras))
       , StyleDoc
line
       ]

  extras :: Map PackageName (Version, BlobKey)
extras = forall (f :: * -> *) k a.
(Foldable f, Ord k) =>
f (Map k a) -> Map k a
Map.unions forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map ConstructPlanException -> Map PackageName (Version, BlobKey)
getExtras [ConstructPlanException]
exceptions'
  getExtras :: ConstructPlanException -> Map PackageName (Version, BlobKey)
getExtras DependencyCycleDetected{} = forall k a. Map k a
Map.empty
  getExtras UnknownPackage{} = forall k a. Map k a
Map.empty
  getExtras (DependencyPlanFailures Package
_ Map
  PackageName (VersionRange, Maybe (Version, BlobKey), BadDependency)
m) =
    forall (f :: * -> *) k a.
(Foldable f, Ord k) =>
f (Map k a) -> Map k a
Map.unions forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map forall {k} {a} {a} {b}.
(k, (a, Maybe (a, b), BadDependency)) -> Map k (a, b)
go forall a b. (a -> b) -> a -> b
$ forall k a. Map k a -> [(k, a)]
Map.toList Map
  PackageName (VersionRange, Maybe (Version, BlobKey), BadDependency)
m
   where
    -- TODO: Likely a good idea to distinguish these to the user.  In

    -- particular, for DependencyMismatch

    go :: (k, (a, Maybe (a, b), BadDependency)) -> Map k (a, b)
go (k
name, (a
_range, Just (a
version,b
cabalHash), BadDependency
NotInBuildPlan)) =
      forall k a. k -> a -> Map k a
Map.singleton k
name (a
version,b
cabalHash)
    go (k
name, (a
_range, Just (a
version,b
cabalHash), DependencyMismatch{})) =
      forall k a. k -> a -> Map k a
Map.singleton k
name (a
version, b
cabalHash)
    go (k, (a, Maybe (a, b), BadDependency))
_ = forall k a. Map k a
Map.empty
  pprintExtra :: (PackageName, (Version, BlobKey)) -> a
pprintExtra (PackageName
name, (Version
version, BlobKey SHA256
cabalHash FileSize
cabalSize)) =
    let cfInfo :: CabalFileInfo
cfInfo = SHA256 -> Maybe FileSize -> CabalFileInfo
CFIHash SHA256
cabalHash (forall a. a -> Maybe a
Just FileSize
cabalSize)
        packageIdRev :: PackageIdentifierRevision
packageIdRev = PackageName
-> Version -> CabalFileInfo -> PackageIdentifierRevision
PackageIdentifierRevision PackageName
name Version
version CabalFileInfo
cfInfo
    in  forall a. IsString a => String -> a
fromString (String
"- " forall a. [a] -> [a] -> [a]
++ Text -> String
T.unpack (Utf8Builder -> Text
utf8BuilderToText (forall a. Display a => a -> Utf8Builder
display PackageIdentifierRevision
packageIdRev)))

  allNotInBuildPlan :: Set PackageName
allNotInBuildPlan = forall a. Ord a => [a] -> Set a
Set.fromList forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap ConstructPlanException -> [PackageName]
toNotInBuildPlan [ConstructPlanException]
exceptions'
  toNotInBuildPlan :: ConstructPlanException -> [PackageName]
toNotInBuildPlan (DependencyPlanFailures Package
_ Map
  PackageName (VersionRange, Maybe (Version, BlobKey), BadDependency)
pDeps) =
    forall a b. (a -> b) -> [a] -> [b]
map forall a b. (a, b) -> a
fst forall a b. (a -> b) -> a -> b
$
      forall a. (a -> Bool) -> [a] -> [a]
filter
        (\(PackageName
_, (VersionRange
_, Maybe (Version, BlobKey)
_, BadDependency
badDep)) -> BadDependency
badDep forall a. Eq a => a -> a -> Bool
== BadDependency
NotInBuildPlan)
        (forall k a. Map k a -> [(k, a)]
Map.toList Map
  PackageName (VersionRange, Maybe (Version, BlobKey), BadDependency)
pDeps)
  toNotInBuildPlan ConstructPlanException
_ = []

  -- This checks if 'allow-newer: true' could resolve all issues.

  onlyHasDependencyMismatches :: Bool
onlyHasDependencyMismatches = forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all ConstructPlanException -> Bool
go [ConstructPlanException]
exceptions'
   where
    go :: ConstructPlanException -> Bool
go DependencyCycleDetected{} = Bool
False
    go UnknownPackage{} = Bool
False
    go (DependencyPlanFailures Package
_ Map
  PackageName (VersionRange, Maybe (Version, BlobKey), BadDependency)
m) =
      forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (\(VersionRange
_, Maybe (Version, BlobKey)
_, BadDependency
depErr) -> BadDependency -> Bool
isMismatch BadDependency
depErr) (forall k a. Map k a -> [a]
M.elems Map
  PackageName (VersionRange, Maybe (Version, BlobKey), BadDependency)
m)
    isMismatch :: BadDependency -> Bool
isMismatch DependencyMismatch{} = Bool
True
    isMismatch Couldn'tResolveItsDependencies{} = Bool
True
    isMismatch BadDependency
_ = Bool
False

  pprintException :: ConstructPlanException -> Maybe StyleDoc
pprintException (DependencyCycleDetected [PackageName]
pNames) = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$
       String -> StyleDoc
flow String
"Dependency cycle detected in packages:"
    forall a. Semigroup a => a -> a -> a
<> StyleDoc
line
    forall a. Semigroup a => a -> a -> a
<> Int -> StyleDoc -> StyleDoc
indent Int
4
         ( StyleDoc -> StyleDoc -> StyleDoc -> [StyleDoc] -> StyleDoc
encloseSep StyleDoc
"[" StyleDoc
"]" StyleDoc
","
             (forall a b. (a -> b) -> [a] -> [b]
map (Style -> StyleDoc -> StyleDoc
style Style
Error forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. IsString a => String -> a
fromString forall b c a. (b -> c) -> (a -> b) -> a -> c
. PackageName -> String
packageNameString) [PackageName]
pNames)
         )
  pprintException (DependencyPlanFailures Package
pkg Map
  PackageName (VersionRange, Maybe (Version, BlobKey), BadDependency)
pDeps) =
    case forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe forall {b}.
(PackageName, (VersionRange, Maybe (Version, b), BadDependency))
-> Maybe StyleDoc
pprintDep (forall k a. Map k a -> [(k, a)]
Map.toList Map
  PackageName (VersionRange, Maybe (Version, BlobKey), BadDependency)
pDeps) of
      [] -> forall a. Maybe a
Nothing
      [StyleDoc]
depErrors -> forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$
        String -> StyleDoc
flow String
"In the dependencies for" StyleDoc -> StyleDoc -> StyleDoc
<+> StyleDoc
pkgIdent forall a. Semigroup a => a -> a -> a
<>
        Map FlagName Bool -> StyleDoc
pprintFlags (Package -> Map FlagName Bool
packageFlags Package
pkg) forall a. Semigroup a => a -> a -> a
<> StyleDoc
":" forall a. Semigroup a => a -> a -> a
<> StyleDoc
line forall a. Semigroup a => a -> a -> a
<>
        Int -> StyleDoc -> StyleDoc
indent Int
4 ([StyleDoc] -> StyleDoc
vsep [StyleDoc]
depErrors) forall a. Semigroup a => a -> a -> a
<>
        case ParentMap
-> Set PackageName -> PackageName -> Maybe [PackageIdentifier]
getShortestDepsPath ParentMap
parentMap Set PackageName
wanted' (Package -> PackageName
packageName Package
pkg) of
          Maybe [PackageIdentifier]
Nothing ->
               StyleDoc
line
            forall a. Semigroup a => a -> a -> a
<> String -> StyleDoc
flow String
"needed for unknown reason - stack invariant violated."
          Just [] ->
               StyleDoc
line
            forall a. Semigroup a => a -> a -> a
<> [StyleDoc] -> StyleDoc
fillSep
                 [ String -> StyleDoc
flow String
"needed since"
                 , StyleDoc
pkgName'
                 , String -> StyleDoc
flow String
"is a build target."
                 ]
          Just (PackageIdentifier
target:[PackageIdentifier]
path) ->
               StyleDoc
line
            forall a. Semigroup a => a -> a -> a
<> String -> StyleDoc
flow String
"needed due to" StyleDoc -> StyleDoc -> StyleDoc
<+> StyleDoc -> StyleDoc -> StyleDoc -> [StyleDoc] -> StyleDoc
encloseSep StyleDoc
"" StyleDoc
"" StyleDoc
" -> " [StyleDoc]
pathElems
           where
            pathElems :: [StyleDoc]
pathElems =
              [Style -> StyleDoc -> StyleDoc
style Style
Target forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. IsString a => String -> a
fromString forall b c a. (b -> c) -> (a -> b) -> a -> c
. PackageIdentifier -> String
packageIdentifierString forall a b. (a -> b) -> a -> b
$ PackageIdentifier
target] forall a. [a] -> [a] -> [a]
++
              forall a b. (a -> b) -> [a] -> [b]
map (forall a. IsString a => String -> a
fromString forall b c a. (b -> c) -> (a -> b) -> a -> c
. PackageIdentifier -> String
packageIdentifierString) [PackageIdentifier]
path forall a. [a] -> [a] -> [a]
++
              [StyleDoc
pkgIdent]
       where
        pkgName' :: StyleDoc
pkgName' =
          Style -> StyleDoc -> StyleDoc
style Style
Current forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. IsString a => String -> a
fromString forall b c a. (b -> c) -> (a -> b) -> a -> c
. PackageName -> String
packageNameString forall a b. (a -> b) -> a -> b
$ Package -> PackageName
packageName Package
pkg
        pkgIdent :: StyleDoc
pkgIdent =
          Style -> StyleDoc -> StyleDoc
style
            Style
Current
            (forall a. IsString a => String -> a
fromString forall b c a. (b -> c) -> (a -> b) -> a -> c
. PackageIdentifier -> String
packageIdentifierString forall a b. (a -> b) -> a -> b
$ Package -> PackageIdentifier
packageIdentifier Package
pkg)
  -- Skip these when they are redundant with 'NotInBuildPlan' info.

  pprintException (UnknownPackage PackageName
name)
    | PackageName
name forall a. Ord a => a -> Set a -> Bool
`Set.member` Set PackageName
allNotInBuildPlan = forall a. Maybe a
Nothing
    | PackageName
name forall a. Ord a => a -> Set a -> Bool
`Set.member` Set PackageName
wiredInPackages = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ [StyleDoc] -> StyleDoc
fillSep
        [ String -> StyleDoc
flow String
"Can't build a package with same name as a wired-in-package:"
        , Style -> StyleDoc -> StyleDoc
style Style
Current forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. IsString a => String -> a
fromString forall b c a. (b -> c) -> (a -> b) -> a -> c
. PackageName -> String
packageNameString forall a b. (a -> b) -> a -> b
$ PackageName
name
        ]
    | Just [PackageName]
pruned <- forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup PackageName
name Map PackageName [PackageName]
prunedGlobalDeps =
        let prunedDeps :: [StyleDoc]
prunedDeps =
              forall a b. (a -> b) -> [a] -> [b]
map (Style -> StyleDoc -> StyleDoc
style Style
Current forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. IsString a => String -> a
fromString forall b c a. (b -> c) -> (a -> b) -> a -> c
. PackageName -> String
packageNameString) [PackageName]
pruned
        in  forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ [StyleDoc] -> StyleDoc
fillSep
              [ String -> StyleDoc
flow String
"Can't use GHC boot package"
              , Style -> StyleDoc -> StyleDoc
style Style
Current forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. IsString a => String -> a
fromString forall b c a. (b -> c) -> (a -> b) -> a -> c
. PackageName -> String
packageNameString forall a b. (a -> b) -> a -> b
$ PackageName
name
              , String -> StyleDoc
flow String
"when it has an overridden dependency (issue #4510);"
              , String -> StyleDoc
flow String
"you need to add the following as explicit dependencies \
                     \to the project:"
              , StyleDoc
line
              , StyleDoc -> StyleDoc -> StyleDoc -> [StyleDoc] -> StyleDoc
encloseSep StyleDoc
"" StyleDoc
"" StyleDoc
", " [StyleDoc]
prunedDeps
              ]
    | Bool
otherwise = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ [StyleDoc] -> StyleDoc
fillSep
        [ String -> StyleDoc
flow String
"Unknown package:"
        , Style -> StyleDoc -> StyleDoc
style Style
Current forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. IsString a => String -> a
fromString forall b c a. (b -> c) -> (a -> b) -> a -> c
. PackageName -> String
packageNameString forall a b. (a -> b) -> a -> b
$ PackageName
name
        ]

  pprintFlags :: Map FlagName Bool -> StyleDoc
pprintFlags Map FlagName Bool
flags
    | forall k a. Map k a -> Bool
Map.null Map FlagName Bool
flags = StyleDoc
""
    | Bool
otherwise = StyleDoc -> StyleDoc
parens forall a b. (a -> b) -> a -> b
$ [StyleDoc] -> StyleDoc
sep forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map forall {a}. (Semigroup a, IsString a) => (FlagName, Bool) -> a
pprintFlag forall a b. (a -> b) -> a -> b
$ forall k a. Map k a -> [(k, a)]
Map.toList Map FlagName Bool
flags
  pprintFlag :: (FlagName, Bool) -> a
pprintFlag (FlagName
name, Bool
True) = a
"+" forall a. Semigroup a => a -> a -> a
<> forall a. IsString a => String -> a
fromString (FlagName -> String
flagNameString FlagName
name)
  pprintFlag (FlagName
name, Bool
False) = a
"-" forall a. Semigroup a => a -> a -> a
<> forall a. IsString a => String -> a
fromString (FlagName -> String
flagNameString FlagName
name)

  pprintDep :: (PackageName, (VersionRange, Maybe (Version, b), BadDependency))
-> Maybe StyleDoc
pprintDep (PackageName
name, (VersionRange
range, Maybe (Version, b)
mlatestApplicable, BadDependency
badDep)) = case BadDependency
badDep of
    BadDependency
NotInBuildPlan
      | PackageName
name forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` forall (t :: * -> *) m. (Foldable t, Monoid m) => t m -> m
fold Map PackageName [PackageName]
prunedGlobalDeps -> forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$
          Style -> StyleDoc -> StyleDoc
style Style
Error (forall a. IsString a => String -> a
fromString forall a b. (a -> b) -> a -> b
$ PackageName -> String
packageNameString PackageName
name) StyleDoc -> StyleDoc -> StyleDoc
<+>
          StyleDoc -> StyleDoc
align
            (  ( if VersionRange
range forall a. Eq a => a -> a -> Bool
== VersionRange
C.anyVersion
                   then String -> StyleDoc
flow String
"needed"
                   else String -> StyleDoc
flow String
"must match" StyleDoc -> StyleDoc -> StyleDoc
<+> StyleDoc
goodRange
               )
            forall a. Semigroup a => a -> a -> a
<> StyleDoc
","
            forall a. Semigroup a => a -> a -> a
<> StyleDoc
softline
            forall a. Semigroup a => a -> a -> a
<> [StyleDoc] -> StyleDoc
fillSep
                 [ String -> StyleDoc
flow String
"but this GHC boot package has been pruned (issue \
                        \#4510); you need to add the package explicitly to \
                        \extra-deps"
                 ,Maybe Version -> StyleDoc
latestApplicable forall a. Maybe a
Nothing
                 ]
            )
      | Bool
otherwise -> forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$
          Style -> StyleDoc -> StyleDoc
style Style
Error (forall a. IsString a => String -> a
fromString forall a b. (a -> b) -> a -> b
$ PackageName -> String
packageNameString PackageName
name) StyleDoc -> StyleDoc -> StyleDoc
<+>
          StyleDoc -> StyleDoc
align
            (  ( if VersionRange
range forall a. Eq a => a -> a -> Bool
== VersionRange
C.anyVersion
                   then String -> StyleDoc
flow String
"needed"
                   else String -> StyleDoc
flow String
"must match" StyleDoc -> StyleDoc -> StyleDoc
<+> StyleDoc
goodRange
               )
            forall a. Semigroup a => a -> a -> a
<> StyleDoc
","
            forall a. Semigroup a => a -> a -> a
<> StyleDoc
softline
            forall a. Semigroup a => a -> a -> a
<> [StyleDoc] -> StyleDoc
fillSep
                 [ String -> StyleDoc
flow String
"but the Stack configuration has no specified version"
                 , Maybe Version -> StyleDoc
latestApplicable forall a. Maybe a
Nothing
                 ]
            )
    -- TODO: For local packages, suggest editing constraints

    DependencyMismatch Version
version -> forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$
      Style -> StyleDoc -> StyleDoc
style
         Style
Error
         (forall a. IsString a => String -> a
fromString forall b c a. (b -> c) -> (a -> b) -> a -> c
. PackageIdentifier -> String
packageIdentifierString forall a b. (a -> b) -> a -> b
$ PackageName -> Version -> PackageIdentifier
PackageIdentifier PackageName
name Version
version)
      StyleDoc -> StyleDoc -> StyleDoc
<+>
      StyleDoc -> StyleDoc
align
        ( [StyleDoc] -> StyleDoc
fillSep
            [ String -> StyleDoc
flow String
"from Stack configuration does not match"
            , StyleDoc
goodRange
            , Maybe Version -> StyleDoc
latestApplicable (forall a. a -> Maybe a
Just Version
version)
            ]
        )
    -- I think the main useful info is these explain why missing packages are

    -- needed. Instead lets give the user the shortest path from a target to the

    -- package.

    Couldn'tResolveItsDependencies Version
_version -> forall a. Maybe a
Nothing
    BadDependency
HasNoLibrary -> forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$
      Style -> StyleDoc -> StyleDoc
style Style
Error (forall a. IsString a => String -> a
fromString forall a b. (a -> b) -> a -> b
$ PackageName -> String
packageNameString PackageName
name) StyleDoc -> StyleDoc -> StyleDoc
<+>
      StyleDoc -> StyleDoc
align (String -> StyleDoc
flow String
"is a library dependency, but the package provides no library")
    BDDependencyCycleDetected [PackageName]
names -> forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$
      Style -> StyleDoc -> StyleDoc
style Style
Error (forall a. IsString a => String -> a
fromString forall a b. (a -> b) -> a -> b
$ PackageName -> String
packageNameString PackageName
name) StyleDoc -> StyleDoc -> StyleDoc
<+>
      StyleDoc -> StyleDoc
align
        ( String -> StyleDoc
flow forall a b. (a -> b) -> a -> b
$ String
"dependency cycle detected: "
             forall a. [a] -> [a] -> [a]
++ forall a. [a] -> [[a]] -> [a]
L.intercalate String
", " (forall a b. (a -> b) -> [a] -> [b]
map PackageName -> String
packageNameString [PackageName]
names)
        )
   where
    goodRange :: StyleDoc
goodRange = Style -> StyleDoc -> StyleDoc
style Style
Good (forall a. IsString a => String -> a
fromString (forall a. Pretty a => a -> String
C.display VersionRange
range))
    latestApplicable :: Maybe Version -> StyleDoc
latestApplicable Maybe Version
mversion =
      case Maybe (Version, b)
mlatestApplicable of
        Maybe (Version, b)
Nothing
          | forall a. Maybe a -> Bool
isNothing Maybe Version
mversion ->
              String -> StyleDoc
flow String
"(no package with that name found, perhaps there is a typo \
                   \in a package's build-depends or an omission from the \
                   \stack.yaml packages list?)"
          | Bool
otherwise -> StyleDoc
""
        Just (Version
laVer, b
_)
          | forall a. a -> Maybe a
Just Version
laVer forall a. Eq a => a -> a -> Bool
== Maybe Version
mversion ->
              String -> StyleDoc
flow String
"(latest matching version is specified)"
          | Bool
otherwise ->
              [StyleDoc] -> StyleDoc
fillSep
                [ String -> StyleDoc
flow String
"(latest matching version is"
                , Style -> StyleDoc -> StyleDoc
style Style
Good (forall a. IsString a => String -> a
fromString forall a b. (a -> b) -> a -> b
$ Version -> String
versionString Version
laVer) forall a. Semigroup a => a -> a -> a
<> StyleDoc
")"
                ]

data ConstructPlanException
  = DependencyCycleDetected [PackageName]
  | DependencyPlanFailures
      Package
      (Map PackageName (VersionRange, LatestApplicableVersion, BadDependency))
  | UnknownPackage PackageName -- TODO perhaps this constructor will be removed,

                               -- and BadDependency will handle it all

  -- ^ Recommend adding to extra-deps, give a helpful version number?

  deriving (ConstructPlanException -> ConstructPlanException -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ConstructPlanException -> ConstructPlanException -> Bool
$c/= :: ConstructPlanException -> ConstructPlanException -> Bool
== :: ConstructPlanException -> ConstructPlanException -> Bool
$c== :: ConstructPlanException -> ConstructPlanException -> Bool
Eq, Int -> ConstructPlanException -> ShowS
[ConstructPlanException] -> ShowS
ConstructPlanException -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ConstructPlanException] -> ShowS
$cshowList :: [ConstructPlanException] -> ShowS
show :: ConstructPlanException -> String
$cshow :: ConstructPlanException -> String
showsPrec :: Int -> ConstructPlanException -> ShowS
$cshowsPrec :: Int -> ConstructPlanException -> ShowS
Show, Typeable)

-- | The latest applicable version and it's latest Cabal file revision.

-- For display purposes only, Nothing if package not found

type LatestApplicableVersion = Maybe (Version, BlobKey)

-- | Reason why a dependency was not used

data BadDependency
  = NotInBuildPlan
  | Couldn'tResolveItsDependencies Version
  | DependencyMismatch Version
  | HasNoLibrary
  -- ^ See description of 'DepType'

  | BDDependencyCycleDetected ![PackageName]
  deriving (BadDependency -> BadDependency -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BadDependency -> BadDependency -> Bool
$c/= :: BadDependency -> BadDependency -> Bool
== :: BadDependency -> BadDependency -> Bool
$c== :: BadDependency -> BadDependency -> Bool
Eq, Eq BadDependency
BadDependency -> BadDependency -> Bool
BadDependency -> BadDependency -> Ordering
BadDependency -> BadDependency -> BadDependency
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: BadDependency -> BadDependency -> BadDependency
$cmin :: BadDependency -> BadDependency -> BadDependency
max :: BadDependency -> BadDependency -> BadDependency
$cmax :: BadDependency -> BadDependency -> BadDependency
>= :: BadDependency -> BadDependency -> Bool
$c>= :: BadDependency -> BadDependency -> Bool
> :: BadDependency -> BadDependency -> Bool
$c> :: BadDependency -> BadDependency -> Bool
<= :: BadDependency -> BadDependency -> Bool
$c<= :: BadDependency -> BadDependency -> Bool
< :: BadDependency -> BadDependency -> Bool
$c< :: BadDependency -> BadDependency -> Bool
compare :: BadDependency -> BadDependency -> Ordering
$ccompare :: BadDependency -> BadDependency -> Ordering
Ord, Int -> BadDependency -> ShowS
[BadDependency] -> ShowS
BadDependency -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BadDependency] -> ShowS
$cshowList :: [BadDependency] -> ShowS
show :: BadDependency -> String
$cshow :: BadDependency -> String
showsPrec :: Int -> BadDependency -> ShowS
$cshowsPrec :: Int -> BadDependency -> ShowS
Show, Typeable)

missingExeError :: String -> Bool -> String -> String
missingExeError :: String -> Bool -> ShowS
missingExeError String
errorCode Bool
isSimpleBuildType String
msg = [String] -> String
unlines
  forall a b. (a -> b) -> a -> b
$ String
"Error: " forall a. Semigroup a => a -> a -> a
<> String
errorCode
  forall a. a -> [a] -> [a]
: String
msg
  forall a. a -> [a] -> [a]
: String
"Possible causes of this issue:"
  forall a. a -> [a] -> [a]
: forall a b. (a -> b) -> [a] -> [b]
map (String
"* " <>) [String]
possibleCauses
 where
  possibleCauses :: [String]
possibleCauses
    = String
"No module named \"Main\". The 'main-is' source file should usually \
      \have a header indicating that it's a 'Main' module."
    forall a. a -> [a] -> [a]
: String
"A Cabal file that refers to nonexistent other files (e.g. a \
      \license-file that doesn't exist). Running 'cabal check' may point \
      \out these issues."
    forall a. a -> [a] -> [a]
: [ String
"The Setup.hs file is changing the installation target dir."
      | Bool -> Bool
not Bool
isSimpleBuildType
      ]

showBuildError ::
     String
  -> Bool
  -> ExitCode
  -> Maybe PackageIdentifier
  -> Path Abs File
  -> [String]
  -> Maybe (Path Abs File)
  -> [Text]
  -> StyleDoc
showBuildError :: String
-> Bool
-> ExitCode
-> Maybe PackageIdentifier
-> Path Abs File
-> [String]
-> Maybe (Path Abs File)
-> [Text]
-> StyleDoc
showBuildError String
errorCode Bool
isBuildingSetup ExitCode
exitCode Maybe PackageIdentifier
mtaskProvides Path Abs File
execName [String]
fullArgs Maybe (Path Abs File)
logFiles [Text]
bss =
  let fullCmd :: String
fullCmd = [String] -> String
unwords
        forall a b. (a -> b) -> a -> b
$ ShowS
dropQuotes (forall b t. Path b t -> String
toFilePath Path Abs File
execName)
        forall a. a -> [a] -> [a]
: forall a b. (a -> b) -> [a] -> [b]
map (Text -> String
T.unpack forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
showProcessArgDebug) [String]
fullArgs
      logLocations :: StyleDoc
logLocations =
        forall b a. b -> (a -> b) -> Maybe a -> b
maybe
          forall a. Monoid a => a
mempty
          (\Path Abs File
fp -> StyleDoc
line forall a. Semigroup a => a -> a -> a
<> String -> StyleDoc
flow String
"Logs have been written to:" StyleDoc -> StyleDoc -> StyleDoc
<+>
                    forall a. Pretty a => a -> StyleDoc
pretty Path Abs File
fp)
          Maybe (Path Abs File)
logFiles
  in     forall a. IsString a => String -> a
fromString String
errorCode
      forall a. Semigroup a => a -> a -> a
<> StyleDoc
line
      forall a. Semigroup a => a -> a -> a
<> String -> StyleDoc
flow String
"While building" StyleDoc -> StyleDoc -> StyleDoc
<+>
         ( case (Bool
isBuildingSetup, Maybe PackageIdentifier
mtaskProvides) of
             (Bool
False, Maybe PackageIdentifier
Nothing) -> forall e a. Exception e => e -> a
impureThrow BuildException
ShowBuildErrorBug
             (Bool
False, Just PackageIdentifier
taskProvides') ->
                StyleDoc
"package" StyleDoc -> StyleDoc -> StyleDoc
<+>
                  Style -> StyleDoc -> StyleDoc
style
                    Style
Target
                    (forall a. IsString a => String -> a
fromString forall a b. (a -> b) -> a -> b
$ ShowS
dropQuotes (PackageIdentifier -> String
packageIdentifierString PackageIdentifier
taskProvides'))
             (Bool
True, Maybe PackageIdentifier
Nothing) -> StyleDoc
"simple" StyleDoc -> StyleDoc -> StyleDoc
<+> Style -> StyleDoc -> StyleDoc
style Style
File StyleDoc
"Setup.hs"
             (Bool
True, Just PackageIdentifier
taskProvides') ->
                StyleDoc
"custom" StyleDoc -> StyleDoc -> StyleDoc
<+>
                  Style -> StyleDoc -> StyleDoc
style Style
File StyleDoc
"Setup.hs" StyleDoc -> StyleDoc -> StyleDoc
<+>
                  String -> StyleDoc
flow String
"for package" StyleDoc -> StyleDoc -> StyleDoc
<+>
                  Style -> StyleDoc -> StyleDoc
style
                    Style
Target
                    (forall a. IsString a => String -> a
fromString forall a b. (a -> b) -> a -> b
$ ShowS
dropQuotes (PackageIdentifier -> String
packageIdentifierString PackageIdentifier
taskProvides'))
         ) StyleDoc -> StyleDoc -> StyleDoc
<+>
         String -> StyleDoc
flow String
"(scroll up to its section to see the error) using:"
      forall a. Semigroup a => a -> a -> a
<> StyleDoc
line
      forall a. Semigroup a => a -> a -> a
<> Style -> StyleDoc -> StyleDoc
style Style
Shell (forall a. IsString a => String -> a
fromString String
fullCmd)
      forall a. Semigroup a => a -> a -> a
<> StyleDoc
line
      forall a. Semigroup a => a -> a -> a
<> String -> StyleDoc
flow String
"Process exited with code:" StyleDoc -> StyleDoc -> StyleDoc
<+> (forall a. IsString a => String -> a
fromString forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show) ExitCode
exitCode StyleDoc -> StyleDoc -> StyleDoc
<+>
         ( if ExitCode
exitCode forall a. Eq a => a -> a -> Bool
== Int -> ExitCode
ExitFailure (-Int
9)
             then String -> StyleDoc
flow String
"(THIS MAY INDICATE OUT OF MEMORY)"
             else forall a. Monoid a => a
mempty
         )
      forall a. Semigroup a => a -> a -> a
<> StyleDoc
logLocations
      forall a. Semigroup a => a -> a -> a
<> if forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Text]
bss
           then forall a. Monoid a => a
mempty
           else StyleDoc
blankLine forall a. Semigroup a => a -> a -> a
<> String -> StyleDoc
string ([String] -> String
removeTrailingSpaces (forall a b. (a -> b) -> [a] -> [b]
map Text -> String
T.unpack [Text]
bss))
   where
    removeTrailingSpaces :: [String] -> String
removeTrailingSpaces = forall a. (a -> Bool) -> [a] -> [a]
dropWhileEnd Char -> Bool
isSpace forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> String
unlines
    dropQuotes :: ShowS
dropQuotes = forall a. (a -> Bool) -> [a] -> [a]
filter (Char
'\"' /=)

-- | Get the shortest reason for the package to be in the build plan. In

-- other words, trace the parent dependencies back to a 'wanted'

-- package.

getShortestDepsPath ::
     ParentMap
  -> Set PackageName
  -> PackageName
  -> Maybe [PackageIdentifier]
getShortestDepsPath :: ParentMap
-> Set PackageName -> PackageName -> Maybe [PackageIdentifier]
getShortestDepsPath (MonoidMap Map
  PackageName (First Version, [(PackageIdentifier, VersionRange)])
parentsMap) Set PackageName
wanted' PackageName
name =
  if forall a. Ord a => a -> Set a -> Bool
Set.member PackageName
name Set PackageName
wanted'
    then forall a. a -> Maybe a
Just []
    else case forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup PackageName
name Map
  PackageName (First Version, [(PackageIdentifier, VersionRange)])
parentsMap of
      Maybe (First Version, [(PackageIdentifier, VersionRange)])
Nothing -> forall a. Maybe a
Nothing
      Just (First Version
_, [(PackageIdentifier, VersionRange)]
parents) -> forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ Int -> Map PackageName DepsPath -> [PackageIdentifier]
findShortest Int
256 Map PackageName DepsPath
paths0
       where
        paths0 :: Map PackageName DepsPath
paths0 = forall k a. Ord k => [(k, a)] -> Map k a
M.fromList forall a b. (a -> b) -> a -> b
$
          forall a b. (a -> b) -> [a] -> [b]
map (\(PackageIdentifier
ident, VersionRange
_) -> (PackageIdentifier -> PackageName
pkgName PackageIdentifier
ident, PackageIdentifier -> DepsPath
startDepsPath PackageIdentifier
ident)) [(PackageIdentifier, VersionRange)]
parents
 where
  -- The 'paths' map is a map from PackageName to the shortest path

  -- found to get there. It is the frontier of our breadth-first

  -- search of dependencies.

  findShortest :: Int -> Map PackageName DepsPath -> [PackageIdentifier]
  findShortest :: Int -> Map PackageName DepsPath -> [PackageIdentifier]
findShortest Int
fuel Map PackageName DepsPath
_ | Int
fuel forall a. Ord a => a -> a -> Bool
<= Int
0 =
    [ PackageName -> Version -> PackageIdentifier
PackageIdentifier
        (String -> PackageName
mkPackageName String
"stack-ran-out-of-jet-fuel")
        ([Int] -> Version
C.mkVersion [Int
0])
    ]
  findShortest Int
_ Map PackageName DepsPath
paths | forall k a. Map k a -> Bool
M.null Map PackageName DepsPath
paths = []
  findShortest Int
fuel Map PackageName DepsPath
paths =
    case [(PackageName, DepsPath)]
targets of
      [] -> Int -> Map PackageName DepsPath -> [PackageIdentifier]
findShortest (Int
fuel forall a. Num a => a -> a -> a
- Int
1) forall a b. (a -> b) -> a -> b
$ forall k a. Ord k => (a -> a -> a) -> [(k, a)] -> Map k a
M.fromListWith DepsPath -> DepsPath -> DepsPath
chooseBest forall a b. (a -> b) -> a -> b
$
              forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (PackageName, DepsPath) -> [(PackageName, DepsPath)]
extendPath [(PackageName, DepsPath)]
recurses
      [(PackageName, DepsPath)]
_ -> let (DepsPath Int
_ Int
_ [PackageIdentifier]
path) = forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
L.minimum (forall a b. (a -> b) -> [a] -> [b]
map forall a b. (a, b) -> b
snd [(PackageName, DepsPath)]
targets) in [PackageIdentifier]
path
   where
    ([(PackageName, DepsPath)]
targets, [(PackageName, DepsPath)]
recurses) =
      forall a. (a -> Bool) -> [a] -> ([a], [a])
L.partition (\(PackageName
n, DepsPath
_) -> PackageName
n forall a. Ord a => a -> Set a -> Bool
`Set.member` Set PackageName
wanted') (forall k a. Map k a -> [(k, a)]
M.toList Map PackageName DepsPath
paths)
  chooseBest :: DepsPath -> DepsPath -> DepsPath
  chooseBest :: DepsPath -> DepsPath -> DepsPath
chooseBest = forall a. Ord a => a -> a -> a
max
  -- Extend a path to all its parents.

  extendPath :: (PackageName, DepsPath) -> [(PackageName, DepsPath)]
  extendPath :: (PackageName, DepsPath) -> [(PackageName, DepsPath)]
extendPath (PackageName
n, DepsPath
dp) =
    case forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup PackageName
n Map
  PackageName (First Version, [(PackageIdentifier, VersionRange)])
parentsMap of
      Maybe (First Version, [(PackageIdentifier, VersionRange)])
Nothing -> []
      Just (First Version
_, [(PackageIdentifier, VersionRange)]
parents) ->
        forall a b. (a -> b) -> [a] -> [b]
map (\(PackageIdentifier
pkgId, VersionRange
_) -> (PackageIdentifier -> PackageName
pkgName PackageIdentifier
pkgId, PackageIdentifier -> DepsPath -> DepsPath
extendDepsPath PackageIdentifier
pkgId DepsPath
dp)) [(PackageIdentifier, VersionRange)]
parents

startDepsPath :: PackageIdentifier -> DepsPath
startDepsPath :: PackageIdentifier -> DepsPath
startDepsPath PackageIdentifier
ident = DepsPath
  { dpLength :: Int
dpLength = Int
1
  , dpNameLength :: Int
dpNameLength = forall (t :: * -> *) a. Foldable t => t a -> Int
length (PackageName -> String
packageNameString (PackageIdentifier -> PackageName
pkgName PackageIdentifier
ident))
  , dpPath :: [PackageIdentifier]
dpPath = [PackageIdentifier
ident]
  }

extendDepsPath :: PackageIdentifier -> DepsPath -> DepsPath
extendDepsPath :: PackageIdentifier -> DepsPath -> DepsPath
extendDepsPath PackageIdentifier
ident DepsPath
dp = DepsPath
  { dpLength :: Int
dpLength = DepsPath -> Int
dpLength DepsPath
dp forall a. Num a => a -> a -> a
+ Int
1
  , dpNameLength :: Int
dpNameLength = DepsPath -> Int
dpNameLength DepsPath
dp forall a. Num a => a -> a -> a
+ forall (t :: * -> *) a. Foldable t => t a -> Int
length (PackageName -> String
packageNameString (PackageIdentifier -> PackageName
pkgName PackageIdentifier
ident))
  , dpPath :: [PackageIdentifier]
dpPath = [PackageIdentifier
ident]
  }

data DepsPath = DepsPath
  { DepsPath -> Int
dpLength :: Int
    -- ^ Length of dpPath

  , DepsPath -> Int
dpNameLength :: Int
    -- ^ Length of package names combined

  , DepsPath -> [PackageIdentifier]
dpPath :: [PackageIdentifier]
    -- ^ A path where the packages later in the list depend on those that come

    -- earlier

  }
  deriving (DepsPath -> DepsPath -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DepsPath -> DepsPath -> Bool
$c/= :: DepsPath -> DepsPath -> Bool
== :: DepsPath -> DepsPath -> Bool
$c== :: DepsPath -> DepsPath -> Bool
Eq, Eq DepsPath
DepsPath -> DepsPath -> Bool
DepsPath -> DepsPath -> Ordering
DepsPath -> DepsPath -> DepsPath
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: DepsPath -> DepsPath -> DepsPath
$cmin :: DepsPath -> DepsPath -> DepsPath
max :: DepsPath -> DepsPath -> DepsPath
$cmax :: DepsPath -> DepsPath -> DepsPath
>= :: DepsPath -> DepsPath -> Bool
$c>= :: DepsPath -> DepsPath -> Bool
> :: DepsPath -> DepsPath -> Bool
$c> :: DepsPath -> DepsPath -> Bool
<= :: DepsPath -> DepsPath -> Bool
$c<= :: DepsPath -> DepsPath -> Bool
< :: DepsPath -> DepsPath -> Bool
$c< :: DepsPath -> DepsPath -> Bool
compare :: DepsPath -> DepsPath -> Ordering
$ccompare :: DepsPath -> DepsPath -> Ordering
Ord, Int -> DepsPath -> ShowS
[DepsPath] -> ShowS
DepsPath -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DepsPath] -> ShowS
$cshowList :: [DepsPath] -> ShowS
show :: DepsPath -> String
$cshow :: DepsPath -> String
showsPrec :: Int -> DepsPath -> ShowS
$cshowsPrec :: Int -> DepsPath -> ShowS
Show)