Skip to content
Open
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension


Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
4 changes: 2 additions & 2 deletions .github/workflows/main.yml
Original file line number Diff line number Diff line change
Expand Up @@ -77,7 +77,7 @@ jobs:


- name: Check that the changes are correctly formatted
if: matrix.os == 'none'
if: matrix.os == 'ubuntu-latest'
run: |
opam install ocamlformat.0.27.0
opam install ocamlformat.0.28.1
opam exec -- dune build @fmt
2 changes: 1 addition & 1 deletion .ocamlformat
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
version=0.27.0
version=0.28.1-2-g1646c68
disable=false

break-cases=fit-or-vertical
Expand Down
14 changes: 6 additions & 8 deletions src/analysis/ast_iterators.ml
Original file line number Diff line number Diff line change
Expand Up @@ -147,20 +147,18 @@ let build_uid_to_locs_tbl ~(local_defs : Mtyper.typedtree) () =
Types.Uid.Tbl.create 64
in
let iter = iter_on_defs ~uid_to_locs_tbl in
begin
match local_defs with
| `Interface sign -> iter.signature iter sign
| `Implementation str -> iter.structure iter str
begin match local_defs with
| `Interface sign -> iter.signature iter sign
| `Implementation str -> iter.structure iter str
end;
uid_to_locs_tbl

let iter_on_usages ~f (local_defs : Mtyper.typedtree) =
let occ_iter = Cmt_format.iter_on_occurrences ~f in
let iter = iter_only_visible occ_iter in
begin
match local_defs with
| `Interface signature -> iter.signature iter signature
| `Implementation structure -> iter.structure iter structure
begin match local_defs with
| `Interface signature -> iter.signature iter signature
| `Implementation structure -> iter.structure iter structure
end

let iterator_on_usages ~f =
Expand Down
22 changes: 11 additions & 11 deletions src/analysis/browse_misc.ml
Original file line number Diff line number Diff line change
Expand Up @@ -41,7 +41,7 @@ let print_constructor c =
let desc =
Tarrow
( Ast_helper.no_label,
dummy_type_scheme (Ttuple (List.map ~f:(fun a -> None, a) args)),
dummy_type_scheme (Ttuple (List.map ~f:(fun a -> (None, a)) args)),
c.cstr_res,
commu_ok )
in
Expand Down Expand Up @@ -76,10 +76,10 @@ let signature_of_env ?(ignore_extensions = true) env =
| Env_type (_, i, t) -> Some (Sig_type (i, t, Trec_not, Exported))
(* Texp_first == bluff, FIXME *)
| Env_extension (_, i, e) -> begin
match e.ext_type_path with
| Path.Pident id when Ident.name id = "exn" ->
Some (Sig_typext (i, e, Text_exception, Exported))
| _ -> Some (Sig_typext (i, e, Text_first, Exported))
match e.ext_type_path with
| Path.Pident id when Ident.name id = "exn" ->
Some (Sig_typext (i, e, Text_exception, Exported))
| _ -> Some (Sig_typext (i, e, Text_first, Exported))
end
| Env_module (_, i, pr, m) ->
Some (Sig_module (i, pr, m, Trec_not, Exported))
Expand Down Expand Up @@ -141,7 +141,7 @@ let dump_browse node =
`List (append Env.empty node [])

let annotate_tail_calls (ts : Mbrowse.t) :
(Env.t * Browse_raw.node * Query_protocol.is_tail_position) list =
(Env.t * Browse_raw.node * Query_protocol.is_tail_position) list =
let is_one_of candidates node = List.mem node ~set:candidates in
let find_entry_points candidates (env, node) =
(Tail_analysis.entry_points node, (env, node, is_one_of candidates node))
Expand All @@ -155,9 +155,9 @@ let annotate_tail_calls (ts : Mbrowse.t) :
let _, tail_positions = List.fold_n_map entry_points ~f:propagate ~init:[] in
List.map
~f:(fun (env, node, tail) ->
( env,
node,
if not tail then `No
else if Tail_analysis.is_call node then `Tail_call
else `Tail_position ))
( env,
node,
if not tail then `No
else if Tail_analysis.is_call node then `Tail_call
else `Tail_position ))
tail_positions
Loading
Loading