Skip to content

Commit

Permalink
Add locations to docstring attributes
Browse files Browse the repository at this point in the history
  • Loading branch information
lpw25 committed Apr 17, 2020
1 parent 59fac07 commit a534650
Showing 1 changed file with 12 additions and 8 deletions.
20 changes: 12 additions & 8 deletions parsing/docstrings.ml
Original file line number Diff line number Diff line change
Expand Up @@ -89,18 +89,20 @@ let doc_loc = {txt = "ocaml.doc"; loc = Location.none}

let docs_attr ds =
let open Parsetree in
let body = ds.ds_body in
let loc = ds.ds_loc in
let exp =
{ pexp_desc = Pexp_constant (Pconst_string(ds.ds_body, ds.ds_loc, None));
pexp_loc = ds.ds_loc;
{ pexp_desc = Pexp_constant (Pconst_string(body, loc, None));
pexp_loc = loc;
pexp_loc_stack = [];
pexp_attributes = []; }
in
let item =
{ pstr_desc = Pstr_eval (exp, []); pstr_loc = exp.pexp_loc }
{ pstr_desc = Pstr_eval (exp, []); pstr_loc = loc }
in
{ attr_name = doc_loc;
attr_payload = PStr [item];
attr_loc = Location.none }
attr_loc = loc }

let add_docs_attrs docs attrs =
let attrs =
Expand Down Expand Up @@ -139,18 +141,20 @@ let text_loc = {txt = "ocaml.text"; loc = Location.none}

let text_attr ds =
let open Parsetree in
let body = ds.ds_body in
let loc = ds.ds_loc in
let exp =
{ pexp_desc = Pexp_constant (Pconst_string(ds.ds_body, ds.ds_loc, None));
pexp_loc = ds.ds_loc;
{ pexp_desc = Pexp_constant (Pconst_string(body, loc, None));
pexp_loc = loc;
pexp_loc_stack = [];
pexp_attributes = []; }
in
let item =
{ pstr_desc = Pstr_eval (exp, []); pstr_loc = exp.pexp_loc }
{ pstr_desc = Pstr_eval (exp, []); pstr_loc = loc }
in
{ attr_name = text_loc;
attr_payload = PStr [item];
attr_loc = Location.none }
attr_loc = loc }

let add_text_attrs dsl attrs =
let fdsl = List.filter (function {ds_body=""} -> false| _ ->true) dsl in
Expand Down

0 comments on commit a534650

Please sign in to comment.