Skip to content
Snippets Groups Projects
Commit 448d37db authored by Duncan Coutts's avatar Duncan Coutts Committed by Mikhail Glushenkov
Browse files

Move the ExtDependency type to the only module where it's used

Fewer shared types makes the code easier to grok and navigate.
parent 0be5efeb
No related branches found
No related tags found
No related merge requests found
......@@ -13,8 +13,6 @@
-- Common types for dependency resolution.
-----------------------------------------------------------------------------
module Distribution.Client.Dependency.Types (
ExtDependency(..),
PreSolver(..),
Solver(..),
DependencyResolver,
......@@ -48,9 +46,6 @@ import Data.Monoid
import Distribution.Client.Types
( OptionalStanza(..), SourcePackage(..), ConfiguredPackage )
import Distribution.Compat.ReadP
( (<++) )
import qualified Distribution.Compat.ReadP as Parse
( pfail, munch1 )
import Distribution.PackageDescription
......@@ -61,7 +56,7 @@ import qualified Distribution.Client.PackageIndex as PackageIndex
( PackageIndex )
import Distribution.Simple.PackageIndex ( InstalledPackageIndex )
import Distribution.Package
( Dependency, PackageName, InstalledPackageId )
( PackageName )
import Distribution.Version
( VersionRange, simplifyVersionRange )
import Distribution.Compiler
......@@ -76,16 +71,6 @@ import Text.PrettyPrint
import Prelude hiding (fail)
-- | Covers source dependencies and installed dependencies in
-- one type.
data ExtDependency = SourceDependency Dependency
| InstalledDependency InstalledPackageId
instance Text ExtDependency where
disp (SourceDependency dep) = disp dep
disp (InstalledDependency dep) = disp dep
parse = (SourceDependency `fmap` parse) <++ (InstalledDependency `fmap` parse)
-- | All the solvers that can be selected.
data PreSolver = AlwaysTopDown | AlwaysModular | Choose
......
......@@ -15,7 +15,8 @@ module Distribution.Client.List (
import Distribution.Package
( PackageName(..), Package(..), packageName, packageVersion
, Dependency(..), simplifyDependency )
, Dependency(..), simplifyDependency
, InstalledPackageId )
import Distribution.ModuleName (ModuleName)
import Distribution.License (License)
import qualified Distribution.InstalledPackageInfo as Installed
......@@ -44,7 +45,7 @@ import Distribution.Text
import Distribution.Client.Types
( SourcePackage(..), Repo, SourcePackageDb(..) )
import Distribution.Client.Dependency.Types
( PackageConstraint(..), ExtDependency(..) )
( PackageConstraint(..) )
import Distribution.Client.Targets
( UserTarget, resolveUserTargets, PackageSpecifier(..) )
import Distribution.Client.Setup
......@@ -292,6 +293,11 @@ data PackageDisplayInfo = PackageDisplayInfo {
haveTarball :: Bool
}
-- | Covers source dependencies and installed dependencies in
-- one type.
data ExtDependency = SourceDependency Dependency
| InstalledDependency InstalledPackageId
showPackageSummaryInfo :: PackageDisplayInfo -> String
showPackageSummaryInfo pkginfo =
renderStyle (style {lineLength = 80, ribbonsPerLine = 1}) $
......@@ -344,7 +350,7 @@ showPackageDetailedInfo pkginfo =
, entry "Source repo" sourceRepo orNotSpecified text
, entry "Executables" executables hideIfNull (commaSep text)
, entry "Flags" flags hideIfNull (commaSep dispFlag)
, entry "Dependencies" dependencies hideIfNull (commaSep disp)
, entry "Dependencies" dependencies hideIfNull (commaSep dispExtDep)
, entry "Documentation" haddockHtml showIfInstalled text
, entry "Cached" haveTarball alwaysShow dispYesNo
, if not (hasLib pkginfo) then empty else
......@@ -378,6 +384,9 @@ showPackageDetailedInfo pkginfo =
dispYesNo True = text "Yes"
dispYesNo False = text "No"
dispExtDep (SourceDependency dep) = disp dep
dispExtDep (InstalledDependency dep) = disp dep
isInstalled = not (null (installedVersions pkginfo))
hasExes = length (executables pkginfo) >= 2
--TODO: exclude non-buildable exes
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment