Skip to content

Commit 40cd7d8

Browse files
n-osborneshym
andcommitted
Add documentation highlighting in OCaml files
Co-authored-by: Samuel Hym <[email protected]>
1 parent 1a0b6c7 commit 40cd7d8

File tree

1 file changed

+39
-25
lines changed

1 file changed

+39
-25
lines changed

syntax/ocaml.vim

+39-25
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,19 @@ 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
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=ocamlComment start="(\*\*" end="\*)" contains=@ocamlOdoc
100+
else
101+
syn region ocamlCommentInDoc start="(\*" end="\*)" contains=@Spell,ocamlTodo,ocamlCommentInDoc
102+
endif
94103

95104
" Objects
96105
syn region ocamlEnd matchgroup=ocamlObject start="\<object\>" matchgroup=ocamlObject end="\<end\>" contains=ALLBUT,@ocamlContained,ocamlEndErr
@@ -129,8 +138,8 @@ syn match ocamlKeyword "\<include\>" skipwhite skipempty nextgroup=ocamlModPa
129138

130139
" "module" - somewhat complicated stuff ;-)
131140
" 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
141+
syn region ocamlModule matchgroup=ocamlKeyword start="\<module\>" matchgroup=ocamlModule end="\<_\|\u\(\w\|'\)*\>" contains=@ocamlAllErrs,@ocamlCommentLike skipwhite skipempty nextgroup=ocamlPreDef
142+
syn region ocamlPreDef start="."me=e-1 end="[a-z:=)]\@=" contained contains=@ocamlAllErrs,@ocamlCommentLike,ocamlModParam,ocamlGenMod,ocamlModTypeRestr nextgroup=ocamlModTypePre,ocamlModPreRHS
134143
syn region ocamlModParam start="(\*\@!" end=")" contained contains=ocamlGenMod,ocamlModParam,ocamlModParam1,ocamlSig,ocamlVal
135144
syn match ocamlModParam1 "\<\u\(\w\|'\)*\>" contained skipwhite skipempty
136145
syn match ocamlGenMod "()" contained skipwhite skipempty
@@ -140,11 +149,11 @@ syn match ocamlModTypeRestr "\<\w\(\w\|'\)*\( *\. *\w\(\w\|'\)*\)*\>" contain
140149

141150
syn match ocamlModPreRHS "=" contained skipwhite skipempty nextgroup=ocamlModParam,ocamlFullMod
142151
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
152+
syn region ocamlVal matchgroup=ocamlKeyword start="\<val\>" matchgroup=ocamlLCIdentifier end="\<\l\(\w\|'\)*\>" contains=@ocamlAllErrs,@ocamlCommentLike,ocamlFullMod skipwhite skipempty nextgroup=ocamlModTypePre
153+
syn region ocamlModRHS start="." end=". *\w\|([^*]"me=e-2 contained contains=@ocamlCommentLike skipwhite skipempty nextgroup=ocamlModParam,ocamlFullMod
145154
syn match ocamlFullMod "\<\u\(\w\|'\)*\( *\. *\u\(\w\|'\)*\)*" contained skipwhite skipempty nextgroup=ocamlFuncWith
146155

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

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

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

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

166175
" Quoted strings
@@ -386,7 +395,7 @@ syn cluster ocamlTypeExpr add=ocamlTypeObject
386395
syn region ocamlTypeObject contained
387396
\ matchgroup=ocamlEncl start="<"
388397
\ matchgroup=ocamlEncl end=">"
389-
\ contains=ocamlTypeObjectDots,ocamlLCIdentifier,ocamlTypeObjectAnnot,ocamlTypeBlank,ocamlComment,ocamlPpx
398+
\ contains=ocamlTypeObjectDots,ocamlLCIdentifier,ocamlTypeObjectAnnot,ocamlTypeBlank,@ocamlCommentLike,ocamlPpx
390399
hi link ocamlTypeObject ocamlTypeCatchAll
391400
syn cluster ocamlTypeContained add=ocamlTypeObjectDots
392401
syn match ocamlTypeObjectDots contained "\.\."
@@ -395,15 +404,15 @@ syn cluster ocamlTypeContained add=ocamlTypeObjectAnnot
395404
syn region ocamlTypeObjectAnnot contained
396405
\ matchgroup=ocamlKeyChar start=":"
397406
\ matchgroup=ocamlKeyChar end=";\|>\@="
398-
\ contains=@ocamlTypeExpr,ocamlComment,ocamlPpx
407+
\ contains=@ocamlTypeExpr,@ocamlCommentLike,ocamlPpx
399408
hi link ocamlTypeObjectAnnot ocamlTypeCatchAll
400409

401410
" Record type definition
402411
syn cluster ocamlTypeContained add=ocamlTypeRecordDecl
403412
syn region ocamlTypeRecordDecl contained
404413
\ matchgroup=ocamlEncl start="{"
405414
\ matchgroup=ocamlEncl end="}"
406-
\ contains=ocamlTypeMutable,ocamlLCIdentifier,ocamlTypeRecordAnnot,ocamlTypeBlank,ocamlComment,ocamlPpx
415+
\ contains=ocamlTypeMutable,ocamlLCIdentifier,ocamlTypeRecordAnnot,ocamlTypeBlank,@ocamlCommentLike,ocamlPpx
407416
hi link ocamlTypeRecordDecl ocamlTypeCatchAll
408417
syn cluster ocamlTypeContained add=ocamlTypeMutable
409418
syn keyword ocamlTypeMutable contained mutable
@@ -412,7 +421,7 @@ syn cluster ocamlTypeContained add=ocamlTypeRecordAnnot
412421
syn region ocamlTypeRecordAnnot contained
413422
\ matchgroup=ocamlKeyChar start=":"
414423
\ matchgroup=ocamlKeyChar end=";\|}\@="
415-
\ contains=@ocamlTypeExpr,ocamlComment,ocamlPpx
424+
\ contains=@ocamlTypeExpr,@ocamlCommentLike,ocamlPpx
416425
hi link ocamlTypeRecordAnnot ocamlTypeCatchAll
417426

418427
" Polymorphic variant types
@@ -421,7 +430,7 @@ syn cluster ocamlTypeExpr add=ocamlTypeVariant
421430
syn region ocamlTypeVariant contained
422431
\ matchgroup=ocamlEncl start="\[>" start="\[<" start="\[@\@!"
423432
\ matchgroup=ocamlEncl end="\]"
424-
\ contains=ocamlTypeVariantKeyChar,ocamlTypeVariantConstr,ocamlTypeVariantAnnot,ocamlTypeBlank,ocamlComment,ocamlPpx
433+
\ contains=ocamlTypeVariantKeyChar,ocamlTypeVariantConstr,ocamlTypeVariantAnnot,ocamlTypeBlank,@ocamlCommentLike,ocamlPpx
425434
hi link ocamlTypeVariant ocamlTypeCatchAll
426435
syn cluster ocamlTypeContained add=ocamlTypeVariantKeyChar
427436
syn match ocamlTypeVariantKeyChar contained "|"
@@ -434,7 +443,7 @@ syn cluster ocamlTypeContained add=ocamlTypeVariantAnnot
434443
syn region ocamlTypeVariantAnnot contained
435444
\ matchgroup=ocamlKeyword start="\<of\>"
436445
\ matchgroup=ocamlKeyChar end="|\|>\|\]\@="
437-
\ contains=@ocamlTypeExpr,ocamlTypeAmp,ocamlComment,ocamlPpx
446+
\ contains=@ocamlTypeExpr,ocamlTypeAmp,@ocamlCommentLike,ocamlPpx
438447
hi link ocamlTypeVariantAnnot ocamlTypeCatchAll
439448
syn cluster ocamlTypeContained add=ocamlTypeAmp
440449
syn match ocamlTypeAmp contained "&"
@@ -449,7 +458,7 @@ syn region ocamlTypeSumDecl contained
449458
\ matchgroup=ocamlTypeSumConstr start="(\_s*)" start="\[\_s*]" start="(\_s*::\_s*)"
450459
\ matchgroup=NONE end="\(\<type\>\|\<exception\>\|\<val\>\|\<module\>\|\<class\>\|\<method\>\|\<constraint\>\|\<inherit\>\|\<object\>\|\<struct\>\|\<open\>\|\<include\>\|\<let\>\|\<external\>\|\<in\>\|\<end\>\|)\|]\|}\|;\|;;\|=\)\@="
451460
\ matchgroup=NONE end="\(\<and\>\)\@="
452-
\ contains=ocamlTypeSumBar,ocamlTypeSumConstr,ocamlTypeSumAnnot,ocamlTypeBlank,ocamlComment,ocamlPpx
461+
\ contains=ocamlTypeSumBar,ocamlTypeSumConstr,ocamlTypeSumAnnot,ocamlTypeBlank,@ocamlCommentLike,ocamlPpx
453462
hi link ocamlTypeSumDecl ocamlTypeCatchAll
454463
syn cluster ocamlTypeContained add=ocamlTypeSumBar
455464
syn match ocamlTypeSumBar contained "|"
@@ -469,15 +478,15 @@ syn region ocamlTypeSumAnnot contained
469478
\ matchgroup=NONE end="|\@="
470479
\ matchgroup=NONE end="\(\<type\>\|\<exception\>\|\<val\>\|\<module\>\|\<class\>\|\<method\>\|\<constraint\>\|\<inherit\>\|\<object\>\|\<struct\>\|\<open\>\|\<include\>\|\<let\>\|\<external\>\|\<in\>\|\<end\>\|)\|]\|}\|;\|;;\)\@="
471480
\ matchgroup=NONE end="\(\<and\>\)\@="
472-
\ contains=@ocamlTypeExpr,ocamlTypeRecordDecl,ocamlComment,ocamlPpx
481+
\ contains=@ocamlTypeExpr,ocamlTypeRecordDecl,@ocamlCommentLike,ocamlPpx
473482
hi link ocamlTypeSumAnnot ocamlTypeCatchAll
474483

475484
" Type context opened by “type” (type definition), “constraint” (type
476485
" constraint) and “exception” (exception definition)
477486
syn region ocamlTypeDef
478487
\ matchgroup=ocamlKeyword start="\<type\>\(\_s\+\<nonrec\>\)\?\|\<constraint\>\|\<exception\>"
479488
\ 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
489+
\ contains=@ocamlTypeExpr,ocamlTypeEq,ocamlTypePrivate,ocamlTypeDefDots,ocamlTypeRecordDecl,ocamlTypeSumDecl,ocamlTypeDefAnd,@ocamlCommentLike,ocamlPpx
481490
hi link ocamlTypeDef ocamlTypeCatchAll
482491
syn cluster ocamlTypeContained add=ocamlTypePrivate
483492
syn keyword ocamlTypePrivate contained private
@@ -503,7 +512,7 @@ syn region ocamlTypeAnnot matchgroup=ocamlKeyChar start=":\(>\|\_s*type\>\|[>:=]
503512
\ matchgroup=NONE end="\(\<type\>\|\<exception\>\|\<val\>\|\<module\>\|\<class\>\|\<method\>\|\<constraint\>\|\<inherit\>\|\<object\>\|\<struct\>\|\<open\>\|\<include\>\|\<let\>\|\<external\>\|\<in\>\|\<end\>\|)\|]\|}\|;\|;;\)\@="
504513
\ matchgroup=NONE end="\(;\|}\)\@="
505514
\ matchgroup=NONE end="\(=\|:>\)\@="
506-
\ contains=@ocamlTypeExpr,ocamlComment,ocamlPpx
515+
\ contains=@ocamlTypeExpr,@ocamlCommentLike,ocamlPpx
507516
hi link ocamlTypeAnnot ocamlTypeCatchAll
508517

509518
" Type annotation that gives the return type of a `fun` keyword
@@ -512,7 +521,7 @@ syn cluster ocamlTypeContained add=ocamlFunTypeAnnot
512521
syn region ocamlFunTypeAnnot contained containedin=ocamlFun
513522
\ matchgroup=ocamlKeyChar start=":"
514523
\ matchgroup=NONE end="\(->\)\@="
515-
\ contains=@ocamlTypeExpr,ocamlComment,ocamlPpx
524+
\ contains=@ocamlTypeExpr,@ocamlCommentLike,ocamlPpx
516525
hi link ocamlFunTypeAnnot ocamlTypeCatchAll
517526

518527
" Module paths (including functors) in types.
@@ -525,14 +534,14 @@ syn match ocamlTypeModPath contained "\<\u\(\w\|'\)*\_s*\."
525534
syn region ocamlTypeModPath contained transparent
526535
\ matchgroup=ocamlModPath start="\<\u\(\w\|'\)*\_s*(\*\@!"
527536
\ matchgroup=ocamlModPath end=")\_s*\."
528-
\ contains=ocamlTypeDotlessModPath,ocamlTypeBlank,ocamlComment,ocamlPpx
537+
\ contains=ocamlTypeDotlessModPath,ocamlTypeBlank,@ocamlCommentLike,ocamlPpx
529538
hi link ocamlTypeModPath ocamlModPath
530539
syn cluster ocamlTypeContained add=ocamlTypeDotlessModPath
531540
syn match ocamlTypeDotlessModPath contained "\<\u\(\w\|'\)*\_s*\.\?"
532541
syn region ocamlTypeDotlessModPath contained transparent
533542
\ matchgroup=ocamlModPath start="\<\u\(\w\|'\)*\_s*(\*\@!"
534543
\ matchgroup=ocamlModPath end=")\_s*\.\?"
535-
\ contains=ocamlTypeDotlessModPath,ocamlTypeBlank,ocamlComment,ocamlPpx
544+
\ contains=ocamlTypeDotlessModPath,ocamlTypeBlank,@ocamlCommentLike,ocamlPpx
536545
hi link ocamlTypeDotlessModPath ocamlTypeModPath
537546

538547
""""""""""""""""""""""""""""""""""""""""""""""""""""""""""""""""""""""""""""""""
@@ -577,6 +586,7 @@ hi def link ocamlCharErr Error
577586
hi def link ocamlErr Error
578587

579588
hi def link ocamlComment Comment
589+
hi def link ocamlCommentInDoc ocamlComment
580590
hi def link ocamlShebang ocamlComment
581591

582592
hi def link ocamlModPath Include
@@ -662,7 +672,11 @@ hi def link ocamlPpxEncl ocamlEncl
662672

663673
let b:current_syntax = "ocaml"
664674

665-
let &cpo = s:keepcpo
666-
unlet s:keepcpo
675+
" Because of the nesting (ocaml in odoc in ocaml), s:keepcpo might have been
676+
" unlet already
677+
if exists('s:keepcpo')
678+
let &cpo = s:keepcpo
679+
unlet s:keepcpo
680+
endif
667681

668682
" vim: ts=8

0 commit comments

Comments
 (0)