Skip to content
Snippets Groups Projects
This project is mirrored from https://github.com/haskell/Cabal. Pull mirroring updated .
  1. Mar 21, 2015
    • Edsko de Vries's avatar
      Avoid forgetting known installed package IDs · daecdef9
      Edsko de Vries authored
      Introduce ConfiguredId:
      
          -- | A ConfiguredId is a package ID for a configured package.
          --
          -- Once we configure a source package we know it's InstalledPackageId (at
          -- least, in principle, even if we have to fake it currently). It is still
          -- however useful in lots of places to also know the source ID for the
          -- package.  We therefore bundle the two.
          --
          -- An already installed package of course is also "configured" (all it's
          -- configuration parameters and dependencies have been specified).
          --
          -- TODO: I wonder if it would make sense to promote this datatype to Cabal
          -- and use it consistently instead of InstalledPackageIds?
          data ConfiguredId = ConfiguredId {
              confSrcId  :: PackageId
            , confInstId :: InstalledPackageId
            }
      
      And use it for ConfiguredPackage. As the comment says, though, I wonder if we
      should use this in more places.
      
      One slightly tricky thing here is that the output of both solvers had to be
      modified to keep installed package IDs where possible; in the modular solver
      this was easy enough, as it does this properly, but in the top-down solver this
      is a bit of a hack; however, I’ve documented the hack in detail inline in the
      code.
      
      NOTE: Although this change is currently mostly cosmetic, in the future, once we
      drop the single instance restriction, it is very important that we don't
      convert from installed package IDs to source IDs and then back to installed
      package IDs, as this conversion will be lossy.
      daecdef9
    • Edsko de Vries's avatar
      Make top-down solver more independent · 3453175d
      Edsko de Vries authored
      Give the top-down solver it's own copy of `dependencyGraph`. This means that we
      now have three independent implementations of `dependencyGraph`:
      
      - `dependencyGraph` in `Cabal` takes a package index indexed by installed
        package IDs and only has access to library dependencies.
      - `dependencyGraph` in `Distribution.Client.PlanIndex` in `cabal-install` takes
        a package index indexed by installed package IDs and has access to all
        dependencies.
      - `dependencyGraph` in the top-down solver in `cabal-install` takes a package
        index indexed by package _names_, and has access to all dependencies.
      
      Ideally we would switch the top-down solver over to use a package indexed by
      installed package IDs, so that this duplication could be avoided, but that's a
      bit of work and the top-down solver is legacy code anyway. Can still do that
      later, of course.
      
      Moreover, this makes the top-down solver monomorphic where possible, and
      introduce its own SourceDeps class so that it is independent of the FixedDeps
      class (which we will change over to use InstalledPackageIds instead).
      3453175d
    • Edsko de Vries's avatar
      Avoid package index conversion · e866b5e8
      Edsko de Vries authored
      Introduce
      
          dependencyClosure :: InstallPlan
                            -> [PackageIdentifier]
                            -> Either (PackageIndex PlanPackage) [(PlanPackage, [InstalledPackageId])]
      
      And use this in the definition of `pruneInstallPlan` in `freeze`, to avoid
      first converting an install plan from a `Cabal.PackageIndex` to a
      `CabalInstall.PackageIndex`.
      
      This resolves the first of the two irregularities mentioned in the previous
      commit.
      e866b5e8
    • Edsko de Vries's avatar
      Document unused graph traversal functions · 1beba1bb
      Edsko de Vries authored
      Both cabal-install and `Cabal` define a notion of a package index.
      `Cabal` defines
      
          data PackageIndex a = PackageIndex !(Map InstalledPackageId a) !(Map PackageName (Map Version [a]))
      
      whereas `cabal-install` defines
      
          newtype PackageIndex pkg = PackageIndex (Map PackageName [pkg])
      
      Note that Cabal.PackageIndex is indexed by installed package IDs, whereas
      CabalInstall.PackageIndex is indexed by package names.
      
      There are a bunch of "graph traversal" functions that similarly duplicated
      between `Cabal` and `cabal-install`; in `Cabal` we have
      
          brokenPackages            :: PackageInstalled a => PackageIndex a -> [(a, [InstalledPackageId])]
          dependencyClosure         :: PackageInstalled a => PackageIndex a -> [InstalledPackageId] -> Either (PackageIndex a) [(a, [InstalledPackageId])]
          dependencyCycles          :: PackageInstalled a => PackageIndex a -> [[a]]
          dependencyGraph           :: PackageInstalled a => PackageIndex a -> (Graph.Graph, Graph.Vertex -> a, InstalledPackageId -> Maybe Graph.Vertex)
          dependencyInconsistencies :: PackageInstalled a => PackageIndex a -> [(PackageName, [(PackageId, Version)])]
          reverseDependencyClosure  :: PackageInstalled a => PackageIndex a -> [InstalledPackageId] -> [a]
          reverseTopologicalOrder   :: PackageInstalled a => PackageIndex a -> [a]
          topologicalOrder          :: PackageInstalled a => PackageIndex a -> [a]
      
      which are mirrored in `cabal-install` as
      
          brokenPackages            :: PackageFixedDeps pkg => PackageIndex pkg -> [(pkg, [PackageIdentifier])]
          dependencyClosure         :: PackageFixedDeps pkg => PackageIndex pkg -> [PackageIdentifier] -> Either (PackageIndex pkg) [(pkg, [PackageIdentifier])]
          dependencyCycles          :: PackageFixedDeps pkg => PackageIndex pkg -> [[pkg]]
          dependencyGraph           :: PackageFixedDeps pkg => PackageIndex pkg -> (Graph.Graph, Graph.Vertex -> pkg, PackageIdentifier -> Maybe Graph.Vertex)
          dependencyInconsistencies :: PackageFixedDeps pkg => PackageIndex pkg -> [(PackageName, [(PackageIdentifier, Version)])]
          reverseDependencyClosure  :: PackageFixedDeps pkg => PackageIndex pkg -> [PackageIdentifier] -> [pkg]
          reverseTopologicalOrder   :: PackageFixedDeps pkg => PackageIndex pkg -> [pkg]
          topologicalOrder          :: PackageFixedDeps pkg => PackageIndex pkg -> [pkg]
      
      This by itself makes a certain amount of sense, but here's where the situation
      gets confusing. `cabal-install` defines a `PlanIndex` as
      
          type PlanIndex = Cabal.PackageIndex PlanPackage
      
      Note that is using `Cabal`'s notion of a PackageIndex, not `cabal-install`'s; it
      makes sense that a PlanIndex is indexed by installed package IDs rather than
      package names (even if currently we have to fake installed package IDs.
      
      Almost all of the functions listed above, however, are only called on
      `PlanIndex`s. This means that we invoke the functions from `Cabal`, not the
      functions from `cabal-install`; in fact, almost all these functions in
      `cabal-install` are completely unused right now.
      
          In `cabal-install`     but calls from `Cabal`
          ----------------------------------------------------------
          closed                 brokenPackages
          acyclic                dependencyCycles
          consistent             dependencyInconsistencies
          problems               brokenPackages', dependencyCycles',
                                   dependencyInconsistencies'
      
      This is more than just a code clean-up issue. As mentioned in the previous PR,
      the fundamental difference between Cabal and cabal-install is their view of
      dependencies: Cabal knows only about installed libraries and their library
      dependencies, whereas cabal knows about packages and the dependencies of their
      setup scripts, executables, test-suites, benchmarks, as well as their library
      dependencies.
      
      By calling the graph-traversal functions from `Cabal` rather than from
      `cabal-install`, any of these additional dependencies are either completely
      ignored, or else the distinction is lost (depending on how we implemented
      installedDepends for plan packages); and neither option is correct.
      
      For example, in `new` from Distribution.Client.InstallPlan (in `cabal-install`)
      we call `dependendyGraph` on the plan index; since the plan index is defined in
      terms of Cabal's plan index, we call Cabal's `dependencyGraph` here, but that
      means that this graph will completely lack any setup dependencies. The reverse
      graph is used in (only one place): `packagedThatDependOn`, which in turn is
      (only) used in `failed`. But this is wrong: if a package fails to install, if
      another package depends on it through a setup dependency, then that second
      package should also be marked as impossible to install.
      
      What needs to happen is that we modify the graph traversal functions from
      `cabal-install` to take a PackageIndex from `Cabal` (so that we can apply them
      to a PlanIndex), but use the dependencies from `FixedPackageDeps` rather than
      the flat or incomplete dependencies we get from `PackageInstalled`. In fact,
      the whole `PackageInstalled` instance for `ConfiguredPackage`, `ReadyPackage`
      and `PlanPackage` should go: returning only part of the dependencies, or else
      all dependencies flattened, is just too error prone.
      
      This first commit only documents the problem (this commit message) and moves the
      above functions to a new module called Distribution.Client.PlanIndex.
      
      Cleaning this up is complicated by the fact that we _do_ still call two of the
      above functions on a `CabalInstall.PackageIndex`:
      
      * `pruneInstallPlan` from `Distribution.Client.Freeze` calls `dependencyClosure`
      * The top-down solver calls `dependencyGraph`
      
      If we change the above functions to work on a `Cabal.PackageIndex` instead these
      two exceptions will break, so we need to look at that first.
      1beba1bb
    • Edsko de Vries's avatar
      Split the PackageInstalled class · 2ea3dde1
      Edsko de Vries authored
      Introduce a new superclass HasInstalledPackageId:
      
          class Package pkg => HasInstalledPackageId pkg where
            installedPackageId :: pkg -> InstalledPackageId
      
          class HasInstalledPackageId pkg => PackageInstalled pkg where
            installedDepends :: pkg -> [InstalledPackageId]
      
      Most functions that deal with the package index now just require
      HasInstalledPackageId; only the functions that actually require the
      dependencies still rely on PackageInstalled.
      
      The point is that a ConfiguredPackage/ReadyPackage/PlanPackage can reasonably
      be made an instance of HasInstalledPackageId, but not of PackageInstalled; that
      will be the topic of the next, much larger, pull request.
      2ea3dde1
    • Edsko de Vries's avatar
      Move PackageFixedDeps from Cabal to cabal-install · 445ad90d
      Edsko de Vries authored
      The fundamental difference between Cabal and cabal-install is that the former
      deals with installed libraries, and -- in principle -- knows about _library_
      dependencies only, whereas the latters deals with setup, executable, test-suite
      and benchmark dependencies in addition to library dependencies. Currently we
      classify all of these simply as 'dependencies' but that will change shortly.
      
      In this commit we take a first step towards this by moving the PackageFixedDeps
      class, which deals with dependencies of packages rather than installed
      libraries, from Cabal to cabal-install.
      
      The commit is pretty simple; we just move the type class and update import
      statements where necessary.
      445ad90d
  2. Mar 20, 2015
  3. Mar 19, 2015
  4. Mar 18, 2015
  5. Mar 17, 2015
  6. Mar 16, 2015
  7. Mar 15, 2015
    • ttuegel's avatar
      fix HPC tests with GHC 7.10 · 1bda4281
      ttuegel authored
      Starting with version 7.10, GHC puts the module interface (.mix) files
      for each project in a subdirectory of -hpcdir named for the package
      key. We must adjust the search path accordingly when checking for the
      .mix file.
      1bda4281
  8. Mar 13, 2015
    • Duncan Coutts's avatar
      Merge pull request #2466 from edsko/bugfix/package-key · 25807bee
      Duncan Coutts authored
      Make sure to pass the package key to ghc
      25807bee
    • Edsko de Vries's avatar
      Make sure to pass the package key to ghc · 3e78870d
      Edsko de Vries authored
      In https://github.com/haskell/cabal/pull/2439 the invocation of Haddock is
      changed to use Haddock's new `--package-name` and `--package-version` flags,
      necessary for GHC >= 7.10 (Cabal issue
      https://github.com/haskell/cabal/issues/2297 / Haddock issue
      https://github.com/haskell/haddock/issues/353). However, this commit also
      removes the `-package-name` argument to GHC. This is incorrect, as it means
      that GHC will end up calling the package `main` and we end up with Haddock link
      environments such as
      
          (trans_H9c1w14lEUN3zdWCTsn8jG:Control.Monad.Trans.Error.strMsg, main:Control.Monad.Error.Class)
      
      Note that before this commit we ended up with
      
          (trans_H9c1w14lEUN3zdWCTsn8jG:Control.Monad.Trans.Error.strMsg, mtl-2.1.1:Control.Monad.Error.Class)
      
      which is equally wrong as it uses a package source ID rather than a package key
      (Haddock issue https://github.com/haskell/haddock/issues/362). Instead, we need
      to pass _both_ `--package-name` and `--package-version` to Haddock, and
      `-package-name` or `-this-package-key` to GHC, depending on the version.
      Thankfully the infrastructure for chosing between `-package-name` and
      `-this-package-key` is already in place, so we just have to make sure to
      populate the `ghcPackageKey` field. After this commit the link environment
      looks like
      
          (trans_H9c1w14lEUN3zdWCTsn8jG:Control.Monad.Trans.Error.strMsg, mtl_Koly6qxRZLf86guywd4tkE:Control.Monad.Error.Class)
      
      which is correct.
      3e78870d
  9. Mar 11, 2015
  10. Mar 10, 2015
  11. Mar 09, 2015
Loading