Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
This module holds a long list of lenses that access the Atoms record, the record that holds the input data from which the debianization is to be constructed.
Synopsis
- data DebInfo
- 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
- data Site = Site {}
- data Server = Server {
- hostname :: String
- port :: Int
- headerMessage :: String
- retry :: String
- serverFlags :: [String]
- installFile :: InstallFile
- data InstallFile = InstallFile {}
- data TestsStatus
- flags :: Lens' DebInfo Flags
- warning :: Lens' DebInfo (Set Text)
- sourceFormat :: Lens' DebInfo SourceFormat
- watch :: Lens' DebInfo (Maybe Text)
- rulesHead :: Lens' DebInfo (Maybe Text)
- rulesSettings :: Lens' DebInfo [Text]
- rulesIncludes :: Lens' DebInfo [Text]
- rulesFragments :: Lens' DebInfo (Set Text)
- copyright :: Lens' DebInfo (Maybe CopyrightDescription)
- control :: Lens' DebInfo SourceDebDescription
- intermediateFiles :: Lens' DebInfo (Set (FilePath, Text))
- compat :: Lens' DebInfo (Maybe Int)
- changelog :: Lens' DebInfo (Maybe ChangeLog)
- installInit :: Lens' DebInfo (Map BinPkgName Text)
- logrotateStanza :: Lens' DebInfo (Map BinPkgName (Set Text))
- postInst :: Lens' DebInfo (Map BinPkgName Text)
- postRm :: Lens' DebInfo (Map BinPkgName Text)
- preInst :: Lens' DebInfo (Map BinPkgName Text)
- preRm :: Lens' DebInfo (Map BinPkgName Text)
- atomSet :: Lens' DebInfo (Set Atom)
- noDocumentationLibrary :: Lens' DebInfo Bool
- noProfilingLibrary :: Lens' DebInfo Bool
- omitProfVersionDeps :: Lens' DebInfo Bool
- omitLTDeps :: Lens' DebInfo Bool
- buildDir :: Lens' DebInfo (Maybe FilePath)
- sourcePackageName :: Lens' DebInfo (Maybe SrcPkgName)
- overrideDebianNameBase :: Lens' DebInfo (Maybe DebBase)
- revision :: Lens' DebInfo (Maybe String)
- debVersion :: Lens' DebInfo (Maybe DebianVersion)
- maintainerOption :: Lens' DebInfo (Maybe NameAddr)
- uploadersOption :: Lens' DebInfo [NameAddr]
- utilsPackageNameBase :: Lens' DebInfo (Maybe String)
- xDescriptionText :: Lens' DebInfo (Maybe Text)
- comments :: Lens' DebInfo (Maybe [[Text]])
- missingDependencies :: Lens' DebInfo (Set BinPkgName)
- extraLibMap :: Lens' DebInfo (Map String Relations)
- execMap :: Lens' DebInfo (Map String Relations)
- apacheSite :: Lens' DebInfo (Map BinPkgName (String, FilePath, Text))
- sourceArchitectures :: Lens' DebInfo (Maybe PackageArchitectures)
- binaryArchitectures :: Lens' DebInfo (Map BinPkgName PackageArchitectures)
- sourcePriority :: Lens' DebInfo (Maybe PackagePriority)
- binaryPriorities :: Lens' DebInfo (Map BinPkgName PackagePriority)
- sourceSection :: Lens' DebInfo (Maybe Section)
- binarySections :: Lens' DebInfo (Map BinPkgName Section)
- executable :: Lens' DebInfo (Map BinPkgName InstallFile)
- serverInfo :: Lens' DebInfo (Map BinPkgName Server)
- website :: Lens' DebInfo (Map BinPkgName Site)
- backups :: Lens' DebInfo (Map BinPkgName String)
- extraDevDeps :: Lens' DebInfo Relations
- official :: Lens' DebInfo Bool
- testsStatus :: Lens' DebInfo TestsStatus
- allowDebianSelfBuildDeps :: Lens' DebInfo Bool
- binaryDebDescription :: BinPkgName -> Lens' DebInfo BinaryDebDescription
- link :: Monad m => BinPkgName -> FilePath -> FilePath -> StateT DebInfo m ()
- install :: Monad m => BinPkgName -> FilePath -> FilePath -> StateT DebInfo m ()
- installTo :: Monad m => BinPkgName -> FilePath -> FilePath -> StateT DebInfo m ()
- installData :: Monad m => BinPkgName -> FilePath -> FilePath -> StateT DebInfo m ()
- file :: Monad m => BinPkgName -> FilePath -> Text -> StateT DebInfo m ()
- installCabalExec :: Monad m => BinPkgName -> String -> FilePath -> StateT DebInfo m ()
- installCabalExecTo :: Monad m => BinPkgName -> String -> FilePath -> StateT DebInfo m ()
- installDir :: Monad m => BinPkgName -> FilePath -> StateT DebInfo m ()
- makeDebInfo :: Flags -> DebInfo
Types
Information required to represent a non-cabal debianization.
Instances
Data DebInfo Source # | |
Defined in Debian.Debianize.DebInfo gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DebInfo -> c DebInfo # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DebInfo # toConstr :: DebInfo -> Constr # dataTypeOf :: DebInfo -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DebInfo) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DebInfo) # gmapT :: (forall b. Data b => b -> b) -> DebInfo -> DebInfo # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DebInfo -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DebInfo -> r # gmapQ :: (forall d. Data d => d -> u) -> DebInfo -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> DebInfo -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DebInfo -> m DebInfo # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DebInfo -> m DebInfo # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DebInfo -> m DebInfo # | |
Show DebInfo Source # | |
Canonical DebInfo Source # | |
Link BinPkgName FilePath FilePath | Create a symbolic link in the binary package |
Install BinPkgName FilePath FilePath | Install a build file into the binary package |
InstallTo BinPkgName FilePath FilePath | Install a build file into the binary package at an exact location |
InstallData BinPkgName FilePath FilePath | DHInstallTo somewhere relative to DataDir (see above) |
File BinPkgName FilePath Text | Create a file with the given text at the given path |
InstallCabalExec BinPkgName String FilePath | Install a cabal executable into the binary package |
InstallCabalExecTo BinPkgName String FilePath | Install a cabal executable into the binary package at an exact location |
InstallDir BinPkgName FilePath | Create a directory in the binary package |
Instances
Data Atom Source # | |
Defined in Debian.Debianize.DebInfo gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Atom -> c Atom # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Atom # dataTypeOf :: Atom -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Atom) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Atom) # gmapT :: (forall b. Data b => b -> b) -> Atom -> Atom # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Atom -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Atom -> r # gmapQ :: (forall d. Data d => d -> u) -> Atom -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Atom -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Atom -> m Atom # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Atom -> m Atom # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Atom -> m Atom # | |
Show Atom Source # | |
Eq Atom Source # | |
Ord Atom Source # | |
Information about the web site we are packaging.
Instances
Data Site Source # | |
Defined in Debian.Debianize.DebInfo gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Site -> c Site # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Site # dataTypeOf :: Site -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Site) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Site) # gmapT :: (forall b. Data b => b -> b) -> Site -> Site # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Site -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Site -> r # gmapQ :: (forall d. Data d => d -> u) -> Site -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Site -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Site -> m Site # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Site -> m Site # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Site -> m Site # | |
Read Site Source # | |
Show Site Source # | |
Eq Site Source # | |
Ord Site Source # | |
Information about the server we are packaging.
Server | |
|
Instances
Data Server Source # | |
Defined in Debian.Debianize.DebInfo gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Server -> c Server # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Server # toConstr :: Server -> Constr # dataTypeOf :: Server -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Server) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Server) # gmapT :: (forall b. Data b => b -> b) -> Server -> Server # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Server -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Server -> r # gmapQ :: (forall d. Data d => d -> u) -> Server -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Server -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Server -> m Server # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Server -> m Server # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Server -> m Server # | |
Read Server Source # | |
Show Server Source # | |
Eq Server Source # | |
Ord Server Source # | |
data InstallFile Source #
Instances
data TestsStatus Source #
Instances
Data TestsStatus Source # | |
Defined in Debian.Debianize.DebInfo gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TestsStatus -> c TestsStatus # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TestsStatus # toConstr :: TestsStatus -> Constr # dataTypeOf :: TestsStatus -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TestsStatus) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TestsStatus) # gmapT :: (forall b. Data b => b -> b) -> TestsStatus -> TestsStatus # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TestsStatus -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TestsStatus -> r # gmapQ :: (forall d. Data d => d -> u) -> TestsStatus -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TestsStatus -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TestsStatus -> m TestsStatus # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TestsStatus -> m TestsStatus # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TestsStatus -> m TestsStatus # | |
Show TestsStatus Source # | |
Defined in Debian.Debianize.DebInfo showsPrec :: Int -> TestsStatus -> ShowS # show :: TestsStatus -> String # showList :: [TestsStatus] -> ShowS # | |
Eq TestsStatus Source # | |
Defined in Debian.Debianize.DebInfo (==) :: TestsStatus -> TestsStatus -> Bool # (/=) :: TestsStatus -> TestsStatus -> Bool # |
Lenses
installInit :: Lens' DebInfo (Map BinPkgName Text) Source #
logrotateStanza :: Lens' DebInfo (Map BinPkgName (Set Text)) Source #
apacheSite :: Lens' DebInfo (Map BinPkgName (String, FilePath, Text)) Source #
serverInfo :: Lens' DebInfo (Map BinPkgName Server) Source #
binaryDebDescription :: BinPkgName -> Lens' DebInfo BinaryDebDescription Source #
Lens to look up the binary deb description by name and create it if absent. http://www.debian.org/doc/debian-policy/ch-controlfields.html#s-f-Package
Atom builders
installData :: Monad m => BinPkgName -> FilePath -> FilePath -> StateT DebInfo m () Source #
installCabalExec :: Monad m => BinPkgName -> String -> FilePath -> StateT DebInfo m () Source #
installCabalExecTo :: Monad m => BinPkgName -> String -> FilePath -> StateT DebInfo m () Source #
installDir :: Monad m => BinPkgName -> FilePath -> StateT DebInfo m () Source #
DebInfo Builder
makeDebInfo :: Flags -> DebInfo Source #