{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE PatternSynonyms #-}
module Distribution.Simple.Build.Inputs
  ( 
    PreBuildComponentInputs (..)
    
  , buildVerbosity
  , buildComponent
  , buildIsLib
  , buildCLBI
  , buildBI
  , buildCompiler
    
  , BuildingWhat (..)
  , LocalBuildInfo (..)
  , TargetInfo (..)
  , buildingWhatCommonFlags
  , buildingWhatVerbosity
  , buildingWhatWorkingDir
  , buildingWhatDistPref
  )
where
import Distribution.Simple.Compiler
import Distribution.Simple.Setup hiding
  ( BuildFlags (buildVerbosity)
  )
import Distribution.Types.BuildInfo
import Distribution.Types.Component
import Distribution.Types.ComponentLocalBuildInfo
import Distribution.Types.LocalBuildInfo
import Distribution.Types.TargetInfo
import Distribution.Verbosity
data PreBuildComponentInputs = PreBuildComponentInputs
  { PreBuildComponentInputs -> BuildingWhat
buildingWhat :: BuildingWhat
  
  , PreBuildComponentInputs -> LocalBuildInfo
localBuildInfo :: LocalBuildInfo
  
  , PreBuildComponentInputs -> TargetInfo
targetInfo :: TargetInfo
  
  }
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
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
buildIsLib :: PreBuildComponentInputs -> Bool
buildIsLib :: PreBuildComponentInputs -> Bool
buildIsLib = do
  Component
component <- PreBuildComponentInputs -> Component
buildComponent
  let isLib :: Bool
isLib
        | CLib{} <- Component
component = Bool
True
        | Bool
otherwise = Bool
False
  Bool -> PreBuildComponentInputs -> Bool
forall a. a -> PreBuildComponentInputs -> a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
isLib
{-# INLINE buildIsLib #-}
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
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
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