summaryrefslogtreecommitdiff
path: root/compiler/ghci/Linker.lhs
blob: 5b0251c54efa9fa35f626cea962ad42bef5e1f95 (plain)
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
430
431
432
433
434
435
436
437
438
439
440
441
442
443
444
445
446
447
448
449
450
451
452
453
454
455
456
457
458
459
460
461
462
463
464
465
466
467
468
469
470
471
472
473
474
475
476
477
478
479
480
481
482
483
484
485
486
487
488
489
490
491
492
493
494
495
496
497
498
499
500
501
502
503
504
505
506
507
508
509
510
511
512
513
514
515
516
517
518
519
520
521
522
523
524
525
526
527
528
529
530
531
532
533
534
535
536
537
538
539
540
541
542
543
544
545
546
547
548
549
550
551
552
553
554
555
556
557
558
559
560
561
562
563
564
565
566
567
568
569
570
571
572
573
574
575
576
577
578
579
580
581
582
583
584
585
586
587
588
589
590
591
592
593
594
595
596
597
598
599
600
601
602
603
604
605
606
607
608
609
610
611
612
613
614
615
616
617
618
619
620
621
622
623
624
625
626
627
628
629
630
631
632
633
634
635
636
637
638
639
640
641
642
643
644
645
646
647
648
649
650
651
652
653
654
655
656
657
658
659
660
661
662
663
664
665
666
667
668
669
670
671
672
673
674
675
676
677
678
679
680
681
682
683
684
685
686
687
688
689
690
691
692
693
694
695
696
697
698
699
700
701
702
703
704
705
706
707
708
709
710
711
712
713
714
715
716
717
718
719
720
721
722
723
724
725
726
727
728
729
730
731
732
733
734
735
736
737
738
739
740
741
742
743
744
745
746
747
748
749
750
751
752
753
754
755
756
757
758
759
760
761
762
763
764
765
766
767
768
769
770
771
772
773
774
775
776
777
778
779
780
781
782
783
784
785
786
787
788
789
790
791
792
793
794
795
796
797
798
799
800
801
802
803
804
805
806
807
808
809
810
811
812
813
814
815
816
817
818
819
820
821
822
823
824
825
826
827
828
829
830
831
832
833
834
835
836
837
838
839
840
841
842
843
844
845
846
847
848
849
850
851
852
853
854
855
856
857
858
859
860
861
862
863
864
865
866
867
868
869
870
871
872
873
874
875
876
877
878
879
880
881
882
883
884
885
886
887
888
889
890
891
892
893
894
895
896
897
898
899
900
901
902
903
904
905
906
907
908
909
910
911
912
913
914
915
916
917
918
919
920
921
922
923
924
925
926
927
928
929
930
931
932
933
934
935
936
937
938
939
940
941
942
943
944
945
946
947
948
949
950
951
952
953
954
955
956
957
958
959
960
961
962
963
964
965
966
967
968
969
970
971
972
973
974
975
976
977
978
979
980
981
982
983
984
985
986
987
988
989
990
991
992
993
994
995
996
997
998
999
1000
1001
1002
1003
1004
1005
1006
1007
1008
1009
1010
1011
1012
1013
1014
1015
1016
1017
1018
1019
1020
1021
1022
1023
1024
1025
1026
1027
1028
1029
1030
1031
1032
1033
1034
1035
1036
1037
1038
1039
1040
1041
1042
1043
1044
1045
1046
1047
1048
1049
1050
1051
1052
1053
1054
1055
1056
1057
1058
1059
1060
1061
1062
1063
1064
1065
1066
1067
1068
1069
1070
1071
1072
1073
1074
1075
1076
1077
1078
1079
1080
1081
1082
1083
1084
1085
1086
1087
1088
1089
1090
1091
1092
1093
1094
1095
1096
1097
1098
1099
1100
1101
1102
1103
1104
1105
1106
1107
1108
1109
1110
1111
1112
1113
1114
1115
1116
1117
1118
1119
1120
1121
1122
1123
1124
1125
1126
1127
1128
1129
1130
1131
1132
1133
1134
1135
1136
1137
1138
1139
1140
1141
1142
1143
1144
1145
1146
1147
1148
1149
1150
1151
1152
1153
1154
1155
1156
1157
1158
1159
1160
1161
1162
1163
1164
1165
1166
1167
1168
1169
1170
1171
1172
1173
1174
1175
1176
1177
1178
1179
1180
1181
1182
1183
1184
1185
1186
1187
1188
1189
1190
1191
1192
1193
1194
1195
1196
1197
1198
1199
1200
1201
1202
1203
1204
1205
1206
1207
1208
1209
1210
1211
1212
1213
1214
1215
1216
1217
1218
1219
1220
1221
1222
1223
1224
1225
1226
1227
1228
1229
1230
1231
1232
1233
1234
1235
1236
1237
1238
1239
1240
1241
1242
1243
1244
1245
1246
1247
1248
1249
1250
1251
1252
1253
1254
1255
1256
1257
1258
1259
1260
1261
1262
1263
1264
1265
1266
1267
1268
1269
1270
1271
1272
1273
1274
1275
1276
1277
1278
1279
1280
1281
1282
1283
1284
1285
1286
1287
1288
1289
1290
1291
1292
1293
1294
1295
1296
1297
1298
1299
1300
1301
1302
1303
1304
1305
1306
1307
1308
1309
1310
1311
1312
1313
1314
1315
1316
1317
%
% (c) The University of Glasgow 2005-2012
%
\begin{code}
{-# LANGUAGE CPP, NondecreasingIndentation #-}
{-# OPTIONS_GHC -fno-cse #-}
-- -fno-cse is needed for GLOBAL_VAR's to behave properly

-- | The dynamic linker for GHCi.
--
-- This module deals with the top-level issues of dynamic linking,
-- calling the object-code linker and the byte-code linker where
-- necessary.

module Linker ( getHValue, showLinkerState,
                linkExpr, linkDecls, unload, withExtendedLinkEnv,
                extendLinkEnv, deleteFromLinkEnv,
                extendLoadedPkgs,
                linkPackages,initDynLinker,linkModule,
                linkCmdLineLibs,

                -- Saving/restoring globals
                PersistentLinkerState, saveLinkerGlobals, restoreLinkerGlobals
        ) where

#include "HsVersions.h"

import LoadIface
import ObjLink
import ByteCodeLink
import ByteCodeItbls
import ByteCodeAsm
import TcRnMonad
import Packages
import DriverPhases
import Finder
import HscTypes
import Name
import NameEnv
import NameSet
import UniqFM
import Module
import ListSetOps
import DynFlags
import BasicTypes
import Outputable
import Panic
import Util
import ErrUtils
import SrcLoc
import qualified Maybes
import UniqSet
import FastString
import Config
import Platform
import SysTools

-- Standard libraries
import Control.Monad

import Data.IORef
import Data.List
import Control.Concurrent.MVar

import System.FilePath
import System.IO
import System.Directory hiding (findFile)

import Exception
\end{code}


%************************************************************************
%*                                                                      *
                        The Linker's state
%*                                                                      *
%************************************************************************

The persistent linker state *must* match the actual state of the
C dynamic linker at all times, so we keep it in a private global variable.

The global IORef used for PersistentLinkerState actually contains another MVar.
The reason for this is that we want to allow another loaded copy of the GHC
library to side-effect the PLS and for those changes to be reflected here.

The PersistentLinkerState maps Names to actual closures (for
interpreted code only), for use during linking.

\begin{code}
GLOBAL_VAR_M(v_PersistentLinkerState, newMVar (panic "Dynamic linker not initialised"), MVar PersistentLinkerState)
GLOBAL_VAR(v_InitLinkerDone, False, Bool) -- Set True when dynamic linker is initialised

modifyPLS_ :: (PersistentLinkerState -> IO PersistentLinkerState) -> IO ()
modifyPLS_ f = readIORef v_PersistentLinkerState >>= flip modifyMVar_ f

modifyPLS :: (PersistentLinkerState -> IO (PersistentLinkerState, a)) -> IO a
modifyPLS f = readIORef v_PersistentLinkerState >>= flip modifyMVar f

data PersistentLinkerState
   = PersistentLinkerState {

        -- Current global mapping from Names to their true values
        closure_env :: ClosureEnv,

        -- The current global mapping from RdrNames of DataCons to
        -- info table addresses.
        -- When a new Unlinked is linked into the running image, or an existing
        -- module in the image is replaced, the itbl_env must be updated
        -- appropriately.
        itbl_env    :: !ItblEnv,

        -- The currently loaded interpreted modules (home package)
        bcos_loaded :: ![Linkable],

        -- And the currently-loaded compiled modules (home package)
        objs_loaded :: ![Linkable],

        -- The currently-loaded packages; always object code
        -- Held, as usual, in dependency order; though I am not sure if
        -- that is really important
        pkgs_loaded :: ![PackageKey]
     }

emptyPLS :: DynFlags -> PersistentLinkerState
emptyPLS _ = PersistentLinkerState {
                        closure_env = emptyNameEnv,
                        itbl_env    = emptyNameEnv,
                        pkgs_loaded = init_pkgs,
                        bcos_loaded = [],
                        objs_loaded = [] }

  -- Packages that don't need loading, because the compiler
  -- shares them with the interpreted program.
  --
  -- The linker's symbol table is populated with RTS symbols using an
  -- explicit list.  See rts/Linker.c for details.
  where init_pkgs = [rtsPackageKey]


extendLoadedPkgs :: [PackageKey] -> IO ()
extendLoadedPkgs pkgs =
  modifyPLS_ $ \s ->
      return s{ pkgs_loaded = pkgs ++ pkgs_loaded s }

extendLinkEnv :: [(Name,HValue)] -> IO ()
-- Automatically discards shadowed bindings
extendLinkEnv new_bindings =
  modifyPLS_ $ \pls ->
    let new_closure_env = extendClosureEnv (closure_env pls) new_bindings
    in return pls{ closure_env = new_closure_env }

deleteFromLinkEnv :: [Name] -> IO ()
deleteFromLinkEnv to_remove =
  modifyPLS_ $ \pls ->
    let new_closure_env = delListFromNameEnv (closure_env pls) to_remove
    in return pls{ closure_env = new_closure_env }

-- | Get the 'HValue' associated with the given name.
--
-- May cause loading the module that contains the name.
--
-- Throws a 'ProgramError' if loading fails or the name cannot be found.
getHValue :: HscEnv -> Name -> IO HValue
getHValue hsc_env name = do
  initDynLinker (hsc_dflags hsc_env)
  pls <- modifyPLS $ \pls -> do
           if (isExternalName name) then do
             (pls', ok) <- linkDependencies hsc_env pls noSrcSpan [nameModule name]
             if (failed ok) then throwGhcExceptionIO (ProgramError "")
                            else return (pls', pls')
            else
             return (pls, pls)
  lookupName (closure_env pls) name

linkDependencies :: HscEnv -> PersistentLinkerState
                 -> SrcSpan -> [Module]
                 -> IO (PersistentLinkerState, SuccessFlag)
linkDependencies hsc_env pls span needed_mods = do
--   initDynLinker (hsc_dflags hsc_env)
   let hpt = hsc_HPT hsc_env
       dflags = hsc_dflags hsc_env
   -- The interpreter and dynamic linker can only handle object code built
   -- the "normal" way, i.e. no non-std ways like profiling or ticky-ticky.
   -- So here we check the build tag: if we're building a non-standard way
   -- then we need to find & link object files built the "normal" way.
   maybe_normal_osuf <- checkNonStdWay dflags span

   -- Find what packages and linkables are required
   (lnks, pkgs) <- getLinkDeps hsc_env hpt pls
                               maybe_normal_osuf span needed_mods

   -- Link the packages and modules required
   pls1 <- linkPackages' dflags pkgs pls
   linkModules dflags pls1 lnks


-- | Temporarily extend the linker state.

withExtendedLinkEnv :: (MonadIO m, ExceptionMonad m) =>
                       [(Name,HValue)] -> m a -> m a
withExtendedLinkEnv new_env action
    = gbracket (liftIO $ extendLinkEnv new_env)
               (\_ -> reset_old_env)
               (\_ -> action)
    where
        -- Remember that the linker state might be side-effected
        -- during the execution of the IO action, and we don't want to
        -- lose those changes (we might have linked a new module or
        -- package), so the reset action only removes the names we
        -- added earlier.
          reset_old_env = liftIO $ do
            modifyPLS_ $ \pls ->
                let cur = closure_env pls
                    new = delListFromNameEnv cur (map fst new_env)
                in return pls{ closure_env = new }

-- filterNameMap removes from the environment all entries except
-- those for a given set of modules;
-- Note that this removes all *local* (i.e. non-isExternal) names too
-- (these are the temporary bindings from the command line).
-- Used to filter both the ClosureEnv and ItblEnv

filterNameMap :: [Module] -> NameEnv (Name, a) -> NameEnv (Name, a)
filterNameMap mods env
   = filterNameEnv keep_elt env
   where
     keep_elt (n,_) = isExternalName n
                      && (nameModule n `elem` mods)


-- | Display the persistent linker state.
showLinkerState :: DynFlags -> IO ()
showLinkerState dflags
  = do pls <- readIORef v_PersistentLinkerState >>= readMVar
       log_action dflags dflags SevDump noSrcSpan defaultDumpStyle
                 (vcat [text "----- Linker state -----",
                        text "Pkgs:" <+> ppr (pkgs_loaded pls),
                        text "Objs:" <+> ppr (objs_loaded pls),
                        text "BCOs:" <+> ppr (bcos_loaded pls)])
\end{code}


%************************************************************************
%*                                                                      *
\subsection{Initialisation}
%*                                                                      *
%************************************************************************

\begin{code}
-- | Initialise the dynamic linker.  This entails
--
--  a) Calling the C initialisation procedure,
--
--  b) Loading any packages specified on the command line,
--
--  c) Loading any packages specified on the command line, now held in the
--     @-l@ options in @v_Opt_l@,
--
--  d) Loading any @.o\/.dll@ files specified on the command line, now held
--     in @ldInputs@,
--
--  e) Loading any MacOS frameworks.
--
-- NOTE: This function is idempotent; if called more than once, it does
-- nothing.  This is useful in Template Haskell, where we call it before
-- trying to link.
--
initDynLinker :: DynFlags -> IO ()
initDynLinker dflags =
  modifyPLS_ $ \pls0 -> do
    done <- readIORef v_InitLinkerDone
    if done then return pls0
            else do writeIORef v_InitLinkerDone True
                    reallyInitDynLinker dflags

reallyInitDynLinker :: DynFlags -> IO PersistentLinkerState
reallyInitDynLinker dflags =
    do  {  -- Initialise the linker state
          let pls0 = emptyPLS dflags

          -- (a) initialise the C dynamic linker
        ; initObjLinker

          -- (b) Load packages from the command-line (Note [preload packages])
        ; pls <- linkPackages' dflags (preloadPackages (pkgState dflags)) pls0

          -- steps (c), (d) and (e)
        ; linkCmdLineLibs' dflags pls
        }

linkCmdLineLibs :: DynFlags -> IO ()
linkCmdLineLibs dflags = do
  initDynLinker dflags
  modifyPLS_ $ \pls -> do
    linkCmdLineLibs' dflags pls

linkCmdLineLibs' :: DynFlags -> PersistentLinkerState -> IO PersistentLinkerState
linkCmdLineLibs' dflags@(DynFlags { ldInputs     = cmdline_ld_inputs
                                  , libraryPaths = lib_paths}) pls =
  do  {   -- (c) Link libraries from the command-line
        ; let minus_ls = [ lib | Option ('-':'l':lib) <- cmdline_ld_inputs ]
        ; libspecs <- mapM (locateLib dflags False lib_paths) minus_ls

          -- (d) Link .o files from the command-line
        ; classified_ld_inputs <- mapM (classifyLdInput dflags)
                                    [ f | FileOption _ f <- cmdline_ld_inputs ]

          -- (e) Link any MacOS frameworks
        ; let platform = targetPlatform dflags
        ; let (framework_paths, frameworks) =
                if platformUsesFrameworks platform
                 then (frameworkPaths dflags, cmdlineFrameworks dflags)
                  else ([],[])

          -- Finally do (c),(d),(e)
        ; let cmdline_lib_specs = [ l | Just l <- classified_ld_inputs ]
                               ++ libspecs
                               ++ map Framework frameworks
        ; if null cmdline_lib_specs then return pls
                                    else do

        { mapM_ (preloadLib dflags lib_paths framework_paths) cmdline_lib_specs
        ; maybePutStr dflags "final link ... "
        ; ok <- resolveObjs

        ; if succeeded ok then maybePutStrLn dflags "done"
          else throwGhcExceptionIO (ProgramError "linking extra libraries/objects failed")

        ; return pls
        }}


{- Note [preload packages]

Why do we need to preload packages from the command line?  This is an
explanation copied from #2437:

I tried to implement the suggestion from #3560, thinking it would be
easy, but there are two reasons we link in packages eagerly when they
are mentioned on the command line:

  * So that you can link in extra object files or libraries that
    depend on the packages. e.g. ghc -package foo -lbar where bar is a
    C library that depends on something in foo. So we could link in
    foo eagerly if and only if there are extra C libs or objects to
    link in, but....

  * Haskell code can depend on a C function exported by a package, and
    the normal dependency tracking that TH uses can't know about these
    dependencies. The test ghcilink004 relies on this, for example.

I conclude that we need two -package flags: one that says "this is a
package I want to make available", and one that says "this is a
package I want to link in eagerly". Would that be too complicated for
users?
-}

classifyLdInput :: DynFlags -> FilePath -> IO (Maybe LibrarySpec)
classifyLdInput dflags f
  | isObjectFilename platform f = return (Just (Object f))
  | isDynLibFilename platform f = return (Just (DLLPath f))
  | otherwise          = do
        log_action dflags dflags SevInfo noSrcSpan defaultUserStyle
            (text ("Warning: ignoring unrecognised input `" ++ f ++ "'"))
        return Nothing
    where platform = targetPlatform dflags

preloadLib :: DynFlags -> [String] -> [String] -> LibrarySpec -> IO ()
preloadLib dflags lib_paths framework_paths lib_spec
  = do maybePutStr dflags ("Loading object " ++ showLS lib_spec ++ " ... ")
       case lib_spec of
          Object static_ish
             -> do b <- preload_static lib_paths static_ish
                   maybePutStrLn dflags (if b  then "done"
                                                else "not found")

          Archive static_ish
             -> do b <- preload_static_archive lib_paths static_ish
                   maybePutStrLn dflags (if b  then "done"
                                                else "not found")

          DLL dll_unadorned
             -> do maybe_errstr <- loadDLL (mkSOName platform dll_unadorned)
                   case maybe_errstr of
                      Nothing -> maybePutStrLn dflags "done"
                      Just mm | platformOS platform /= OSDarwin ->
                        preloadFailed mm lib_paths lib_spec
                      Just mm | otherwise -> do
                        -- As a backup, on Darwin, try to also load a .so file
                        -- since (apparently) some things install that way - see
                        -- ticket #8770.
                        err2 <- loadDLL $ ("lib" ++ dll_unadorned) <.> "so"
                        case err2 of
                          Nothing -> maybePutStrLn dflags "done"
                          Just _  -> preloadFailed mm lib_paths lib_spec

          DLLPath dll_path
             -> do maybe_errstr <- loadDLL dll_path
                   case maybe_errstr of
                      Nothing -> maybePutStrLn dflags "done"
                      Just mm -> preloadFailed mm lib_paths lib_spec

          Framework framework ->
              if platformUsesFrameworks (targetPlatform dflags)
              then do maybe_errstr <- loadFramework framework_paths framework
                      case maybe_errstr of
                         Nothing -> maybePutStrLn dflags "done"
                         Just mm -> preloadFailed mm framework_paths lib_spec
              else panic "preloadLib Framework"

  where
    platform = targetPlatform dflags

    preloadFailed :: String -> [String] -> LibrarySpec -> IO ()
    preloadFailed sys_errmsg paths spec
       = do maybePutStr dflags "failed.\n"
            throwGhcExceptionIO $
              CmdLineError (
                    "user specified .o/.so/.DLL could not be loaded ("
                    ++ sys_errmsg ++ ")\nWhilst trying to load:  "
                    ++ showLS spec ++ "\nAdditional directories searched:"
                    ++ (if null paths then " (none)" else
                        (concat (intersperse "\n" (map ("   "++) paths)))))

    -- Not interested in the paths in the static case.
    preload_static _paths name
       = do b <- doesFileExist name
            if not b then return False
                     else do if dynamicGhc
                                 then dynLoadObjs dflags [name]
                                 else loadObj name
                             return True
    preload_static_archive _paths name
       = do b <- doesFileExist name
            if not b then return False
                     else do if dynamicGhc
                                 then panic "Loading archives not supported"
                                 else loadArchive name
                             return True
\end{code}


%************************************************************************
%*                                                                      *
                Link a byte-code expression
%*                                                                      *
%************************************************************************

\begin{code}
-- | Link a single expression, /including/ first linking packages and
-- modules that this expression depends on.
--
-- Raises an IO exception ('ProgramError') if it can't find a compiled
-- version of the dependents to link.
--
linkExpr :: HscEnv -> SrcSpan -> UnlinkedBCO -> IO HValue
linkExpr hsc_env span root_ul_bco
  = do {
     -- Initialise the linker (if it's not been done already)
     let dflags = hsc_dflags hsc_env
   ; initDynLinker dflags

     -- Take lock for the actual work.
   ; modifyPLS $ \pls0 -> do {

     -- Link the packages and modules required
   ; (pls, ok) <- linkDependencies hsc_env pls0 span needed_mods
   ; if failed ok then
        throwGhcExceptionIO (ProgramError "")
     else do {

     -- Link the expression itself
     let ie = itbl_env pls
         ce = closure_env pls

     -- Link the necessary packages and linkables
   ; (_, (root_hval:_)) <- linkSomeBCOs dflags False ie ce [root_ul_bco]
   ; return (pls, root_hval)
   }}}
   where
     free_names = nameSetToList (bcoFreeNames root_ul_bco)

     needed_mods :: [Module]
     needed_mods = [ nameModule n | n <- free_names,
                     isExternalName n,      -- Names from other modules
                     not (isWiredInName n)  -- Exclude wired-in names
                   ]                        -- (see note below)
        -- Exclude wired-in names because we may not have read
        -- their interface files, so getLinkDeps will fail
        -- All wired-in names are in the base package, which we link
        -- by default, so we can safely ignore them here.

dieWith :: DynFlags -> SrcSpan -> MsgDoc -> IO a
dieWith dflags span msg = throwGhcExceptionIO (ProgramError (showSDoc dflags (mkLocMessage SevFatal span msg)))


checkNonStdWay :: DynFlags -> SrcSpan -> IO (Maybe FilePath)
checkNonStdWay dflags srcspan =
  if interpWays == haskellWays
      then return Nothing
    -- see #3604: object files compiled for way "dyn" need to link to the
    -- dynamic packages, so we can't load them into a statically-linked GHCi.
    -- we have to treat "dyn" in the same way as "prof".
    --
    -- In the future when GHCi is dynamically linked we should be able to relax
    -- this, but they we may have to make it possible to load either ordinary
    -- .o files or -dynamic .o files into GHCi (currently that's not possible
    -- because the dynamic objects contain refs to e.g. __stginit_base_Prelude_dyn
    -- whereas we have __stginit_base_Prelude_.
      else if objectSuf dflags == normalObjectSuffix && not (null haskellWays)
      then failNonStd dflags srcspan
      else return $ Just $ if dynamicGhc
                           then "dyn_o"
                           else "o"
    where haskellWays = filter (not . wayRTSOnly) (ways dflags)

normalObjectSuffix :: String
normalObjectSuffix = phaseInputExt StopLn

failNonStd :: DynFlags -> SrcSpan -> IO (Maybe FilePath)
failNonStd dflags srcspan = dieWith dflags srcspan $
  ptext (sLit "Dynamic linking required, but this is a non-standard build (eg. prof).") $$
  ptext (sLit "You need to build the program twice: once the") <+> ghciWay <+> ptext (sLit "way, and then") $$
  ptext (sLit "in the desired way using -osuf to set the object file suffix.")
    where ghciWay = if dynamicGhc
                    then ptext (sLit "dynamic")
                    else ptext (sLit "normal")

getLinkDeps :: HscEnv -> HomePackageTable
            -> PersistentLinkerState
            -> Maybe FilePath                   -- replace object suffices?
            -> SrcSpan                          -- for error messages
            -> [Module]                         -- If you need these
            -> IO ([Linkable], [PackageKey])     -- ... then link these first
-- Fails with an IO exception if it can't find enough files

getLinkDeps hsc_env hpt pls replace_osuf span mods
-- Find all the packages and linkables that a set of modules depends on
 = do {
        -- 1.  Find the dependent home-pkg-modules/packages from each iface
        -- (omitting modules from the interactive package, which is already linked)
      ; (mods_s, pkgs_s) <- follow_deps (filterOut isInteractiveModule mods)
                                        emptyUniqSet emptyUniqSet;

      ; let {
        -- 2.  Exclude ones already linked
        --      Main reason: avoid findModule calls in get_linkable
            mods_needed = mods_s `minusList` linked_mods     ;
            pkgs_needed = pkgs_s `minusList` pkgs_loaded pls ;

            linked_mods = map (moduleName.linkableModule)
                                (objs_loaded pls ++ bcos_loaded pls)  }

        -- 3.  For each dependent module, find its linkable
        --     This will either be in the HPT or (in the case of one-shot
        --     compilation) we may need to use maybe_getFileLinkable
      ; let { osuf = objectSuf dflags }
      ; lnks_needed <- mapM (get_linkable osuf) mods_needed

      ; return (lnks_needed, pkgs_needed) } 
  where
    dflags = hsc_dflags hsc_env
    this_pkg = thisPackage dflags

        -- The ModIface contains the transitive closure of the module dependencies
        -- within the current package, *except* for boot modules: if we encounter
        -- a boot module, we have to find its real interface and discover the
        -- dependencies of that.  Hence we need to traverse the dependency
        -- tree recursively.  See bug #936, testcase ghci/prog007.
    follow_deps :: [Module]             -- modules to follow
                -> UniqSet ModuleName         -- accum. module dependencies
                -> UniqSet PackageKey          -- accum. package dependencies
                -> IO ([ModuleName], [PackageKey]) -- result
    follow_deps []     acc_mods acc_pkgs
        = return (uniqSetToList acc_mods, uniqSetToList acc_pkgs)
    follow_deps (mod:mods) acc_mods acc_pkgs
        = do
          mb_iface <- initIfaceCheck hsc_env $
                        loadInterface msg mod (ImportByUser False)
          iface <- case mb_iface of
                    Maybes.Failed err      -> throwGhcExceptionIO (ProgramError (showSDoc dflags err))
                    Maybes.Succeeded iface -> return iface

          when (mi_boot iface) $ link_boot_mod_error mod

          let
            pkg = modulePackageKey mod
            deps  = mi_deps iface

            pkg_deps = dep_pkgs deps
            (boot_deps, mod_deps) = partitionWith is_boot (dep_mods deps)
                    where is_boot (m,True)  = Left m
                          is_boot (m,False) = Right m

            boot_deps' = filter (not . (`elementOfUniqSet` acc_mods)) boot_deps
            acc_mods'  = addListToUniqSet acc_mods (moduleName mod : mod_deps)
            acc_pkgs'  = addListToUniqSet acc_pkgs $ map fst pkg_deps
          --
          if pkg /= this_pkg
             then follow_deps mods acc_mods (addOneToUniqSet acc_pkgs' pkg)
             else follow_deps (map (mkModule this_pkg) boot_deps' ++ mods)
                              acc_mods' acc_pkgs'
        where
            msg = text "need to link module" <+> ppr mod <+>
                  text "due to use of Template Haskell"


    link_boot_mod_error mod =
        throwGhcExceptionIO (ProgramError (showSDoc dflags (
            text "module" <+> ppr mod <+>
            text "cannot be linked; it is only available as a boot module")))

    no_obj :: Outputable a => a -> IO b
    no_obj mod = dieWith dflags span $
                     ptext (sLit "cannot find object file for module ") <>
                        quotes (ppr mod) $$
                     while_linking_expr

    while_linking_expr = ptext (sLit "while linking an interpreted expression")

        -- This one is a build-system bug

    get_linkable osuf mod_name      -- A home-package module
        | Just mod_info <- lookupUFM hpt mod_name
        = adjust_linkable (Maybes.expectJust "getLinkDeps" (hm_linkable mod_info))
        | otherwise
        = do    -- It's not in the HPT because we are in one shot mode,
                -- so use the Finder to get a ModLocation...
             mb_stuff <- findHomeModule hsc_env mod_name
             case mb_stuff of
                  Found loc mod -> found loc mod
                  _ -> no_obj mod_name
        where
            found loc mod = do {
                -- ...and then find the linkable for it
               mb_lnk <- findObjectLinkableMaybe mod loc ;
               case mb_lnk of {
                  Nothing  -> no_obj mod ;
                  Just lnk -> adjust_linkable lnk
              }}

            adjust_linkable lnk
                | Just new_osuf <- replace_osuf = do
                        new_uls <- mapM (adjust_ul new_osuf)
                                        (linkableUnlinked lnk)
                        return lnk{ linkableUnlinked=new_uls }
                | otherwise =
                        return lnk

            adjust_ul new_osuf (DotO file) = do
                MASSERT(osuf `isSuffixOf` file)
                let file_base = dropTail (length osuf + 1) file
                    new_file = file_base <.> new_osuf
                ok <- doesFileExist new_file
                if (not ok)
                   then dieWith dflags span $
                          ptext (sLit "cannot find normal object file ")
                                <> quotes (text new_file) $$ while_linking_expr
                   else return (DotO new_file)
            adjust_ul _ (DotA fp) = panic ("adjust_ul DotA " ++ show fp)
            adjust_ul _ (DotDLL fp) = panic ("adjust_ul DotDLL " ++ show fp)
            adjust_ul _ l@(BCOs {}) = return l
\end{code}


%************************************************************************
%*                                                                      *
              Loading a Decls statement
%*                                                                      *
%************************************************************************
\begin{code}
linkDecls :: HscEnv -> SrcSpan -> CompiledByteCode -> IO () --[HValue]
linkDecls hsc_env span (ByteCode unlinkedBCOs itblEnv) = do
    -- Initialise the linker (if it's not been done already)
    let dflags = hsc_dflags hsc_env
    initDynLinker dflags

    -- Take lock for the actual work.
    modifyPLS $ \pls0 -> do

    -- Link the packages and modules required
    (pls, ok) <- linkDependencies hsc_env pls0 span needed_mods
    if failed ok
      then throwGhcExceptionIO (ProgramError "")
      else do

    -- Link the expression itself
    let ie = plusNameEnv (itbl_env pls) itblEnv
        ce = closure_env pls

    -- Link the necessary packages and linkables
    (final_gce, _) <- linkSomeBCOs dflags False ie ce unlinkedBCOs
    let pls2 = pls { closure_env = final_gce,
                     itbl_env    = ie }
    return (pls2, ()) --hvals)
  where
    free_names =  concatMap (nameSetToList . bcoFreeNames) unlinkedBCOs

    needed_mods :: [Module]
    needed_mods = [ nameModule n | n <- free_names,
                    isExternalName n,       -- Names from other modules
                    not (isWiredInName n)   -- Exclude wired-in names
                  ]                         -- (see note below)
    -- Exclude wired-in names because we may not have read
    -- their interface files, so getLinkDeps will fail
    -- All wired-in names are in the base package, which we link
    -- by default, so we can safely ignore them here.
\end{code}



%************************************************************************
%*                                                                      *
              Loading a single module
%*                                                                      *
%************************************************************************

\begin{code}
linkModule :: HscEnv -> Module -> IO ()
linkModule hsc_env mod = do
  initDynLinker (hsc_dflags hsc_env)
  modifyPLS_ $ \pls -> do
    (pls', ok) <- linkDependencies hsc_env pls noSrcSpan [mod]
    if (failed ok) then throwGhcExceptionIO (ProgramError "could not link module")
      else return pls'
\end{code}

%************************************************************************
%*                                                                      *
                Link some linkables
        The linkables may consist of a mixture of
        byte-code modules and object modules
%*                                                                      *
%************************************************************************

\begin{code}
linkModules :: DynFlags -> PersistentLinkerState -> [Linkable]
            -> IO (PersistentLinkerState, SuccessFlag)
linkModules dflags pls linkables
  = mask_ $ do  -- don't want to be interrupted by ^C in here

        let (objs, bcos) = partition isObjectLinkable
                              (concatMap partitionLinkable linkables)

                -- Load objects first; they can't depend on BCOs
        (pls1, ok_flag) <- dynLinkObjs dflags pls objs

        if failed ok_flag then
                return (pls1, Failed)
          else do
                pls2 <- dynLinkBCOs dflags pls1 bcos
                return (pls2, Succeeded)


-- HACK to support f-x-dynamic in the interpreter; no other purpose
partitionLinkable :: Linkable -> [Linkable]
partitionLinkable li
   = let li_uls = linkableUnlinked li
         li_uls_obj = filter isObject li_uls
         li_uls_bco = filter isInterpretable li_uls
     in
         case (li_uls_obj, li_uls_bco) of
            (_:_, _:_) -> [li {linkableUnlinked=li_uls_obj},
                           li {linkableUnlinked=li_uls_bco}]
            _ -> [li]

findModuleLinkable_maybe :: [Linkable] -> Module -> Maybe Linkable
findModuleLinkable_maybe lis mod
   = case [LM time nm us | LM time nm us <- lis, nm == mod] of
        []   -> Nothing
        [li] -> Just li
        _    -> pprPanic "findModuleLinkable" (ppr mod)

linkableInSet :: Linkable -> [Linkable] -> Bool
linkableInSet l objs_loaded =
  case findModuleLinkable_maybe objs_loaded (linkableModule l) of
        Nothing -> False
        Just m  -> linkableTime l == linkableTime m
\end{code}


%************************************************************************
%*                                                                      *
\subsection{The object-code linker}
%*                                                                      *
%************************************************************************

\begin{code}
dynLinkObjs :: DynFlags -> PersistentLinkerState -> [Linkable]
            -> IO (PersistentLinkerState, SuccessFlag)
dynLinkObjs dflags pls objs = do
        -- Load the object files and link them
        let (objs_loaded', new_objs) = rmDupLinkables (objs_loaded pls) objs
            pls1                     = pls { objs_loaded = objs_loaded' }
            unlinkeds                = concatMap linkableUnlinked new_objs
            wanted_objs              = map nameOfObject unlinkeds

        if dynamicGhc
            then do dynLoadObjs dflags wanted_objs
                    return (pls1, Succeeded)
            else do mapM_ loadObj wanted_objs

                    -- Link them all together
                    ok <- resolveObjs

                    -- If resolving failed, unload all our
                    -- object modules and carry on
                    if succeeded ok then do
                            return (pls1, Succeeded)
                      else do
                            pls2 <- unload_wkr dflags [] pls1
                            return (pls2, Failed)

dynLoadObjs :: DynFlags -> [FilePath] -> IO ()
dynLoadObjs _      []   = return ()
dynLoadObjs dflags objs = do
    let platform = targetPlatform dflags
    soFile <- newTempName dflags (soExt platform)
    let -- When running TH for a non-dynamic way, we still need to make
        -- -l flags to link against the dynamic libraries, so we turn
        -- Opt_Static off
        dflags1 = gopt_unset dflags Opt_Static
        dflags2 = dflags1 {
                      -- We don't want to link the ldInputs in; we'll
                      -- be calling dynLoadObjs with any objects that
                      -- need to be linked.
                      ldInputs = [],
                      -- Even if we're e.g. profiling, we still want
                      -- the vanilla dynamic libraries, so we set the
                      -- ways / build tag to be just WayDyn.
                      ways = [WayDyn],
                      buildTag = mkBuildTag [WayDyn],
                      outputFile = Just soFile
                  }
    linkDynLib dflags2 objs []
    consIORef (filesToNotIntermediateClean dflags) soFile
    m <- loadDLL soFile
    case m of
        Nothing -> return ()
        Just err -> panic ("Loading temp shared object failed: " ++ err)

rmDupLinkables :: [Linkable]    -- Already loaded
               -> [Linkable]    -- New linkables
               -> ([Linkable],  -- New loaded set (including new ones)
                   [Linkable])  -- New linkables (excluding dups)
rmDupLinkables already ls
  = go already [] ls
  where
    go already extras [] = (already, extras)
    go already extras (l:ls)
        | linkableInSet l already = go already     extras     ls
        | otherwise               = go (l:already) (l:extras) ls
\end{code}

%************************************************************************
%*                                                                      *
\subsection{The byte-code linker}
%*                                                                      *
%************************************************************************

\begin{code}
dynLinkBCOs :: DynFlags -> PersistentLinkerState -> [Linkable]
            -> IO PersistentLinkerState
dynLinkBCOs dflags pls bcos = do

        let (bcos_loaded', new_bcos) = rmDupLinkables (bcos_loaded pls) bcos
            pls1                     = pls { bcos_loaded = bcos_loaded' }
            unlinkeds :: [Unlinked]
            unlinkeds                = concatMap linkableUnlinked new_bcos

            cbcs :: [CompiledByteCode]
            cbcs      = map byteCodeOfObject unlinkeds


            ul_bcos    = [b | ByteCode bs _  <- cbcs, b <- bs]
            ies        = [ie | ByteCode _ ie <- cbcs]
            gce       = closure_env pls
            final_ie  = foldr plusNameEnv (itbl_env pls) ies

        (final_gce, _linked_bcos) <- linkSomeBCOs dflags True final_ie gce ul_bcos
                -- XXX What happens to these linked_bcos?

        let pls2 = pls1 { closure_env = final_gce,
                          itbl_env    = final_ie }

        return pls2

-- Link a bunch of BCOs and return them + updated closure env.
linkSomeBCOs :: DynFlags
             -> Bool    -- False <=> add _all_ BCOs to returned closure env
                        -- True  <=> add only toplevel BCOs to closure env
             -> ItblEnv
             -> ClosureEnv
             -> [UnlinkedBCO]
             -> IO (ClosureEnv, [HValue])
                        -- The returned HValues are associated 1-1 with
                        -- the incoming unlinked BCOs.  Each gives the
                        -- value of the corresponding unlinked BCO

linkSomeBCOs dflags toplevs_only ie ce_in ul_bcos
   = do let nms = map unlinkedBCOName ul_bcos
        hvals <- fixIO
                    ( \ hvs -> let ce_out = extendClosureEnv ce_in (zipLazy nms hvs)
                               in  mapM (linkBCO dflags ie ce_out) ul_bcos )
        let ce_all_additions = zip nms hvals
            ce_top_additions = filter (isExternalName.fst) ce_all_additions
            ce_additions     = if toplevs_only then ce_top_additions
                                               else ce_all_additions
            ce_out = -- make sure we're not inserting duplicate names into the
                     -- closure environment, which leads to trouble.
                     ASSERT(all (not . (`elemNameEnv` ce_in)) (map fst ce_additions))
                     extendClosureEnv ce_in ce_additions
        return (ce_out, hvals)

\end{code}


%************************************************************************
%*                                                                      *
                Unload some object modules
%*                                                                      *
%************************************************************************

\begin{code}
-- ---------------------------------------------------------------------------
-- | Unloading old objects ready for a new compilation sweep.
--
-- The compilation manager provides us with a list of linkables that it
-- considers \"stable\", i.e. won't be recompiled this time around.  For
-- each of the modules current linked in memory,
--
--   * if the linkable is stable (and it's the same one -- the user may have
--     recompiled the module on the side), we keep it,
--
--   * otherwise, we unload it.
--
--   * we also implicitly unload all temporary bindings at this point.
--
unload :: DynFlags
       -> [Linkable] -- ^ The linkables to *keep*.
       -> IO ()
unload dflags linkables
  = mask_ $ do -- mask, so we're safe from Ctrl-C in here

        -- Initialise the linker (if it's not been done already)
        initDynLinker dflags

        new_pls
            <- modifyPLS $ \pls -> do
                 pls1 <- unload_wkr dflags linkables pls
                 return (pls1, pls1)

        debugTraceMsg dflags 3 (text "unload: retaining objs" <+> ppr (objs_loaded new_pls))
        debugTraceMsg dflags 3 (text "unload: retaining bcos" <+> ppr (bcos_loaded new_pls))
        return ()

unload_wkr :: DynFlags
           -> [Linkable]                -- stable linkables
           -> PersistentLinkerState
           -> IO PersistentLinkerState
-- Does the core unload business
-- (the wrapper blocks exceptions and deals with the PLS get and put)

unload_wkr _ linkables pls
  = do  let (objs_to_keep, bcos_to_keep) = partition isObjectLinkable linkables

        objs_loaded' <- filterM (maybeUnload objs_to_keep) (objs_loaded pls)
        bcos_loaded' <- filterM (maybeUnload bcos_to_keep) (bcos_loaded pls)

        let bcos_retained = map linkableModule bcos_loaded'
            itbl_env'     = filterNameMap bcos_retained (itbl_env pls)
            closure_env'  = filterNameMap bcos_retained (closure_env pls)
            new_pls = pls { itbl_env = itbl_env',
                            closure_env = closure_env',
                            bcos_loaded = bcos_loaded',
                            objs_loaded = objs_loaded' }

        return new_pls
  where
    maybeUnload :: [Linkable] -> Linkable -> IO Bool
    maybeUnload keep_linkables lnk
      | linkableInSet lnk keep_linkables = return True
      -- We don't do any cleanup when linking objects with the dynamic linker.
      -- Doing so introduces extra complexity for not much benefit.
      | dynamicGhc = return False
      | otherwise
      = do mapM_ unloadObj [f | DotO f <- linkableUnlinked lnk]
                -- The components of a BCO linkable may contain
                -- dot-o files.  Which is very confusing.
                --
                -- But the BCO parts can be unlinked just by
                -- letting go of them (plus of course depopulating
                -- the symbol table which is done in the main body)
           return False
\end{code}


%************************************************************************
%*                                                                      *
                Loading packages
%*                                                                      *
%************************************************************************


\begin{code}
data LibrarySpec
   = Object FilePath    -- Full path name of a .o file, including trailing .o
                        -- For dynamic objects only, try to find the object
                        -- file in all the directories specified in
                        -- v_Library_paths before giving up.

   | Archive FilePath   -- Full path name of a .a file, including trailing .a

   | DLL String         -- "Unadorned" name of a .DLL/.so
                        --  e.g.    On unix     "qt"  denotes "libqt.so"
                        --          On WinDoze  "burble"  denotes "burble.DLL"
                        --  loadDLL is platform-specific and adds the lib/.so/.DLL
                        --  suffixes platform-dependently

   | DLLPath FilePath   -- Absolute or relative pathname to a dynamic library
                        -- (ends with .dll or .so).

   | Framework String   -- Only used for darwin, but does no harm

-- If this package is already part of the GHCi binary, we'll already
-- have the right DLLs for this package loaded, so don't try to
-- load them again.
--
-- But on Win32 we must load them 'again'; doing so is a harmless no-op
-- as far as the loader is concerned, but it does initialise the list
-- of DLL handles that rts/Linker.c maintains, and that in turn is
-- used by lookupSymbol.  So we must call addDLL for each library
-- just to get the DLL handle into the list.
partOfGHCi :: [PackageName]
partOfGHCi
 | isWindowsHost || isDarwinHost = []
 | otherwise = map (PackageName . mkFastString)
                   ["base", "template-haskell", "editline"]

showLS :: LibrarySpec -> String
showLS (Object nm)    = "(static) " ++ nm
showLS (Archive nm)   = "(static archive) " ++ nm
showLS (DLL nm)       = "(dynamic) " ++ nm
showLS (DLLPath nm)   = "(dynamic) " ++ nm
showLS (Framework nm) = "(framework) " ++ nm

-- | Link exactly the specified packages, and their dependents (unless of
-- course they are already linked).  The dependents are linked
-- automatically, and it doesn't matter what order you specify the input
-- packages.
--
linkPackages :: DynFlags -> [PackageKey] -> IO ()
-- NOTE: in fact, since each module tracks all the packages it depends on,
--       we don't really need to use the package-config dependencies.
--
-- However we do need the package-config stuff (to find aux libs etc),
-- and following them lets us load libraries in the right order, which
-- perhaps makes the error message a bit more localised if we get a link
-- failure.  So the dependency walking code is still here.

linkPackages dflags new_pkgs = do
  -- It's probably not safe to try to load packages concurrently, so we take
  -- a lock.
  initDynLinker dflags
  modifyPLS_ $ \pls -> do
    linkPackages' dflags new_pkgs pls

linkPackages' :: DynFlags -> [PackageKey] -> PersistentLinkerState
             -> IO PersistentLinkerState
linkPackages' dflags new_pks pls = do
    pkgs' <- link (pkgs_loaded pls) new_pks
    return $! pls { pkgs_loaded = pkgs' }
  where
     link :: [PackageKey] -> [PackageKey] -> IO [PackageKey]
     link pkgs new_pkgs =
         foldM link_one pkgs new_pkgs

     link_one pkgs new_pkg
        | new_pkg `elem` pkgs   -- Already linked
        = return pkgs

        | Just pkg_cfg <- lookupPackage dflags new_pkg
        = do {  -- Link dependents first
               pkgs' <- link pkgs [ resolveInstalledPackageId dflags ipid
                                  | ipid <- depends pkg_cfg ]
                -- Now link the package itself
             ; linkPackage dflags pkg_cfg
             ; return (new_pkg : pkgs') }

        | otherwise
        = throwGhcExceptionIO (CmdLineError ("unknown package: " ++ packageKeyString new_pkg))


linkPackage :: DynFlags -> PackageConfig -> IO ()
linkPackage dflags pkg
   = do
        let platform  = targetPlatform dflags
            dirs      =  Packages.libraryDirs pkg

        let hs_libs   =  Packages.hsLibraries pkg
            -- The FFI GHCi import lib isn't needed as
            -- compiler/ghci/Linker.lhs + rts/Linker.c link the
            -- interpreted references to FFI to the compiled FFI.
            -- We therefore filter it out so that we don't get
            -- duplicate symbol errors.
            hs_libs'  =  filter ("HSffi" /=) hs_libs

        -- Because of slight differences between the GHC dynamic linker and
        -- the native system linker some packages have to link with a
        -- different list of libraries when using GHCi. Examples include: libs
        -- that are actually gnu ld scripts, and the possability that the .a
        -- libs do not exactly match the .so/.dll equivalents. So if the
        -- package file provides an "extra-ghci-libraries" field then we use
        -- that instead of the "extra-libraries" field.
            extra_libs =
                      (if null (Packages.extraGHCiLibraries pkg)
                            then Packages.extraLibraries pkg
                            else Packages.extraGHCiLibraries pkg)
                      ++ [ lib | '-':'l':lib <- Packages.ldOptions pkg ]

        hs_classifieds    <- mapM (locateLib dflags True  dirs) hs_libs'
        extra_classifieds <- mapM (locateLib dflags False dirs) extra_libs
        let classifieds = hs_classifieds ++ extra_classifieds

        -- Complication: all the .so's must be loaded before any of the .o's.
        let known_dlls = [ dll  | DLLPath dll    <- classifieds ]
            dlls       = [ dll  | DLL dll        <- classifieds ]
            objs       = [ obj  | Object obj     <- classifieds ]
            archs      = [ arch | Archive arch   <- classifieds ]

        maybePutStr dflags
            ("Loading package " ++ sourcePackageIdString pkg ++ " ... ")

        -- See comments with partOfGHCi
        when (packageName pkg `notElem` partOfGHCi) $ do
            loadFrameworks platform pkg
            mapM_ load_dyn (known_dlls ++ map (mkSOName platform) dlls)

        -- After loading all the DLLs, we can load the static objects.
        -- Ordering isn't important here, because we do one final link
        -- step to resolve everything.
        mapM_ loadObj objs
        mapM_ loadArchive archs

        maybePutStr dflags "linking ... "
        ok <- resolveObjs
        if succeeded ok
           then maybePutStrLn dflags "done."
           else let errmsg = "unable to load package `"
                             ++ sourcePackageIdString pkg ++ "'"
                 in throwGhcExceptionIO (InstallationError errmsg)

-- we have already searched the filesystem; the strings passed to load_dyn
-- can be passed directly to loadDLL.  They are either fully-qualified
-- ("/usr/lib/libfoo.so"), or unqualified ("libfoo.so").  In the latter case,
-- loadDLL is going to search the system paths to find the library.
--
load_dyn :: FilePath -> IO ()
load_dyn dll = do r <- loadDLL dll
                  case r of
                    Nothing  -> return ()
                    Just err -> throwGhcExceptionIO (CmdLineError ("can't load .so/.DLL for: "
                                                              ++ dll ++ " (" ++ err ++ ")" ))

loadFrameworks :: Platform -> PackageConfig -> IO ()
loadFrameworks platform pkg
    = if platformUsesFrameworks platform
      then mapM_ load frameworks
      else return ()
  where
    fw_dirs    = Packages.frameworkDirs pkg
    frameworks = Packages.frameworks pkg

    load fw = do  r <- loadFramework fw_dirs fw
                  case r of
                    Nothing  -> return ()
                    Just err -> throwGhcExceptionIO (CmdLineError ("can't load framework: "
                                                        ++ fw ++ " (" ++ err ++ ")" ))

-- Try to find an object file for a given library in the given paths.
-- If it isn't present, we assume that addDLL in the RTS can find it,
-- which generally means that it should be a dynamic library in the
-- standard system search path.

locateLib :: DynFlags -> Bool -> [FilePath] -> String -> IO LibrarySpec
locateLib dflags is_hs dirs lib
  | not is_hs
    -- For non-Haskell libraries (e.g. gmp, iconv):
    --   first look in library-dirs for a dynamic library (libfoo.so)
    --   then  look in library-dirs for a static library (libfoo.a)
    --   then  try "gcc --print-file-name" to search gcc's search path
    --       for a dynamic library (#5289)
    --   otherwise, assume loadDLL can find it
    --
  = findDll `orElse` findArchive `orElse` tryGcc `orElse` assumeDll

  | not dynamicGhc
    -- When the GHC package was not compiled as dynamic library
    -- (=DYNAMIC not set), we search for .o libraries or, if they
    -- don't exist, .a libraries.
  = findObject `orElse` findArchive `orElse` assumeDll

  | otherwise
    -- When the GHC package was compiled as dynamic library (=DYNAMIC set),
    -- we search for .so libraries first.
  = findHSDll `orElse` findDynObject `orElse` assumeDll
   where
     mk_obj_path      dir = dir </> (lib <.> "o")
     mk_dyn_obj_path  dir = dir </> (lib <.> "dyn_o")
     mk_arch_path     dir = dir </> ("lib" ++ lib <.> "a")

     hs_dyn_lib_name = lib ++ "-ghc" ++ cProjectVersion
     mk_hs_dyn_lib_path dir = dir </> mkHsSOName platform hs_dyn_lib_name

     so_name = mkSOName platform lib
     mk_dyn_lib_path dir = case (arch, os) of
                             (ArchX86_64, OSSolaris2) -> dir </> ("64/" ++ so_name)
                             _ -> dir </> so_name

     findObject     = liftM (fmap Object)  $ findFile mk_obj_path        dirs
     findDynObject  = liftM (fmap Object)  $ findFile mk_dyn_obj_path    dirs
     findArchive    = liftM (fmap Archive) $ findFile mk_arch_path       dirs
     findHSDll      = liftM (fmap DLLPath) $ findFile mk_hs_dyn_lib_path dirs
     findDll        = liftM (fmap DLLPath) $ findFile mk_dyn_lib_path    dirs
     tryGcc         = liftM (fmap DLLPath) $ searchForLibUsingGcc dflags so_name dirs

     assumeDll   = return (DLL lib)
     infixr `orElse`
     f `orElse` g = do m <- f
                       case m of
                           Just x -> return x
                           Nothing -> g

     platform = targetPlatform dflags
     arch = platformArch platform
     os = platformOS platform

searchForLibUsingGcc :: DynFlags -> String -> [FilePath] -> IO (Maybe FilePath)
searchForLibUsingGcc dflags so dirs = do
   str <- askCc dflags (map (FileOption "-L") dirs
                          ++ [Option "--print-file-name", Option so])
   let file = case lines str of
                []  -> ""
                l:_ -> l
   if (file == so)
      then return Nothing
      else return (Just file)

-- ----------------------------------------------------------------------------
-- Loading a dynamic library (dlopen()-ish on Unix, LoadLibrary-ish on Win32)

-- Darwin / MacOS X only: load a framework
-- a framework is a dynamic library packaged inside a directory of the same
-- name. They are searched for in different paths than normal libraries.
loadFramework :: [FilePath] -> FilePath -> IO (Maybe String)
loadFramework extraPaths rootname
   = do { either_dir <- tryIO getHomeDirectory
        ; let homeFrameworkPath = case either_dir of
                                  Left _ -> []
                                  Right dir -> [dir ++ "/Library/Frameworks"]
              ps = extraPaths ++ homeFrameworkPath ++ defaultFrameworkPaths
        ; mb_fwk <- findFile mk_fwk ps
        ; case mb_fwk of
            Just fwk_path -> loadDLL fwk_path
            Nothing       -> return (Just "not found") }
                -- Tried all our known library paths, but dlopen()
                -- has no built-in paths for frameworks: give up
   where
     mk_fwk dir = dir </> (rootname ++ ".framework/" ++ rootname)
        -- sorry for the hardcoded paths, I hope they won't change anytime soon:
     defaultFrameworkPaths = ["/Library/Frameworks", "/System/Library/Frameworks"]
\end{code}

%************************************************************************
%*                                                                      *
                Helper functions
%*                                                                      *
%************************************************************************

\begin{code}
findFile :: (FilePath -> FilePath)      -- Maps a directory path to a file path
         -> [FilePath]                  -- Directories to look in
         -> IO (Maybe FilePath)         -- The first file path to match
findFile _            [] = return Nothing
findFile mk_file_path (dir : dirs)
  = do let file_path = mk_file_path dir
       b <- doesFileExist file_path
       if b then return (Just file_path)
            else findFile mk_file_path dirs
\end{code}

\begin{code}
maybePutStr :: DynFlags -> String -> IO ()
maybePutStr dflags s
    = when (verbosity dflags > 0) $
          do let act = log_action dflags
             act dflags SevInteractive noSrcSpan defaultUserStyle (text s)

maybePutStrLn :: DynFlags -> String -> IO ()
maybePutStrLn dflags s = maybePutStr dflags (s ++ "\n")
\end{code}

%************************************************************************
%*                                                                      *
        Tunneling global variables into new instance of GHC library
%*                                                                      *
%************************************************************************

\begin{code}
saveLinkerGlobals :: IO (MVar PersistentLinkerState, Bool)
saveLinkerGlobals = liftM2 (,) (readIORef v_PersistentLinkerState) (readIORef v_InitLinkerDone)

restoreLinkerGlobals :: (MVar PersistentLinkerState, Bool) -> IO ()
restoreLinkerGlobals (pls, ild) = do
    writeIORef v_PersistentLinkerState pls
    writeIORef v_InitLinkerDone ild
\end{code}