blob: fe986340794006857347283cdffcd78719435934 [file] [log] [blame]
Bram Moolenaar071d4272004-06-13 20:20:40 +00001" Vim syntax file
2" Language: FORTH
Bram Moolenaar25a6e8a2018-03-30 12:27:32 +02003" Current Maintainer: Johan Kotlinski <kotlinski@gmail.com>
Bram Moolenaarbe4e0162023-02-02 13:59:48 +00004" Previous Maintainer: Christian V. J. Brssow <cvjb@cvjb.de>
5" Last Change: 2023-01-12
Bram Moolenaar071d4272004-06-13 20:20:40 +00006" Filenames: *.fs,*.ft
Bram Moolenaar25a6e8a2018-03-30 12:27:32 +02007" URL: https://github.com/jkotlinski/forth.vim
Bram Moolenaar071d4272004-06-13 20:20:40 +00008
Bram Moolenaar89bcfda2016-08-30 23:26:57 +02009" quit when a syntax file was already loaded
10if exists("b:current_syntax")
Bram Moolenaar071d4272004-06-13 20:20:40 +000011 finish
12endif
13
Bram Moolenaar6ee8d892012-01-10 14:55:01 +010014let s:cpo_save = &cpo
15set cpo&vim
16
Bram Moolenaar071d4272004-06-13 20:20:40 +000017" Synchronization method
Bram Moolenaar8299df92004-07-10 09:47:34 +000018syn sync ccomment
19syn sync maxlines=200
Bram Moolenaar071d4272004-06-13 20:20:40 +000020
21" I use gforth, so I set this to case ignore
22syn case ignore
23
24" Some special, non-FORTH keywords
25syn keyword forthTodo contained TODO FIXME XXX
Bram Moolenaar071d4272004-06-13 20:20:40 +000026
27" Characters allowed in keywords
Bram Moolenaare37d50a2008-08-06 17:06:04 +000028" I don't know if 128-255 are allowed in ANS-FORTH
Bram Moolenaar89bcfda2016-08-30 23:26:57 +020029setlocal iskeyword=!,@,33-35,%,$,38-64,A-Z,91-96,a-z,123-126,128-255
Bram Moolenaar071d4272004-06-13 20:20:40 +000030
Bram Moolenaar3577c6f2008-06-24 21:16:56 +000031" when wanted, highlight trailing white space
32if exists("forth_space_errors")
33 if !exists("forth_no_trail_space_error")
34 syn match forthSpaceError display excludenl "\s\+$"
35 endif
36 if !exists("forth_no_tab_space_error")
37 syn match forthSpaceError display " \+\t"me=e-1
38 endif
39endif
Bram Moolenaar071d4272004-06-13 20:20:40 +000040
41" Keywords
42
43" basic mathematical and logical operators
44syn keyword forthOperators + - * / MOD /MOD NEGATE ABS MIN MAX
Bram Moolenaare37d50a2008-08-06 17:06:04 +000045syn keyword forthOperators AND OR XOR NOT LSHIFT RSHIFT INVERT 2* 2/ 1+
46syn keyword forthOperators 1- 2+ 2- 8* UNDER+
Bram Moolenaar071d4272004-06-13 20:20:40 +000047syn keyword forthOperators M+ */ */MOD M* UM* M*/ UM/MOD FM/MOD SM/REM
Bram Moolenaare37d50a2008-08-06 17:06:04 +000048syn keyword forthOperators D+ D- DNEGATE DABS DMIN DMAX D2* D2/
Bram Moolenaar071d4272004-06-13 20:20:40 +000049syn keyword forthOperators F+ F- F* F/ FNEGATE FABS FMAX FMIN FLOOR FROUND
50syn keyword forthOperators F** FSQRT FEXP FEXPM1 FLN FLNP1 FLOG FALOG FSIN
51syn keyword forthOperators FCOS FSINCOS FTAN FASIN FACOS FATAN FATAN2 FSINH
Bram Moolenaare37d50a2008-08-06 17:06:04 +000052syn keyword forthOperators FCOSH FTANH FASINH FACOSH FATANH F2* F2/ 1/F
53syn keyword forthOperators F~REL F~ABS F~
54syn keyword forthOperators 0< 0<= 0<> 0= 0> 0>= < <= <> = > >= U< U<=
55syn keyword forthOperators U> U>= D0< D0<= D0<> D0= D0> D0>= D< D<= D<>
56syn keyword forthOperators D= D> D>= DU< DU<= DU> DU>= WITHIN ?NEGATE
Bram Moolenaar25a6e8a2018-03-30 12:27:32 +020057syn keyword forthOperators ?DNEGATE TRUE FALSE
58
59" various words that take an input and do something with it
60syn keyword forthFunction . U. .R U.R
Bram Moolenaar071d4272004-06-13 20:20:40 +000061
62" stack manipulations
63syn keyword forthStack DROP NIP DUP OVER TUCK SWAP ROT -ROT ?DUP PICK ROLL
Bram Moolenaare37d50a2008-08-06 17:06:04 +000064syn keyword forthStack 2DROP 2NIP 2DUP 2OVER 2TUCK 2SWAP 2ROT 2-ROT
65syn keyword forthStack 3DUP 4DUP 5DUP 3DROP 4DROP 5DROP 8DROP 4SWAP 4ROT
66syn keyword forthStack 4-ROT 4TUCK 8SWAP 8DUP
Bram Moolenaar071d4272004-06-13 20:20:40 +000067syn keyword forthRStack >R R> R@ RDROP 2>R 2R> 2R@ 2RDROP
Bram Moolenaare37d50a2008-08-06 17:06:04 +000068syn keyword forthRstack 4>R 4R> 4R@ 4RDROP
Bram Moolenaar071d4272004-06-13 20:20:40 +000069syn keyword forthFStack FDROP FNIP FDUP FOVER FTUCK FSWAP FROT
70
71" stack pointer manipulations
Bram Moolenaar25a6e8a2018-03-30 12:27:32 +020072syn keyword forthSP SP@ SP! FP@ FP! RP@ RP! LP@ LP! DEPTH
Bram Moolenaar071d4272004-06-13 20:20:40 +000073
74" address operations
75syn keyword forthMemory @ ! +! C@ C! 2@ 2! F@ F! SF@ SF! DF@ DF!
76syn keyword forthAdrArith CHARS CHAR+ CELLS CELL+ CELL ALIGN ALIGNED FLOATS
77syn keyword forthAdrArith FLOAT+ FLOAT FALIGN FALIGNED SFLOATS SFLOAT+
78syn keyword forthAdrArith SFALIGN SFALIGNED DFLOATS DFLOAT+ DFALIGN DFALIGNED
79syn keyword forthAdrArith MAXALIGN MAXALIGNED CFALIGN CFALIGNED
80syn keyword forthAdrArith ADDRESS-UNIT-BITS ALLOT ALLOCATE HERE
Bram Moolenaar25a6e8a2018-03-30 12:27:32 +020081syn keyword forthMemBlks MOVE ERASE CMOVE CMOVE> FILL BLANK UNUSED
Bram Moolenaar071d4272004-06-13 20:20:40 +000082
83" conditionals
84syn keyword forthCond IF ELSE ENDIF THEN CASE OF ENDOF ENDCASE ?DUP-IF
85syn keyword forthCond ?DUP-0=-IF AHEAD CS-PICK CS-ROLL CATCH THROW WITHIN
86
87" iterations
88syn keyword forthLoop BEGIN WHILE REPEAT UNTIL AGAIN
89syn keyword forthLoop ?DO LOOP I J K +DO U+DO -DO U-DO DO +LOOP -LOOP
Bram Moolenaar25a6e8a2018-03-30 12:27:32 +020090syn keyword forthLoop UNLOOP LEAVE ?LEAVE EXIT DONE FOR NEXT RECURSE
Bram Moolenaar071d4272004-06-13 20:20:40 +000091
92" new words
Bram Moolenaare37d50a2008-08-06 17:06:04 +000093syn match forthClassDef '\<:class\s*[^ \t]\+\>'
94syn match forthObjectDef '\<:object\s*[^ \t]\+\>'
Bram Moolenaar071d4272004-06-13 20:20:40 +000095syn match forthColonDef '\<:m\?\s*[^ \t]\+\>'
96syn keyword forthEndOfColonDef ; ;M ;m
Bram Moolenaare37d50a2008-08-06 17:06:04 +000097syn keyword forthEndOfClassDef ;class
98syn keyword forthEndOfObjectDef ;object
99syn keyword forthDefine CONSTANT 2CONSTANT FCONSTANT VARIABLE 2VARIABLE
Bram Moolenaarbe4e0162023-02-02 13:59:48 +0000100syn keyword forthDefine FVARIABLE CREATE USER VALUE TO DEFER IS <BUILDS DOES> IMMEDIATE
Bram Moolenaare37d50a2008-08-06 17:06:04 +0000101syn keyword forthDefine COMPILE-ONLY COMPILE RESTRICT INTERPRET POSTPONE EXECUTE
102syn keyword forthDefine LITERAL CREATE-INTERPRET/COMPILE INTERPRETATION>
103syn keyword forthDefine <INTERPRETATION COMPILATION> <COMPILATION ] LASTXT
104syn keyword forthDefine COMP' POSTPONE, FIND-NAME NAME>INT NAME?INT NAME>COMP
Bram Moolenaar25a6e8a2018-03-30 12:27:32 +0200105syn keyword forthDefine NAME>STRING STATE C; CVARIABLE BUFFER: MARKER
106syn keyword forthDefine , 2, F, C, COMPILE,
Bram Moolenaarbe4e0162023-02-02 13:59:48 +0000107syn match forthDefine "\[DEFINED]"
108syn match forthDefine "\[UNDEFINED]"
109syn match forthDefine "\[IF]"
Bram Moolenaare37d50a2008-08-06 17:06:04 +0000110syn match forthDefine "\[IFDEF]"
111syn match forthDefine "\[IFUNDEF]"
112syn match forthDefine "\[THEN]"
113syn match forthDefine "\[ENDIF]"
114syn match forthDefine "\[ELSE]"
115syn match forthDefine "\[?DO]"
116syn match forthDefine "\[DO]"
117syn match forthDefine "\[LOOP]"
118syn match forthDefine "\[+LOOP]"
119syn match forthDefine "\[NEXT]"
120syn match forthDefine "\[BEGIN]"
121syn match forthDefine "\[UNTIL]"
122syn match forthDefine "\[AGAIN]"
123syn match forthDefine "\[WHILE]"
124syn match forthDefine "\[REPEAT]"
Bram Moolenaar071d4272004-06-13 20:20:40 +0000125syn match forthDefine "\[COMP']"
126syn match forthDefine "'"
127syn match forthDefine '\<\[\>'
128syn match forthDefine "\[']"
129syn match forthDefine '\[COMPILE]'
Bram Moolenaar25a6e8a2018-03-30 12:27:32 +0200130syn match forthDefine '\[CHAR]'
Bram Moolenaar071d4272004-06-13 20:20:40 +0000131
132" debugging
133syn keyword forthDebug PRINTDEBUGDATA PRINTDEBUGLINE
134syn match forthDebug "\<\~\~\>"
135
136" Assembler
137syn keyword forthAssembler ASSEMBLER CODE END-CODE ;CODE FLUSH-ICACHE C,
138
139" basic character operations
140syn keyword forthCharOps (.) CHAR EXPECT FIND WORD TYPE -TRAILING EMIT KEY
Bram Moolenaar25a6e8a2018-03-30 12:27:32 +0200141syn keyword forthCharOps KEY? TIB CR BL COUNT SPACE SPACES
Bram Moolenaar071d4272004-06-13 20:20:40 +0000142" recognize 'char (' or '[char] (' correctly, so it doesn't
143" highlight everything after the paren as a comment till a closing ')'
144syn match forthCharOps '\<char\s\S\s'
145syn match forthCharOps '\<\[char\]\s\S\s'
146syn region forthCharOps start=+."\s+ skip=+\\"+ end=+"+
147
148" char-number conversion
Bram Moolenaar6ee8d892012-01-10 14:55:01 +0100149syn keyword forthConversion <<# <# # #> #>> #S (NUMBER) (NUMBER?) CONVERT D>F
Bram Moolenaare37d50a2008-08-06 17:06:04 +0000150syn keyword forthConversion D>S DIGIT DPL F>D HLD HOLD NUMBER S>D SIGN >NUMBER
Bram Moolenaar25a6e8a2018-03-30 12:27:32 +0200151syn keyword forthConversion F>S S>F HOLDS
Bram Moolenaar071d4272004-06-13 20:20:40 +0000152
Bram Moolenaarcdf04202010-05-29 15:11:47 +0200153" interpreter, wordbook, compiler
Bram Moolenaar071d4272004-06-13 20:20:40 +0000154syn keyword forthForth (LOCAL) BYE COLD ABORT >BODY >NEXT >LINK CFA >VIEW HERE
155syn keyword forthForth PAD WORDS VIEW VIEW> N>LINK NAME> LINK> L>NAME FORGET
Bram Moolenaare37d50a2008-08-06 17:06:04 +0000156syn keyword forthForth BODY> ASSERT( ASSERT0( ASSERT1( ASSERT2( ASSERT3( )
Bram Moolenaar25a6e8a2018-03-30 12:27:32 +0200157syn keyword forthForth >IN ACCEPT ENVIRONMENT? EVALUATE QUIT SOURCE ACTION-OF
158syn keyword forthForth DEFER! DEFER@ PARSE PARSE-NAME REFILL RESTORE-INPUT
159syn keyword forthForth SAVE-INPUT SOURCE-ID
Bram Moolenaar071d4272004-06-13 20:20:40 +0000160syn region forthForth start=+ABORT"\s+ skip=+\\"+ end=+"+
161
162" vocabularies
163syn keyword forthVocs ONLY FORTH ALSO ROOT SEAL VOCS ORDER CONTEXT #VOCS
164syn keyword forthVocs VOCABULARY DEFINITIONS
165
Bram Moolenaare37d50a2008-08-06 17:06:04 +0000166" File keywords
Bram Moolenaar6ee8d892012-01-10 14:55:01 +0100167syn keyword forthFileMode R/O R/W W/O BIN
Bram Moolenaare37d50a2008-08-06 17:06:04 +0000168syn keyword forthFileWords OPEN-FILE CREATE-FILE CLOSE-FILE DELETE-FILE
169syn keyword forthFileWords RENAME-FILE READ-FILE READ-LINE KEY-FILE
170syn keyword forthFileWords KEY?-FILE WRITE-FILE WRITE-LINE EMIT-FILE
171syn keyword forthFileWords FLUSH-FILE FILE-STATUS FILE-POSITION
172syn keyword forthFileWords REPOSITION-FILE FILE-SIZE RESIZE-FILE
173syn keyword forthFileWords SLURP-FILE SLURP-FID STDIN STDOUT STDERR
Bram Moolenaar25a6e8a2018-03-30 12:27:32 +0200174syn keyword forthFileWords INCLUDE-FILE INCLUDED REQUIRED
Bram Moolenaare37d50a2008-08-06 17:06:04 +0000175syn keyword forthBlocks OPEN-BLOCKS USE LOAD --> BLOCK-OFFSET
176syn keyword forthBlocks GET-BLOCK-FID BLOCK-POSITION LIST SCR BLOCK
177syn keyword forthBlocks BUFER EMPTY-BUFFERS EMPTY-BUFFER UPDATE UPDATED?
178syn keyword forthBlocks SAVE-BUFFERS SAVE-BUFFER FLUSH THRU +LOAD +THRU
Bram Moolenaar25a6e8a2018-03-30 12:27:32 +0200179syn keyword forthBlocks BLOCK-INCLUDED BLK
Bram Moolenaare37d50a2008-08-06 17:06:04 +0000180
Bram Moolenaar071d4272004-06-13 20:20:40 +0000181" numbers
182syn keyword forthMath DECIMAL HEX BASE
Bram Moolenaar25a6e8a2018-03-30 12:27:32 +0200183syn match forthInteger '\<-\=[0-9]\+.\=\>'
184syn match forthInteger '\<&-\=[0-9]\+.\=\>'
Bram Moolenaarbe4e0162023-02-02 13:59:48 +0000185syn match forthInteger '\<#-\=[0-9]\+.\=\>'
Bram Moolenaar071d4272004-06-13 20:20:40 +0000186" recognize hex and binary numbers, the '$' and '%' notation is for gforth
Bram Moolenaar6c391a72021-09-09 21:55:11 +0200187syn match forthInteger '\<\$\x*\x\+\>' " *1* --- don't mess
Bram Moolenaar071d4272004-06-13 20:20:40 +0000188syn match forthInteger '\<\x*\d\x*\>' " *2* --- this order!
189syn match forthInteger '\<%[0-1]*[0-1]\+\>'
Bram Moolenaare37d50a2008-08-06 17:06:04 +0000190syn match forthFloat '\<-\=\d*[.]\=\d\+[DdEe]\d\+\>'
191syn match forthFloat '\<-\=\d*[.]\=\d\+[DdEe][-+]\d\+\>'
192
Bram Moolenaar25a6e8a2018-03-30 12:27:32 +0200193" XXX If you find this overkill you can remove it. this has to come after the
Bram Moolenaare37d50a2008-08-06 17:06:04 +0000194" highlighting for numbers otherwise it has no effect.
195syn region forthComment start='0 \[if\]' end='\[endif\]' end='\[then\]' contains=forthTodo
Bram Moolenaar071d4272004-06-13 20:20:40 +0000196
197" Strings
Bram Moolenaarbe4e0162023-02-02 13:59:48 +0000198syn region forthString start=+\.*\"+ end=+"+ end=+$+ contains=@Spell
Bram Moolenaar071d4272004-06-13 20:20:40 +0000199" XXX
Bram Moolenaarbe4e0162023-02-02 13:59:48 +0000200syn region forthString start=+s\"+ end=+"+ end=+$+ contains=@Spell
201syn region forthString start=+s\\\"+ end=+"+ end=+$+ contains=@Spell
202syn region forthString start=+c\"+ end=+"+ end=+$+ contains=@Spell
Bram Moolenaar071d4272004-06-13 20:20:40 +0000203
204" Comments
Bram Moolenaarbe4e0162023-02-02 13:59:48 +0000205syn match forthComment '\\\%(\s.*\)\=$' contains=@Spell,forthTodo,forthSpaceError
206syn region forthComment start='\\S\s' end='.*' contains=@Spell,forthTodo,forthSpaceError
207syn match forthComment '\.(\s[^)]*)' contains=@Spell,forthTodo,forthSpaceError
208syn region forthComment start='\(^\|\s\)\zs(\s' skip='\\)' end=')' contains=@Spell,forthTodo,forthSpaceError
209syn region forthComment start='/\*' end='\*/' contains=@Spell,forthTodo,forthSpaceError
Bram Moolenaar071d4272004-06-13 20:20:40 +0000210
211" Include files
212syn match forthInclude '^INCLUDE\s\+\k\+'
Bram Moolenaar25a6e8a2018-03-30 12:27:32 +0200213syn match forthInclude '^REQUIRE\s\+\k\+'
214syn match forthInclude '^FLOAD\s\+'
215syn match forthInclude '^NEEDS\s\+'
Bram Moolenaar071d4272004-06-13 20:20:40 +0000216
Bram Moolenaare37d50a2008-08-06 17:06:04 +0000217" Locals definitions
218syn region forthLocals start='{\s' start='{$' end='\s}' end='^}'
219syn match forthLocals '{ }' " otherwise, at least two spaces between
220syn region forthDeprecated start='locals|' end='|'
221
Bram Moolenaar071d4272004-06-13 20:20:40 +0000222" Define the default highlighting.
Bram Moolenaarf37506f2016-08-31 22:22:10 +0200223hi def link forthTodo Todo
224hi def link forthOperators Operator
225hi def link forthMath Number
226hi def link forthInteger Number
227hi def link forthFloat Float
228hi def link forthStack Special
229hi def link forthRstack Special
230hi def link forthFStack Special
231hi def link forthSP Special
232hi def link forthMemory Function
233hi def link forthAdrArith Function
234hi def link forthMemBlks Function
235hi def link forthCond Conditional
236hi def link forthLoop Repeat
237hi def link forthColonDef Define
238hi def link forthEndOfColonDef Define
239hi def link forthDefine Define
240hi def link forthDebug Debug
241hi def link forthAssembler Include
242hi def link forthCharOps Character
243hi def link forthConversion String
244hi def link forthForth Statement
245hi def link forthVocs Statement
246hi def link forthString String
247hi def link forthComment Comment
248hi def link forthClassDef Define
249hi def link forthEndOfClassDef Define
250hi def link forthObjectDef Define
251hi def link forthEndOfObjectDef Define
252hi def link forthInclude Include
253hi def link forthLocals Type " nothing else uses type and locals must stand out
254hi def link forthDeprecated Error " if you must, change to Type
255hi def link forthFileMode Function
Bram Moolenaar25a6e8a2018-03-30 12:27:32 +0200256hi def link forthFunction Function
Bram Moolenaarf37506f2016-08-31 22:22:10 +0200257hi def link forthFileWords Statement
258hi def link forthBlocks Statement
259hi def link forthSpaceError Error
Bram Moolenaar071d4272004-06-13 20:20:40 +0000260
Bram Moolenaar071d4272004-06-13 20:20:40 +0000261let b:current_syntax = "forth"
262
Bram Moolenaar6ee8d892012-01-10 14:55:01 +0100263let &cpo = s:cpo_save
264unlet s:cpo_save
Bram Moolenaar071d4272004-06-13 20:20:40 +0000265" vim:ts=8:sw=4:nocindent:smartindent:
Bram Moolenaarbe4e0162023-02-02 13:59:48 +0000266