ocamltest: take parsing of response files out of environments module

This commit is a follow-up to 123334881a.

Its purpose is to make the environments module abstract again,
by moving the parsing mechanism in its own module.
Consequently, the environments module can be linked earlier again (as
was the case before the commit mentionned above) and can thus be
used in other modules.
master
Sébastien Hinderer 2019-06-05 16:17:29 +02:00
parent b1848d3a27
commit 47c887584d
7 changed files with 81 additions and 32 deletions

View File

@ -36,6 +36,7 @@ actions_helpers.cmo : \
run_command.cmi \
result.cmi \
ocamltest_stdlib.cmi \
modifier_parser.cmi \
filecompare.cmi \
environments.cmi \
builtin_variables.cmi \
@ -46,6 +47,7 @@ actions_helpers.cmx : \
run_command.cmx \
result.cmx \
ocamltest_stdlib.cmx \
modifier_parser.cmx \
filecompare.cmx \
environments.cmx \
builtin_variables.cmx \
@ -86,12 +88,10 @@ builtin_variables.cmi : \
variables.cmi
environments.cmo : \
variables.cmi \
tsl_lexer.cmi \
ocamltest_stdlib.cmi \
environments.cmi
environments.cmx : \
variables.cmx \
tsl_lexer.cmx \
ocamltest_stdlib.cmx \
environments.cmi
environments.cmi : \
@ -132,6 +132,20 @@ main.cmx : \
actions.cmx \
main.cmi
main.cmi :
modifier_parser.cmo : \
variables.cmi \
tsl_lexer.cmi \
ocamltest_stdlib.cmi \
environments.cmi \
modifier_parser.cmi
modifier_parser.cmx : \
variables.cmx \
tsl_lexer.cmx \
ocamltest_stdlib.cmx \
environments.cmx \
modifier_parser.cmi
modifier_parser.cmi : \
environments.cmi
ocaml_actions.cmo : \
result.cmi \
ocamltest_stdlib.cmi \

View File

@ -96,13 +96,14 @@ core := \
run_command.mli run_command.ml \
filecompare.mli filecompare.ml \
variables.mli variables.ml \
environments.mli environments.ml \
result.mli result.ml \
actions.mli actions.ml \
tests.mli tests.ml \
tsl_ast.mli tsl_ast.ml \
tsl_parser.mly \
tsl_lexer.mli tsl_lexer.mll \
environments.mli environments.ml \
modifier_parser.mli modifier_parser.ml \
tsl_semantics.mli tsl_semantics.ml \
builtin_variables.mli builtin_variables.ml \
actions_helpers.mli actions_helpers.ml \

View File

@ -205,7 +205,7 @@ let run_script log env =
log scriptenv in
let final_value =
if Result.is_pass result then begin
match Environments.modifiers_of_file response_file with
match Modifier_parser.modifiers_of_file response_file with
| modifiers ->
let modified_env = Environments.apply_modifiers newenv modifiers in
(result, modified_env)
@ -248,7 +248,7 @@ let run_hook hook_name log input_env =
} in let exit_status = run settings in
let final_value = match exit_status with
| 0 ->
begin match Environments.modifiers_of_file response_file with
begin match Modifier_parser.modifiers_of_file response_file with
| modifiers ->
let modified_env = Environments.apply_modifiers hookenv modifiers in
(Result.pass, modified_env)

View File

@ -142,26 +142,3 @@ let rec apply_modifier environment = function
| Remove variable -> remove variable environment
and apply_modifiers environment modifiers =
List.fold_left apply_modifier environment modifiers
let modifier_of_string str =
let lexbuf = Lexing.from_string str in
let variable_name, result = Tsl_lexer.modifier lexbuf in
let variable =
match Variables.find_variable variable_name with
| None -> raise (Variables.No_such_variable variable_name)
| Some variable -> variable
in
match result with
| `Remove -> Remove variable
| `Add value -> Add (variable, value)
| `Append value -> Append (variable, value)
let modifiers_of_file filename =
let ic = open_in filename in
let rec modifiers_of_lines acc = match input_line_opt ic with
| None -> acc
| Some line ->
modifiers_of_lines ((modifier_of_string (String.trim line)) :: acc) in
let modifiers = modifiers_of_lines [] in
close_in ic;
List.rev modifiers

View File

@ -67,7 +67,3 @@ exception Modifiers_name_already_registered of string
exception Modifiers_name_not_found of string
val register_modifiers : string -> modifiers -> unit
val modifier_of_string : string -> modifier
val modifiers_of_file : string -> modifiers

View File

@ -0,0 +1,41 @@
(**************************************************************************)
(* *)
(* OCaml *)
(* *)
(* Sebastien Hinderer, projet Gallium, INRIA Paris *)
(* *)
(* Copyright 2019 Institut National de Recherche en Informatique et *)
(* en Automatique. *)
(* *)
(* All rights reserved. This file is distributed under the terms of *)
(* the GNU Lesser General Public License version 2.1, with the *)
(* special exception on linking described in the file LICENSE. *)
(* *)
(**************************************************************************)
(* Parsing of modifier (response) files created by hooks and scripts *)
open Ocamltest_stdlib
let modifier_of_string str =
let lexbuf = Lexing.from_string str in
let variable_name, result = Tsl_lexer.modifier lexbuf in
let variable =
match Variables.find_variable variable_name with
| None -> raise (Variables.No_such_variable variable_name)
| Some variable -> variable
in
match result with
| `Remove -> Environments.Remove variable
| `Add value -> Environments.Add (variable, value)
| `Append value -> Environments.Append (variable, value)
let modifiers_of_file filename =
let ic = open_in filename in
let rec modifiers_of_lines acc = match input_line_opt ic with
| None -> acc
| Some line ->
modifiers_of_lines ((modifier_of_string (String.trim line)) :: acc) in
let modifiers = modifiers_of_lines [] in
close_in ic;
List.rev modifiers

View File

@ -0,0 +1,20 @@
(**************************************************************************)
(* *)
(* OCaml *)
(* *)
(* Sebastien Hinderer, projet Gallium, INRIA Paris *)
(* *)
(* Copyright 2019 Institut National de Recherche en Informatique et *)
(* en Automatique. *)
(* *)
(* All rights reserved. This file is distributed under the terms of *)
(* the GNU Lesser General Public License version 2.1, with the *)
(* special exception on linking described in the file LICENSE. *)
(* *)
(**************************************************************************)
(* Parsing of modifier (response) files created by hooks and scripts *)
val modifier_of_string : string -> Environments.modifier
val modifiers_of_file : string -> Environments.modifiers