{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
module Distribution.Types.GivenComponent (
  GivenComponent(..)
) where

import Distribution.Compat.Prelude

import Distribution.Types.ComponentId
import Distribution.Types.LibraryName
import Distribution.Types.PackageName

-- | A 'GivenComponent' represents a library depended on and explicitly
-- specified by the user/client with @--dependency@
--
-- It enables Cabal to know which 'ComponentId' to associate with a library
--
-- @since 2.3.0.0
data GivenComponent =
  GivenComponent
    { GivenComponent -> PackageName
givenComponentPackage :: PackageName
    , GivenComponent -> LibraryName
givenComponentName    :: LibraryName -- --dependency is for libraries
                                           -- only, not for any component
    , GivenComponent -> ComponentId
givenComponentId      :: ComponentId }
  deriving ((forall x. GivenComponent -> Rep GivenComponent x)
-> (forall x. Rep GivenComponent x -> GivenComponent)
-> Generic GivenComponent
forall x. Rep GivenComponent x -> GivenComponent
forall x. GivenComponent -> Rep GivenComponent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GivenComponent x -> GivenComponent
$cfrom :: forall x. GivenComponent -> Rep GivenComponent x
Generic, ReadPrec [GivenComponent]
ReadPrec GivenComponent
Int -> ReadS GivenComponent
ReadS [GivenComponent]
(Int -> ReadS GivenComponent)
-> ReadS [GivenComponent]
-> ReadPrec GivenComponent
-> ReadPrec [GivenComponent]
-> Read GivenComponent
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GivenComponent]
$creadListPrec :: ReadPrec [GivenComponent]
readPrec :: ReadPrec GivenComponent
$creadPrec :: ReadPrec GivenComponent
readList :: ReadS [GivenComponent]
$creadList :: ReadS [GivenComponent]
readsPrec :: Int -> ReadS GivenComponent
$creadsPrec :: Int -> ReadS GivenComponent
Read, Int -> GivenComponent -> ShowS
[GivenComponent] -> ShowS
GivenComponent -> String
(Int -> GivenComponent -> ShowS)
-> (GivenComponent -> String)
-> ([GivenComponent] -> ShowS)
-> Show GivenComponent
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GivenComponent] -> ShowS
$cshowList :: [GivenComponent] -> ShowS
show :: GivenComponent -> String
$cshow :: GivenComponent -> String
showsPrec :: Int -> GivenComponent -> ShowS
$cshowsPrec :: Int -> GivenComponent -> ShowS
Show, GivenComponent -> GivenComponent -> Bool
(GivenComponent -> GivenComponent -> Bool)
-> (GivenComponent -> GivenComponent -> Bool) -> Eq GivenComponent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GivenComponent -> GivenComponent -> Bool
$c/= :: GivenComponent -> GivenComponent -> Bool
== :: GivenComponent -> GivenComponent -> Bool
$c== :: GivenComponent -> GivenComponent -> Bool
Eq, Typeable)

instance Binary GivenComponent
instance Structured GivenComponent