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