module Distribution.Types.ParStrat where

-- | How to control parallelism, e.g. a fixed number of jobs or by using a system semaphore.
data ParStratX sem
  = -- | Compile in parallel with the given number of jobs (`-jN` or `-j`).
    NumJobs (Maybe Int)
  | -- | `--semaphore`: use a system semaphore to control parallelism.
    UseSem sem
  | -- | No parallelism (neither `-jN` nor `--semaphore`, but could be `-j1`).
    Serial
  deriving (Int -> ParStratX sem -> ShowS
[ParStratX sem] -> ShowS
ParStratX sem -> String
(Int -> ParStratX sem -> ShowS)
-> (ParStratX sem -> String)
-> ([ParStratX sem] -> ShowS)
-> Show (ParStratX sem)
forall sem. Show sem => Int -> ParStratX sem -> ShowS
forall sem. Show sem => [ParStratX sem] -> ShowS
forall sem. Show sem => ParStratX sem -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall sem. Show sem => Int -> ParStratX sem -> ShowS
showsPrec :: Int -> ParStratX sem -> ShowS
$cshow :: forall sem. Show sem => ParStratX sem -> String
show :: ParStratX sem -> String
$cshowList :: forall sem. Show sem => [ParStratX sem] -> ShowS
showList :: [ParStratX sem] -> ShowS
Show)

-- | Used by Cabal to indicate that we want to use this specific semaphore (created by cabal-install)
type ParStrat = ParStratX String

-- | Used by cabal-install to say we want to create a semaphore with N slots.
type ParStratInstall = ParStratX Int

-- | Determine if the parallelism strategy enables parallel builds.
isParallelBuild :: ParStratX n -> Bool
isParallelBuild :: forall n. ParStratX n -> Bool
isParallelBuild ParStratX n
Serial = Bool
False
isParallelBuild (NumJobs (Just Int
1)) = Bool
False
isParallelBuild (NumJobs Maybe Int
_) = Bool
True
isParallelBuild UseSem{} = Bool
True