{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE TypeFamilies #-}

module Distribution.Types.TargetInfo
  ( TargetInfo (..)
  ) where

import Distribution.Compat.Prelude
import Prelude ()

import Distribution.Types.Component
import Distribution.Types.ComponentLocalBuildInfo
import Distribution.Types.UnitId

import Distribution.Compat.Graph (IsNode (..))

-- | The 'TargetInfo' contains all the information necessary to build a
-- specific target (e.g., component/module/file) in a package.  In
-- principle, one can get the 'Component' from a
-- 'ComponentLocalBuildInfo' and 'LocalBuildInfo', but it is much more
-- convenient to have the component in hand.
data TargetInfo = TargetInfo
  { TargetInfo -> ComponentLocalBuildInfo
targetCLBI :: ComponentLocalBuildInfo
  , TargetInfo -> Component
targetComponent :: Component
  -- TODO: BuildTargets supporting parsing these is dumb,
  -- we don't have support for compiling single modules or
  -- file paths. Accommodating it now is premature
  -- generalization.  Figure it out later.
  -- targetSub       :: Maybe (Either ModuleName FilePath)
  }
  deriving ((forall x. TargetInfo -> Rep TargetInfo x)
-> (forall x. Rep TargetInfo x -> TargetInfo) -> Generic TargetInfo
forall x. Rep TargetInfo x -> TargetInfo
forall x. TargetInfo -> Rep TargetInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. TargetInfo -> Rep TargetInfo x
from :: forall x. TargetInfo -> Rep TargetInfo x
$cto :: forall x. Rep TargetInfo x -> TargetInfo
to :: forall x. Rep TargetInfo x -> TargetInfo
Generic, Int -> TargetInfo -> ShowS
[TargetInfo] -> ShowS
TargetInfo -> String
(Int -> TargetInfo -> ShowS)
-> (TargetInfo -> String)
-> ([TargetInfo] -> ShowS)
-> Show TargetInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TargetInfo -> ShowS
showsPrec :: Int -> TargetInfo -> ShowS
$cshow :: TargetInfo -> String
show :: TargetInfo -> String
$cshowList :: [TargetInfo] -> ShowS
showList :: [TargetInfo] -> ShowS
Show)

instance Binary TargetInfo
instance Structured TargetInfo

instance IsNode TargetInfo where
  type Key TargetInfo = UnitId
  nodeKey :: TargetInfo -> Key TargetInfo
nodeKey = ComponentLocalBuildInfo -> Key ComponentLocalBuildInfo
ComponentLocalBuildInfo -> UnitId
forall a. IsNode a => a -> Key a
nodeKey (ComponentLocalBuildInfo -> UnitId)
-> (TargetInfo -> ComponentLocalBuildInfo) -> TargetInfo -> UnitId
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TargetInfo -> ComponentLocalBuildInfo
targetCLBI
  nodeNeighbors :: TargetInfo -> [Key TargetInfo]
nodeNeighbors = ComponentLocalBuildInfo -> [Key ComponentLocalBuildInfo]
ComponentLocalBuildInfo -> [UnitId]
forall a. IsNode a => a -> [Key a]
nodeNeighbors (ComponentLocalBuildInfo -> [UnitId])
-> (TargetInfo -> ComponentLocalBuildInfo)
-> TargetInfo
-> [UnitId]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TargetInfo -> ComponentLocalBuildInfo
targetCLBI