Skip to content

Commit

Permalink
Change node folding for a more natural position of expr_extra nodes
Browse files Browse the repository at this point in the history
  • Loading branch information
voodoos committed Feb 11, 2020
1 parent 954584a commit e014287
Show file tree
Hide file tree
Showing 8 changed files with 112 additions and 120 deletions.
29 changes: 14 additions & 15 deletions src/ocaml/merlin_specific/402/browse_raw.ml
Original file line number Diff line number Diff line change
Expand Up @@ -232,10 +232,20 @@ let option_fold f' o env (f : _ f0) acc = match o with
| None -> acc
| Some x -> f' x env f acc

let of_expression e = app (Expression e)
let of_core_type ct = app (Core_type ct)
let of_exp_extra (exp,_,_) = match exp with
| Texp_constraint ct ->
of_core_type ct
| Texp_coerce (cto,ct) ->
of_core_type ct ** option_fold of_core_type cto
| Texp_poly cto ->
option_fold of_core_type cto
| Texp_open _ | Texp_newtype _ ->
id_fold
let of_expression e = app (Expression e) **
list_fold of_exp_extra e.exp_extra
let of_case c = app (Case c)
let of_pattern p = app (Pattern p)
let of_core_type ct = app (Core_type ct)
let of_value_binding vb = app (Value_binding vb)
let of_module_type mt = app (Module_type mt)
let of_module_expr me = app (Module_expr me)
Expand Down Expand Up @@ -328,16 +338,6 @@ let of_expression_desc loc = function
| Texp_pack me ->
of_module_expr me

and of_exp_extra (exp,_,_) = match exp with
| Texp_constraint ct ->
of_core_type ct
| Texp_coerce (cto,ct) ->
of_core_type ct ** option_fold of_core_type cto
| Texp_poly cto ->
option_fold of_core_type cto
| Texp_open _ | Texp_newtype _ ->
id_fold

and of_class_expr_desc = function
| Tcl_ident (_,_,cts) ->
list_fold of_core_type cts
Expand Down Expand Up @@ -496,9 +496,8 @@ let of_node = function
| Pattern { pat_desc; pat_extra } ->
of_pattern_desc pat_desc **
list_fold of_pat_extra pat_extra
| Expression { exp_desc; exp_extra; exp_loc } ->
of_expression_desc exp_loc exp_desc **
list_fold of_exp_extra exp_extra
| Expression { exp_desc; exp_extra=_; exp_loc } ->
of_expression_desc exp_loc exp_desc
| Case { c_lhs; c_guard; c_rhs } ->
of_pattern c_lhs ** of_expression c_rhs **
option_fold of_expression c_guard
Expand Down
29 changes: 14 additions & 15 deletions src/ocaml/merlin_specific/403/browse_raw.ml
Original file line number Diff line number Diff line change
Expand Up @@ -232,10 +232,20 @@ let option_fold f' o env (f : _ f0) acc = match o with
| None -> acc
| Some x -> f' x env f acc

let of_expression e = app (Expression e)
let of_core_type ct = app (Core_type ct)
let of_exp_extra (exp,_,_) = match exp with
| Texp_constraint ct ->
of_core_type ct
| Texp_coerce (cto,ct) ->
of_core_type ct ** option_fold of_core_type cto
| Texp_poly cto ->
option_fold of_core_type cto
| Texp_open _ | Texp_newtype _ ->
id_fold
let of_expression e = app (Expression e) **
list_fold of_exp_extra e.exp_extra
let of_case c = app (Case c)
let of_pattern p = app (Pattern p)
let of_core_type ct = app (Core_type ct)
let of_label_declaration ct = app (Label_declaration ct)
let of_value_binding vb = app (Value_binding vb)
let of_module_type mt = app (Module_type mt)
Expand Down Expand Up @@ -334,16 +344,6 @@ let of_expression_desc loc = function
| Texp_unreachable | Texp_extension_constructor _ ->
id_fold

and of_exp_extra (exp,_,_) = match exp with
| Texp_constraint ct ->
of_core_type ct
| Texp_coerce (cto,ct) ->
of_core_type ct ** option_fold of_core_type cto
| Texp_poly cto ->
option_fold of_core_type cto
| Texp_open _ | Texp_newtype _ ->
id_fold

and of_class_expr_desc = function
| Tcl_ident (_,_,cts) ->
list_fold of_core_type cts
Expand Down Expand Up @@ -502,9 +502,8 @@ let of_node = function
| Pattern { pat_desc; pat_extra } ->
of_pattern_desc pat_desc **
list_fold of_pat_extra pat_extra
| Expression { exp_desc; exp_extra; exp_loc } ->
of_expression_desc exp_loc exp_desc **
list_fold of_exp_extra exp_extra
| Expression { exp_desc; exp_extra=_; exp_loc } ->
of_expression_desc exp_loc exp_desc
| Case { c_lhs; c_guard; c_rhs } ->
of_pattern c_lhs ** of_expression c_rhs **
option_fold of_expression c_guard
Expand Down
29 changes: 14 additions & 15 deletions src/ocaml/merlin_specific/404/browse_raw.ml
Original file line number Diff line number Diff line change
Expand Up @@ -239,10 +239,20 @@ let option_fold f' o env (f : _ f0) acc = match o with
| None -> acc
| Some x -> f' x env f acc

let of_expression e = app (Expression e)
let of_core_type ct = app (Core_type ct)
let of_exp_extra (exp,_,_) = match exp with
| Texp_constraint ct ->
of_core_type ct
| Texp_coerce (cto,ct) ->
of_core_type ct ** option_fold of_core_type cto
| Texp_poly cto ->
option_fold of_core_type cto
| Texp_open _ | Texp_newtype _ ->
id_fold
let of_expression e = app (Expression e) **
list_fold of_exp_extra e.exp_extra
let of_case c = app (Case c)
let of_pattern p = app (Pattern p)
let of_core_type ct = app (Core_type ct)
let of_label_declaration ct = app (Label_declaration ct)
let of_value_binding vb = app (Value_binding vb)
let of_module_type mt = app (Module_type mt)
Expand Down Expand Up @@ -347,16 +357,6 @@ let of_expression_desc loc = function
| Texp_unreachable | Texp_extension_constructor _ ->
id_fold

and of_exp_extra (exp,_,_) = match exp with
| Texp_constraint ct ->
of_core_type ct
| Texp_coerce (cto,ct) ->
of_core_type ct ** option_fold of_core_type cto
| Texp_poly cto ->
option_fold of_core_type cto
| Texp_open _ | Texp_newtype _ ->
id_fold

and of_class_expr_desc = function
| Tcl_ident (_,_,cts) ->
list_fold of_core_type cts
Expand Down Expand Up @@ -515,9 +515,8 @@ let of_node = function
| Pattern { pat_desc; pat_extra } ->
of_pattern_desc pat_desc **
list_fold of_pat_extra pat_extra
| Expression { exp_desc; exp_extra; exp_loc } ->
of_expression_desc exp_loc exp_desc **
list_fold of_exp_extra exp_extra
| Expression { exp_desc; exp_extra=_; exp_loc } ->
of_expression_desc exp_loc exp_desc
| Case { c_lhs; c_guard; c_rhs } ->
of_pattern c_lhs ** of_expression c_rhs **
option_fold of_expression c_guard
Expand Down
29 changes: 14 additions & 15 deletions src/ocaml/merlin_specific/405/browse_raw.ml
Original file line number Diff line number Diff line change
Expand Up @@ -239,10 +239,20 @@ let option_fold f' o env (f : _ f0) acc = match o with
| None -> acc
| Some x -> f' x env f acc

let of_expression e = app (Expression e)
let of_core_type ct = app (Core_type ct)
let of_exp_extra (exp,_,_) = match exp with
| Texp_constraint ct ->
of_core_type ct
| Texp_coerce (cto,ct) ->
of_core_type ct ** option_fold of_core_type cto
| Texp_poly cto ->
option_fold of_core_type cto
| Texp_open _ | Texp_newtype _ ->
id_fold
let of_expression e = app (Expression e) **
list_fold of_exp_extra e.exp_extra
let of_case c = app (Case c)
let of_pattern p = app (Pattern p)
let of_core_type ct = app (Core_type ct)
let of_label_declaration ct = app (Label_declaration ct)
let of_value_binding vb = app (Value_binding vb)
let of_module_type mt = app (Module_type mt)
Expand Down Expand Up @@ -347,16 +357,6 @@ let of_expression_desc loc = function
| Texp_unreachable | Texp_extension_constructor _ ->
id_fold

and of_exp_extra (exp,_,_) = match exp with
| Texp_constraint ct ->
of_core_type ct
| Texp_coerce (cto,ct) ->
of_core_type ct ** option_fold of_core_type cto
| Texp_poly cto ->
option_fold of_core_type cto
| Texp_open _ | Texp_newtype _ ->
id_fold

and of_class_expr_desc = function
| Tcl_ident (_,_,cts) ->
list_fold of_core_type cts
Expand Down Expand Up @@ -515,9 +515,8 @@ let of_node = function
| Pattern { pat_desc; pat_extra } ->
of_pattern_desc pat_desc **
list_fold of_pat_extra pat_extra
| Expression { exp_desc; exp_extra; exp_loc } ->
of_expression_desc exp_loc exp_desc **
list_fold of_exp_extra exp_extra
| Expression { exp_desc; exp_extra=_; exp_loc } ->
of_expression_desc exp_loc exp_desc
| Case { c_lhs; c_guard; c_rhs } ->
of_pattern c_lhs ** of_expression c_rhs **
option_fold of_expression c_guard
Expand Down
29 changes: 14 additions & 15 deletions src/ocaml/merlin_specific/406/browse_raw.ml
Original file line number Diff line number Diff line change
Expand Up @@ -239,10 +239,20 @@ let option_fold f' o env (f : _ f0) acc = match o with
| None -> acc
| Some x -> f' x env f acc

let of_expression e = app (Expression e)
let of_core_type ct = app (Core_type ct)
let of_exp_extra (exp,_,_) = match exp with
| Texp_constraint ct ->
of_core_type ct
| Texp_coerce (cto,ct) ->
of_core_type ct ** option_fold of_core_type cto
| Texp_poly cto ->
option_fold of_core_type cto
| Texp_open _ | Texp_newtype _ ->
id_fold
let of_expression e = app (Expression e) **
list_fold of_exp_extra e.exp_extra
let of_case c = app (Case c)
let of_pattern p = app (Pattern p)
let of_core_type ct = app (Core_type ct)
let of_label_declaration ct = app (Label_declaration ct)
let of_value_binding vb = app (Value_binding vb)
let of_module_type mt = app (Module_type mt)
Expand Down Expand Up @@ -347,16 +357,6 @@ let of_expression_desc loc = function
| Texp_unreachable | Texp_extension_constructor _ ->
id_fold

and of_exp_extra (exp,_,_) = match exp with
| Texp_constraint ct ->
of_core_type ct
| Texp_coerce (cto,ct) ->
of_core_type ct ** option_fold of_core_type cto
| Texp_poly cto ->
option_fold of_core_type cto
| Texp_open _ | Texp_newtype _ ->
id_fold

and of_class_expr_desc = function
| Tcl_ident (_,_,cts) ->
list_fold of_core_type cts
Expand Down Expand Up @@ -519,9 +519,8 @@ let of_node = function
| Pattern { pat_desc; pat_extra } ->
of_pattern_desc pat_desc **
list_fold of_pat_extra pat_extra
| Expression { exp_desc; exp_extra; exp_loc } ->
of_expression_desc exp_loc exp_desc **
list_fold of_exp_extra exp_extra
| Expression { exp_desc; exp_extra=_; exp_loc } ->
of_expression_desc exp_loc exp_desc
| Case { c_lhs; c_guard; c_rhs } ->
of_pattern c_lhs ** of_expression c_rhs **
option_fold of_expression c_guard
Expand Down
29 changes: 14 additions & 15 deletions src/ocaml/merlin_specific/407/browse_raw.ml
Original file line number Diff line number Diff line change
Expand Up @@ -239,10 +239,20 @@ let option_fold f' o env (f : _ f0) acc = match o with
| None -> acc
| Some x -> f' x env f acc

let of_expression e = app (Expression e)
let of_core_type ct = app (Core_type ct)
let of_exp_extra (exp,_,_) = match exp with
| Texp_constraint ct ->
of_core_type ct
| Texp_coerce (cto,ct) ->
of_core_type ct ** option_fold of_core_type cto
| Texp_poly cto ->
option_fold of_core_type cto
| Texp_open _ | Texp_newtype _ ->
id_fold
let of_expression e = app (Expression e) **
list_fold of_exp_extra e.exp_extra
let of_case c = app (Case c)
let of_pattern p = app (Pattern p)
let of_core_type ct = app (Core_type ct)
let of_label_declaration ct = app (Label_declaration ct)
let of_value_binding vb = app (Value_binding vb)
let of_module_type mt = app (Module_type mt)
Expand Down Expand Up @@ -347,16 +357,6 @@ let of_expression_desc loc = function
| Texp_unreachable | Texp_extension_constructor _ ->
id_fold

and of_exp_extra (exp,_,_) = match exp with
| Texp_constraint ct ->
of_core_type ct
| Texp_coerce (cto,ct) ->
of_core_type ct ** option_fold of_core_type cto
| Texp_poly cto ->
option_fold of_core_type cto
| Texp_open _ | Texp_newtype _ ->
id_fold

and of_class_expr_desc = function
| Tcl_ident (_,_,cts) ->
list_fold of_core_type cts
Expand Down Expand Up @@ -519,9 +519,8 @@ let of_node = function
| Pattern { pat_desc; pat_extra } ->
of_pattern_desc pat_desc **
list_fold of_pat_extra pat_extra
| Expression { exp_desc; exp_extra; exp_loc } ->
of_expression_desc exp_loc exp_desc **
list_fold of_exp_extra exp_extra
| Expression { exp_desc; exp_extra=_; exp_loc } ->
of_expression_desc exp_loc exp_desc
| Case { c_lhs; c_guard; c_rhs } ->
of_pattern c_lhs ** of_expression c_rhs **
option_fold of_expression c_guard
Expand Down
29 changes: 14 additions & 15 deletions src/ocaml/merlin_specific/408/browse_raw.ml
Original file line number Diff line number Diff line change
Expand Up @@ -240,10 +240,20 @@ let option_fold f' o env (f : _ f0) acc = match o with
| None -> acc
| Some x -> f' x env f acc

let of_expression e = app (Expression e)
let of_core_type ct = app (Core_type ct)
let of_exp_extra (exp,_,_) = match exp with
| Texp_constraint ct ->
of_core_type ct
| Texp_coerce (cto,ct) ->
of_core_type ct ** option_fold of_core_type cto
| Texp_poly cto ->
option_fold of_core_type cto
| Texp_newtype _ ->
id_fold
let of_expression e = app (Expression e) **
list_fold of_exp_extra e.exp_extra
let of_case c = app (Case c)
let of_pattern p = app (Pattern p)
let of_core_type ct = app (Core_type ct)
let of_label_declaration ct = app (Label_declaration ct)
let of_value_binding vb = app (Value_binding vb)
let of_module_type mt = app (Module_type mt)
Expand Down Expand Up @@ -358,16 +368,6 @@ let of_expression_desc loc = function
| Texp_open (od, e) ->
app (Module_expr od.open_expr) ** of_expression e

and of_exp_extra (exp,_,_) = match exp with
| Texp_constraint ct ->
of_core_type ct
| Texp_coerce (cto,ct) ->
of_core_type ct ** option_fold of_core_type cto
| Texp_poly cto ->
option_fold of_core_type cto
| Texp_newtype _ ->
id_fold

and of_class_expr_desc = function
| Tcl_ident (_,_,cts) ->
list_fold of_core_type cts
Expand Down Expand Up @@ -540,9 +540,8 @@ let of_node = function
| Pattern { pat_desc; pat_extra } ->
of_pattern_desc pat_desc **
list_fold of_pat_extra pat_extra
| Expression { exp_desc; exp_extra; exp_loc } ->
of_expression_desc exp_loc exp_desc **
list_fold of_exp_extra exp_extra
| Expression { exp_desc; exp_extra=_; exp_loc } ->
of_expression_desc exp_loc exp_desc
| Case { c_lhs; c_guard; c_rhs } ->
of_pattern c_lhs ** of_expression c_rhs **
option_fold of_expression c_guard
Expand Down
Loading

0 comments on commit e014287

Please sign in to comment.