cabal-debian-4.0.3: Create a debianization for a cabal package

Safe HaskellNone

Debian.Debianize

Contents

Description

QUICK START:

You can either run the cabal-debian --debianize, or for more power and flexibility you can put a Debianize.hs script in the package's debian subdirectory. Atoms value and pass it to the debianize function. The callDebianize function retrieves extra arguments from the CABALDEBIAN environment variable and calls debianize with the build directory set as it would be when the packages is built by dpkg-buildpackage.

To see what your debianization would produce, or how it differs from the debianization already present:

 % cabal-debian --debianize -n

This is equivalent to the library call

 % ghc -e 'Debian.Debianize.callDebianize ["-n"]'

To actually create the debianization and then build the debs,

 % ghc -e 'Debian.Debianize.callDebianize []'
 % sudo dpkg-buildpackage

At this point you may need to modify Cabal.defaultFlags to achieve specific packaging goals. Create a module for this in debian/Debianize.hs:

 import Data.Lens.Lazy
 import Data.Map as Map (insertWith)
 import Data.Set as Set (union, singleton)
 import Debian.Relation (BinPkgName(BinPkgName), Relation(Rel))
 import Debian.Debianize (defaultAtoms, depends, debianization, writeDebianization)
 main = debianization "." defaultAtoms >>=
        return . modL depends (insertWith union (BinPkgName "cabal-debian") (singleton (Rel (BinPkgName "debian-policy") Nothing Nothing))) >>=
        writeDebianization "."

Then to test it,

 % CABALDEBIAN='["-n"]' runhaskell debian/Debianize.hs

or equivalently

 % ghc -e 'Debian.Debianize.runDebianize ["-n"]'

and to run it for real:

 % runhaskell debian/Debianize.hs
DESIGN OVERVIEW

The three phases of the operation of the system are Input -> Finalization -> Output.

Input
Module Debian.Debianize.Input - gather inputs using IO operations and customization functions, from the .cabal file, an existing debianization, and so on. This information results in a value of type Atoms. Modules Types, Lenses, Inputs.
Customize
Make modifications to the input values
Finalization
Module Debian.Debianize.Finalize - Fill in any information missing from Atoms that is required to build the debianization based on the inputs and our policy decisions.
Debianize
Module Debian.Debianize.Files - Compute the paths and files of the debianization from the Atoms value.
Output
Module Debian.Debianize.Output - Perform a variety of output operations on the debianzation - writing or updating the files in a debian directory, comparing two debianizations, validate a debianization (ensure two debianizations match in source and binary package names), or describe a debianization.

There is also a high level function to run a script that runs this entire pipeline when it finds from a script found in a debian/Debianize.hs file.

Synopsis

Documentation

debianization :: Top -> DebT IO () -> DebT IO () -> DebT IO ()Source

Given an Atoms value, get any additional configuration information from the environment, read the cabal package description and possibly the debian/changelog file, then generate and return the new debianization (along with the data directory computed from the cabal package description.)

doDebianizeAction :: Top -> DebT IO ()Source

Depending on the options in atoms, either validate, describe, or write the generated debianization.

runDebianizeScript :: [String] -> IO BoolSource

Run the script in debian/Debianize.hs with the given command line arguments. Returns True if the script exists and succeeds. In this case it may be assumed that a debianization was created (or updated) in the debian subdirectory of the current directory. In this way we can include a script in a package to produce a customized debianization more sophisticated than the one that would be produced by the cabal-debian executable. An example is included in the debian subdirectory of this library.

writeDebianization :: Top -> DebT IO ()Source

Write the files of the debianization d to the directory top.

describeDebianization :: (MonadIO m, Functor m) => DebT m StringSource

Return a string describing the debianization - a list of file names and their contents in a somewhat human readable format.

compareDebianization :: Atoms -> Atoms -> IO StringSource

Compare the old and new debianizations, returning a string describing the differences.

validateDebianization :: Atoms -> Atoms -> ()Source

Make sure the new debianization matches the existing debianization in several ways - specifically, version number, and the names of the source and binary packages. Some debian packages come with a skeleton debianization that needs to be filled in, this can be used to make sure the debianization we produce is usable.

tightDependencyFixup :: Monad m => [(BinPkgName, BinPkgName)] -> BinPkgName -> DebT m ()Source

Create equals dependencies. For each pair (A, B), use dpkg-query to find out B's version number, version B. Then write a rule into P's .substvar that makes P require that that exact version of A, and another that makes P conflict with any older version of A.

doExecutable :: Monad m => BinPkgName -> InstallFile -> DebT m ()Source

Add a debian binary package to the debianization containing a cabal executable file.

doServer :: Monad m => BinPkgName -> Server -> DebT m ()Source

Add a debian binary package to the debianization containing a cabal executable file set up to be a server.

doWebsite :: Monad m => BinPkgName -> Site -> DebT m ()Source

Add a debian binary package to the debianization containing a cabal executable file set up to be a web site.

doBackups :: Monad m => BinPkgName -> String -> DebT m ()Source

Add a debian binary package to the debianization containing a cabal executable file set up to be a backup script.

inputDebianizationFile :: Top -> FilePath -> DebT IO ()Source

Try to input a file and if successful add it to the debianization.

inputMaintainer :: MonadIO m => DebT m ()Source

Try to compute a string for the the debian Maintainer: field using, in this order 1. the maintainer explicitly specified using Debian.Debianize.Monad.maintainer 2. the maintainer field of the cabal package, 3. the value returned by getDebianMaintainer, which looks in several environment variables, 4. the signature from the latest entry in debian/changelog, 5. the Debian Haskell Group, pkg-haskell-maintainers@lists.alioth.debian.org

Deb monad - Monad

runDebT :: Monad m => DebT m a -> Atoms -> m (a, Atoms)Source

execDebT :: Monad m => DebT m a -> Atoms -> m AtomsSource

evalDebT :: Monad m => DebT m a -> Atoms -> m aSource

runDebM :: DebM a -> Atoms -> (a, Atoms)Source

mapCabal :: Monad m => PackageName -> String -> DebT m ()Source

Map all versions of Cabal package pname to Debian package dname. Not really a debian package name, but the name of a cabal package that maps to the debian package name we want. (Should this be a SrcPkgName?)

splitCabal :: Monad m => PackageName -> String -> Version -> DebT m ()Source

Map versions less than ver of Cabal Package pname to Debian package ltname

substvarsSource

Arguments

:: Top 
-> DebType

The type of deb we want to write substvars for - Dev, Prof, or Doc

-> DebT IO () 

Expand the contents of the .substvars file for a library package. Each cabal package corresponds to a directory name-version, either in usrlib or in usrlibhaskell-packagesghc/lib. In that directory is a compiler subdirectory such as ghc-6.8.2. In the ghc subdirectory is one or two library files of the form libHSname-version.a and libHSname-version_p.a. We can determine the debian package names by running dpkg -S on these names, or examining the varlibdpkginfo/*.list files. From these we can determine the source package name, and from that the documentation package name.

Utility functions

withCurrentDirectory :: FilePath -> IO a -> IO aSource

From Darcs.Utils - set the working directory and run an IO operation.

buildDebVersionMap :: IO DebMapSource

Read and parse the status file for installed debian packages: varlibdpkgstatus

dpkgFileMap :: IO (Map FilePath (Set BinPkgName))Source

Create a map from pathname to the names of the packages that contains that pathname using the contents of the debian package info directory varlibdpkginfo.

debOfFile :: FilePath -> ReaderT (Map FilePath (Set BinPkgName)) IO (Maybe BinPkgName)Source

Given a path, return the name of the package that owns it.

(~=) :: Monad m => Lens a b -> b -> StateT a m ()Source

Set a lens value. (This is a version of Data.Lens.Lazy.~= that returns () instead of b.)

(~?=) :: Monad m => Lens a (Maybe b) -> Maybe b -> StateT a m ()Source

Set b if it currently isNothing and the argument isJust, that is 1. Nothing happens if the argument isNothing 2. Nothing happens if the current value isJust

(%=) :: Monad m => Lens a b -> (b -> b) -> StateT a m ()Source

Modify a value. (This is a version of Data.Lens.Lazy.%= that returns () instead of a.)

(+=) :: (Monad m, Ord b) => Lens a (Set b) -> b -> StateT a m ()Source

Insert an element into a (Set b)

(++=) :: (Monad m, Ord b) => Lens a (Map b c) -> (b, c) -> StateT a m ()Source

Insert an element into a (Map b c)

(+++=) :: (Monad m, Ord b, Monoid c) => Lens a (Map b c) -> (b, c) -> StateT a m ()Source

Insert an element into a (Map b (Set c))

TBD