{-# 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
data GivenComponent =
GivenComponent
{ GivenComponent -> PackageName
givenComponentPackage :: PackageName
, GivenComponent -> LibraryName
givenComponentName :: LibraryName
, GivenComponent -> ComponentId
givenComponentId :: ComponentId }
deriving (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]
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
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
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