xref: /vim-8.2.3635/runtime/syntax/lisp.vim (revision 818c9e7e)
1" Vim syntax file
2" Language:    Lisp
3" Maintainer:  Charles E. Campbell <[email protected]>
4" Last Change: Jan 20, 2016
5" Version:     24
6" URL:	       http://www.drchip.org/astronaut/vim/index.html#SYNTAX_LISP
7"
8"  Thanks to F Xavier Noria for a list of 978 Common Lisp symbols taken from HyperSpec
9"  Clisp additions courtesy of http://clisp.cvs.sourceforge.net/*checkout*/clisp/clisp/emacs/lisp.vim
10
11" ---------------------------------------------------------------------
12"  Load Once: {{{1
13if exists("b:current_syntax")
14 finish
15endif
16
17if exists("g:lisp_isk")
18 exe "setl isk=".g:lisp_isk
19elseif !has("patch-7.4.1141")
20 setl isk=38,42,43,45,47-58,60-62,64-90,97-122,_
21else
22 syn iskeyword 38,42,43,45,47-58,60-62,64-90,97-122,_
23endif
24
25if exists("g:lispsyntax_ignorecase") || exists("g:lispsyntax_clisp")
26 set ignorecase
27endif
28
29" ---------------------------------------------------------------------
30" Clusters: {{{1
31syn cluster			lispAtomCluster		contains=lispAtomBarSymbol,lispAtomList,lispAtomNmbr0,lispComment,lispDecl,lispFunc,lispLeadWhite
32syn cluster			lispBaseListCluster	contains=lispAtom,lispAtomBarSymbol,lispAtomMark,lispBQList,lispBarSymbol,lispComment,lispConcat,lispDecl,lispFunc,lispKey,lispList,lispNumber,lispEscapeSpecial,lispSymbol,lispVar,lispLeadWhite
33if exists("g:lisp_instring")
34 syn cluster			lispListCluster		contains=@lispBaseListCluster,lispString,lispInString,lispInStringString
35else
36 syn cluster			lispListCluster		contains=@lispBaseListCluster,lispString
37endif
38
39syn case ignore
40
41" ---------------------------------------------------------------------
42" Lists: {{{1
43syn match			lispSymbol			contained			![^()'`,"; \t]\+!
44syn match			lispBarSymbol			contained			!|..\{-}|!
45if exists("g:lisp_rainbow") && g:lisp_rainbow != 0
46 syn region lispParen0           matchgroup=hlLevel0 start="`\=(" end=")" skip="|.\{-}|" contains=@lispListCluster,lispParen1
47 syn region lispParen1 contained matchgroup=hlLevel1 start="`\=(" end=")" skip="|.\{-}|" contains=@lispListCluster,lispParen2
48 syn region lispParen2 contained matchgroup=hlLevel2 start="`\=(" end=")" skip="|.\{-}|" contains=@lispListCluster,lispParen3
49 syn region lispParen3 contained matchgroup=hlLevel3 start="`\=(" end=")" skip="|.\{-}|" contains=@lispListCluster,lispParen4
50 syn region lispParen4 contained matchgroup=hlLevel4 start="`\=(" end=")" skip="|.\{-}|" contains=@lispListCluster,lispParen5
51 syn region lispParen5 contained matchgroup=hlLevel5 start="`\=(" end=")" skip="|.\{-}|" contains=@lispListCluster,lispParen6
52 syn region lispParen6 contained matchgroup=hlLevel6 start="`\=(" end=")" skip="|.\{-}|" contains=@lispListCluster,lispParen7
53 syn region lispParen7 contained matchgroup=hlLevel7 start="`\=(" end=")" skip="|.\{-}|" contains=@lispListCluster,lispParen8
54 syn region lispParen8 contained matchgroup=hlLevel8 start="`\=(" end=")" skip="|.\{-}|" contains=@lispListCluster,lispParen9
55 syn region lispParen9 contained matchgroup=hlLevel9 start="`\=(" end=")" skip="|.\{-}|" contains=@lispListCluster,lispParen0
56else
57 syn region lispList			matchgroup=Delimiter start="("   skip="|.\{-}|"			matchgroup=Delimiter end=")"	contains=@lispListCluster
58 syn region lispBQList			matchgroup=PreProc   start="`("  skip="|.\{-}|"			matchgroup=PreProc   end=")"		contains=@lispListCluster
59endif
60
61" ---------------------------------------------------------------------
62" Atoms: {{{1
63syn match lispAtomMark			"'"
64syn match lispAtom			"'("me=e-1			contains=lispAtomMark	nextgroup=lispAtomList
65syn match lispAtom			"'[^ \t()]\+"			contains=lispAtomMark
66syn match lispAtomBarSymbol		!'|..\{-}|!			contains=lispAtomMark
67syn region lispAtom			start=+'"+			skip=+\\"+ end=+"+
68syn region lispAtomList			contained			matchgroup=Special start="("	skip="|.\{-}|" matchgroup=Special end=")"	contains=@lispAtomCluster,lispString,lispEscapeSpecial
69syn match lispAtomNmbr			contained			"\<\d\+"
70syn match lispLeadWhite			contained			"^\s\+"
71
72" ---------------------------------------------------------------------
73" Standard Lisp Functions and Macros: {{{1
74syn keyword lispFunc		*				find-method					pprint-indent
75syn keyword lispFunc		**				find-package					pprint-linear
76syn keyword lispFunc		***				find-restart					pprint-logical-block
77syn keyword lispFunc		+				find-symbol					pprint-newline
78syn keyword lispFunc		++				finish-output					pprint-pop
79syn keyword lispFunc		+++				first						pprint-tab
80syn keyword lispFunc		-				fixnum						pprint-tabular
81syn keyword lispFunc		/				flet						prin1
82syn keyword lispFunc		//				float						prin1-to-string
83syn keyword lispFunc		///				float-digits					princ
84syn keyword lispFunc		/=				float-precision					princ-to-string
85syn keyword lispFunc		1+				float-radix					print
86syn keyword lispFunc		1-				float-sign					print-not-readable
87syn keyword lispFunc		<				floating-point-inexact				print-not-readable-object
88syn keyword lispFunc		<=				floating-point-invalid-operation print-object
89syn keyword lispFunc		=				floating-point-overflow				print-unreadable-object
90syn keyword lispFunc		>				floating-point-underflow			probe-file
91syn keyword lispFunc		>=				floatp						proclaim
92syn keyword lispFunc		abort				floor						prog
93syn keyword lispFunc		abs				fmakunbound					prog*
94syn keyword lispFunc		access				force-output					prog1
95syn keyword lispFunc		acons				format						prog2
96syn keyword lispFunc		acos				formatter					progn
97syn keyword lispFunc		acosh				fourth						program-error
98syn keyword lispFunc		add-method			fresh-line					progv
99syn keyword lispFunc		adjoin				fround						provide
100syn keyword lispFunc		adjust-array			ftruncate					psetf
101syn keyword lispFunc		adjustable-array-p		ftype						psetq
102syn keyword lispFunc		allocate-instance		funcall						push
103syn keyword lispFunc		alpha-char-p			function					pushnew
104syn keyword lispFunc		alphanumericp			function-keywords				putprop
105syn keyword lispFunc		and				function-lambda-expression			quote
106syn keyword lispFunc		append				functionp					random
107syn keyword lispFunc		apply				gbitp						random-state
108syn keyword lispFunc		applyhook			gcd						random-state-p
109syn keyword lispFunc		apropos				generic-function				rassoc
110syn keyword lispFunc		apropos-list			gensym						rassoc-if
111syn keyword lispFunc		aref				gentemp						rassoc-if-not
112syn keyword lispFunc		arithmetic-error		get						ratio
113syn keyword lispFunc		arithmetic-error-operands	get-decoded-time				rational
114syn keyword lispFunc		arithmetic-error-operation	get-dispatch-macro-character			rationalize
115syn keyword lispFunc		array				get-internal-real-time				rationalp
116syn keyword lispFunc		array-dimension			get-internal-run-time				read
117syn keyword lispFunc		array-dimension-limit		get-macro-character				read-byte
118syn keyword lispFunc		array-dimensions		get-output-stream-string			read-char
119syn keyword lispFunc		array-displacement		get-properties					read-char-no-hang
120syn keyword lispFunc		array-element-type		get-setf-expansion				read-delimited-list
121syn keyword lispFunc		array-has-fill-pointer-p	get-setf-method					read-eval-print
122syn keyword lispFunc		array-in-bounds-p		get-universal-time				read-from-string
123syn keyword lispFunc		array-rank			getf						read-line
124syn keyword lispFunc		array-rank-limit		gethash						read-preserving-whitespace
125syn keyword lispFunc		array-row-major-index		go						read-sequence
126syn keyword lispFunc		array-total-size		graphic-char-p					reader-error
127syn keyword lispFunc		array-total-size-limit		handler-bind					readtable
128syn keyword lispFunc		arrayp				handler-case					readtable-case
129syn keyword lispFunc		ash				hash-table					readtablep
130syn keyword lispFunc		asin				hash-table-count				real
131syn keyword lispFunc		asinh				hash-table-p					realp
132syn keyword lispFunc		assert				hash-table-rehash-size				realpart
133syn keyword lispFunc		assoc				hash-table-rehash-threshold			reduce
134syn keyword lispFunc		assoc-if			hash-table-size					reinitialize-instance
135syn keyword lispFunc		assoc-if-not			hash-table-test					rem
136syn keyword lispFunc		atan				host-namestring					remf
137syn keyword lispFunc		atanh				identity					remhash
138syn keyword lispFunc		atom				if						remove
139syn keyword lispFunc		base-char			if-exists					remove-duplicates
140syn keyword lispFunc		base-string			ignorable					remove-if
141syn keyword lispFunc		bignum				ignore						remove-if-not
142syn keyword lispFunc		bit				ignore-errors					remove-method
143syn keyword lispFunc		bit-and				imagpart					remprop
144syn keyword lispFunc		bit-andc1			import						rename-file
145syn keyword lispFunc		bit-andc2			in-package					rename-package
146syn keyword lispFunc		bit-eqv				in-package					replace
147syn keyword lispFunc		bit-ior				incf						require
148syn keyword lispFunc		bit-nand			initialize-instance				rest
149syn keyword lispFunc		bit-nor				inline						restart
150syn keyword lispFunc		bit-not				input-stream-p					restart-bind
151syn keyword lispFunc		bit-orc1			inspect						restart-case
152syn keyword lispFunc		bit-orc2			int-char					restart-name
153syn keyword lispFunc		bit-vector			integer						return
154syn keyword lispFunc		bit-vector-p			integer-decode-float				return-from
155syn keyword lispFunc		bit-xor				integer-length					revappend
156syn keyword lispFunc		block				integerp					reverse
157syn keyword lispFunc		boole				interactive-stream-p				room
158syn keyword lispFunc		boole-1				intern						rotatef
159syn keyword lispFunc		boole-2				internal-time-units-per-second			round
160syn keyword lispFunc		boole-and			intersection					row-major-aref
161syn keyword lispFunc		boole-andc1			invalid-method-error				rplaca
162syn keyword lispFunc		boole-andc2			invoke-debugger					rplacd
163syn keyword lispFunc		boole-c1			invoke-restart					safety
164syn keyword lispFunc		boole-c2			invoke-restart-interactively			satisfies
165syn keyword lispFunc		boole-clr			isqrt						sbit
166syn keyword lispFunc		boole-eqv			keyword						scale-float
167syn keyword lispFunc		boole-ior			keywordp					schar
168syn keyword lispFunc		boole-nand			labels						search
169syn keyword lispFunc		boole-nor			lambda						second
170syn keyword lispFunc		boole-orc1			lambda-list-keywords				sequence
171syn keyword lispFunc		boole-orc2			lambda-parameters-limit				serious-condition
172syn keyword lispFunc		boole-set			last						set
173syn keyword lispFunc		boole-xor			lcm						set-char-bit
174syn keyword lispFunc		boolean				ldb						set-difference
175syn keyword lispFunc		both-case-p			ldb-test					set-dispatch-macro-character
176syn keyword lispFunc		boundp				ldiff						set-exclusive-or
177syn keyword lispFunc		break				least-negative-double-float			set-macro-character
178syn keyword lispFunc		broadcast-stream		least-negative-long-float			set-pprint-dispatch
179syn keyword lispFunc		broadcast-stream-streams	least-negative-normalized-double-float		set-syntax-from-char
180syn keyword lispFunc		built-in-class			least-negative-normalized-long-float		setf
181syn keyword lispFunc		butlast				least-negative-normalized-short-float		setq
182syn keyword lispFunc		byte				least-negative-normalized-single-float		seventh
183syn keyword lispFunc		byte-position			least-negative-short-float			shadow
184syn keyword lispFunc		byte-size			least-negative-single-float			shadowing-import
185syn keyword lispFunc		call-arguments-limit		least-positive-double-float			shared-initialize
186syn keyword lispFunc		call-method			least-positive-long-float			shiftf
187syn keyword lispFunc		call-next-method		least-positive-normalized-double-float		short-float
188syn keyword lispFunc		capitalize			least-positive-normalized-long-float		short-float-epsilon
189syn keyword lispFunc		car				least-positive-normalized-short-float		short-float-negative-epsilon
190syn keyword lispFunc		case				least-positive-normalized-single-float		short-site-name
191syn keyword lispFunc		catch				least-positive-short-float			signal
192syn keyword lispFunc		ccase				least-positive-single-float			signed-byte
193syn keyword lispFunc		cdr				length						signum
194syn keyword lispFunc		ceiling				let						simple-condition
195syn keyword lispFunc		cell-error			let*						simple-array
196syn keyword lispFunc		cell-error-name			lisp						simple-base-string
197syn keyword lispFunc		cerror				lisp-implementation-type			simple-bit-vector
198syn keyword lispFunc		change-class			lisp-implementation-version			simple-bit-vector-p
199syn keyword lispFunc		char				list						simple-condition-format-arguments
200syn keyword lispFunc		char-bit			list*						simple-condition-format-control
201syn keyword lispFunc		char-bits			list-all-packages				simple-error
202syn keyword lispFunc		char-bits-limit			list-length					simple-string
203syn keyword lispFunc		char-code			listen						simple-string-p
204syn keyword lispFunc		char-code-limit			listp						simple-type-error
205syn keyword lispFunc		char-control-bit		load						simple-vector
206syn keyword lispFunc		char-downcase			load-logical-pathname-translations		simple-vector-p
207syn keyword lispFunc		char-equal			load-time-value					simple-warning
208syn keyword lispFunc		char-font			locally						sin
209syn keyword lispFunc		char-font-limit			log						single-flaot-epsilon
210syn keyword lispFunc		char-greaterp			logand						single-float
211syn keyword lispFunc		char-hyper-bit			logandc1					single-float-epsilon
212syn keyword lispFunc		char-int			logandc2					single-float-negative-epsilon
213syn keyword lispFunc		char-lessp			logbitp						sinh
214syn keyword lispFunc		char-meta-bit			logcount					sixth
215syn keyword lispFunc		char-name			logeqv						sleep
216syn keyword lispFunc		char-not-equal			logical-pathname				slot-boundp
217syn keyword lispFunc		char-not-greaterp		logical-pathname-translations			slot-exists-p
218syn keyword lispFunc		char-not-lessp			logior						slot-makunbound
219syn keyword lispFunc		char-super-bit			lognand						slot-missing
220syn keyword lispFunc		char-upcase			lognor						slot-unbound
221syn keyword lispFunc		char/=				lognot						slot-value
222syn keyword lispFunc		char<				logorc1						software-type
223syn keyword lispFunc		char<=				logorc2						software-version
224syn keyword lispFunc		char=				logtest						some
225syn keyword lispFunc		char>				logxor						sort
226syn keyword lispFunc		char>=				long-float					space
227syn keyword lispFunc		character			long-float-epsilon				special
228syn keyword lispFunc		characterp			long-float-negative-epsilon			special-form-p
229syn keyword lispFunc		check-type			long-site-name					special-operator-p
230syn keyword lispFunc		cis				loop						speed
231syn keyword lispFunc		class				loop-finish					sqrt
232syn keyword lispFunc		class-name			lower-case-p					stable-sort
233syn keyword lispFunc		class-of			machine-instance				standard
234syn keyword lispFunc		clear-input			machine-type					standard-char
235syn keyword lispFunc		clear-output			machine-version					standard-char-p
236syn keyword lispFunc		close				macro-function					standard-class
237syn keyword lispFunc		clrhash				macroexpand					standard-generic-function
238syn keyword lispFunc		code-char			macroexpand-1					standard-method
239syn keyword lispFunc		coerce				macroexpand-l					standard-object
240syn keyword lispFunc		commonp				macrolet					step
241syn keyword lispFunc		compilation-speed		make-array					storage-condition
242syn keyword lispFunc		compile				make-array					store-value
243syn keyword lispFunc		compile-file			make-broadcast-stream				stream
244syn keyword lispFunc		compile-file-pathname		make-char					stream-element-type
245syn keyword lispFunc		compiled-function		make-concatenated-stream			stream-error
246syn keyword lispFunc		compiled-function-p		make-condition					stream-error-stream
247syn keyword lispFunc		compiler-let			make-dispatch-macro-character			stream-external-format
248syn keyword lispFunc		compiler-macro			make-echo-stream				streamp
249syn keyword lispFunc		compiler-macro-function	make-hash-table						streamup
250syn keyword lispFunc		complement			make-instance					string
251syn keyword lispFunc		complex				make-instances-obsolete				string-capitalize
252syn keyword lispFunc		complexp			make-list					string-char
253syn keyword lispFunc		compute-applicable-methods	make-load-form					string-char-p
254syn keyword lispFunc		compute-restarts		make-load-form-saving-slots			string-downcase
255syn keyword lispFunc		concatenate			make-method					string-equal
256syn keyword lispFunc		concatenated-stream		make-package					string-greaterp
257syn keyword lispFunc		concatenated-stream-streams	make-pathname					string-left-trim
258syn keyword lispFunc		cond				make-random-state				string-lessp
259syn keyword lispFunc		condition			make-sequence					string-not-equal
260syn keyword lispFunc		conjugate			make-string					string-not-greaterp
261syn keyword lispFunc		cons				make-string-input-stream			string-not-lessp
262syn keyword lispFunc		consp				make-string-output-stream			string-right-strim
263syn keyword lispFunc		constantly			make-symbol					string-right-trim
264syn keyword lispFunc		constantp			make-synonym-stream				string-stream
265syn keyword lispFunc		continue			make-two-way-stream				string-trim
266syn keyword lispFunc		control-error			makunbound					string-upcase
267syn keyword lispFunc		copy-alist			map						string/=
268syn keyword lispFunc		copy-list			map-into					string<
269syn keyword lispFunc		copy-pprint-dispatch		mapc						string<=
270syn keyword lispFunc		copy-readtable			mapcan						string=
271syn keyword lispFunc		copy-seq			mapcar						string>
272syn keyword lispFunc		copy-structure			mapcon						string>=
273syn keyword lispFunc		copy-symbol			maphash						stringp
274syn keyword lispFunc		copy-tree			mapl						structure
275syn keyword lispFunc		cos				maplist						structure-class
276syn keyword lispFunc		cosh				mask-field					structure-object
277syn keyword lispFunc		count				max						style-warning
278syn keyword lispFunc		count-if			member						sublim
279syn keyword lispFunc		count-if-not			member-if					sublis
280syn keyword lispFunc		ctypecase			member-if-not					subseq
281syn keyword lispFunc		debug				merge						subsetp
282syn keyword lispFunc		decf				merge-pathname					subst
283syn keyword lispFunc		declaim				merge-pathnames					subst-if
284syn keyword lispFunc		declaration			method						subst-if-not
285syn keyword lispFunc		declare				method-combination				substitute
286syn keyword lispFunc		decode-float			method-combination-error			substitute-if
287syn keyword lispFunc		decode-universal-time		method-qualifiers				substitute-if-not
288syn keyword lispFunc		defclass			min						subtypep
289syn keyword lispFunc		defconstant			minusp						svref
290syn keyword lispFunc		defgeneric			mismatch					sxhash
291syn keyword lispFunc		define-compiler-macro		mod						symbol
292syn keyword lispFunc		define-condition		most-negative-double-float			symbol-function
293syn keyword lispFunc		define-method-combination	most-negative-fixnum				symbol-macrolet
294syn keyword lispFunc		define-modify-macro		most-negative-long-float			symbol-name
295syn keyword lispFunc		define-setf-expander		most-negative-short-float			symbol-package
296syn keyword lispFunc		define-setf-method		most-negative-single-float			symbol-plist
297syn keyword lispFunc		define-symbol-macro		most-positive-double-float			symbol-value
298syn keyword lispFunc		defmacro			most-positive-fixnum				symbolp
299syn keyword lispFunc		defmethod			most-positive-long-float			synonym-stream
300syn keyword lispFunc		defpackage			most-positive-short-float			synonym-stream-symbol
301syn keyword lispFunc		defparameter			most-positive-single-float			sys
302syn keyword lispFunc		defsetf				muffle-warning					system
303syn keyword lispFunc		defstruct			multiple-value-bind				t
304syn keyword lispFunc		deftype				multiple-value-call				tagbody
305syn keyword lispFunc		defun				multiple-value-list				tailp
306syn keyword lispFunc		defvar				multiple-value-prog1				tan
307syn keyword lispFunc		delete				multiple-value-seteq				tanh
308syn keyword lispFunc		delete-duplicates		multiple-value-setq				tenth
309syn keyword lispFunc		delete-file			multiple-values-limit				terpri
310syn keyword lispFunc		delete-if			name-char					the
311syn keyword lispFunc		delete-if-not			namestring					third
312syn keyword lispFunc		delete-package			nbutlast					throw
313syn keyword lispFunc		denominator			nconc						time
314syn keyword lispFunc		deposit-field			next-method-p					trace
315syn keyword lispFunc		describe			nil						translate-logical-pathname
316syn keyword lispFunc		describe-object			nintersection					translate-pathname
317syn keyword lispFunc		destructuring-bind		ninth						tree-equal
318syn keyword lispFunc		digit-char			no-applicable-method				truename
319syn keyword lispFunc		digit-char-p			no-next-method					truncase
320syn keyword lispFunc		directory			not						truncate
321syn keyword lispFunc		directory-namestring		notany						two-way-stream
322syn keyword lispFunc		disassemble			notevery					two-way-stream-input-stream
323syn keyword lispFunc		division-by-zero		notinline					two-way-stream-output-stream
324syn keyword lispFunc		do				nreconc						type
325syn keyword lispFunc		do*				nreverse					type-error
326syn keyword lispFunc		do-all-symbols			nset-difference					type-error-datum
327syn keyword lispFunc		do-exeternal-symbols		nset-exclusive-or				type-error-expected-type
328syn keyword lispFunc		do-external-symbols		nstring						type-of
329syn keyword lispFunc		do-symbols			nstring-capitalize				typecase
330syn keyword lispFunc		documentation			nstring-downcase				typep
331syn keyword lispFunc		dolist				nstring-upcase					unbound-slot
332syn keyword lispFunc		dotimes				nsublis						unbound-slot-instance
333syn keyword lispFunc		double-float			nsubst						unbound-variable
334syn keyword lispFunc		double-float-epsilon		nsubst-if					undefined-function
335syn keyword lispFunc		double-float-negative-epsilon	nsubst-if-not					unexport
336syn keyword lispFunc		dpb				nsubstitute					unintern
337syn keyword lispFunc		dribble				nsubstitute-if					union
338syn keyword lispFunc		dynamic-extent			nsubstitute-if-not				unless
339syn keyword lispFunc		ecase				nth						unread
340syn keyword lispFunc		echo-stream			nth-value					unread-char
341syn keyword lispFunc		echo-stream-input-stream	nthcdr						unsigned-byte
342syn keyword lispFunc		echo-stream-output-stream	null						untrace
343syn keyword lispFunc		ed				number						unuse-package
344syn keyword lispFunc		eighth				numberp						unwind-protect
345syn keyword lispFunc		elt				numerator					update-instance-for-different-class
346syn keyword lispFunc		encode-universal-time		nunion						update-instance-for-redefined-class
347syn keyword lispFunc		end-of-file			oddp						upgraded-array-element-type
348syn keyword lispFunc		endp				open						upgraded-complex-part-type
349syn keyword lispFunc		enough-namestring		open-stream-p					upper-case-p
350syn keyword lispFunc		ensure-directories-exist	optimize					use-package
351syn keyword lispFunc		ensure-generic-function	or							use-value
352syn keyword lispFunc		eq				otherwise					user
353syn keyword lispFunc		eql				output-stream-p					user-homedir-pathname
354syn keyword lispFunc		equal				package						values
355syn keyword lispFunc		equalp				package-error					values-list
356syn keyword lispFunc		error				package-error-package				vector
357syn keyword lispFunc		etypecase			package-name					vector-pop
358syn keyword lispFunc		eval				package-nicknames				vector-push
359syn keyword lispFunc		eval-when			package-shadowing-symbols			vector-push-extend
360syn keyword lispFunc		evalhook			package-use-list				vectorp
361syn keyword lispFunc		evenp				package-used-by-list				warn
362syn keyword lispFunc		every				packagep					warning
363syn keyword lispFunc		exp				pairlis						when
364syn keyword lispFunc		export				parse-error					wild-pathname-p
365syn keyword lispFunc		expt				parse-integer					with-accessors
366syn keyword lispFunc		extended-char			parse-namestring				with-compilation-unit
367syn keyword lispFunc		fboundp				pathname					with-condition-restarts
368syn keyword lispFunc		fceiling			pathname-device					with-hash-table-iterator
369syn keyword lispFunc		fdefinition			pathname-directory				with-input-from-string
370syn keyword lispFunc		ffloor				pathname-host					with-open-file
371syn keyword lispFunc		fifth				pathname-match-p				with-open-stream
372syn keyword lispFunc		file-author			pathname-name					with-output-to-string
373syn keyword lispFunc		file-error			pathname-type					with-package-iterator
374syn keyword lispFunc		file-error-pathname		pathname-version				with-simple-restart
375syn keyword lispFunc		file-length			pathnamep					with-slots
376syn keyword lispFunc		file-namestring			peek-char					with-standard-io-syntax
377syn keyword lispFunc		file-position			phase						write
378syn keyword lispFunc		file-stream			pi						write-byte
379syn keyword lispFunc		file-string-length		plusp						write-char
380syn keyword lispFunc		file-write-date			pop						write-line
381syn keyword lispFunc		fill				position					write-sequence
382syn keyword lispFunc		fill-pointer			position-if					write-string
383syn keyword lispFunc		find				position-if-not					write-to-string
384syn keyword lispFunc		find-all-symbols		pprint						y-or-n-p
385syn keyword lispFunc		find-class			pprint-dispatch					yes-or-no-p
386syn keyword lispFunc		find-if				pprint-exit-if-list-exhausted			zerop
387syn keyword lispFunc		find-if-not			pprint-fill
388
389syn match   lispFunc		"\<c[ad]\+r\>"
390if exists("g:lispsyntax_clisp")
391  " CLISP FFI:
392  syn match lispFunc	"\<\(ffi:\)\?with-c-\(place\|var\)\>"
393  syn match lispFunc	"\<\(ffi:\)\?with-foreign-\(object\|string\)\>"
394  syn match lispFunc	"\<\(ffi:\)\?default-foreign-\(language\|library\)\>"
395  syn match lispFunc	"\<\([us]_\?\)\?\(element\|deref\|cast\|slot\|validp\)\>"
396  syn match lispFunc	"\<\(ffi:\)\?set-foreign-pointer\>"
397  syn match lispFunc	"\<\(ffi:\)\?allocate-\(deep\|shallow\)\>"
398  syn match lispFunc	"\<\(ffi:\)\?c-lines\>"
399  syn match lispFunc	"\<\(ffi:\)\?foreign-\(value\|free\|variable\|function\|object\)\>"
400  syn match lispFunc	"\<\(ffi:\)\?foreign-address\(-null\|unsigned\)\?\>"
401  syn match lispFunc	"\<\(ffi:\)\?undigned-foreign-address\>"
402  syn match lispFunc	"\<\(ffi:\)\?c-var-\(address\|object\)\>"
403  syn match lispFunc	"\<\(ffi:\)\?typeof\>"
404  syn match lispFunc	"\<\(ffi:\)\?\(bit\)\?sizeof\>"
405" CLISP Macros, functions et al:
406  syn match lispFunc	"\<\(ext:\)\?with-collect\>"
407  syn match lispFunc	"\<\(ext:\)\?letf\*\?\>"
408  syn match lispFunc	"\<\(ext:\)\?finalize\>\>"
409  syn match lispFunc	"\<\(ext:\)\?memoized\>"
410  syn match lispFunc	"\<\(ext:\)\?getenv\>"
411  syn match lispFunc	"\<\(ext:\)\?convert-string-\(to\|from\)-bytes\>"
412  syn match lispFunc	"\<\(ext:\)\?ethe\>"
413  syn match lispFunc	"\<\(ext:\)\?with-gensyms\>"
414  syn match lispFunc	"\<\(ext:\)\?open-http\>"
415  syn match lispFunc	"\<\(ext:\)\?string-concat\>"
416  syn match lispFunc	"\<\(ext:\)\?with-http-\(in\|out\)put\>"
417  syn match lispFunc	"\<\(ext:\)\?with-html-output\>"
418  syn match lispFunc	"\<\(ext:\)\?expand-form\>"
419  syn match lispFunc	"\<\(ext:\)\?\(without-\)\?package-lock\>"
420  syn match lispFunc	"\<\(ext:\)\?re-export\>"
421  syn match lispFunc	"\<\(ext:\)\?saveinitmem\>"
422  syn match lispFunc	"\<\(ext:\)\?\(read\|write\)-\(integer\|float\)\>"
423  syn match lispFunc	"\<\(ext:\)\?\(read\|write\)-\(char\|byte\)-sequence\>"
424  syn match lispFunc	"\<\(custom:\)\?\*system-package-list\*\>"
425  syn match lispFunc	"\<\(custom:\)\?\*ansi\*\>"
426endif
427
428" ---------------------------------------------------------------------
429" Lisp Keywords (modifiers): {{{1
430syn keyword lispKey		:abort				:from-end			:overwrite
431syn keyword lispKey		:adjustable			:gensym				:predicate
432syn keyword lispKey		:append				:host				:preserve-whitespace
433syn keyword lispKey		:array				:if-does-not-exist		:pretty
434syn keyword lispKey		:base				:if-exists			:print
435syn keyword lispKey		:case				:include			:print-function
436syn keyword lispKey		:circle				:index				:probe
437syn keyword lispKey		:conc-name			:inherited			:radix
438syn keyword lispKey		:constructor			:initial-contents		:read-only
439syn keyword lispKey		:copier				:initial-element		:rehash-size
440syn keyword lispKey		:count				:initial-offset			:rehash-threshold
441syn keyword lispKey		:create				:initial-value			:rename
442syn keyword lispKey		:default			:input				:rename-and-delete
443syn keyword lispKey		:defaults			:internal			:size
444syn keyword lispKey		:device				:io				:start
445syn keyword lispKey		:direction			:junk-allowed			:start1
446syn keyword lispKey		:directory			:key				:start2
447syn keyword lispKey		:displaced-index-offset		:length				:stream
448syn keyword lispKey		:displaced-to			:level				:supersede
449syn keyword lispKey		:element-type			:name				:test
450syn keyword lispKey		:end				:named				:test-not
451syn keyword lispKey		:end1				:new-version			:type
452syn keyword lispKey		:end2				:nicknames			:use
453syn keyword lispKey		:error				:output				:verbose
454syn keyword lispKey		:escape				:output-file			:version
455syn keyword lispKey		:external
456" defpackage arguments
457syn keyword lispKey	:documentation	:shadowing-import-from	:modern		:export
458syn keyword lispKey	:case-sensitive	:case-inverted		:shadow		:import-from	:intern
459" lambda list keywords
460syn keyword lispKey	&allow-other-keys	&aux		&body
461syn keyword lispKey	&environment	&key			&optional	&rest		&whole
462" make-array argument
463syn keyword lispKey	:fill-pointer
464" readtable-case values
465syn keyword lispKey	:upcase		:downcase		:preserve	:invert
466" eval-when situations
467syn keyword lispKey	:load-toplevel	:compile-toplevel	:execute
468" ANSI Extended LOOP:
469syn keyword lispKey	:while      :until       :for         :do       :if          :then         :else     :when      :unless :in
470syn keyword lispKey	:across     :finally     :collect     :nconc    :maximize    :minimize     :sum
471syn keyword lispKey	:and        :with        :initially   :append   :into        :count        :end      :repeat
472syn keyword lispKey	:always     :never       :thereis     :from     :to          :upto         :downto   :below
473syn keyword lispKey	:above      :by          :on          :being    :each        :the          :hash-key :hash-keys
474syn keyword lispKey	:hash-value :hash-values :using       :of-type  :upfrom      :downfrom
475if exists("g:lispsyntax_clisp")
476  " CLISP FFI:
477  syn keyword lispKey	:arguments  :return-type :library     :full     :malloc-free
478  syn keyword lispKey	:none       :alloca      :in          :out      :in-out      :stdc-stdcall :stdc     :c
479  syn keyword lispKey	:language   :built-in    :typedef     :external
480  syn keyword lispKey	:fini       :init-once   :init-always
481endif
482
483" ---------------------------------------------------------------------
484" Standard Lisp Variables: {{{1
485syn keyword lispVar		*applyhook*			*load-pathname*			*print-pprint-dispatch*
486syn keyword lispVar		*break-on-signals*		*load-print*			*print-pprint-dispatch*
487syn keyword lispVar		*break-on-signals*		*load-truename*			*print-pretty*
488syn keyword lispVar		*break-on-warnings*		*load-verbose*			*print-radix*
489syn keyword lispVar		*compile-file-pathname*		*macroexpand-hook*		*print-readably*
490syn keyword lispVar		*compile-file-pathname*		*modules*			*print-right-margin*
491syn keyword lispVar		*compile-file-truename*		*package*			*print-right-margin*
492syn keyword lispVar		*compile-file-truename*		*print-array*			*query-io*
493syn keyword lispVar		*compile-print*			*print-base*			*random-state*
494syn keyword lispVar		*compile-verbose*		*print-case*			*read-base*
495syn keyword lispVar		*compile-verbose*		*print-circle*			*read-default-float-format*
496syn keyword lispVar		*debug-io*			*print-escape*			*read-eval*
497syn keyword lispVar		*debugger-hook*			*print-gensym*			*read-suppress*
498syn keyword lispVar		*default-pathname-defaults*	*print-length*			*readtable*
499syn keyword lispVar		*error-output*			*print-level*			*standard-input*
500syn keyword lispVar		*evalhook*			*print-lines*			*standard-output*
501syn keyword lispVar		*features*			*print-miser-width*		*terminal-io*
502syn keyword lispVar		*gensym-counter*		*print-miser-width*		*trace-output*
503
504" ---------------------------------------------------------------------
505" Strings: {{{1
506syn region			lispString			start=+"+ skip=+\\\\\|\\"+ end=+"+	contains=@Spell
507if exists("g:lisp_instring")
508 syn region			lispInString			keepend matchgroup=Delimiter start=+"(+rs=s+1 skip=+|.\{-}|+ matchgroup=Delimiter end=+)"+ contains=@lispBaseListCluster,lispInStringString
509 syn region			lispInStringString		start=+\\"+ skip=+\\\\+ end=+\\"+ contained
510endif
511
512" ---------------------------------------------------------------------
513" Shared with Xlisp, Declarations, Macros, Functions: {{{1
514syn keyword lispDecl		defmacro			do-all-symbols		labels
515syn keyword lispDecl		defsetf				do-external-symbols	let
516syn keyword lispDecl		deftype				do-symbols		locally
517syn keyword lispDecl		defun				dotimes			macrolet
518syn keyword lispDecl		do*				flet			multiple-value-bind
519if exists("g:lispsyntax_clisp")
520  " CLISP FFI:
521  syn match lispDecl	"\<\(ffi:\)\?def-c-\(var\|const\|enum\|type\|struct\)\>"
522  syn match lispDecl	"\<\(ffi:\)\?def-call-\(out\|in\)\>"
523  syn match lispDecl	"\<\(ffi:\)\?c-\(function\|struct\|pointer\|string\)\>"
524  syn match lispDecl	"\<\(ffi:\)\?c-ptr\(-null\)\?\>"
525  syn match lispDecl	"\<\(ffi:\)\?c-array\(-ptr\|-max\)\?\>"
526  syn match lispDecl	"\<\(ffi:\)\?[us]\?\(char\|short\|int\|long\)\>"
527  syn match lispDecl	"\<\(win32:\|w32\)\?d\?word\>"
528  syn match lispDecl	"\<\([us]_\?\)\?int\(8\|16\|32\|64\)\(_t\)\?\>"
529  syn keyword lispDecl	size_t off_t time_t handle
530endif
531
532" ---------------------------------------------------------------------
533" Numbers: supporting integers and floating point numbers {{{1
534syn match lispNumber		"-\=\(\.\d\+\|\d\+\(\.\d*\)\=\)\([dDeEfFlL][-+]\=\d\+\)\="
535syn match lispNumber		"-\=\(\d\+/\d\+\)"
536
537syn match lispEscapeSpecial		"\*\w[a-z_0-9-]*\*"
538syn match lispEscapeSpecial		!#|[^()'`,"; \t]\+|#!
539syn match lispEscapeSpecial		!#x\x\+!
540syn match lispEscapeSpecial		!#o\o\+!
541syn match lispEscapeSpecial		!#b[01]\+!
542syn match lispEscapeSpecial		!#\\[ -}\~]!
543syn match lispEscapeSpecial		!#[':][^()'`,"; \t]\+!
544syn match lispEscapeSpecial		!#([^()'`,"; \t]\+)!
545syn match lispEscapeSpecial		!#\\\%(Space\|Newline\|Tab\|Page\|Rubout\|Linefeed\|Return\|Backspace\)!
546syn match lispEscapeSpecial		"\<+[a-zA-Z_][a-zA-Z_0-9-]*+\>"
547
548syn match lispConcat		"\s\.\s"
549syn match lispParenError	")"
550
551" ---------------------------------------------------------------------
552" Comments: {{{1
553syn cluster lispCommentGroup	contains=lispTodo,@Spell
554syn match   lispComment		";.*$"				contains=@lispCommentGroup
555syn region  lispCommentRegion	start="#|" end="|#"		contains=lispCommentRegion,@lispCommentGroup
556syn keyword lispTodo		contained			combak			combak:			todo			todo:
557
558" ---------------------------------------------------------------------
559" Synchronization: {{{1
560syn sync lines=100
561
562" ---------------------------------------------------------------------
563" Define Highlighting: {{{1
564" For version 5.7 and earlier: only when not done already
565" For version 5.8 and later: only when an item doesn't have highlighting yet
566if version >= 508
567  command -nargs=+ HiLink hi def link <args>
568
569  HiLink lispCommentRegion	lispComment
570  HiLink lispAtomNmbr		lispNumber
571  HiLink lispAtomMark		lispMark
572  HiLink lispInStringString	lispString
573
574  HiLink lispAtom		Identifier
575  HiLink lispAtomBarSymbol	Special
576  HiLink lispBarSymbol		Special
577  HiLink lispComment		Comment
578  HiLink lispConcat		Statement
579  HiLink lispDecl		Statement
580  HiLink lispFunc		Statement
581  HiLink lispKey		Type
582  HiLink lispMark		Delimiter
583  HiLink lispNumber		Number
584  HiLink lispParenError		Error
585  HiLink lispEscapeSpecial	Type
586  HiLink lispString		String
587  HiLink lispTodo		Todo
588  HiLink lispVar		Statement
589
590  if exists("g:lisp_rainbow") && g:lisp_rainbow != 0
591   if &bg == "dark"
592    hi def hlLevel0 ctermfg=red         guifg=red1
593    hi def hlLevel1 ctermfg=yellow      guifg=orange1
594    hi def hlLevel2 ctermfg=green       guifg=yellow1
595    hi def hlLevel3 ctermfg=cyan        guifg=greenyellow
596    hi def hlLevel4 ctermfg=magenta     guifg=green1
597    hi def hlLevel5 ctermfg=red         guifg=springgreen1
598    hi def hlLevel6 ctermfg=yellow      guifg=cyan1
599    hi def hlLevel7 ctermfg=green       guifg=slateblue1
600    hi def hlLevel8 ctermfg=cyan        guifg=magenta1
601    hi def hlLevel9 ctermfg=magenta     guifg=purple1
602   else
603    hi def hlLevel0 ctermfg=red         guifg=red3
604    hi def hlLevel1 ctermfg=darkyellow  guifg=orangered3
605    hi def hlLevel2 ctermfg=darkgreen   guifg=orange2
606    hi def hlLevel3 ctermfg=blue        guifg=yellow3
607    hi def hlLevel4 ctermfg=darkmagenta guifg=olivedrab4
608    hi def hlLevel5 ctermfg=red         guifg=green4
609    hi def hlLevel6 ctermfg=darkyellow  guifg=paleturquoise3
610    hi def hlLevel7 ctermfg=darkgreen   guifg=deepskyblue4
611    hi def hlLevel8 ctermfg=blue        guifg=darkslateblue
612    hi def hlLevel9 ctermfg=darkmagenta guifg=darkviolet
613   endif
614  endif
615
616  delcommand HiLink
617endif
618
619let b:current_syntax = "lisp"
620
621" ---------------------------------------------------------------------
622" vim: ts=8 nowrap fdm=marker
623