{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE PatternSynonyms #-}

module Distribution.Simple.Build.Inputs
  ( -- * Inputs of actions for building components
    PreBuildComponentInputs (..)

    -- * Queries over the component being built
  , buildVerbosity
  , buildComponent
  , buildIsLib
  , buildCLBI
  , buildBI
  , buildCompiler

    -- * Re-exports
  , BuildingWhat (..)
  , LocalBuildInfo (..)
  , TargetInfo (..)
  , buildingWhatVerbosity
  , buildingWhatDistPref
  )
where

import Distribution.Simple.Compiler
import Distribution.Simple.Setup (BuildingWhat (..), buildingWhatDistPref, buildingWhatVerbosity)
import Distribution.Types.BuildInfo
import Distribution.Types.Component
import Distribution.Types.ComponentLocalBuildInfo
import Distribution.Types.LocalBuildInfo
import Distribution.Types.TargetInfo
import Distribution.Verbosity

-- | The information required for a build computation which is available right
-- before building each component, i.e. the pre-build component inputs.
data PreBuildComponentInputs = PreBuildComponentInputs
  { PreBuildComponentInputs -> BuildingWhat
buildingWhat :: BuildingWhat
  -- ^ What kind of build are we doing?
  , PreBuildComponentInputs -> LocalBuildInfo
localBuildInfo :: LocalBuildInfo
  -- ^ Information about the package
  , PreBuildComponentInputs -> TargetInfo
targetInfo :: TargetInfo
  -- ^ Information about an individual component
  }

-- | Get the @'Verbosity'@ from the context the component being built is in.
buildVerbosity :: PreBuildComponentInputs -> Verbosity
buildVerbosity :: PreBuildComponentInputs -> Verbosity
buildVerbosity = BuildingWhat -> Verbosity
buildingWhatVerbosity (BuildingWhat -> Verbosity)
-> (PreBuildComponentInputs -> BuildingWhat)
-> PreBuildComponentInputs
-> Verbosity
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PreBuildComponentInputs -> BuildingWhat
buildingWhat

-- | Get the @'Component'@ being built.
buildComponent :: PreBuildComponentInputs -> Component
buildComponent :: PreBuildComponentInputs -> Component
buildComponent = TargetInfo -> Component
targetComponent (TargetInfo -> Component)
-> (PreBuildComponentInputs -> TargetInfo)
-> PreBuildComponentInputs
-> Component
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PreBuildComponentInputs -> TargetInfo
targetInfo

-- | Is the @'Component'@ being built a @'Library'@?
buildIsLib :: PreBuildComponentInputs -> Bool
buildIsLib :: PreBuildComponentInputs -> Bool
buildIsLib = do
  component <- PreBuildComponentInputs -> Component
buildComponent
  let isLib
        | CLib{} <- Component
component = Bool
True
        | Bool
otherwise = Bool
False
  return isLib
{-# INLINE buildIsLib #-}

-- | Get the @'ComponentLocalBuildInfo'@ for the component being built.
buildCLBI :: PreBuildComponentInputs -> ComponentLocalBuildInfo
buildCLBI :: PreBuildComponentInputs -> ComponentLocalBuildInfo
buildCLBI = TargetInfo -> ComponentLocalBuildInfo
targetCLBI (TargetInfo -> ComponentLocalBuildInfo)
-> (PreBuildComponentInputs -> TargetInfo)
-> PreBuildComponentInputs
-> ComponentLocalBuildInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PreBuildComponentInputs -> TargetInfo
targetInfo

-- | Get the @'BuildInfo'@ of the component being built.
buildBI :: PreBuildComponentInputs -> BuildInfo
buildBI :: PreBuildComponentInputs -> BuildInfo
buildBI = Component -> BuildInfo
componentBuildInfo (Component -> BuildInfo)
-> (PreBuildComponentInputs -> Component)
-> PreBuildComponentInputs
-> BuildInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PreBuildComponentInputs -> Component
buildComponent

-- | Get the @'Compiler'@ being used to build the component.
buildCompiler :: PreBuildComponentInputs -> Compiler
buildCompiler :: PreBuildComponentInputs -> Compiler
buildCompiler = LocalBuildInfo -> Compiler
compiler (LocalBuildInfo -> Compiler)
-> (PreBuildComponentInputs -> LocalBuildInfo)
-> PreBuildComponentInputs
-> Compiler
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PreBuildComponentInputs -> LocalBuildInfo
localBuildInfo