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,20 @@ syn region ocamlNone transparent matchgroup=ocamlEncl start="{" matchgroup=oca
8687syn region ocamlNone transparent matchgroup =ocamlEncl start =" \[ " matchgroup =ocamlEncl end =" \] " contains =ALLBUT,@ocamlContained,ocamlBrackErr
8788syn 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
9291syn keyword ocamlTodo contained TODO FIXME XXX NOTE
9392
93+ syn cluster ocamlCommentLike contains =ocamlComment,ocamlCommentInDoc,ocamlDocumentation,ocamlEmptyDocumentation
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+ syn match ocamlEmptyDocumentation " (\*\* )"
101+ else
102+ syn region ocamlCommentInDoc start =" (\* " end =" \* )" contains =@Spell,ocamlTodo,ocamlCommentInDoc
103+ endif
94104
95105" Objects
96106syn region ocamlEnd matchgroup =ocamlObject start =" \< object\> " matchgroup =ocamlObject end =" \< end\> " contains =ALLBUT,@ocamlContained,ocamlEndErr
@@ -129,8 +139,8 @@ syn match ocamlKeyword "\<include\>" skipwhite skipempty nextgroup=ocamlModPa
129139
130140" "module" - somewhat complicated stuff ;-)
131141" 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
142+ syn region ocamlModule matchgroup =ocamlKeyword start =" \< module\> " matchgroup =ocamlModule end =" \< _\|\u\(\w\| '\) *\> " contains =@ocamlAllErrs,@ocamlCommentLike skipwhite skipempty nextgroup =ocamlPreDef
143+ syn region ocamlPreDef start =" ." me =e - 1 end =" [a-z:=)]\@ =" contained contains =@ocamlAllErrs,@ocamlCommentLike ,ocamlModParam,ocamlGenMod,ocamlModTypeRestr nextgroup =ocamlModTypePre,ocamlModPreRHS
134144syn region ocamlModParam start =" (\*\@ !" end =" )" contained contains =ocamlGenMod,ocamlModParam,ocamlModParam1,ocamlSig,ocamlVal
135145syn match ocamlModParam1 " \<\u\(\w\| '\) *\> " contained skipwhite skipempty
136146syn match ocamlGenMod " ()" contained skipwhite skipempty
@@ -140,11 +150,11 @@ syn match ocamlModTypeRestr "\<\w\(\w\|'\)*\( *\. *\w\(\w\|'\)*\)*\>" contain
140150
141151syn match ocamlModPreRHS " =" contained skipwhite skipempty nextgroup =ocamlModParam,ocamlFullMod
142152syn 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
153+ syn region ocamlVal matchgroup =ocamlKeyword start =" \< val\> " matchgroup =ocamlLCIdentifier end =" \<\l\(\w\| '\) *\> " contains =@ocamlAllErrs,@ocamlCommentLike ,ocamlFullMod skipwhite skipempty nextgroup =ocamlModTypePre
154+ syn region ocamlModRHS start =" ." end =" . *\w\| ([^*]" me =e - 2 contained contains =@ocamlCommentLike skipwhite skipempty nextgroup =ocamlModParam,ocamlFullMod
145155syn match ocamlFullMod " \<\u\(\w\| '\) *\( *\. *\u\(\w\| '\) *\) *" contained skipwhite skipempty nextgroup =ocamlFuncWith
146156
147- syn region ocamlFuncWith start =" ([*)]\@ !" end =" )" contained contains =ocamlComment ,ocamlWith,ocamlStruct skipwhite skipempty nextgroup =ocamlFuncWith
157+ syn region ocamlFuncWith start =" ([*)]\@ !" end =" )" contained contains =@ocamlCommentLike ,ocamlWith,ocamlStruct skipwhite skipempty nextgroup =ocamlFuncWith
148158
149159syn region ocamlModTRWith start =" (\*\@ !" end =" )" contained contains =@ocamlAENoParen,ocamlWith
150160syn match ocamlWith " \<\(\u\(\w\| '\) * *\. *\) *\w\(\w\| '\) *\> " contained skipwhite skipempty nextgroup =ocamlWithRest
@@ -157,10 +167,10 @@ syn region ocamlStruct matchgroup=ocamlStructEncl start="\<\(module\s\+\)\=str
157167syn region ocamlSig matchgroup =ocamlSigEncl start =" \< sig\> " matchgroup =ocamlSigEncl end =" \< end\> " contains =ALLBUT,@ocamlContained,ocamlEndErr
158168
159169" "functor"
160- syn region ocamlFunctor start =" \< functor\> " matchgroup =ocamlKeyword end =" ->" contains =@ocamlAllErrs,ocamlComment ,ocamlModParam,ocamlGenMod skipwhite skipempty nextgroup =ocamlStruct,ocamlSig,ocamlFuncWith,ocamlFunctor
170+ syn region ocamlFunctor start =" \< functor\> " matchgroup =ocamlKeyword end =" ->" contains =@ocamlAllErrs,@ocamlCommentLike ,ocamlModParam,ocamlGenMod skipwhite skipempty nextgroup =ocamlStruct,ocamlSig,ocamlFuncWith,ocamlFunctor
161171
162172" "module type"
163- syn region ocamlModTypeOf start =" \< module\s\+ type\(\s\+ of\)\=\> " matchgroup =ocamlModule end =" \<\w\(\w\| '\) *\> " contains =ocamlComment skipwhite skipempty nextgroup =ocamlMTDef
173+ syn region ocamlModTypeOf start =" \< module\s\+ type\(\s\+ of\)\=\> " matchgroup =ocamlModule end =" \<\w\(\w\| '\) *\> " contains =@ocamlCommentLike skipwhite skipempty nextgroup =ocamlMTDef
164174syn match ocamlMTDef " =\s *\w\(\w\| '\) *\> " hs =s + 1 ,me =s + 1 skipwhite skipempty nextgroup =ocamlFullMod
165175
166176" Quoted strings
@@ -386,7 +396,7 @@ syn cluster ocamlTypeExpr add=ocamlTypeObject
386396syn region ocamlTypeObject contained
387397\ matchgroup= ocamlEncl start = " <"
388398\ matchgroup= ocamlEncl end = " >"
389- \ contains= ocamlTypeObjectDots,ocamlLCIdentifier,ocamlTypeObjectAnnot,ocamlTypeBlank,ocamlComment ,ocamlPpx
399+ \ contains= ocamlTypeObjectDots,ocamlLCIdentifier,ocamlTypeObjectAnnot,ocamlTypeBlank,@o camlCommentLike ,ocamlPpx
390400hi link ocamlTypeObject ocamlTypeCatchAll
391401syn cluster ocamlTypeContained add =ocamlTypeObjectDots
392402syn match ocamlTypeObjectDots contained " \.\. "
@@ -395,15 +405,15 @@ syn cluster ocamlTypeContained add=ocamlTypeObjectAnnot
395405syn region ocamlTypeObjectAnnot contained
396406\ matchgroup= ocamlKeyChar start = " :"
397407\ matchgroup= ocamlKeyChar end = " ;\| >\@ ="
398- \ contains= @o camlTypeExpr,ocamlComment ,ocamlPpx
408+ \ contains= @o camlTypeExpr,@o camlCommentLike ,ocamlPpx
399409hi link ocamlTypeObjectAnnot ocamlTypeCatchAll
400410
401411" Record type definition
402412syn cluster ocamlTypeContained add =ocamlTypeRecordDecl
403413syn region ocamlTypeRecordDecl contained
404414\ matchgroup= ocamlEncl start = " {"
405415\ matchgroup= ocamlEncl end = " }"
406- \ contains= ocamlTypeMutable,ocamlLCIdentifier,ocamlTypeRecordAnnot,ocamlTypeBlank,ocamlComment ,ocamlPpx
416+ \ contains= ocamlTypeMutable,ocamlLCIdentifier,ocamlTypeRecordAnnot,ocamlTypeBlank,@o camlCommentLike ,ocamlPpx
407417hi link ocamlTypeRecordDecl ocamlTypeCatchAll
408418syn cluster ocamlTypeContained add =ocamlTypeMutable
409419syn keyword ocamlTypeMutable contained mutable
@@ -412,7 +422,7 @@ syn cluster ocamlTypeContained add=ocamlTypeRecordAnnot
412422syn region ocamlTypeRecordAnnot contained
413423\ matchgroup= ocamlKeyChar start = " :"
414424\ matchgroup= ocamlKeyChar end = " ;\| }\@ ="
415- \ contains= @o camlTypeExpr,ocamlComment ,ocamlPpx
425+ \ contains= @o camlTypeExpr,@o camlCommentLike ,ocamlPpx
416426hi link ocamlTypeRecordAnnot ocamlTypeCatchAll
417427
418428" Polymorphic variant types
@@ -421,7 +431,7 @@ syn cluster ocamlTypeExpr add=ocamlTypeVariant
421431syn region ocamlTypeVariant contained
422432\ matchgroup= ocamlEncl start = " \[ >" start = " \[ <" start = " \[ @\@ !"
423433\ matchgroup= ocamlEncl end = " \] "
424- \ contains= ocamlTypeVariantKeyChar,ocamlTypeVariantConstr,ocamlTypeVariantAnnot,ocamlTypeBlank,ocamlComment ,ocamlPpx
434+ \ contains= ocamlTypeVariantKeyChar,ocamlTypeVariantConstr,ocamlTypeVariantAnnot,ocamlTypeBlank,@o camlCommentLike ,ocamlPpx
425435hi link ocamlTypeVariant ocamlTypeCatchAll
426436syn cluster ocamlTypeContained add =ocamlTypeVariantKeyChar
427437syn match ocamlTypeVariantKeyChar contained " |"
@@ -434,7 +444,7 @@ syn cluster ocamlTypeContained add=ocamlTypeVariantAnnot
434444syn region ocamlTypeVariantAnnot contained
435445\ matchgroup= ocamlKeyword start = " \< of\> "
436446\ matchgroup= ocamlKeyChar end = " |\| >\|\]\@ ="
437- \ contains= @o camlTypeExpr,ocamlTypeAmp,ocamlComment ,ocamlPpx
447+ \ contains= @o camlTypeExpr,ocamlTypeAmp,@o camlCommentLike ,ocamlPpx
438448hi link ocamlTypeVariantAnnot ocamlTypeCatchAll
439449syn cluster ocamlTypeContained add =ocamlTypeAmp
440450syn match ocamlTypeAmp contained " &"
@@ -449,7 +459,7 @@ syn region ocamlTypeSumDecl contained
449459\ matchgroup= ocamlTypeSumConstr start = " (\_ s*)" start = " \[\_ s*]" start = " (\_ s*::\_ s*)"
450460\ matchgroup= NONE end = " \(\< type\>\|\< exception\>\|\< val\>\|\< module\>\|\< class\>\|\< method\>\|\< constraint\>\|\< inherit\>\|\< object\>\|\< struct\>\|\< open\>\|\< include\>\|\< let\>\|\< external\>\|\< in\>\|\< end\>\| )\| ]\| }\| ;\| ;;\| =\)\@ ="
451461\ matchgroup= NONE end = " \(\< and\>\)\@ ="
452- \ contains= ocamlTypeSumBar,ocamlTypeSumConstr,ocamlTypeSumAnnot,ocamlTypeBlank,ocamlComment ,ocamlPpx
462+ \ contains= ocamlTypeSumBar,ocamlTypeSumConstr,ocamlTypeSumAnnot,ocamlTypeBlank,@o camlCommentLike ,ocamlPpx
453463hi link ocamlTypeSumDecl ocamlTypeCatchAll
454464syn cluster ocamlTypeContained add =ocamlTypeSumBar
455465syn match ocamlTypeSumBar contained " |"
@@ -469,15 +479,15 @@ syn region ocamlTypeSumAnnot contained
469479\ matchgroup= NONE end = " |\@ ="
470480\ matchgroup= NONE end = " \(\< type\>\|\< exception\>\|\< val\>\|\< module\>\|\< class\>\|\< method\>\|\< constraint\>\|\< inherit\>\|\< object\>\|\< struct\>\|\< open\>\|\< include\>\|\< let\>\|\< external\>\|\< in\>\|\< end\>\| )\| ]\| }\| ;\| ;;\)\@ ="
471481\ matchgroup= NONE end = " \(\< and\>\)\@ ="
472- \ contains= @o camlTypeExpr,ocamlTypeRecordDecl,ocamlComment ,ocamlPpx
482+ \ contains= @o camlTypeExpr,ocamlTypeRecordDecl,@o camlCommentLike ,ocamlPpx
473483hi link ocamlTypeSumAnnot ocamlTypeCatchAll
474484
475485" Type context opened by “type” (type definition), “constraint” (type
476486" constraint) and “exception” (exception definition)
477487syn region ocamlTypeDef
478488\ matchgroup= ocamlKeyword start = " \< type\>\(\_ s\+\< nonrec\>\)\?\|\< constraint\>\|\< exception\> "
479489\ matchgroup= NONE end = " \(\< type\>\|\< exception\>\|\< val\>\|\< module\>\|\< class\>\|\< method\>\|\< constraint\>\|\< inherit\>\|\< object\>\|\< struct\>\|\< open\>\|\< include\>\|\< let\>\|\< external\>\|\< in\>\|\< end\>\| )\| ]\| }\| ;\| ;;\)\@ ="
480- \ contains= @o camlTypeExpr,ocamlTypeEq,ocamlTypePrivate,ocamlTypeDefDots,ocamlTypeRecordDecl,ocamlTypeSumDecl,ocamlTypeDefAnd,ocamlComment ,ocamlPpx
490+ \ contains= @o camlTypeExpr,ocamlTypeEq,ocamlTypePrivate,ocamlTypeDefDots,ocamlTypeRecordDecl,ocamlTypeSumDecl,ocamlTypeDefAnd,@o camlCommentLike ,ocamlPpx
481491hi link ocamlTypeDef ocamlTypeCatchAll
482492syn cluster ocamlTypeContained add =ocamlTypePrivate
483493syn keyword ocamlTypePrivate contained private
@@ -503,7 +513,7 @@ syn region ocamlTypeAnnot matchgroup=ocamlKeyChar start=":\(>\|\_s*type\>\|[>:=]
503513\ matchgroup= NONE end = " \(\< type\>\|\< exception\>\|\< val\>\|\< module\>\|\< class\>\|\< method\>\|\< constraint\>\|\< inherit\>\|\< object\>\|\< struct\>\|\< open\>\|\< include\>\|\< let\>\|\< external\>\|\< in\>\|\< end\>\| )\| ]\| }\| ;\| ;;\)\@ ="
504514\ matchgroup= NONE end = " \( ;\| }\)\@ ="
505515\ matchgroup= NONE end = " \( =\| :>\)\@ ="
506- \ contains= @o camlTypeExpr,ocamlComment ,ocamlPpx
516+ \ contains= @o camlTypeExpr,@o camlCommentLike ,ocamlPpx
507517hi link ocamlTypeAnnot ocamlTypeCatchAll
508518
509519" Type annotation that gives the return type of a `fun` keyword
@@ -512,7 +522,7 @@ syn cluster ocamlTypeContained add=ocamlFunTypeAnnot
512522syn region ocamlFunTypeAnnot contained containedin =ocamlFun
513523\ matchgroup= ocamlKeyChar start = " :"
514524\ matchgroup= NONE end = " \( ->\)\@ ="
515- \ contains= @o camlTypeExpr,ocamlComment ,ocamlPpx
525+ \ contains= @o camlTypeExpr,@o camlCommentLike ,ocamlPpx
516526hi link ocamlFunTypeAnnot ocamlTypeCatchAll
517527
518528" Module paths (including functors) in types.
@@ -525,14 +535,14 @@ syn match ocamlTypeModPath contained "\<\u\(\w\|'\)*\_s*\."
525535syn region ocamlTypeModPath contained transparent
526536\ matchgroup= ocamlModPath start = " \<\u\(\w\| '\) *\_ s*(\*\@ !"
527537\ matchgroup= ocamlModPath end = " )\_ s*\. "
528- \ contains= ocamlTypeDotlessModPath,ocamlTypeBlank,ocamlComment ,ocamlPpx
538+ \ contains= ocamlTypeDotlessModPath,ocamlTypeBlank,@o camlCommentLike ,ocamlPpx
529539hi link ocamlTypeModPath ocamlModPath
530540syn cluster ocamlTypeContained add =ocamlTypeDotlessModPath
531541syn match ocamlTypeDotlessModPath contained " \<\u\(\w\| '\) *\_ s*\.\? "
532542syn region ocamlTypeDotlessModPath contained transparent
533543\ matchgroup= ocamlModPath start = " \<\u\(\w\| '\) *\_ s*(\*\@ !"
534544\ matchgroup= ocamlModPath end = " )\_ s*\.\? "
535- \ contains= ocamlTypeDotlessModPath,ocamlTypeBlank,ocamlComment ,ocamlPpx
545+ \ contains= ocamlTypeDotlessModPath,ocamlTypeBlank,@o camlCommentLike ,ocamlPpx
536546hi link ocamlTypeDotlessModPath ocamlTypeModPath
537547
538548" """""""""""""""""""""""""""""""""""""""""""""""""""""""""""""""""""""""""""""""
@@ -577,6 +587,7 @@ hi def link ocamlCharErr Error
577587hi def link ocamlErr Error
578588
579589hi def link ocamlComment Comment
590+ hi def link ocamlCommentInDoc ocamlComment
580591hi def link ocamlShebang ocamlComment
581592
582593hi def link ocamlModPath Include
@@ -662,7 +673,11 @@ hi def link ocamlPpxEncl ocamlEncl
662673
663674let b: current_syntax = " ocaml"
664675
665- let &cpo = s: keepcpo
666- unlet s: keepcpo
676+ " Because of the nesting (ocaml in odoc in ocaml), s:keepcpo might have been
677+ " unlet already
678+ if exists (' s:keepcpo' )
679+ let &cpo = s: keepcpo
680+ unlet s: keepcpo
681+ endif
667682
668683" vim: ts = 8
0 commit comments