module Debian.Debianize.DebInfo
(
#if __HADDOCK__
DebInfo(..)
#else
DebInfo
#endif
, Atom(File, Install, InstallCabalExec, InstallCabalExecTo, InstallData, InstallDir, InstallTo, Link)
, Site(Site, domain, server, serverAdmin)
, Server(Server, headerMessage, hostname, installFile, port, retry, serverFlags)
, InstallFile(InstallFile, destDir, destName, execName, sourceDir)
, TestsStatus(..)
, flags
, warning
, sourceFormat
, watch
, rulesHead
, rulesSettings
, rulesIncludes
, rulesFragments
, copyright
, control
, intermediateFiles
, compat
, changelog
, installInit
, logrotateStanza
, postInst
, postRm
, preInst
, preRm
, atomSet
, noDocumentationLibrary
, noProfilingLibrary
, omitProfVersionDeps
, omitLTDeps
, buildDir
, sourcePackageName
, overrideDebianNameBase
, revision
, debVersion
, maintainerOption
, uploadersOption
, utilsPackageNameBase
, xDescriptionText
, comments
, missingDependencies
, extraLibMap
, execMap
, apacheSite
, sourceArchitectures
, binaryArchitectures
, sourcePriority
, binaryPriorities
, sourceSection
, binarySections
, executable
, serverInfo
, website
, backups
, extraDevDeps
, official
, testsStatus
, allowDebianSelfBuildDeps
, binaryDebDescription
, link
, install
, installTo
, installData
, file
, installCabalExec
, installCabalExecTo
, installDir
, makeDebInfo
) where
import Control.Lens
import Control.Monad.State (StateT)
import Data.Generics (Data, Typeable)
import Data.Map as Map (Map)
#if !MIN_VERSION_base(4,8,0)
import Data.Monoid (Monoid(..))
#endif
import Data.Set as Set (insert, Set)
import Data.Text (Text)
import Debian.Changes (ChangeLog)
import Debian.Debianize.BasicInfo (Flags)
import Debian.Debianize.Prelude (listElemLens, maybeLens)
import Debian.Debianize.BinaryDebDescription (BinaryDebDescription, Canonical(canonical), newBinaryDebDescription, package)
import Debian.Debianize.CopyrightDescription (CopyrightDescription)
import qualified Debian.Debianize.SourceDebDescription as S (newSourceDebDescription, SourceDebDescription, binaryPackages)
import Debian.Debianize.VersionSplits (DebBase)
import Debian.Orphans ()
import Debian.Policy (PackageArchitectures, PackagePriority, Section, SourceFormat(..))
import Debian.Relation (BinPkgName, Relations, SrcPkgName)
import Debian.Version (DebianVersion)
import Prelude hiding (init, init, log, log)
#if MIN_VERSION_hsemail(2,0,0)
import Text.Parsec.Rfc2822 (NameAddr)
#else
import Text.ParserCombinators.Parsec.Rfc2822 (NameAddr)
#endif
data DebInfo
= DebInfo
{ _flags :: Flags
, _warning :: Set Text
, _sourceFormat :: SourceFormat
, _watch :: Maybe Text
, _rulesHead :: Maybe Text
, _rulesSettings :: [Text]
, _rulesIncludes :: [Text]
, _rulesFragments :: Set Text
, _copyright :: Maybe CopyrightDescription
, _control :: S.SourceDebDescription
, _intermediateFiles :: Set (FilePath, Text)
, _compat :: Maybe Int
, _changelog :: Maybe ChangeLog
, _installInit :: Map BinPkgName Text
, _logrotateStanza :: Map BinPkgName (Set Text)
, _postInst :: Map BinPkgName Text
, _postRm :: Map BinPkgName Text
, _preInst :: Map BinPkgName Text
, _preRm :: Map BinPkgName Text
, _atomSet :: Set Atom
, _noDocumentationLibrary :: Bool
, _noProfilingLibrary :: Bool
, _omitProfVersionDeps :: Bool
, _omitLTDeps :: Bool
, _buildDir :: Maybe FilePath
, _sourcePackageName :: Maybe SrcPkgName
, _overrideDebianNameBase :: Maybe DebBase
, _revision :: Maybe String
, _debVersion :: Maybe DebianVersion
, _maintainerOption :: Maybe NameAddr
, _uploadersOption :: [NameAddr]
, _utilsPackageNameBase :: Maybe String
, _xDescriptionText :: Maybe Text
, _comments :: Maybe [[Text]]
, _missingDependencies :: Set BinPkgName
, _extraLibMap :: Map String Relations
, _execMap :: Map String Relations
, _apacheSite :: Map BinPkgName (String, FilePath, Text)
, _sourceArchitectures :: Maybe PackageArchitectures
, _binaryArchitectures :: Map BinPkgName PackageArchitectures
, _sourcePriority :: Maybe PackagePriority
, _binaryPriorities :: Map BinPkgName PackagePriority
, _sourceSection :: Maybe Section
, _binarySections :: Map BinPkgName Section
, _executable :: Map BinPkgName InstallFile
, _serverInfo :: Map BinPkgName Server
, _website :: Map BinPkgName Site
, _backups :: Map BinPkgName String
, _extraDevDeps :: Relations
, _official :: Bool
, _testsStatus :: TestsStatus
, _allowDebianSelfBuildDeps :: Bool
} deriving (Show, Data, Typeable)
data Atom
= Link BinPkgName FilePath FilePath
| Install BinPkgName FilePath FilePath
| InstallTo BinPkgName FilePath FilePath
| InstallData BinPkgName FilePath FilePath
| File BinPkgName FilePath Text
| InstallCabalExec BinPkgName String FilePath
| InstallCabalExecTo BinPkgName String FilePath
| InstallDir BinPkgName FilePath
deriving (Show, Eq, Ord, Data, Typeable)
data InstallFile
= InstallFile
{ execName :: String
, sourceDir :: Maybe FilePath
, destDir :: Maybe FilePath
, destName :: String
} deriving (Read, Show, Eq, Ord, Data, Typeable)
data Site
= Site
{ domain :: String
, serverAdmin :: String
, server :: Server
} deriving (Read, Show, Eq, Ord, Data, Typeable)
data Server
= Server
{ hostname :: String
, port :: Int
, headerMessage :: String
, retry :: String
, serverFlags :: [String]
, installFile :: InstallFile
} deriving (Read, Show, Eq, Ord, Data, Typeable)
data TestsStatus = TestsDisable | TestsBuild | TestsRun deriving (Eq, Show, Data, Typeable)
makeDebInfo :: Flags -> DebInfo
makeDebInfo fs =
DebInfo
{ _flags = fs
, _warning = mempty
, _sourceFormat = Quilt3
, _watch = Nothing
, _rulesHead = Nothing
, _rulesSettings = mempty
, _rulesIncludes = mempty
, _rulesFragments = mempty
, _copyright = Nothing
, _control = S.newSourceDebDescription
, _intermediateFiles = mempty
, _compat = Nothing
, _changelog = Nothing
, _installInit = mempty
, _logrotateStanza = mempty
, _postInst = mempty
, _postRm = mempty
, _preInst = mempty
, _preRm = mempty
, _atomSet = mempty
, _noDocumentationLibrary = False
, _noProfilingLibrary = False
, _omitProfVersionDeps = False
, _omitLTDeps = False
, _buildDir = Nothing
, _sourcePackageName = Nothing
, _overrideDebianNameBase = Nothing
, _revision = Nothing
, _debVersion = Nothing
, _maintainerOption = Nothing
, _uploadersOption = []
, _utilsPackageNameBase = Nothing
, _xDescriptionText = Nothing
, _comments = Nothing
, _missingDependencies = mempty
, _extraLibMap = mempty
, _execMap = mempty
, _apacheSite = mempty
, _sourceArchitectures = Nothing
, _binaryArchitectures = mempty
, _sourcePriority = Nothing
, _binaryPriorities = mempty
, _sourceSection = Nothing
, _binarySections = mempty
, _executable = mempty
, _serverInfo = mempty
, _website = mempty
, _backups = mempty
, _extraDevDeps = mempty
, _official = False
, _testsStatus = TestsRun
, _allowDebianSelfBuildDeps = False
}
instance Canonical DebInfo where
canonical x = x {_control = canonical (_control x)}
$(makeLenses ''DebInfo)
link :: Monad m => BinPkgName -> FilePath -> FilePath -> StateT DebInfo m ()
link b src dest = atomSet %= (Set.insert $ Link b src dest) >> return ()
install :: Monad m => BinPkgName -> FilePath -> FilePath -> StateT DebInfo m ()
install b src dest = atomSet %= (Set.insert $ Install b src dest) >> return ()
installTo :: Monad m => BinPkgName -> FilePath -> FilePath -> StateT DebInfo m ()
installTo b src dest = atomSet %= (Set.insert $ InstallTo b src dest) >> return ()
installData :: Monad m => BinPkgName -> FilePath -> FilePath -> StateT DebInfo m ()
installData b src dest = atomSet %= (Set.insert $ InstallData b src dest) >> return ()
file :: Monad m => BinPkgName -> FilePath -> Text -> StateT DebInfo m ()
file b dest content = atomSet %= (Set.insert $ File b dest content) >> return ()
installCabalExec :: Monad m => BinPkgName -> String -> FilePath -> StateT DebInfo m ()
installCabalExec b name dest = atomSet %= (Set.insert $ InstallCabalExec b name dest) >> return ()
installCabalExecTo :: Monad m => BinPkgName -> String -> FilePath -> StateT DebInfo m ()
installCabalExecTo b name dest = atomSet %= (Set.insert $ InstallCabalExecTo b name dest) >> return ()
installDir :: Monad m => BinPkgName -> FilePath -> StateT DebInfo m ()
installDir b dir = atomSet %= (Set.insert $ InstallDir b dir) >> return ()
binaryDebDescription :: BinPkgName -> Lens' DebInfo BinaryDebDescription
binaryDebDescription b =
control . S.binaryPackages . listElemLens ((== b) . view package) . maybeLens (newBinaryDebDescription b) (iso id id)