blob: 721bceb367dcca21c30cdb1b43be8ebc3d5d4ebc [file] [log] [blame]
Bram Moolenaar071d4272004-06-13 20:20:40 +00001" Vim syntax file
2" Language: FORTH
Bram Moolenaar25a6e8a2018-03-30 12:27:32 +02003" Current Maintainer: Johan Kotlinski <kotlinski@gmail.com>
Bram Moolenaarcb80aa22020-10-26 21:12:46 +01004" Previous Maintainer: Christian V. J. BrΓΌssow <cvjb@cvjb.de>
Bram Moolenaar25a6e8a2018-03-30 12:27:32 +02005" Last Change: 2018-03-29
Bram Moolenaar071d4272004-06-13 20:20:40 +00006" Filenames: *.fs,*.ft
Bram Moolenaar25a6e8a2018-03-30 12:27:32 +02007" URL: https://github.com/jkotlinski/forth.vim
Bram Moolenaar071d4272004-06-13 20:20:40 +00008
Bram Moolenaar89bcfda2016-08-30 23:26:57 +02009" quit when a syntax file was already loaded
10if exists("b:current_syntax")
Bram Moolenaar071d4272004-06-13 20:20:40 +000011 finish
12endif
13
Bram Moolenaar6ee8d892012-01-10 14:55:01 +010014let s:cpo_save = &cpo
15set cpo&vim
16
Bram Moolenaar071d4272004-06-13 20:20:40 +000017" Synchronization method
Bram Moolenaar8299df92004-07-10 09:47:34 +000018syn sync ccomment
19syn sync maxlines=200
Bram Moolenaar071d4272004-06-13 20:20:40 +000020
21" I use gforth, so I set this to case ignore
22syn case ignore
23
24" Some special, non-FORTH keywords
25syn keyword forthTodo contained TODO FIXME XXX
26syn match forthTodo contained 'Copyright\(\s([Cc])\)\=\(\s[0-9]\{2,4}\)\='
27
28" Characters allowed in keywords
Bram Moolenaare37d50a2008-08-06 17:06:04 +000029" I don't know if 128-255 are allowed in ANS-FORTH
Bram Moolenaar89bcfda2016-08-30 23:26:57 +020030setlocal iskeyword=!,@,33-35,%,$,38-64,A-Z,91-96,a-z,123-126,128-255
Bram Moolenaar071d4272004-06-13 20:20:40 +000031
Bram Moolenaar3577c6f2008-06-24 21:16:56 +000032" when wanted, highlight trailing white space
33if exists("forth_space_errors")
34 if !exists("forth_no_trail_space_error")
35 syn match forthSpaceError display excludenl "\s\+$"
36 endif
37 if !exists("forth_no_tab_space_error")
38 syn match forthSpaceError display " \+\t"me=e-1
39 endif
40endif
Bram Moolenaar071d4272004-06-13 20:20:40 +000041
42" Keywords
43
44" basic mathematical and logical operators
45syn keyword forthOperators + - * / MOD /MOD NEGATE ABS MIN MAX
Bram Moolenaare37d50a2008-08-06 17:06:04 +000046syn keyword forthOperators AND OR XOR NOT LSHIFT RSHIFT INVERT 2* 2/ 1+
47syn keyword forthOperators 1- 2+ 2- 8* UNDER+
Bram Moolenaar071d4272004-06-13 20:20:40 +000048syn keyword forthOperators M+ */ */MOD M* UM* M*/ UM/MOD FM/MOD SM/REM
Bram Moolenaare37d50a2008-08-06 17:06:04 +000049syn keyword forthOperators D+ D- DNEGATE DABS DMIN DMAX D2* D2/
Bram Moolenaar071d4272004-06-13 20:20:40 +000050syn keyword forthOperators F+ F- F* F/ FNEGATE FABS FMAX FMIN FLOOR FROUND
51syn keyword forthOperators F** FSQRT FEXP FEXPM1 FLN FLNP1 FLOG FALOG FSIN
52syn keyword forthOperators FCOS FSINCOS FTAN FASIN FACOS FATAN FATAN2 FSINH
Bram Moolenaare37d50a2008-08-06 17:06:04 +000053syn keyword forthOperators FCOSH FTANH FASINH FACOSH FATANH F2* F2/ 1/F
54syn keyword forthOperators F~REL F~ABS F~
55syn keyword forthOperators 0< 0<= 0<> 0= 0> 0>= < <= <> = > >= U< U<=
56syn keyword forthOperators U> U>= D0< D0<= D0<> D0= D0> D0>= D< D<= D<>
57syn keyword forthOperators D= D> D>= DU< DU<= DU> DU>= WITHIN ?NEGATE
Bram Moolenaar25a6e8a2018-03-30 12:27:32 +020058syn keyword forthOperators ?DNEGATE TRUE FALSE
59
60" various words that take an input and do something with it
61syn keyword forthFunction . U. .R U.R
Bram Moolenaar071d4272004-06-13 20:20:40 +000062
63" stack manipulations
64syn keyword forthStack DROP NIP DUP OVER TUCK SWAP ROT -ROT ?DUP PICK ROLL
Bram Moolenaare37d50a2008-08-06 17:06:04 +000065syn keyword forthStack 2DROP 2NIP 2DUP 2OVER 2TUCK 2SWAP 2ROT 2-ROT
66syn keyword forthStack 3DUP 4DUP 5DUP 3DROP 4DROP 5DROP 8DROP 4SWAP 4ROT
67syn keyword forthStack 4-ROT 4TUCK 8SWAP 8DUP
Bram Moolenaar071d4272004-06-13 20:20:40 +000068syn keyword forthRStack >R R> R@ RDROP 2>R 2R> 2R@ 2RDROP
Bram Moolenaare37d50a2008-08-06 17:06:04 +000069syn keyword forthRstack 4>R 4R> 4R@ 4RDROP
Bram Moolenaar071d4272004-06-13 20:20:40 +000070syn keyword forthFStack FDROP FNIP FDUP FOVER FTUCK FSWAP FROT
71
72" stack pointer manipulations
Bram Moolenaar25a6e8a2018-03-30 12:27:32 +020073syn keyword forthSP SP@ SP! FP@ FP! RP@ RP! LP@ LP! DEPTH
Bram Moolenaar071d4272004-06-13 20:20:40 +000074
75" address operations
76syn keyword forthMemory @ ! +! C@ C! 2@ 2! F@ F! SF@ SF! DF@ DF!
77syn keyword forthAdrArith CHARS CHAR+ CELLS CELL+ CELL ALIGN ALIGNED FLOATS
78syn keyword forthAdrArith FLOAT+ FLOAT FALIGN FALIGNED SFLOATS SFLOAT+
79syn keyword forthAdrArith SFALIGN SFALIGNED DFLOATS DFLOAT+ DFALIGN DFALIGNED
80syn keyword forthAdrArith MAXALIGN MAXALIGNED CFALIGN CFALIGNED
81syn keyword forthAdrArith ADDRESS-UNIT-BITS ALLOT ALLOCATE HERE
Bram Moolenaar25a6e8a2018-03-30 12:27:32 +020082syn keyword forthMemBlks MOVE ERASE CMOVE CMOVE> FILL BLANK UNUSED
Bram Moolenaar071d4272004-06-13 20:20:40 +000083
84" conditionals
85syn keyword forthCond IF ELSE ENDIF THEN CASE OF ENDOF ENDCASE ?DUP-IF
86syn keyword forthCond ?DUP-0=-IF AHEAD CS-PICK CS-ROLL CATCH THROW WITHIN
87
88" iterations
89syn keyword forthLoop BEGIN WHILE REPEAT UNTIL AGAIN
90syn keyword forthLoop ?DO LOOP I J K +DO U+DO -DO U-DO DO +LOOP -LOOP
Bram Moolenaar25a6e8a2018-03-30 12:27:32 +020091syn keyword forthLoop UNLOOP LEAVE ?LEAVE EXIT DONE FOR NEXT RECURSE
Bram Moolenaar071d4272004-06-13 20:20:40 +000092
93" new words
Bram Moolenaare37d50a2008-08-06 17:06:04 +000094syn match forthClassDef '\<:class\s*[^ \t]\+\>'
95syn match forthObjectDef '\<:object\s*[^ \t]\+\>'
Bram Moolenaar071d4272004-06-13 20:20:40 +000096syn match forthColonDef '\<:m\?\s*[^ \t]\+\>'
97syn keyword forthEndOfColonDef ; ;M ;m
Bram Moolenaare37d50a2008-08-06 17:06:04 +000098syn keyword forthEndOfClassDef ;class
99syn keyword forthEndOfObjectDef ;object
100syn keyword forthDefine CONSTANT 2CONSTANT FCONSTANT VARIABLE 2VARIABLE
101syn keyword forthDefine FVARIABLE CREATE USER VALUE TO DEFER IS DOES> IMMEDIATE
102syn keyword forthDefine COMPILE-ONLY COMPILE RESTRICT INTERPRET POSTPONE EXECUTE
103syn keyword forthDefine LITERAL CREATE-INTERPRET/COMPILE INTERPRETATION>
104syn keyword forthDefine <INTERPRETATION COMPILATION> <COMPILATION ] LASTXT
105syn keyword forthDefine COMP' POSTPONE, FIND-NAME NAME>INT NAME?INT NAME>COMP
Bram Moolenaar25a6e8a2018-03-30 12:27:32 +0200106syn keyword forthDefine NAME>STRING STATE C; CVARIABLE BUFFER: MARKER
107syn keyword forthDefine , 2, F, C, COMPILE,
Bram Moolenaare37d50a2008-08-06 17:06:04 +0000108syn match forthDefine "\[IFDEF]"
109syn match forthDefine "\[IFUNDEF]"
110syn match forthDefine "\[THEN]"
111syn match forthDefine "\[ENDIF]"
112syn match forthDefine "\[ELSE]"
113syn match forthDefine "\[?DO]"
114syn match forthDefine "\[DO]"
115syn match forthDefine "\[LOOP]"
116syn match forthDefine "\[+LOOP]"
117syn match forthDefine "\[NEXT]"
118syn match forthDefine "\[BEGIN]"
119syn match forthDefine "\[UNTIL]"
120syn match forthDefine "\[AGAIN]"
121syn match forthDefine "\[WHILE]"
122syn match forthDefine "\[REPEAT]"
Bram Moolenaar071d4272004-06-13 20:20:40 +0000123syn match forthDefine "\[COMP']"
124syn match forthDefine "'"
125syn match forthDefine '\<\[\>'
126syn match forthDefine "\[']"
127syn match forthDefine '\[COMPILE]'
Bram Moolenaar25a6e8a2018-03-30 12:27:32 +0200128syn match forthDefine '\[CHAR]'
Bram Moolenaar071d4272004-06-13 20:20:40 +0000129
130" debugging
131syn keyword forthDebug PRINTDEBUGDATA PRINTDEBUGLINE
132syn match forthDebug "\<\~\~\>"
133
134" Assembler
135syn keyword forthAssembler ASSEMBLER CODE END-CODE ;CODE FLUSH-ICACHE C,
136
137" basic character operations
138syn keyword forthCharOps (.) CHAR EXPECT FIND WORD TYPE -TRAILING EMIT KEY
Bram Moolenaar25a6e8a2018-03-30 12:27:32 +0200139syn keyword forthCharOps KEY? TIB CR BL COUNT SPACE SPACES
Bram Moolenaar071d4272004-06-13 20:20:40 +0000140" recognize 'char (' or '[char] (' correctly, so it doesn't
141" highlight everything after the paren as a comment till a closing ')'
142syn match forthCharOps '\<char\s\S\s'
143syn match forthCharOps '\<\[char\]\s\S\s'
144syn region forthCharOps start=+."\s+ skip=+\\"+ end=+"+
145
146" char-number conversion
Bram Moolenaar6ee8d892012-01-10 14:55:01 +0100147syn keyword forthConversion <<# <# # #> #>> #S (NUMBER) (NUMBER?) CONVERT D>F
Bram Moolenaare37d50a2008-08-06 17:06:04 +0000148syn keyword forthConversion D>S DIGIT DPL F>D HLD HOLD NUMBER S>D SIGN >NUMBER
Bram Moolenaar25a6e8a2018-03-30 12:27:32 +0200149syn keyword forthConversion F>S S>F HOLDS
Bram Moolenaar071d4272004-06-13 20:20:40 +0000150
Bram Moolenaarcdf04202010-05-29 15:11:47 +0200151" interpreter, wordbook, compiler
Bram Moolenaar071d4272004-06-13 20:20:40 +0000152syn keyword forthForth (LOCAL) BYE COLD ABORT >BODY >NEXT >LINK CFA >VIEW HERE
153syn keyword forthForth PAD WORDS VIEW VIEW> N>LINK NAME> LINK> L>NAME FORGET
Bram Moolenaare37d50a2008-08-06 17:06:04 +0000154syn keyword forthForth BODY> ASSERT( ASSERT0( ASSERT1( ASSERT2( ASSERT3( )
Bram Moolenaar25a6e8a2018-03-30 12:27:32 +0200155syn keyword forthForth >IN ACCEPT ENVIRONMENT? EVALUATE QUIT SOURCE ACTION-OF
156syn keyword forthForth DEFER! DEFER@ PARSE PARSE-NAME REFILL RESTORE-INPUT
157syn keyword forthForth SAVE-INPUT SOURCE-ID
Bram Moolenaar071d4272004-06-13 20:20:40 +0000158syn region forthForth start=+ABORT"\s+ skip=+\\"+ end=+"+
159
160" vocabularies
161syn keyword forthVocs ONLY FORTH ALSO ROOT SEAL VOCS ORDER CONTEXT #VOCS
162syn keyword forthVocs VOCABULARY DEFINITIONS
163
Bram Moolenaare37d50a2008-08-06 17:06:04 +0000164" File keywords
Bram Moolenaar6ee8d892012-01-10 14:55:01 +0100165syn keyword forthFileMode R/O R/W W/O BIN
Bram Moolenaare37d50a2008-08-06 17:06:04 +0000166syn keyword forthFileWords OPEN-FILE CREATE-FILE CLOSE-FILE DELETE-FILE
167syn keyword forthFileWords RENAME-FILE READ-FILE READ-LINE KEY-FILE
168syn keyword forthFileWords KEY?-FILE WRITE-FILE WRITE-LINE EMIT-FILE
169syn keyword forthFileWords FLUSH-FILE FILE-STATUS FILE-POSITION
170syn keyword forthFileWords REPOSITION-FILE FILE-SIZE RESIZE-FILE
171syn keyword forthFileWords SLURP-FILE SLURP-FID STDIN STDOUT STDERR
Bram Moolenaar25a6e8a2018-03-30 12:27:32 +0200172syn keyword forthFileWords INCLUDE-FILE INCLUDED REQUIRED
Bram Moolenaare37d50a2008-08-06 17:06:04 +0000173syn keyword forthBlocks OPEN-BLOCKS USE LOAD --> BLOCK-OFFSET
174syn keyword forthBlocks GET-BLOCK-FID BLOCK-POSITION LIST SCR BLOCK
175syn keyword forthBlocks BUFER EMPTY-BUFFERS EMPTY-BUFFER UPDATE UPDATED?
176syn keyword forthBlocks SAVE-BUFFERS SAVE-BUFFER FLUSH THRU +LOAD +THRU
Bram Moolenaar25a6e8a2018-03-30 12:27:32 +0200177syn keyword forthBlocks BLOCK-INCLUDED BLK
Bram Moolenaare37d50a2008-08-06 17:06:04 +0000178
Bram Moolenaar071d4272004-06-13 20:20:40 +0000179" numbers
180syn keyword forthMath DECIMAL HEX BASE
Bram Moolenaar25a6e8a2018-03-30 12:27:32 +0200181syn match forthInteger '\<-\=[0-9]\+.\=\>'
182syn match forthInteger '\<&-\=[0-9]\+.\=\>'
Bram Moolenaar071d4272004-06-13 20:20:40 +0000183" recognize hex and binary numbers, the '$' and '%' notation is for gforth
Bram Moolenaar6c391a72021-09-09 21:55:11 +0200184syn match forthInteger '\<\$\x*\x\+\>' " *1* --- don't mess
Bram Moolenaar071d4272004-06-13 20:20:40 +0000185syn match forthInteger '\<\x*\d\x*\>' " *2* --- this order!
186syn match forthInteger '\<%[0-1]*[0-1]\+\>'
Bram Moolenaare37d50a2008-08-06 17:06:04 +0000187syn match forthFloat '\<-\=\d*[.]\=\d\+[DdEe]\d\+\>'
188syn match forthFloat '\<-\=\d*[.]\=\d\+[DdEe][-+]\d\+\>'
189
Bram Moolenaar25a6e8a2018-03-30 12:27:32 +0200190" XXX If you find this overkill you can remove it. this has to come after the
Bram Moolenaare37d50a2008-08-06 17:06:04 +0000191" highlighting for numbers otherwise it has no effect.
192syn region forthComment start='0 \[if\]' end='\[endif\]' end='\[then\]' contains=forthTodo
Bram Moolenaar071d4272004-06-13 20:20:40 +0000193
194" Strings
Bram Moolenaar25a6e8a2018-03-30 12:27:32 +0200195syn region forthString start=+\.*\"+ end=+"+ end=+$+
Bram Moolenaar071d4272004-06-13 20:20:40 +0000196" XXX
Bram Moolenaar25a6e8a2018-03-30 12:27:32 +0200197syn region forthString start=+s\"+ end=+"+ end=+$+
198syn region forthString start=+s\\\"+ end=+"+ end=+$+
199syn region forthString start=+c\"+ end=+"+ end=+$+
Bram Moolenaar071d4272004-06-13 20:20:40 +0000200
201" Comments
Bram Moolenaar25a6e8a2018-03-30 12:27:32 +0200202syn match forthComment '\\\s.*$' contains=forthTodo,forthSpaceError
203syn region forthComment start='\\S\s' end='.*' contains=forthTodo,forthSpaceError
204syn match forthComment '\.(\s[^)]*)' contains=forthTodo,forthSpaceError
205syn region forthComment start='\(^\|\s\)\zs(\s' skip='\\)' end=')' contains=forthTodo,forthSpaceError
206syn region forthComment start='/\*' end='\*/' contains=forthTodo,forthSpaceError
Bram Moolenaar071d4272004-06-13 20:20:40 +0000207
208" Include files
209syn match forthInclude '^INCLUDE\s\+\k\+'
Bram Moolenaar25a6e8a2018-03-30 12:27:32 +0200210syn match forthInclude '^REQUIRE\s\+\k\+'
211syn match forthInclude '^FLOAD\s\+'
212syn match forthInclude '^NEEDS\s\+'
Bram Moolenaar071d4272004-06-13 20:20:40 +0000213
Bram Moolenaare37d50a2008-08-06 17:06:04 +0000214" Locals definitions
215syn region forthLocals start='{\s' start='{$' end='\s}' end='^}'
216syn match forthLocals '{ }' " otherwise, at least two spaces between
217syn region forthDeprecated start='locals|' end='|'
218
Bram Moolenaar071d4272004-06-13 20:20:40 +0000219" Define the default highlighting.
Bram Moolenaarf37506f2016-08-31 22:22:10 +0200220hi def link forthTodo Todo
221hi def link forthOperators Operator
222hi def link forthMath Number
223hi def link forthInteger Number
224hi def link forthFloat Float
225hi def link forthStack Special
226hi def link forthRstack Special
227hi def link forthFStack Special
228hi def link forthSP Special
229hi def link forthMemory Function
230hi def link forthAdrArith Function
231hi def link forthMemBlks Function
232hi def link forthCond Conditional
233hi def link forthLoop Repeat
234hi def link forthColonDef Define
235hi def link forthEndOfColonDef Define
236hi def link forthDefine Define
237hi def link forthDebug Debug
238hi def link forthAssembler Include
239hi def link forthCharOps Character
240hi def link forthConversion String
241hi def link forthForth Statement
242hi def link forthVocs Statement
243hi def link forthString String
244hi def link forthComment Comment
245hi def link forthClassDef Define
246hi def link forthEndOfClassDef Define
247hi def link forthObjectDef Define
248hi def link forthEndOfObjectDef Define
249hi def link forthInclude Include
250hi def link forthLocals Type " nothing else uses type and locals must stand out
251hi def link forthDeprecated Error " if you must, change to Type
252hi def link forthFileMode Function
Bram Moolenaar25a6e8a2018-03-30 12:27:32 +0200253hi def link forthFunction Function
Bram Moolenaarf37506f2016-08-31 22:22:10 +0200254hi def link forthFileWords Statement
255hi def link forthBlocks Statement
256hi def link forthSpaceError Error
Bram Moolenaar071d4272004-06-13 20:20:40 +0000257
Bram Moolenaar071d4272004-06-13 20:20:40 +0000258let b:current_syntax = "forth"
259
Bram Moolenaar6ee8d892012-01-10 14:55:01 +0100260let &cpo = s:cpo_save
261unlet s:cpo_save
Bram Moolenaar071d4272004-06-13 20:20:40 +0000262" vim:ts=8:sw=4:nocindent:smartindent: