Skip to content

Commit

Permalink
fix: use correct file permissions for preprocessing (#1153)
Browse files Browse the repository at this point in the history
from jboillot/bugfix/ocamllsp-pp-output-file-creation
  • Loading branch information
jboillot authored Jun 22, 2023
1 parent 1f78031 commit 8131c43
Show file tree
Hide file tree
Showing 6 changed files with 106 additions and 5 deletions.
6 changes: 6 additions & 0 deletions CHANGES.md
Original file line number Diff line number Diff line change
@@ -1,3 +1,9 @@
# Unreleased

## Fixes

- Fix file permissions used when specifying output files of pp and ppx. (#1153)

# 1.16.1

## Fixes
Expand Down
9 changes: 5 additions & 4 deletions ocaml-lsp-server/src/ocaml_lsp_server.ml
Original file line number Diff line number Diff line change
Expand Up @@ -878,20 +878,21 @@ let run_in_directory ~prog ~prog_is_quoted:_ ~args ~cwd ?stdin ?stdout ?stderr
let argv = [ "sh"; "-c"; cmd ] in
let stdin =
match stdin with
| Some file -> Unix.openfile file [ Unix.O_WRONLY ] 0x664
| None -> Unix.openfile "/dev/null" [ Unix.O_RDONLY ] 0x777
| Some file -> Unix.openfile file [ Unix.O_RDONLY ] 0o664
| None -> Unix.openfile "/dev/null" [ Unix.O_RDONLY ] 0o777
in
let stdout, should_close_stdout =
match stdout with
| Some file -> (Unix.openfile file [ Unix.O_WRONLY ] 0x664, true)
| Some file ->
(Unix.openfile file [ Unix.O_WRONLY; Unix.O_CREAT ] 0o664, true)
| None ->
(* Runned programs should never output to stdout since it is the channel
used by LSP to communicate with the editor *)
(Unix.stderr, false)
in
let stderr =
Option.map stderr ~f:(fun file ->
Unix.openfile file [ Unix.O_WRONLY ] 0x664)
Unix.openfile file [ Unix.O_WRONLY; Unix.O_CREAT ] 0o664)
in
let pid =
let cwd : Spawn.Working_dir.t = Path cwd in
Expand Down
22 changes: 21 additions & 1 deletion ocaml-lsp-server/test/e2e-new/dune
Original file line number Diff line number Diff line change
Expand Up @@ -12,6 +12,7 @@
(deps
%{bin:ocamlformat-rpc}
for_ppx.ml
for_pp.ml
(package ocaml-lsp-server)))
(libraries
stdune
Expand All @@ -32,4 +33,23 @@
ppx_expect.config_types
ppx_inline_test.config)
(preprocess
(pps ppx_expect)))
(per_module
((action
(run %{dep:for_pp.sh} %{input-file}))
for_pp)
((pps ppx_expect)
action_extract
action_inline
code_actions
document_flow
for_ppx
hover_extended
metrics
semantic_hl_data
semantic_hl_helpers
semantic_hl_tests
start_stop
test
with_pp
with_ppx
workspace_change_config))))
1 change: 1 addition & 0 deletions ocaml-lsp-server/test/e2e-new/for_pp.ml
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
type world
2 changes: 2 additions & 0 deletions ocaml-lsp-server/test/e2e-new/for_pp.sh
Original file line number Diff line number Diff line change
@@ -0,0 +1,2 @@
#!/bin/sh
sed 's/world/universe/g' $1
71 changes: 71 additions & 0 deletions ocaml-lsp-server/test/e2e-new/with_pp.ml
Original file line number Diff line number Diff line change
@@ -0,0 +1,71 @@
open! Test.Import

let path = Filename.concat (Sys.getcwd ()) "for_pp.ml"

let uri = DocumentUri.of_path path

let print_hover hover =
match hover with
| None -> print_endline "no hover response"
| Some hover ->
hover |> Hover.yojson_of_t
|> Yojson.Safe.pretty_to_string ~std:false
|> print_endline

let hover_req client position =
Client.request
client
(TextDocumentHover
{ HoverParams.position
; textDocument = TextDocumentIdentifier.create ~uri
; workDoneToken = None
})

let%expect_test "with-pp" =
let position = Position.create ~line:0 ~character:9 in
let handler =
Client.Handler.make
~on_notification:(fun client _notification ->
Client.state client;
Fiber.return ())
()
in
let output =
Test.run ~handler @@ fun client ->
let run_client () =
let capabilities = ClientCapabilities.create () in
Client.start client (InitializeParams.create ~capabilities ())
in
let run () =
let* (_ : InitializeResult.t) = Client.initialized client in
let textDocument =
let text = Io.String_path.read_file path in
TextDocumentItem.create ~uri ~languageId:"ocaml" ~version:0 ~text
in
let* () =
Client.notification
client
(TextDocumentDidOpen (DidOpenTextDocumentParams.create ~textDocument))
in
let* () =
let+ resp = hover_req client position in
print_hover resp
in
let output = [%expect.output] in
let* () = Client.request client Shutdown in
let+ () = Client.stop client in
output
in
Fiber.fork_and_join_unit run_client run
in
let (_ : string) = [%expect.output] in
print_endline output;
[%expect
{|
{
"contents": { "kind": "plaintext", "value": "type universe" },
"range": {
"end": { "character": 13, "line": 0 },
"start": { "character": 0, "line": 0 }
}
}|}]

0 comments on commit 8131c43

Please sign in to comment.