blob: 8713a721a8abb143cd864d30e619db07977e14b6 [file] [log] [blame]
Bram Moolenaar071d4272004-06-13 20:20:40 +00001" Vim syntax file
2" Language: FORTH
3" Maintainer: Christian V. J. Brüssow <cvjb@cvjb.de>
Bram Moolenaare37d50a2008-08-06 17:06:04 +00004" Last Change: Sa 09 Feb 2008 13:27:29 CET
Bram Moolenaar071d4272004-06-13 20:20:40 +00005" Filenames: *.fs,*.ft
Bram Moolenaar3577c6f2008-06-24 21:16:56 +00006" URL: http://www.cvjb.de/comp/vim/forth.vim
Bram Moolenaar071d4272004-06-13 20:20:40 +00007
8" $Id$
9
10" The list of keywords is incomplete, compared with the offical ANS
11" wordlist. If you use this language, please improve it, and send me
12" the patches.
Bram Moolenaare37d50a2008-08-06 17:06:04 +000013"
14" Before sending me patches, please download the newest version of this file
15" from http://www.cvjb.de/comp/vim/forth.vim or http://www.vim.org/ (search
16" for forth.vim).
Bram Moolenaar071d4272004-06-13 20:20:40 +000017
18" Many Thanks to...
19"
Bram Moolenaare37d50a2008-08-06 17:06:04 +000020" 2008-02-09:
21" Shawn K. Quinn <sjquinn at speakeasy dot net> send a big patch with
22" new words commonly used in Forth programs or defined by GNU Forth.
23"
Bram Moolenaar3577c6f2008-06-24 21:16:56 +000024" 2007-07-11:
25" Benjamin Krill <ben at codiert dot org> send me a patch
26" to highlight space errors.
27" You can toggle this feature on through setting the
28" flag forth_space_errors in you vimrc. If you have switched it on,
29" you can turn off highlighting of trailing spaces in comments by
30" setting forth_no_trail_space_error in your vimrc. If you do not want
31" the highlighting of a tabulator following a space in comments, you
32" can turn this off by setting forth_no_tab_space_error.
Bram Moolenaar8299df92004-07-10 09:47:34 +000033"
Bram Moolenaar3577c6f2008-06-24 21:16:56 +000034" 2006-05-25:
35" Bill McCarthy <WJMc@...> and Ilya Sher <ilya-vim@...>
36" Who found a bug in the ccomment line in 2004!!!
37" I'm really very sorry, that it has taken two years to fix that
38" in the offical version of this file. Shame on me.
39" I think my face will be red the next ten years...
40"
41" 2006-05-21:
42" Thomas E. Vaughan <tevaugha at ball dot com> send me a patch
43" for the parenthesis comment word, so words with a trailing
44" parenthesis will not start the highlighting for such comments.
45"
Bram Moolenaar071d4272004-06-13 20:20:40 +000046" 2003-05-10:
47" Andrew Gaul <andrew at gaul.org> send me a patch for
48" forthOperators.
49"
50" 2003-04-03:
Bram Moolenaar3577c6f2008-06-24 21:16:56 +000051" Ron Aaron <ron at ronware dot org> made updates for an
Bram Moolenaar071d4272004-06-13 20:20:40 +000052" improved Win32Forth support.
53"
54" 2002-04-22:
Bram Moolenaar3577c6f2008-06-24 21:16:56 +000055" Charles Shattuck <charley at forth dot org> helped me to settle up with the
Bram Moolenaar071d4272004-06-13 20:20:40 +000056" binary and hex number highlighting.
57"
58" 2002-04-20:
Bram Moolenaar3577c6f2008-06-24 21:16:56 +000059" Charles Shattuck <charley at forth dot org> send me some code for correctly
Bram Moolenaar071d4272004-06-13 20:20:40 +000060" highlighting char and [char] followed by an opening paren. He also added
61" some words for operators, conditionals, and definitions; and added the
62" highlighting for s" and c".
63"
64" 2000-03-28:
Bram Moolenaar3577c6f2008-06-24 21:16:56 +000065" John Providenza <john at probo dot com> made improvements for the
Bram Moolenaar071d4272004-06-13 20:20:40 +000066" highlighting of strings, and added the code for highlighting hex numbers.
67"
68
69
70" For version 5.x: Clear all syntax items
71" For version 6.x: Quit when a syntax file was already loaded
72if version < 600
73 syntax clear
74elseif exists("b:current_syntax")
75 finish
76endif
77
78" Synchronization method
Bram Moolenaar8299df92004-07-10 09:47:34 +000079syn sync ccomment
80syn sync maxlines=200
Bram Moolenaar071d4272004-06-13 20:20:40 +000081
82" I use gforth, so I set this to case ignore
83syn case ignore
84
85" Some special, non-FORTH keywords
86syn keyword forthTodo contained TODO FIXME XXX
87syn match forthTodo contained 'Copyright\(\s([Cc])\)\=\(\s[0-9]\{2,4}\)\='
88
89" Characters allowed in keywords
Bram Moolenaare37d50a2008-08-06 17:06:04 +000090" I don't know if 128-255 are allowed in ANS-FORTH
Bram Moolenaar071d4272004-06-13 20:20:40 +000091if version >= 600
92 setlocal iskeyword=!,@,33-35,%,$,38-64,A-Z,91-96,a-z,123-126,128-255
93else
94 set iskeyword=!,@,33-35,%,$,38-64,A-Z,91-96,a-z,123-126,128-255
95endif
96
Bram Moolenaar3577c6f2008-06-24 21:16:56 +000097" when wanted, highlight trailing white space
98if exists("forth_space_errors")
99 if !exists("forth_no_trail_space_error")
100 syn match forthSpaceError display excludenl "\s\+$"
101 endif
102 if !exists("forth_no_tab_space_error")
103 syn match forthSpaceError display " \+\t"me=e-1
104 endif
105endif
Bram Moolenaar071d4272004-06-13 20:20:40 +0000106
107" Keywords
108
109" basic mathematical and logical operators
110syn keyword forthOperators + - * / MOD /MOD NEGATE ABS MIN MAX
Bram Moolenaare37d50a2008-08-06 17:06:04 +0000111syn keyword forthOperators AND OR XOR NOT LSHIFT RSHIFT INVERT 2* 2/ 1+
112syn keyword forthOperators 1- 2+ 2- 8* UNDER+
Bram Moolenaar071d4272004-06-13 20:20:40 +0000113syn keyword forthOperators M+ */ */MOD M* UM* M*/ UM/MOD FM/MOD SM/REM
Bram Moolenaare37d50a2008-08-06 17:06:04 +0000114syn keyword forthOperators D+ D- DNEGATE DABS DMIN DMAX D2* D2/
Bram Moolenaar071d4272004-06-13 20:20:40 +0000115syn keyword forthOperators F+ F- F* F/ FNEGATE FABS FMAX FMIN FLOOR FROUND
116syn keyword forthOperators F** FSQRT FEXP FEXPM1 FLN FLNP1 FLOG FALOG FSIN
117syn keyword forthOperators FCOS FSINCOS FTAN FASIN FACOS FATAN FATAN2 FSINH
Bram Moolenaare37d50a2008-08-06 17:06:04 +0000118syn keyword forthOperators FCOSH FTANH FASINH FACOSH FATANH F2* F2/ 1/F
119syn keyword forthOperators F~REL F~ABS F~
120syn keyword forthOperators 0< 0<= 0<> 0= 0> 0>= < <= <> = > >= U< U<=
121syn keyword forthOperators U> U>= D0< D0<= D0<> D0= D0> D0>= D< D<= D<>
122syn keyword forthOperators D= D> D>= DU< DU<= DU> DU>= WITHIN ?NEGATE
123syn keyword forthOperators ?DNEGATE
Bram Moolenaar071d4272004-06-13 20:20:40 +0000124
125" stack manipulations
126syn keyword forthStack DROP NIP DUP OVER TUCK SWAP ROT -ROT ?DUP PICK ROLL
Bram Moolenaare37d50a2008-08-06 17:06:04 +0000127syn keyword forthStack 2DROP 2NIP 2DUP 2OVER 2TUCK 2SWAP 2ROT 2-ROT
128syn keyword forthStack 3DUP 4DUP 5DUP 3DROP 4DROP 5DROP 8DROP 4SWAP 4ROT
129syn keyword forthStack 4-ROT 4TUCK 8SWAP 8DUP
Bram Moolenaar071d4272004-06-13 20:20:40 +0000130syn keyword forthRStack >R R> R@ RDROP 2>R 2R> 2R@ 2RDROP
Bram Moolenaare37d50a2008-08-06 17:06:04 +0000131syn keyword forthRstack 4>R 4R> 4R@ 4RDROP
Bram Moolenaar071d4272004-06-13 20:20:40 +0000132syn keyword forthFStack FDROP FNIP FDUP FOVER FTUCK FSWAP FROT
133
134" stack pointer manipulations
135syn keyword forthSP SP@ SP! FP@ FP! RP@ RP! LP@ LP!
136
137" address operations
138syn keyword forthMemory @ ! +! C@ C! 2@ 2! F@ F! SF@ SF! DF@ DF!
139syn keyword forthAdrArith CHARS CHAR+ CELLS CELL+ CELL ALIGN ALIGNED FLOATS
140syn keyword forthAdrArith FLOAT+ FLOAT FALIGN FALIGNED SFLOATS SFLOAT+
141syn keyword forthAdrArith SFALIGN SFALIGNED DFLOATS DFLOAT+ DFALIGN DFALIGNED
142syn keyword forthAdrArith MAXALIGN MAXALIGNED CFALIGN CFALIGNED
143syn keyword forthAdrArith ADDRESS-UNIT-BITS ALLOT ALLOCATE HERE
144syn keyword forthMemBlks MOVE ERASE CMOVE CMOVE> FILL BLANK
145
146" conditionals
147syn keyword forthCond IF ELSE ENDIF THEN CASE OF ENDOF ENDCASE ?DUP-IF
148syn keyword forthCond ?DUP-0=-IF AHEAD CS-PICK CS-ROLL CATCH THROW WITHIN
149
150" iterations
151syn keyword forthLoop BEGIN WHILE REPEAT UNTIL AGAIN
152syn keyword forthLoop ?DO LOOP I J K +DO U+DO -DO U-DO DO +LOOP -LOOP
153syn keyword forthLoop UNLOOP LEAVE ?LEAVE EXIT DONE FOR NEXT
154
155" new words
Bram Moolenaare37d50a2008-08-06 17:06:04 +0000156syn match forthClassDef '\<:class\s*[^ \t]\+\>'
157syn match forthObjectDef '\<:object\s*[^ \t]\+\>'
Bram Moolenaar071d4272004-06-13 20:20:40 +0000158syn match forthColonDef '\<:m\?\s*[^ \t]\+\>'
159syn keyword forthEndOfColonDef ; ;M ;m
Bram Moolenaare37d50a2008-08-06 17:06:04 +0000160syn keyword forthEndOfClassDef ;class
161syn keyword forthEndOfObjectDef ;object
162syn keyword forthDefine CONSTANT 2CONSTANT FCONSTANT VARIABLE 2VARIABLE
163syn keyword forthDefine FVARIABLE CREATE USER VALUE TO DEFER IS DOES> IMMEDIATE
164syn keyword forthDefine COMPILE-ONLY COMPILE RESTRICT INTERPRET POSTPONE EXECUTE
165syn keyword forthDefine LITERAL CREATE-INTERPRET/COMPILE INTERPRETATION>
166syn keyword forthDefine <INTERPRETATION COMPILATION> <COMPILATION ] LASTXT
167syn keyword forthDefine COMP' POSTPONE, FIND-NAME NAME>INT NAME?INT NAME>COMP
168syn keyword forthDefine NAME>STRING STATE C; CVARIABLE
169syn keyword forthDefine , 2, F, C,
170syn match forthDefine "\[IFDEF]"
171syn match forthDefine "\[IFUNDEF]"
172syn match forthDefine "\[THEN]"
173syn match forthDefine "\[ENDIF]"
174syn match forthDefine "\[ELSE]"
175syn match forthDefine "\[?DO]"
176syn match forthDefine "\[DO]"
177syn match forthDefine "\[LOOP]"
178syn match forthDefine "\[+LOOP]"
179syn match forthDefine "\[NEXT]"
180syn match forthDefine "\[BEGIN]"
181syn match forthDefine "\[UNTIL]"
182syn match forthDefine "\[AGAIN]"
183syn match forthDefine "\[WHILE]"
184syn match forthDefine "\[REPEAT]"
Bram Moolenaar071d4272004-06-13 20:20:40 +0000185syn match forthDefine "\[COMP']"
186syn match forthDefine "'"
187syn match forthDefine '\<\[\>'
188syn match forthDefine "\[']"
189syn match forthDefine '\[COMPILE]'
Bram Moolenaar071d4272004-06-13 20:20:40 +0000190
191" debugging
192syn keyword forthDebug PRINTDEBUGDATA PRINTDEBUGLINE
193syn match forthDebug "\<\~\~\>"
194
195" Assembler
196syn keyword forthAssembler ASSEMBLER CODE END-CODE ;CODE FLUSH-ICACHE C,
197
198" basic character operations
199syn keyword forthCharOps (.) CHAR EXPECT FIND WORD TYPE -TRAILING EMIT KEY
200syn keyword forthCharOps KEY? TIB CR
201" recognize 'char (' or '[char] (' correctly, so it doesn't
202" highlight everything after the paren as a comment till a closing ')'
203syn match forthCharOps '\<char\s\S\s'
204syn match forthCharOps '\<\[char\]\s\S\s'
205syn region forthCharOps start=+."\s+ skip=+\\"+ end=+"+
206
207" char-number conversion
Bram Moolenaare37d50a2008-08-06 17:06:04 +0000208syn keyword forthConversion <<# <# # #> #>> #S (NUMBER) (NUMBER?) CONVERT D>F
209syn keyword forthConversion D>S DIGIT DPL F>D HLD HOLD NUMBER S>D SIGN >NUMBER
210syn keyword forthConversion F>S S>F
Bram Moolenaar071d4272004-06-13 20:20:40 +0000211
212" interptreter, wordbook, compiler
213syn keyword forthForth (LOCAL) BYE COLD ABORT >BODY >NEXT >LINK CFA >VIEW HERE
214syn keyword forthForth PAD WORDS VIEW VIEW> N>LINK NAME> LINK> L>NAME FORGET
Bram Moolenaare37d50a2008-08-06 17:06:04 +0000215syn keyword forthForth BODY> ASSERT( ASSERT0( ASSERT1( ASSERT2( ASSERT3( )
Bram Moolenaar071d4272004-06-13 20:20:40 +0000216syn region forthForth start=+ABORT"\s+ skip=+\\"+ end=+"+
217
218" vocabularies
219syn keyword forthVocs ONLY FORTH ALSO ROOT SEAL VOCS ORDER CONTEXT #VOCS
220syn keyword forthVocs VOCABULARY DEFINITIONS
221
Bram Moolenaare37d50a2008-08-06 17:06:04 +0000222" File keywords
223syn keyword forthFileMode R/O R/W W/O BIN
224syn keyword forthFileWords OPEN-FILE CREATE-FILE CLOSE-FILE DELETE-FILE
225syn keyword forthFileWords RENAME-FILE READ-FILE READ-LINE KEY-FILE
226syn keyword forthFileWords KEY?-FILE WRITE-FILE WRITE-LINE EMIT-FILE
227syn keyword forthFileWords FLUSH-FILE FILE-STATUS FILE-POSITION
228syn keyword forthFileWords REPOSITION-FILE FILE-SIZE RESIZE-FILE
229syn keyword forthFileWords SLURP-FILE SLURP-FID STDIN STDOUT STDERR
230syn keyword forthBlocks OPEN-BLOCKS USE LOAD --> BLOCK-OFFSET
231syn keyword forthBlocks GET-BLOCK-FID BLOCK-POSITION LIST SCR BLOCK
232syn keyword forthBlocks BUFER EMPTY-BUFFERS EMPTY-BUFFER UPDATE UPDATED?
233syn keyword forthBlocks SAVE-BUFFERS SAVE-BUFFER FLUSH THRU +LOAD +THRU
234syn keyword forthBlocks BLOCK-INCLUDED
235
Bram Moolenaar071d4272004-06-13 20:20:40 +0000236" numbers
237syn keyword forthMath DECIMAL HEX BASE
238syn match forthInteger '\<-\=[0-9.]*[0-9.]\+\>'
Bram Moolenaare37d50a2008-08-06 17:06:04 +0000239syn match forthInteger '\<&-\=[0-9.]*[0-9.]\+\>'
Bram Moolenaar071d4272004-06-13 20:20:40 +0000240" recognize hex and binary numbers, the '$' and '%' notation is for gforth
241syn match forthInteger '\<\$\x*\x\+\>' " *1* --- dont't mess
242syn match forthInteger '\<\x*\d\x*\>' " *2* --- this order!
243syn match forthInteger '\<%[0-1]*[0-1]\+\>'
Bram Moolenaare37d50a2008-08-06 17:06:04 +0000244syn match forthFloat '\<-\=\d*[.]\=\d\+[DdEe]\d\+\>'
245syn match forthFloat '\<-\=\d*[.]\=\d\+[DdEe][-+]\d\+\>'
246
247" XXX If you find this overkill you can remove it. this has to come after the
248" highlighting for numbers otherwise it has no effect.
249syn region forthComment start='0 \[if\]' end='\[endif\]' end='\[then\]' contains=forthTodo
Bram Moolenaar071d4272004-06-13 20:20:40 +0000250
251" Strings
252syn region forthString start=+\.*\"+ end=+"+ end=+$+
253" XXX
254syn region forthString start=+s\"+ end=+"+ end=+$+
255syn region forthString start=+c\"+ end=+"+ end=+$+
256
257" Comments
Bram Moolenaar3577c6f2008-06-24 21:16:56 +0000258syn match forthComment '\\\s.*$' contains=forthTodo,forthSpaceError
259syn region forthComment start='\\S\s' end='.*' contains=forthTodo,forthSpaceError
260syn match forthComment '\.(\s[^)]*)' contains=forthTodo,forthSpaceError
261syn region forthComment start='\s(\s' skip='\\)' end=')' contains=forthTodo,forthSpaceError
262syn region forthComment start='/\*' end='\*/' contains=forthTodo,forthSpaceError
Bram Moolenaar071d4272004-06-13 20:20:40 +0000263
264" Include files
265syn match forthInclude '^INCLUDE\s\+\k\+'
Bram Moolenaare37d50a2008-08-06 17:06:04 +0000266syn match forthInclude '^require\s\+\k\+'
Bram Moolenaar071d4272004-06-13 20:20:40 +0000267syn match forthInclude '^fload\s\+'
268syn match forthInclude '^needs\s\+'
269
Bram Moolenaare37d50a2008-08-06 17:06:04 +0000270" Locals definitions
271syn region forthLocals start='{\s' start='{$' end='\s}' end='^}'
272syn match forthLocals '{ }' " otherwise, at least two spaces between
273syn region forthDeprecated start='locals|' end='|'
274
Bram Moolenaar071d4272004-06-13 20:20:40 +0000275" Define the default highlighting.
276" For version 5.7 and earlier: only when not done already
277" For version 5.8 and later: only when an item doesn't have highlighting yet
278if version >= 508 || !exists("did_forth_syn_inits")
279 if version < 508
Bram Moolenaar3577c6f2008-06-24 21:16:56 +0000280 let did_forth_syn_inits = 1
281 command -nargs=+ HiLink hi link <args>
Bram Moolenaar071d4272004-06-13 20:20:40 +0000282 else
Bram Moolenaar3577c6f2008-06-24 21:16:56 +0000283 command -nargs=+ HiLink hi def link <args>
Bram Moolenaar071d4272004-06-13 20:20:40 +0000284 endif
285
286 " The default methods for highlighting. Can be overriden later.
287 HiLink forthTodo Todo
288 HiLink forthOperators Operator
289 HiLink forthMath Number
290 HiLink forthInteger Number
291 HiLink forthFloat Float
292 HiLink forthStack Special
293 HiLink forthRstack Special
294 HiLink forthFStack Special
295 HiLink forthSP Special
296 HiLink forthMemory Function
297 HiLink forthAdrArith Function
298 HiLink forthMemBlks Function
299 HiLink forthCond Conditional
300 HiLink forthLoop Repeat
301 HiLink forthColonDef Define
302 HiLink forthEndOfColonDef Define
303 HiLink forthDefine Define
304 HiLink forthDebug Debug
305 HiLink forthAssembler Include
306 HiLink forthCharOps Character
307 HiLink forthConversion String
308 HiLink forthForth Statement
309 HiLink forthVocs Statement
310 HiLink forthString String
311 HiLink forthComment Comment
312 HiLink forthClassDef Define
313 HiLink forthEndOfClassDef Define
314 HiLink forthObjectDef Define
315 HiLink forthEndOfObjectDef Define
316 HiLink forthInclude Include
Bram Moolenaare37d50a2008-08-06 17:06:04 +0000317 HiLink forthLocals Type " nothing else uses type and locals must stand out
318 HiLink forthDeprecated Error " if you must, change to Type
319 HiLink forthFileMode Function
320 HiLink forthFileWords Statement
321 HiLink forthBlocks Statement
Bram Moolenaar3577c6f2008-06-24 21:16:56 +0000322 HiLink forthSpaceError Error
Bram Moolenaar071d4272004-06-13 20:20:40 +0000323
324 delcommand HiLink
325endif
326
327let b:current_syntax = "forth"
328
329" vim:ts=8:sw=4:nocindent:smartindent: