{-# LANGUAGE DeriveFunctor #-}
module Distribution.Types.AnnotatedId
( AnnotatedId (..)
) where
import Distribution.Compat.Prelude
import 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
[AnnotatedId id] -> ShowS
AnnotatedId id -> String
(Int -> AnnotatedId id -> ShowS)
-> (AnnotatedId id -> String)
-> ([AnnotatedId id] -> ShowS)
-> Show (AnnotatedId id)
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
$cshowsPrec :: forall id. Show id => Int -> AnnotatedId id -> ShowS
showsPrec :: Int -> AnnotatedId id -> ShowS
$cshow :: forall id. Show id => AnnotatedId id -> String
show :: AnnotatedId id -> String
$cshowList :: forall id. Show id => [AnnotatedId id] -> ShowS
showList :: [AnnotatedId id] -> ShowS
Show, (forall a b. (a -> b) -> AnnotatedId a -> AnnotatedId b)
-> (forall a b. a -> AnnotatedId b -> AnnotatedId a)
-> Functor AnnotatedId
forall a b. a -> AnnotatedId b -> AnnotatedId a
forall a b. (a -> b) -> AnnotatedId a -> AnnotatedId b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b. (a -> b) -> AnnotatedId a -> AnnotatedId b
fmap :: forall a b. (a -> b) -> AnnotatedId a -> AnnotatedId b
$c<$ :: forall a b. a -> AnnotatedId b -> AnnotatedId a
<$ :: forall a b. a -> AnnotatedId b -> AnnotatedId a
Functor)
instance Eq id => Eq (AnnotatedId id) where
AnnotatedId id
x == :: AnnotatedId id -> AnnotatedId id -> Bool
== AnnotatedId id
y = AnnotatedId id -> id
forall id. AnnotatedId id -> id
ann_id AnnotatedId id
x id -> id -> Bool
forall a. Eq a => a -> a -> Bool
== AnnotatedId id -> id
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 = id -> id -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (AnnotatedId id -> id
forall id. AnnotatedId id -> id
ann_id AnnotatedId id
x) (AnnotatedId id -> id
forall id. AnnotatedId id -> id
ann_id AnnotatedId id
y)
instance Package (AnnotatedId id) where
packageId :: AnnotatedId id -> PackageId
packageId = AnnotatedId id -> PackageId
forall id. AnnotatedId id -> PackageId
ann_pid