6
6
" Issac Trotts <[email protected] >
7
7
" URL: https://github.com/ocaml/vim-ocaml
8
8
" Last Change:
9
+ " 2024 Jan 25 - Add OCamldoc/Odoc highlighting (Samuel Hym, Nicolas Osborne)
9
10
" 2019 Nov 05 - Accurate type highlighting (Maëlan)
10
11
" 2018 Nov 08 - Improved highlighting of operators (Maëlan)
11
12
" 2018 Apr 22 - Improved support for PPX (Andrey Popp)
@@ -86,11 +87,21 @@ syn region ocamlNone transparent matchgroup=ocamlEncl start="{" matchgroup=oca
86
87
syn region ocamlNone transparent matchgroup =ocamlEncl start =" \[ " matchgroup =ocamlEncl end =" \] " contains =ALLBUT,@ocamlContained,ocamlBrackErr
87
88
syn region ocamlNone transparent matchgroup =ocamlEncl start =" \[ |" matchgroup =ocamlEncl end =" |\] " contains =ALLBUT,@ocamlContained,ocamlArrErr
88
89
89
-
90
- " Comments
91
- syn region ocamlComment start =" (\* " end =" \* )" contains =@Spell,ocamlComment,ocamlTodo
90
+ " Comments and documentation
92
91
syn keyword ocamlTodo contained TODO FIXME XXX NOTE
93
92
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 " (\*\* /\*\* )"
94
105
95
106
" Objects
96
107
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
129
140
130
141
" "module" - somewhat complicated stuff ;-)
131
142
" 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
134
145
syn region ocamlModParam start =" (\*\@ !" end =" )" contained contains =ocamlGenMod,ocamlModParam,ocamlModParam1,ocamlSig,ocamlVal
135
146
syn match ocamlModParam1 " \<\u\(\w\| '\) *\> " contained skipwhite skipempty
136
147
syn match ocamlGenMod " ()" contained skipwhite skipempty
@@ -140,11 +151,11 @@ syn match ocamlModTypeRestr "\<\w\(\w\|'\)*\( *\. *\w\(\w\|'\)*\)*\>" contain
140
151
141
152
syn match ocamlModPreRHS " =" contained skipwhite skipempty nextgroup =ocamlModParam,ocamlFullMod
142
153
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
145
156
syn match ocamlFullMod " \<\u\(\w\| '\) *\( *\. *\u\(\w\| '\) *\) *" contained skipwhite skipempty nextgroup =ocamlFuncWith
146
157
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
148
159
149
160
syn region ocamlModTRWith start =" (\*\@ !" end =" )" contained contains =@ocamlAENoParen,ocamlWith
150
161
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
157
168
syn region ocamlSig matchgroup =ocamlSigEncl start =" \< sig\> " matchgroup =ocamlSigEncl end =" \< end\> " contains =ALLBUT,@ocamlContained,ocamlEndErr
158
169
159
170
" "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
161
172
162
173
" "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
164
175
syn match ocamlMTDef " =\s *\w\(\w\| '\) *\> " hs =s + 1 ,me =s + 1 skipwhite skipempty nextgroup =ocamlFullMod
165
176
166
177
" Quoted strings
@@ -323,7 +334,7 @@ syn cluster ocamlTypeExpr add=ocamlTypeParen
323
334
syn region ocamlTypeParen contained transparent
324
335
\ matchgroup= ocamlEncl start = " (\*\@ !"
325
336
\ matchgroup= ocamlEncl end = " )"
326
- \ contains= @o camlTypeExpr,ocamlComment ,ocamlPpx
337
+ \ contains= @o camlTypeExpr,@o camlCommentLike ,ocamlPpx
327
338
328
339
syn cluster ocamlTypeExpr add =ocamlTypeKeyChar,ocamlTypeAs
329
340
syn match ocamlTypeKeyChar contained " ->"
@@ -386,7 +397,7 @@ syn cluster ocamlTypeExpr add=ocamlTypeObject
386
397
syn region ocamlTypeObject contained
387
398
\ matchgroup= ocamlEncl start = " <"
388
399
\ matchgroup= ocamlEncl end = " >"
389
- \ contains= ocamlTypeObjectDots,ocamlLCIdentifier,ocamlTypeObjectAnnot,ocamlTypeBlank,ocamlComment ,ocamlPpx
400
+ \ contains= ocamlTypeObjectDots,ocamlLCIdentifier,ocamlTypeObjectAnnot,ocamlTypeBlank,@o camlCommentLike ,ocamlPpx
390
401
hi link ocamlTypeObject ocamlTypeCatchAll
391
402
syn cluster ocamlTypeContained add =ocamlTypeObjectDots
392
403
syn match ocamlTypeObjectDots contained " \.\. "
@@ -395,15 +406,15 @@ syn cluster ocamlTypeContained add=ocamlTypeObjectAnnot
395
406
syn region ocamlTypeObjectAnnot contained
396
407
\ matchgroup= ocamlKeyChar start = " :"
397
408
\ matchgroup= ocamlKeyChar end = " ;\| >\@ ="
398
- \ contains= @o camlTypeExpr,ocamlComment ,ocamlPpx
409
+ \ contains= @o camlTypeExpr,@o camlCommentLike ,ocamlPpx
399
410
hi link ocamlTypeObjectAnnot ocamlTypeCatchAll
400
411
401
412
" Record type definition
402
413
syn cluster ocamlTypeContained add =ocamlTypeRecordDecl
403
414
syn region ocamlTypeRecordDecl contained
404
415
\ matchgroup= ocamlEncl start = " {"
405
416
\ matchgroup= ocamlEncl end = " }"
406
- \ contains= ocamlTypeMutable,ocamlLCIdentifier,ocamlTypeRecordAnnot,ocamlTypeBlank,ocamlComment ,ocamlPpx
417
+ \ contains= ocamlTypeMutable,ocamlLCIdentifier,ocamlTypeRecordAnnot,ocamlTypeBlank,@o camlCommentLike ,ocamlPpx
407
418
hi link ocamlTypeRecordDecl ocamlTypeCatchAll
408
419
syn cluster ocamlTypeContained add =ocamlTypeMutable
409
420
syn keyword ocamlTypeMutable contained mutable
@@ -412,7 +423,7 @@ syn cluster ocamlTypeContained add=ocamlTypeRecordAnnot
412
423
syn region ocamlTypeRecordAnnot contained
413
424
\ matchgroup= ocamlKeyChar start = " :"
414
425
\ matchgroup= ocamlKeyChar end = " ;\| }\@ ="
415
- \ contains= @o camlTypeExpr,ocamlComment ,ocamlPpx
426
+ \ contains= @o camlTypeExpr,@o camlCommentLike ,ocamlPpx
416
427
hi link ocamlTypeRecordAnnot ocamlTypeCatchAll
417
428
418
429
" Polymorphic variant types
@@ -421,7 +432,7 @@ syn cluster ocamlTypeExpr add=ocamlTypeVariant
421
432
syn region ocamlTypeVariant contained
422
433
\ matchgroup= ocamlEncl start = " \[ >" start = " \[ <" start = " \[ @\@ !"
423
434
\ matchgroup= ocamlEncl end = " \] "
424
- \ contains= ocamlTypeVariantKeyChar,ocamlTypeVariantConstr,ocamlTypeVariantAnnot,ocamlTypeBlank,ocamlComment ,ocamlPpx
435
+ \ contains= ocamlTypeVariantKeyChar,ocamlTypeVariantConstr,ocamlTypeVariantAnnot,ocamlTypeBlank,@o camlCommentLike ,ocamlPpx
425
436
hi link ocamlTypeVariant ocamlTypeCatchAll
426
437
syn cluster ocamlTypeContained add =ocamlTypeVariantKeyChar
427
438
syn match ocamlTypeVariantKeyChar contained " |"
@@ -434,7 +445,7 @@ syn cluster ocamlTypeContained add=ocamlTypeVariantAnnot
434
445
syn region ocamlTypeVariantAnnot contained
435
446
\ matchgroup= ocamlKeyword start = " \< of\> "
436
447
\ matchgroup= ocamlKeyChar end = " |\| >\|\]\@ ="
437
- \ contains= @o camlTypeExpr,ocamlTypeAmp,ocamlComment ,ocamlPpx
448
+ \ contains= @o camlTypeExpr,ocamlTypeAmp,@o camlCommentLike ,ocamlPpx
438
449
hi link ocamlTypeVariantAnnot ocamlTypeCatchAll
439
450
syn cluster ocamlTypeContained add =ocamlTypeAmp
440
451
syn match ocamlTypeAmp contained " &"
@@ -449,7 +460,7 @@ syn region ocamlTypeSumDecl contained
449
460
\ matchgroup= ocamlTypeSumConstr start = " (\_ s*)" start = " \[\_ s*]" start = " (\_ s*::\_ s*)"
450
461
\ matchgroup= NONE end = " \(\< type\>\|\< exception\>\|\< val\>\|\< module\>\|\< class\>\|\< method\>\|\< constraint\>\|\< inherit\>\|\< object\>\|\< struct\>\|\< open\>\|\< include\>\|\< let\>\|\< external\>\|\< in\>\|\< end\>\| )\| ]\| }\| ;\| ;;\| =\)\@ ="
451
462
\ matchgroup= NONE end = " \(\< and\>\)\@ ="
452
- \ contains= ocamlTypeSumBar,ocamlTypeSumConstr,ocamlTypeSumAnnot,ocamlTypeBlank,ocamlComment ,ocamlPpx
463
+ \ contains= ocamlTypeSumBar,ocamlTypeSumConstr,ocamlTypeSumAnnot,ocamlTypeBlank,@o camlCommentLike ,ocamlPpx
453
464
hi link ocamlTypeSumDecl ocamlTypeCatchAll
454
465
syn cluster ocamlTypeContained add =ocamlTypeSumBar
455
466
syn match ocamlTypeSumBar contained " |"
@@ -469,15 +480,15 @@ syn region ocamlTypeSumAnnot contained
469
480
\ matchgroup= NONE end = " |\@ ="
470
481
\ matchgroup= NONE end = " \(\< type\>\|\< exception\>\|\< val\>\|\< module\>\|\< class\>\|\< method\>\|\< constraint\>\|\< inherit\>\|\< object\>\|\< struct\>\|\< open\>\|\< include\>\|\< let\>\|\< external\>\|\< in\>\|\< end\>\| )\| ]\| }\| ;\| ;;\)\@ ="
471
482
\ matchgroup= NONE end = " \(\< and\>\)\@ ="
472
- \ contains= @o camlTypeExpr,ocamlTypeRecordDecl,ocamlComment ,ocamlPpx
483
+ \ contains= @o camlTypeExpr,ocamlTypeRecordDecl,@o camlCommentLike ,ocamlPpx
473
484
hi link ocamlTypeSumAnnot ocamlTypeCatchAll
474
485
475
486
" Type context opened by “type” (type definition), “constraint” (type
476
487
" constraint) and “exception” (exception definition)
477
488
syn region ocamlTypeDef
478
489
\ matchgroup= ocamlKeyword start = " \< type\>\(\_ s\+\< nonrec\>\)\?\|\< constraint\>\|\< exception\> "
479
490
\ 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
491
+ \ contains= @o camlTypeExpr,ocamlTypeEq,ocamlTypePrivate,ocamlTypeDefDots,ocamlTypeRecordDecl,ocamlTypeSumDecl,ocamlTypeDefAnd,@o camlCommentLike ,ocamlPpx
481
492
hi link ocamlTypeDef ocamlTypeCatchAll
482
493
syn cluster ocamlTypeContained add =ocamlTypePrivate
483
494
syn keyword ocamlTypePrivate contained private
@@ -503,7 +514,7 @@ syn region ocamlTypeAnnot matchgroup=ocamlKeyChar start=":\(>\|\_s*type\>\|[>:=]
503
514
\ matchgroup= NONE end = " \(\< type\>\|\< exception\>\|\< val\>\|\< module\>\|\< class\>\|\< method\>\|\< constraint\>\|\< inherit\>\|\< object\>\|\< struct\>\|\< open\>\|\< include\>\|\< let\>\|\< external\>\|\< in\>\|\< end\>\| )\| ]\| }\| ;\| ;;\)\@ ="
504
515
\ matchgroup= NONE end = " \( ;\| }\)\@ ="
505
516
\ matchgroup= NONE end = " \( =\| :>\)\@ ="
506
- \ contains= @o camlTypeExpr,ocamlComment ,ocamlPpx
517
+ \ contains= @o camlTypeExpr,@o camlCommentLike ,ocamlPpx
507
518
hi link ocamlTypeAnnot ocamlTypeCatchAll
508
519
509
520
" Type annotation that gives the return type of a `fun` keyword
@@ -512,7 +523,7 @@ syn cluster ocamlTypeContained add=ocamlFunTypeAnnot
512
523
syn region ocamlFunTypeAnnot contained containedin =ocamlFun
513
524
\ matchgroup= ocamlKeyChar start = " :"
514
525
\ matchgroup= NONE end = " \( ->\)\@ ="
515
- \ contains= @o camlTypeExpr,ocamlComment ,ocamlPpx
526
+ \ contains= @o camlTypeExpr,@o camlCommentLike ,ocamlPpx
516
527
hi link ocamlFunTypeAnnot ocamlTypeCatchAll
517
528
518
529
" Module paths (including functors) in types.
@@ -525,14 +536,14 @@ syn match ocamlTypeModPath contained "\<\u\(\w\|'\)*\_s*\."
525
536
syn region ocamlTypeModPath contained transparent
526
537
\ matchgroup= ocamlModPath start = " \<\u\(\w\| '\) *\_ s*(\*\@ !"
527
538
\ matchgroup= ocamlModPath end = " )\_ s*\. "
528
- \ contains= ocamlTypeDotlessModPath,ocamlTypeBlank,ocamlComment ,ocamlPpx
539
+ \ contains= ocamlTypeDotlessModPath,ocamlTypeBlank,@o camlCommentLike ,ocamlPpx
529
540
hi link ocamlTypeModPath ocamlModPath
530
541
syn cluster ocamlTypeContained add =ocamlTypeDotlessModPath
531
542
syn match ocamlTypeDotlessModPath contained " \<\u\(\w\| '\) *\_ s*\.\? "
532
543
syn region ocamlTypeDotlessModPath contained transparent
533
544
\ matchgroup= ocamlModPath start = " \<\u\(\w\| '\) *\_ s*(\*\@ !"
534
545
\ matchgroup= ocamlModPath end = " )\_ s*\.\? "
535
- \ contains= ocamlTypeDotlessModPath,ocamlTypeBlank,ocamlComment ,ocamlPpx
546
+ \ contains= ocamlTypeDotlessModPath,ocamlTypeBlank,@o camlCommentLike ,ocamlPpx
536
547
hi link ocamlTypeDotlessModPath ocamlTypeModPath
537
548
538
549
" """""""""""""""""""""""""""""""""""""""""""""""""""""""""""""""""""""""""""""""
@@ -577,6 +588,9 @@ hi def link ocamlCharErr Error
577
588
hi def link ocamlErr Error
578
589
579
590
hi def link ocamlComment Comment
591
+ hi def link ocamlDocEncl ocamlComment
592
+ hi def link ocamlCommentInDoc ocamlComment
593
+ hi def link ocamlStopComment PreProc
580
594
hi def link ocamlShebang ocamlComment
581
595
582
596
hi def link ocamlModPath Include
@@ -662,7 +676,11 @@ hi def link ocamlPpxEncl ocamlEncl
662
676
663
677
let b: current_syntax = " ocaml"
664
678
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
667
685
668
686
" vim: ts = 8
0 commit comments