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