Skip to content

Commit 5d2b639

Browse files
n-osborneshymMaelan
committed
Add documentation highlighting in OCaml files
Co-authored-by: Samuel Hym <[email protected]> Co-authored-by: Maëlan <[email protected]>
1 parent 87e4832 commit 5d2b639

File tree

1 file changed

+44
-26
lines changed

1 file changed

+44
-26
lines changed

syntax/ocaml.vim

Lines changed: 44 additions & 26 deletions
Original file line numberDiff line numberDiff line change
@@ -6,6 +6,7 @@
66
" Issac Trotts <[email protected]>
77
" URL: https://github.com/ocaml/vim-ocaml
88
" Last Change:
9+
" 2024 Jan 25 - Add OCamldoc/Odoc highlighting (Samuel Hym, Nicolas Osborne)
910
" 2019 Nov 05 - Accurate type highlighting (Maëlan)
1011
" 2018 Nov 08 - Improved highlighting of operators (Maëlan)
1112
" 2018 Apr 22 - Improved support for PPX (Andrey Popp)
@@ -86,11 +87,21 @@ syn region ocamlNone transparent matchgroup=ocamlEncl start="{" matchgroup=oca
8687
syn region ocamlNone transparent matchgroup=ocamlEncl start="\[" matchgroup=ocamlEncl end="\]" contains=ALLBUT,@ocamlContained,ocamlBrackErr
8788
syn region ocamlNone transparent matchgroup=ocamlEncl start="\[|" matchgroup=ocamlEncl end="|\]" contains=ALLBUT,@ocamlContained,ocamlArrErr
8889

89-
90-
" Comments
91-
syn region ocamlComment start="(\*" end="\*)" contains=@Spell,ocamlComment,ocamlTodo
90+
" Comments and documentation
9291
syn keyword ocamlTodo contained TODO FIXME XXX NOTE
9392

93+
syn cluster ocamlCommentLike contains=ocamlComment,ocamlCommentInDoc,ocamlDocumentation,ocamlStopComment
94+
95+
if !exists('odoc_syntax_loading')
96+
" Load odoc syntax only when we are not in a *.mld file
97+
syn region ocamlComment start="(\*" end="\*)" contains=@Spell,ocamlComment,ocamlTodo
98+
syn include @ocamlOdoc syntax/odoc.vim
99+
syn region ocamlDocumentation matchgroup=ocamlDocEncl start="(\*\*[*)]\@!" end="\*)" contains=@ocamlOdoc,ocamlCommentInDoc,@Spell,ocamlTodo
100+
else
101+
syn region ocamlCommentInDoc start="(\*" end="\*)" contains=@Spell,ocamlTodo,ocamlCommentInDoc
102+
endif
103+
104+
syn match ocamlStopComment "(\*\*/\*\*)"
94105

95106
" Objects
96107
syn region ocamlEnd matchgroup=ocamlObject start="\<object\>" matchgroup=ocamlObject end="\<end\>" contains=ALLBUT,@ocamlContained,ocamlEndErr
@@ -129,8 +140,8 @@ syn match ocamlKeyword "\<include\>" skipwhite skipempty nextgroup=ocamlModPa
129140

130141
" "module" - somewhat complicated stuff ;-)
131142
" 2022-10: please document it?
132-
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 end="[a-z:=)]\@=" contained contains=@ocamlAllErrs,ocamlComment,ocamlModParam,ocamlGenMod,ocamlModTypeRestr nextgroup=ocamlModTypePre,ocamlModPreRHS
143+
syn region ocamlModule matchgroup=ocamlKeyword start="\<module\>" matchgroup=ocamlModule end="\<_\|\u\(\w\|'\)*\>" contains=@ocamlAllErrs,@ocamlCommentLike skipwhite skipempty nextgroup=ocamlPreDef
144+
syn region ocamlPreDef start="."me=e-1 end="[a-z:=)]\@=" contained contains=@ocamlAllErrs,@ocamlCommentLike,ocamlModParam,ocamlGenMod,ocamlModTypeRestr nextgroup=ocamlModTypePre,ocamlModPreRHS
134145
syn region ocamlModParam start="(\*\@!" end=")" contained contains=ocamlGenMod,ocamlModParam,ocamlModParam1,ocamlSig,ocamlVal
135146
syn match ocamlModParam1 "\<\u\(\w\|'\)*\>" contained skipwhite skipempty
136147
syn match ocamlGenMod "()" contained skipwhite skipempty
@@ -140,11 +151,11 @@ syn match ocamlModTypeRestr "\<\w\(\w\|'\)*\( *\. *\w\(\w\|'\)*\)*\>" contain
140151

141152
syn match ocamlModPreRHS "=" contained skipwhite skipempty nextgroup=ocamlModParam,ocamlFullMod
142153
syn keyword ocamlKeyword val
143-
syn region ocamlVal matchgroup=ocamlKeyword start="\<val\>" matchgroup=ocamlLCIdentifier end="\<\l\(\w\|'\)*\>" contains=@ocamlAllErrs,ocamlComment,ocamlFullMod skipwhite skipempty nextgroup=ocamlModTypePre
144-
syn region ocamlModRHS start="." end=". *\w\|([^*]"me=e-2 contained contains=ocamlComment skipwhite skipempty nextgroup=ocamlModParam,ocamlFullMod
154+
syn region ocamlVal matchgroup=ocamlKeyword start="\<val\>" matchgroup=ocamlLCIdentifier end="\<\l\(\w\|'\)*\>" contains=@ocamlAllErrs,@ocamlCommentLike,ocamlFullMod skipwhite skipempty nextgroup=ocamlModTypePre
155+
syn region ocamlModRHS start="." end=". *\w\|([^*]"me=e-2 contained contains=@ocamlCommentLike skipwhite skipempty nextgroup=ocamlModParam,ocamlFullMod
145156
syn match ocamlFullMod "\<\u\(\w\|'\)*\( *\. *\u\(\w\|'\)*\)*" contained skipwhite skipempty nextgroup=ocamlFuncWith
146157

147-
syn region ocamlFuncWith start="([*)]\@!" end=")" contained contains=ocamlComment,ocamlWith,ocamlStruct skipwhite skipempty nextgroup=ocamlFuncWith
158+
syn region ocamlFuncWith start="([*)]\@!" end=")" contained contains=@ocamlCommentLike,ocamlWith,ocamlStruct skipwhite skipempty nextgroup=ocamlFuncWith
148159

149160
syn region ocamlModTRWith start="(\*\@!" end=")" contained contains=@ocamlAENoParen,ocamlWith
150161
syn match ocamlWith "\<\(\u\(\w\|'\)* *\. *\)*\w\(\w\|'\)*\>" contained skipwhite skipempty nextgroup=ocamlWithRest
@@ -157,10 +168,10 @@ syn region ocamlStruct matchgroup=ocamlStructEncl start="\<\(module\s\+\)\=str
157168
syn region ocamlSig matchgroup=ocamlSigEncl start="\<sig\>" matchgroup=ocamlSigEncl end="\<end\>" contains=ALLBUT,@ocamlContained,ocamlEndErr
158169

159170
" "functor"
160-
syn region ocamlFunctor start="\<functor\>" matchgroup=ocamlKeyword end="->" contains=@ocamlAllErrs,ocamlComment,ocamlModParam,ocamlGenMod skipwhite skipempty nextgroup=ocamlStruct,ocamlSig,ocamlFuncWith,ocamlFunctor
171+
syn region ocamlFunctor start="\<functor\>" matchgroup=ocamlKeyword end="->" contains=@ocamlAllErrs,@ocamlCommentLike,ocamlModParam,ocamlGenMod skipwhite skipempty nextgroup=ocamlStruct,ocamlSig,ocamlFuncWith,ocamlFunctor
161172

162173
" "module type"
163-
syn region ocamlModTypeOf start="\<module\s\+type\(\s\+of\)\=\>" matchgroup=ocamlModule end="\<\w\(\w\|'\)*\>" contains=ocamlComment skipwhite skipempty nextgroup=ocamlMTDef
174+
syn region ocamlModTypeOf start="\<module\s\+type\(\s\+of\)\=\>" matchgroup=ocamlModule end="\<\w\(\w\|'\)*\>" contains=@ocamlCommentLike skipwhite skipempty nextgroup=ocamlMTDef
164175
syn match ocamlMTDef "=\s*\w\(\w\|'\)*\>"hs=s+1,me=s+1 skipwhite skipempty nextgroup=ocamlFullMod
165176

166177
" Quoted strings
@@ -323,7 +334,7 @@ syn cluster ocamlTypeExpr add=ocamlTypeParen
323334
syn region ocamlTypeParen contained transparent
324335
\ matchgroup=ocamlEncl start="(\*\@!"
325336
\ matchgroup=ocamlEncl end=")"
326-
\ contains=@ocamlTypeExpr,ocamlComment,ocamlPpx
337+
\ contains=@ocamlTypeExpr,@ocamlCommentLike,ocamlPpx
327338

328339
syn cluster ocamlTypeExpr add=ocamlTypeKeyChar,ocamlTypeAs
329340
syn match ocamlTypeKeyChar contained "->"
@@ -386,7 +397,7 @@ syn cluster ocamlTypeExpr add=ocamlTypeObject
386397
syn region ocamlTypeObject contained
387398
\ matchgroup=ocamlEncl start="<"
388399
\ matchgroup=ocamlEncl end=">"
389-
\ contains=ocamlTypeObjectDots,ocamlLCIdentifier,ocamlTypeObjectAnnot,ocamlTypeBlank,ocamlComment,ocamlPpx
400+
\ contains=ocamlTypeObjectDots,ocamlLCIdentifier,ocamlTypeObjectAnnot,ocamlTypeBlank,@ocamlCommentLike,ocamlPpx
390401
hi link ocamlTypeObject ocamlTypeCatchAll
391402
syn cluster ocamlTypeContained add=ocamlTypeObjectDots
392403
syn match ocamlTypeObjectDots contained "\.\."
@@ -395,15 +406,15 @@ syn cluster ocamlTypeContained add=ocamlTypeObjectAnnot
395406
syn region ocamlTypeObjectAnnot contained
396407
\ matchgroup=ocamlKeyChar start=":"
397408
\ matchgroup=ocamlKeyChar end=";\|>\@="
398-
\ contains=@ocamlTypeExpr,ocamlComment,ocamlPpx
409+
\ contains=@ocamlTypeExpr,@ocamlCommentLike,ocamlPpx
399410
hi link ocamlTypeObjectAnnot ocamlTypeCatchAll
400411

401412
" Record type definition
402413
syn cluster ocamlTypeContained add=ocamlTypeRecordDecl
403414
syn region ocamlTypeRecordDecl contained
404415
\ matchgroup=ocamlEncl start="{"
405416
\ matchgroup=ocamlEncl end="}"
406-
\ contains=ocamlTypeMutable,ocamlLCIdentifier,ocamlTypeRecordAnnot,ocamlTypeBlank,ocamlComment,ocamlPpx
417+
\ contains=ocamlTypeMutable,ocamlLCIdentifier,ocamlTypeRecordAnnot,ocamlTypeBlank,@ocamlCommentLike,ocamlPpx
407418
hi link ocamlTypeRecordDecl ocamlTypeCatchAll
408419
syn cluster ocamlTypeContained add=ocamlTypeMutable
409420
syn keyword ocamlTypeMutable contained mutable
@@ -412,7 +423,7 @@ syn cluster ocamlTypeContained add=ocamlTypeRecordAnnot
412423
syn region ocamlTypeRecordAnnot contained
413424
\ matchgroup=ocamlKeyChar start=":"
414425
\ matchgroup=ocamlKeyChar end=";\|}\@="
415-
\ contains=@ocamlTypeExpr,ocamlComment,ocamlPpx
426+
\ contains=@ocamlTypeExpr,@ocamlCommentLike,ocamlPpx
416427
hi link ocamlTypeRecordAnnot ocamlTypeCatchAll
417428

418429
" Polymorphic variant types
@@ -421,7 +432,7 @@ syn cluster ocamlTypeExpr add=ocamlTypeVariant
421432
syn region ocamlTypeVariant contained
422433
\ matchgroup=ocamlEncl start="\[>" start="\[<" start="\[@\@!"
423434
\ matchgroup=ocamlEncl end="\]"
424-
\ contains=ocamlTypeVariantKeyChar,ocamlTypeVariantConstr,ocamlTypeVariantAnnot,ocamlTypeBlank,ocamlComment,ocamlPpx
435+
\ contains=ocamlTypeVariantKeyChar,ocamlTypeVariantConstr,ocamlTypeVariantAnnot,ocamlTypeBlank,@ocamlCommentLike,ocamlPpx
425436
hi link ocamlTypeVariant ocamlTypeCatchAll
426437
syn cluster ocamlTypeContained add=ocamlTypeVariantKeyChar
427438
syn match ocamlTypeVariantKeyChar contained "|"
@@ -434,7 +445,7 @@ syn cluster ocamlTypeContained add=ocamlTypeVariantAnnot
434445
syn region ocamlTypeVariantAnnot contained
435446
\ matchgroup=ocamlKeyword start="\<of\>"
436447
\ matchgroup=ocamlKeyChar end="|\|>\|\]\@="
437-
\ contains=@ocamlTypeExpr,ocamlTypeAmp,ocamlComment,ocamlPpx
448+
\ contains=@ocamlTypeExpr,ocamlTypeAmp,@ocamlCommentLike,ocamlPpx
438449
hi link ocamlTypeVariantAnnot ocamlTypeCatchAll
439450
syn cluster ocamlTypeContained add=ocamlTypeAmp
440451
syn match ocamlTypeAmp contained "&"
@@ -449,7 +460,7 @@ syn region ocamlTypeSumDecl contained
449460
\ matchgroup=ocamlTypeSumConstr start="(\_s*)" start="\[\_s*]" start="(\_s*::\_s*)"
450461
\ matchgroup=NONE end="\(\<type\>\|\<exception\>\|\<val\>\|\<module\>\|\<class\>\|\<method\>\|\<constraint\>\|\<inherit\>\|\<object\>\|\<struct\>\|\<open\>\|\<include\>\|\<let\>\|\<external\>\|\<in\>\|\<end\>\|)\|]\|}\|;\|;;\|=\)\@="
451462
\ matchgroup=NONE end="\(\<and\>\)\@="
452-
\ contains=ocamlTypeSumBar,ocamlTypeSumConstr,ocamlTypeSumAnnot,ocamlTypeBlank,ocamlComment,ocamlPpx
463+
\ contains=ocamlTypeSumBar,ocamlTypeSumConstr,ocamlTypeSumAnnot,ocamlTypeBlank,@ocamlCommentLike,ocamlPpx
453464
hi link ocamlTypeSumDecl ocamlTypeCatchAll
454465
syn cluster ocamlTypeContained add=ocamlTypeSumBar
455466
syn match ocamlTypeSumBar contained "|"
@@ -469,15 +480,15 @@ syn region ocamlTypeSumAnnot contained
469480
\ matchgroup=NONE end="|\@="
470481
\ matchgroup=NONE end="\(\<type\>\|\<exception\>\|\<val\>\|\<module\>\|\<class\>\|\<method\>\|\<constraint\>\|\<inherit\>\|\<object\>\|\<struct\>\|\<open\>\|\<include\>\|\<let\>\|\<external\>\|\<in\>\|\<end\>\|)\|]\|}\|;\|;;\)\@="
471482
\ matchgroup=NONE end="\(\<and\>\)\@="
472-
\ contains=@ocamlTypeExpr,ocamlTypeRecordDecl,ocamlComment,ocamlPpx
483+
\ contains=@ocamlTypeExpr,ocamlTypeRecordDecl,@ocamlCommentLike,ocamlPpx
473484
hi link ocamlTypeSumAnnot ocamlTypeCatchAll
474485

475486
" Type context opened by “type” (type definition), “constraint” (type
476487
" constraint) and “exception” (exception definition)
477488
syn region ocamlTypeDef
478489
\ matchgroup=ocamlKeyword start="\<type\>\(\_s\+\<nonrec\>\)\?\|\<constraint\>\|\<exception\>"
479490
\ matchgroup=NONE end="\(\<type\>\|\<exception\>\|\<val\>\|\<module\>\|\<class\>\|\<method\>\|\<constraint\>\|\<inherit\>\|\<object\>\|\<struct\>\|\<open\>\|\<include\>\|\<let\>\|\<external\>\|\<in\>\|\<end\>\|)\|]\|}\|;\|;;\)\@="
480-
\ contains=@ocamlTypeExpr,ocamlTypeEq,ocamlTypePrivate,ocamlTypeDefDots,ocamlTypeRecordDecl,ocamlTypeSumDecl,ocamlTypeDefAnd,ocamlComment,ocamlPpx
491+
\ contains=@ocamlTypeExpr,ocamlTypeEq,ocamlTypePrivate,ocamlTypeDefDots,ocamlTypeRecordDecl,ocamlTypeSumDecl,ocamlTypeDefAnd,@ocamlCommentLike,ocamlPpx
481492
hi link ocamlTypeDef ocamlTypeCatchAll
482493
syn cluster ocamlTypeContained add=ocamlTypePrivate
483494
syn keyword ocamlTypePrivate contained private
@@ -503,7 +514,7 @@ syn region ocamlTypeAnnot matchgroup=ocamlKeyChar start=":\(>\|\_s*type\>\|[>:=]
503514
\ matchgroup=NONE end="\(\<type\>\|\<exception\>\|\<val\>\|\<module\>\|\<class\>\|\<method\>\|\<constraint\>\|\<inherit\>\|\<object\>\|\<struct\>\|\<open\>\|\<include\>\|\<let\>\|\<external\>\|\<in\>\|\<end\>\|)\|]\|}\|;\|;;\)\@="
504515
\ matchgroup=NONE end="\(;\|}\)\@="
505516
\ matchgroup=NONE end="\(=\|:>\)\@="
506-
\ contains=@ocamlTypeExpr,ocamlComment,ocamlPpx
517+
\ contains=@ocamlTypeExpr,@ocamlCommentLike,ocamlPpx
507518
hi link ocamlTypeAnnot ocamlTypeCatchAll
508519

509520
" Type annotation that gives the return type of a `fun` keyword
@@ -512,7 +523,7 @@ syn cluster ocamlTypeContained add=ocamlFunTypeAnnot
512523
syn region ocamlFunTypeAnnot contained containedin=ocamlFun
513524
\ matchgroup=ocamlKeyChar start=":"
514525
\ matchgroup=NONE end="\(->\)\@="
515-
\ contains=@ocamlTypeExpr,ocamlComment,ocamlPpx
526+
\ contains=@ocamlTypeExpr,@ocamlCommentLike,ocamlPpx
516527
hi link ocamlFunTypeAnnot ocamlTypeCatchAll
517528

518529
" Module paths (including functors) in types.
@@ -525,14 +536,14 @@ syn match ocamlTypeModPath contained "\<\u\(\w\|'\)*\_s*\."
525536
syn region ocamlTypeModPath contained transparent
526537
\ matchgroup=ocamlModPath start="\<\u\(\w\|'\)*\_s*(\*\@!"
527538
\ matchgroup=ocamlModPath end=")\_s*\."
528-
\ contains=ocamlTypeDotlessModPath,ocamlTypeBlank,ocamlComment,ocamlPpx
539+
\ contains=ocamlTypeDotlessModPath,ocamlTypeBlank,@ocamlCommentLike,ocamlPpx
529540
hi link ocamlTypeModPath ocamlModPath
530541
syn cluster ocamlTypeContained add=ocamlTypeDotlessModPath
531542
syn match ocamlTypeDotlessModPath contained "\<\u\(\w\|'\)*\_s*\.\?"
532543
syn region ocamlTypeDotlessModPath contained transparent
533544
\ matchgroup=ocamlModPath start="\<\u\(\w\|'\)*\_s*(\*\@!"
534545
\ matchgroup=ocamlModPath end=")\_s*\.\?"
535-
\ contains=ocamlTypeDotlessModPath,ocamlTypeBlank,ocamlComment,ocamlPpx
546+
\ contains=ocamlTypeDotlessModPath,ocamlTypeBlank,@ocamlCommentLike,ocamlPpx
536547
hi link ocamlTypeDotlessModPath ocamlTypeModPath
537548

538549
""""""""""""""""""""""""""""""""""""""""""""""""""""""""""""""""""""""""""""""""
@@ -577,6 +588,9 @@ hi def link ocamlCharErr Error
577588
hi def link ocamlErr Error
578589

579590
hi def link ocamlComment Comment
591+
hi def link ocamlDocEncl ocamlComment
592+
hi def link ocamlCommentInDoc ocamlComment
593+
hi def link ocamlStopComment PreProc
580594
hi def link ocamlShebang ocamlComment
581595

582596
hi def link ocamlModPath Include
@@ -662,7 +676,11 @@ hi def link ocamlPpxEncl ocamlEncl
662676

663677
let b:current_syntax = "ocaml"
664678

665-
let &cpo = s:keepcpo
666-
unlet s:keepcpo
679+
" Because of the nesting (ocaml in odoc in ocaml), s:keepcpo might have been
680+
" unlet already
681+
if exists('s:keepcpo')
682+
let &cpo = s:keepcpo
683+
unlet s:keepcpo
684+
endif
667685

668686
" vim: ts=8

0 commit comments

Comments
 (0)