File: CabalDebian.hs

package info (click to toggle)
cabal-debian 4.17.4-1
  • links: PTS
  • area: main
  • in suites: jessie, jessie-kfreebsd
  • size: 1,040 kB
  • ctags: 8
  • sloc: haskell: 4,820; sh: 167; makefile: 145
file content (55 lines) | stat: -rw-r--r-- 3,170 bytes parent folder | download
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
{-# LANGUAGE ScopedTypeVariables #-}
-- | This is the main function of the cabal-debian executable.  This
-- is generally run by the autobuilder to debianize packages that
-- don't have any custom debianization code in Setup.hs.  This is a
-- less flexible and powerful method than calling the debianize
-- function directly, many sophisticated configuration options cannot
-- be accessed using the command line interface.

import Control.Monad.Trans (MonadIO, liftIO)
import Data.Lens.Lazy (access)
import Data.List as List (unlines)
import Debian.Debianize.Details (debianDefaultAtoms)
import Debian.Debianize.Finalize (debianization)
import Debian.Debianize.Monad (DebT, evalDebT)
import Debian.Debianize.Options (compileCommandlineArgs, compileEnvironmentArgs, options)
import Debian.Debianize.Output (doDebianizeAction)
import Debian.Debianize.SubstVars (substvars)
import Debian.Debianize.Types.Atoms (DebAction(Debianize, SubstVar, Usage), EnvSet(EnvSet), debAction, newAtoms)
import Prelude hiding (unlines, writeFile, init)
import System.Console.GetOpt (OptDescr, usageInfo)
import System.Environment (getProgName)

main :: IO ()
main = cabalDebianMain debianDefaultAtoms

-- | The main function for the cabal-debian executable.
cabalDebianMain :: (MonadIO m, Functor m) => DebT m () -> m ()
cabalDebianMain init =
    -- This picks up the options required to decide what action we are
    -- taking.  Much of this will be repeated in the call to debianize.
    do atoms <- newAtoms
       evalDebT (do init
                    compileEnvironmentArgs
                    compileCommandlineArgs
                    action <- access debAction
                    finish action) atoms
    where
      envset = EnvSet "/" "/" "/"
      finish :: forall m. (MonadIO m, Functor m) => DebAction -> DebT m ()
      finish (SubstVar debType) = substvars debType
      finish Debianize = debianization (return ()) (return ()) >> doDebianizeAction envset
      finish Usage = do
          progName <- liftIO getProgName
          let info = unlines [ "Typical usage is to cd to the top directory of the package's unpacked source and run: "
                             , ""
                             , "    " ++ progName ++ " --maintainer 'Maintainer Name <maintainer@email>'."
                             , ""
                             , "This will read the package's cabal file and any existing debian/changelog file and"
                             , "deduce what it can about the debianization, then it will create or modify files in"
                             , "the debian subdirectory.  Note that it will not remove any files in debian, and"
                             , "these could affect the operation of the debianization in unknown ways.  For this"
                             , "reason I recommend either using a pristine unpacked directory each time, or else"
                             , "using a revision control system to revert the package to a known state before running."
                             , "The following additional options are available:" ]
          liftIO $ putStrLn (usageInfo info (options :: [OptDescr (DebT m ())]))