{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
module Distribution.Types.Library (
Library(..),
emptyLibrary,
explicitLibModules,
libModulesAutogen,
) where
import Distribution.Compat.Prelude
import Prelude ()
import Distribution.ModuleName
import Distribution.Types.BuildInfo
import Distribution.Types.LibraryVisibility
import Distribution.Types.ModuleReexport
import Distribution.Types.LibraryName
import qualified Distribution.Types.BuildInfo.Lens as L
data Library = Library
{ Library -> LibraryName
libName :: LibraryName
, Library -> [ModuleName]
exposedModules :: [ModuleName]
, Library -> [ModuleReexport]
reexportedModules :: [ModuleReexport]
, Library -> [ModuleName]
signatures :: [ModuleName]
, Library -> Bool
libExposed :: Bool
, Library -> LibraryVisibility
libVisibility :: LibraryVisibility
, Library -> BuildInfo
libBuildInfo :: BuildInfo
}
deriving ((forall x. Library -> Rep Library x)
-> (forall x. Rep Library x -> Library) -> Generic Library
forall x. Rep Library x -> Library
forall x. Library -> Rep Library x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Library x -> Library
$cfrom :: forall x. Library -> Rep Library x
Generic, Int -> Library -> ShowS
[Library] -> ShowS
Library -> String
(Int -> Library -> ShowS)
-> (Library -> String) -> ([Library] -> ShowS) -> Show Library
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Library] -> ShowS
$cshowList :: [Library] -> ShowS
show :: Library -> String
$cshow :: Library -> String
showsPrec :: Int -> Library -> ShowS
$cshowsPrec :: Int -> Library -> ShowS
External instance of the constraint type Show ModuleReexport
External instance of the constraint type Show ModuleName
External instance of the constraint type Show BuildInfo
External instance of the constraint type Show LibraryVisibility
External instance of the constraint type Show Bool
External instance of the constraint type Show ModuleReexport
External instance of the constraint type Show ModuleName
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 ModuleName
External instance of the constraint type Show LibraryName
External instance of the constraint type Ord Int
Show, Library -> Library -> Bool
(Library -> Library -> Bool)
-> (Library -> Library -> Bool) -> Eq Library
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Library -> Library -> Bool
$c/= :: Library -> Library -> Bool
== :: Library -> Library -> Bool
$c== :: Library -> Library -> Bool
External instance of the constraint type Eq ModuleReexport
External instance of the constraint type Eq ModuleName
External instance of the constraint type Eq BuildInfo
External instance of the constraint type Eq LibraryVisibility
External instance of the constraint type Eq Bool
External instance of the constraint type Eq ModuleReexport
External instance of the constraint type Eq ModuleName
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 ModuleName
External instance of the constraint type Eq LibraryName
Eq, ReadPrec [Library]
ReadPrec Library
Int -> ReadS Library
ReadS [Library]
(Int -> ReadS Library)
-> ReadS [Library]
-> ReadPrec Library
-> ReadPrec [Library]
-> Read Library
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Library]
$creadListPrec :: ReadPrec [Library]
readPrec :: ReadPrec Library
$creadPrec :: ReadPrec Library
readList :: ReadS [Library]
$creadList :: ReadS [Library]
readsPrec :: Int -> ReadS Library
$creadsPrec :: Int -> ReadS Library
External instance of the constraint type Read ModuleReexport
External instance of the constraint type Read ModuleName
External instance of the constraint type Read BuildInfo
External instance of the constraint type Read LibraryVisibility
External instance of the constraint type Read Bool
External instance of the constraint type Read ModuleReexport
External instance of the constraint type Read ModuleName
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 ModuleName
External instance of the constraint type Read LibraryName
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 Library
Read, Typeable, Typeable Library
DataType
Constr
Typeable Library
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Library -> c Library)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Library)
-> (Library -> Constr)
-> (Library -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Library))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Library))
-> ((forall b. Data b => b -> b) -> Library -> Library)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Library -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Library -> r)
-> (forall u. (forall d. Data d => d -> u) -> Library -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Library -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Library -> m Library)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Library -> m Library)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Library -> m Library)
-> Data Library
Library -> DataType
Library -> Constr
(forall b. Data b => b -> b) -> Library -> Library
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Library -> c Library
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Library
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Library -> u
forall u. (forall d. Data d => d -> u) -> Library -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Library -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Library -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Library -> m Library
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Library -> m Library
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Library
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Library -> c Library
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Library)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Library)
$cLibrary :: Constr
$tLibrary :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Library -> m Library
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Library -> m Library
gmapMp :: (forall d. Data d => d -> m d) -> Library -> m Library
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Library -> m Library
gmapM :: (forall d. Data d => d -> m d) -> Library -> m Library
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Library -> m Library
gmapQi :: Int -> (forall d. Data d => d -> u) -> Library -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Library -> u
gmapQ :: (forall d. Data d => d -> u) -> Library -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Library -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Library -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Library -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Library -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Library -> r
gmapT :: (forall b. Data b => b -> b) -> Library -> Library
$cgmapT :: (forall b. Data b => b -> b) -> Library -> Library
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Library)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Library)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c Library)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Library)
dataTypeOf :: Library -> DataType
$cdataTypeOf :: Library -> DataType
toConstr :: Library -> Constr
$ctoConstr :: Library -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Library
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Library
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Library -> c Library
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Library -> c Library
External instance of the constraint type Data ModuleReexport
External instance of the constraint type Data ModuleName
External instance of the constraint type Data ModuleReexport
External instance of the constraint type Data ModuleName
External instance of the constraint type forall a. Data a => Data [a]
External instance of the constraint type Data ModuleName
External instance of the constraint type Data LibraryName
External instance of the constraint type Data ModuleReexport
External instance of the constraint type Data ModuleName
External instance of the constraint type forall a. Data a => Data [a]
External instance of the constraint type forall a. Data a => Data [a]
External instance of the constraint type Data ModuleName
External instance of the constraint type Data Bool
External instance of the constraint type Data LibraryVisibility
External instance of the constraint type Data BuildInfo
Data)
instance L.HasBuildInfo Library where
buildInfo :: LensLike f Library Library BuildInfo BuildInfo
buildInfo BuildInfo -> f BuildInfo
f Library
l = (\BuildInfo
x -> Library
l { libBuildInfo :: BuildInfo
libBuildInfo = BuildInfo
x }) (BuildInfo -> Library) -> f BuildInfo -> f Library
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Functor f
<$> BuildInfo -> f BuildInfo
f (Library -> BuildInfo
libBuildInfo Library
l)
instance Binary Library
instance Structured Library
instance NFData Library where rnf :: Library -> ()
rnf = Library -> ()
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 :: * -> *) 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 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 forall a. NFData a => NFData [a]
External instance of the constraint type NFData ModuleReexport
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 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 BuildInfo
Instance of class: Generic of the constraint type Generic Library
genericRnf
emptyLibrary :: Library
emptyLibrary :: Library
emptyLibrary = Library :: LibraryName
-> [ModuleName]
-> [ModuleReexport]
-> [ModuleName]
-> Bool
-> LibraryVisibility
-> BuildInfo
-> Library
Library
{ libName :: LibraryName
libName = LibraryName
LMainLibName
, exposedModules :: [ModuleName]
exposedModules = [ModuleName]
forall a. Monoid a => a
External instance of the constraint type forall a. Monoid [a]
mempty
, reexportedModules :: [ModuleReexport]
reexportedModules = [ModuleReexport]
forall a. Monoid a => a
External instance of the constraint type forall a. Monoid [a]
mempty
, signatures :: [ModuleName]
signatures = [ModuleName]
forall a. Monoid a => a
External instance of the constraint type forall a. Monoid [a]
mempty
, libExposed :: Bool
libExposed = Bool
True
, libVisibility :: LibraryVisibility
libVisibility = LibraryVisibility
forall a. Monoid a => a
External instance of the constraint type Monoid LibraryVisibility
mempty
, libBuildInfo :: BuildInfo
libBuildInfo = BuildInfo
forall a. Monoid a => a
External instance of the constraint type Monoid BuildInfo
mempty
}
instance Monoid Library where
mempty :: Library
mempty = Library
emptyLibrary
mappend :: Library -> Library -> Library
mappend = Library -> Library -> Library
forall a. Semigroup a => a -> a -> a
Instance of class: Semigroup of the constraint type Semigroup Library
(<>)
instance Semigroup Library where
Library
a <> :: Library -> Library -> Library
<> Library
b = Library :: LibraryName
-> [ModuleName]
-> [ModuleReexport]
-> [ModuleName]
-> Bool
-> LibraryVisibility
-> BuildInfo
-> Library
Library
{ libName :: LibraryName
libName = LibraryName -> LibraryName -> LibraryName
combineLibraryName (Library -> LibraryName
libName Library
a) (Library -> LibraryName
libName Library
b)
, exposedModules :: [ModuleName]
exposedModules = (Library -> [ModuleName]) -> [ModuleName]
forall {a}. Monoid a => (Library -> a) -> a
External instance of the constraint type forall a. Monoid [a]
combine Library -> [ModuleName]
exposedModules
, reexportedModules :: [ModuleReexport]
reexportedModules = (Library -> [ModuleReexport]) -> [ModuleReexport]
forall {a}. Monoid a => (Library -> a) -> a
External instance of the constraint type forall a. Monoid [a]
combine Library -> [ModuleReexport]
reexportedModules
, signatures :: [ModuleName]
signatures = (Library -> [ModuleName]) -> [ModuleName]
forall {a}. Monoid a => (Library -> a) -> a
External instance of the constraint type forall a. Monoid [a]
combine Library -> [ModuleName]
signatures
, libExposed :: Bool
libExposed = Library -> Bool
libExposed Library
a Bool -> Bool -> Bool
&& Library -> Bool
libExposed Library
b
, libVisibility :: LibraryVisibility
libVisibility = (Library -> LibraryVisibility) -> LibraryVisibility
forall {a}. Monoid a => (Library -> a) -> a
External instance of the constraint type Monoid LibraryVisibility
combine Library -> LibraryVisibility
libVisibility
, libBuildInfo :: BuildInfo
libBuildInfo = (Library -> BuildInfo) -> BuildInfo
forall {a}. Monoid a => (Library -> a) -> a
External instance of the constraint type Monoid BuildInfo
combine Library -> BuildInfo
libBuildInfo
}
where combine :: (Library -> a) -> a
combine Library -> a
field = Library -> a
field Library
a a -> a -> a
forall a. Monoid a => a -> a -> a
Evidence bound by a type signature of the constraint type Monoid a
`mappend` Library -> a
field Library
b
explicitLibModules :: Library -> [ModuleName]
explicitLibModules :: Library -> [ModuleName]
explicitLibModules Library
lib = Library -> [ModuleName]
exposedModules Library
lib
[ModuleName] -> [ModuleName] -> [ModuleName]
forall a. [a] -> [a] -> [a]
++ BuildInfo -> [ModuleName]
otherModules (Library -> BuildInfo
libBuildInfo Library
lib)
[ModuleName] -> [ModuleName] -> [ModuleName]
forall a. [a] -> [a] -> [a]
++ Library -> [ModuleName]
signatures Library
lib
libModulesAutogen :: Library -> [ModuleName]
libModulesAutogen :: Library -> [ModuleName]
libModulesAutogen Library
lib = BuildInfo -> [ModuleName]
autogenModules (Library -> BuildInfo
libBuildInfo Library
lib)
combineLibraryName :: LibraryName -> LibraryName -> LibraryName
combineLibraryName :: LibraryName -> LibraryName -> LibraryName
combineLibraryName l :: LibraryName
l@(LSubLibName UnqualComponentName
_) LibraryName
_ = LibraryName
l
combineLibraryName LibraryName
_ LibraryName
l = LibraryName
l