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