{-# LANGUAGE CPP #-}

{-|
This module provides dependency sorting functions

@
import "Distribution.RPM.Build.Order"

'dependencySort' ["pkg1", "pkg2", "../pkg3"]

=> ["pkg2", "../pkg3", "pkg1"]
@
where pkg1 depends on pkg3, which depends on pkg2 say.

Package paths can be directories or spec files.
-}

module Distribution.RPM.Build.Order
  (dependencySort,
   dependencySortRpmOpts,
   dependencySortParallel,
   dependencyLayers,
   leafPackages,
   independentPackages,
   Components (..),
   sortGraph,
   depsPackages)
where

#if !MIN_VERSION_base(4,8,0)
import Control.Applicative ((<$>))
#endif
import Data.List (intercalate)
import Data.Graph.Inductive.Query.DFS (topsort', components)

import Distribution.RPM.Build.Graph

-- | sort packages by dependencies
dependencySort :: [FilePath] -> IO [FilePath]
dependencySort :: [FilePath] -> IO [FilePath]
dependencySort = [FilePath] -> [FilePath] -> IO [FilePath]
dependencySortRpmOpts []

-- | sort packages by dependencies with rpm options
--
-- @since 0.4.2
dependencySortRpmOpts :: [String] -> [FilePath] -> IO [FilePath]
dependencySortRpmOpts :: [FilePath] -> [FilePath] -> IO [FilePath]
dependencySortRpmOpts [FilePath]
rpmopts [FilePath]
pkgs = do
  Gr FilePath () -> [FilePath]
forall (gr :: * -> * -> *) a b. Graph gr => gr a b -> [a]
topsort' (Gr FilePath () -> [FilePath])
-> IO (Gr FilePath ()) -> IO [FilePath]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [FilePath] -> [FilePath] -> IO (Gr FilePath ())
createGraphRpmOpts [FilePath]
rpmopts [FilePath]
pkgs

-- | dependency sort of packages in graph components
dependencySortParallel :: [FilePath] -> IO [[FilePath]]
dependencySortParallel :: [FilePath] -> IO [[FilePath]]
dependencySortParallel [FilePath]
pkgs = do
  Gr FilePath ()
graph <- [FilePath] -> IO (Gr FilePath ())
createGraph [FilePath]
pkgs
  [[FilePath]] -> IO [[FilePath]]
forall (m :: * -> *) a. Monad m => a -> m a
return ([[FilePath]] -> IO [[FilePath]])
-> [[FilePath]] -> IO [[FilePath]]
forall a b. (a -> b) -> a -> b
$ ([Node] -> [FilePath]) -> [[Node]] -> [[FilePath]]
forall a b. (a -> b) -> [a] -> [b]
map (Gr FilePath () -> [FilePath]
forall (gr :: * -> * -> *) a b. Graph gr => gr a b -> [a]
topsort' (Gr FilePath () -> [FilePath])
-> ([Node] -> Gr FilePath ()) -> [Node] -> [FilePath]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Gr FilePath () -> [Node] -> Gr FilePath ()
forall a b. Gr a b -> [Node] -> Gr a b
subgraph' Gr FilePath ()
graph) (Gr FilePath () -> [[Node]]
forall (gr :: * -> * -> *) a b. Graph gr => gr a b -> [[Node]]
components Gr FilePath ()
graph)

-- | group packages in dependency layers, lowest first
dependencyLayers :: [FilePath] -> IO [[FilePath]]
dependencyLayers :: [FilePath] -> IO [[FilePath]]
dependencyLayers [FilePath]
pkgs = do
  Gr FilePath ()
graph <- [FilePath] -> IO (Gr FilePath ())
createGraph [FilePath]
pkgs
  [[FilePath]] -> IO [[FilePath]]
forall (m :: * -> *) a. Monad m => a -> m a
return ([[FilePath]] -> IO [[FilePath]])
-> [[FilePath]] -> IO [[FilePath]]
forall a b. (a -> b) -> a -> b
$ Gr FilePath () -> [[FilePath]]
packageLayers Gr FilePath ()
graph

-- | returns the leaves of a set of packages
leafPackages :: [FilePath] -> IO [FilePath]
leafPackages :: [FilePath] -> IO [FilePath]
leafPackages [FilePath]
pkgs = do
  Gr FilePath ()
graph <- [FilePath] -> IO (Gr FilePath ())
createGraph [FilePath]
pkgs
  [FilePath] -> IO [FilePath]
forall (m :: * -> *) a. Monad m => a -> m a
return ([FilePath] -> IO [FilePath]) -> [FilePath] -> IO [FilePath]
forall a b. (a -> b) -> a -> b
$ Gr FilePath () -> [FilePath]
packageLeaves Gr FilePath ()
graph

-- | returns independent packages among a set of packages
independentPackages :: [FilePath] -> IO [FilePath]
independentPackages :: [FilePath] -> IO [FilePath]
independentPackages [FilePath]
pkgs = do
  Gr FilePath ()
graph <- [FilePath] -> IO (Gr FilePath ())
createGraph [FilePath]
pkgs
  [FilePath] -> IO [FilePath]
forall (m :: * -> *) a. Monad m => a -> m a
return ([FilePath] -> IO [FilePath]) -> [FilePath] -> IO [FilePath]
forall a b. (a -> b) -> a -> b
$ Gr FilePath () -> [FilePath]
separatePackages Gr FilePath ()
graph

-- | Used to control the output from sortGraph
data Components = Parallel -- ^ separate independent stacks
                | Combine -- ^ combine indepdendent stacks together
                | Connected -- ^ only stack of packages
                | Separate -- ^ only independent packages in the package set

-- | output sorted packages from a PackageGraph arrange by Components
sortGraph :: Components -> PackageGraph -> IO ()
sortGraph :: Components -> Gr FilePath () -> IO ()
sortGraph Components
opt Gr FilePath ()
graph =
  -- FIXME output list(s) instead
  FilePath -> IO ()
putStrLn (FilePath -> IO ()) -> FilePath -> IO ()
forall a b. (a -> b) -> a -> b
$
  case Components
opt of
    Components
Parallel ->
      FilePath -> [FilePath] -> FilePath
forall a. [a] -> [[a]] -> [a]
intercalate FilePath
"\n\n" ([FilePath] -> FilePath) -> [FilePath] -> FilePath
forall a b. (a -> b) -> a -> b
$ ([Node] -> FilePath) -> [[Node]] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map ([FilePath] -> FilePath
unwords ([FilePath] -> FilePath)
-> ([Node] -> [FilePath]) -> [Node] -> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Gr FilePath () -> [FilePath]
forall (gr :: * -> * -> *) a b. Graph gr => gr a b -> [a]
topsort' (Gr FilePath () -> [FilePath])
-> ([Node] -> Gr FilePath ()) -> [Node] -> [FilePath]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Gr FilePath () -> [Node] -> Gr FilePath ()
forall a b. Gr a b -> [Node] -> Gr a b
subgraph' Gr FilePath ()
graph) (Gr FilePath () -> [[Node]]
forall (gr :: * -> * -> *) a b. Graph gr => gr a b -> [[Node]]
components Gr FilePath ()
graph)
    Components
Combine -> ([FilePath] -> FilePath
unwords ([FilePath] -> FilePath)
-> (Gr FilePath () -> [FilePath]) -> Gr FilePath () -> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Gr FilePath () -> [FilePath]
forall (gr :: * -> * -> *) a b. Graph gr => gr a b -> [a]
topsort') Gr FilePath ()
graph
    Components
Connected ->
      FilePath -> [FilePath] -> FilePath
forall a. [a] -> [[a]] -> [a]
intercalate FilePath
"\n\n" ([FilePath] -> FilePath) -> [FilePath] -> FilePath
forall a b. (a -> b) -> a -> b
$ ([Node] -> FilePath) -> [[Node]] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map ([FilePath] -> FilePath
unwords ([FilePath] -> FilePath)
-> ([Node] -> [FilePath]) -> [Node] -> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Gr FilePath () -> [FilePath]
forall (gr :: * -> * -> *) a b. Graph gr => gr a b -> [a]
topsort' (Gr FilePath () -> [FilePath])
-> ([Node] -> Gr FilePath ()) -> [Node] -> [FilePath]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Gr FilePath () -> [Node] -> Gr FilePath ()
forall a b. Gr a b -> [Node] -> Gr a b
subgraph' Gr FilePath ()
graph) ([[Node]] -> [FilePath]) -> [[Node]] -> [FilePath]
forall a b. (a -> b) -> a -> b
$ ([Node] -> Bool) -> [[Node]] -> [[Node]]
forall a. (a -> Bool) -> [a] -> [a]
filter ((Node -> Node -> Bool
forall a. Ord a => a -> a -> Bool
>Node
1) (Node -> Bool) -> ([Node] -> Node) -> [Node] -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Node] -> Node
forall (t :: * -> *) a. Foldable t => t a -> Node
length) (Gr FilePath () -> [[Node]]
forall (gr :: * -> * -> *) a b. Graph gr => gr a b -> [[Node]]
components Gr FilePath ()
graph)
    Components
Separate -> [FilePath] -> FilePath
unlines ([FilePath] -> FilePath) -> [FilePath] -> FilePath
forall a b. (a -> b) -> a -> b
$ Gr FilePath () -> [FilePath]
separatePackages Gr FilePath ()
graph

-- | Given a list of one or more packages, look for dependencies
-- in neighboring packages and output them in a topological order
--
-- @since 0.4.9
depsPackages :: Bool -- ^ whether to look for reverse dependencies
             -> [String] -- ^ rpm options
             -> Bool -- ^ verbose output
             -> [String] -- ^ packages to exclude
             -> [String] -- ^ buildrequires to ignore
             -> Bool -- ^ allow rpmspec failures
             -> Bool -- ^ parallel output
             -> Maybe FilePath -- ^ subdir for packages
             -> [FilePath] -- ^ list of package paths
             -> IO ()
depsPackages :: Bool
-> [FilePath]
-> Bool
-> [FilePath]
-> [FilePath]
-> Bool
-> Bool
-> Maybe FilePath
-> [FilePath]
-> IO ()
depsPackages Bool
rev [FilePath]
rpmopts Bool
verbose [FilePath]
excludedPkgs [FilePath]
ignoredBRs Bool
lenient Bool
parallel Maybe FilePath
mdir [FilePath]
pkgs =
  Bool
-> [FilePath]
-> Bool
-> [FilePath]
-> [FilePath]
-> Bool
-> Maybe FilePath
-> [FilePath]
-> IO (Gr FilePath ())
depsGraph Bool
rev [FilePath]
rpmopts Bool
verbose [FilePath]
excludedPkgs [FilePath]
ignoredBRs Bool
lenient Maybe FilePath
mdir [FilePath]
pkgs IO (Gr FilePath ()) -> (Gr FilePath () -> IO ()) -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
  Components -> Gr FilePath () -> IO ()
sortGraph (if Bool
parallel then Components
Parallel else Components
Combine)