xref: /vim-8.2.3635/runtime/syntax/forth.vim (revision 818c9e7e)
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" For version 5.x: Clear all syntax items
84" For version 6.x: Quit when a syntax file was already loaded
85if version < 600
86    syntax clear
87elseif exists("b:current_syntax")
88    finish
89endif
90
91let s:cpo_save = &cpo
92set cpo&vim
93
94" Synchronization method
95syn sync ccomment
96syn sync maxlines=200
97
98" I use gforth, so I set this to case ignore
99syn case ignore
100
101" Some special, non-FORTH keywords
102syn keyword forthTodo contained TODO FIXME XXX
103syn match forthTodo contained 'Copyright\(\s([Cc])\)\=\(\s[0-9]\{2,4}\)\='
104
105" Characters allowed in keywords
106" I don't know if 128-255 are allowed in ANS-FORTH
107if version >= 600
108    setlocal iskeyword=!,@,33-35,%,$,38-64,A-Z,91-96,a-z,123-126,128-255
109else
110    set iskeyword=!,@,33-35,%,$,38-64,A-Z,91-96,a-z,123-126,128-255
111endif
112
113" when wanted, highlight trailing white space
114if exists("forth_space_errors")
115    if !exists("forth_no_trail_space_error")
116        syn match forthSpaceError display excludenl "\s\+$"
117    endif
118    if !exists("forth_no_tab_space_error")
119        syn match forthSpaceError display " \+\t"me=e-1
120    endif
121endif
122
123" Keywords
124
125" basic mathematical and logical operators
126syn keyword forthOperators + - * / MOD /MOD NEGATE ABS MIN MAX
127syn keyword forthOperators AND OR XOR NOT LSHIFT RSHIFT INVERT 2* 2/ 1+
128syn keyword forthOperators 1- 2+ 2- 8* UNDER+
129syn keyword forthOperators M+ */ */MOD M* UM* M*/ UM/MOD FM/MOD SM/REM
130syn keyword forthOperators D+ D- DNEGATE DABS DMIN DMAX D2* D2/
131syn keyword forthOperators F+ F- F* F/ FNEGATE FABS FMAX FMIN FLOOR FROUND
132syn keyword forthOperators F** FSQRT FEXP FEXPM1 FLN FLNP1 FLOG FALOG FSIN
133syn keyword forthOperators FCOS FSINCOS FTAN FASIN FACOS FATAN FATAN2 FSINH
134syn keyword forthOperators FCOSH FTANH FASINH FACOSH FATANH F2* F2/ 1/F
135syn keyword forthOperators F~REL F~ABS F~
136syn keyword forthOperators 0< 0<= 0<> 0= 0> 0>= < <= <> = > >= U< U<=
137syn keyword forthOperators U> U>= D0< D0<= D0<> D0= D0> D0>= D< D<= D<>
138syn keyword forthOperators D= D> D>= DU< DU<= DU> DU>= WITHIN ?NEGATE
139syn keyword forthOperators ?DNEGATE
140
141" stack manipulations
142syn keyword forthStack DROP NIP DUP OVER TUCK SWAP ROT -ROT ?DUP PICK ROLL
143syn keyword forthStack 2DROP 2NIP 2DUP 2OVER 2TUCK 2SWAP 2ROT 2-ROT
144syn keyword forthStack 3DUP 4DUP 5DUP 3DROP 4DROP 5DROP 8DROP 4SWAP 4ROT
145syn keyword forthStack 4-ROT 4TUCK 8SWAP 8DUP
146syn keyword forthRStack >R R> R@ RDROP 2>R 2R> 2R@ 2RDROP
147syn keyword forthRstack 4>R 4R> 4R@ 4RDROP
148syn keyword forthFStack FDROP FNIP FDUP FOVER FTUCK FSWAP FROT
149
150" stack pointer manipulations
151syn keyword forthSP SP@ SP! FP@ FP! RP@ RP! LP@ LP!
152
153" address operations
154syn keyword forthMemory @ ! +! C@ C! 2@ 2! F@ F! SF@ SF! DF@ DF!
155syn keyword forthAdrArith CHARS CHAR+ CELLS CELL+ CELL ALIGN ALIGNED FLOATS
156syn keyword forthAdrArith FLOAT+ FLOAT FALIGN FALIGNED SFLOATS SFLOAT+
157syn keyword forthAdrArith SFALIGN SFALIGNED DFLOATS DFLOAT+ DFALIGN DFALIGNED
158syn keyword forthAdrArith MAXALIGN MAXALIGNED CFALIGN CFALIGNED
159syn keyword forthAdrArith ADDRESS-UNIT-BITS ALLOT ALLOCATE HERE
160syn keyword forthMemBlks MOVE ERASE CMOVE CMOVE> FILL BLANK
161
162" conditionals
163syn keyword forthCond IF ELSE ENDIF THEN CASE OF ENDOF ENDCASE ?DUP-IF
164syn keyword forthCond ?DUP-0=-IF AHEAD CS-PICK CS-ROLL CATCH THROW WITHIN
165
166" iterations
167syn keyword forthLoop BEGIN WHILE REPEAT UNTIL AGAIN
168syn keyword forthLoop ?DO LOOP I J K +DO U+DO -DO U-DO DO +LOOP -LOOP
169syn keyword forthLoop UNLOOP LEAVE ?LEAVE EXIT DONE FOR NEXT
170
171" new words
172syn match forthClassDef '\<:class\s*[^ \t]\+\>'
173syn match forthObjectDef '\<:object\s*[^ \t]\+\>'
174syn match forthColonDef '\<:m\?\s*[^ \t]\+\>'
175syn keyword forthEndOfColonDef ; ;M ;m
176syn keyword forthEndOfClassDef ;class
177syn keyword forthEndOfObjectDef ;object
178syn keyword forthDefine CONSTANT 2CONSTANT FCONSTANT VARIABLE 2VARIABLE
179syn keyword forthDefine FVARIABLE CREATE USER VALUE TO DEFER IS DOES> IMMEDIATE
180syn keyword forthDefine COMPILE-ONLY COMPILE RESTRICT INTERPRET POSTPONE EXECUTE
181syn keyword forthDefine LITERAL CREATE-INTERPRET/COMPILE INTERPRETATION>
182syn keyword forthDefine <INTERPRETATION COMPILATION> <COMPILATION ] LASTXT
183syn keyword forthDefine COMP' POSTPONE, FIND-NAME NAME>INT NAME?INT NAME>COMP
184syn keyword forthDefine NAME>STRING STATE C; CVARIABLE
185syn keyword forthDefine , 2, F, C,
186syn match forthDefine "\[IFDEF]"
187syn match forthDefine "\[IFUNDEF]"
188syn match forthDefine "\[THEN]"
189syn match forthDefine "\[ENDIF]"
190syn match forthDefine "\[ELSE]"
191syn match forthDefine "\[?DO]"
192syn match forthDefine "\[DO]"
193syn match forthDefine "\[LOOP]"
194syn match forthDefine "\[+LOOP]"
195syn match forthDefine "\[NEXT]"
196syn match forthDefine "\[BEGIN]"
197syn match forthDefine "\[UNTIL]"
198syn match forthDefine "\[AGAIN]"
199syn match forthDefine "\[WHILE]"
200syn match forthDefine "\[REPEAT]"
201syn match forthDefine "\[COMP']"
202syn match forthDefine "'"
203syn match forthDefine '\<\[\>'
204syn match forthDefine "\[']"
205syn match forthDefine '\[COMPILE]'
206
207" debugging
208syn keyword forthDebug PRINTDEBUGDATA PRINTDEBUGLINE
209syn match forthDebug "\<\~\~\>"
210
211" Assembler
212syn keyword forthAssembler ASSEMBLER CODE END-CODE ;CODE FLUSH-ICACHE C,
213
214" basic character operations
215syn keyword forthCharOps (.) CHAR EXPECT FIND WORD TYPE -TRAILING EMIT KEY
216syn keyword forthCharOps KEY? TIB CR
217" recognize 'char (' or '[char] (' correctly, so it doesn't
218" highlight everything after the paren as a comment till a closing ')'
219syn match forthCharOps '\<char\s\S\s'
220syn match forthCharOps '\<\[char\]\s\S\s'
221syn region forthCharOps start=+."\s+ skip=+\\"+ end=+"+
222
223" char-number conversion
224syn keyword forthConversion <<# <# # #> #>> #S (NUMBER) (NUMBER?) CONVERT D>F
225syn keyword forthConversion D>S DIGIT DPL F>D HLD HOLD NUMBER S>D SIGN >NUMBER
226syn keyword forthConversion F>S S>F
227
228" interpreter, wordbook, compiler
229syn keyword forthForth (LOCAL) BYE COLD ABORT >BODY >NEXT >LINK CFA >VIEW HERE
230syn keyword forthForth PAD WORDS VIEW VIEW> N>LINK NAME> LINK> L>NAME FORGET
231syn keyword forthForth BODY> ASSERT( ASSERT0( ASSERT1( ASSERT2( ASSERT3( )
232syn region forthForth start=+ABORT"\s+ skip=+\\"+ end=+"+
233
234" vocabularies
235syn keyword forthVocs ONLY FORTH ALSO ROOT SEAL VOCS ORDER CONTEXT #VOCS
236syn keyword forthVocs VOCABULARY DEFINITIONS
237
238" File keywords
239syn keyword forthFileMode R/O R/W W/O BIN
240syn keyword forthFileWords OPEN-FILE CREATE-FILE CLOSE-FILE DELETE-FILE
241syn keyword forthFileWords RENAME-FILE READ-FILE READ-LINE KEY-FILE
242syn keyword forthFileWords KEY?-FILE WRITE-FILE WRITE-LINE EMIT-FILE
243syn keyword forthFileWords FLUSH-FILE FILE-STATUS FILE-POSITION
244syn keyword forthFileWords REPOSITION-FILE FILE-SIZE RESIZE-FILE
245syn keyword forthFileWords SLURP-FILE SLURP-FID STDIN STDOUT STDERR
246syn keyword forthBlocks OPEN-BLOCKS USE LOAD --> BLOCK-OFFSET
247syn keyword forthBlocks GET-BLOCK-FID BLOCK-POSITION LIST SCR BLOCK
248syn keyword forthBlocks BUFER EMPTY-BUFFERS EMPTY-BUFFER UPDATE UPDATED?
249syn keyword forthBlocks SAVE-BUFFERS SAVE-BUFFER FLUSH THRU +LOAD +THRU
250syn keyword forthBlocks BLOCK-INCLUDED
251
252" numbers
253syn keyword forthMath DECIMAL HEX BASE
254syn match forthInteger '\<-\=[0-9.]*[0-9.]\+\>'
255syn match forthInteger '\<&-\=[0-9.]*[0-9.]\+\>'
256" recognize hex and binary numbers, the '$' and '%' notation is for gforth
257syn match forthInteger '\<\$\x*\x\+\>' " *1* --- dont't mess
258syn match forthInteger '\<\x*\d\x*\>'  " *2* --- this order!
259syn match forthInteger '\<%[0-1]*[0-1]\+\>'
260syn match forthFloat '\<-\=\d*[.]\=\d\+[DdEe]\d\+\>'
261syn match forthFloat '\<-\=\d*[.]\=\d\+[DdEe][-+]\d\+\>'
262
263" XXX If you find this overkill you can remove it. This has to come after the
264" highlighting for numbers otherwise it has no effect.
265syn region forthComment start='0 \[if\]' end='\[endif\]' end='\[then\]' contains=forthTodo
266
267" Strings
268syn region forthString start=+\.*\"+ end=+"+ end=+$+ contains=@Spell
269" XXX
270syn region forthString start=+s\"+ end=+"+ end=+$+ contains=@Spell
271syn region forthString start=+c\"+ end=+"+ end=+$+ contains=@Spell
272
273" Comments
274syn match forthComment '\\\s.*$' contains=@Spell,forthTodo,forthSpaceError
275syn region forthComment start='\\S\s' end='.*' contains=@Spell,forthTodo,forthSpaceError
276syn match forthComment '\.(\s[^)]*)' contains=@Spell,forthTodo,forthSpaceError
277syn region forthComment start='\(^\|\s\)\zs(\s' skip='\\)' end=')' contains=@Spell,forthTodo,forthSpaceError
278syn region forthComment start='/\*' end='\*/' contains=@Spell,forthTodo,forthSpaceError
279
280" Include files
281syn match forthInclude '^INCLUDE\s\+\k\+'
282syn match forthInclude '^require\s\+\k\+'
283syn match forthInclude '^fload\s\+'
284syn match forthInclude '^needs\s\+'
285
286" Locals definitions
287syn region forthLocals start='{\s' start='{$' end='\s}' end='^}'
288syn match forthLocals '{ }' " otherwise, at least two spaces between
289syn region forthDeprecated start='locals|' end='|'
290
291" Define the default highlighting.
292" For version 5.7 and earlier: only when not done already
293" For version 5.8 and later: only when an item doesn't have highlighting yet
294if version >= 508 || !exists("did_forth_syn_inits")
295    if version < 508
296	let did_forth_syn_inits = 1
297	command -nargs=+ HiLink hi link <args>
298    else
299	command -nargs=+ HiLink hi def link <args>
300    endif
301
302    " The default methods for highlighting. Can be overridden later.
303    HiLink forthTodo Todo
304    HiLink forthOperators Operator
305    HiLink forthMath Number
306    HiLink forthInteger Number
307    HiLink forthFloat Float
308    HiLink forthStack Special
309    HiLink forthRstack Special
310    HiLink forthFStack Special
311    HiLink forthSP Special
312    HiLink forthMemory Function
313    HiLink forthAdrArith Function
314    HiLink forthMemBlks Function
315    HiLink forthCond Conditional
316    HiLink forthLoop Repeat
317    HiLink forthColonDef Define
318    HiLink forthEndOfColonDef Define
319    HiLink forthDefine Define
320    HiLink forthDebug Debug
321    HiLink forthAssembler Include
322    HiLink forthCharOps Character
323    HiLink forthConversion String
324    HiLink forthForth Statement
325    HiLink forthVocs Statement
326    HiLink forthString String
327    HiLink forthComment Comment
328    HiLink forthClassDef Define
329    HiLink forthEndOfClassDef Define
330    HiLink forthObjectDef Define
331    HiLink forthEndOfObjectDef Define
332    HiLink forthInclude Include
333    HiLink forthLocals Type " nothing else uses type and locals must stand out
334    HiLink forthDeprecated Error " if you must, change to Type
335    HiLink forthFileMode Function
336    HiLink forthFileWords Statement
337    HiLink forthBlocks Statement
338    HiLink forthSpaceError Error
339
340    delcommand HiLink
341endif
342
343let b:current_syntax = "forth"
344
345let &cpo = s:cpo_save
346unlet s:cpo_save
347" vim:ts=8:sw=4:nocindent:smartindent:
348