Cabal-2.0.1.0: 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 Source # 
Data ForeignLib Source # 

Methods

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

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

toConstr :: ForeignLib -> Constr #

dataTypeOf :: ForeignLib -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ForeignLib Source # 
Show ForeignLib Source # 
Generic ForeignLib Source # 

Associated Types

type Rep ForeignLib :: * -> * #

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

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 Source # 
Data LibVersionInfo Source # 

Methods

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

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

toConstr :: LibVersionInfo -> Constr #

dataTypeOf :: LibVersionInfo -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord LibVersionInfo Source # 
Read LibVersionInfo Source # 
Show LibVersionInfo Source # 
Generic LibVersionInfo Source # 

Associated Types

type Rep LibVersionInfo :: * -> * #

Binary LibVersionInfo Source # 
Text LibVersionInfo Source # 
type Rep LibVersionInfo Source # 

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.