{-# LANGUAGE CPP #-}
module Distribution.RPM.Build.Order
(dependencySort,
dependencySortRpmOpts,
dependencySortParallel,
dependencyLayers,
leafPackages,
independentPackages,
Components (..),
sortGraph)
where
#if !MIN_VERSION_base(4,8,0)
import Control.Applicative ((<$>))
#endif
import Data.Graph.Inductive.Query.DFS (topsort', components)
import Distribution.RPM.Build.Graph
dependencySort :: [FilePath] -> IO [FilePath]
dependencySort :: [FilePath] -> IO [FilePath]
dependencySort = [FilePath] -> [FilePath] -> IO [FilePath]
dependencySortRpmOpts []
dependencySortRpmOpts :: [String] -> [FilePath] -> IO [FilePath]
dependencySortRpmOpts :: [FilePath] -> [FilePath] -> IO [FilePath]
dependencySortRpmOpts rpmopts :: [FilePath]
rpmopts pkgs :: [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
dependencySortParallel :: [FilePath] -> IO [[FilePath]]
dependencySortParallel :: [FilePath] -> IO [[FilePath]]
dependencySortParallel pkgs :: [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)
dependencyLayers :: [FilePath] -> IO [[FilePath]]
dependencyLayers :: [FilePath] -> IO [[FilePath]]
dependencyLayers pkgs :: [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
leafPackages :: [FilePath] -> IO [FilePath]
leafPackages :: [FilePath] -> IO [FilePath]
leafPackages pkgs :: [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
independentPackages :: [FilePath] -> IO [FilePath]
independentPackages :: [FilePath] -> IO [FilePath]
independentPackages pkgs :: [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
data Components = Parallel
| Combine
| Connected
| Separate
sortGraph :: Components -> PackageGraph -> IO ()
sortGraph :: Components -> Gr FilePath () -> IO ()
sortGraph opt :: Components
opt graph :: Gr FilePath ()
graph =
case Components
opt of
Parallel ->
([Node] -> IO ()) -> [[Node]] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ ((FilePath -> IO ()
putStrLn (FilePath -> IO ())
-> ([FilePath] -> FilePath) -> [FilePath] -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ('\n'Char -> FilePath -> FilePath
forall a. a -> [a] -> [a]
:) (FilePath -> FilePath)
-> ([FilePath] -> FilePath) -> [FilePath] -> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [FilePath] -> FilePath
unwords) ([FilePath] -> IO ()) -> ([Node] -> [FilePath]) -> [Node] -> IO ()
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)
Combine -> (FilePath -> IO ()
putStrLn (FilePath -> IO ())
-> (Gr FilePath () -> FilePath) -> Gr FilePath () -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [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
Connected ->
([Node] -> IO ()) -> [[Node]] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ ((FilePath -> IO ()
putStrLn (FilePath -> IO ())
-> ([FilePath] -> FilePath) -> [FilePath] -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ('\n'Char -> FilePath -> FilePath
forall a. a -> [a] -> [a]
:) (FilePath -> FilePath)
-> ([FilePath] -> FilePath) -> [FilePath] -> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [FilePath] -> FilePath
unwords) ([FilePath] -> IO ()) -> ([Node] -> [FilePath]) -> [Node] -> IO ()
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]] -> IO ()) -> [[Node]] -> IO ()
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
>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)
Separate ->
let independent :: [FilePath]
independent = Gr FilePath () -> [FilePath]
separatePackages Gr FilePath ()
graph
in (FilePath -> IO ()) -> [FilePath] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ FilePath -> IO ()
putStrLn [FilePath]
independent