{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}

module Distribution.Types.ForeignLib
  ( ForeignLib (..)
  , emptyForeignLib
  , foreignLibModules
  , foreignLibIsShared
  , foreignLibVersion
  , LibVersionInfo
  , mkLibVersionInfo
  , libVersionInfoCRA
  , libVersionNumber
  , libVersionNumberShow
  , libVersionMajor
  ) where

import Distribution.Compat.Prelude
import Prelude ()

import Distribution.ModuleName
import Distribution.Parsec
import Distribution.Pretty
import Distribution.System
import Distribution.Types.BuildInfo
import Distribution.Types.ForeignLibOption
import Distribution.Types.ForeignLibType
import Distribution.Types.UnqualComponentName
import Distribution.Utils.Path
import Distribution.Version

import Data.Monoid
import qualified Distribution.Compat.CharParsing as P
import qualified Text.PrettyPrint as Disp
import qualified Text.Read as Read

import qualified Distribution.Types.BuildInfo.Lens as L

-- | A foreign library stanza is like a library stanza, except that
-- the built code is intended for consumption by a non-Haskell client.
data ForeignLib = ForeignLib
  { ForeignLib -> UnqualComponentName
foreignLibName :: UnqualComponentName
  -- ^ Name of the foreign library
  , ForeignLib -> ForeignLibType
foreignLibType :: ForeignLibType
  -- ^ What kind of foreign library is this (static or dynamic).
  , ForeignLib -> [ForeignLibOption]
foreignLibOptions :: [ForeignLibOption]
  -- ^ What options apply to this foreign library (e.g., are we
  -- merging in all foreign dependencies.)
  , ForeignLib -> BuildInfo
foreignLibBuildInfo :: BuildInfo
  -- ^ Build information for this foreign library.
  , ForeignLib -> Maybe LibVersionInfo
foreignLibVersionInfo :: Maybe LibVersionInfo
  -- ^ Libtool-style version-info data to compute library version.
  -- Refer to the libtool documentation on the
  -- current:revision:age versioning scheme.
  , ForeignLib -> Maybe Version
foreignLibVersionLinux :: Maybe Version
  -- ^ Linux library version
  , ForeignLib -> [RelativePath Source 'File]
foreignLibModDefFile :: [RelativePath Source File]
  -- ^ (Windows-specific) module definition files
  --
  -- This is a list rather than a maybe field so that we can flatten
  -- the condition trees (for instance, when creating an sdist)
  }
  deriving ((forall x. ForeignLib -> Rep ForeignLib x)
-> (forall x. Rep ForeignLib x -> ForeignLib) -> Generic ForeignLib
forall x. Rep ForeignLib x -> ForeignLib
forall x. ForeignLib -> Rep ForeignLib x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ForeignLib -> Rep ForeignLib x
from :: forall x. ForeignLib -> Rep ForeignLib x
$cto :: forall x. Rep ForeignLib x -> ForeignLib
to :: forall x. Rep ForeignLib x -> ForeignLib
Generic, Int -> ForeignLib -> ShowS
[ForeignLib] -> ShowS
ForeignLib -> String
(Int -> ForeignLib -> ShowS)
-> (ForeignLib -> String)
-> ([ForeignLib] -> ShowS)
-> Show ForeignLib
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ForeignLib -> ShowS
showsPrec :: Int -> ForeignLib -> ShowS
$cshow :: ForeignLib -> String
show :: ForeignLib -> String
$cshowList :: [ForeignLib] -> ShowS
showList :: [ForeignLib] -> ShowS
Show, ReadPrec [ForeignLib]
ReadPrec ForeignLib
Int -> ReadS ForeignLib
ReadS [ForeignLib]
(Int -> ReadS ForeignLib)
-> ReadS [ForeignLib]
-> ReadPrec ForeignLib
-> ReadPrec [ForeignLib]
-> Read ForeignLib
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ForeignLib
readsPrec :: Int -> ReadS ForeignLib
$creadList :: ReadS [ForeignLib]
readList :: ReadS [ForeignLib]
$creadPrec :: ReadPrec ForeignLib
readPrec :: ReadPrec ForeignLib
$creadListPrec :: ReadPrec [ForeignLib]
readListPrec :: ReadPrec [ForeignLib]
Read, ForeignLib -> ForeignLib -> Bool
(ForeignLib -> ForeignLib -> Bool)
-> (ForeignLib -> ForeignLib -> Bool) -> Eq ForeignLib
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ForeignLib -> ForeignLib -> Bool
== :: ForeignLib -> ForeignLib -> Bool
$c/= :: ForeignLib -> ForeignLib -> Bool
/= :: ForeignLib -> ForeignLib -> Bool
Eq, Eq ForeignLib
Eq ForeignLib =>
(ForeignLib -> ForeignLib -> Ordering)
-> (ForeignLib -> ForeignLib -> Bool)
-> (ForeignLib -> ForeignLib -> Bool)
-> (ForeignLib -> ForeignLib -> Bool)
-> (ForeignLib -> ForeignLib -> Bool)
-> (ForeignLib -> ForeignLib -> ForeignLib)
-> (ForeignLib -> ForeignLib -> ForeignLib)
-> Ord ForeignLib
ForeignLib -> ForeignLib -> Bool
ForeignLib -> ForeignLib -> Ordering
ForeignLib -> ForeignLib -> ForeignLib
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
$ccompare :: ForeignLib -> ForeignLib -> Ordering
compare :: ForeignLib -> ForeignLib -> Ordering
$c< :: ForeignLib -> ForeignLib -> Bool
< :: ForeignLib -> ForeignLib -> Bool
$c<= :: ForeignLib -> ForeignLib -> Bool
<= :: ForeignLib -> ForeignLib -> Bool
$c> :: ForeignLib -> ForeignLib -> Bool
> :: ForeignLib -> ForeignLib -> Bool
$c>= :: ForeignLib -> ForeignLib -> Bool
>= :: ForeignLib -> ForeignLib -> Bool
$cmax :: ForeignLib -> ForeignLib -> ForeignLib
max :: ForeignLib -> ForeignLib -> ForeignLib
$cmin :: ForeignLib -> ForeignLib -> ForeignLib
min :: ForeignLib -> ForeignLib -> ForeignLib
Ord, Typeable, Typeable ForeignLib
Typeable ForeignLib =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> ForeignLib -> c ForeignLib)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c ForeignLib)
-> (ForeignLib -> Constr)
-> (ForeignLib -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c ForeignLib))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c ForeignLib))
-> ((forall b. Data b => b -> b) -> ForeignLib -> ForeignLib)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> ForeignLib -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> ForeignLib -> r)
-> (forall u. (forall d. Data d => d -> u) -> ForeignLib -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> ForeignLib -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> ForeignLib -> m ForeignLib)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> ForeignLib -> m ForeignLib)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> ForeignLib -> m ForeignLib)
-> Data ForeignLib
ForeignLib -> Constr
ForeignLib -> DataType
(forall b. Data b => b -> b) -> ForeignLib -> ForeignLib
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) -> ForeignLib -> u
forall u. (forall d. Data d => d -> u) -> ForeignLib -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ForeignLib -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ForeignLib -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ForeignLib -> m ForeignLib
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ForeignLib -> m ForeignLib
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ForeignLib
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ForeignLib -> c ForeignLib
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ForeignLib)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ForeignLib)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ForeignLib -> c ForeignLib
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ForeignLib -> c ForeignLib
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ForeignLib
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ForeignLib
$ctoConstr :: ForeignLib -> Constr
toConstr :: ForeignLib -> Constr
$cdataTypeOf :: ForeignLib -> DataType
dataTypeOf :: ForeignLib -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ForeignLib)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ForeignLib)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ForeignLib)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ForeignLib)
$cgmapT :: (forall b. Data b => b -> b) -> ForeignLib -> ForeignLib
gmapT :: (forall b. Data b => b -> b) -> ForeignLib -> ForeignLib
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ForeignLib -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ForeignLib -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ForeignLib -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ForeignLib -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ForeignLib -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> ForeignLib -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ForeignLib -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ForeignLib -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ForeignLib -> m ForeignLib
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ForeignLib -> m ForeignLib
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ForeignLib -> m ForeignLib
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ForeignLib -> m ForeignLib
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ForeignLib -> m ForeignLib
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ForeignLib -> m ForeignLib
Data)

data LibVersionInfo = LibVersionInfo Int Int Int deriving (Typeable LibVersionInfo
Typeable LibVersionInfo =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> LibVersionInfo -> c LibVersionInfo)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c LibVersionInfo)
-> (LibVersionInfo -> Constr)
-> (LibVersionInfo -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c LibVersionInfo))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c LibVersionInfo))
-> ((forall b. Data b => b -> b)
    -> LibVersionInfo -> LibVersionInfo)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> LibVersionInfo -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> LibVersionInfo -> r)
-> (forall u.
    (forall d. Data d => d -> u) -> LibVersionInfo -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> LibVersionInfo -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d)
    -> LibVersionInfo -> m LibVersionInfo)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> LibVersionInfo -> m LibVersionInfo)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> LibVersionInfo -> m LibVersionInfo)
-> Data LibVersionInfo
LibVersionInfo -> Constr
LibVersionInfo -> DataType
(forall b. Data b => b -> b) -> LibVersionInfo -> LibVersionInfo
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) -> LibVersionInfo -> u
forall u. (forall d. Data d => d -> u) -> LibVersionInfo -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> LibVersionInfo -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> LibVersionInfo -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> LibVersionInfo -> m LibVersionInfo
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> LibVersionInfo -> m LibVersionInfo
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c LibVersionInfo
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> LibVersionInfo -> c LibVersionInfo
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c LibVersionInfo)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c LibVersionInfo)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> LibVersionInfo -> c LibVersionInfo
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> LibVersionInfo -> c LibVersionInfo
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c LibVersionInfo
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c LibVersionInfo
$ctoConstr :: LibVersionInfo -> Constr
toConstr :: LibVersionInfo -> Constr
$cdataTypeOf :: LibVersionInfo -> DataType
dataTypeOf :: LibVersionInfo -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c LibVersionInfo)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c LibVersionInfo)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c LibVersionInfo)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c LibVersionInfo)
$cgmapT :: (forall b. Data b => b -> b) -> LibVersionInfo -> LibVersionInfo
gmapT :: (forall b. Data b => b -> b) -> LibVersionInfo -> LibVersionInfo
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> LibVersionInfo -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> LibVersionInfo -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> LibVersionInfo -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> LibVersionInfo -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> LibVersionInfo -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> LibVersionInfo -> [u]
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> LibVersionInfo -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> LibVersionInfo -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> LibVersionInfo -> m LibVersionInfo
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> LibVersionInfo -> m LibVersionInfo
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> LibVersionInfo -> m LibVersionInfo
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> LibVersionInfo -> m LibVersionInfo
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> LibVersionInfo -> m LibVersionInfo
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> LibVersionInfo -> m LibVersionInfo
Data, LibVersionInfo -> LibVersionInfo -> Bool
(LibVersionInfo -> LibVersionInfo -> Bool)
-> (LibVersionInfo -> LibVersionInfo -> Bool) -> Eq LibVersionInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: LibVersionInfo -> LibVersionInfo -> Bool
== :: LibVersionInfo -> LibVersionInfo -> Bool
$c/= :: LibVersionInfo -> LibVersionInfo -> Bool
/= :: LibVersionInfo -> LibVersionInfo -> Bool
Eq, (forall x. LibVersionInfo -> Rep LibVersionInfo x)
-> (forall x. Rep LibVersionInfo x -> LibVersionInfo)
-> Generic LibVersionInfo
forall x. Rep LibVersionInfo x -> LibVersionInfo
forall x. LibVersionInfo -> Rep LibVersionInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. LibVersionInfo -> Rep LibVersionInfo x
from :: forall x. LibVersionInfo -> Rep LibVersionInfo x
$cto :: forall x. Rep LibVersionInfo x -> LibVersionInfo
to :: forall x. Rep LibVersionInfo x -> LibVersionInfo
Generic, Typeable)

instance Ord LibVersionInfo where
  LibVersionInfo Int
c Int
r Int
_ compare :: LibVersionInfo -> LibVersionInfo -> Ordering
`compare` LibVersionInfo Int
c' Int
r' Int
_ =
    case Int
c Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
`compare` Int
c' of
      Ordering
EQ -> Int
r Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
`compare` Int
r'
      Ordering
e -> Ordering
e

instance Show LibVersionInfo where
  showsPrec :: Int -> LibVersionInfo -> ShowS
showsPrec Int
d (LibVersionInfo Int
c Int
r Int
a) =
    Bool -> ShowS -> ShowS
showParen (Int
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
10) (ShowS -> ShowS) -> ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$
      String -> ShowS
showString String
"mkLibVersionInfo "
        ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> (Int, Int, Int) -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
11 (Int
c, Int
r, Int
a)

instance Read LibVersionInfo where
  readPrec :: ReadPrec LibVersionInfo
readPrec = ReadPrec LibVersionInfo -> ReadPrec LibVersionInfo
forall a. ReadPrec a -> ReadPrec a
Read.parens (ReadPrec LibVersionInfo -> ReadPrec LibVersionInfo)
-> ReadPrec LibVersionInfo -> ReadPrec LibVersionInfo
forall a b. (a -> b) -> a -> b
$ do
    Read.Ident "mkLibVersionInfo" <- ReadPrec Lexeme
Read.lexP
    t <- Read.step Read.readPrec
    return (mkLibVersionInfo t)

instance Binary LibVersionInfo
instance Structured LibVersionInfo
instance NFData LibVersionInfo where rnf :: LibVersionInfo -> ()
rnf = LibVersionInfo -> ()
forall a. (Generic a, GNFData (Rep a)) => a -> ()
genericRnf

instance Pretty LibVersionInfo where
  pretty :: LibVersionInfo -> Doc
pretty (LibVersionInfo Int
c Int
r Int
a) =
    [Doc] -> Doc
Disp.hcat ([Doc] -> Doc) -> [Doc] -> Doc
forall a b. (a -> b) -> a -> b
$ Doc -> [Doc] -> [Doc]
Disp.punctuate (Char -> Doc
Disp.char Char
':') ([Doc] -> [Doc]) -> [Doc] -> [Doc]
forall a b. (a -> b) -> a -> b
$ (Int -> Doc) -> [Int] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map Int -> Doc
Disp.int [Int
c, Int
r, Int
a]

instance Parsec LibVersionInfo where
  parsec :: forall (m :: * -> *). CabalParsing m => m LibVersionInfo
parsec = do
    c <- m Int
forall (m :: * -> *) a. (CharParsing m, Integral a) => m a
P.integral
    (r, a) <- P.option (0, 0) $ do
      _ <- P.char ':'
      r <- P.integral
      a <- P.option 0 $ do
        _ <- P.char ':'
        P.integral
      return (r, a)
    return $ mkLibVersionInfo (c, r, a)

-- | 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.
mkLibVersionInfo :: (Int, Int, Int) -> LibVersionInfo
mkLibVersionInfo :: (Int, Int, Int) -> LibVersionInfo
mkLibVersionInfo (Int
c, Int
r, Int
a) = Int -> Int -> Int -> LibVersionInfo
LibVersionInfo Int
c Int
r Int
a

-- | From a given 'LibVersionInfo', extract the @(current, revision,
-- age)@ numbers.
libVersionInfoCRA :: LibVersionInfo -> (Int, Int, Int)
libVersionInfoCRA :: LibVersionInfo -> (Int, Int, Int)
libVersionInfoCRA (LibVersionInfo Int
c Int
r Int
a) = (Int
c, Int
r, Int
a)

-- | Given a version-info field, produce a @major.minor.build@ version
libVersionNumber :: LibVersionInfo -> (Int, Int, Int)
libVersionNumber :: LibVersionInfo -> (Int, Int, Int)
libVersionNumber (LibVersionInfo Int
c Int
r Int
a) = (Int
c Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
a, Int
a, Int
r)

-- | Given a version-info field, return @"major.minor.build"@ as a
-- 'String'
libVersionNumberShow :: LibVersionInfo -> String
libVersionNumberShow :: LibVersionInfo -> String
libVersionNumberShow LibVersionInfo
v =
  let (Int
major, Int
minor, Int
build) = LibVersionInfo -> (Int, Int, Int)
libVersionNumber LibVersionInfo
v
   in Int -> String
forall a. Show a => a -> String
show Int
major String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"." String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
minor String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"." String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
build

-- | Return the @major@ version of a version-info field.
libVersionMajor :: LibVersionInfo -> Int
libVersionMajor :: LibVersionInfo -> Int
libVersionMajor (LibVersionInfo Int
c Int
_ Int
a) = Int
c Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
a

instance L.HasBuildInfo ForeignLib where
  buildInfo :: Lens' ForeignLib BuildInfo
buildInfo BuildInfo -> f BuildInfo
f ForeignLib
l = (\BuildInfo
x -> ForeignLib
l{foreignLibBuildInfo = x}) (BuildInfo -> ForeignLib) -> f BuildInfo -> f ForeignLib
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> BuildInfo -> f BuildInfo
f (ForeignLib -> BuildInfo
foreignLibBuildInfo ForeignLib
l)

instance Binary ForeignLib
instance Structured ForeignLib
instance NFData ForeignLib where rnf :: ForeignLib -> ()
rnf = ForeignLib -> ()
forall a. (Generic a, GNFData (Rep a)) => a -> ()
genericRnf

instance Semigroup ForeignLib where
  ForeignLib
a <> :: ForeignLib -> ForeignLib -> ForeignLib
<> ForeignLib
b =
    ForeignLib
      { foreignLibName :: UnqualComponentName
foreignLibName = ForeignLib
-> ForeignLib
-> (ForeignLib -> UnqualComponentName)
-> String
-> UnqualComponentName
forall b a.
(Monoid b, Eq b, Show b) =>
a -> a -> (a -> b) -> String -> b
combineNames ForeignLib
a ForeignLib
b ForeignLib -> UnqualComponentName
foreignLibName String
"foreign library"
      , foreignLibType :: ForeignLibType
foreignLibType = (ForeignLib -> ForeignLibType) -> ForeignLibType
forall {a}. Monoid a => (ForeignLib -> a) -> a
combine ForeignLib -> ForeignLibType
foreignLibType
      , foreignLibOptions :: [ForeignLibOption]
foreignLibOptions = (ForeignLib -> [ForeignLibOption]) -> [ForeignLibOption]
forall {a}. Monoid a => (ForeignLib -> a) -> a
combine ForeignLib -> [ForeignLibOption]
foreignLibOptions
      , foreignLibBuildInfo :: BuildInfo
foreignLibBuildInfo = (ForeignLib -> BuildInfo) -> BuildInfo
forall {a}. Monoid a => (ForeignLib -> a) -> a
combine ForeignLib -> BuildInfo
foreignLibBuildInfo
      , foreignLibVersionInfo :: Maybe LibVersionInfo
foreignLibVersionInfo = (ForeignLib -> Maybe LibVersionInfo) -> Maybe LibVersionInfo
forall {a}. (ForeignLib -> Maybe a) -> Maybe a
chooseLast ForeignLib -> Maybe LibVersionInfo
foreignLibVersionInfo
      , foreignLibVersionLinux :: Maybe Version
foreignLibVersionLinux = (ForeignLib -> Maybe Version) -> Maybe Version
forall {a}. (ForeignLib -> Maybe a) -> Maybe a
chooseLast ForeignLib -> Maybe Version
foreignLibVersionLinux
      , foreignLibModDefFile :: [RelativePath Source 'File]
foreignLibModDefFile = (ForeignLib -> [RelativePath Source 'File])
-> [RelativePath Source 'File]
forall {a}. Monoid a => (ForeignLib -> a) -> a
combine ForeignLib -> [RelativePath Source 'File]
foreignLibModDefFile
      }
    where
      combine :: (ForeignLib -> a) -> a
combine ForeignLib -> a
field = ForeignLib -> a
field ForeignLib
a a -> a -> a
forall a. Monoid a => a -> a -> a
`mappend` ForeignLib -> a
field ForeignLib
b
      -- chooseLast: the second field overrides the first, unless it is Nothing
      chooseLast :: (ForeignLib -> Maybe a) -> Maybe a
chooseLast ForeignLib -> Maybe a
field = Last a -> Maybe a
forall a. Last a -> Maybe a
getLast (Maybe a -> Last a
forall a. Maybe a -> Last a
Last (ForeignLib -> Maybe a
field ForeignLib
a) Last a -> Last a -> Last a
forall a. Semigroup a => a -> a -> a
<> Maybe a -> Last a
forall a. Maybe a -> Last a
Last (ForeignLib -> Maybe a
field ForeignLib
b))

instance Monoid ForeignLib where
  mempty :: ForeignLib
mempty =
    ForeignLib
      { foreignLibName :: UnqualComponentName
foreignLibName = UnqualComponentName
forall a. Monoid a => a
mempty
      , foreignLibType :: ForeignLibType
foreignLibType = ForeignLibType
ForeignLibTypeUnknown
      , foreignLibOptions :: [ForeignLibOption]
foreignLibOptions = []
      , foreignLibBuildInfo :: BuildInfo
foreignLibBuildInfo = BuildInfo
forall a. Monoid a => a
mempty
      , foreignLibVersionInfo :: Maybe LibVersionInfo
foreignLibVersionInfo = Maybe LibVersionInfo
forall a. Maybe a
Nothing
      , foreignLibVersionLinux :: Maybe Version
foreignLibVersionLinux = Maybe Version
forall a. Maybe a
Nothing
      , foreignLibModDefFile :: [RelativePath Source 'File]
foreignLibModDefFile = []
      }
  mappend :: ForeignLib -> ForeignLib -> ForeignLib
mappend = ForeignLib -> ForeignLib -> ForeignLib
forall a. Semigroup a => a -> a -> a
(<>)

-- | An empty foreign library.
emptyForeignLib :: ForeignLib
emptyForeignLib :: ForeignLib
emptyForeignLib = ForeignLib
forall a. Monoid a => a
mempty

-- | Modules defined by a foreign library.
foreignLibModules :: ForeignLib -> [ModuleName]
foreignLibModules :: ForeignLib -> [ModuleName]
foreignLibModules = BuildInfo -> [ModuleName]
otherModules (BuildInfo -> [ModuleName])
-> (ForeignLib -> BuildInfo) -> ForeignLib -> [ModuleName]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignLib -> BuildInfo
foreignLibBuildInfo

-- | Is the foreign library shared?
foreignLibIsShared :: ForeignLib -> Bool
foreignLibIsShared :: ForeignLib -> Bool
foreignLibIsShared = ForeignLibType -> Bool
foreignLibTypeIsShared (ForeignLibType -> Bool)
-> (ForeignLib -> ForeignLibType) -> ForeignLib -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignLib -> ForeignLibType
foreignLibType

-- | 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.
foreignLibVersion :: ForeignLib -> OS -> [Int]
foreignLibVersion :: ForeignLib -> OS -> [Int]
foreignLibVersion ForeignLib
flib OS
Linux =
  case ForeignLib -> Maybe Version
foreignLibVersionLinux ForeignLib
flib of
    Just Version
v -> Version -> [Int]
versionNumbers Version
v
    Maybe Version
Nothing ->
      case ForeignLib -> Maybe LibVersionInfo
foreignLibVersionInfo ForeignLib
flib of
        Just LibVersionInfo
v' ->
          let (Int
major, Int
minor, Int
build) = LibVersionInfo -> (Int, Int, Int)
libVersionNumber LibVersionInfo
v'
           in [Int
major, Int
minor, Int
build]
        Maybe LibVersionInfo
Nothing -> []
foreignLibVersion ForeignLib
_ OS
_ = []