{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE OverloadedStrings #-}
module Distribution.Types.InstalledPackageInfo (
InstalledPackageInfo (..),
emptyInstalledPackageInfo,
mungedPackageId,
mungedPackageName,
AbiDependency (..),
ExposedModule (..),
) where
import Distribution.Compat.Prelude
import Prelude ()
import Distribution.Backpack
import Distribution.Compat.Graph (IsNode (..))
import Distribution.License
import Distribution.ModuleName
import Distribution.Package hiding (installedUnitId)
import Distribution.Types.AbiDependency
import Distribution.Types.ExposedModule
import Distribution.Types.LibraryName
import Distribution.Types.LibraryVisibility
import Distribution.Types.MungedPackageId
import Distribution.Types.MungedPackageName
import Distribution.Version (nullVersion)
import Distribution.Utils.ShortText (ShortText)
import qualified Distribution.Package as Package
import qualified Distribution.SPDX as SPDX
data InstalledPackageInfo
= InstalledPackageInfo {
InstalledPackageInfo -> PackageId
sourcePackageId :: PackageId,
InstalledPackageInfo -> LibraryName
sourceLibName :: LibraryName,
InstalledPackageInfo -> ComponentId
installedComponentId_ :: ComponentId,
InstalledPackageInfo -> LibraryVisibility
libVisibility :: LibraryVisibility,
InstalledPackageInfo -> UnitId
installedUnitId :: UnitId,
InstalledPackageInfo -> [(ModuleName, OpenModule)]
instantiatedWith :: [(ModuleName, OpenModule)],
InstalledPackageInfo -> String
compatPackageKey :: String,
InstalledPackageInfo -> Either License License
license :: Either SPDX.License License,
InstalledPackageInfo -> ShortText
copyright :: !ShortText,
InstalledPackageInfo -> ShortText
maintainer :: !ShortText,
InstalledPackageInfo -> ShortText
author :: !ShortText,
InstalledPackageInfo -> ShortText
stability :: !ShortText,
InstalledPackageInfo -> ShortText
homepage :: !ShortText,
InstalledPackageInfo -> ShortText
pkgUrl :: !ShortText,
InstalledPackageInfo -> ShortText
synopsis :: !ShortText,
InstalledPackageInfo -> ShortText
description :: !ShortText,
InstalledPackageInfo -> ShortText
category :: !ShortText,
InstalledPackageInfo -> AbiHash
abiHash :: AbiHash,
InstalledPackageInfo -> Bool
indefinite :: Bool,
InstalledPackageInfo -> Bool
exposed :: Bool,
InstalledPackageInfo -> [ExposedModule]
exposedModules :: [ExposedModule],
InstalledPackageInfo -> [ModuleName]
hiddenModules :: [ModuleName],
InstalledPackageInfo -> Bool
trusted :: Bool,
InstalledPackageInfo -> [String]
importDirs :: [FilePath],
InstalledPackageInfo -> [String]
libraryDirs :: [FilePath],
InstalledPackageInfo -> [String]
libraryDynDirs :: [FilePath],
InstalledPackageInfo -> String
dataDir :: FilePath,
InstalledPackageInfo -> [String]
hsLibraries :: [String],
:: [String],
:: [String],
InstalledPackageInfo -> [String]
includeDirs :: [FilePath],
InstalledPackageInfo -> [String]
includes :: [String],
InstalledPackageInfo -> [UnitId]
depends :: [UnitId],
InstalledPackageInfo -> [AbiDependency]
abiDepends :: [AbiDependency],
InstalledPackageInfo -> [String]
ccOptions :: [String],
InstalledPackageInfo -> [String]
cxxOptions :: [String],
InstalledPackageInfo -> [String]
ldOptions :: [String],
InstalledPackageInfo -> [String]
frameworkDirs :: [FilePath],
InstalledPackageInfo -> [String]
frameworks :: [String],
InstalledPackageInfo -> [String]
haddockInterfaces :: [FilePath],
InstalledPackageInfo -> [String]
haddockHTMLs :: [FilePath],
InstalledPackageInfo -> Maybe String
pkgRoot :: Maybe FilePath
}
deriving (InstalledPackageInfo -> InstalledPackageInfo -> Bool
(InstalledPackageInfo -> InstalledPackageInfo -> Bool)
-> (InstalledPackageInfo -> InstalledPackageInfo -> Bool)
-> Eq InstalledPackageInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InstalledPackageInfo -> InstalledPackageInfo -> Bool
$c/= :: InstalledPackageInfo -> InstalledPackageInfo -> Bool
== :: InstalledPackageInfo -> InstalledPackageInfo -> Bool
$c== :: InstalledPackageInfo -> InstalledPackageInfo -> Bool
External instance of the constraint type Eq AbiDependency
External instance of the constraint type Eq ExposedModule
External instance of the constraint type Eq License
External instance of the constraint type Eq License
External instance of the constraint type Eq Char
External instance of the constraint type Eq OpenModule
External instance of the constraint type Eq ModuleName
External instance of the constraint type Eq OpenModule
External instance of the constraint type forall a b. (Eq a, Eq b) => Eq (a, b)
External instance of the constraint type forall a. Eq a => Eq (Maybe a)
External instance of the constraint type Eq AbiDependency
External instance of the constraint type forall a. Eq a => Eq [a]
External instance of the constraint type forall a. Eq a => Eq [a]
External instance of the constraint type Eq Char
External instance of the constraint type Eq ModuleName
External instance of the constraint type Eq ExposedModule
External instance of the constraint type Eq Bool
External instance of the constraint type Eq Bool
External instance of the constraint type Eq AbiHash
External instance of the constraint type Eq ShortText
External instance of the constraint type Eq ShortText
External instance of the constraint type Eq License
External instance of the constraint type Eq License
External instance of the constraint type forall a b. (Eq a, Eq b) => Eq (Either a b)
External instance of the constraint type Eq Char
External instance of the constraint type forall a. Eq a => Eq [a]
External instance of the constraint type Eq Char
External instance of the constraint type forall a b. (Eq a, Eq b) => Eq (a, b)
External instance of the constraint type Eq ModuleName
External instance of the constraint type Eq OpenModule
External instance of the constraint type forall a. Eq a => Eq [a]
External instance of the constraint type Eq UnitId
External instance of the constraint type Eq UnitId
External instance of the constraint type Eq LibraryVisibility
External instance of the constraint type Eq ComponentId
External instance of the constraint type Eq LibraryName
External instance of the constraint type Eq PackageId
Eq, (forall x. InstalledPackageInfo -> Rep InstalledPackageInfo x)
-> (forall x. Rep InstalledPackageInfo x -> InstalledPackageInfo)
-> Generic InstalledPackageInfo
forall x. Rep InstalledPackageInfo x -> InstalledPackageInfo
forall x. InstalledPackageInfo -> Rep InstalledPackageInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep InstalledPackageInfo x -> InstalledPackageInfo
$cfrom :: forall x. InstalledPackageInfo -> Rep InstalledPackageInfo x
Generic, Typeable, ReadPrec [InstalledPackageInfo]
ReadPrec InstalledPackageInfo
Int -> ReadS InstalledPackageInfo
ReadS [InstalledPackageInfo]
(Int -> ReadS InstalledPackageInfo)
-> ReadS [InstalledPackageInfo]
-> ReadPrec InstalledPackageInfo
-> ReadPrec [InstalledPackageInfo]
-> Read InstalledPackageInfo
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [InstalledPackageInfo]
$creadListPrec :: ReadPrec [InstalledPackageInfo]
readPrec :: ReadPrec InstalledPackageInfo
$creadPrec :: ReadPrec InstalledPackageInfo
readList :: ReadS [InstalledPackageInfo]
$creadList :: ReadS [InstalledPackageInfo]
readsPrec :: Int -> ReadS InstalledPackageInfo
$creadsPrec :: Int -> ReadS InstalledPackageInfo
External instance of the constraint type Read AbiDependency
External instance of the constraint type Read ExposedModule
External instance of the constraint type Read License
External instance of the constraint type Read License
External instance of the constraint type Read Char
External instance of the constraint type Read OpenModule
External instance of the constraint type Read ModuleName
External instance of the constraint type Read OpenModule
External instance of the constraint type forall a b. (Read a, Read b) => Read (a, b)
External instance of the constraint type forall a. Read a => Read (Maybe a)
External instance of the constraint type Read AbiDependency
External instance of the constraint type forall a. Read a => Read [a]
External instance of the constraint type forall a. Read a => Read [a]
External instance of the constraint type Read Char
External instance of the constraint type Read ModuleName
External instance of the constraint type Read ExposedModule
External instance of the constraint type Read Bool
External instance of the constraint type Read Bool
External instance of the constraint type Read AbiHash
External instance of the constraint type Read ShortText
External instance of the constraint type Read ShortText
External instance of the constraint type Read License
External instance of the constraint type Read License
External instance of the constraint type forall a b. (Read a, Read b) => Read (Either a b)
External instance of the constraint type Read Char
External instance of the constraint type forall a. Read a => Read [a]
External instance of the constraint type Read Char
External instance of the constraint type forall a b. (Read a, Read b) => Read (a, b)
External instance of the constraint type Read ModuleName
External instance of the constraint type Read OpenModule
External instance of the constraint type forall a. Read a => Read [a]
External instance of the constraint type Read UnitId
External instance of the constraint type Read UnitId
External instance of the constraint type Read LibraryVisibility
External instance of the constraint type Read ComponentId
External instance of the constraint type Read LibraryName
External instance of the constraint type Read PackageId
External instance of the constraint type Monad ReadPrec
External instance of the constraint type Monad ReadPrec
Instance of class: Read of the constraint type Read InstalledPackageInfo
Read, Int -> InstalledPackageInfo -> ShowS
[InstalledPackageInfo] -> ShowS
InstalledPackageInfo -> String
(Int -> InstalledPackageInfo -> ShowS)
-> (InstalledPackageInfo -> String)
-> ([InstalledPackageInfo] -> ShowS)
-> Show InstalledPackageInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InstalledPackageInfo] -> ShowS
$cshowList :: [InstalledPackageInfo] -> ShowS
show :: InstalledPackageInfo -> String
$cshow :: InstalledPackageInfo -> String
showsPrec :: Int -> InstalledPackageInfo -> ShowS
$cshowsPrec :: Int -> InstalledPackageInfo -> ShowS
External instance of the constraint type Show AbiDependency
External instance of the constraint type Show ExposedModule
External instance of the constraint type Show License
External instance of the constraint type Show License
External instance of the constraint type Show Char
External instance of the constraint type Show OpenModule
External instance of the constraint type Show ModuleName
External instance of the constraint type Show OpenModule
External instance of the constraint type forall a b. (Show a, Show b) => Show (a, b)
External instance of the constraint type forall a. Show a => Show (Maybe a)
External instance of the constraint type Show AbiDependency
External instance of the constraint type forall a. Show a => Show [a]
External instance of the constraint type forall a. Show a => Show [a]
External instance of the constraint type Show Char
External instance of the constraint type Show ModuleName
External instance of the constraint type Show ExposedModule
External instance of the constraint type Show Bool
External instance of the constraint type Show Bool
External instance of the constraint type Show AbiHash
External instance of the constraint type Show ShortText
External instance of the constraint type Show ShortText
External instance of the constraint type Show License
External instance of the constraint type Show License
External instance of the constraint type forall a b. (Show a, Show b) => Show (Either a b)
External instance of the constraint type Show Char
External instance of the constraint type forall a. Show a => Show [a]
External instance of the constraint type Show Char
External instance of the constraint type forall a b. (Show a, Show b) => Show (a, b)
External instance of the constraint type Show ModuleName
External instance of the constraint type Show OpenModule
External instance of the constraint type forall a. Show a => Show [a]
External instance of the constraint type Show UnitId
External instance of the constraint type Show UnitId
External instance of the constraint type Show LibraryVisibility
External instance of the constraint type Show ComponentId
External instance of the constraint type Show LibraryName
External instance of the constraint type Show PackageId
External instance of the constraint type Ord Int
Show)
instance Binary InstalledPackageInfo
instance Structured InstalledPackageInfo
instance NFData InstalledPackageInfo where rnf :: InstalledPackageInfo -> ()
rnf = InstalledPackageInfo -> ()
forall a. (Generic a, GNFData (Rep a)) => a -> ()
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type NFData PackageId
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type NFData LibraryName
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type NFData ComponentId
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type NFData LibraryVisibility
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type NFData UnitId
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type forall a b. (NFData a, NFData b) => NFData (a, b)
External instance of the constraint type NFData ModuleName
External instance of the constraint type NFData OpenModule
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type NFData Char
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type forall a b. (NFData a, NFData b) => NFData (Either a b)
External instance of the constraint type NFData License
External instance of the constraint type NFData License
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type NFData ShortText
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type NFData ShortText
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type NFData ShortText
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type NFData ShortText
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type NFData ShortText
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type NFData ShortText
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type NFData ShortText
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type NFData ShortText
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type NFData ShortText
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type NFData AbiHash
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type NFData Bool
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type NFData Bool
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type NFData ExposedModule
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type NFData ModuleName
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type NFData Bool
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type NFData Char
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type NFData Char
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type NFData Char
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type NFData Char
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type NFData Char
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type NFData Char
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type NFData Char
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type NFData Char
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type NFData Char
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type NFData UnitId
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type NFData AbiDependency
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type NFData Char
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type NFData Char
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type NFData Char
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type NFData Char
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type NFData Char
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type NFData Char
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type NFData Char
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type forall a. NFData a => NFData (Maybe a)
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type NFData Char
Instance of class: Generic of the constraint type Generic InstalledPackageInfo
genericRnf
instance Package.HasMungedPackageId InstalledPackageInfo where
mungedId :: InstalledPackageInfo -> MungedPackageId
mungedId = InstalledPackageInfo -> MungedPackageId
mungedPackageId
instance Package.Package InstalledPackageInfo where
packageId :: InstalledPackageInfo -> PackageId
packageId = InstalledPackageInfo -> PackageId
sourcePackageId
instance Package.HasUnitId InstalledPackageInfo where
installedUnitId :: InstalledPackageInfo -> UnitId
installedUnitId = InstalledPackageInfo -> UnitId
installedUnitId
instance Package.PackageInstalled InstalledPackageInfo where
installedDepends :: InstalledPackageInfo -> [UnitId]
installedDepends = InstalledPackageInfo -> [UnitId]
depends
instance IsNode InstalledPackageInfo where
type Key InstalledPackageInfo = UnitId
nodeKey :: InstalledPackageInfo -> Key InstalledPackageInfo
nodeKey = InstalledPackageInfo -> Key InstalledPackageInfo
InstalledPackageInfo -> UnitId
installedUnitId
nodeNeighbors :: InstalledPackageInfo -> [Key InstalledPackageInfo]
nodeNeighbors = InstalledPackageInfo -> [Key InstalledPackageInfo]
InstalledPackageInfo -> [UnitId]
depends
mungedPackageId :: InstalledPackageInfo -> MungedPackageId
mungedPackageId :: InstalledPackageInfo -> MungedPackageId
mungedPackageId InstalledPackageInfo
ipi =
MungedPackageName -> Version -> MungedPackageId
MungedPackageId (InstalledPackageInfo -> MungedPackageName
mungedPackageName InstalledPackageInfo
ipi) (InstalledPackageInfo -> Version
forall pkg. Package pkg => pkg -> Version
Instance of class: Package of the constraint type Package InstalledPackageInfo
packageVersion InstalledPackageInfo
ipi)
mungedPackageName :: InstalledPackageInfo -> MungedPackageName
mungedPackageName :: InstalledPackageInfo -> MungedPackageName
mungedPackageName InstalledPackageInfo
ipi = PackageName -> LibraryName -> MungedPackageName
MungedPackageName (InstalledPackageInfo -> PackageName
forall pkg. Package pkg => pkg -> PackageName
Instance of class: Package of the constraint type Package InstalledPackageInfo
packageName InstalledPackageInfo
ipi) (InstalledPackageInfo -> LibraryName
sourceLibName InstalledPackageInfo
ipi)
emptyInstalledPackageInfo :: InstalledPackageInfo
emptyInstalledPackageInfo :: InstalledPackageInfo
emptyInstalledPackageInfo
= InstalledPackageInfo :: PackageId
-> LibraryName
-> ComponentId
-> LibraryVisibility
-> UnitId
-> [(ModuleName, OpenModule)]
-> String
-> Either License License
-> ShortText
-> ShortText
-> ShortText
-> ShortText
-> ShortText
-> ShortText
-> ShortText
-> ShortText
-> ShortText
-> AbiHash
-> Bool
-> Bool
-> [ExposedModule]
-> [ModuleName]
-> Bool
-> [String]
-> [String]
-> [String]
-> String
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [UnitId]
-> [AbiDependency]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> Maybe String
-> InstalledPackageInfo
InstalledPackageInfo {
sourcePackageId :: PackageId
sourcePackageId = PackageName -> Version -> PackageId
PackageIdentifier (String -> PackageName
mkPackageName String
"") Version
nullVersion,
sourceLibName :: LibraryName
sourceLibName = LibraryName
LMainLibName,
installedComponentId_ :: ComponentId
installedComponentId_ = String -> ComponentId
mkComponentId String
"",
installedUnitId :: UnitId
installedUnitId = String -> UnitId
mkUnitId String
"",
instantiatedWith :: [(ModuleName, OpenModule)]
instantiatedWith = [],
compatPackageKey :: String
compatPackageKey = String
"",
license :: Either License License
license = License -> Either License License
forall a b. a -> Either a b
Left License
SPDX.NONE,
copyright :: ShortText
copyright = ShortText
"",
maintainer :: ShortText
maintainer = ShortText
"",
author :: ShortText
author = ShortText
"",
stability :: ShortText
stability = ShortText
"",
homepage :: ShortText
homepage = ShortText
"",
pkgUrl :: ShortText
pkgUrl = ShortText
"",
synopsis :: ShortText
synopsis = ShortText
"",
description :: ShortText
description = ShortText
"",
category :: ShortText
category = ShortText
"",
abiHash :: AbiHash
abiHash = String -> AbiHash
mkAbiHash String
"",
indefinite :: Bool
indefinite = Bool
False,
exposed :: Bool
exposed = Bool
False,
exposedModules :: [ExposedModule]
exposedModules = [],
hiddenModules :: [ModuleName]
hiddenModules = [],
trusted :: Bool
trusted = Bool
False,
importDirs :: [String]
importDirs = [],
libraryDirs :: [String]
libraryDirs = [],
libraryDynDirs :: [String]
libraryDynDirs = [],
dataDir :: String
dataDir = String
"",
hsLibraries :: [String]
hsLibraries = [],
extraLibraries :: [String]
extraLibraries = [],
extraGHCiLibraries :: [String]
extraGHCiLibraries= [],
includeDirs :: [String]
includeDirs = [],
includes :: [String]
includes = [],
depends :: [UnitId]
depends = [],
abiDepends :: [AbiDependency]
abiDepends = [],
ccOptions :: [String]
ccOptions = [],
cxxOptions :: [String]
cxxOptions = [],
ldOptions :: [String]
ldOptions = [],
frameworkDirs :: [String]
frameworkDirs = [],
frameworks :: [String]
frameworks = [],
haddockInterfaces :: [String]
haddockInterfaces = [],
haddockHTMLs :: [String]
haddockHTMLs = [],
pkgRoot :: Maybe String
pkgRoot = Maybe String
forall a. Maybe a
Nothing,
libVisibility :: LibraryVisibility
libVisibility = LibraryVisibility
LibraryVisibilityPrivate
}