{-# LANGUAGE CPP #-}
-----------------------------------------------------------------------------
-- |
-- Module      :  Distribution.Client.GenBounds
-- Copyright   :  (c) Doug Beardsley 2015
-- License     :  BSD-like
--
-- Maintainer  :  cabal-devel@gmail.com
-- Stability   :  provisional
-- Portability :  portable
--
-- The cabal gen-bounds command for generating PVP-compliant version bounds.
-----------------------------------------------------------------------------
module Distribution.Client.GenBounds (
    genBounds
  ) where

import Prelude ()
import Distribution.Client.Compat.Prelude

import Distribution.Client.Utils
         ( incVersion )
import Distribution.Client.Freeze
         ( getFreezePkgs )
import Distribution.Client.Setup
         ( GlobalFlags(..), FreezeFlags(..), RepoContext )
import Distribution.Package
         ( Package(..), unPackageName, packageName, packageVersion )
import Distribution.PackageDescription
         ( enabledBuildDepends )
import Distribution.PackageDescription.Configuration
         ( finalizePD )
import Distribution.Types.ComponentRequestedSpec
         ( defaultComponentRequestedSpec )
import Distribution.Types.Dependency
import Distribution.Simple.Compiler
         ( Compiler, PackageDBStack, compilerInfo )
import Distribution.Simple.PackageDescription
         ( readGenericPackageDescription )
import Distribution.Simple.Program
         ( ProgramDb )
import Distribution.Simple.Utils
         ( tryFindPackageDesc )
import Distribution.System
         ( Platform )
import Distribution.Version
         ( Version, alterVersion, VersionInterval (..)
         , LowerBound(..), UpperBound(..), VersionRange, asVersionIntervals
         , orLaterVersion, earlierVersion, intersectVersionRanges, hasUpperBound)
import System.Directory
         ( getCurrentDirectory )

-- | Given a version, return an API-compatible (according to PVP) version range.
--
-- Example: @0.4.1.2@ produces the version range @>= 0.4.1 && < 0.5@.
--
-- This version is slightly different than the one in
-- 'Distribution.Client.Init'.  This one uses a.b.c as the lower bound because
-- the user could be using a new function introduced in a.b.c which would make
-- ">= a.b" incorrect.
pvpize :: Version -> VersionRange
pvpize :: Version -> VersionRange
pvpize Version
v = Version -> VersionRange
orLaterVersion (Int -> Version
vn Int
3)
           VersionRange -> VersionRange -> VersionRange
`intersectVersionRanges`
           Version -> VersionRange
earlierVersion (Int -> Version -> Version
incVersion Int
1 (Int -> Version
vn Int
2))
  where
    vn :: Int -> Version
vn Int
n = ([Int] -> [Int]) -> Version -> Version
alterVersion (Int -> [Int] -> [Int]
forall a. Int -> [a] -> [a]
take Int
n) Version
v

-- | Show the PVP-mandated version range for this package. The @padTo@ parameter
-- specifies the width of the package name column.
showBounds :: Package pkg => Int -> pkg -> String
showBounds :: Int -> pkg -> String
showBounds Int
padTo pkg
p = [String] -> String
unwords ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$
    (Int -> String -> String
padAfter Int
padTo (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ PackageName -> String
unPackageName (PackageName -> String) -> PackageName -> String
forall a b. (a -> b) -> a -> b
$ pkg -> PackageName
forall pkg. Package pkg => pkg -> PackageName
packageName pkg
p) String -> [String] -> [String]
forall a. a -> [a] -> [a]
:
    -- TODO: use normaliseVersionRange
    (VersionInterval -> String) -> [VersionInterval] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map VersionInterval -> String
showInterval (VersionRange -> [VersionInterval]
asVersionIntervals (VersionRange -> [VersionInterval])
-> VersionRange -> [VersionInterval]
forall a b. (a -> b) -> a -> b
$ Version -> VersionRange
pvpize (Version -> VersionRange) -> Version -> VersionRange
forall a b. (a -> b) -> a -> b
$ pkg -> Version
forall pkg. Package pkg => pkg -> Version
packageVersion pkg
p)
  where
    padAfter :: Int -> String -> String
    padAfter :: Int -> String -> String
padAfter Int
n String
str = String
str String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> Char -> String
forall a. Int -> a -> [a]
replicate (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- String -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length String
str) Char
' '

    showInterval :: VersionInterval -> String
    showInterval :: VersionInterval -> String
showInterval (VersionInterval (LowerBound Version
_ Bound
_) UpperBound
NoUpperBound) =
      String -> String
forall a. HasCallStack => String -> a
error String
"Error: expected upper bound...this should never happen!"
    showInterval (VersionInterval (LowerBound Version
l Bound
_) (UpperBound Version
u Bound
_)) =
      [String] -> String
unwords [String
">=", Version -> String
forall a. Pretty a => a -> String
prettyShow Version
l, String
"&& <", Version -> String
forall a. Pretty a => a -> String
prettyShow Version
u]

-- | Entry point for the @gen-bounds@ command.
genBounds
    :: Verbosity
    -> PackageDBStack
    -> RepoContext
    -> Compiler
    -> Platform
    -> ProgramDb
    -> GlobalFlags
    -> FreezeFlags
    -> IO ()
genBounds :: Verbosity
-> PackageDBStack
-> RepoContext
-> Compiler
-> Platform
-> ProgramDb
-> GlobalFlags
-> FreezeFlags
-> IO ()
genBounds Verbosity
verbosity PackageDBStack
packageDBs RepoContext
repoCtxt Compiler
comp Platform
platform ProgramDb
progdb GlobalFlags
globalFlags FreezeFlags
freezeFlags = do
    let cinfo :: CompilerInfo
cinfo = Compiler -> CompilerInfo
compilerInfo Compiler
comp

    String
cwd <- IO String
getCurrentDirectory
    String
path <- Verbosity -> String -> IO String
tryFindPackageDesc Verbosity
verbosity String
cwd
    GenericPackageDescription
gpd <- Verbosity -> String -> IO GenericPackageDescription
readGenericPackageDescription Verbosity
verbosity String
path
    -- NB: We don't enable tests or benchmarks, since often they
    -- don't really have useful bounds.
    let epd :: Either [Dependency] (PackageDescription, FlagAssignment)
epd = FlagAssignment
-> ComponentRequestedSpec
-> (Dependency -> Bool)
-> Platform
-> CompilerInfo
-> [PackageVersionConstraint]
-> GenericPackageDescription
-> Either [Dependency] (PackageDescription, FlagAssignment)
finalizePD FlagAssignment
forall a. Monoid a => a
mempty ComponentRequestedSpec
defaultComponentRequestedSpec
                    (Bool -> Dependency -> Bool
forall a b. a -> b -> a
const Bool
True) Platform
platform CompilerInfo
cinfo [] GenericPackageDescription
gpd
    case Either [Dependency] (PackageDescription, FlagAssignment)
epd of
      Left [Dependency]
_ -> String -> IO ()
putStrLn String
"finalizePD failed"
      Right (PackageDescription
pd,FlagAssignment
_) -> do
        let needBounds :: [Dependency]
needBounds = (Dependency -> Bool) -> [Dependency] -> [Dependency]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool) -> (Dependency -> Bool) -> Dependency -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VersionRange -> Bool
hasUpperBound (VersionRange -> Bool)
-> (Dependency -> VersionRange) -> Dependency -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Dependency -> VersionRange
depVersion) ([Dependency] -> [Dependency]) -> [Dependency] -> [Dependency]
forall a b. (a -> b) -> a -> b
$
                         PackageDescription -> ComponentRequestedSpec -> [Dependency]
enabledBuildDepends PackageDescription
pd ComponentRequestedSpec
defaultComponentRequestedSpec

        if ([Dependency] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Dependency]
needBounds)
          then String -> IO ()
putStrLn
               String
"Congratulations, all your dependencies have upper bounds!"
          else [Dependency] -> IO ()
go [Dependency]
needBounds
  where
     go :: [Dependency] -> IO ()
go [Dependency]
needBounds = do
       [SolverPlanPackage]
pkgs  <- Verbosity
-> PackageDBStack
-> RepoContext
-> Compiler
-> Platform
-> ProgramDb
-> GlobalFlags
-> FreezeFlags
-> IO [SolverPlanPackage]
getFreezePkgs
                  Verbosity
verbosity PackageDBStack
packageDBs RepoContext
repoCtxt Compiler
comp Platform
platform ProgramDb
progdb
                  GlobalFlags
globalFlags FreezeFlags
freezeFlags

       String -> IO ()
putStrLn String
boundsNeededMsg

       let isNeeded :: pkg -> Bool
isNeeded pkg
pkg = PackageName -> String
unPackageName (pkg -> PackageName
forall pkg. Package pkg => pkg -> PackageName
packageName pkg
pkg)
                          String -> [String] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` (Dependency -> String) -> [Dependency] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map Dependency -> String
depName [Dependency]
needBounds
       let thePkgs :: [SolverPlanPackage]
thePkgs = (SolverPlanPackage -> Bool)
-> [SolverPlanPackage] -> [SolverPlanPackage]
forall a. (a -> Bool) -> [a] -> [a]
filter SolverPlanPackage -> Bool
forall pkg. Package pkg => pkg -> Bool
isNeeded [SolverPlanPackage]
pkgs

       let padTo :: Int
padTo = [Int] -> Int
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum ([Int] -> Int) -> [Int] -> Int
forall a b. (a -> b) -> a -> b
$ (SolverPlanPackage -> Int) -> [SolverPlanPackage] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map (String -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length (String -> Int)
-> (SolverPlanPackage -> String) -> SolverPlanPackage -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PackageName -> String
unPackageName (PackageName -> String)
-> (SolverPlanPackage -> PackageName)
-> SolverPlanPackage
-> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SolverPlanPackage -> PackageName
forall pkg. Package pkg => pkg -> PackageName
packageName) [SolverPlanPackage]
pkgs
       (SolverPlanPackage -> IO ()) -> [SolverPlanPackage] -> IO ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
(a -> f b) -> t a -> f ()
traverse_ (String -> IO ()
putStrLn (String -> IO ())
-> (SolverPlanPackage -> String) -> SolverPlanPackage -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> String -> String
forall a. [a] -> [a] -> [a]
++String
",") (String -> String)
-> (SolverPlanPackage -> String) -> SolverPlanPackage -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> SolverPlanPackage -> String
forall pkg. Package pkg => Int -> pkg -> String
showBounds Int
padTo) [SolverPlanPackage]
thePkgs

     depName :: Dependency -> String
     depName :: Dependency -> String
depName (Dependency PackageName
pn VersionRange
_ NonEmptySet LibraryName
_) = PackageName -> String
unPackageName PackageName
pn

     depVersion :: Dependency -> VersionRange
     depVersion :: Dependency -> VersionRange
depVersion (Dependency PackageName
_ VersionRange
vr NonEmptySet LibraryName
_) = VersionRange
vr

-- | The message printed when some dependencies are found to be lacking proper
-- PVP-mandated bounds.
boundsNeededMsg :: String
boundsNeededMsg :: String
boundsNeededMsg = [String] -> String
unlines
  [ String
""
  , String
"The following packages need bounds and here is a suggested starting point."
  , String
"You can copy and paste this into the build-depends section in your .cabal"
  , String
"file and it should work (with the appropriate removal of commas)."
  , String
""
  , String
"Note that version bounds are a statement that you've successfully built and"
  , String
"tested your package and expect it to work with any of the specified package"
  , String
"versions (PROVIDED that those packages continue to conform with the PVP)."
  , String
"Therefore, the version bounds generated here are the most conservative"
  , String
"based on the versions that you are currently building with.  If you know"
  , String
"your package will work with versions outside the ranges generated here,"
  , String
"feel free to widen them."
  , String
""
  ]