Skip to content

Commit 3a2c156

Browse files
Maelancopy
authored andcommitted
ocaml syntax: fix linting of functor and functor params
The `module` keyword is now treated uniformly. Previously, it was matched differently in signatures (matchgroup `ocamlModSpec`) than elsewhere (matchgroup `ocamlModule`). Both cases have almost identical syntax: (* in signatures: *) module M (X1 : T1) … (Xn: Tn) : MODULE TYPE (* in structures: *) module M (X1 : T1) … (Xn: Tn) [: MODULE TYPE] = MODULE DEF The case distinction was not taking profit of the small difference in syntax, and it was creating complexity and mismatch between both cases. Each case had shortcomings. In signatures, functor parameters like this where not highlighted corrrectly: (* in signatures: *) module M (X1 : T1) : … Also, the only case where the `functor` keyword was highlighted correctly was in a `module` type annotation *in a signature*. It was not highlighted correctly in `module` type annotations *in structures*, nor in `module` definitions, nor in `module type` definitions. (* in signatures: *) module type T = functor (X1 : T1) -> … module M : functor (X1 : T1) -> … (* the only case that was working *) (* in structures: *) module type T = functor (X1 : T1) -> … module M : functor (X1 : T1) -> … = … module M = functor (X1 : T1) -> … These bugs are now fixed. The `ocamlModule` matchgroup subsumes the features of both former cases (`module` in signatures / in structures). The `functor` keyword is no more "contained", so that it now matches in all of the 5 situations above.
1 parent 3f6e0f7 commit 3a2c156

File tree

1 file changed

+8
-7
lines changed

1 file changed

+8
-7
lines changed

syntax/ocaml.vim

Lines changed: 8 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -77,7 +77,7 @@ syn match ocamlKwErr "\<\(mutable\|nonrec\|of\|private\)\>"
7777
syn cluster ocamlAllErrs contains=@ocamlAENoParen,ocamlParenErr
7878
syn cluster ocamlAENoParen contains=ocamlBraceErr,ocamlBrackErr,ocamlCountErr,ocamlDoErr,ocamlDoneErr,ocamlEndErr,ocamlThenErr,ocamlKwErr
7979

80-
syn cluster ocamlContained contains=ocamlTodo,ocamlPreDef,ocamlModParam,ocamlModParam1,ocamlMPRestr,ocamlMPRestr2,ocamlModRHS,ocamlFuncWith,ocamlModTypeRestr,ocamlModTRWith,ocamlWith,ocamlWithRest,ocamlModType,ocamlFullMod,ocamlVal
80+
syn cluster ocamlContained contains=ocamlTodo,ocamlPreDef,ocamlModParam,ocamlModParam1,ocamlMPRestr,ocamlModRHS,ocamlFuncWith,ocamlModTypeRestr,ocamlModTRWith,ocamlWith,ocamlWithRest,ocamlModType,ocamlFullMod,ocamlVal
8181

8282

8383
" Enclosing delimiters
@@ -128,16 +128,14 @@ syn match ocamlKeyword "\<open\>" skipwhite skipempty nextgroup=ocamlFullMod
128128
syn match ocamlKeyword "\<include\>" skipwhite skipempty nextgroup=ocamlModParam,ocamlFullMod
129129

130130
" "module" - somewhat complicated stuff ;-)
131-
syn region ocamlModSpec matchgroup=ocamlKeyword start="\<module\>" matchgroup=ocamlModule end="\<\u\(\w\|'\)*\>" contained contains=@ocamlAllErrs,ocamlComment skipwhite skipempty nextgroup=ocamlModTRWith,ocamlMPRestr
132131
syn region ocamlModule matchgroup=ocamlKeyword start="\<module\>" matchgroup=ocamlModule end="\<\u\(\w\|'\)*\>" contains=@ocamlAllErrs,ocamlComment skipwhite skipempty nextgroup=ocamlPreDef
133-
syn region ocamlPreDef start="."me=e-1 matchgroup=ocamlKeyword end="\l\|=\|)"me=e-1 contained contains=@ocamlAllErrs,ocamlComment,ocamlModParam,ocamlGenMod,ocamlModTypeRestr,ocamlModTRWith nextgroup=ocamlModPreRHS
132+
syn region ocamlPreDef start="."me=e-1 end="[a-z:=)]\@=" contained contains=@ocamlAllErrs,ocamlComment,ocamlModParam,ocamlGenMod,ocamlModTypeRestr nextgroup=ocamlMPRestr,ocamlModPreRHS
134133
syn region ocamlModParam start="(\*\@!" end=")" contained contains=ocamlGenMod,ocamlModParam,ocamlModParam1,ocamlSig,ocamlVal
135134
syn match ocamlModParam1 "\<\u\(\w\|'\)*\>" contained skipwhite skipempty
136135
syn match ocamlGenMod "()" contained skipwhite skipempty
137136

138-
syn region ocamlMPRestr start=":" end="."me=e-1 contained contains=@ocamlComment skipwhite skipempty nextgroup=ocamlSig,ocamlMPRestr2,ocamlModTypeRestr,ocamlModTypeOf
137+
syn match ocamlMPRestr ":" contained skipwhite skipempty nextgroup=ocamlModTRWith,ocamlSig,ocamlMPRestr2,ocamlModTypeRestr,ocamlModTypeOf
139138
syn match ocamlModTypeRestr "\<\w\(\w\|'\)*\( *\. *\w\(\w\|'\)*\)*\>" contained
140-
syn region ocamlMPRestr2 start="\<functor\>" matchgroup=ocamlKeyword end="->" contained contains=@ocamlAllErrs,ocamlComment,ocamlModParam,ocamlGenMod skipwhite skipempty nextgroup=ocamlFuncWith,ocamlMPRestr2
141139
syn match ocamlModPreRHS "=" contained skipwhite skipempty nextgroup=ocamlModParam,ocamlFullMod
142140
syn keyword ocamlKeyword val
143141
syn region ocamlVal matchgroup=ocamlKeyword start="\<val\>" matchgroup=ocamlLCIdentifier end="\<\l\(\w\|'\)*\>" contains=@ocamlAllErrs,ocamlComment,ocamlFullMod skipwhite skipempty nextgroup=ocamlMPRestr
@@ -146,15 +144,18 @@ syn match ocamlFullMod "\<\u\(\w\|'\)*\( *\. *\u\(\w\|'\)*\)*" contained skip
146144

147145
syn region ocamlFuncWith start="([*)]\@!" end=")" contained contains=ocamlComment,ocamlWith,ocamlStruct skipwhite skipempty nextgroup=ocamlFuncWith
148146

149-
syn region ocamlModTRWith start=":\s*(\*\@!"hs=s+1 end=")" contained contains=@ocamlAENoParen,ocamlWith
147+
syn region ocamlModTRWith start="(\*\@!" end=")" contained contains=@ocamlAENoParen,ocamlWith
150148
syn match ocamlWith "\<\(\u\(\w\|'\)* *\. *\)*\w\(\w\|'\)*\>" contained skipwhite skipempty nextgroup=ocamlWithRest
151149
syn region ocamlWithRest start="[^)]" end=")"me=e-1 contained contains=ALLBUT,@ocamlContained
152150

153151
" "struct"
154152
syn region ocamlStruct matchgroup=ocamlStructEncl start="\<\(module\s\+\)\=struct\>" matchgroup=ocamlStructEncl end="\<end\>" contains=ALLBUT,@ocamlContained,ocamlEndErr
155153

156154
" "sig"
157-
syn region ocamlSig matchgroup=ocamlSigEncl start="\<sig\>" matchgroup=ocamlSigEncl end="\<end\>" contains=ALLBUT,@ocamlContained,ocamlEndErr,ocamlModule
155+
syn region ocamlSig matchgroup=ocamlSigEncl start="\<sig\>" matchgroup=ocamlSigEncl end="\<end\>" contains=ALLBUT,@ocamlContained,ocamlEndErr
156+
157+
" "functor"
158+
syn region ocamlMPRestr2 start="\<functor\>" matchgroup=ocamlKeyword end="->" contains=@ocamlAllErrs,ocamlComment,ocamlModParam,ocamlGenMod skipwhite skipempty nextgroup=ocamlStruct,ocamlSig,ocamlFuncWith,ocamlMPRestr2
158159

159160
" "module type"
160161
syn region ocamlModTypeOf start="\<module\s\+type\(\s\+of\)\=\>" matchgroup=ocamlModule end="\<\w\(\w\|'\)*\>" contains=ocamlComment skipwhite skipempty nextgroup=ocamlMTDef

0 commit comments

Comments
 (0)