{-# LANGUAGE DeriveGeneric #-}
module Distribution.Client.Types.ConfiguredId (
    InstalledPackageId,
    ConfiguredId (..),
    annotatedIdToConfiguredId,
    HasConfiguredId (..),
) where
import Distribution.Client.Compat.Prelude
import Prelude ()
import Distribution.InstalledPackageInfo (InstalledPackageInfo, sourceComponentName, installedComponentId)
import Distribution.Package              (Package (..))
import Distribution.Types.AnnotatedId    (AnnotatedId (..))
import Distribution.Types.ComponentId    (ComponentId)
import Distribution.Types.ComponentName  (ComponentName)
import Distribution.Types.PackageId      (PackageId)
type InstalledPackageId = ComponentId
data ConfiguredId = ConfiguredId {
    ConfiguredId -> PackageId
confSrcId  :: PackageId
  , ConfiguredId -> Maybe ComponentName
confCompName :: Maybe ComponentName
  , ConfiguredId -> ComponentId
confInstId :: ComponentId
  }
  deriving (ConfiguredId -> ConfiguredId -> Bool
(ConfiguredId -> ConfiguredId -> Bool)
-> (ConfiguredId -> ConfiguredId -> Bool) -> Eq ConfiguredId
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ConfiguredId -> ConfiguredId -> Bool
$c/= :: ConfiguredId -> ConfiguredId -> Bool
== :: ConfiguredId -> ConfiguredId -> Bool
$c== :: ConfiguredId -> ConfiguredId -> Bool
Eq, Eq ConfiguredId
Eq ConfiguredId
-> (ConfiguredId -> ConfiguredId -> Ordering)
-> (ConfiguredId -> ConfiguredId -> Bool)
-> (ConfiguredId -> ConfiguredId -> Bool)
-> (ConfiguredId -> ConfiguredId -> Bool)
-> (ConfiguredId -> ConfiguredId -> Bool)
-> (ConfiguredId -> ConfiguredId -> ConfiguredId)
-> (ConfiguredId -> ConfiguredId -> ConfiguredId)
-> Ord ConfiguredId
ConfiguredId -> ConfiguredId -> Bool
ConfiguredId -> ConfiguredId -> Ordering
ConfiguredId -> ConfiguredId -> ConfiguredId
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ConfiguredId -> ConfiguredId -> ConfiguredId
$cmin :: ConfiguredId -> ConfiguredId -> ConfiguredId
max :: ConfiguredId -> ConfiguredId -> ConfiguredId
$cmax :: ConfiguredId -> ConfiguredId -> ConfiguredId
>= :: ConfiguredId -> ConfiguredId -> Bool
$c>= :: ConfiguredId -> ConfiguredId -> Bool
> :: ConfiguredId -> ConfiguredId -> Bool
$c> :: ConfiguredId -> ConfiguredId -> Bool
<= :: ConfiguredId -> ConfiguredId -> Bool
$c<= :: ConfiguredId -> ConfiguredId -> Bool
< :: ConfiguredId -> ConfiguredId -> Bool
$c< :: ConfiguredId -> ConfiguredId -> Bool
compare :: ConfiguredId -> ConfiguredId -> Ordering
$ccompare :: ConfiguredId -> ConfiguredId -> Ordering
$cp1Ord :: Eq ConfiguredId
Ord, (forall x. ConfiguredId -> Rep ConfiguredId x)
-> (forall x. Rep ConfiguredId x -> ConfiguredId)
-> Generic ConfiguredId
forall x. Rep ConfiguredId x -> ConfiguredId
forall x. ConfiguredId -> Rep ConfiguredId x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ConfiguredId x -> ConfiguredId
$cfrom :: forall x. ConfiguredId -> Rep ConfiguredId x
Generic)
annotatedIdToConfiguredId :: AnnotatedId ComponentId -> ConfiguredId
annotatedIdToConfiguredId :: AnnotatedId ComponentId -> ConfiguredId
annotatedIdToConfiguredId AnnotatedId ComponentId
aid = ConfiguredId :: PackageId -> Maybe ComponentName -> ComponentId -> ConfiguredId
ConfiguredId {
        confSrcId :: PackageId
confSrcId    = AnnotatedId ComponentId -> PackageId
forall id. AnnotatedId id -> PackageId
ann_pid AnnotatedId ComponentId
aid,
        confCompName :: Maybe ComponentName
confCompName = ComponentName -> Maybe ComponentName
forall a. a -> Maybe a
Just (AnnotatedId ComponentId -> ComponentName
forall id. AnnotatedId id -> ComponentName
ann_cname AnnotatedId ComponentId
aid),
        confInstId :: ComponentId
confInstId   = AnnotatedId ComponentId -> ComponentId
forall id. AnnotatedId id -> id
ann_id AnnotatedId ComponentId
aid
    }
instance Binary ConfiguredId
instance Structured ConfiguredId
instance Show ConfiguredId where
  show :: ConfiguredId -> String
show ConfiguredId
cid = ComponentId -> String
forall a. Show a => a -> String
show (ConfiguredId -> ComponentId
confInstId ConfiguredId
cid)
instance Package ConfiguredId where
  packageId :: ConfiguredId -> PackageId
packageId = ConfiguredId -> PackageId
confSrcId
class HasConfiguredId a where
    configuredId :: a -> ConfiguredId
instance HasConfiguredId InstalledPackageInfo where
    configuredId :: InstalledPackageInfo -> ConfiguredId
configuredId InstalledPackageInfo
ipkg = PackageId -> Maybe ComponentName -> ComponentId -> ConfiguredId
ConfiguredId (InstalledPackageInfo -> PackageId
forall pkg. Package pkg => pkg -> PackageId
packageId InstalledPackageInfo
ipkg)
                            (ComponentName -> Maybe ComponentName
forall a. a -> Maybe a
Just (InstalledPackageInfo -> ComponentName
sourceComponentName InstalledPackageInfo
ipkg))
                            (InstalledPackageInfo -> ComponentId
installedComponentId InstalledPackageInfo
ipkg)