blob: bbdced2efd51916a71011d2250d6b7c7c003f7a8 [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 Moolenaarcdf04202010-05-29 15:11:47 +02004" Last Change: Di 07 Jul 2009 21:38:45 CEST
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
Bram Moolenaarcdf04202010-05-29 15:11:47 +02008" $Id: forth.vim,v 1.12 2008/07/07 21:39:12 bruessow Exp $
Bram Moolenaar071d4272004-06-13 20:20:40 +00009
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 Moolenaarcdf04202010-05-29 15:11:47 +020020" 2009-06-28:
21" Josh Grams send a patch to allow the parenthesis comments at the
22" beginning of a line. That patch also fixed a typo in one of the
23" comments.
24"
Bram Moolenaare37d50a2008-08-06 17:06:04 +000025" 2008-02-09:
26" Shawn K. Quinn <sjquinn at speakeasy dot net> send a big patch with
27" new words commonly used in Forth programs or defined by GNU Forth.
28"
Bram Moolenaar3577c6f2008-06-24 21:16:56 +000029" 2007-07-11:
30" Benjamin Krill <ben at codiert dot org> send me a patch
31" to highlight space errors.
32" You can toggle this feature on through setting the
33" flag forth_space_errors in you vimrc. If you have switched it on,
34" you can turn off highlighting of trailing spaces in comments by
35" setting forth_no_trail_space_error in your vimrc. If you do not want
36" the highlighting of a tabulator following a space in comments, you
37" can turn this off by setting forth_no_tab_space_error.
Bram Moolenaar8299df92004-07-10 09:47:34 +000038"
Bram Moolenaar3577c6f2008-06-24 21:16:56 +000039" 2006-05-25:
40" Bill McCarthy <WJMc@...> and Ilya Sher <ilya-vim@...>
41" Who found a bug in the ccomment line in 2004!!!
42" I'm really very sorry, that it has taken two years to fix that
43" in the offical version of this file. Shame on me.
44" I think my face will be red the next ten years...
45"
46" 2006-05-21:
47" Thomas E. Vaughan <tevaugha at ball dot com> send me a patch
48" for the parenthesis comment word, so words with a trailing
49" parenthesis will not start the highlighting for such comments.
50"
Bram Moolenaar071d4272004-06-13 20:20:40 +000051" 2003-05-10:
52" Andrew Gaul <andrew at gaul.org> send me a patch for
53" forthOperators.
54"
55" 2003-04-03:
Bram Moolenaar3577c6f2008-06-24 21:16:56 +000056" Ron Aaron <ron at ronware dot org> made updates for an
Bram Moolenaar071d4272004-06-13 20:20:40 +000057" improved Win32Forth support.
58"
59" 2002-04-22:
Bram Moolenaar3577c6f2008-06-24 21:16:56 +000060" Charles Shattuck <charley at forth dot org> helped me to settle up with the
Bram Moolenaar071d4272004-06-13 20:20:40 +000061" binary and hex number highlighting.
62"
63" 2002-04-20:
Bram Moolenaar3577c6f2008-06-24 21:16:56 +000064" Charles Shattuck <charley at forth dot org> send me some code for correctly
Bram Moolenaar071d4272004-06-13 20:20:40 +000065" highlighting char and [char] followed by an opening paren. He also added
66" some words for operators, conditionals, and definitions; and added the
67" highlighting for s" and c".
68"
69" 2000-03-28:
Bram Moolenaar3577c6f2008-06-24 21:16:56 +000070" John Providenza <john at probo dot com> made improvements for the
Bram Moolenaar071d4272004-06-13 20:20:40 +000071" highlighting of strings, and added the code for highlighting hex numbers.
72"
73
74
75" For version 5.x: Clear all syntax items
76" For version 6.x: Quit when a syntax file was already loaded
77if version < 600
78 syntax clear
79elseif exists("b:current_syntax")
80 finish
81endif
82
83" Synchronization method
Bram Moolenaar8299df92004-07-10 09:47:34 +000084syn sync ccomment
85syn sync maxlines=200
Bram Moolenaar071d4272004-06-13 20:20:40 +000086
87" I use gforth, so I set this to case ignore
88syn case ignore
89
90" Some special, non-FORTH keywords
91syn keyword forthTodo contained TODO FIXME XXX
92syn match forthTodo contained 'Copyright\(\s([Cc])\)\=\(\s[0-9]\{2,4}\)\='
93
94" Characters allowed in keywords
Bram Moolenaare37d50a2008-08-06 17:06:04 +000095" I don't know if 128-255 are allowed in ANS-FORTH
Bram Moolenaar071d4272004-06-13 20:20:40 +000096if version >= 600
97 setlocal iskeyword=!,@,33-35,%,$,38-64,A-Z,91-96,a-z,123-126,128-255
98else
99 set iskeyword=!,@,33-35,%,$,38-64,A-Z,91-96,a-z,123-126,128-255
100endif
101
Bram Moolenaar3577c6f2008-06-24 21:16:56 +0000102" when wanted, highlight trailing white space
103if exists("forth_space_errors")
104 if !exists("forth_no_trail_space_error")
105 syn match forthSpaceError display excludenl "\s\+$"
106 endif
107 if !exists("forth_no_tab_space_error")
108 syn match forthSpaceError display " \+\t"me=e-1
109 endif
110endif
Bram Moolenaar071d4272004-06-13 20:20:40 +0000111
112" Keywords
113
114" basic mathematical and logical operators
115syn keyword forthOperators + - * / MOD /MOD NEGATE ABS MIN MAX
Bram Moolenaare37d50a2008-08-06 17:06:04 +0000116syn keyword forthOperators AND OR XOR NOT LSHIFT RSHIFT INVERT 2* 2/ 1+
117syn keyword forthOperators 1- 2+ 2- 8* UNDER+
Bram Moolenaar071d4272004-06-13 20:20:40 +0000118syn keyword forthOperators M+ */ */MOD M* UM* M*/ UM/MOD FM/MOD SM/REM
Bram Moolenaare37d50a2008-08-06 17:06:04 +0000119syn keyword forthOperators D+ D- DNEGATE DABS DMIN DMAX D2* D2/
Bram Moolenaar071d4272004-06-13 20:20:40 +0000120syn keyword forthOperators F+ F- F* F/ FNEGATE FABS FMAX FMIN FLOOR FROUND
121syn keyword forthOperators F** FSQRT FEXP FEXPM1 FLN FLNP1 FLOG FALOG FSIN
122syn keyword forthOperators FCOS FSINCOS FTAN FASIN FACOS FATAN FATAN2 FSINH
Bram Moolenaare37d50a2008-08-06 17:06:04 +0000123syn keyword forthOperators FCOSH FTANH FASINH FACOSH FATANH F2* F2/ 1/F
124syn keyword forthOperators F~REL F~ABS F~
125syn keyword forthOperators 0< 0<= 0<> 0= 0> 0>= < <= <> = > >= U< U<=
126syn keyword forthOperators U> U>= D0< D0<= D0<> D0= D0> D0>= D< D<= D<>
127syn keyword forthOperators D= D> D>= DU< DU<= DU> DU>= WITHIN ?NEGATE
128syn keyword forthOperators ?DNEGATE
Bram Moolenaar071d4272004-06-13 20:20:40 +0000129
130" stack manipulations
131syn keyword forthStack DROP NIP DUP OVER TUCK SWAP ROT -ROT ?DUP PICK ROLL
Bram Moolenaare37d50a2008-08-06 17:06:04 +0000132syn keyword forthStack 2DROP 2NIP 2DUP 2OVER 2TUCK 2SWAP 2ROT 2-ROT
133syn keyword forthStack 3DUP 4DUP 5DUP 3DROP 4DROP 5DROP 8DROP 4SWAP 4ROT
134syn keyword forthStack 4-ROT 4TUCK 8SWAP 8DUP
Bram Moolenaar071d4272004-06-13 20:20:40 +0000135syn keyword forthRStack >R R> R@ RDROP 2>R 2R> 2R@ 2RDROP
Bram Moolenaare37d50a2008-08-06 17:06:04 +0000136syn keyword forthRstack 4>R 4R> 4R@ 4RDROP
Bram Moolenaar071d4272004-06-13 20:20:40 +0000137syn keyword forthFStack FDROP FNIP FDUP FOVER FTUCK FSWAP FROT
138
139" stack pointer manipulations
140syn keyword forthSP SP@ SP! FP@ FP! RP@ RP! LP@ LP!
141
142" address operations
143syn keyword forthMemory @ ! +! C@ C! 2@ 2! F@ F! SF@ SF! DF@ DF!
144syn keyword forthAdrArith CHARS CHAR+ CELLS CELL+ CELL ALIGN ALIGNED FLOATS
145syn keyword forthAdrArith FLOAT+ FLOAT FALIGN FALIGNED SFLOATS SFLOAT+
146syn keyword forthAdrArith SFALIGN SFALIGNED DFLOATS DFLOAT+ DFALIGN DFALIGNED
147syn keyword forthAdrArith MAXALIGN MAXALIGNED CFALIGN CFALIGNED
148syn keyword forthAdrArith ADDRESS-UNIT-BITS ALLOT ALLOCATE HERE
149syn keyword forthMemBlks MOVE ERASE CMOVE CMOVE> FILL BLANK
150
151" conditionals
152syn keyword forthCond IF ELSE ENDIF THEN CASE OF ENDOF ENDCASE ?DUP-IF
153syn keyword forthCond ?DUP-0=-IF AHEAD CS-PICK CS-ROLL CATCH THROW WITHIN
154
155" iterations
156syn keyword forthLoop BEGIN WHILE REPEAT UNTIL AGAIN
157syn keyword forthLoop ?DO LOOP I J K +DO U+DO -DO U-DO DO +LOOP -LOOP
158syn keyword forthLoop UNLOOP LEAVE ?LEAVE EXIT DONE FOR NEXT
159
160" new words
Bram Moolenaare37d50a2008-08-06 17:06:04 +0000161syn match forthClassDef '\<:class\s*[^ \t]\+\>'
162syn match forthObjectDef '\<:object\s*[^ \t]\+\>'
Bram Moolenaar071d4272004-06-13 20:20:40 +0000163syn match forthColonDef '\<:m\?\s*[^ \t]\+\>'
164syn keyword forthEndOfColonDef ; ;M ;m
Bram Moolenaare37d50a2008-08-06 17:06:04 +0000165syn keyword forthEndOfClassDef ;class
166syn keyword forthEndOfObjectDef ;object
167syn keyword forthDefine CONSTANT 2CONSTANT FCONSTANT VARIABLE 2VARIABLE
168syn keyword forthDefine FVARIABLE CREATE USER VALUE TO DEFER IS DOES> IMMEDIATE
169syn keyword forthDefine COMPILE-ONLY COMPILE RESTRICT INTERPRET POSTPONE EXECUTE
170syn keyword forthDefine LITERAL CREATE-INTERPRET/COMPILE INTERPRETATION>
171syn keyword forthDefine <INTERPRETATION COMPILATION> <COMPILATION ] LASTXT
172syn keyword forthDefine COMP' POSTPONE, FIND-NAME NAME>INT NAME?INT NAME>COMP
173syn keyword forthDefine NAME>STRING STATE C; CVARIABLE
174syn keyword forthDefine , 2, F, C,
175syn match forthDefine "\[IFDEF]"
176syn match forthDefine "\[IFUNDEF]"
177syn match forthDefine "\[THEN]"
178syn match forthDefine "\[ENDIF]"
179syn match forthDefine "\[ELSE]"
180syn match forthDefine "\[?DO]"
181syn match forthDefine "\[DO]"
182syn match forthDefine "\[LOOP]"
183syn match forthDefine "\[+LOOP]"
184syn match forthDefine "\[NEXT]"
185syn match forthDefine "\[BEGIN]"
186syn match forthDefine "\[UNTIL]"
187syn match forthDefine "\[AGAIN]"
188syn match forthDefine "\[WHILE]"
189syn match forthDefine "\[REPEAT]"
Bram Moolenaar071d4272004-06-13 20:20:40 +0000190syn match forthDefine "\[COMP']"
191syn match forthDefine "'"
192syn match forthDefine '\<\[\>'
193syn match forthDefine "\[']"
194syn match forthDefine '\[COMPILE]'
Bram Moolenaar071d4272004-06-13 20:20:40 +0000195
196" debugging
197syn keyword forthDebug PRINTDEBUGDATA PRINTDEBUGLINE
198syn match forthDebug "\<\~\~\>"
199
200" Assembler
201syn keyword forthAssembler ASSEMBLER CODE END-CODE ;CODE FLUSH-ICACHE C,
202
203" basic character operations
204syn keyword forthCharOps (.) CHAR EXPECT FIND WORD TYPE -TRAILING EMIT KEY
205syn keyword forthCharOps KEY? TIB CR
206" recognize 'char (' or '[char] (' correctly, so it doesn't
207" highlight everything after the paren as a comment till a closing ')'
208syn match forthCharOps '\<char\s\S\s'
209syn match forthCharOps '\<\[char\]\s\S\s'
210syn region forthCharOps start=+."\s+ skip=+\\"+ end=+"+
211
212" char-number conversion
Bram Moolenaare37d50a2008-08-06 17:06:04 +0000213syn keyword forthConversion <<# <# # #> #>> #S (NUMBER) (NUMBER?) CONVERT D>F
214syn keyword forthConversion D>S DIGIT DPL F>D HLD HOLD NUMBER S>D SIGN >NUMBER
215syn keyword forthConversion F>S S>F
Bram Moolenaar071d4272004-06-13 20:20:40 +0000216
Bram Moolenaarcdf04202010-05-29 15:11:47 +0200217" interpreter, wordbook, compiler
Bram Moolenaar071d4272004-06-13 20:20:40 +0000218syn keyword forthForth (LOCAL) BYE COLD ABORT >BODY >NEXT >LINK CFA >VIEW HERE
219syn keyword forthForth PAD WORDS VIEW VIEW> N>LINK NAME> LINK> L>NAME FORGET
Bram Moolenaare37d50a2008-08-06 17:06:04 +0000220syn keyword forthForth BODY> ASSERT( ASSERT0( ASSERT1( ASSERT2( ASSERT3( )
Bram Moolenaar071d4272004-06-13 20:20:40 +0000221syn region forthForth start=+ABORT"\s+ skip=+\\"+ end=+"+
222
223" vocabularies
224syn keyword forthVocs ONLY FORTH ALSO ROOT SEAL VOCS ORDER CONTEXT #VOCS
225syn keyword forthVocs VOCABULARY DEFINITIONS
226
Bram Moolenaare37d50a2008-08-06 17:06:04 +0000227" File keywords
228syn keyword forthFileMode R/O R/W W/O BIN
229syn keyword forthFileWords OPEN-FILE CREATE-FILE CLOSE-FILE DELETE-FILE
230syn keyword forthFileWords RENAME-FILE READ-FILE READ-LINE KEY-FILE
231syn keyword forthFileWords KEY?-FILE WRITE-FILE WRITE-LINE EMIT-FILE
232syn keyword forthFileWords FLUSH-FILE FILE-STATUS FILE-POSITION
233syn keyword forthFileWords REPOSITION-FILE FILE-SIZE RESIZE-FILE
234syn keyword forthFileWords SLURP-FILE SLURP-FID STDIN STDOUT STDERR
235syn keyword forthBlocks OPEN-BLOCKS USE LOAD --> BLOCK-OFFSET
236syn keyword forthBlocks GET-BLOCK-FID BLOCK-POSITION LIST SCR BLOCK
237syn keyword forthBlocks BUFER EMPTY-BUFFERS EMPTY-BUFFER UPDATE UPDATED?
238syn keyword forthBlocks SAVE-BUFFERS SAVE-BUFFER FLUSH THRU +LOAD +THRU
239syn keyword forthBlocks BLOCK-INCLUDED
240
Bram Moolenaar071d4272004-06-13 20:20:40 +0000241" numbers
242syn keyword forthMath DECIMAL HEX BASE
243syn match forthInteger '\<-\=[0-9.]*[0-9.]\+\>'
Bram Moolenaare37d50a2008-08-06 17:06:04 +0000244syn match forthInteger '\<&-\=[0-9.]*[0-9.]\+\>'
Bram Moolenaar071d4272004-06-13 20:20:40 +0000245" recognize hex and binary numbers, the '$' and '%' notation is for gforth
246syn match forthInteger '\<\$\x*\x\+\>' " *1* --- dont't mess
247syn match forthInteger '\<\x*\d\x*\>' " *2* --- this order!
248syn match forthInteger '\<%[0-1]*[0-1]\+\>'
Bram Moolenaare37d50a2008-08-06 17:06:04 +0000249syn match forthFloat '\<-\=\d*[.]\=\d\+[DdEe]\d\+\>'
250syn match forthFloat '\<-\=\d*[.]\=\d\+[DdEe][-+]\d\+\>'
251
252" XXX If you find this overkill you can remove it. this has to come after the
253" highlighting for numbers otherwise it has no effect.
254syn region forthComment start='0 \[if\]' end='\[endif\]' end='\[then\]' contains=forthTodo
Bram Moolenaar071d4272004-06-13 20:20:40 +0000255
256" Strings
257syn region forthString start=+\.*\"+ end=+"+ end=+$+
258" XXX
259syn region forthString start=+s\"+ end=+"+ end=+$+
260syn region forthString start=+c\"+ end=+"+ end=+$+
261
262" Comments
Bram Moolenaar3577c6f2008-06-24 21:16:56 +0000263syn match forthComment '\\\s.*$' contains=forthTodo,forthSpaceError
264syn region forthComment start='\\S\s' end='.*' contains=forthTodo,forthSpaceError
265syn match forthComment '\.(\s[^)]*)' contains=forthTodo,forthSpaceError
Bram Moolenaarcdf04202010-05-29 15:11:47 +0200266syn region forthComment start='\(^\|\s\)\zs(\s' skip='\\)' end=')' contains=forthTodo,forthSpaceError
Bram Moolenaar3577c6f2008-06-24 21:16:56 +0000267syn region forthComment start='/\*' end='\*/' contains=forthTodo,forthSpaceError
Bram Moolenaar071d4272004-06-13 20:20:40 +0000268
269" Include files
270syn match forthInclude '^INCLUDE\s\+\k\+'
Bram Moolenaare37d50a2008-08-06 17:06:04 +0000271syn match forthInclude '^require\s\+\k\+'
Bram Moolenaar071d4272004-06-13 20:20:40 +0000272syn match forthInclude '^fload\s\+'
273syn match forthInclude '^needs\s\+'
274
Bram Moolenaare37d50a2008-08-06 17:06:04 +0000275" Locals definitions
276syn region forthLocals start='{\s' start='{$' end='\s}' end='^}'
277syn match forthLocals '{ }' " otherwise, at least two spaces between
278syn region forthDeprecated start='locals|' end='|'
279
Bram Moolenaar071d4272004-06-13 20:20:40 +0000280" Define the default highlighting.
281" For version 5.7 and earlier: only when not done already
282" For version 5.8 and later: only when an item doesn't have highlighting yet
283if version >= 508 || !exists("did_forth_syn_inits")
284 if version < 508
Bram Moolenaar3577c6f2008-06-24 21:16:56 +0000285 let did_forth_syn_inits = 1
286 command -nargs=+ HiLink hi link <args>
Bram Moolenaar071d4272004-06-13 20:20:40 +0000287 else
Bram Moolenaar3577c6f2008-06-24 21:16:56 +0000288 command -nargs=+ HiLink hi def link <args>
Bram Moolenaar071d4272004-06-13 20:20:40 +0000289 endif
290
291 " The default methods for highlighting. Can be overriden later.
292 HiLink forthTodo Todo
293 HiLink forthOperators Operator
294 HiLink forthMath Number
295 HiLink forthInteger Number
296 HiLink forthFloat Float
297 HiLink forthStack Special
298 HiLink forthRstack Special
299 HiLink forthFStack Special
300 HiLink forthSP Special
301 HiLink forthMemory Function
302 HiLink forthAdrArith Function
303 HiLink forthMemBlks Function
304 HiLink forthCond Conditional
305 HiLink forthLoop Repeat
306 HiLink forthColonDef Define
307 HiLink forthEndOfColonDef Define
308 HiLink forthDefine Define
309 HiLink forthDebug Debug
310 HiLink forthAssembler Include
311 HiLink forthCharOps Character
312 HiLink forthConversion String
313 HiLink forthForth Statement
314 HiLink forthVocs Statement
315 HiLink forthString String
316 HiLink forthComment Comment
317 HiLink forthClassDef Define
318 HiLink forthEndOfClassDef Define
319 HiLink forthObjectDef Define
320 HiLink forthEndOfObjectDef Define
321 HiLink forthInclude Include
Bram Moolenaare37d50a2008-08-06 17:06:04 +0000322 HiLink forthLocals Type " nothing else uses type and locals must stand out
323 HiLink forthDeprecated Error " if you must, change to Type
324 HiLink forthFileMode Function
325 HiLink forthFileWords Statement
326 HiLink forthBlocks Statement
Bram Moolenaar3577c6f2008-06-24 21:16:56 +0000327 HiLink forthSpaceError Error
Bram Moolenaar071d4272004-06-13 20:20:40 +0000328
329 delcommand HiLink
330endif
331
332let b:current_syntax = "forth"
333
334" vim:ts=8:sw=4:nocindent:smartindent: