~ubuntu-branches/ubuntu/precise/ghc/precise

« back to all changes in this revision

Viewing changes to libraries/Cabal/Distribution/Simple.hs

  • Committer: Bazaar Package Importer
  • Author(s): Joachim Breitner
  • Date: 2011-01-17 12:49:24 UTC
  • Revision ID: james.westby@ubuntu.com-20110117124924-do1pym1jlf5o636m
Tags: upstream-7.0.1
ImportĀ upstreamĀ versionĀ 7.0.1

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
-----------------------------------------------------------------------------
 
2
-- |
 
3
-- Module      :  Distribution.Simple
 
4
-- Copyright   :  Isaac Jones 2003-2005
 
5
--
 
6
-- Maintainer  :  cabal-devel@haskell.org
 
7
-- Portability :  portable
 
8
--
 
9
-- This is the command line front end to the Simple build system. When given
 
10
-- the parsed command-line args and package information, is able to perform
 
11
-- basic commands like configure, build, install, register, etc.
 
12
--
 
13
-- This module exports the main functions that Setup.hs scripts use. It
 
14
-- re-exports the 'UserHooks' type, the standard entry points like
 
15
-- 'defaultMain' and 'defaultMainWithHooks' and the predefined sets of
 
16
-- 'UserHooks' that custom @Setup.hs@ scripts can extend to add their own
 
17
-- behaviour.
 
18
--
 
19
-- This module isn't called \"Simple\" because it's simple.  Far from
 
20
-- it.  It's called \"Simple\" because it does complicated things to
 
21
-- simple software.
 
22
--
 
23
-- The original idea was that there could be different build systems that all
 
24
-- presented the same compatible command line interfaces. There is still a
 
25
-- "Distribution.Make" system but in practice no packages use it.
 
26
 
 
27
{- All rights reserved.
 
28
 
 
29
Redistribution and use in source and binary forms, with or without
 
30
modification, are permitted provided that the following conditions are
 
31
met:
 
32
 
 
33
    * Redistributions of source code must retain the above copyright
 
34
      notice, this list of conditions and the following disclaimer.
 
35
 
 
36
    * Redistributions in binary form must reproduce the above
 
37
      copyright notice, this list of conditions and the following
 
38
      disclaimer in the documentation and/or other materials provided
 
39
      with the distribution.
 
40
 
 
41
    * Neither the name of Isaac Jones nor the names of other
 
42
      contributors may be used to endorse or promote products derived
 
43
      from this software without specific prior written permission.
 
44
 
 
45
THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
 
46
"AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
 
47
LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR
 
48
A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT
 
49
OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL,
 
50
SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT
 
51
LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE,
 
52
DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY
 
53
THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
 
54
(INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE
 
55
OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. -}
 
56
 
 
57
{-
 
58
Work around this warning:
 
59
libraries/Cabal/Distribution/Simple.hs:78:0:
 
60
    Warning: In the use of `runTests'
 
61
             (imported from Distribution.Simple.UserHooks):
 
62
             Deprecated: "Please use the new testing interface instead!"
 
63
-}
 
64
{-# OPTIONS_GHC -fno-warn-deprecations #-}
 
65
 
 
66
module Distribution.Simple (
 
67
        module Distribution.Package,
 
68
        module Distribution.Version,
 
69
        module Distribution.License,
 
70
        module Distribution.Simple.Compiler,
 
71
        module Language.Haskell.Extension,
 
72
        -- * Simple interface
 
73
        defaultMain, defaultMainNoRead, defaultMainArgs,
 
74
        -- * Customization
 
75
        UserHooks(..), Args,
 
76
        defaultMainWithHooks, defaultMainWithHooksArgs,
 
77
        -- ** Standard sets of hooks
 
78
        simpleUserHooks,
 
79
        autoconfUserHooks,
 
80
        defaultUserHooks, emptyUserHooks,
 
81
        -- ** Utils
 
82
        defaultHookedPackageDesc
 
83
  ) where
 
84
 
 
85
-- local
 
86
import Distribution.Simple.Compiler hiding (Flag)
 
87
import Distribution.Simple.UserHooks
 
88
import Distribution.Package --must not specify imports, since we're exporting moule.
 
89
import Distribution.PackageDescription
 
90
         ( PackageDescription(..), GenericPackageDescription
 
91
         , updatePackageDescription, hasLibs
 
92
         , HookedBuildInfo, emptyHookedBuildInfo )
 
93
import Distribution.PackageDescription.Parse
 
94
         ( readPackageDescription, readHookedBuildInfo )
 
95
import Distribution.PackageDescription.Configuration
 
96
         ( flattenPackageDescription )
 
97
import Distribution.Simple.Program
 
98
         ( defaultProgramConfiguration, addKnownPrograms, builtinPrograms
 
99
         , restoreProgramConfiguration, reconfigurePrograms )
 
100
import Distribution.Simple.PreProcess (knownSuffixHandlers, PPSuffixHandler)
 
101
import Distribution.Simple.Setup
 
102
import Distribution.Simple.Command
 
103
 
 
104
import Distribution.Simple.Build        ( build )
 
105
import Distribution.Simple.SrcDist      ( sdist )
 
106
import Distribution.Simple.Register
 
107
         ( register, unregister )
 
108
 
 
109
import Distribution.Simple.Configure
 
110
         ( getPersistBuildConfig, maybeGetPersistBuildConfig
 
111
         , writePersistBuildConfig, checkPersistBuildConfigOutdated
 
112
         , configure, checkForeignDeps )
 
113
 
 
114
import Distribution.Simple.LocalBuildInfo ( LocalBuildInfo(..) )
 
115
import Distribution.Simple.BuildPaths ( srcPref)
 
116
import Distribution.Simple.Test (test)
 
117
import Distribution.Simple.Install (install)
 
118
import Distribution.Simple.Haddock (haddock, hscolour)
 
119
import Distribution.Simple.Utils
 
120
         (die, notice, info, warn, setupMessage, chattyTry,
 
121
          defaultPackageDesc, defaultHookedPackageDesc,
 
122
          rawSystemExit, cabalVersion, topHandler )
 
123
import Distribution.System
 
124
         ( OS(..), buildOS )
 
125
import Distribution.Verbosity
 
126
import Language.Haskell.Extension
 
127
import Distribution.Version
 
128
import Distribution.License
 
129
import Distribution.Text
 
130
         ( display )
 
131
 
 
132
-- Base
 
133
import System.Environment(getArgs,getProgName)
 
134
import System.Directory(removeFile, doesFileExist,
 
135
                        doesDirectoryExist, removeDirectoryRecursive)
 
136
import System.Exit
 
137
import System.IO.Error   (isDoesNotExistError)
 
138
import Distribution.Compat.Exception (catchIO, throwIOIO)
 
139
 
 
140
import Control.Monad   (when)
 
141
import Data.List       (intersperse, unionBy)
 
142
 
 
143
-- | A simple implementation of @main@ for a Cabal setup script.
 
144
-- It reads the package description file using IO, and performs the
 
145
-- action specified on the command line.
 
146
defaultMain :: IO ()
 
147
defaultMain = getArgs >>= defaultMainHelper simpleUserHooks
 
148
 
 
149
-- | A version of 'defaultMain' that is passed the command line
 
150
-- arguments, rather than getting them from the environment.
 
151
defaultMainArgs :: [String] -> IO ()
 
152
defaultMainArgs = defaultMainHelper simpleUserHooks
 
153
 
 
154
-- | A customizable version of 'defaultMain'.
 
155
defaultMainWithHooks :: UserHooks -> IO ()
 
156
defaultMainWithHooks hooks = getArgs >>= defaultMainHelper hooks
 
157
 
 
158
-- | A customizable version of 'defaultMain' that also takes the command
 
159
-- line arguments.
 
160
defaultMainWithHooksArgs :: UserHooks -> [String] -> IO ()
 
161
defaultMainWithHooksArgs = defaultMainHelper
 
162
 
 
163
-- | Like 'defaultMain', but accepts the package description as input
 
164
-- rather than using IO to read it.
 
165
defaultMainNoRead :: GenericPackageDescription -> IO ()
 
166
defaultMainNoRead pkg_descr =
 
167
  getArgs >>=
 
168
  defaultMainHelper simpleUserHooks { readDesc = return (Just pkg_descr) }
 
169
 
 
170
defaultMainHelper :: UserHooks -> Args -> IO ()
 
171
defaultMainHelper hooks args = topHandler $
 
172
  case commandsRun globalCommand commands args of
 
173
    CommandHelp   help                 -> printHelp help
 
174
    CommandList   opts                 -> printOptionsList opts
 
175
    CommandErrors errs                 -> printErrors errs
 
176
    CommandReadyToGo (flags, commandParse)  ->
 
177
      case commandParse of
 
178
        _ | fromFlag (globalVersion flags)        -> printVersion
 
179
          | fromFlag (globalNumericVersion flags) -> printNumericVersion
 
180
        CommandHelp     help           -> printHelp help
 
181
        CommandList     opts           -> printOptionsList opts
 
182
        CommandErrors   errs           -> printErrors errs
 
183
        CommandReadyToGo action        -> action
 
184
 
 
185
  where
 
186
    printHelp help = getProgName >>= putStr . help
 
187
    printOptionsList = putStr . unlines
 
188
    printErrors errs = do
 
189
      putStr (concat (intersperse "\n" errs))
 
190
      exitWith (ExitFailure 1)
 
191
    printNumericVersion = putStrLn $ display cabalVersion
 
192
    printVersion        = putStrLn $ "Cabal library version "
 
193
                                  ++ display cabalVersion
 
194
 
 
195
    progs = addKnownPrograms (hookedPrograms hooks) defaultProgramConfiguration
 
196
    commands =
 
197
      [configureCommand progs `commandAddAction` \fs as ->
 
198
                                                 configureAction    hooks fs as >> return ()
 
199
      ,buildCommand     progs `commandAddAction` buildAction        hooks
 
200
      ,installCommand         `commandAddAction` installAction      hooks
 
201
      ,copyCommand            `commandAddAction` copyAction         hooks
 
202
      ,haddockCommand         `commandAddAction` haddockAction      hooks
 
203
      ,cleanCommand           `commandAddAction` cleanAction        hooks
 
204
      ,sdistCommand           `commandAddAction` sdistAction        hooks
 
205
      ,hscolourCommand        `commandAddAction` hscolourAction     hooks
 
206
      ,registerCommand        `commandAddAction` registerAction     hooks
 
207
      ,unregisterCommand      `commandAddAction` unregisterAction   hooks
 
208
      ,testCommand            `commandAddAction` testAction         hooks
 
209
      ]
 
210
 
 
211
-- | Combine the preprocessors in the given hooks with the
 
212
-- preprocessors built into cabal.
 
213
allSuffixHandlers :: UserHooks
 
214
                  -> [PPSuffixHandler]
 
215
allSuffixHandlers hooks
 
216
    = overridesPP (hookedPreProcessors hooks) knownSuffixHandlers
 
217
    where
 
218
      overridesPP :: [PPSuffixHandler] -> [PPSuffixHandler] -> [PPSuffixHandler]
 
219
      overridesPP = unionBy (\x y -> fst x == fst y)
 
220
 
 
221
configureAction :: UserHooks -> ConfigFlags -> Args -> IO LocalBuildInfo
 
222
configureAction hooks flags args = do
 
223
                let distPref = fromFlag $ configDistPref flags
 
224
                pbi <- preConf hooks args flags
 
225
 
 
226
                (mb_pd_file, pkg_descr0) <- confPkgDescr
 
227
 
 
228
                --    get_pkg_descr (configVerbosity flags')
 
229
                --let pkg_descr = updatePackageDescription pbi pkg_descr0
 
230
                let epkg_descr = (pkg_descr0, pbi)
 
231
 
 
232
                --(warns, ers) <- sanityCheckPackage pkg_descr
 
233
                --errorOut (configVerbosity flags') warns ers
 
234
 
 
235
                localbuildinfo0 <- confHook hooks epkg_descr flags
 
236
 
 
237
                -- remember the .cabal filename if we know it
 
238
                -- and all the extra command line args
 
239
                let localbuildinfo = localbuildinfo0 {
 
240
                                       pkgDescrFile = mb_pd_file,
 
241
                                       extraConfigArgs = args
 
242
                                     }
 
243
                writePersistBuildConfig distPref localbuildinfo
 
244
 
 
245
                let pkg_descr = localPkgDescr localbuildinfo
 
246
                postConf hooks args flags pkg_descr localbuildinfo
 
247
                return localbuildinfo
 
248
              where
 
249
                verbosity = fromFlag (configVerbosity flags)
 
250
                confPkgDescr :: IO (Maybe FilePath, GenericPackageDescription)
 
251
                confPkgDescr = do
 
252
                  mdescr <- readDesc hooks
 
253
                  case mdescr of
 
254
                    Just descr -> return (Nothing, descr)
 
255
                    Nothing -> do
 
256
                      pdfile <- defaultPackageDesc verbosity
 
257
                      descr  <- readPackageDescription verbosity pdfile
 
258
                      return (Just pdfile, descr)
 
259
 
 
260
buildAction :: UserHooks -> BuildFlags -> Args -> IO ()
 
261
buildAction hooks flags args = do
 
262
  let distPref  = fromFlag $ buildDistPref flags
 
263
      verbosity = fromFlag $ buildVerbosity flags
 
264
 
 
265
  lbi <- getBuildConfig hooks verbosity distPref
 
266
  progs <- reconfigurePrograms verbosity
 
267
             (buildProgramPaths flags)
 
268
             (buildProgramArgs flags)
 
269
             (withPrograms lbi)
 
270
 
 
271
  hookedAction preBuild buildHook postBuild
 
272
               (return lbi { withPrograms = progs })
 
273
               hooks flags args
 
274
 
 
275
hscolourAction :: UserHooks -> HscolourFlags -> Args -> IO ()
 
276
hscolourAction hooks flags args
 
277
    = do let distPref  = fromFlag $ hscolourDistPref flags
 
278
             verbosity = fromFlag $ hscolourVerbosity flags
 
279
         hookedAction preHscolour hscolourHook postHscolour
 
280
                      (getBuildConfig hooks verbosity distPref)
 
281
                      hooks flags args
 
282
 
 
283
haddockAction :: UserHooks -> HaddockFlags -> Args -> IO ()
 
284
haddockAction hooks flags args = do
 
285
  let distPref  = fromFlag $ haddockDistPref flags
 
286
      verbosity = fromFlag $ haddockVerbosity flags
 
287
 
 
288
  lbi <- getBuildConfig hooks verbosity distPref
 
289
  progs <- reconfigurePrograms verbosity
 
290
             (haddockProgramPaths flags)
 
291
             (haddockProgramArgs flags)
 
292
             (withPrograms lbi)
 
293
 
 
294
  hookedAction preHaddock haddockHook postHaddock
 
295
               (return lbi { withPrograms = progs })
 
296
               hooks flags args
 
297
 
 
298
cleanAction :: UserHooks -> CleanFlags -> Args -> IO ()
 
299
cleanAction hooks flags args = do
 
300
                pbi <- preClean hooks args flags
 
301
 
 
302
                pdfile <- defaultPackageDesc verbosity
 
303
                ppd <- readPackageDescription verbosity pdfile
 
304
                let pkg_descr0 = flattenPackageDescription ppd
 
305
                let pkg_descr = updatePackageDescription pbi pkg_descr0
 
306
 
 
307
                cleanHook hooks pkg_descr () hooks flags
 
308
                postClean hooks args flags pkg_descr ()
 
309
  where verbosity = fromFlag (cleanVerbosity flags)
 
310
 
 
311
copyAction :: UserHooks -> CopyFlags -> Args -> IO ()
 
312
copyAction hooks flags args
 
313
    = do let distPref  = fromFlag $ copyDistPref flags
 
314
             verbosity = fromFlag $ copyVerbosity flags
 
315
         hookedAction preCopy copyHook postCopy
 
316
                      (getBuildConfig hooks verbosity distPref)
 
317
                      hooks flags args
 
318
 
 
319
installAction :: UserHooks -> InstallFlags -> Args -> IO ()
 
320
installAction hooks flags args
 
321
    = do let distPref  = fromFlag $ installDistPref flags
 
322
             verbosity = fromFlag $ installVerbosity flags
 
323
         hookedAction preInst instHook postInst
 
324
                      (getBuildConfig hooks verbosity distPref)
 
325
                      hooks flags args
 
326
 
 
327
sdistAction :: UserHooks -> SDistFlags -> Args -> IO ()
 
328
sdistAction hooks flags args = do
 
329
                let distPref = fromFlag $ sDistDistPref flags
 
330
                pbi <- preSDist hooks args flags
 
331
 
 
332
                mlbi <- maybeGetPersistBuildConfig distPref
 
333
                pdfile <- defaultPackageDesc verbosity
 
334
                ppd <- readPackageDescription verbosity pdfile
 
335
                let pkg_descr0 = flattenPackageDescription ppd
 
336
                let pkg_descr = updatePackageDescription pbi pkg_descr0
 
337
 
 
338
                sDistHook hooks pkg_descr mlbi hooks flags
 
339
                postSDist hooks args flags pkg_descr mlbi
 
340
  where verbosity = fromFlag (sDistVerbosity flags)
 
341
 
 
342
testAction :: UserHooks -> TestFlags -> Args -> IO ()
 
343
testAction hooks flags args = do
 
344
    let distPref  = fromFlag $ testDistPref flags
 
345
        verbosity = fromFlag $ testVerbosity flags
 
346
    localBuildInfo <- getBuildConfig hooks verbosity distPref
 
347
    let pkg_descr = localPkgDescr localBuildInfo
 
348
    -- It is safe to do 'runTests' before the new test handler because the
 
349
    -- default action is a no-op and if the package uses the old test interface
 
350
    -- the new handler will find no tests.
 
351
    runTests hooks args False pkg_descr localBuildInfo
 
352
    --FIXME: this is a hack, passing the args inside the flags
 
353
    -- it's because the args to not get passed to the main test hook
 
354
    let flags' = flags { testList = Flag args }
 
355
    hookedAction preTest testHook postTest
 
356
            (getBuildConfig hooks verbosity distPref)
 
357
            hooks flags' args
 
358
 
 
359
registerAction :: UserHooks -> RegisterFlags -> Args -> IO ()
 
360
registerAction hooks flags args
 
361
    = do let distPref  = fromFlag $ regDistPref flags
 
362
             verbosity = fromFlag $ regVerbosity flags
 
363
         hookedAction preReg regHook postReg
 
364
                      (getBuildConfig hooks verbosity distPref)
 
365
                      hooks flags args
 
366
 
 
367
unregisterAction :: UserHooks -> RegisterFlags -> Args -> IO ()
 
368
unregisterAction hooks flags args
 
369
    = do let distPref  = fromFlag $ regDistPref flags
 
370
             verbosity = fromFlag $ regVerbosity flags
 
371
         hookedAction preUnreg unregHook postUnreg
 
372
                      (getBuildConfig hooks verbosity distPref)
 
373
                      hooks flags args
 
374
 
 
375
hookedAction :: (UserHooks -> Args -> flags -> IO HookedBuildInfo)
 
376
        -> (UserHooks -> PackageDescription -> LocalBuildInfo
 
377
                      -> UserHooks -> flags -> IO ())
 
378
        -> (UserHooks -> Args -> flags -> PackageDescription
 
379
                      -> LocalBuildInfo -> IO ())
 
380
        -> IO LocalBuildInfo
 
381
        -> UserHooks -> flags -> Args -> IO ()
 
382
hookedAction pre_hook cmd_hook post_hook get_build_config hooks flags args = do
 
383
   pbi <- pre_hook hooks args flags
 
384
   localbuildinfo <- get_build_config
 
385
   let pkg_descr0 = localPkgDescr localbuildinfo
 
386
   --pkg_descr0 <- get_pkg_descr (get_verbose flags)
 
387
   let pkg_descr = updatePackageDescription pbi pkg_descr0
 
388
   -- TODO: should we write the modified package descr back to the
 
389
   -- localbuildinfo?
 
390
   cmd_hook hooks pkg_descr localbuildinfo hooks flags
 
391
   post_hook hooks args flags pkg_descr localbuildinfo
 
392
 
 
393
getBuildConfig :: UserHooks -> Verbosity -> FilePath -> IO LocalBuildInfo
 
394
getBuildConfig hooks verbosity distPref = do
 
395
  lbi_wo_programs <- getPersistBuildConfig distPref
 
396
  -- Restore info about unconfigured programs, since it is not serialized
 
397
  let lbi = lbi_wo_programs {
 
398
    withPrograms = restoreProgramConfiguration
 
399
                     (builtinPrograms ++ hookedPrograms hooks)
 
400
                     (withPrograms lbi_wo_programs)
 
401
  }
 
402
 
 
403
  case pkgDescrFile lbi of
 
404
    Nothing -> return lbi
 
405
    Just pkg_descr_file -> do
 
406
      outdated <- checkPersistBuildConfigOutdated distPref pkg_descr_file
 
407
      if outdated
 
408
        then reconfigure pkg_descr_file lbi
 
409
        else return lbi
 
410
 
 
411
  where
 
412
    reconfigure :: FilePath -> LocalBuildInfo -> IO LocalBuildInfo
 
413
    reconfigure pkg_descr_file lbi = do
 
414
      notice verbosity $ pkg_descr_file ++ " has been changed. "
 
415
                      ++ "Re-configuring with most recently used options. " 
 
416
                      ++ "If this fails, please run configure manually.\n"
 
417
      let cFlags = configFlags lbi
 
418
      let cFlags' = cFlags {
 
419
            -- Since the list of unconfigured programs is not serialized,
 
420
            -- restore it to the same value as normally used at the beginning
 
421
            -- of a conigure run:
 
422
            configPrograms = restoreProgramConfiguration
 
423
                               (builtinPrograms ++ hookedPrograms hooks)
 
424
                               (configPrograms cFlags),
 
425
 
 
426
            -- Use the current, not saved verbosity level:
 
427
            configVerbosity = Flag verbosity
 
428
          }
 
429
      configureAction hooks cFlags' (extraConfigArgs lbi)
 
430
 
 
431
 
 
432
-- --------------------------------------------------------------------------
 
433
-- Cleaning
 
434
 
 
435
clean :: PackageDescription -> CleanFlags -> IO ()
 
436
clean pkg_descr flags = do
 
437
    let distPref = fromFlag $ cleanDistPref flags
 
438
    notice verbosity "cleaning..."
 
439
 
 
440
    maybeConfig <- if fromFlag (cleanSaveConf flags)
 
441
                     then maybeGetPersistBuildConfig distPref
 
442
                     else return Nothing
 
443
 
 
444
    -- remove the whole dist/ directory rather than tracking exactly what files
 
445
    -- we created in there.
 
446
    chattyTry "removing dist/" $ do
 
447
      exists <- doesDirectoryExist distPref
 
448
      when exists (removeDirectoryRecursive distPref)
 
449
 
 
450
    -- Any extra files the user wants to remove
 
451
    mapM_ removeFileOrDirectory (extraTmpFiles pkg_descr)
 
452
 
 
453
    -- If the user wanted to save the config, write it back
 
454
    maybe (return ()) (writePersistBuildConfig distPref) maybeConfig
 
455
 
 
456
  where
 
457
        removeFileOrDirectory :: FilePath -> IO ()
 
458
        removeFileOrDirectory fname = do
 
459
            isDir <- doesDirectoryExist fname
 
460
            isFile <- doesFileExist fname
 
461
            if isDir then removeDirectoryRecursive fname
 
462
              else if isFile then removeFile fname
 
463
              else return ()
 
464
        verbosity = fromFlag (cleanVerbosity flags)
 
465
 
 
466
-- --------------------------------------------------------------------------
 
467
-- Default hooks
 
468
 
 
469
-- | Hooks that correspond to a plain instantiation of the
 
470
-- \"simple\" build system
 
471
simpleUserHooks :: UserHooks
 
472
simpleUserHooks =
 
473
    emptyUserHooks {
 
474
       confHook  = configure,
 
475
       postConf  = finalChecks,
 
476
       buildHook = defaultBuildHook,
 
477
       copyHook  = \desc lbi _ f -> install desc lbi f, -- has correct 'copy' behavior with params
 
478
       testHook = defaultTestHook,
 
479
       instHook  = defaultInstallHook,
 
480
       sDistHook = \p l h f -> sdist p l f srcPref (allSuffixHandlers h),
 
481
       cleanHook = \p _ _ f -> clean p f,
 
482
       hscolourHook = \p l h f -> hscolour p l (allSuffixHandlers h) f,
 
483
       haddockHook  = \p l h f -> haddock  p l (allSuffixHandlers h) f,
 
484
       regHook   = defaultRegHook,
 
485
       unregHook = \p l _ f -> unregister p l f
 
486
      }
 
487
  where
 
488
    finalChecks _args flags pkg_descr lbi =
 
489
      checkForeignDeps pkg_descr lbi (lessVerbose verbosity)
 
490
      where
 
491
        verbosity = fromFlag (configVerbosity flags)
 
492
 
 
493
-- | Basic autoconf 'UserHooks':
 
494
--
 
495
-- * 'postConf' runs @.\/configure@, if present.
 
496
--
 
497
-- * the pre-hooks 'preBuild', 'preClean', 'preCopy', 'preInst',
 
498
--   'preReg' and 'preUnreg' read additional build information from
 
499
--   /package/@.buildinfo@, if present.
 
500
--
 
501
-- Thus @configure@ can use local system information to generate
 
502
-- /package/@.buildinfo@ and possibly other files.
 
503
 
 
504
{-# DEPRECATED defaultUserHooks
 
505
     "Use simpleUserHooks or autoconfUserHooks, unless you need Cabal-1.2\n             compatibility in which case you must stick with defaultUserHooks" #-}
 
506
defaultUserHooks :: UserHooks
 
507
defaultUserHooks = autoconfUserHooks {
 
508
          confHook = \pkg flags -> do
 
509
                       let verbosity = fromFlag (configVerbosity flags)
 
510
                       warn verbosity $
 
511
                         "defaultUserHooks in Setup script is deprecated."
 
512
                       confHook autoconfUserHooks pkg flags,
 
513
          postConf = oldCompatPostConf
 
514
    }
 
515
    -- This is the annoying old version that only runs configure if it exists.
 
516
    -- It's here for compatibility with existing Setup.hs scripts. See:
 
517
    -- http://hackage.haskell.org/trac/hackage/ticket/165
 
518
    where oldCompatPostConf args flags pkg_descr lbi
 
519
              = do let verbosity = fromFlag (configVerbosity flags)
 
520
                   noExtraFlags args
 
521
                   confExists <- doesFileExist "configure"
 
522
                   when confExists $
 
523
                       runConfigureScript verbosity
 
524
                         backwardsCompatHack flags
 
525
 
 
526
                   pbi <- getHookedBuildInfo verbosity
 
527
                   let pkg_descr' = updatePackageDescription pbi pkg_descr
 
528
                   postConf simpleUserHooks args flags pkg_descr' lbi
 
529
 
 
530
          backwardsCompatHack = True
 
531
 
 
532
autoconfUserHooks :: UserHooks
 
533
autoconfUserHooks
 
534
    = simpleUserHooks
 
535
      {
 
536
       postConf    = defaultPostConf,
 
537
       preBuild    = readHook buildVerbosity,
 
538
       preClean    = readHook cleanVerbosity,
 
539
       preCopy     = readHook copyVerbosity,
 
540
       preInst     = readHook installVerbosity,
 
541
       preHscolour = readHook hscolourVerbosity,
 
542
       preHaddock  = readHook haddockVerbosity,
 
543
       preReg      = readHook regVerbosity,
 
544
       preUnreg    = readHook regVerbosity
 
545
      }
 
546
    where defaultPostConf :: Args -> ConfigFlags -> PackageDescription -> LocalBuildInfo -> IO ()
 
547
          defaultPostConf args flags pkg_descr lbi
 
548
              = do let verbosity = fromFlag (configVerbosity flags)
 
549
                   noExtraFlags args
 
550
                   confExists <- doesFileExist "configure"
 
551
                   if confExists
 
552
                     then runConfigureScript verbosity
 
553
                            backwardsCompatHack flags
 
554
                     else die "configure script not found."
 
555
 
 
556
                   pbi <- getHookedBuildInfo verbosity
 
557
                   let pkg_descr' = updatePackageDescription pbi pkg_descr
 
558
                   postConf simpleUserHooks args flags pkg_descr' lbi
 
559
 
 
560
          backwardsCompatHack = False
 
561
 
 
562
          readHook :: (a -> Flag Verbosity) -> Args -> a -> IO HookedBuildInfo
 
563
          readHook get_verbosity a flags = do
 
564
              noExtraFlags a
 
565
              getHookedBuildInfo verbosity
 
566
            where
 
567
              verbosity = fromFlag (get_verbosity flags)
 
568
 
 
569
runConfigureScript :: Verbosity -> Bool -> ConfigFlags -> IO ()
 
570
runConfigureScript verbosity backwardsCompatHack flags =
 
571
 
 
572
  handleNoWindowsSH $
 
573
    rawSystemExit verbosity "sh" args
 
574
 
 
575
  where
 
576
    args = "configure" : configureArgs backwardsCompatHack flags
 
577
 
 
578
    handleNoWindowsSH action
 
579
      | buildOS /= Windows
 
580
      = action
 
581
 
 
582
      | otherwise
 
583
      = action
 
584
          `catchIO` \ioe -> if isDoesNotExistError ioe
 
585
                              then die notFoundMsg
 
586
                              else throwIOIO ioe
 
587
 
 
588
    notFoundMsg = "The package has a './configure' script. This requires a "
 
589
               ++ "Unix compatibility toolchain such as MinGW+MSYS or Cygwin."
 
590
 
 
591
getHookedBuildInfo :: Verbosity -> IO HookedBuildInfo
 
592
getHookedBuildInfo verbosity = do
 
593
  maybe_infoFile <- defaultHookedPackageDesc
 
594
  case maybe_infoFile of
 
595
    Nothing       -> return emptyHookedBuildInfo
 
596
    Just infoFile -> do
 
597
      info verbosity $ "Reading parameters from " ++ infoFile
 
598
      readHookedBuildInfo verbosity infoFile
 
599
 
 
600
defaultTestHook :: PackageDescription -> LocalBuildInfo
 
601
                -> UserHooks -> TestFlags -> IO ()
 
602
defaultTestHook pkg_descr localbuildinfo _ flags =
 
603
    test pkg_descr localbuildinfo flags
 
604
 
 
605
defaultInstallHook :: PackageDescription -> LocalBuildInfo
 
606
                   -> UserHooks -> InstallFlags -> IO ()
 
607
defaultInstallHook pkg_descr localbuildinfo _ flags = do
 
608
  let copyFlags = defaultCopyFlags {
 
609
                      copyDistPref   = installDistPref flags,
 
610
                      copyDest       = toFlag NoCopyDest,
 
611
                      copyVerbosity  = installVerbosity flags
 
612
                  }
 
613
  install pkg_descr localbuildinfo copyFlags
 
614
  let registerFlags = defaultRegisterFlags {
 
615
                          regDistPref  = installDistPref flags,
 
616
                          regInPlace   = installInPlace flags,
 
617
                          regPackageDB = installPackageDB flags,
 
618
                          regVerbosity = installVerbosity flags
 
619
                      }
 
620
  when (hasLibs pkg_descr) $ register pkg_descr localbuildinfo registerFlags
 
621
 
 
622
defaultBuildHook :: PackageDescription -> LocalBuildInfo
 
623
        -> UserHooks -> BuildFlags -> IO ()
 
624
defaultBuildHook pkg_descr localbuildinfo hooks flags =
 
625
  build pkg_descr localbuildinfo flags (allSuffixHandlers hooks)
 
626
 
 
627
defaultRegHook :: PackageDescription -> LocalBuildInfo
 
628
        -> UserHooks -> RegisterFlags -> IO ()
 
629
defaultRegHook pkg_descr localbuildinfo _ flags =
 
630
    if hasLibs pkg_descr
 
631
    then register pkg_descr localbuildinfo flags
 
632
    else setupMessage verbosity
 
633
           "Package contains no library to register:" (packageId pkg_descr)
 
634
  where verbosity = fromFlag (regVerbosity flags)