Skip to content

Commit

Permalink
Format more of Merlin's specific files
Browse files Browse the repository at this point in the history
  • Loading branch information
voodoos committed Sep 24, 2024
1 parent 2ee8957 commit 253fce4
Show file tree
Hide file tree
Showing 26 changed files with 1,410 additions and 1,500 deletions.
1 change: 1 addition & 0 deletions src/ocaml/.ocamlformat-enable
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
merlin_specific/**
1,215 changes: 569 additions & 646 deletions src/ocaml/merlin_specific/browse_raw.ml

Large diffs are not rendered by default.

147 changes: 73 additions & 74 deletions src/ocaml/merlin_specific/browse_raw.mli
Original file line number Diff line number Diff line change
@@ -1,30 +1,30 @@
(* {{{ COPYING *(
This file is part of Merlin, an helper for ocaml editors
This file is part of Merlin, an helper for ocaml editors
Copyright (C) 2013 - 2014 Frédéric Bour <frederic.bour(_)lakaban.net>
Thomas Refis <refis.thomas(_)gmail.com>
Simon Castellan <simon.castellan(_)iuwt.fr>
Copyright (C) 2013 - 2014 Frédéric Bour <frederic.bour(_)lakaban.net>
Thomas Refis <refis.thomas(_)gmail.com>
Simon Castellan <simon.castellan(_)iuwt.fr>
Permission is hereby granted, free of charge, to any person obtaining a
copy of this software and associated documentation files (the "Software"),
to deal in the Software without restriction, including without limitation the
rights to use, copy, modify, merge, publish, distribute, sublicense, and/or
sell copies of the Software, and to permit persons to whom the Software is
furnished to do so, subject to the following conditions:
Permission is hereby granted, free of charge, to any person obtaining a
copy of this software and associated documentation files (the "Software"),
to deal in the Software without restriction, including without limitation the
rights to use, copy, modify, merge, publish, distribute, sublicense, and/or
sell copies of the Software, and to permit persons to whom the Software is
furnished to do so, subject to the following conditions:
The above copyright notice and this permission notice shall be included in
all copies or substantial portions of the Software.
The above copyright notice and this permission notice shall be included in
all copies or substantial portions of the Software.
The Software is provided "as is", without warranty of any kind, express or
implied, including but not limited to the warranties of merchantability,
fitness for a particular purpose and noninfringement. In no event shall
the authors or copyright holders be liable for any claim, damages or other
liability, whether in an action of contract, tort or otherwise, arising
from, out of or in connection with the software or the use or other dealings
in the Software.
The Software is provided "as is", without warranty of any kind, express or
implied, including but not limited to the warranties of merchantability,
fitness for a particular purpose and noninfringement. In no event shall
the authors or copyright holders be liable for any claim, damages or other
liability, whether in an action of contract, tort or otherwise, arising
from, out of or in connection with the software or the use or other dealings
in the Software.
)* }}} *)
)* }}} *)

(** [Browse_node] offers a uniform interface to traverse constructions from
* [TypedTree].
Expand All @@ -48,56 +48,54 @@ open Typedtree

type node =
| Dummy
| Pattern : _ general_pattern -> node
| Expression of expression
| Case : _ case -> node
| Class_expr of class_expr
| Class_structure of class_structure
| Class_field of class_field
| Class_field_kind of class_field_kind
| Module_expr of module_expr
| Module_type_constraint of module_type_constraint
| Structure of structure
| Signature of signature
| Pattern : _ general_pattern -> node
| Expression of expression
| Case : _ case -> node
| Class_expr of class_expr
| Class_structure of class_structure
| Class_field of class_field
| Class_field_kind of class_field_kind
| Module_expr of module_expr
| Module_type_constraint of module_type_constraint
| Structure of structure
| Signature of signature
| (* Items come with their final environment *)
Structure_item of structure_item * Env.t
| Signature_item of signature_item * Env.t
| Module_binding of module_binding
| Value_binding of value_binding
| Module_type of module_type
| Module_declaration of module_declaration
| Module_type_declaration of module_type_declaration
| With_constraint of with_constraint
| Core_type of core_type
| Package_type of package_type
| Row_field of row_field
| Value_description of value_description
| Type_declaration of type_declaration
| Type_kind of type_kind
| Type_extension of type_extension
| Extension_constructor of extension_constructor
| Label_declaration of label_declaration
| Constructor_declaration of constructor_declaration
| Class_type of class_type
| Class_signature of class_signature
| Class_type_field of class_type_field
| Class_declaration of class_declaration
| Class_description of class_description
| Class_type_declaration of class_type_declaration
| Binding_op of binding_op

| Include_description of include_description
| Include_declaration of include_declaration
| Open_description of open_description
| Open_declaration of open_declaration

| Method_call of expression * meth * Location.t
| Record_field of [ `Expression of expression
| `Pattern of pattern ]
* Types.label_description
* Longident.t Location.loc
| Module_binding_name of module_binding
| Module_declaration_name of module_declaration
Structure_item of structure_item * Env.t
| Signature_item of signature_item * Env.t
| Module_binding of module_binding
| Value_binding of value_binding
| Module_type of module_type
| Module_declaration of module_declaration
| Module_type_declaration of module_type_declaration
| With_constraint of with_constraint
| Core_type of core_type
| Package_type of package_type
| Row_field of row_field
| Value_description of value_description
| Type_declaration of type_declaration
| Type_kind of type_kind
| Type_extension of type_extension
| Extension_constructor of extension_constructor
| Label_declaration of label_declaration
| Constructor_declaration of constructor_declaration
| Class_type of class_type
| Class_signature of class_signature
| Class_type_field of class_type_field
| Class_declaration of class_declaration
| Class_description of class_description
| Class_type_declaration of class_type_declaration
| Binding_op of binding_op
| Include_description of include_description
| Include_declaration of include_declaration
| Open_description of open_description
| Open_declaration of open_declaration
| Method_call of expression * meth * Location.t
| Record_field of
[ `Expression of expression | `Pattern of pattern ]
* Types.label_description
* Longident.t Location.loc
| Module_binding_name of module_binding
| Module_declaration_name of module_declaration
| Module_type_declaration_name of module_type_declaration

val fold_node : (Env.t -> node -> 'a -> 'a) -> Env.t -> node -> 'a -> 'a
Expand All @@ -115,16 +113,17 @@ val string_of_node : node -> string
val node_paths : node -> Path.t Location.loc list
val node_paths_and_longident : node -> (Path.t Location.loc * Longident.t) list

val node_is_constructor : node ->
val node_is_constructor :
node ->
[ `Description of Types.constructor_description
| `Declaration of Typedtree.constructor_declaration
| `Extension_constructor of Typedtree.extension_constructor ]
Location.loc option
Location.loc
option

val node_of_binary_part : Env.t -> Cmt_format.binary_part -> node

val all_holes :
Env.t * node ->
(Location.t *
Env.t *
[`Exp of Types.type_expr | `Mod of Types.module_type]) list
(Location.t * Env.t * [ `Exp of Types.type_expr | `Mod of Types.module_type ])
list
14 changes: 7 additions & 7 deletions src/ocaml/merlin_specific/tast_helper.ml
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,7 @@ module Pat = struct
let pat_extra = []
let pat_attributes = []

let constant ?(loc=Location.none) pat_env pat_type c =
let constant ?(loc = Location.none) pat_env pat_type c =
let pat_desc = Tpat_constant c in
{ pat_desc; pat_loc = loc; pat_extra; pat_attributes; pat_type; pat_env }

Expand All @@ -17,24 +17,24 @@ module Pat = struct
let pat_desc = Tpat_var (Ident.create_local str.Asttypes.txt, str, uid) in
{ pat_desc; pat_loc; pat_extra; pat_attributes; pat_type; pat_env }

let record ?(loc=Location.none) pat_env pat_type lst closed_flag =
let record ?(loc = Location.none) pat_env pat_type lst closed_flag =
let pat_desc = Tpat_record (lst, closed_flag) in
{ pat_desc; pat_loc = loc; pat_extra; pat_attributes; pat_type; pat_env }

let tuple ?(loc=Location.none) pat_env pat_type lst =
let tuple ?(loc = Location.none) pat_env pat_type lst =
let pat_desc = Tpat_tuple lst in
{ pat_desc; pat_loc = loc; pat_extra; pat_attributes; pat_type; pat_env }

let construct ?(loc=Location.none)
pat_env pat_type lid cstr_desc args locs_coretype =
let construct ?(loc = Location.none) pat_env pat_type lid cstr_desc args
locs_coretype =
let pat_desc = Tpat_construct (lid, cstr_desc, args, locs_coretype) in
{ pat_desc; pat_loc = loc; pat_extra; pat_attributes; pat_type; pat_env }

let pat_or ?(loc=Location.none) ?row_desc pat_env pat_type p1 p2 =
let pat_or ?(loc = Location.none) ?row_desc pat_env pat_type p1 p2 =
let pat_desc = Tpat_or (p1, p2, row_desc) in
{ pat_desc; pat_loc = loc; pat_extra; pat_attributes; pat_type; pat_env }

let variant ?(loc=Location.none) pat_env pat_type lbl sub rd =
let variant ?(loc = Location.none) pat_env pat_type lbl sub rd =
let pat_desc = Tpat_variant (lbl, sub, rd) in
{ pat_desc; pat_loc = loc; pat_extra; pat_attributes; pat_type; pat_env }
end
45 changes: 21 additions & 24 deletions src/ocaml/merlin_specific/typer_raw.ml
Original file line number Diff line number Diff line change
@@ -1,40 +1,37 @@
(* {{{ COPYING *(
This file is part of Merlin, an helper for ocaml editors
This file is part of Merlin, an helper for ocaml editors
Copyright (C) 2013 - 2015 Frédéric Bour <frederic.bour(_)lakaban.net>
Thomas Refis <refis.thomas(_)gmail.com>
Simon Castellan <simon.castellan(_)iuwt.fr>
Copyright (C) 2013 - 2015 Frédéric Bour <frederic.bour(_)lakaban.net>
Thomas Refis <refis.thomas(_)gmail.com>
Simon Castellan <simon.castellan(_)iuwt.fr>
Permission is hereby granted, free of charge, to any person obtaining a
copy of this software and associated documentation files (the "Software"),
to deal in the Software without restriction, including without limitation the
rights to use, copy, modify, merge, publish, distribute, sublicense, and/or
sell copies of the Software, and to permit persons to whom the Software is
furnished to do so, subject to the following conditions:
Permission is hereby granted, free of charge, to any person obtaining a
copy of this software and associated documentation files (the "Software"),
to deal in the Software without restriction, including without limitation the
rights to use, copy, modify, merge, publish, distribute, sublicense, and/or
sell copies of the Software, and to permit persons to whom the Software is
furnished to do so, subject to the following conditions:
The above copyright notice and this permission notice shall be included in
all copies or substantial portions of the Software.
The above copyright notice and this permission notice shall be included in
all copies or substantial portions of the Software.
The Software is provided "as is", without warranty of any kind, express or
implied, including but not limited to the warranties of merchantability,
fitness for a particular purpose and noninfringement. In no event shall
the authors or copyright holders be liable for any claim, damages or other
liability, whether in an action of contract, tort or otherwise, arising
from, out of or in connection with the software or the use or other dealings
in the Software.
The Software is provided "as is", without warranty of any kind, express or
implied, including but not limited to the warranties of merchantability,
fitness for a particular purpose and noninfringement. In no event shall
the authors or copyright holders be liable for any claim, damages or other
liability, whether in an action of contract, tort or otherwise, arising
from, out of or in connection with the software or the use or other dealings
in the Software.
)* }}} *)
)* }}} *)

open Std

let fresh_env () =
(*Ident.reinit();*)
let initially_opened_module =
if !Clflags.nopervasives then
None
else
Some "Stdlib"
if !Clflags.nopervasives then None else Some "Stdlib"
in
Typemod.initial_env
~loc:(Location.in_file "command line")
Expand Down
40 changes: 20 additions & 20 deletions src/ocaml/merlin_specific/typer_raw.mli
Original file line number Diff line number Diff line change
@@ -1,29 +1,29 @@
(* {{{ COPYING *(
This file is part of Merlin, an helper for ocaml editors
This file is part of Merlin, an helper for ocaml editors
Copyright (C) 2013 - 2015 Frédéric Bour <frederic.bour(_)lakaban.net>
Thomas Refis <refis.thomas(_)gmail.com>
Simon Castellan <simon.castellan(_)iuwt.fr>
Copyright (C) 2013 - 2015 Frédéric Bour <frederic.bour(_)lakaban.net>
Thomas Refis <refis.thomas(_)gmail.com>
Simon Castellan <simon.castellan(_)iuwt.fr>
Permission is hereby granted, free of charge, to any person obtaining a
copy of this software and associated documentation files (the "Software"),
to deal in the Software without restriction, including without limitation the
rights to use, copy, modify, merge, publish, distribute, sublicense, and/or
sell copies of the Software, and to permit persons to whom the Software is
furnished to do so, subject to the following conditions:
Permission is hereby granted, free of charge, to any person obtaining a
copy of this software and associated documentation files (the "Software"),
to deal in the Software without restriction, including without limitation the
rights to use, copy, modify, merge, publish, distribute, sublicense, and/or
sell copies of the Software, and to permit persons to whom the Software is
furnished to do so, subject to the following conditions:
The above copyright notice and this permission notice shall be included in
all copies or substantial portions of the Software.
The above copyright notice and this permission notice shall be included in
all copies or substantial portions of the Software.
The Software is provided "as is", without warranty of any kind, express or
implied, including but not limited to the warranties of merchantability,
fitness for a particular purpose and noninfringement. In no event shall
the authors or copyright holders be liable for any claim, damages or other
liability, whether in an action of contract, tort or otherwise, arising
from, out of or in connection with the software or the use or other dealings
in the Software.
The Software is provided "as is", without warranty of any kind, express or
implied, including but not limited to the warranties of merchantability,
fitness for a particular purpose and noninfringement. In no event shall
the authors or copyright holders be liable for any claim, damages or other
liability, whether in an action of contract, tort or otherwise, arising
from, out of or in connection with the software or the use or other dealings
in the Software.
)* }}} *)
)* }}} *)

val fresh_env : unit -> Env.t
1 change: 1 addition & 0 deletions src/ocaml/parsing/.ocamlformat-enable
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
msupport_parsing.ml
6 changes: 2 additions & 4 deletions src/ocaml/parsing/msupport_parsing.ml
Original file line number Diff line number Diff line change
@@ -1,6 +1,4 @@
(* Filled in from Msupport. *)
let msupport_raise_error : (exn -> unit) ref =
ref raise
let msupport_raise_error : (exn -> unit) ref = ref raise

let raise_error exn =
!msupport_raise_error exn
let raise_error exn = !msupport_raise_error exn
1 change: 0 additions & 1 deletion src/utils/.ocamlformat

This file was deleted.

2 changes: 0 additions & 2 deletions src/utils/.ocamlformat-enable

This file was deleted.

4 changes: 4 additions & 0 deletions src/utils/.ocamlformat-ignore
Original file line number Diff line number Diff line change
@@ -0,0 +1,4 @@
misc.ml
misc.mli
stamped_hashtable.ml
stamped_hashtable.mli
Loading

0 comments on commit 253fce4

Please sign in to comment.