module Distribution.Types.AnnotatedId (
AnnotatedId(..)
) where
import Prelude ()
import Distribution.Compat.Prelude
import Distribution.Package
import Distribution.Types.ComponentName
data AnnotatedId id = AnnotatedId {
forall id. AnnotatedId id -> PackageId
ann_pid :: PackageId,
forall id. AnnotatedId id -> ComponentName
ann_cname :: ComponentName,
forall id. AnnotatedId id -> id
ann_id :: id
}
deriving (Int -> AnnotatedId id -> ShowS
forall id. Show id => Int -> AnnotatedId id -> ShowS
forall id. Show id => [AnnotatedId id] -> ShowS
forall id. Show id => AnnotatedId id -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AnnotatedId id] -> ShowS
$cshowList :: forall id. Show id => [AnnotatedId id] -> ShowS
show :: AnnotatedId id -> String
$cshow :: forall id. Show id => AnnotatedId id -> String
showsPrec :: Int -> AnnotatedId id -> ShowS
$cshowsPrec :: forall id. Show id => Int -> AnnotatedId id -> ShowS
Show)
instance Eq id => Eq (AnnotatedId id) where
AnnotatedId id
x == :: AnnotatedId id -> AnnotatedId id -> Bool
== AnnotatedId id
y = forall id. AnnotatedId id -> id
ann_id AnnotatedId id
x forall a. Eq a => a -> a -> Bool
== forall id. AnnotatedId id -> id
ann_id AnnotatedId id
y
instance Ord id => Ord (AnnotatedId id) where
compare :: AnnotatedId id -> AnnotatedId id -> Ordering
compare AnnotatedId id
x AnnotatedId id
y = forall a. Ord a => a -> a -> Ordering
compare (forall id. AnnotatedId id -> id
ann_id AnnotatedId id
x) (forall id. AnnotatedId id -> id
ann_id AnnotatedId id
y)
instance Package (AnnotatedId id) where
packageId :: AnnotatedId id -> PackageId
packageId = forall id. AnnotatedId id -> PackageId
ann_pid
instance Functor AnnotatedId where
fmap :: forall a b. (a -> b) -> AnnotatedId a -> AnnotatedId b
fmap a -> b
f (AnnotatedId PackageId
pid ComponentName
cn a
x) = forall id. PackageId -> ComponentName -> id -> AnnotatedId id
AnnotatedId PackageId
pid ComponentName
cn (a -> b
f a
x)