Merge branch 'liam-fitzgerald/langserver-rpc-rewrite' (#2181)

* liam-fitzgerald/langserver-rpc-rewrite:
  language-server: align kingside hoon
  language-server: address review issues
  language-server: fixup tests
  language-server: prevent breach being required
  langauge-server: cleanup debug artifacts
  language-server: refactor RPC marks
  language-server: dynamic error highlighting
  language-server: basic request/response cycle
  language-server: first pass at JSON parsers

Signed-off-by: Jared Tobin <jared@tlon.io>
This commit is contained in:
Jared Tobin 2020-01-28 17:20:07 +04:00
commit f19fd5c1a9
No known key found for this signature in database
GPG Key ID: 0E4647D58F8A69E4
9 changed files with 848 additions and 155 deletions

View File

@ -1,8 +1,10 @@
/- lsp-sur=language-server
/+ *server,
auto=language-server-complete,
lsp-parser=language-server-parser,
easy-print=language-server-easy-print,
rune-snippet=language-server-rune-snippet,
build=language-server-build,
default-agent
|%
+$ card card:agent:gall
@ -29,10 +31,19 @@
+$ position
[row=@ud col=@ud]
::
+$ all-state bufs=(map uri=@t buf=wall)
+$ state-zero
$: %0
bufs=(map uri=@t buf=wall)
builds=(map uri=@t =vase)
ford-diagnostics=(map uri=@t (list diagnostic:lsp-sur))
==
+$ versioned-state
$%
state-zero
==
--
^- agent:gall
=| all-state
=| state-zero
=* state -
=<
|_ =bowl:gall
@ -57,7 +68,7 @@
|= old-state=vase
^- (quip card _this)
~& > %lsp-upgrade
[~ this(state !<(all-state old-state))]
[~ this(state *state-zero)]
::
++ on-poke
^+ on-poke:*agent:gall
@ -65,26 +76,31 @@
^- (quip card _this)
=^ cards state
?+ mark (on-poke:def mark vase)
%handle-http-request
(handle-http-request:lsp !<([eyre-id=@ta inbound-request:eyre] vase))
%language-server-rpc-notification
(on-notification:lsp !<(all:notification:lsp-sur vase))
%language-server-rpc-request
(on-request:lsp !<(all:request:lsp-sur vase))
==
[cards this]
::
++ on-watch
|= =path
?: ?=([%primary ~] path)
`this
?. ?=([%http-response @ ~] path)
(on-watch:def path)
`this
++ on-leave on-leave:def
++ on-peek on-peek:def
++ on-peek on-peek:def
++ on-agent on-agent:def
++ on-arvo
^+ on-arvo:*agent:gall
|= [=wire =sign-arvo]
^- (quip card _this)
=^ cards state
?+ wire (on-arvo:def wire sign-arvo)
[%connect ~] ?>(?=(%bound +<.sign-arvo) `state)
?+ sign-arvo (on-arvo:def wire sign-arvo)
[%e %bound *] `state
[%f *] (handle-build:lsp wire +.sign-arvo)
==
[cards this]
::
@ -93,107 +109,71 @@
::
|_ bow=bowl:gall
::
++ parser
=, dejs:format
|^
%: ot
uri+so
:- %data
%- of
:~ sync+sync
completion+position
commit+ni
hover+position
==
~
==
::
++ sync
%- ar
%: ou
range+(uf ~ (pe ~ range))
'rangeLength'^(uf ~ (pe ~ ni))
text+(un so)
~
==
::
++ range
%: ot
start+position
end+position
~
==
::
++ position
%: ot
line+ni
character+ni
~
==
--
::
++ json-response
|= [eyre-id=@ta jon=json]
^- (list card)
(give-simple-payload:app eyre-id (json-response:gen (json-to-octs jon)))
::
:: +handle-http-request: received on a new connection established
++ give-rpc-notification
|= res=out:notification:lsp-sur
^- (list card)
:_ ~
[%give %fact ~[/primary] %language-server-rpc-notification !>(res)]
::
++ handle-http-request
|= [eyre-id=@ta =inbound-request:eyre]
++ on-notification
|= not=all:notification:lsp-sur
^- (quip card _state)
?> ?=(^ body.request.inbound-request)
=/ =lsp-req
%- parser
(need (de-json:html q.u.body.request.inbound-request))
=/ buf (~(gut by bufs) uri.lsp-req *wall)
=^ cards buf
?- +<.lsp-req
%sync (handle-sync buf eyre-id +>.lsp-req)
%completion (handle-completion buf eyre-id +>.lsp-req)
%commit (handle-commit buf eyre-id uri.lsp-req)
%hover (handle-hover buf eyre-id +>.lsp-req)
=^ cards state
?+ -.not [~ state]
%text-document--did-open (handle-did-open +.not)
%text-document--did-change (handle-did-change +.not)
%text-document--did-save (handle-did-save +.not)
%text-document--did-close (handle-did-close +.not)
%exit handle-exit
==
[cards state]
++ on-request
|= req=all:request:lsp-sur
^- (quip card _state)
=^ cards state
?+ -.req [~ state]
%text-document--hover
(handle-hover req)
==
=. bufs
(~(put by bufs) uri.lsp-req buf)
[cards state]
::
++ regen-diagnostics
|= buf=wall
^- json
=/ t=tape
(zing (join "\0a" buf))
=/ parse
(lily:auto t (lsp-parser *beam))
?: ?=(%| -.parse)
(format-diagnostic p.parse)
=, enjs:format
%- pairs
:~ good+b+&
==
++ give-rpc-response
|= res=all:response:lsp-sur
^- (list card)
:_ ~
[%give %fact ~[/primary] %language-server-rpc-response !>(res)]
::
++ format-diagnostic
|= [row=@ col=@]
^- json
=, enjs:format
%- pairs
:~ good+b+|
:+ %diagnostics %a :_ ~
=/ loc (pairs line+(numb (dec row)) character+(numb col) ~)
%- pairs
:~ range+(pairs start+loc end+loc ~)
severity+n+'1'
message+s+'syntax error'
==
==
++ handle-exit
^- (quip card _state)
~& > %lsp-shutdown
:_ *state-zero
%+ turn
~(tap in ~(key by builds))
|= uri=@t
[%pass /ford/[uri] %arvo %f %kill ~]
::
++ handle-commit
|= [buf=wall eyre-id=@ta uri=@t]
^- [(list card) wall]
:_ buf
=/ jon
(regen-diagnostics buf)
:_ (json-response eyre-id jon)
++ handle-did-close
|= [uri=@t version=(unit @)]
^- (quip card _state)
=. bufs
(~(del by bufs) uri)
=. ford-diagnostics
(~(del by ford-diagnostics) uri)
=. builds
(~(del by builds) uri)
:_ state
[%pass /ford/[uri] %arvo %f %kill ~]~
::
++ handle-did-save
|= [uri=@t version=(unit @)]
^- (quip card _state)
:_ state
:_ (give-rpc-notification (get-diagnostics uri))
:*
%pass
/commit
@ -204,18 +184,101 @@
!>([q.byk.bow |])
==
::
++ handle-did-change
|= [document=versioned-doc-id:lsp-sur changes=(list change:lsp-sur)]
^- (quip card _state)
=/ updated=wall
(sync-buf (~(got by bufs) uri.document) changes)
=. bufs
(~(put by bufs) uri.document updated)
`state
::
++ handle-build
|= [=path =gift:able:ford]
^- (quip card _state)
?. ?=([%made *] gift)
[~ state]
?. ?=([%complete *] result.gift)
[~ state]
=/ uri=@t
(snag 1 path)
=/ =build-result:ford
build-result.result.gift
?+ build-result [~ state]
::
[%success %core *]
=. builds
(~(put by builds) uri vase.build-result)
=. ford-diagnostics
(~(del by ford-diagnostics) uri)
:_ state
(give-rpc-notification (get-diagnostics uri))
::
[%error *]
=/ error-ranges=(list =range:lsp-sur)
(get-errors-from-tang:build uri message.build-result)
?~ error-ranges
[~ state]
=. ford-diagnostics
%+ ~(put by ford-diagnostics)
uri
[i.error-ranges 1 'Build Error']~
:_ state
(give-rpc-notification (get-diagnostics uri))
==
::
++ get-diagnostics
|= uri=@t
^- out:notification:lsp-sur
:+ %text-document--publish-diagnostics
uri
%+ weld
(~(gut by ford-diagnostics) uri ~)
(get-parser-diagnostics uri)
::
++ handle-did-open
|= item=text-document-item:lsp-sur
^- (quip card _state)
=. bufs
(~(put by bufs) uri.item (to-wall (trip text.item)))
=/ =path
(uri-to-path:build uri.item)
=/ =schematic:ford
[%core [our.bow %home] (flop path)]
:_ state
^- (list card)
:_ (give-rpc-notification (get-diagnostics uri.item))
^- card
[%pass /ford/[uri.item] %arvo %f %build live=%.y schematic]
::
++ get-parser-diagnostics
|= uri=@t
^- (list diagnostic:lsp-sur)
=/ t=tape
(zing (join "\0a" `wall`(~(got by bufs) uri)))
=/ parse
(lily:auto t (lsp-parser *beam))
?. ?=(%| -.parse)
~
=/ loc=position:lsp-sur
[(dec -.p.parse) +.p.parse]
:_ ~
[[loc loc] 1 'Syntax Error']
::
++ handle-hover
|= [buf=wall eyre-id=@ta row=@ud col=@ud]
^- [(list card) wall]
|= hov=text-document--hover:request:lsp-sur
^- (quip card _state)
=/ buf=wall
(~(got by bufs) uri.hov)
=/ txt
(zing (join "\0a" buf))
=+ (get-id:auto (get-pos buf row col) txt)
=+ (get-id:auto (get-pos buf row.hov col.hov) txt)
?~ id
[(json-response eyre-id *json) buf]
[(give-rpc-response [%text-document--hover id.hov ~]) state]
=/ match=(unit (option:auto type))
(search-exact:auto u.id (get-identifiers:auto -:!>(..zuse)))
?~ match
[(json-response eyre-id *json) buf]
[(give-rpc-response [%text-document--hover id.hov ~]) state]
=/ contents
%- crip
;: weld
@ -223,14 +286,11 @@
~(ram re ~(duck easy-print detail.u.match))
"`"
==
:_ buf
%+ json-response eyre-id
%- pairs:enjs:format
[contents+s+contents ~]
:_ state
(give-rpc-response [%text-document--hover id.hov `contents])
::
++ handle-sync
|= [buf=wall eyre-id=@ta changes=(list change)]
:- (json-response eyre-id *json)
++ sync-buf
|= [buf=wall changes=(list change:lsp-sur)]
|- ^- wall
?~ changes
buf
@ -277,48 +337,4 @@
0
(sub a b)
::
++ handle-completion
|= [buf=wall eyre-id=@ta row=@ud col=@ud]
^- [(list card) wall]
=/ =tape (zing (join "\0a" buf))
=/ pos (get-pos buf row col)
:_ buf
:: Check if we're on a rune
::
=/ rune (swag [(safe-sub pos 2) 2] tape)
?: (~(has by runes:rune-snippet) rune)
(json-response eyre-id (rune-snippet rune))
:: Don't run on large files because it's slow
::
?: (gth (lent buf) 1.000)
=, enjs:format
(json-response eyre-id (pairs good+b+& result+~ ~))
::
=/ tl
(tab-list-tape:auto -:!>(..zuse) pos tape)
=, enjs:format
%+ json-response eyre-id
?: ?=(%| -.tl)
(format-diagnostic p.tl)
?~ p.tl
*json
%- pairs
:~ good+b+&
::
:- %result
%- pairs
:~ 'isIncomplete'^b+&
::
:- %items
:- %a
=/ lots (gth (lent u.p.tl) 10)
%- flop
%+ turn (scag 50 u.p.tl)
|= [=term =type]
?: lots
(frond label+s+term)
=/ detail (crip ~(ram re ~(duck easy-print type)))
(pairs label+s+term detail+s+detail ~)
==
==
--

View File

@ -0,0 +1,61 @@
/- *language-server
::
|%
++ parse-error
|= =tape
^- (unit [=path =range])
=/ parse-pair
%+ cook
|=([row=@ud col=@ud] [(dec row) col])
(ifix [lac rac] ;~((glue ace) dem dem))
=/ parse-path
%+ cook
|=(p=path (slag 3 p))
(ifix [net (jest '::')] (more net urs:ab))
=/ parse-full
;~(plug parse-path ;~(sfix ;~((glue dot) parse-pair parse-pair) ban))
(rust tape parse-full)
::
++ get-errors-from-tang
|= [uri=@t =tang]
^- (list range)
=/ =path
(uri-to-path uri)
%+ murn tang
|= =tank
^- (unit range)
?. ?=([%leaf *] tank)
~
=/ error
(parse-error p.tank)
?~ error
~
?: =(path path.u.error)
`range.u.error
~
::
++ uri-to-path
|= uri=@t
^- path
=/ pier-root=(set cord)
%- sy
['app' 'gen' 'lib' 'mar' 'ren' 'sur' 'sys' 'test' ~]
=/ path=(list cord)
(parse-uri uri)
|-
?< ?=(~ path)
?: (~(has in pier-root) i.path)
`^path`path
$(path t.path)
::
++ parse-uri
|= uri=@t
=- (fall - /fail)
%+ rush uri
%+ more
;~(pose (plus fas) dot)
%+ cook
crip
(star ;~(pose col hep alf))
::
--

View File

@ -116,7 +116,7 @@
::
{$face *}
=^ cox gid $(q.ham q.q.ham)
:_(gid [%palm [['/' ~] ~ ~ ~] [%leaf (trip p.q.ham)] cox ~])
:_(gid [%palm [['=' ~] ~ ~ ~] [%leaf (trip p.q.ham)] cox ~])
::
{$list *}
=^ cox gid $(q.ham q.q.ham)
@ -128,7 +128,7 @@
::
{$plot *}
=^ coz gid (many p.q.ham)
:_(gid [%rose [[' ' ~] ['{' ~] ['}' ~]] coz])
:_(gid [%rose [[' ' ~] ['[' ~] [']' ~]] coz])
::
{$pear *}
:_(gid [%leaf '$' ~(rend co [%$ p.q.ham q.q.ham])])

View File

@ -0,0 +1,277 @@
/- lsp=language-server
|%
::
++ util
|%
++ get-json-string
|= [jon=(map @t json) key=@t]
^- (unit cord)
=/ cord-jon=(unit json)
(~(get by jon) key)
?~ cord-jon
~
?> ?=([%s *] u.cord-jon)
`p.u.cord-jon
--
::
::
++ dejs
=, dejs:format
|%
++ request
|= jon=json
?> ?=([%o *] jon)
=/ method=cord
%- method
(trip (need (get-json-string:util p.jon 'method')))
=/ id=cord
(need (get-json-string:util p.jon 'id'))
=/ params=json
(~(got by p.jon) 'params')
^- all:request:lsp
|^
?+ method [%unknown jon]
%text-document--hover
(text-document--hover params id)
==
::
++ text-document--hover
|= [params=json id=cord]
^- text-document--hover:request:lsp
:+ %text-document--hover
id
%. params
%: ot
position+position
'textDocument'^text-document-id
~
==
::
--
::
++ notification
|= jon=json
?> ?=([%o *] jon)
=/ method=cord
%- method
(trip (need (get-json-string:util p.jon 'method')))
=/ params=json
(~(got by p.jon) 'params')
^- all:notification:lsp
|^
?+ method [%unknown jon]
%text-document--did-change
(text-document--did-change params)
%text-document--did-open
(text-document--did-open params)
%text-document--did-save
(text-document--did-save params)
%text-document--did-close
(text-document--did-close params)
==
::
++ text-document--did-save
|= jon=json
^- text-document--did-save:notification:lsp
?> ?=([%o *] jon)
=/ doc-id
(~(got by p.jon) 'textDocument')
:- %text-document--did-save
(text-document-id doc-id)
::
++ text-document--did-close
|= jon=json
^- text-document--did-close:notification:lsp
?> ?=([%o *] jon)
=/ doc-id
(~(got by p.jon) 'textDocument')
:- %text-document--did-close
(text-document-id doc-id)
::
++ text-document--did-change
|= jon=json
^- text-document--did-change:notification:lsp
:- %text-document--did-change
%. jon
%: ot
'textDocument'^text-document-id
'contentChanges'^text-document-changes
~
==
::
++ text-document--did-open
|= jon=json
^- text-document--did-open:notification:lsp
?> ?=([%o *] jon)
:- %text-document--did-open
(text-document-item (~(got by p.jon) 'textDocument'))
--
:: Utilities
::
++ text-document-item
|= jon=json
^- text-document-item:lsp
%. jon
%: ot
uri+so
version+(mu ni)
text+so
~
==
::
++ text-document-id
%: ou
uri+(un so)
version+(uf ~ (pe ~ ni))
~
==
::
++ text-document-changes
%- ar
%: ou
range+(uf ~ (pe ~ range))
'rangeLength'^(uf ~ (pe ~ ni))
text+(un so)
~
==
::
++ method
|= =tape
^- cord
%- crip %- zing
%+ join "--"
^- (list ^tape)
%+ turn
^- (list (list ^tape))
%+ scan
tape
%+ more
fas
;~ plug
(star low)
(star ;~(plug (cook |=(a=@ (add a 32)) hig) (star low)))
==
|= words=(list ^tape)
^- ^tape
(zing (join "-" words))
::
++ range
%: ot
start+position
end+position
~
==
::
++ position
%: ot
line+ni
character+ni
~
==
--
::
:: TODO: fix
::
++ enjs
=, enjs:format
|%
++ text-document--publish-diagnostics
|= pub=text-document--publish-diagnostics:notification:lsp
^- json
%: pairs
uri+s+uri.pub
diagnostics+a+(turn diagnostics.pub diagnostic)
~
==
++ notification
|= notification=all:notification:lsp
^- json
=/ params=json
?+ -.notification !!
%text-document--publish-diagnostics
(text-document--publish-diagnostics notification)
==
~! -.notification
=/ method=cord (crip (unparse-method -.notification))
%: pairs
method+s+method
params+params
~
==
::
++ response
|= res=all:response:lsp
^- json
|^
?- -.res
%text-document--hover
(text-document--hover res)
==
::
++ wrap-in-id
|= [id=cord res=json]
%: pairs
id+s+id
result+res
~
==
++ text-document--hover
|= hov=text-document--hover:response:lsp
%+ wrap-in-id id.hov
%+ frond 'contents'
?~ contents.hov
~
s+u.contents.hov
--
++ unparse-method
|= =cord
^- ^tape
%+ rash cord
%+ cook |=(l=(list ^tape) (zing (join "/" l)))
%+ more (jest '--')
%+ cook
|= tapes=(list ^tape)
^- ^tape
?~ tapes ~
%- zing
:- i.tapes
%+ turn t.tapes
|= t=^tape
^- ^tape
?~ t ~
[`@tD`(sub i.t 32) t.t]
%+ more
;~(less (jest '--') hep)
(star alf)
::
++ position
|= =position:lsp
^- json
%: pairs
line+(numb row.position)
character+(numb col.position)
~
==
::
++ range
|= =range:lsp
^- json
%: pairs
start+(position start.range)
end+(position end.range)
~
==
::
++ diagnostic
|= diag=diagnostic:lsp
^- json
%: pairs
range+(range range.diag)
severity+(numb severity.diag)
message+s+message.diag
~
==
::
--
--

View File

@ -0,0 +1,16 @@
/- *language-server
/+ lsp-json=language-server-json
|_ not=all:notification
++ grab
|%
++ noun not
++ json
|= jon=^json
(notification:dejs:lsp-json jon)
--
++ grow
|%
++ json
(notification:enjs:lsp-json not)
--
--

View File

@ -0,0 +1,11 @@
/- *language-server
/+ lsp-json=language-server-json
|_ req=all:request
++ grab
|%
++ noun req
++ json
|= jon=^json
(request:dejs:lsp-json jon)
--
--

View File

@ -0,0 +1,15 @@
/- *language-server
/+ lsp=language-server-json
|_ res=all:response
::
++ grow
|%
++ json (response:enjs:lsp res)
--
::
++ grab
|%
++ noun all:response
--
::
--

View File

@ -0,0 +1,95 @@
|%
::
+$ versioned-doc-id
[uri=@t version=(unit @)]
::
++ request
|%
+$ all
$%
text-document--hover
unknown
==
+$ text-document--hover
[%text-document--hover id=cord position versioned-doc-id]
+$ unknown
[%unknown json]
--
++ response
|%
+$ all
$%
text-document--hover
==
+$ text-document--hover
[%text-document--hover id=cord contents=(unit @t)]
--
::
+$ diagnostic
[=range severity=@ud message=@t]
::
+$ position
[row=@ud col=@ud]
::
+$ text-document-item
[uri=@t version=(unit @) text=@t]
::
++ notification
|%
::
+$ in
$%
text-document--did-change
text-document--did-open
text-document--did-save
text-document--did-close
exit
unknown
==
::
+$ out
$%
text-document--publish-diagnostics
==
::
+$ all
$%
out
in
==
::
+$ text-document--did-change
[%text-document--did-change versioned-doc-id changes=(list change)]
::
+$ text-document--did-open
[%text-document--did-open text-document-item]
::
+$ text-document--did-save
[%text-document--did-save versioned-doc-id]
::
+$ text-document--did-close
[%text-document--did-close versioned-doc-id]
::
+$ exit
[%exit ~]
::
+$ unknown
[%unknown =json]
::
+$ text-document--publish-diagnostics
[%text-document--publish-diagnostics uri=@t diagnostics=(list diagnostic)]
::
--
::
+$ change
$: range=(unit range)
range-length=(unit @ud)
text=@t
==
::
+$ range
$: start=position
end=position
==
::
--

View File

@ -0,0 +1,202 @@
:: tests for lsp JSON parsing
/- lsp-sur=language-server
/+ *test, *language-server-json
=, enjs:format
|%
::
++ position
[5 3]
++ position-jon
^- json
:- %o
%: malt
['character' %n '3']
['line' %n '5']
~
==
::
++ range
[position position]
::
++ range-jon
^- json
:- %o
%: malt
['start' position-jon]
['end' position-jon]
~
==
::
++ change-jon
^- json
:- %o
%: malt
['text' `json`[%s `@t`'text']]
['rangeLength' [%n '3']]
['range' range-jon]
~
==
::
++ changes-jon
^- json
:- %a
^- (list json)
[change-jon ~]
::
++ text-document-item
^- text-document-item:lsp-sur
['file://' `1 'text']
::
++ text-document-item-jon
^- json
:- %o
%: malt
['uri' `json`[%s 'file://']]
['version' `json`[%n '1']]
['text' `json`[%s 'text']]
~
==
::
++ text-document-id
^- versioned-doc-id:lsp-sur
['file://' `1]
::
++ text-document-id-jon
^- json
:- %o
%: malt
['uri' `json`[%s 'file://']]
['version' `json`[%n '1']]
~
==
++ diagnostic
^- diagnostic:lsp-sur
[range 1 'Syntax Error']
::
++ diagnostic-jon
^- json
:- %o
%: malt
['range' range-jon]
['severity' `json`[%n '1']]
['message' `json`[%s 'Syntax Error']]
~
==
::
++ make-notification-jon
|= [method=@t params=json]
^- json
%: pairs
['method' `json`[%s method]]
params+params
~
==
++ make-request-jon
|= [id=@t method=@t params=json]
^- json
%: pairs
['id' `json`[%s id]]
['method' `json`[%s method]]
params+params
~
==
++ make-response-jon
|= [id=@t result=json]
%: pairs
id+s+id
result+result
~
==
::
:: Notifications
::
++ test-parse-did-change
%+ expect-eq
!> ^- all:notification:lsp-sur
[%text-document--did-change text-document-id [[~ [[5 3] [5 3]]] `3 'text']~]
!> %- notification:dejs
%+ make-notification-jon 'textDocument/didChange'
:- %o
%: malt
['contentChanges' changes-jon]
['textDocument' text-document-id-jon]
~
==
::
++ test-parse-did-save
%+ expect-eq
!> ^- all:notification:lsp-sur
[%text-document--did-save text-document-id]
!> %- notification:dejs
%+ make-notification-jon 'textDocument/didSave'
:- %o
%: malt
['textDocument' text-document-id-jon]
~
==
::
++ test-parse-did-close
%+ expect-eq
!> ^- all:notification:lsp-sur
[%text-document--did-close text-document-id]
!> %- notification:dejs
%+ make-notification-jon 'textDocument/didClose'
:- %o
%: malt
['textDocument' text-document-id-jon]
~
==
::
++ test-parse-did-open
%+ expect-eq
!> ^- all:notification:lsp-sur
[%text-document--did-open text-document-item]
!> %- notification:dejs
%+ make-notification-jon 'textDocument/didOpen'
:- %o
%: malt
['textDocument' text-document-item-jon]
~
==
::
:: Requests
::
++ test-parse-hover
%+ expect-eq
!> ^- all:request:lsp-sur
[%text-document--hover '3' position text-document-id]
!> %- request:dejs
^- json
%^ make-request-jon '3' 'textDocument/hover'
:- %o
%: malt
['position' position-jon]
['textDocument' text-document-id-jon]
~
==
:: to JSON
::
:: notifications
::
++ test-enjs-publish-diagnostics
%+ expect-eq
!> %- notification:enjs
[%text-document--publish-diagnostics 'file://' [diagnostic ~]]
!> ^- json
%+ make-notification-jon 'textDocument/publishDiagnostics'
:- %o
%: malt
['uri' `json`[%s 'file://']]
['diagnostics' `json`[%a [diagnostic-jon ~]]]
~
==
:: responses
++ test-enjs-hover
%+ expect-eq
!> %- response:enjs
[%text-document--hover '1' `'text']
!> ^- json
%+ make-response-jon '1'
%+ frond 'contents'
s+'text'
--