~ubuntu-branches/debian/squeeze/erlang/squeeze

« back to all changes in this revision

Viewing changes to lib/kernel/src/hipe_unified_loader.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2010-03-09 17:34:57 UTC
  • mfrom: (10.1.2 sid)
  • Revision ID: james.westby@ubuntu.com-20100309173457-4yd6hlcb2osfhx31
Tags: 1:13.b.4-dfsg-3
Manpages in section 1 are needed even if only arch-dependent packages are
built. So, re-enabled them.

Show diffs side-by-side

added added

removed removed

Lines of Context:
103
103
      case code:get_chunk(Bin, ChunkTag) of
104
104
        undefined -> no_native;
105
105
        NativeCode when is_binary(NativeCode) ->
106
 
          OldReferencesToPatch = patch_to_emu_step1(Mod),
107
 
          case load_module(Mod, NativeCode, Bin, OldReferencesToPatch) of
108
 
            bad_crc -> no_native;
109
 
            Result -> Result
 
106
         erlang:system_flag(multi_scheduling, block),
 
107
         try
 
108
           OldReferencesToPatch = patch_to_emu_step1(Mod),
 
109
           case load_module(Mod, NativeCode, Bin, OldReferencesToPatch) of
 
110
             bad_crc -> no_native;
 
111
             Result -> Result
 
112
           end
 
113
         after
 
114
           erlang:system_flag(multi_scheduling, unblock)
110
115
          end
111
116
      end
112
117
  catch
121
126
 
122
127
post_beam_load(Mod) when is_atom(Mod) ->
123
128
  Architecture = erlang:system_info(hipe_architecture),
124
 
  try chunk_name(Architecture) of _ChunkTag -> patch_to_emu(Mod)
125
 
  catch _:_ -> ok
 
129
  try chunk_name(Architecture) of
 
130
    _ChunkTag ->
 
131
      erlang:system_flag(multi_scheduling, block),
 
132
      try
 
133
       patch_to_emu(Mod)
 
134
      after
 
135
       erlang:system_flag(multi_scheduling, unblock)
 
136
      end
 
137
  catch
 
138
    _:_ ->
 
139
      ok
126
140
  end.
127
141
 
128
142
%%========================================================================
141
155
-spec load_module(Mod, binary(), _) -> 'bad_crc' | {'module',Mod}
142
156
                                        when is_subtype(Mod,atom()).
143
157
load_module(Mod, Bin, Beam) ->
 
158
  erlang:system_flag(multi_scheduling, block),
 
159
  try
 
160
    load_module_nosmp(Mod, Bin, Beam)
 
161
  after
 
162
    erlang:system_flag(multi_scheduling, unblock)
 
163
  end.
 
164
 
 
165
load_module_nosmp(Mod, Bin, Beam) ->
144
166
  load_module(Mod, Bin, Beam, []).
145
167
 
146
168
load_module(Mod, Bin, Beam, OldReferencesToPatch) ->
154
176
-spec load(Mod, binary()) -> 'bad_crc' | {'module',Mod}
155
177
                              when is_subtype(Mod,atom()).
156
178
load(Mod, Bin) ->
 
179
  erlang:system_flag(multi_scheduling, block),
 
180
  try
 
181
    load_nosmp(Mod, Bin)
 
182
  after
 
183
    erlang:system_flag(multi_scheduling, unblock)
 
184
  end.
 
185
 
 
186
load_nosmp(Mod, Bin) ->
157
187
  ?debug_msg("********* Loading funs in module ~w *********\n",[Mod]),
158
188
  %% Loading just some functions in a module; patch closures separately.
159
189
  put(hipe_patch_closures, true),