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