Skip to content

Commit

Permalink
Cosmetics
Browse files Browse the repository at this point in the history
  • Loading branch information
nojb committed Jul 25, 2018
1 parent d91aa81 commit 0defbbe
Show file tree
Hide file tree
Showing 20 changed files with 461 additions and 460 deletions.
30 changes: 15 additions & 15 deletions asmcomp/asmgen.ml
Expand Up @@ -148,21 +148,21 @@ let compile_unit _output_prefix asm_filename keep_asm
obj_filename gen =
let create_asm = keep_asm || not !Emitaux.binary_backend_available in
Emitaux.create_asm_file := create_asm;
Misc.try_finally begin fun () ->
if create_asm then Emitaux.output_channel := open_out asm_filename;
Misc.try_finally gen
~always:(fun () ->
if create_asm then close_out !Emitaux.output_channel)
~exceptionally:(fun () ->
if create_asm && not keep_asm then remove_file asm_filename);
let assemble_result =
Profile.record "assemble"
(Proc.assemble_file asm_filename) obj_filename
in
if assemble_result <> 0
then raise(Error(Assembler_error asm_filename));
if create_asm && not keep_asm then remove_file asm_filename
end
Misc.try_finally (fun () ->
if create_asm then Emitaux.output_channel := open_out asm_filename;
Misc.try_finally gen
~always:(fun () ->
if create_asm then close_out !Emitaux.output_channel)
~exceptionally:(fun () ->
if create_asm && not keep_asm then remove_file asm_filename);
let assemble_result =
Profile.record "assemble"
(Proc.assemble_file asm_filename) obj_filename
in
if assemble_result <> 0
then raise(Error(Assembler_error asm_filename));
if create_asm && not keep_asm then remove_file asm_filename
)
~exceptionally:(fun () -> remove_file obj_filename)

let set_export_info (ulambda, prealloc, structured_constants, export) =
Expand Down
32 changes: 16 additions & 16 deletions asmcomp/asmlibrarian.ml
Expand Up @@ -49,22 +49,22 @@ let read_info name =
let create_archive file_list lib_name =
let archive_name = Filename.remove_extension lib_name ^ ext_lib in
let outchan = open_out_bin lib_name in
Misc.try_finally begin fun () ->
output_string outchan cmxa_magic_number;
let (objfile_list, descr_list) =
List.split (List.map read_info file_list) in
List.iter2
(fun file_name (unit, crc) ->
Asmlink.check_consistency file_name unit crc)
file_list descr_list;
let infos =
{ lib_units = descr_list;
lib_ccobjs = !Clflags.ccobjs;
lib_ccopts = !Clflags.all_ccopts } in
output_value outchan infos;
if Ccomp.create_archive archive_name objfile_list <> 0
then raise(Error(Archiver_error archive_name));
end
Misc.try_finally (fun () ->
output_string outchan cmxa_magic_number;
let (objfile_list, descr_list) =
List.split (List.map read_info file_list) in
List.iter2
(fun file_name (unit, crc) ->
Asmlink.check_consistency file_name unit crc)
file_list descr_list;
let infos =
{ lib_units = descr_list;
lib_ccobjs = !Clflags.ccobjs;
lib_ccopts = !Clflags.all_ccopts } in
output_value outchan infos;
if Ccomp.create_archive archive_name objfile_list <> 0
then raise(Error(Archiver_error archive_name));
)
~always:(fun () -> close_out outchan)
~exceptionally:(fun () ->
remove_file lib_name;
Expand Down
4 changes: 2 additions & 2 deletions asmcomp/asmlink.ml
Expand Up @@ -353,8 +353,8 @@ let link ppf objfiles output_name =
(fun () -> make_startup_file ppf units_tolink);
Misc.try_finally
(fun () ->
call_linker (List.map object_file_name objfiles)
startup_obj output_name)
call_linker (List.map object_file_name objfiles)
startup_obj output_name)
~always:(fun () -> remove_file startup_obj)
)

Expand Down
12 changes: 6 additions & 6 deletions asmcomp/asmpackager.ml
Expand Up @@ -248,12 +248,12 @@ let package_files ppf initial_env files targetcmx ~backend =
Location.input_name := targetcmx;
(* Set the name of the current compunit *)
Compilenv.reset ?packname:!Clflags.for_package targetname;
Misc.try_finally begin fun () ->
let coercion =
Typemod.package_units initial_env files targetcmi targetname in
package_object_files ppf files targetcmx targetobj targetname coercion
~backend
end
Misc.try_finally (fun () ->
let coercion =
Typemod.package_units initial_env files targetcmi targetname in
package_object_files ppf files targetcmx targetobj targetname coercion
~backend
)
~exceptionally:(fun () -> remove_file targetcmx; remove_file targetobj)

(* Error report *)
Expand Down
38 changes: 19 additions & 19 deletions bytecomp/bytelibrarian.ml
Expand Up @@ -90,25 +90,25 @@ let copy_object_file oc name =

let create_archive file_list lib_name =
let outchan = open_out_bin lib_name in
Misc.try_finally begin fun () ->
output_string outchan cma_magic_number;
let ofs_pos_toc = pos_out outchan in
output_binary_int outchan 0;
let units =
List.flatten(List.map (copy_object_file outchan) file_list) in
let toc =
{ lib_units = units;
lib_custom = !Clflags.custom_runtime;
lib_ccobjs = !Clflags.ccobjs @ !lib_ccobjs;
lib_ccopts = !Clflags.all_ccopts @ !lib_ccopts;
lib_dllibs = !Clflags.dllibs @ !lib_dllibs } in
let pos_toc = pos_out outchan in
Emitcode.marshal_to_channel_with_possibly_32bit_compat
~filename:lib_name ~kind:"bytecode library"
outchan toc;
seek_out outchan ofs_pos_toc;
output_binary_int outchan pos_toc;
end
Misc.try_finally (fun () ->
output_string outchan cma_magic_number;
let ofs_pos_toc = pos_out outchan in
output_binary_int outchan 0;
let units =
List.flatten(List.map (copy_object_file outchan) file_list) in
let toc =
{ lib_units = units;
lib_custom = !Clflags.custom_runtime;
lib_ccobjs = !Clflags.ccobjs @ !lib_ccobjs;
lib_ccopts = !Clflags.all_ccopts @ !lib_ccopts;
lib_dllibs = !Clflags.dllibs @ !lib_dllibs } in
let pos_toc = pos_out outchan in
Emitcode.marshal_to_channel_with_possibly_32bit_compat
~filename:lib_name ~kind:"bytecode library"
outchan toc;
seek_out outchan ofs_pos_toc;
output_binary_int outchan pos_toc;
)
~always:(fun () -> close_out outchan)
~exceptionally:(fun () -> remove_file lib_name)

Expand Down

0 comments on commit 0defbbe

Please sign in to comment.