1 {-# OPTIONS -fno-cse #-}
2 {-# LANGUAGE NamedFieldPuns #-}
3 -- -fno-cse is needed for GLOBAL_VAR's to behave properly
5 -----------------------------------------------------------------------------
9 -- (c) The University of Glasgow 2005
11 -----------------------------------------------------------------------------
13 module DriverPipeline
(
14 -- Run a series of compilation steps in a pipeline, for a
15 -- collection of source files.
18 -- Interfaces for the batch-mode driver
21 -- Interfaces for the compilation manager (interpreted/batch-mode)
28 #include
"HsVersions.h"
39 import UniqFM
( eltsUFM
)
42 import StaticFlags
( v_Ld_inputs
, opt_PIC
, opt_Static
, WayName
(..) )
46 import StringBuffer
( hGetStringBuffer
)
47 import BasicTypes
( SuccessFlag
(..) )
48 import Maybes
( expectJust
)
49 import ParserCoreUtils
( getCoreModuleName
)
52 import LlvmCodeGen
( llvmFixupAsm
)
57 import Data
.IORef
( readIORef
)
58 import System
.Directory
59 import System
.FilePath
62 import Data
.List
( isSuffixOf )
64 import System
.Environment
67 -- ---------------------------------------------------------------------------
70 -- | Just preprocess a file, put the result in a temp. file (used by the
71 -- compilation manager during the summary phase).
73 -- We return the augmented DynFlags, because they contain the result
74 -- of slurping in the OPTIONS pragmas
77 -> (FilePath, Maybe Phase
) -- ^ filename and starting phase
78 -> IO (DynFlags
, FilePath)
79 preprocess hsc_env
(filename
, mb_phase
) =
80 ASSERT2
(isJust mb_phase || isHaskellSrcFilename filename
, text filename
)
81 runPipeline anyHsc hsc_env
(filename
, mb_phase
)
82 Nothing Temporary Nothing
{-no ModLocation-} Nothing
{-no stub-}
84 -- ---------------------------------------------------------------------------
88 -- Compile a single module, under the control of the compilation manager.
90 -- This is the interface between the compilation manager and the
91 -- compiler proper (hsc), where we deal with tedious details like
92 -- reading the OPTIONS pragma from the source file, converting the
93 -- C or assembly that GHC produces into an object file, and compiling
96 -- NB. No old interface can also mean that the source has changed.
99 -> ModSummary
-- ^ summary for module being compiled
100 -> Int -- ^ module N ...
102 -> Maybe ModIface
-- ^ old interface, if we have one
103 -> Maybe Linkable
-- ^ old linkable, if we have one
105 -> IO HomeModInfo
-- ^ the complete HomeModInfo, if successful
107 compile
= compile
' (hscCompileNothing
, hscCompileInteractive
, hscCompileBatch
)
110 (Compiler
(HscStatus
, ModIface
, ModDetails
),
111 Compiler
(InteractiveStatus
, ModIface
, ModDetails
),
112 Compiler
(HscStatus
, ModIface
, ModDetails
))
114 -> ModSummary
-- ^ summary for module being compiled
115 -> Int -- ^ module N ...
117 -> Maybe ModIface
-- ^ old interface, if we have one
118 -> Maybe Linkable
-- ^ old linkable, if we have one
120 -> IO HomeModInfo
-- ^ the complete HomeModInfo, if successful
122 compile
' (nothingCompiler
, interactiveCompiler
, batchCompiler
)
123 hsc_env0 summary mod_index nmods mb_old_iface maybe_old_linkable
126 let dflags0
= ms_hspp_opts summary
127 this_mod
= ms_mod summary
128 src_flavour
= ms_hsc_src summary
129 location
= ms_location summary
130 input_fn
= expectJust
"compile:hs" (ml_hs_file location
)
131 input_fnpp
= ms_hspp_file summary
133 debugTraceMsg dflags0
2 (text
"compile: input file" <+> text input_fnpp
)
135 let basename
= dropExtension input_fn
137 -- We add the directory in which the .hs files resides) to the import path.
138 -- This is needed when we try to compile the .hc file later, if it
139 -- imports a _stub.h file that we created here.
140 let current_dir
= case takeDirectory basename
of
141 "" -> "." -- XXX Hack required for filepath-1.1 and earlier
142 -- (GHC 6.12 and earlier)
144 old_paths
= includePaths dflags0
145 dflags
= dflags0
{ includePaths
= current_dir
: old_paths
}
146 hsc_env
= hsc_env0
{hsc_dflags
= dflags
}
148 -- Figure out what lang we're generating
149 let hsc_lang
= hscTarget dflags
150 -- ... and what the next phase should be
151 let next_phase
= hscNextPhase dflags src_flavour hsc_lang
152 -- ... and what file to generate the output into
153 output_fn
<- getOutputFilename next_phase
154 Temporary basename dflags next_phase
(Just location
)
156 let dflags
' = dflags
{ hscTarget
= hsc_lang
,
157 hscOutName
= output_fn
,
158 extCoreName
= basename
++ ".hcr" }
159 let hsc_env
' = hsc_env
{ hsc_dflags
= dflags
' }
161 -- -fforce-recomp should also work with --make
162 let force_recomp
= dopt Opt_ForceRecomp dflags
164 | force_recomp ||
isNothing maybe_old_linkable
= SourceModified
165 |
otherwise = source_modified0
166 object_filename
= ml_obj_file location
168 let handleBatch HscNoRecomp
169 = ASSERT
(isJust maybe_old_linkable
)
170 return maybe_old_linkable
172 handleBatch
(HscRecomp hasStub _
)
173 | isHsBoot src_flavour
174 = do when (isObjectTarget hsc_lang
) $ -- interpreted reaches here too
175 liftIO
$ touchObjectFile dflags
' object_filename
176 return maybe_old_linkable
179 = do (hs_unlinked
, unlinked_time
) <-
182 return ([], ms_hs_date summary
)
183 -- We're in --make mode: finish the compilation pipeline.
185 maybe_stub_o
<- case hasStub
of
186 Nothing
-> return Nothing
188 stub_o
<- compileStub hsc_env
' stub_c
190 _
<- runPipeline StopLn hsc_env
' (output_fn
,Nothing
)
195 -- The object filename comes from the ModLocation
196 o_time
<- getModificationTime object_filename
197 return ([DotO object_filename
], o_time
)
199 let linkable
= LM unlinked_time this_mod hs_unlinked
200 return (Just linkable
)
202 handleInterpreted HscNoRecomp
203 = ASSERT
(isJust maybe_old_linkable
)
204 return maybe_old_linkable
205 handleInterpreted
(HscRecomp _hasStub Nothing
)
206 = ASSERT
(isHsBoot src_flavour
)
207 return maybe_old_linkable
208 handleInterpreted
(HscRecomp hasStub
(Just
(comp_bc
, modBreaks
)))
209 = do stub_o
<- case hasStub
of
212 stub_o
<- compileStub hsc_env
' stub_c
215 let hs_unlinked
= [BCOs comp_bc modBreaks
]
216 unlinked_time
= ms_hs_date summary
217 -- Why do we use the timestamp of the source file here,
218 -- rather than the current time? This works better in
219 -- the case where the local clock is out of sync
220 -- with the filesystem's clock. It's just as accurate:
221 -- if the source is modified, then the linkable will
223 let linkable
= LM unlinked_time this_mod
224 (hs_unlinked
++ stub_o
)
225 return (Just linkable
)
227 let -- runCompiler :: Compiler result -> (result -> Maybe Linkable)
229 runCompiler compiler handle
230 = do (result
, iface
, details
)
231 <- compiler hsc_env
' summary source_modified mb_old_iface
232 (Just
(mod_index
, nmods
))
233 linkable
<- handle result
234 return (HomeModInfo
{ hm_details
= details
,
236 hm_linkable
= linkable
})
239 HscInterpreted
-> runCompiler interactiveCompiler handleInterpreted
240 HscNothing
-> runCompiler nothingCompiler handleBatch
241 _other
-> runCompiler batchCompiler handleBatch
243 -----------------------------------------------------------------------------
244 -- stub .h and .c files (for foreign export support)
246 -- The _stub.c file is derived from the haskell source file, possibly taking
247 -- into account the -stubdir option.
249 -- The object file created by compiling the _stub.c file is put into a
250 -- temporary file, which will be later combined with the main .o file
251 -- (see the MergeStubs phase).
253 compileStub
:: HscEnv
-> FilePath -> IO FilePath
254 compileStub hsc_env stub_c
= do
255 (_
, stub_o
) <- runPipeline StopLn hsc_env
(stub_c
,Nothing
) Nothing
256 Temporary Nothing
{-no ModLocation-} Nothing
260 -- ---------------------------------------------------------------------------
263 link
:: GhcLink
-- interactive or batch
264 -> DynFlags
-- dynamic flags
265 -> Bool -- attempt linking in batch mode?
266 -> HomePackageTable
-- what to link
269 -- For the moment, in the batch linker, we don't bother to tell doLink
270 -- which packages to link -- it just tries all that are available.
271 -- batch_attempt_linking should only be *looked at* in batch mode. It
272 -- should only be True if the upsweep was successful and someone
273 -- exports main, i.e., we have good reason to believe that linking
276 link LinkInMemory _ _ _
277 = if cGhcWithInterpreter
== "YES"
278 then -- Not Linking...(demand linker will do the job)
280 else panicBadLink LinkInMemory
285 link LinkBinary dflags batch_attempt_linking hpt
286 = link
' dflags batch_attempt_linking hpt
288 link LinkDynLib dflags batch_attempt_linking hpt
289 = link
' dflags batch_attempt_linking hpt
291 panicBadLink
:: GhcLink
-> a
292 panicBadLink other
= panic
("link: GHC not built to link this way: " ++
295 link
' :: DynFlags
-- dynamic flags
296 -> Bool -- attempt linking in batch mode?
297 -> HomePackageTable
-- what to link
300 link
' dflags batch_attempt_linking hpt
301 | batch_attempt_linking
304 home_mod_infos
= eltsUFM hpt
306 -- the packages we depend on
307 pkg_deps
= concatMap (map fst . dep_pkgs
. mi_deps
. hm_iface
) home_mod_infos
309 -- the linkables to link
310 linkables
= map (expectJust
"link".hm_linkable
) home_mod_infos
312 debugTraceMsg dflags
3 (text
"link: linkables are ..." $$ vcat
(map ppr linkables
))
314 -- check for the -no-link flag
315 if isNoLink
(ghcLink dflags
)
316 then do debugTraceMsg dflags
3 (text
"link(batch): linking omitted (-c flag given).")
320 let getOfiles
(LM _ _ us
) = map nameOfObject
(filter isObject us
)
321 obj_files
= concatMap getOfiles linkables
323 exe_file
= exeFileName dflags
325 linking_needed
<- linkingNeeded dflags linkables pkg_deps
327 if not (dopt Opt_ForceRecomp dflags
) && not linking_needed
328 then do debugTraceMsg dflags
2 (text exe_file
<+> ptext
(sLit
"is up to date, linking not required."))
332 compilationProgressMsg dflags
$ showSDoc
$
333 (ptext
(sLit
"Linking") <+> text exe_file
<+> text
"...")
335 -- Don't showPass in Batch mode; doLink will do that for us.
336 let link
= case ghcLink dflags
of
337 LinkBinary
-> linkBinary
338 LinkDynLib
-> linkDynLib
339 other
-> panicBadLink other
340 link dflags obj_files pkg_deps
342 debugTraceMsg dflags
3 (text
"link: done")
344 -- linkBinary only returns if it succeeds
348 = do debugTraceMsg dflags
3 (text
"link(batch): upsweep (partially) failed OR" $$
349 text
" Main.main not exported; not linking.")
353 linkingNeeded
:: DynFlags
-> [Linkable
] -> [PackageId
] -> IO Bool
354 linkingNeeded dflags linkables pkg_deps
= do
355 -- if the modification time on the executable is later than the
356 -- modification times on all of the objects and libraries, then omit
357 -- linking (unless the -fforce-recomp flag was given).
358 let exe_file
= exeFileName dflags
359 e_exe_time
<- tryIO
$ getModificationTime exe_file
361 Left _
-> return True
363 -- first check object files and extra_ld_inputs
364 extra_ld_inputs
<- readIORef v_Ld_inputs
365 e_extra_times
<- mapM (tryIO
. getModificationTime) extra_ld_inputs
366 let (errs
,extra_times
) = splitEithers e_extra_times
367 let obj_times
= map linkableTime linkables
++ extra_times
368 if not (null errs
) ||
any (t
<) obj_times
372 -- next, check libraries. XXX this only checks Haskell libraries,
373 -- not extra_libraries or -l things from the command line.
374 let pkg_map
= pkgIdMap
(pkgState dflags
)
375 pkg_hslibs
= [ (libraryDirs c
, lib
)
376 | Just c
<- map (lookupPackage pkg_map
) pkg_deps
,
377 lib
<- packageHsLibs dflags c
]
379 pkg_libfiles
<- mapM (uncurry findHSLib
) pkg_hslibs
380 if any isNothing pkg_libfiles
then return True else do
381 e_lib_times
<- mapM (tryIO
. getModificationTime)
382 (catMaybes pkg_libfiles
)
383 let (lib_errs
,lib_times
) = splitEithers e_lib_times
384 if not (null lib_errs
) ||
any (t
<) lib_times
386 else checkLinkInfo dflags pkg_deps exe_file
388 -- Returns 'False' if it was, and we can avoid linking, because the
389 -- previous binary was linked with "the same options".
390 checkLinkInfo
:: DynFlags
-> [PackageId
] -> FilePath -> IO Bool
391 checkLinkInfo dflags pkg_deps exe_file
392 |
not (platformSupportsSavingLinkOpts
(platformOS
(targetPlatform dflags
)))
393 -- ToDo: Windows and OS X do not use the ELF binary format, so
394 -- readelf does not work there. We need to find another way to do
396 = return False -- conservatively we should return True, but not
397 -- linking in this case was the behaviour for a long
398 -- time so we leave it as-is.
401 link_info
<- getLinkInfo dflags pkg_deps
402 debugTraceMsg dflags
3 $ text
("Link info: " ++ link_info
)
403 m_exe_link_info
<- readElfSection dflags ghcLinkInfoSectionName exe_file
404 debugTraceMsg dflags
3 $ text
("Exe link info: " ++ show m_exe_link_info
)
405 return (Just link_info
/= m_exe_link_info
)
407 platformSupportsSavingLinkOpts
:: OS
-> Bool
408 platformSupportsSavingLinkOpts os
409 | os
== OSSolaris2
= False -- see #5382
410 |
otherwise = osElfTarget os
412 ghcLinkInfoSectionName
:: String
413 ghcLinkInfoSectionName
= ".debug-ghc-link-info"
414 -- if we use the ".debug" prefix, then strip will strip it by default
416 findHSLib
:: [String] -> String -> IO (Maybe FilePath)
417 findHSLib dirs lib
= do
418 let batch_lib_file
= "lib" ++ lib
<.> "a"
419 found
<- filterM doesFileExist (map (</> batch_lib_file
) dirs
)
422 (x
:_
) -> return (Just x
)
424 -- -----------------------------------------------------------------------------
425 -- Compile files in one-shot mode.
427 oneShot
:: HscEnv
-> Phase
-> [(String, Maybe Phase
)] -> IO ()
428 oneShot hsc_env stop_phase srcs
= do
429 o_files
<- mapM (compileFile hsc_env stop_phase
) srcs
430 doLink
(hsc_dflags hsc_env
) stop_phase o_files
432 compileFile
:: HscEnv
-> Phase
-> (FilePath, Maybe Phase
) -> IO FilePath
433 compileFile hsc_env stop_phase
(src
, mb_phase
) = do
434 exists
<- doesFileExist src
436 ghcError
(CmdLineError
("does not exist: " ++ src
))
439 dflags
= hsc_dflags hsc_env
440 split = dopt Opt_SplitObjs dflags
441 mb_o_file
= outputFile dflags
442 ghc_link
= ghcLink dflags
-- Set by -c or -no-link
444 -- When linking, the -o argument refers to the linker's output.
445 -- otherwise, we use it as the name for the pipeline's output.
447 | StopLn
<- stop_phase
, not (isNoLink ghc_link
) = Persistent
448 -- -o foo applies to linker
449 | Just o_file
<- mb_o_file
= SpecificFile o_file
450 -- -o foo applies to the file we are compiling now
451 |
otherwise = Persistent
453 stop_phase
' = case stop_phase
of
454 As |
split -> SplitAs
457 ( _
, out_file
) <- runPipeline stop_phase
' hsc_env
458 (src
, mb_phase
) Nothing output
459 Nothing
{-no ModLocation-} Nothing
463 doLink
:: DynFlags
-> Phase
-> [FilePath] -> IO ()
464 doLink dflags stop_phase o_files
465 |
not (isStopLn stop_phase
)
466 = return () -- We stopped before the linking phase
469 = case ghcLink dflags
of
471 LinkBinary
-> linkBinary dflags o_files
[]
472 LinkDynLib
-> linkDynLib dflags o_files
[]
473 other
-> panicBadLink other
476 -- ---------------------------------------------------------------------------
480 -- ^ Output should be to a temporary file: we're going to
481 -- run more compilation steps on this output later.
483 -- ^ We want a persistent file, i.e. a file in the current directory
484 -- derived from the input filename, but with the appropriate extension.
485 -- eg. in "ghc -c Foo.hs" the output goes into ./Foo.o.
486 | SpecificFile
FilePath
487 -- ^ The output must go into the specified file.
489 -- | Run a compilation pipeline, consisting of multiple phases.
491 -- This is the interface to the compilation pipeline, which runs
492 -- a series of compilation steps on a single source file, specifying
493 -- at which stage to stop.
495 -- The DynFlags can be modified by phases in the pipeline (eg. by
496 -- OPTIONS_GHC pragmas), and the changes affect later phases in the
499 :: Phase
-- ^ When to stop
500 -> HscEnv
-- ^ Compilation environment
501 -> (FilePath,Maybe Phase
) -- ^ Input filename (and maybe -x suffix)
502 -> Maybe FilePath -- ^ original basename (if different from ^^^)
503 -> PipelineOutput
-- ^ Output filename
504 -> Maybe ModLocation
-- ^ A ModLocation, if this is a Haskell module
505 -> Maybe FilePath -- ^ stub object, if we have one
506 -> IO (DynFlags
, FilePath) -- ^ (final flags, output filename)
508 runPipeline stop_phase hsc_env0
(input_fn
, mb_phase
)
509 mb_basename output maybe_loc maybe_stub_o
511 let dflags0
= hsc_dflags hsc_env0
512 (input_basename
, suffix
) = splitExtension input_fn
513 suffix
' = drop 1 suffix
-- strip off the .
514 basename | Just b
<- mb_basename
= b
515 |
otherwise = input_basename
517 -- Decide where dump files should go based on the pipeline output
518 dflags
= dflags0
{ dumpPrefix
= Just
(basename
++ ".") }
519 hsc_env
= hsc_env0
{hsc_dflags
= dflags
}
521 -- If we were given a -x flag, then use that phase to start from
522 start_phase
= fromMaybe (startPhase suffix
') mb_phase
524 -- We want to catch cases of "you can't get there from here" before
525 -- we start the pipeline, because otherwise it will just run off the
528 -- There is a partial ordering on phases, where A < B iff A occurs
529 -- before B in a normal compilation pipeline.
531 when (not (start_phase `happensBefore` stop_phase
)) $
533 ("cannot compile this file to desired target: "
536 -- this is a function which will be used to calculate output file names
537 -- as we go along (we partially apply it to some of its inputs here)
538 let get_output_fn
= getOutputFilename stop_phase output basename
540 -- Execute the pipeline...
541 let env
= PipeEnv
{ stop_phase
,
542 src_basename
= basename
,
543 src_suffix
= suffix
',
544 output_spec
= output
}
546 state
= PipeState
{ hsc_env
, maybe_loc
, maybe_stub_o
= maybe_stub_o
}
548 (state
', output_fn
) <- unP
(pipeLoop start_phase input_fn
) env state
550 let PipeState
{ hsc_env
=hsc_env
', maybe_loc
} = state
'
551 dflags
' = hsc_dflags hsc_env
'
553 -- Sometimes, a compilation phase doesn't actually generate any output
554 -- (eg. the CPP phase when -fcpp is not turned on). If we end on this
555 -- stage, but we wanted to keep the output, then we have to explicitly
556 -- copy the file, remembering to prepend a {-# LINE #-} pragma so that
557 -- further compilation stages can tell what the original filename was.
560 return (dflags
', output_fn
)
562 do final_fn
<- get_output_fn dflags
' stop_phase maybe_loc
563 when (final_fn
/= output_fn
) $ do
564 let msg
= ("Copying `" ++ output_fn
++"' to `" ++ final_fn
++ "'")
565 line_prag
= Just
("{-# LINE 1 \"" ++ input_fn
++ "\" #-}\n")
566 copyWithHeader dflags msg line_prag output_fn final_fn
567 return (dflags
', final_fn
)
569 -- -----------------------------------------------------------------------------
570 -- The pipeline uses a monad to carry around various bits of information
572 -- PipeEnv: invariant information passed down
573 data PipeEnv
= PipeEnv
{
574 stop_phase
:: Phase
, -- ^ Stop just before this phase
575 src_basename
:: String, -- ^ basename of original input source
576 src_suffix
:: String, -- ^ its extension
577 output_spec
:: PipelineOutput
-- ^ says where to put the pipeline output
580 -- PipeState: information that might change during a pipeline run
581 data PipeState
= PipeState
{
583 -- ^ only the DynFlags change in the HscEnv. The DynFlags change
584 -- at various points, for example when we read the OPTIONS_GHC
585 -- pragmas in the Cpp phase.
586 maybe_loc
:: Maybe ModLocation
,
587 -- ^ the ModLocation. This is discovered during compilation,
588 -- in the Hsc phase where we read the module header.
589 maybe_stub_o
:: Maybe FilePath
590 -- ^ the stub object. This is set by the Hsc phase if a stub
591 -- object was created. The stub object will be joined with
592 -- the main compilation object using "ld -r" at the end.
595 getPipeEnv
:: CompPipeline PipeEnv
596 getPipeEnv
= P
$ \env state
-> return (state
, env
)
598 getPipeState
:: CompPipeline PipeState
599 getPipeState
= P
$ \_env state
-> return (state
, state
)
601 getDynFlags
:: CompPipeline DynFlags
602 getDynFlags
= P
$ \_env state
-> return (state
, hsc_dflags
(hsc_env state
))
604 setDynFlags
:: DynFlags
-> CompPipeline
()
605 setDynFlags dflags
= P
$ \_env state
->
606 return (state
{hsc_env
= (hsc_env state
){ hsc_dflags
= dflags
}}, ())
608 setModLocation
:: ModLocation
-> CompPipeline
()
609 setModLocation loc
= P
$ \_env state
->
610 return (state
{ maybe_loc
= Just loc
}, ())
612 setStubO
:: FilePath -> CompPipeline
()
613 setStubO stub_o
= P
$ \_env state
->
614 return (state
{ maybe_stub_o
= Just stub_o
}, ())
616 newtype CompPipeline a
= P
{ unP
:: PipeEnv
-> PipeState
-> IO (PipeState
, a
) }
618 instance Monad CompPipeline
where
619 return a
= P
$ \_env state
-> return (state
, a
)
620 P m
>>= k
= P
$ \env state
-> do (state
',a
) <- m env state
623 io
:: IO a
-> CompPipeline a
624 io m
= P
$ \_env state
-> do a
<- m
; return (state
, a
)
626 phaseOutputFilename
:: Phase
{-next phase-} -> CompPipeline
FilePath
627 phaseOutputFilename next_phase
= do
628 PipeEnv
{stop_phase
, src_basename
, output_spec
} <- getPipeEnv
629 PipeState
{maybe_loc
, hsc_env
} <- getPipeState
630 let dflags
= hsc_dflags hsc_env
631 io
$ getOutputFilename stop_phase output_spec
632 src_basename dflags next_phase maybe_loc
634 -- ---------------------------------------------------------------------------
635 -- outer pipeline loop
637 -- | pipeLoop runs phases until we reach the stop phase
638 pipeLoop
:: Phase
-> FilePath -> CompPipeline
FilePath
639 pipeLoop
phase input_fn
= do
640 PipeEnv
{stop_phase
} <- getPipeEnv
641 PipeState
{hsc_env
} <- getPipeState
643 _ |
phase `eqPhase` stop_phase
-- All done
646 |
not (phase `happensBefore` stop_phase
)
647 -- Something has gone wrong. We'll try to cover all the cases when
648 -- this could happen, so if we reach here it is a panic.
649 -- eg. it might happen if the -C flag is used on a source file that
650 -- has {-# OPTIONS -fasm #-}.
651 -> panic
("pipeLoop: at phase " ++ show phase ++
652 " but I wanted to stop at phase " ++ show stop_phase
)
655 -> do io
$ debugTraceMsg
(hsc_dflags hsc_env
) 4
656 (ptext
(sLit
"Running phase") <+> ppr
phase)
657 dflags
<- getDynFlags
658 (next_phase
, output_fn
) <- runPhase
phase input_fn dflags
659 pipeLoop next_phase output_fn
661 -- -----------------------------------------------------------------------------
662 -- In each phase, we need to know into what filename to generate the
663 -- output. All the logic about which filenames we generate output
664 -- into is embodied in the following function.
667 :: Phase
-> PipelineOutput
-> String
668 -> DynFlags
-> Phase
{-next phase-} -> Maybe ModLocation
-> IO FilePath
669 getOutputFilename stop_phase output basename
672 func dflags next_phase maybe_location
673 | is_last_phase
, Persistent
<- output
= persistent_fn
674 | is_last_phase
, SpecificFile f
<- output
= return f
675 | keep_this_output
= persistent_fn
676 |
otherwise = newTempName dflags suffix
679 odir
= objectDir dflags
680 osuf
= objectSuf dflags
681 keep_hc
= dopt Opt_KeepHcFiles dflags
682 keep_s
= dopt Opt_KeepSFiles dflags
683 keep_bc
= dopt Opt_KeepLlvmFiles dflags
685 myPhaseInputExt HCc
= hcsuf
686 myPhaseInputExt MergeStub
= osuf
687 myPhaseInputExt StopLn
= osuf
688 myPhaseInputExt other
= phaseInputExt other
690 is_last_phase
= next_phase `eqPhase` stop_phase
692 -- sometimes, we keep output from intermediate stages
696 LlvmOpt | keep_bc
-> True
697 HCc | keep_hc
-> True
700 suffix
= myPhaseInputExt next_phase
702 -- persistent object files get put in odir
704 | StopLn
<- next_phase
= return odir_persistent
705 |
otherwise = return persistent
707 persistent
= basename
<.> suffix
710 | Just loc
<- maybe_location
= ml_obj_file loc
711 | Just d
<- odir
= d
</> persistent
712 |
otherwise = persistent
715 -- -----------------------------------------------------------------------------
716 -- | Each phase in the pipeline returns the next phase to execute, and the
717 -- name of the file in which the output was placed.
719 -- We must do things dynamically this way, because we often don't know
720 -- what the rest of the phases will be until part-way through the
721 -- compilation: for example, an {-# OPTIONS -fasm #-} at the beginning
722 -- of a source file can change the latter stages of the pipeline from
723 -- taking the via-C route to using the native code generator.
725 runPhase
:: Phase
-- ^ Run this phase
726 -> FilePath -- ^ name of the input file
727 -> DynFlags
-- ^ for convenience, we pass the current dflags in
728 -> CompPipeline
(Phase
, -- next phase to run
729 FilePath) -- output filename
731 -- Invariant: the output filename always contains the output
732 -- Interesting case: Hsc when there is no recompilation to do
733 -- Then the output filename is still a .o file
736 -------------------------------------------------------------------------------
739 runPhase
(Unlit sf
) input_fn dflags
741 output_fn
<- phaseOutputFilename
(Cpp sf
)
743 let unlit_flags
= getOpts dflags opt_L
744 flags
= map SysTools
.Option unlit_flags
++
745 [ -- The -h option passes the file name for unlit to
746 -- put in a #line directive
748 -- cpp interprets \b etc as escape sequences,
749 -- so we use / for filenames in pragmas
750 , SysTools
.Option
$ reslash Forwards
$ normalise input_fn
751 , SysTools
.FileOption
"" input_fn
752 , SysTools
.FileOption
"" output_fn
755 io
$ SysTools
.runUnlit dflags flags
757 return (Cpp sf
, output_fn
)
759 -------------------------------------------------------------------------------
760 -- Cpp phase : (a) gets OPTIONS out of file
761 -- (b) runs cpp if necessary
763 runPhase
(Cpp sf
) input_fn dflags0
765 src_opts
<- io
$ getOptionsFromFile dflags0 input_fn
766 (dflags1
, unhandled_flags
, warns
)
767 <- io
$ parseDynamicFilePragma dflags0 src_opts
769 io
$ checkProcessArgsResult unhandled_flags
771 if not (xopt Opt_Cpp dflags1
) then do
772 -- we have to be careful to emit warnings only once.
773 unless (dopt Opt_Pp dflags1
) $ io
$ handleFlagWarnings dflags1 warns
775 -- no need to preprocess CPP, just pass input file along
776 -- to the next phase of the pipeline.
777 return (HsPp sf
, input_fn
)
779 output_fn
<- phaseOutputFilename
(HsPp sf
)
780 io
$ doCpp dflags1
True{-raw-} False{-no CC opts-} input_fn output_fn
781 -- re-read the pragmas now that we've preprocessed the file
783 src_opts
<- io
$ getOptionsFromFile dflags0 output_fn
784 (dflags2
, unhandled_flags
, warns
)
785 <- io
$ parseDynamicFilePragma dflags0 src_opts
786 io
$ checkProcessArgsResult unhandled_flags
787 unless (dopt Opt_Pp dflags2
) $ io
$ handleFlagWarnings dflags2 warns
788 -- the HsPp pass below will emit warnings
792 return (HsPp sf
, output_fn
)
794 -------------------------------------------------------------------------------
797 runPhase
(HsPp sf
) input_fn dflags
799 if not (dopt Opt_Pp dflags
) then
800 -- no need to preprocess, just pass input file along
801 -- to the next phase of the pipeline.
802 return (Hsc sf
, input_fn
)
804 let hspp_opts
= getOpts dflags opt_F
805 PipeEnv
{src_basename
, src_suffix
} <- getPipeEnv
806 let orig_fn
= src_basename
<.> src_suffix
807 output_fn
<- phaseOutputFilename
(Hsc sf
)
808 io
$ SysTools
.runPp dflags
809 ( [ SysTools
.Option orig_fn
810 , SysTools
.Option input_fn
811 , SysTools
.FileOption
"" output_fn
813 map SysTools
.Option hspp_opts
816 -- re-read pragmas now that we've parsed the file (see #3674)
817 src_opts
<- io
$ getOptionsFromFile dflags output_fn
818 (dflags1
, unhandled_flags
, warns
)
819 <- io
$ parseDynamicFilePragma dflags src_opts
821 io
$ checkProcessArgsResult unhandled_flags
822 io
$ handleFlagWarnings dflags1 warns
824 return (Hsc sf
, output_fn
)
826 -----------------------------------------------------------------------------
829 -- Compilation of a single module, in "legacy" mode (_not_ under
830 -- the direction of the compilation manager).
831 runPhase
(Hsc src_flavour
) input_fn dflags0
832 = do -- normal Hsc mode, not mkdependHS
834 PipeEnv
{ stop_phase
=stop
,
835 src_basename
=basename
,
836 src_suffix
=suff
} <- getPipeEnv
838 -- we add the current directory (i.e. the directory in which
839 -- the .hs files resides) to the include path, since this is
840 -- what gcc does, and it's probably what you want.
841 let current_dir
= case takeDirectory basename
of
842 "" -> "." -- XXX Hack required for filepath-1.1 and earlier
843 -- (GHC 6.12 and earlier)
846 paths
= includePaths dflags0
847 dflags
= dflags0
{ includePaths
= current_dir
: paths
}
851 -- gather the imports and module name
852 (hspp_buf
,mod_name
,imps
,src_imps
) <- io
$
854 ExtCoreFile
-> do -- no explicit imports in ExtCore input.
855 m
<- getCoreModuleName input_fn
856 return (Nothing
, mkModuleName m
, [], [])
859 buf
<- hGetStringBuffer input_fn
860 (src_imps
,imps
,L _ mod_name
) <- getImports dflags buf input_fn
(basename
<.> suff
)
861 return (Just buf
, mod_name
, imps
, src_imps
)
863 -- Build a ModLocation to pass to hscMain.
864 -- The source filename is rather irrelevant by now, but it's used
865 -- by hscMain for messages. hscMain also needs
866 -- the .hi and .o filenames, and this is as good a way
867 -- as any to generate them, and better than most. (e.g. takes
868 -- into accout the -osuf flags)
869 location1
<- io
$ mkHomeModLocation2 dflags mod_name basename suff
871 -- Boot-ify it if necessary
872 let location2 | isHsBoot src_flavour
= addBootSuffixLocn location1
873 |
otherwise = location1
876 -- Take -ohi into account if present
877 -- This can't be done in mkHomeModuleLocation because
878 -- it only applies to the module being compiles
879 let ohi
= outputHi dflags
880 location3 | Just fn
<- ohi
= location2
{ ml_hi_file
= fn
}
881 |
otherwise = location2
883 -- Take -o into account if present
884 -- Very like -ohi, but we must *only* do this if we aren't linking
885 -- (If we're linking then the -o applies to the linked thing, not to
886 -- the object file for one module.)
887 -- Note the nasty duplication with the same computation in compileFile above
888 let expl_o_file
= outputFile dflags
889 location4 | Just ofile
<- expl_o_file
890 , isNoLink
(ghcLink dflags
)
891 = location3
{ ml_obj_file
= ofile
}
892 |
otherwise = location3
894 o_file
= ml_obj_file location4
-- The real object file
896 setModLocation location4
898 -- Figure out if the source has changed, for recompilation avoidance.
900 -- Setting source_unchanged to True means that M.o seems
901 -- to be up to date wrt M.hs; so no need to recompile unless imports have
902 -- changed (which the compiler itself figures out).
903 -- Setting source_unchanged to False tells the compiler that M.o is out of
904 -- date wrt M.hs (or M.o doesn't exist) so we must recompile regardless.
905 src_timestamp
<- io
$ getModificationTime (basename
<.> suff
)
907 let hsc_lang
= hscTarget dflags
908 source_unchanged
<- io
$
909 if not (isStopLn stop
)
910 -- SourceModified unconditionally if
911 -- (a) recompilation checker is off, or
912 -- (b) we aren't going all the way to .o file (e.g. ghc -S)
913 then return SourceModified
914 -- Otherwise look at file modification dates
915 else do o_file_exists
<- doesFileExist o_file
917 then return SourceModified
-- Need to recompile
918 else do t2
<- getModificationTime o_file
919 if t2
> src_timestamp
920 then return SourceUnmodified
921 else return SourceModified
924 let next_phase
= hscNextPhase dflags src_flavour hsc_lang
925 output_fn
<- phaseOutputFilename next_phase
927 let dflags
' = dflags
{ hscTarget
= hsc_lang
,
928 hscOutName
= output_fn
,
929 extCoreName
= basename
++ ".hcr" }
932 PipeState
{hsc_env
=hsc_env
'} <- getPipeState
934 -- Tell the finder cache about this module
935 mod <- io
$ addHomeModuleToFinder hsc_env
' mod_name location4
937 -- Make the ModSummary to hand to hscMain
939 mod_summary
= ModSummary
{ ms_mod
= mod,
940 ms_hsc_src
= src_flavour
,
941 ms_hspp_file
= input_fn
,
942 ms_hspp_opts
= dflags
,
943 ms_hspp_buf
= hspp_buf
,
944 ms_location
= location4
,
945 ms_hs_date
= src_timestamp
,
946 ms_obj_date
= Nothing
,
947 ms_textual_imps
= imps
,
948 ms_srcimps
= src_imps
}
951 result
<- io
$ hscCompileOneShot hsc_env
'
952 mod_summary source_unchanged
954 Nothing
-- No "module i of n" progress info
958 -> do io
$ touchObjectFile dflags
' o_file
959 -- The .o file must have a later modification date
960 -- than the source file (else we wouldn't be in HscNoRecomp)
961 -- but we touch it anyway, to keep 'make' happy (we think).
962 return (StopLn
, o_file
)
963 (HscRecomp hasStub _
)
964 -> do case hasStub
of
967 do stub_o
<- io
$ compileStub hsc_env
' stub_c
969 -- In the case of hs-boot files, generate a dummy .o-boot
970 -- stamp file for the benefit of Make
971 when (isHsBoot src_flavour
) $
972 io
$ touchObjectFile dflags
' o_file
973 return (next_phase
, output_fn
)
975 -----------------------------------------------------------------------------
978 runPhase CmmCpp input_fn dflags
980 output_fn
<- phaseOutputFilename Cmm
981 io
$ doCpp dflags
False{-not raw-} True{-include CC opts-}
983 return (Cmm
, output_fn
)
985 runPhase Cmm input_fn dflags
987 PipeEnv
{src_basename
} <- getPipeEnv
988 let hsc_lang
= hscTarget dflags
990 let next_phase
= hscNextPhase dflags HsSrcFile hsc_lang
992 output_fn
<- phaseOutputFilename next_phase
994 let dflags
' = dflags
{ hscTarget
= hsc_lang
,
995 hscOutName
= output_fn
,
996 extCoreName
= src_basename
++ ".hcr" }
999 PipeState
{hsc_env
} <- getPipeState
1001 io
$ hscCompileCmmFile hsc_env input_fn
1003 -- XXX: catch errors above and convert them into ghcError? Original
1006 --when (not ok) $ ghcError (PhaseFailed "cmm" (ExitFailure 1))
1008 return (next_phase
, output_fn
)
1010 -----------------------------------------------------------------------------
1013 -- we don't support preprocessing .c files (with -E) now. Doing so introduces
1014 -- way too many hacks, and I can't say I've ever used it anyway.
1016 runPhase cc_phase input_fn dflags
1017 |
any (cc_phase `eqPhase`
) [Cc
, Ccpp
, HCc
, Cobjc
, Cobjcpp
]
1019 let platform
= targetPlatform dflags
1020 cc_opts
= getOpts dflags opt_c
1021 hcc
= cc_phase `eqPhase` HCc
1023 let cmdline_include_paths
= includePaths dflags
1025 -- HC files have the dependent packages stamped into them
1026 pkgs
<- if hcc
then io
$ getHCFilePackages input_fn
else return []
1028 -- add package include paths even if we're just compiling .c
1029 -- files; this is the Value Add(TM) that using ghc instead of
1031 pkg_include_dirs
<- io
$ getPackageIncludePath dflags pkgs
1032 let include_paths
= foldr (\ x xs
-> "-I" : x
: xs
) []
1033 (cmdline_include_paths
++ pkg_include_dirs
)
1035 let gcc_extra_viac_flags
= extraGccViaCFlags dflags
1036 let pic_c_flags
= picCCOpts dflags
1038 let verbFlags
= getVerbFlags dflags
1040 -- cc-options are not passed when compiling .hc files. Our
1041 -- hc code doesn't not #include any header files anyway, so these
1042 -- options aren't necessary.
1043 pkg_extra_cc_opts
<- io
$
1044 if cc_phase `eqPhase` HCc
1046 else getPackageExtraCcOpts dflags pkgs
1049 case platformOS platform
of
1051 do pkgFrameworkPaths
<- io
$ getPackageFrameworkPath dflags pkgs
1052 let cmdlineFrameworkPaths
= frameworkPaths dflags
1053 return $ map ("-F"++)
1054 (cmdlineFrameworkPaths
++ pkgFrameworkPaths
)
1058 let split_objs
= dopt Opt_SplitObjs dflags
1059 split_opt | hcc
&& split_objs
= [ "-DUSE_SPLIT_MARKERS" ]
1062 let cc_opt | optLevel dflags
>= 2 = "-O2"
1065 -- Decide next phase
1068 output_fn
<- phaseOutputFilename next_phase
1072 -- on x86 the floating point regs have greater precision
1073 -- than a double, which leads to unpredictable results.
1074 -- By default, we turn this off with -ffloat-store unless
1075 -- the user specified -fexcess-precision.
1076 (if platformArch platform
== ArchX86
&&
1077 not (dopt Opt_ExcessPrecision dflags
)
1078 then [ "-ffloat-store" ]
1081 -- gcc's -fstrict-aliasing allows two accesses to memory
1082 -- to be considered non-aliasing if they have different types.
1083 -- This interacts badly with the C code we generate, which is
1084 -- very weakly typed, being derived from C--.
1085 ["-fno-strict-aliasing"]
1087 let gcc_lang_opt | cc_phase `eqPhase` Ccpp
= "c++"
1088 | cc_phase `eqPhase` Cobjc
= "objective-c"
1089 | cc_phase `eqPhase` Cobjcpp
= "objective-c++"
1091 io
$ SysTools
.runCc dflags
(
1092 -- force the C compiler to interpret this file as C when
1093 -- compiling .hc files, by adding the -x c option.
1094 -- Also useful for plain .c files, just in case GHC saw a
1096 [ SysTools
.Option
"-x", SysTools
.Option gcc_lang_opt
1097 , SysTools
.FileOption
"" input_fn
1098 , SysTools
.Option
"-o"
1099 , SysTools
.FileOption
"" output_fn
1101 ++ map SysTools
.Option
(
1104 -- Stub files generated for foreign exports references the runIO_closure
1105 -- and runNonIO_closure symbols, which are defined in the base package.
1106 -- These symbols are imported into the stub.c file via RtsAPI.h, and the
1107 -- way we do the import depends on whether we're currently compiling
1108 -- the base package or not.
1109 ++ (if platformOS platform
== OSMinGW32
&&
1110 thisPackage dflags
== basePackageId
1111 then [ "-DCOMPILING_BASE_PACKAGE" ]
1114 -- We only support SparcV9 and better because V8 lacks an atomic CAS
1115 -- instruction. Note that the user can still override this
1116 -- (e.g., -mcpu=ultrasparc) as GCC picks the "best" -mcpu flag
1117 -- regardless of the ordering.
1119 -- This is a temporary hack.
1120 ++ (if platformArch platform
== ArchSPARC
1125 then gcc_extra_viac_flags
++ more_hcc_opts
1128 ++ [ "-S", "-Wimplicit", cc_opt
]
1129 ++ [ "-D__GLASGOW_HASKELL__="++cProjectVersionInt
]
1134 ++ pkg_extra_cc_opts
1137 return (next_phase
, output_fn
)
1139 -- ToDo: postprocess the output from gcc
1141 -----------------------------------------------------------------------------
1144 runPhase SplitMangle input_fn dflags
1145 = do -- tmp_pfx is the prefix used for the split .s files
1147 split_s_prefix
<- io
$ SysTools
.newTempName dflags
"split"
1148 let n_files_fn
= split_s_prefix
1150 io
$ SysTools
.runSplit dflags
1151 [ SysTools
.FileOption
"" input_fn
1152 , SysTools
.FileOption
"" split_s_prefix
1153 , SysTools
.FileOption
"" n_files_fn
1156 -- Save the number of split files for future references
1157 s
<- io
$ readFile n_files_fn
1158 let n_files
= read s
:: Int
1159 dflags
' = dflags
{ splitInfo
= Just
(split_s_prefix
, n_files
) }
1163 -- Remember to delete all these files
1164 io
$ addFilesToClean dflags
' [ split_s_prefix
++ "__" ++ show n
++ ".s"
1165 | n
<- [1..n_files
]]
1167 return (SplitAs
, "**splitmangle**")
1168 -- we don't use the filename
1170 -----------------------------------------------------------------------------
1173 runPhase As input_fn dflags
1175 let as_opts
= getOpts dflags opt_a
1176 let cmdline_include_paths
= includePaths dflags
1178 next_phase
<- maybeMergeStub
1179 output_fn
<- phaseOutputFilename next_phase
1181 -- we create directories for the object file, because it
1182 -- might be a hierarchical module.
1183 io
$ createDirectoryHierarchy
(takeDirectory output_fn
)
1185 io
$ SysTools
.runAs dflags
1186 (map SysTools
.Option as_opts
1187 ++ [ SysTools
.Option
("-I" ++ p
) | p
<- cmdline_include_paths
]
1189 -- We only support SparcV9 and better because V8 lacks an atomic CAS
1190 -- instruction so we have to make sure that the assembler accepts the
1191 -- instruction set. Note that the user can still override this
1192 -- (e.g., -mcpu=ultrasparc). GCC picks the "best" -mcpu flag
1193 -- regardless of the ordering.
1195 -- This is a temporary hack.
1196 ++ (if platformArch
(targetPlatform dflags
) == ArchSPARC
1197 then [SysTools
.Option
"-mcpu=v9"]
1200 ++ [ SysTools
.Option
"-c"
1201 , SysTools
.FileOption
"" input_fn
1202 , SysTools
.Option
"-o"
1203 , SysTools
.FileOption
"" output_fn
1206 return (next_phase
, output_fn
)
1209 runPhase SplitAs _input_fn dflags
1211 -- we'll handle the stub_o file in this phase, so don't MergeStub,
1212 -- just jump straight to StopLn afterwards.
1213 let next_phase
= StopLn
1214 output_fn
<- phaseOutputFilename next_phase
1216 let base_o
= dropExtension output_fn
1217 osuf
= objectSuf dflags
1218 split_odir
= base_o
++ "_" ++ osuf
++ "_split"
1220 io
$ createDirectoryHierarchy split_odir
1222 -- remove M_split/ *.o, because we're going to archive M_split/ *.o
1223 -- later and we don't want to pick up any old objects.
1224 fs
<- io
$ getDirectoryContents split_odir
1225 io
$ mapM_ removeFile $
1226 map (split_odir
</>) $ filter (osuf `
isSuffixOf`
) fs
1228 let as_opts
= getOpts dflags opt_a
1230 let (split_s_prefix
, n
) = case splitInfo dflags
of
1231 Nothing
-> panic
"No split info"
1234 let split_s n
= split_s_prefix
++ "__" ++ show n
<.> "s"
1236 split_obj
:: Int -> FilePath
1237 split_obj n
= split_odir
</>
1238 takeFileName base_o
++ "__" ++ show n
<.> osuf
1241 = SysTools
.runAs dflags
1242 (map SysTools
.Option as_opts
++
1244 -- We only support SparcV9 and better because V8 lacks an atomic CAS
1245 -- instruction so we have to make sure that the assembler accepts the
1246 -- instruction set. Note that the user can still override this
1247 -- (e.g., -mcpu=ultrasparc). GCC picks the "best" -mcpu flag
1248 -- regardless of the ordering.
1250 -- This is a temporary hack.
1251 (if platformArch
(targetPlatform dflags
) == ArchSPARC
1252 then [SysTools
.Option
"-mcpu=v9"]
1255 [ SysTools
.Option
"-c"
1256 , SysTools
.Option
"-o"
1257 , SysTools
.FileOption
"" (split_obj n
)
1258 , SysTools
.FileOption
"" (split_s n
)
1261 io
$ mapM_ assemble_file
[1..n
]
1263 -- Note [pipeline-split-init]
1264 -- If we have a stub file, it may contain constructor
1265 -- functions for initialisation of this module. We can't
1266 -- simply leave the stub as a separate object file, because it
1267 -- will never be linked in: nothing refers to it. We need to
1268 -- ensure that if we ever refer to the data in this module
1269 -- that needs initialisation, then we also pull in the
1270 -- initialisation routine.
1272 -- To that end, we make a DANGEROUS ASSUMPTION here: the data
1273 -- that needs to be initialised is all in the FIRST split
1274 -- object. See Note [codegen-split-init].
1276 PipeState
{maybe_stub_o
} <- getPipeState
1277 case maybe_stub_o
of
1278 Nothing
-> return ()
1279 Just stub_o
-> io
$ do
1280 tmp_split_1
<- newTempName dflags osuf
1281 let split_1
= split_obj
1
1282 copyFile split_1 tmp_split_1
1284 joinObjectFiles dflags
[tmp_split_1
, stub_o
] split_1
1286 -- join them into a single .o file
1287 io
$ joinObjectFiles dflags
(map split_obj
[1..n
]) output_fn
1289 return (next_phase
, output_fn
)
1291 -----------------------------------------------------------------------------
1294 runPhase LlvmOpt input_fn dflags
1296 let lo_opts
= getOpts dflags opt_lo
1297 let opt_lvl
= max 0 (min 2 $ optLevel dflags
)
1298 -- don't specify anything if user has specified commands. We do this for
1299 -- opt but not llc since opt is very specifically for optimisation passes
1300 -- only, so if the user is passing us extra options we assume they know
1301 -- what they are doing and don't get in the way.
1302 let optFlag
= if null lo_opts
1303 then [SysTools
.Option
(llvmOpts
!! opt_lvl
)]
1306 output_fn
<- phaseOutputFilename LlvmLlc
1308 io
$ SysTools
.runLlvmOpt dflags
1309 ([ SysTools
.FileOption
"" input_fn
,
1310 SysTools
.Option
"-o",
1311 SysTools
.FileOption
"" output_fn
]
1313 ++ map SysTools
.Option lo_opts
)
1315 return (LlvmLlc
, output_fn
)
1317 -- we always (unless -optlo specified) run Opt since we rely on it to
1318 -- fix up some pretty big deficiencies in the code we generate
1319 llvmOpts
= ["-mem2reg", "-O1", "-O2"]
1321 -----------------------------------------------------------------------------
1324 runPhase LlvmLlc input_fn dflags
1326 let lc_opts
= getOpts dflags opt_lc
1327 opt_lvl
= max 0 (min 2 $ optLevel dflags
)
1328 rmodel | opt_PIC
= "pic"
1329 |
not opt_Static
= "dynamic-no-pic"
1330 |
otherwise = "static"
1332 output_fn
<- phaseOutputFilename LlvmMangle
1334 io
$ SysTools
.runLlvmLlc dflags
1335 ([ SysTools
.Option
(llvmOpts
!! opt_lvl
),
1336 SysTools
.Option
$ "-relocation-model=" ++ rmodel
,
1337 SysTools
.FileOption
"" input_fn
,
1338 SysTools
.Option
"-o", SysTools
.FileOption
"" output_fn
]
1339 ++ map SysTools
.Option lc_opts
1340 ++ map SysTools
.Option fpOpts
)
1342 return (LlvmMangle
, output_fn
)
1344 -- Bug in LLVM at O3 on OSX.
1345 llvmOpts
= if platformOS
(targetPlatform dflags
) == OSDarwin
1346 then ["-O1", "-O2", "-O2"]
1347 else ["-O1", "-O2", "-O3"]
1348 -- On ARMv7 using LLVM, LLVM fails to allocate floating point registers
1349 -- while compiling GHC source code. It's probably due to fact
1350 -- that it does not enable VFP by default. Let's do this manually
1352 fpOpts
= case platformArch
(targetPlatform dflags
) of
1353 ArchARM ARMv7 ext
-> if (elem VFPv3 ext
)
1354 then ["-mattr=+v7,+vfp3"]
1355 else if (elem VFPv3D16 ext
)
1356 then ["-mattr=+v7,+vfp3,+d16"]
1360 -----------------------------------------------------------------------------
1363 runPhase LlvmMangle input_fn _dflags
1365 output_fn
<- phaseOutputFilename As
1366 io
$ llvmFixupAsm input_fn output_fn
1367 return (As
, output_fn
)
1369 -----------------------------------------------------------------------------
1370 -- merge in stub objects
1372 runPhase MergeStub input_fn dflags
1374 PipeState
{maybe_stub_o
} <- getPipeState
1375 output_fn
<- phaseOutputFilename StopLn
1376 case maybe_stub_o
of
1378 panic
"runPhase(MergeStub): no stub"
1380 io
$ joinObjectFiles dflags
[input_fn
, stub_o
] output_fn
1381 return (StopLn
, output_fn
)
1383 -- warning suppression
1384 runPhase other _input_fn _dflags
=
1385 panic
("runPhase: don't know how to run phase " ++ show other
)
1387 maybeMergeStub
:: CompPipeline Phase
1390 PipeState
{maybe_stub_o
} <- getPipeState
1391 if isJust maybe_stub_o
then return MergeStub
else return StopLn
1393 -----------------------------------------------------------------------------
1394 -- MoveBinary sort-of-phase
1395 -- After having produced a binary, move it somewhere else and generate a
1396 -- wrapper script calling the binary. Currently, we need this only in
1397 -- a parallel way (i.e. in GUM), because PVM expects the binary in a
1398 -- central directory.
1399 -- This is called from linkBinary below, after linking. I haven't made it
1400 -- a separate phase to minimise interfering with other modules, and
1401 -- we don't need the generality of a phase (MoveBinary is always
1402 -- done after linking and makes only sense in a parallel setup) -- HWL
1404 runPhase_MoveBinary
:: DynFlags
-> FilePath -> IO Bool
1405 runPhase_MoveBinary dflags input_fn
1406 | WayPar `
elem`
(wayNames dflags
) && not opt_Static
=
1407 panic
("Don't know how to combine PVM wrapper and dynamic wrapper")
1408 | WayPar `
elem`
(wayNames dflags
) = do
1409 let sysMan
= pgm_sysman dflags
1410 pvm_root
<- getEnv "PVM_ROOT"
1411 pvm_arch
<- getEnv "PVM_ARCH"
1413 pvm_executable_base
= "=" ++ input_fn
1414 pvm_executable
= pvm_root
++ "/bin/" ++ pvm_arch
++ "/" ++ pvm_executable_base
1415 -- nuke old binary; maybe use configur'ed names for cp and rm?
1416 _
<- tryIO
(removeFile pvm_executable
)
1417 -- move the newly created binary into PVM land
1418 copy dflags
"copying PVM executable" input_fn pvm_executable
1419 -- generate a wrapper script for running a parallel prg under PVM
1420 writeFile input_fn
(mk_pvm_wrapper_script pvm_executable pvm_executable_base sysMan
)
1422 |
otherwise = return True
1424 mkExtraCObj
:: DynFlags
-> String -> IO FilePath
1425 mkExtraCObj dflags xs
1426 = do cFile
<- newTempName dflags
"c"
1427 oFile
<- newTempName dflags
"o"
1429 let rtsDetails
= getPackageDetails
(pkgState dflags
) rtsPackageId
1430 SysTools
.runCc dflags
1432 FileOption
"" cFile
,
1434 FileOption
"" oFile
]
1435 ++ map SysTools
.Option
(getOpts dflags opt_c
) -- see #5528
1436 ++ map (FileOption
"-I") (includeDirs rtsDetails
))
1439 -- When linking a binary, we need to create a C main() function that
1440 -- starts everything off. This used to be compiled statically as part
1441 -- of the RTS, but that made it hard to change the -rtsopts setting,
1442 -- so now we generate and compile a main() stub as part of every
1443 -- binary and pass the -rtsopts setting directly to the RTS (#5373)
1445 mkExtraObjToLinkIntoBinary
:: DynFlags
-> [PackageId
] -> IO FilePath
1446 mkExtraObjToLinkIntoBinary dflags dep_packages
= do
1447 link_info
<- getLinkInfo dflags dep_packages
1449 let have_rts_opts_flags
=
1450 isJust (rtsOpts dflags
) ||
case rtsOptsEnabled dflags
of
1451 RtsOptsSafeOnly
-> False
1454 when (dopt Opt_NoHsMain dflags
&& have_rts_opts_flags
) $ do
1455 hPutStrLn stderr $ "Warning: -rtsopts and -with-rtsopts have no effect with -no-hs-main.\n" ++
1456 " Call hs_init_ghc() from your main() function to set these options."
1458 mkExtraCObj dflags
(showSDoc
(vcat
[main
,
1459 link_opts link_info
]
1460 <> char
'\n')) -- final newline, to
1465 | dopt Opt_NoHsMain dflags
= empty
1466 |
otherwise = vcat
[
1467 ptext
(sLit
"#include \"Rts.h\""),
1468 ptext
(sLit
"extern StgClosure ZCMain_main_closure;"),
1469 ptext
(sLit
"int main(int argc, char *argv[])"),
1471 ptext
(sLit
" RtsConfig __conf = defaultRtsConfig;"),
1472 ptext
(sLit
" __conf.rts_opts_enabled = ")
1473 <> text
(show (rtsOptsEnabled dflags
)) <> semi
,
1474 case rtsOpts dflags
of
1476 Just opts
-> ptext
(sLit
" __conf.rts_opts= ") <>
1477 text
(show opts
) <> semi
,
1478 ptext
(sLit
" return hs_main(argc, argv, &ZCMain_main_closure,__conf);"),
1483 |
not (platformSupportsSavingLinkOpts
(platformOS
(targetPlatform dflags
)))
1485 |
otherwise = hcat
[
1486 text
"__asm__(\"\\t.section ", text ghcLinkInfoSectionName
,
1488 text elfSectionNote
,
1491 text
"\\t.ascii \\\"", info
', text
"\\\"\\n\");" ]
1493 -- we need to escape twice: once because we're inside a C string,
1494 -- and again because we're inside an asm string.
1495 info
' = text
$ (escape
.escape
) info
1497 escape
:: String -> String
1498 escape
= concatMap (charToC
.fromIntegral.ord)
1500 elfSectionNote
:: String
1501 elfSectionNote
= case platformArch
(targetPlatform dflags
) of
1502 ArchARM _ _
-> "%note"
1505 -- The "link info" is a string representing the parameters of the
1506 -- link. We save this information in the binary, and the next time we
1507 -- link, if nothing else has changed, we use the link info stored in
1508 -- the existing binary to decide whether to re-link or not.
1509 getLinkInfo
:: DynFlags
-> [PackageId
] -> IO String
1510 getLinkInfo dflags dep_packages
= do
1511 package_link_opts
<- getPackageLinkOpts dflags dep_packages
1512 pkg_frameworks
<- case platformOS
(targetPlatform dflags
) of
1513 OSDarwin
-> getPackageFrameworks dflags dep_packages
1515 extra_ld_inputs
<- readIORef v_Ld_inputs
1517 link_info
= (package_link_opts
,
1520 rtsOptsEnabled dflags
,
1521 dopt Opt_NoHsMain dflags
,
1523 getOpts dflags opt_l
)
1525 return (show link_info
)
1527 -- generates a Perl skript starting a parallel prg under PVM
1528 mk_pvm_wrapper_script
:: String -> String -> String -> String
1529 mk_pvm_wrapper_script pvm_executable pvm_executable_base sysMan
= unlines $
1531 "eval 'exec perl -S $0 ${1+\"$@\"}'",
1532 " if $running_under_some_shell;",
1533 "# =!=!=!=!=!=!=!=!=!=!=!",
1534 "# This script is automatically generated: DO NOT EDIT!!!",
1535 "# Generated by Glasgow Haskell Compiler",
1536 "# ngoqvam choHbogh vaj' vIHoHnISbej !!!!",
1538 "$pvm_executable = '" ++ pvm_executable
++ "';",
1539 "$pvm_executable_base = '" ++ pvm_executable_base
++ "';",
1540 "$SysMan = '" ++ sysMan
++ "';",
1542 {- ToDo: add the magical shortcuts again iff we actually use them -- HWL
1543 "# first, some magical shortcuts to run "commands" on the binary",
1544 "# (which is hidden)",
1545 "if ($#ARGV == 1 && $ARGV[0] eq '+RTS' && $ARGV[1] =~ /^--((size|file|strip|rm|nm).*)/ ) {",
1546 " local($cmd) = $1;",
1547 " system("$cmd $pvm_executable");",
1548 " exit(0); # all done",
1551 "# Now, run the real binary; process the args first",
1552 "$ENV{'PE'} = $pvm_executable_base;", -- ++ pvm_executable_base,
1554 "$nprocessors = 0; # the default: as many PEs as machines in PVM config",
1555 "@nonPVM_args = ();",
1556 "$in_RTS_args = 0;",
1558 "args: while ($a = shift(@ARGV)) {",
1559 " if ( $a eq '+RTS' ) {",
1560 " $in_RTS_args = 1;",
1561 " } elsif ( $a eq '-RTS' ) {",
1562 " $in_RTS_args = 0;",
1564 " if ( $a eq '-d' && $in_RTS_args ) {",
1566 " } elsif ( $a =~ /^-qN(\\d+)/ && $in_RTS_args ) {",
1567 " $nprocessors = $1;",
1568 " } elsif ( $a =~ /^-qp(\\d+)/ && $in_RTS_args ) {",
1569 " $nprocessors = $1;",
1571 " push(@nonPVM_args, $a);",
1575 "local($return_val) = 0;",
1576 "# Start the parallel execution by calling SysMan",
1577 "system(\"$SysMan $debug $pvm_executable $nprocessors @nonPVM_args\");",
1578 "$return_val = $?;",
1579 "# ToDo: fix race condition moving files and flushing them!!",
1580 "system(\"cp $ENV{'HOME'}/$pvm_executable_base.???.gr .\") if -f \"$ENV{'HOME'}/$pvm_executable_base.002.gr\";",
1581 "exit($return_val);"
1584 -----------------------------------------------------------------------------
1585 -- Look for the /* GHC_PACKAGES ... */ comment at the top of a .hc file
1587 getHCFilePackages
:: FilePath -> IO [PackageId
]
1588 getHCFilePackages filename
=
1589 Exception
.bracket (openFile filename ReadMode
) hClose $ \h
-> do
1592 '/':'*':' ':'G
':'H
':'C
':'_
':'P
':'A
':'C
':'K
':'A
':'G
':'E
':'S
':rest
->
1593 return (map stringToPackageId
(words rest
))
1597 -----------------------------------------------------------------------------
1598 -- Static linking, of .o files
1600 -- The list of packages passed to link is the list of packages on
1601 -- which this program depends, as discovered by the compilation
1602 -- manager. It is combined with the list of packages that the user
1603 -- specifies on the command line with -package flags.
1605 -- In one-shot linking mode, we can't discover the package
1606 -- dependencies (because we haven't actually done any compilation or
1607 -- read any interface files), so the user must explicitly specify all
1610 linkBinary
:: DynFlags
-> [FilePath] -> [PackageId
] -> IO ()
1611 linkBinary dflags o_files dep_packages
= do
1612 let platform
= targetPlatform dflags
1613 verbFlags
= getVerbFlags dflags
1614 output_fn
= exeFileName dflags
1616 -- get the full list of packages to link with, by combining the
1617 -- explicit packages with the auto packages and all of their
1618 -- dependencies, and eliminating duplicates.
1620 pkg_lib_paths
<- getPackageLibraryPath dflags dep_packages
1621 let pkg_lib_path_opts
= concat (map get_pkg_lib_path_opts pkg_lib_paths
)
1622 get_pkg_lib_path_opts l
1623 | osElfTarget
(platformOS platform
) &&
1624 dynLibLoader dflags
== SystemDependent
&&
1626 = ["-L" ++ l
, "-Wl,-rpath", "-Wl," ++ l
]
1627 |
otherwise = ["-L" ++ l
]
1629 let lib_paths
= libraryPaths dflags
1630 let lib_path_opts
= map ("-L"++) lib_paths
1632 extraLinkObj
<- mkExtraObjToLinkIntoBinary dflags dep_packages
1634 pkg_link_opts
<- getPackageLinkOpts dflags dep_packages
1636 pkg_framework_path_opts
<-
1637 case platformOS platform
of
1639 do pkg_framework_paths
<- getPackageFrameworkPath dflags dep_packages
1640 return $ map ("-F" ++) pkg_framework_paths
1644 framework_path_opts
<-
1645 case platformOS platform
of
1647 do let framework_paths
= frameworkPaths dflags
1648 return $ map ("-F" ++) framework_paths
1652 pkg_framework_opts
<-
1653 case platformOS platform
of
1655 do pkg_frameworks
<- getPackageFrameworks dflags dep_packages
1656 return $ concat [ ["-framework", fw
] | fw
<- pkg_frameworks
]
1661 case platformOS platform
of
1663 do let frameworks
= cmdlineFrameworks dflags
1664 -- reverse because they're added in reverse order from
1666 return $ concat [ ["-framework", fw
] | fw
<- reverse frameworks
]
1670 -- probably _stub.o files
1671 extra_ld_inputs
<- readIORef v_Ld_inputs
1673 -- opts from -optl-<blah> (including -l<blah> options)
1674 let extra_ld_opts
= getOpts dflags opt_l
1676 let ways
= wayNames dflags
1678 -- Here are some libs that need to be linked at the *end* of
1679 -- the command line, because they contain symbols that are referred to
1680 -- by the RTS. We can't therefore use the ordinary way opts for these.
1682 debug_opts | WayDebug `
elem` ways
= [
1683 #if defined
(HAVE_LIBBFD
)
1690 thread_opts | WayThreaded `
elem` ways
= [
1691 #if !defined
(mingw32_TARGET_OS
) && !defined
(freebsd_TARGET_OS
) && !defined
(openbsd_TARGET_OS
) && !defined
(haiku_TARGET_OS
)
1694 #if defined
(osf3_TARGET_OS
)
1700 rc_objs
<- maybeCreateManifest dflags output_fn
1702 SysTools
.runLink dflags
(
1703 map SysTools
.Option verbFlags
1704 ++ [ SysTools
.Option
"-o"
1705 , SysTools
.FileOption
"" output_fn
1707 ++ map SysTools
.Option
(
1710 -- Permit the linker to auto link _symbol to _imp_symbol.
1711 -- This lets us link against DLLs without needing an "import library".
1712 ++ (if platformOS platform
== OSMinGW32
1713 then ["-Wl,--enable-auto-import"]
1716 -- '-no_compact_unwind'
1717 -- C++/Objective-C exceptions cannot use optimised
1718 -- stack unwinding code. The optimised form is the
1719 -- default in Xcode 4 on at least x86_64, and
1720 -- without this flag we're also seeing warnings
1722 -- ld: warning: could not create compact unwind for .LFB3: non-standard register 5 being saved in prolog
1724 ++ (if cLdHasNoCompactUnwind
== "YES" &&
1725 platformOS platform
== OSDarwin
&&
1726 platformArch platform `
elem`
[ArchX86
, ArchX86_64
]
1727 then ["-Wl,-no_compact_unwind"]
1730 -- '-Wl,-read_only_relocs,suppress'
1731 -- ld gives loads of warnings like:
1732 -- ld: warning: text reloc in _base_GHCziArr_unsafeArray_info to _base_GHCziArr_unsafeArray_closure
1733 -- when linking any program. We're not sure
1734 -- whether this is something we ought to fix, but
1735 -- for now this flags silences them.
1736 ++ (if platformOS platform
== OSDarwin
&&
1737 platformArch platform
== ArchX86
1738 then ["-Wl,-read_only_relocs,suppress"]
1746 ++ framework_path_opts
1748 ++ pkg_lib_path_opts
1751 ++ pkg_framework_path_opts
1752 ++ pkg_framework_opts
1757 -- parallel only: move binary to another dir -- HWL
1758 success
<- runPhase_MoveBinary dflags output_fn
1759 if success
then return ()
1760 else ghcError
(InstallationError
("cannot move binary"))
1763 exeFileName
:: DynFlags
-> FilePath
1765 | Just s
<- outputFile dflags
=
1766 if platformOS
(targetPlatform dflags
) == OSMinGW32
1767 then if null (takeExtension s
)
1772 if platformOS
(targetPlatform dflags
) == OSMinGW32
1778 -> FilePath -- filename of executable
1779 -> IO [FilePath] -- extra objects to embed, maybe
1780 maybeCreateManifest dflags exe_filename
1781 | platformOS
(targetPlatform dflags
) == OSMinGW32
&&
1782 dopt Opt_GenManifest dflags
1783 = do let manifest_filename
= exe_filename
<.> "manifest"
1785 writeFile manifest_filename
$
1786 "<?xml version=\"1.0\" encoding=\"UTF-8\" standalone=\"yes\"?>\n"++
1787 " <assembly xmlns=\"urn:schemas-microsoft-com:asm.v1\" manifestVersion=\"1.0\">\n"++
1788 " <assemblyIdentity version=\"1.0.0.0\"\n"++
1789 " processorArchitecture=\"X86\"\n"++
1790 " name=\"" ++ dropExtension exe_filename
++ "\"\n"++
1791 " type=\"win32\"/>\n\n"++
1792 " <trustInfo xmlns=\"urn:schemas-microsoft-com:asm.v3\">\n"++
1794 " <requestedPrivileges>\n"++
1795 " <requestedExecutionLevel level=\"asInvoker\" uiAccess=\"false\"/>\n"++
1796 " </requestedPrivileges>\n"++
1801 -- Windows will find the manifest file if it is named
1802 -- foo.exe.manifest. However, for extra robustness, and so that
1803 -- we can move the binary around, we can embed the manifest in
1804 -- the binary itself using windres:
1805 if not (dopt Opt_EmbedManifest dflags
) then return [] else do
1807 rc_filename
<- newTempName dflags
"rc"
1808 rc_obj_filename
<- newTempName dflags
(objectSuf dflags
)
1810 writeFile rc_filename
$
1811 "1 24 MOVEABLE PURE " ++ show manifest_filename
++ "\n"
1812 -- magic numbers :-)
1813 -- show is a bit hackish above, but we need to escape the
1814 -- backslashes in the path.
1816 let wr_opts
= getOpts dflags opt_windres
1817 runWindres dflags
$ map SysTools
.Option
$
1818 ["--input="++rc_filename
,
1819 "--output="++rc_obj_filename
,
1820 "--output-format=coff"]
1822 -- no FileOptions here: windres doesn't like seeing
1823 -- backslashes, apparently
1825 removeFile manifest_filename
1827 return [rc_obj_filename
]
1828 |
otherwise = return []
1831 linkDynLib
:: DynFlags
-> [String] -> [PackageId
] -> IO ()
1832 linkDynLib dflags o_files dep_packages
= do
1833 let verbFlags
= getVerbFlags dflags
1834 let o_file
= outputFile dflags
1836 pkgs
<- getPreloadPackagesAnd dflags dep_packages
1838 let pkg_lib_paths
= collectLibraryPaths pkgs
1839 let pkg_lib_path_opts
= concatMap get_pkg_lib_path_opts pkg_lib_paths
1840 get_pkg_lib_path_opts l
1841 | osElfTarget
(platformOS
(targetPlatform dflags
)) &&
1842 dynLibLoader dflags
== SystemDependent
&&
1844 = ["-L" ++ l
, "-Wl,-rpath", "-Wl," ++ l
]
1845 |
otherwise = ["-L" ++ l
]
1847 let lib_paths
= libraryPaths dflags
1848 let lib_path_opts
= map ("-L"++) lib_paths
1850 -- We don't want to link our dynamic libs against the RTS package,
1851 -- because the RTS lib comes in several flavours and we want to be
1852 -- able to pick the flavour when a binary is linked.
1853 -- On Windows we need to link the RTS import lib as Windows does
1854 -- not allow undefined symbols.
1855 -- The RTS library path is still added to the library search path
1856 -- above in case the RTS is being explicitly linked in (see #3807).
1857 let pkgs_no_rts
= case platformOS
(targetPlatform dflags
) of
1861 filter ((/= rtsPackageId
) . packageConfigId
) pkgs
1862 let pkg_link_opts
= collectLinkOpts dflags pkgs_no_rts
1864 -- probably _stub.o files
1865 extra_ld_inputs
<- readIORef v_Ld_inputs
1867 let extra_ld_opts
= getOpts dflags opt_l
1869 #if defined
(mingw32_HOST_OS
)
1870 -----------------------------------------------------------------------------
1872 -----------------------------------------------------------------------------
1873 let output_fn
= case o_file
of { Just s
-> s
; Nothing
-> "HSdll.dll"; }
1875 SysTools
.runLink dflags
(
1876 map SysTools
.Option verbFlags
1877 ++ [ SysTools
.Option
"-o"
1878 , SysTools
.FileOption
"" output_fn
1879 , SysTools
.Option
"-shared"
1881 [ SysTools
.FileOption
"-Wl,--out-implib=" (output_fn
++ ".a")
1882 | dopt Opt_SharedImplib dflags
1884 ++ map (SysTools
.FileOption
"") o_files
1885 ++ map SysTools
.Option
(
1887 -- Permit the linker to auto link _symbol to _imp_symbol
1888 -- This lets us link against DLLs without needing an "import library"
1889 ["-Wl,--enable-auto-import"]
1894 ++ pkg_lib_path_opts
1897 #elif defined
(darwin_TARGET_OS
)
1898 -----------------------------------------------------------------------------
1899 -- Making a darwin dylib
1900 -----------------------------------------------------------------------------
1901 -- About the options used for Darwin:
1903 -- Apple's way of saying -shared
1904 -- -undefined dynamic_lookup:
1905 -- Without these options, we'd have to specify the correct dependencies
1906 -- for each of the dylibs. Note that we could (and should) do without this
1907 -- for all libraries except the RTS; all we need to do is to pass the
1908 -- correct HSfoo_dyn.dylib files to the link command.
1909 -- This feature requires Mac OS X 10.3 or later; there is a similar feature,
1910 -- -flat_namespace -undefined suppress, which works on earlier versions,
1911 -- but it has other disadvantages.
1913 -- Build the dynamic library as a single "module", i.e. no dynamic binding
1914 -- nonsense when referring to symbols from within the library. The NCG
1915 -- assumes that this option is specified (on i386, at least).
1917 -- Mac OS/X stores the path where a dynamic library is (to be) installed
1918 -- in the library itself. It's called the "install name" of the library.
1919 -- Then any library or executable that links against it before it's
1920 -- installed will search for it in its ultimate install location. By
1921 -- default we set the install name to the absolute path at build time, but
1922 -- it can be overridden by the -dylib-install-name option passed to ghc.
1924 -----------------------------------------------------------------------------
1926 let output_fn
= case o_file
of { Just s
-> s
; Nothing
-> "a.out"; }
1928 instName
<- case dylibInstallName dflags
of
1931 pwd
<- getCurrentDirectory
1932 return $ pwd `combine` output_fn
1933 SysTools
.runLink dflags
(
1934 map SysTools
.Option verbFlags
1935 ++ [ SysTools
.Option
"-dynamiclib"
1936 , SysTools
.Option
"-o"
1937 , SysTools
.FileOption
"" output_fn
1939 ++ map SysTools
.Option
(
1941 ++ [ "-undefined", "dynamic_lookup", "-single_module",
1942 #if !defined
(x86_64_TARGET_ARCH
)
1943 "-Wl,-read_only_relocs,suppress",
1945 "-install_name", instName
]
1949 ++ pkg_lib_path_opts
1953 -----------------------------------------------------------------------------
1955 -----------------------------------------------------------------------------
1957 let output_fn
= case o_file
of { Just s
-> s
; Nothing
-> "a.out"; }
1958 let buildingRts
= thisPackage dflags
== rtsPackageId
1959 let bsymbolicFlag
= if buildingRts
1960 then -- -Bsymbolic breaks the way we implement
1963 else -- we need symbolic linking to resolve
1964 -- non-PIC intra-package-relocations
1967 SysTools
.runLink dflags
(
1968 map SysTools
.Option verbFlags
1969 ++ [ SysTools
.Option
"-o"
1970 , SysTools
.FileOption
"" output_fn
1972 ++ map SysTools
.Option
(
1976 -- Set the library soname. We use -h rather than -soname as
1977 -- Solaris 10 doesn't support the latter:
1978 ++ [ "-Wl,-h," ++ takeFileName output_fn
]
1982 ++ pkg_lib_path_opts
1986 -- -----------------------------------------------------------------------------
1989 doCpp
:: DynFlags
-> Bool -> Bool -> FilePath -> FilePath -> IO ()
1990 doCpp dflags raw include_cc_opts input_fn output_fn
= do
1991 let hscpp_opts
= getOpts dflags opt_P
1992 let cmdline_include_paths
= includePaths dflags
1994 pkg_include_dirs
<- getPackageIncludePath dflags
[]
1995 let include_paths
= foldr (\ x xs
-> "-I" : x
: xs
) []
1996 (cmdline_include_paths
++ pkg_include_dirs
)
1998 let verbFlags
= getVerbFlags dflags
2001 | include_cc_opts
= getOpts dflags opt_c
2004 let cpp_prog args | raw
= SysTools
.runCpp dflags args
2005 |
otherwise = SysTools
.runCc dflags
(SysTools
.Option
"-E" : args
)
2008 [ "-D" ++ HOST_OS
++ "_BUILD_OS=1",
2009 "-D" ++ HOST_ARCH
++ "_BUILD_ARCH=1",
2010 "-D" ++ TARGET_OS
++ "_HOST_OS=1",
2011 "-D" ++ TARGET_ARCH
++ "_HOST_ARCH=1" ]
2012 -- remember, in code we *compile*, the HOST is the same our TARGET,
2013 -- and BUILD is the same as our HOST.
2015 cpp_prog
( map SysTools
.Option verbFlags
2016 ++ map SysTools
.Option include_paths
2017 ++ map SysTools
.Option hsSourceCppOpts
2018 ++ map SysTools
.Option target_defs
2019 ++ map SysTools
.Option hscpp_opts
2020 ++ map SysTools
.Option cc_opts
2021 ++ [ SysTools
.Option
"-x"
2022 , SysTools
.Option
"c"
2023 , SysTools
.Option input_fn
2024 -- We hackily use Option instead of FileOption here, so that the file
2025 -- name is not back-slashed on Windows. cpp is capable of
2026 -- dealing with / in filenames, so it works fine. Furthermore
2027 -- if we put in backslashes, cpp outputs #line directives
2028 -- with *double* backslashes. And that in turn means that
2029 -- our error messages get double backslashes in them.
2030 -- In due course we should arrange that the lexer deals
2031 -- with these \\ escapes properly.
2032 , SysTools
.Option
"-o"
2033 , SysTools
.FileOption
"" output_fn
2036 hsSourceCppOpts
:: [String]
2037 -- Default CPP defines in Haskell source
2039 [ "-D__GLASGOW_HASKELL__="++cProjectVersionInt
]
2041 -- ---------------------------------------------------------------------------
2042 -- join object files into a single relocatable object file, using ld -r
2044 joinObjectFiles
:: DynFlags
-> [FilePath] -> FilePath -> IO ()
2045 joinObjectFiles dflags o_files output_fn
= do
2046 let ld_r args
= SysTools
.runLink dflags
([
2047 SysTools
.Option
"-nostdlib",
2048 SysTools
.Option
"-nodefaultlibs",
2049 SysTools
.Option
"-Wl,-r"
2051 -- gcc on sparc sets -Wl,--relax implicitly, but
2052 -- -r and --relax are incompatible for ld, so
2053 -- disable --relax explicitly.
2054 ++ (if platformArch
(targetPlatform dflags
) == ArchSPARC
2055 then [SysTools
.Option
"-Wl,-no-relax"]
2058 SysTools
.Option ld_build_id
,
2059 SysTools
.Option ld_x_flag
,
2060 SysTools
.Option
"-o",
2061 SysTools
.FileOption
"" output_fn
]
2064 ld_x_flag |
null cLD_X
= ""
2065 |
otherwise = "-Wl,-x"
2067 -- suppress the generation of the .note.gnu.build-id section,
2068 -- which we don't need and sometimes causes ld to emit a
2070 ld_build_id | cLdHasBuildId
== "YES" = "-Wl,--build-id=none"
2073 if cLdIsGNULd
== "YES"
2075 script
<- newTempName dflags
"ldscript"
2076 writeFile script
$ "INPUT(" ++ unwords o_files
++ ")"
2077 ld_r
[SysTools
.FileOption
"" script
]
2079 ld_r
(map (SysTools
.FileOption
"") o_files
)
2081 -- -----------------------------------------------------------------------------
2084 hscNextPhase
:: DynFlags
-> HscSource
-> HscTarget
-> Phase
2085 hscNextPhase _ HsBootFile _
= StopLn
2086 hscNextPhase dflags _ hsc_lang
=
2089 HscAsm | dopt Opt_SplitObjs dflags
-> SplitMangle
2092 HscNothing
-> StopLn
2093 HscInterpreted
-> StopLn
2095 touchObjectFile
:: DynFlags
-> FilePath -> IO ()
2096 touchObjectFile dflags path
= do
2097 createDirectoryHierarchy
$ takeDirectory path
2098 SysTools
.touch dflags
"Touching object file" path