{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE NoFieldSelectors  #-}

-- | Module exporting the `DotOpts` type used by Stack's @dot@ and

-- @ls dependencies@ commands.

module Stack.Types.DotOpts
  ( DotOpts (..)
  ) where

import           Stack.Prelude
import           Stack.Types.BuildOptsCLI ( ApplyCLIFlag )

-- | Options record for @stack dot@ and @stack ls dependencies@

data DotOpts = DotOpts
  { DotOpts -> Bool
includeExternal :: !Bool
    -- ^ Include external dependencies

  , DotOpts -> Bool
includeBase :: !Bool
    -- ^ Include dependencies on base

  , DotOpts -> Maybe Int
dependencyDepth :: !(Maybe Int)
    -- ^ Limit the depth of dependency resolution to (Just n) or continue until

    -- fixpoint

  , DotOpts -> Set PackageName
prune :: !(Set PackageName)
    -- ^ Package names to prune from the graph

  , DotOpts -> [Text]
dotTargets :: [Text]
    -- ^ Stack TARGETs to trace dependencies for

  , DotOpts -> Map ApplyCLIFlag (Map FlagName Bool)
flags :: !(Map ApplyCLIFlag (Map FlagName Bool))
    -- ^ Flags to apply when calculating dependencies

  , DotOpts -> Bool
testTargets :: Bool
    -- ^ Like the "--test" flag for build, affects the meaning of 'dotTargets'.

  , DotOpts -> Bool
benchTargets :: Bool
    -- ^ Like the "--bench" flag for build, affects the meaning of 'dotTargets'.

  , DotOpts -> Bool
globalHints :: Bool
    -- ^ Use global hints instead of relying on an actual GHC installation.

  }