Cabal-2.0.0.2: A framework for packaging Haskell software

Safe HaskellNone
LanguageHaskell2010

Distribution.Types.ForeignLib

Synopsis

Documentation

data ForeignLib Source #

A foreign library stanza is like a library stanza, except that the built code is intended for consumption by a non-Haskell client.

Constructors

ForeignLib 

Fields

Instances

Eq ForeignLib # 
Data ForeignLib # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ForeignLib -> c ForeignLib Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ForeignLib Source #

toConstr :: ForeignLib -> Constr Source #

dataTypeOf :: ForeignLib -> DataType Source #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ForeignLib) Source #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ForeignLib) Source #

gmapT :: (forall b. Data b => b -> b) -> ForeignLib -> ForeignLib Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ForeignLib -> r Source #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ForeignLib -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> ForeignLib -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ForeignLib -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ForeignLib -> m ForeignLib Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ForeignLib -> m ForeignLib Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ForeignLib -> m ForeignLib Source #

Read ForeignLib # 
Show ForeignLib # 
Generic ForeignLib # 

Associated Types

type Rep ForeignLib :: * -> * Source #

Semigroup ForeignLib # 
Monoid ForeignLib # 
Binary ForeignLib # 
type Rep ForeignLib # 

emptyForeignLib :: ForeignLib Source #

An empty foreign library.

foreignLibModules :: ForeignLib -> [ModuleName] Source #

Modules defined by a foreign library.

foreignLibIsShared :: ForeignLib -> Bool Source #

Is the foreign library shared?

foreignLibVersion :: ForeignLib -> OS -> [Int] Source #

Get a version number for a foreign library. If we're on Linux, and a Linux version is specified, use that. If we're on Linux, and libtool-style version-info is specified, translate that field into appropriate version numbers. Otherwise, this feature is unsupported so we don't return any version data.

data LibVersionInfo Source #

Instances

Eq LibVersionInfo # 
Data LibVersionInfo # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LibVersionInfo -> c LibVersionInfo Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LibVersionInfo Source #

toConstr :: LibVersionInfo -> Constr Source #

dataTypeOf :: LibVersionInfo -> DataType Source #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c LibVersionInfo) Source #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LibVersionInfo) Source #

gmapT :: (forall b. Data b => b -> b) -> LibVersionInfo -> LibVersionInfo Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LibVersionInfo -> r Source #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LibVersionInfo -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> LibVersionInfo -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LibVersionInfo -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LibVersionInfo -> m LibVersionInfo Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LibVersionInfo -> m LibVersionInfo Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LibVersionInfo -> m LibVersionInfo Source #

Ord LibVersionInfo # 
Read LibVersionInfo # 
Show LibVersionInfo # 
Generic LibVersionInfo # 
Binary LibVersionInfo # 
Text LibVersionInfo # 
type Rep LibVersionInfo # 

mkLibVersionInfo :: (Int, Int, Int) -> LibVersionInfo Source #

Construct LibVersionInfo from (current, revision, age) numbers.

For instance, mkLibVersionInfo (3,0,0) constructs a LibVersionInfo representing the version-info 3:0:0.

All version components must be non-negative.

libVersionInfoCRA :: LibVersionInfo -> (Int, Int, Int) Source #

From a given LibVersionInfo, extract the (current, revision, age) numbers.

libVersionNumber :: LibVersionInfo -> (Int, Int, Int) Source #

Given a version-info field, produce a major.minor.build version

libVersionNumberShow :: LibVersionInfo -> String Source #

Given a version-info field, return "major.minor.build" as a String

libVersionMajor :: LibVersionInfo -> Int Source #

Return the major version of a version-info field.