Fix header level for foreign-libraries section
[cabal.git] / Cabal / Distribution / Make.hs
blob63467c02a912ebfcd01ef301ae953a537a9c0ca6
1 {-# LANGUAGE FlexibleContexts #-}
2 {-# LANGUAGE RankNTypes #-}
4 -----------------------------------------------------------------------------
5 -- |
6 -- Module : Distribution.Make
7 -- Copyright : Martin Sjögren 2004
8 -- License : BSD3
9 --
10 -- Maintainer : cabal-devel@haskell.org
11 -- Portability : portable
13 -- This is an alternative build system that delegates everything to the @make@
14 -- program. All the commands just end up calling @make@ with appropriate
15 -- arguments. The intention was to allow preexisting packages that used
16 -- makefiles to be wrapped into Cabal packages. In practice essentially all
17 -- such packages were converted over to the \"Simple\" build system instead.
18 -- Consequently this module is not used much and it certainly only sees cursory
19 -- maintenance and no testing. Perhaps at some point we should stop pretending
20 -- that it works.
22 -- Uses the parsed command-line from "Distribution.Simple.Setup" in order to build
23 -- Haskell tools using a back-end build system based on make. Obviously we
24 -- assume that there is a configure script, and that after the ConfigCmd has
25 -- been run, there is a Makefile. Further assumptions:
27 -- [ConfigCmd] We assume the configure script accepts
28 -- @--with-hc@,
29 -- @--with-hc-pkg@,
30 -- @--prefix@,
31 -- @--bindir@,
32 -- @--libdir@,
33 -- @--libexecdir@,
34 -- @--datadir@.
36 -- [BuildCmd] We assume that the default Makefile target will build everything.
38 -- [InstallCmd] We assume there is an @install@ target. Note that we assume that
39 -- this does *not* register the package!
41 -- [CopyCmd] We assume there is a @copy@ target, and a variable @$(destdir)@.
42 -- The @copy@ target should probably just invoke @make install@
43 -- recursively (e.g. @$(MAKE) install prefix=$(destdir)\/$(prefix)
44 -- bindir=$(destdir)\/$(bindir)@. The reason we can\'t invoke @make
45 -- install@ directly here is that we don\'t know the value of @$(prefix)@.
47 -- [SDistCmd] We assume there is a @dist@ target.
49 -- [RegisterCmd] We assume there is a @register@ target and a variable @$(user)@.
51 -- [UnregisterCmd] We assume there is an @unregister@ target.
53 -- [HaddockCmd] We assume there is a @docs@ or @doc@ target.
56 -- copy :
57 -- $(MAKE) install prefix=$(destdir)/$(prefix) \
58 -- bindir=$(destdir)/$(bindir) \
60 module Distribution.Make (
61 module Distribution.Package,
62 License(..), Version,
63 defaultMain, defaultMainArgs, defaultMainNoRead
64 ) where
66 import Prelude ()
67 import Distribution.Compat.Prelude
69 -- local
70 import Distribution.Compat.Exception
71 import Distribution.Package
72 import Distribution.Simple.Program
73 import Distribution.PackageDescription
74 import Distribution.Simple.Setup
75 import Distribution.Simple.Command
77 import Distribution.Simple.Utils
79 import Distribution.License
80 import Distribution.Version
81 import Distribution.Text
83 import System.Environment (getArgs, getProgName)
84 import System.Exit
86 defaultMain :: IO ()
87 defaultMain = getArgs >>= defaultMainArgs
89 defaultMainArgs :: [String] -> IO ()
90 defaultMainArgs = defaultMainHelper
92 {-# DEPRECATED defaultMainNoRead "it ignores its PackageDescription arg" #-}
93 defaultMainNoRead :: PackageDescription -> IO ()
94 defaultMainNoRead = const defaultMain
96 defaultMainHelper :: [String] -> IO ()
97 defaultMainHelper args =
98 case commandsRun (globalCommand commands) commands args of
99 CommandHelp help -> printHelp help
100 CommandList opts -> printOptionsList opts
101 CommandErrors errs -> printErrors errs
102 CommandReadyToGo (flags, commandParse) ->
103 case commandParse of
104 _ | fromFlag (globalVersion flags) -> printVersion
105 | fromFlag (globalNumericVersion flags) -> printNumericVersion
106 CommandHelp help -> printHelp help
107 CommandList opts -> printOptionsList opts
108 CommandErrors errs -> printErrors errs
109 CommandReadyToGo action -> action
111 where
112 printHelp help = getProgName >>= putStr . help
113 printOptionsList = putStr . unlines
114 printErrors errs = do
115 putStr (intercalate "\n" errs)
116 exitWith (ExitFailure 1)
117 printNumericVersion = putStrLn $ display cabalVersion
118 printVersion = putStrLn $ "Cabal library version "
119 ++ display cabalVersion
121 progs = defaultProgramDb
122 commands =
123 [configureCommand progs `commandAddAction` configureAction
124 ,buildCommand progs `commandAddAction` buildAction
125 ,installCommand `commandAddAction` installAction
126 ,copyCommand `commandAddAction` copyAction
127 ,haddockCommand `commandAddAction` haddockAction
128 ,cleanCommand `commandAddAction` cleanAction
129 ,sdistCommand `commandAddAction` sdistAction
130 ,registerCommand `commandAddAction` registerAction
131 ,unregisterCommand `commandAddAction` unregisterAction
134 configureAction :: ConfigFlags -> [String] -> IO ()
135 configureAction flags args = do
136 noExtraFlags args
137 let verbosity = fromFlag (configVerbosity flags)
138 rawSystemExit verbosity "sh" $
139 "configure"
140 : configureArgs backwardsCompatHack flags
141 where backwardsCompatHack = True
143 copyAction :: CopyFlags -> [String] -> IO ()
144 copyAction flags args = do
145 noExtraFlags args
146 let destArgs = case fromFlag $ copyDest flags of
147 NoCopyDest -> ["install"]
148 CopyTo path -> ["copy", "destdir=" ++ path]
149 rawSystemExit (fromFlag $ copyVerbosity flags) "make" destArgs
151 installAction :: InstallFlags -> [String] -> IO ()
152 installAction flags args = do
153 noExtraFlags args
154 rawSystemExit (fromFlag $ installVerbosity flags) "make" ["install"]
155 rawSystemExit (fromFlag $ installVerbosity flags) "make" ["register"]
157 haddockAction :: HaddockFlags -> [String] -> IO ()
158 haddockAction flags args = do
159 noExtraFlags args
160 rawSystemExit (fromFlag $ haddockVerbosity flags) "make" ["docs"]
161 `catchIO` \_ ->
162 rawSystemExit (fromFlag $ haddockVerbosity flags) "make" ["doc"]
164 buildAction :: BuildFlags -> [String] -> IO ()
165 buildAction flags args = do
166 noExtraFlags args
167 rawSystemExit (fromFlag $ buildVerbosity flags) "make" []
169 cleanAction :: CleanFlags -> [String] -> IO ()
170 cleanAction flags args = do
171 noExtraFlags args
172 rawSystemExit (fromFlag $ cleanVerbosity flags) "make" ["clean"]
174 sdistAction :: SDistFlags -> [String] -> IO ()
175 sdistAction flags args = do
176 noExtraFlags args
177 rawSystemExit (fromFlag $ sDistVerbosity flags) "make" ["dist"]
179 registerAction :: RegisterFlags -> [String] -> IO ()
180 registerAction flags args = do
181 noExtraFlags args
182 rawSystemExit (fromFlag $ regVerbosity flags) "make" ["register"]
184 unregisterAction :: RegisterFlags -> [String] -> IO ()
185 unregisterAction flags args = do
186 noExtraFlags args
187 rawSystemExit (fromFlag $ regVerbosity flags) "make" ["unregister"]