This file is indexed.

/usr/lib/hugs/packages/Cabal/Distribution/Simple/GHC.hs is in libhugs-cabal-bundled 98.200609.21-5.3ubuntu1.

This file is owned by root:root, with mode 0o644.

The actual contents of the file can be viewed below.

  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
 56
 57
 58
 59
 60
 61
 62
 63
 64
 65
 66
 67
 68
 69
 70
 71
 72
 73
 74
 75
 76
 77
 78
 79
 80
 81
 82
 83
 84
 85
 86
 87
 88
 89
 90
 91
 92
 93
 94
 95
 96
 97
 98
 99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313
314
315
316
317
318
319
320
321
322
323
324
325
326
327
328
329
330
331
332
333
334
335
336
337
338
339
340
341
342
343
344
345
346
347
348
349
350
351
352
353
354
355
356
357
358
359
360
361
362
363
364
365
366
367
368
369
370
371
372
373
374
375
376
377
378
379
380
381
382
383
384
385
386
387
388
389
390
391
392
393
394
395
396
397
398
399
400
401
402
403
404
405
406
407
408
409
410
411
412
413
414
415
416
417
418
419
420
421
422
423
424
425
426
427
428
429
{-# OPTIONS_GHC -cpp #-}
-----------------------------------------------------------------------------
-- |
-- Module      :  Distribution.Simple.GHC
-- Copyright   :  Isaac Jones 2003-2006
-- 
-- Maintainer  :  Isaac Jones <ijones@syntaxpolice.org>
-- Stability   :  alpha
-- Portability :  portable
--

{- Copyright (c) 2003-2005, Isaac Jones
All rights reserved.

Redistribution and use in source and binary forms, with or without
modiication, are permitted provided that the following conditions are
met:

    * Redistributions of source code must retain the above copyright
      notice, this list of conditions and the following disclaimer.

    * Redistributions in binary form must reproduce the above
      copyright notice, this list of conditions and the following
      disclaimer in the documentation and/or other materials provided
      with the distribution.

    * Neither the name of Isaac Jones nor the names of other
      contributors may be used to endorse or promote products derived
      from this software without specific prior written permission.

THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
"AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR
A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT
OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL,
SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT
LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE,
DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY
THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
(INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE
OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. -}

module Distribution.Simple.GHC (
	build, installLib, installExe
 ) where

import Distribution.PackageDescription
				( PackageDescription(..), BuildInfo(..),
				  withLib, setupMessage,
				  Executable(..), withExe, Library(..),
				  libModules, hcOptions )
import Distribution.Simple.LocalBuildInfo
				( LocalBuildInfo(..), autogenModulesDir,
				  mkLibDir, mkIncludeDir )
import Distribution.Simple.Utils( rawSystemExit, rawSystemPath,
				  rawSystemVerbose, maybeExit, xargs,
				  die, dirOf, moduleToFilePath,
				  smartCopySources, findFile, copyFileVerbose,
                                  mkLibName, mkProfLibName, dotToSep )
import Distribution.Package  	( PackageIdentifier(..), showPackageId )
import Distribution.Program	( rawSystemProgram, ranlibProgram,
				  Program(..), ProgramConfiguration(..),
				  ProgramLocation(..),
				  lookupProgram, arProgram )
import Distribution.Compiler 	( Compiler(..), CompilerFlavor(..),
				  extensionsToGHCFlag )
import Distribution.Version	( Version(..) )
import Distribution.Compat.FilePath
				( joinFileName, exeExtension, joinFileExt,
				  splitFilePath, objExtension, joinPaths,
                                  isAbsolutePath, splitFileExt )
import Distribution.Compat.Directory 
				( createDirectoryIfMissing )
import qualified Distribution.Simple.GHCPackageConfig as GHC
				( localPackageConfig,
				  canReadLocalPackageConfig )
import Language.Haskell.Extension (Extension(..))

import Control.Monad		( unless, when )
import Data.List		( isSuffixOf, nub )
import System.Directory		( removeFile, renameFile,
				  getDirectoryContents, doesFileExist )
import System.Exit              (ExitCode(..))






import Control.Exception (try)




-- -----------------------------------------------------------------------------
-- Building

-- |Building for GHC.  If .ghc-packages exists and is readable, add
-- it to the command-line.
build :: PackageDescription -> LocalBuildInfo -> Int -> IO ()
build pkg_descr lbi verbose = do
  let pref = buildDir lbi
  let ghcPath = compilerPath (compiler lbi)
      ifVanillaLib forceVanilla = when (forceVanilla || withVanillaLib lbi)
      ifProfLib = when (withProfLib lbi)
      ifGHCiLib = when (withGHCiLib lbi)

  -- GHC versions prior to 6.4 didn't have the user package database,
  -- so we fake it.  TODO: This can go away in due course.
  pkg_conf <- if versionBranch (compilerVersion (compiler lbi)) >= [6,4]
		then return []
		else do  pkgConf <- GHC.localPackageConfig
			 pkgConfReadable <- GHC.canReadLocalPackageConfig
			 if pkgConfReadable 
				then return ["-package-conf", pkgConf]
				else return []
	       
  -- Build lib
  withLib pkg_descr () $ \lib -> do
      when (verbose > 3) (putStrLn "Building library...")
      let libBi = libBuildInfo lib
          libTargetDir = pref
	  forceVanillaLib = TemplateHaskell `elem` extensions libBi
	  -- TH always needs vanilla libs, even when building for profiling

      createDirectoryIfMissing True libTargetDir
      -- put hi-boot files into place for mutually recurive modules
      smartCopySources verbose (hsSourceDirs libBi)
                       libTargetDir (libModules pkg_descr) ["hi-boot"] False False
      let ghcArgs = 
                 pkg_conf
              ++ ["-package-name", showPackageId (package pkg_descr) ]
	      ++ (if splitObjs lbi then ["-split-objs"] else [])
              ++ constructGHCCmdLine lbi libBi libTargetDir verbose
              ++ (libModules pkg_descr)
          ghcArgsProf = ghcArgs
              ++ ["-prof",
                  "-hisuf", "p_hi",
                  "-osuf", "p_o"
                 ]
              ++ ghcProfOptions libBi
      unless (null (libModules pkg_descr)) $
        do ifVanillaLib forceVanillaLib (rawSystemExit verbose ghcPath ghcArgs)
           ifProfLib (rawSystemExit verbose ghcPath ghcArgsProf)

      -- build any C sources
      unless (null (cSources libBi)) $ do
         when (verbose > 3) (putStrLn "Building C Sources...")
         -- FIX: similar 'versionBranch' logic duplicated below. refactor for code sharing
         sequence_ [do let ghc_vers = compilerVersion (compiler lbi)
			   odir | versionBranch ghc_vers >= [6,4,1] = pref
				| otherwise = pref `joinFileName` dirOf c
				-- ghc 6.4.1 fixed a bug in -odir handling
				-- for C compilations.
                       createDirectoryIfMissing True odir
		       let cArgs = ["-I" ++ dir | dir <- includeDirs libBi]
			       ++ ["-optc" ++ opt | opt <- ccOptions libBi]
			       ++ ["-odir", odir, "-hidir", pref, "-c"]
			       ++ (if verbose > 4 then ["-v"] else [])
                       rawSystemExit verbose ghcPath (cArgs ++ [c])
                                   | c <- cSources libBi]

      -- link:
      when (verbose > 3) (putStrLn "cabal-linking...")
      let cObjs = [ path `joinFileName` file `joinFileExt` objExtension
                  | (path, file, _) <- (map splitFilePath (cSources libBi)) ]
          libName  = mkLibName pref (showPackageId (package pkg_descr))
          profLibName  = mkProfLibName pref (showPackageId (package pkg_descr))
	  ghciLibName = mkGHCiLibName pref (showPackageId (package pkg_descr))

      stubObjs <- sequence [moduleToFilePath [libTargetDir] (x ++"_stub") [objExtension]
                           |  x <- libModules pkg_descr ]  >>= return . concat
      stubProfObjs <- sequence [moduleToFilePath [libTargetDir] (x ++"_stub") ["p_" ++ objExtension]
                           |  x <- libModules pkg_descr ]  >>= return . concat

      hObjs     <- getHaskellObjects pkg_descr libBi lbi
			pref objExtension
      hProfObjs <- 
	if (withProfLib lbi)
		then getHaskellObjects pkg_descr libBi lbi
			pref ("p_" ++ objExtension)
		else return []

      unless (null hObjs && null cObjs && null stubObjs) $ do
        try (removeFile libName) -- first remove library if it exists
        try (removeFile profLibName) -- first remove library if it exists
	try (removeFile ghciLibName) -- first remove library if it exists
        let arArgs = ["q"++ (if verbose > 4 then "v" else "")]
                ++ [libName]
            arObjArgs =
		   hObjs
                ++ map (pref `joinFileName`) cObjs
                ++ stubObjs
            arProfArgs = ["q"++ (if verbose > 4 then "v" else "")]
                ++ [profLibName]
            arProfObjArgs =
		   hProfObjs
                ++ map (pref `joinFileName`) cObjs
                ++ stubProfObjs
	    ldArgs = ["-r"]
                ++ ["-x"] -- FIXME: only some systems's ld support the "-x" flag
	        ++ ["-o", ghciLibName `joinFileExt` "tmp"]
            ldObjArgs =
		   hObjs
                ++ map (pref `joinFileName`) cObjs
		++ stubObjs








            ld = "ld"
            rawSystemLd = rawSystemPath
             --TODO: discover this at configure time on unix
            maxCommandLineSize = 30 * 1024

            runLd ld args = do
              exists <- doesFileExist ghciLibName
              status <- rawSystemLd verbose ld
                          (args ++ if exists then [ghciLibName] else [])
              when (status == ExitSuccess)
                   (renameFile (ghciLibName `joinFileExt` "tmp") ghciLibName)
              return status

        ifVanillaLib False $ maybeExit $ xargs maxCommandLineSize
          (rawSystemPath verbose) "ar" arArgs arObjArgs

        ifProfLib $ maybeExit $ xargs maxCommandLineSize
          (rawSystemPath verbose) "ar" arProfArgs arProfObjArgs

        ifGHCiLib $ maybeExit $ xargs maxCommandLineSize
          runLd ld ldArgs ldObjArgs

  -- build any executables
  withExe pkg_descr $ \ (Executable exeName' modPath exeBi) -> do
                 when (verbose > 3)
                      (putStrLn $ "Building executable: " ++ exeName' ++ "...")

                 -- exeNameReal, the name that GHC really uses (with .exe on Windows)
                 let exeNameReal = exeName' `joinFileExt`
                                   (if null $ snd $ splitFileExt exeName' then exeExtension else "")

		 let targetDir = pref `joinFileName` exeName'
                 let exeDir = joinPaths targetDir (exeName' ++ "-tmp")
                 createDirectoryIfMissing True targetDir
                 createDirectoryIfMissing True exeDir
                 -- put hi-boot files into place for mutually recursive modules
                 -- FIX: what about exeName.hi-boot?
                 smartCopySources verbose (hsSourceDirs exeBi)
                                  exeDir (otherModules exeBi) ["hi-boot"] False False

                 -- build executables
                 unless (null (cSources exeBi)) $ do
                  when (verbose > 3) (putStrLn "Building C Sources.")
                  sequence_ [do let cSrcODir |versionBranch (compilerVersion (compiler lbi))
                                                    >= [6,4,1] = exeDir
                                             | otherwise 
                                                 = exeDir `joinFileName` (dirOf c)
                                createDirectoryIfMissing True cSrcODir
		                let cArgs = ["-I" ++ dir | dir <- includeDirs exeBi]
			                    ++ ["-optc" ++ opt | opt <- ccOptions exeBi]
			                    ++ ["-odir", cSrcODir, "-hidir", pref, "-c"]
			                    ++ (if verbose > 4 then ["-v"] else [])
                                rawSystemExit verbose ghcPath (cArgs ++ [c])
                                    | c <- cSources exeBi]
                 srcMainFile <- findFile (hsSourceDirs exeBi) modPath

                 let cObjs = [ path `joinFileName` file `joinFileExt` objExtension
                                   | (path, file, _) <- (map splitFilePath (cSources exeBi)) ]
                 let binArgs linkExe profExe =
                            pkg_conf
                         ++ ["-I"++pref]
			 ++ (if linkExe
			        then ["-o", targetDir `joinFileName` exeNameReal]
                                else ["-c"])
                         ++ constructGHCCmdLine lbi exeBi exeDir verbose
                         ++ [exeDir `joinFileName` x | x <- cObjs]
                         ++ [srcMainFile]
			 ++ ldOptions exeBi
			 ++ ["-l"++lib | lib <- extraLibs exeBi]
			 ++ ["-L"++libDir | libDir <- extraLibDirs exeBi]
                         ++ if profExe
                               then "-prof":ghcProfOptions exeBi
                               else []

		 -- For building exe's for profiling that use TH we actually
		 -- have to build twice, once without profiling and the again
		 -- with profiling. This is because the code that TH needs to
		 -- run at compile time needs to be the vanilla ABI so it can
		 -- be loaded up and run by the compiler.
		 when (withProfExe lbi && TemplateHaskell `elem` extensions exeBi)
		    (rawSystemExit verbose ghcPath (binArgs False False))

		 rawSystemExit verbose ghcPath (binArgs True (withProfExe lbi))


-- when using -split-objs, we need to search for object files in the
-- Module_split directory for each module.
getHaskellObjects :: PackageDescription -> BuildInfo -> LocalBuildInfo
 	-> FilePath -> String -> IO [FilePath]
getHaskellObjects pkg_descr libBi lbi pref obj_ext
  | splitObjs lbi = do
	let dirs = [ pref `joinFileName` (dotToSep x ++ "_split") 
		   | x <- libModules pkg_descr ]
	objss <- mapM getDirectoryContents dirs
	let objs = [ dir `joinFileName` obj
		   | (objs,dir) <- zip objss dirs, obj <- objs,
		     obj_ext `isSuffixOf` obj ]
	return objs
  | otherwise  = 
	return [ pref `joinFileName` (dotToSep x) `joinFileExt` obj_ext
               | x <- libModules pkg_descr ]


constructGHCCmdLine
	:: LocalBuildInfo
        -> BuildInfo
	-> FilePath
	-> Int				-- verbosity level
        -> [String]
constructGHCCmdLine lbi bi odir verbose = 
        ["--make"]
     ++ (if verbose > 4 then ["-v"] else [])
	    -- Unsupported extensions have already been checked by configure
     ++ (if compilerVersion (compiler lbi) > Version [6,4] []
            then ["-hide-all-packages"]
            else [])
     ++ ["-i"]
     ++ ["-i" ++ autogenModulesDir lbi]
     ++ ["-i" ++ l | l <- nub (hsSourceDirs bi)]
     ++ ["-I" ++ dir | dir <- includeDirs bi]
     ++ ["-optc" ++ opt | opt <- ccOptions bi]
     ++ [ "-#include \"" ++ inc ++ "\"" | inc <- includes bi ++ installIncludes bi ]
     ++ [ "-odir",  odir, "-hidir", odir ]
     ++ (concat [ ["-package", showPackageId pkg] | pkg <- packageDeps lbi ])
     ++ hcOptions GHC (options bi)
     ++ snd (extensionsToGHCFlag (extensions bi))

mkGHCiLibName :: FilePath -- ^file Prefix
              -> String   -- ^library name.
              -> String
mkGHCiLibName pref lib = pref `joinFileName` ("HS" ++ lib ++ ".o")

-- -----------------------------------------------------------------------------
-- Installing

-- |Install executables for GHC.
installExe :: Int      -- ^verbose
              -> FilePath -- ^install location
              -> FilePath -- ^Build location
              -> PackageDescription -> IO ()
installExe verbose pref buildPref pkg_descr
    = do createDirectoryIfMissing True pref
         withExe pkg_descr $ \ (Executable e _ b) -> do
             let exeName = e `joinFileExt` exeExtension
             copyFileVerbose verbose (buildPref `joinFileName` e `joinFileName` exeName) (pref `joinFileName` exeName)

-- |Install for ghc, .hi, .a and, if --with-ghci given, .o
installLib    :: Int      -- ^verbose
              -> ProgramConfiguration
              -> Bool     -- ^has vanilla library
              -> Bool     -- ^has profiling library
	      -> Bool     -- ^has GHCi libs
              -> FilePath -- ^install location
              -> FilePath -- ^Build location
              -> PackageDescription -> IO ()
installLib verbose programConf hasVanilla hasProf hasGHCi pref buildPref
              pd@PackageDescription{library=Just l,
                                    package=p}
    = do ifVanilla $ smartCopySources verbose [buildPref] pref (libModules pd) ["hi"] True False
         ifProf $ smartCopySources verbose [buildPref] pref (libModules pd) ["p_hi"] True False
         let libTargetLoc = mkLibName pref (showPackageId p)
             profLibTargetLoc = mkProfLibName pref (showPackageId p)
	     libGHCiTargetLoc = mkGHCiLibName pref (showPackageId p)
         ifVanilla $ copyFileVerbose verbose (mkLibName buildPref (showPackageId p)) libTargetLoc
         ifProf $ copyFileVerbose verbose (mkProfLibName buildPref (showPackageId p)) profLibTargetLoc
	 ifGHCi $ copyFileVerbose verbose (mkGHCiLibName buildPref (showPackageId p)) libGHCiTargetLoc

	 installIncludeFiles verbose pd pref

         -- use ranlib or ar -s to build an index. this is necessary
         -- on some systems like MacOS X.  If we can't find those,
         -- don't worry too much about it.
         let progName = programName $ ranlibProgram
         mProg <- lookupProgram progName programConf
         case foundProg mProg of
           Just rl  -> do ifVanilla $ rawSystemProgram verbose rl [libTargetLoc]
                          ifProf $ rawSystemProgram verbose rl [profLibTargetLoc]

           Nothing -> do let progName = programName $ arProgram
                         mProg <- lookupProgram progName programConf
                         case mProg of
                          Just ar  -> do ifVanilla $ rawSystemProgram verbose ar ["-s", libTargetLoc]
                                         ifProf $ rawSystemProgram verbose ar ["-s", profLibTargetLoc]
                          Nothing -> setupMessage  "Warning: Unable to generate index for library (missing ranlib and ar)" pd
         return ()
    where ifVanilla action = when hasVanilla (action >> return ())
          ifProf action = when hasProf (action >> return ())
	  ifGHCi action = when hasGHCi (action >> return ())
installLib _ _ _ _ _ _ _ PackageDescription{library=Nothing}
    = die $ "Internal Error. installLibGHC called with no library."

-- | Install the files listed in install-includes
installIncludeFiles :: Int -> PackageDescription -> FilePath -> IO ()
installIncludeFiles verbose pkg_descr@PackageDescription{library=Just l} libdir
 = do
   createDirectoryIfMissing True incdir
   incs <- mapM (findInc relincdirs) (installIncludes lbi)
   sequence_ [ copyFileVerbose verbose path (incdir `joinFileName` f)
	     | (f,path) <- incs ]
  where
   relincdirs = filter (not.isAbsolutePath) (includeDirs lbi)
   lbi = libBuildInfo l
   incdir = mkIncludeDir libdir

   findInc [] f = die ("can't find include file " ++ f)
   findInc (d:ds) f = do
     let path = (d `joinFileName` f)
     b <- doesFileExist path
     if b then return (f,path) else findInc ds f

-- Also checks whether the program was actually found.
foundProg :: Maybe Program -> Maybe Program
foundProg Nothing = Nothing
foundProg (Just Program{programLocation=EmptyLocation}) = Nothing
foundProg x = x