module Distribution.Types.AnnotatedId (
    AnnotatedId(..)
) where

import Prelude ()
import Distribution.Compat.Prelude

import Distribution.Package
import Distribution.Types.ComponentName

-- | An 'AnnotatedId' is a 'ComponentId', 'UnitId', etc.
-- which is annotated with some other useful information
-- that is useful for printing to users, etc.
--
-- Invariant: if ann_id x == ann_id y, then ann_pid x == ann_pid y
-- and ann_cname x == ann_cname y
data AnnotatedId id = AnnotatedId {
        AnnotatedId id -> PackageId
ann_pid   :: PackageId,
        AnnotatedId id -> ComponentName
ann_cname :: ComponentName,
        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
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 = 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

instance Functor AnnotatedId where
    fmap :: (a -> b) -> AnnotatedId a -> AnnotatedId b
fmap a -> b
f (AnnotatedId PackageId
pid ComponentName
cn a
x) = PackageId -> ComponentName -> b -> AnnotatedId b
forall id. PackageId -> ComponentName -> id -> AnnotatedId id
AnnotatedId PackageId
pid ComponentName
cn (a -> b
f a
x)