Update runtime files
diff --git a/runtime/syntax/basic.vim b/runtime/syntax/basic.vim
index ad9450b..7fe411a 100644
--- a/runtime/syntax/basic.vim
+++ b/runtime/syntax/basic.vim
@@ -1,14 +1,15 @@
 " Vim syntax file
-" Language:		BASIC
+" Language:		BASIC (QuickBASIC 4.5)
 " Maintainer:		Doug Kearns <dougkearns@gmail.com>
 " Previous Maintainer:	Allan Kelly <allan@fruitloaf.co.uk>
 " Contributors:		Thilo Six
-" Last Change:		2015 Jan 10
+" Last Change:		2021 Aug 08
 
 " First version based on Micro$soft QBASIC circa 1989, as documented in
 " 'Learn BASIC Now' by Halvorson&Rygmyr. Microsoft Press 1989.
-" This syntax file not a complete implementation yet.  Send suggestions to the
-" maintainer.
+"
+" Second version attempts to match Microsoft QuickBASIC 4.5 while keeping FreeBASIC
+" (-lang qb) and QB64 (excluding extensions) in mind. -- DJK
 
 " Prelude {{{1
 if exists("b:current_syntax")
@@ -18,154 +19,357 @@
 let s:cpo_save = &cpo
 set cpo&vim
 
-" Keywords {{{1
-syn keyword basicStatement	BEEP beep Beep BLOAD bload Bload BSAVE bsave Bsave
-syn keyword basicStatement	CALL call Call ABSOLUTE absolute Absolute
-syn keyword basicStatement	CHAIN chain Chain CHDIR chdir Chdir
-syn keyword basicStatement	CIRCLE circle Circle CLEAR clear Clear
-syn keyword basicStatement	CLOSE close Close CLS cls Cls COLOR color Color
-syn keyword basicStatement	COM com Com COMMON common Common
-syn keyword basicStatement	CONST const Const DATA data Data
-syn keyword basicStatement	DECLARE declare Declare DEF def Def
-syn keyword basicStatement	DEFDBL defdbl Defdbl DEFINT defint Defint
-syn keyword basicStatement	DEFLNG deflng Deflng DEFSNG defsng Defsng
-syn keyword basicStatement	DEFSTR defstr Defstr DIM dim Dim
-syn keyword basicStatement	DO do Do LOOP loop Loop
-syn keyword basicStatement	DRAW draw Draw END end End
-syn keyword basicStatement	ENVIRON environ Environ ERASE erase Erase
-syn keyword basicStatement	ERROR error Error EXIT exit Exit
-syn keyword basicStatement	FIELD field Field FILES files Files
-syn keyword basicStatement	FOR for For NEXT next Next
-syn keyword basicStatement	FUNCTION function Function GET get Get
-syn keyword basicStatement	GOSUB gosub Gosub GOTO goto Goto
-syn keyword basicStatement	IF if If THEN then Then ELSE else Else
-syn keyword basicStatement	INPUT input Input INPUT# input# Input#
-syn keyword basicStatement	IOCTL ioctl Ioctl KEY key Key
-syn keyword basicStatement	KILL kill Kill LET let Let
-syn keyword basicStatement	LINE line Line LOCATE locate Locate
-syn keyword basicStatement	LOCK lock Lock UNLOCK unlock Unlock
-syn keyword basicStatement	LPRINT lprint Lprint USING using Using
-syn keyword basicStatement	LSET lset Lset MKDIR mkdir Mkdir
-syn keyword basicStatement	NAME name Name ON on On
-syn keyword basicStatement	ERROR error Error OPEN open Open
-syn keyword basicStatement	OPTION option Option BASE base Base
-syn keyword basicStatement	OUT out Out PAINT paint Paint
-syn keyword basicStatement	PALETTE palette Palette PCOPY pcopy Pcopy
-syn keyword basicStatement	PEN pen Pen PLAY play Play
-syn keyword basicStatement	PMAP pmap Pmap POKE poke Poke
-syn keyword basicStatement	PRESET preset Preset PRINT print Print
-syn keyword basicStatement	PRINT# print# Print# USING using Using
-syn keyword basicStatement	PSET pset Pset PUT put Put
-syn keyword basicStatement	RANDOMIZE randomize Randomize READ read Read
-syn keyword basicStatement	REDIM redim Redim RESET reset Reset
-syn keyword basicStatement	RESTORE restore Restore RESUME resume Resume
-syn keyword basicStatement	RETURN return Return RMDIR rmdir Rmdir
-syn keyword basicStatement	RSET rset Rset RUN run Run
-syn keyword basicStatement	SEEK seek Seek SELECT select Select
-syn keyword basicStatement	CASE case Case SHARED shared Shared
-syn keyword basicStatement	SHELL shell Shell SLEEP sleep Sleep
-syn keyword basicStatement	SOUND sound Sound STATIC static Static
-syn keyword basicStatement	STOP stop Stop STRIG strig Strig
-syn keyword basicStatement	SUB sub Sub SWAP swap Swap
-syn keyword basicStatement	SYSTEM system System TIMER timer Timer
-syn keyword basicStatement	TROFF troff Troff TRON tron Tron
-syn keyword basicStatement	TYPE type Type UNLOCK unlock Unlock
-syn keyword basicStatement	VIEW view View WAIT wait Wait
-syn keyword basicStatement	WHILE while While WEND wend Wend
-syn keyword basicStatement	WIDTH width Width WINDOW window Window
-syn keyword basicStatement	WRITE write Write DATE$ date$ Date$
-syn keyword basicStatement	MID$ mid$ Mid$ TIME$ time$ Time$
+syn iskeyword @,48-57,.,!,#,%,&,$
+syn case      ignore
 
-syn keyword basicFunction	ABS abs Abs ASC asc Asc
-syn keyword basicFunction	ATN atn Atn CDBL cdbl Cdbl
-syn keyword basicFunction	CINT cint Cint CLNG clng Clng
-syn keyword basicFunction	COS cos Cos CSNG csng Csng
-syn keyword basicFunction	CSRLIN csrlin Csrlin CVD cvd Cvd
-syn keyword basicFunction	CVDMBF cvdmbf Cvdmbf CVI cvi Cvi
-syn keyword basicFunction	CVL cvl Cvl CVS cvs Cvs
-syn keyword basicFunction	CVSMBF cvsmbf Cvsmbf EOF eof Eof
-syn keyword basicFunction	ERDEV erdev Erdev ERL erl Erl
-syn keyword basicFunction	ERR err Err EXP exp Exp
-syn keyword basicFunction	FILEATTR fileattr Fileattr FIX fix Fix
-syn keyword basicFunction	FRE fre Fre FREEFILE freefile Freefile
-syn keyword basicFunction	INP inp Inp INSTR instr Instr
-syn keyword basicFunction	INT int Int LBOUND lbound Lbound
-syn keyword basicFunction	LEN len Len LOC loc Loc
-syn keyword basicFunction	LOF lof Lof LOG log Log
-syn keyword basicFunction	LPOS lpos Lpos PEEK peek Peek
-syn keyword basicFunction	PEN pen Pen POINT point Point
-syn keyword basicFunction	POS pos Pos RND rnd Rnd
-syn keyword basicFunction	SADD sadd Sadd SCREEN screen Screen
-syn keyword basicFunction	SEEK seek Seek SETMEM setmem Setmem
-syn keyword basicFunction	SGN sgn Sgn SIN sin Sin
-syn keyword basicFunction	SPC spc Spc SQR sqr Sqr
-syn keyword basicFunction	STICK stick Stick STRIG strig Strig
-syn keyword basicFunction	TAB tab Tab TAN tan Tan
-syn keyword basicFunction	UBOUND ubound Ubound VAL val Val
-syn keyword basicFunction	VALPTR valptr Valptr VALSEG valseg Valseg
-syn keyword basicFunction	VARPTR varptr Varptr VARSEG varseg Varseg
-syn keyword basicFunction	CHR$ Chr$ chr$ COMMAND$ command$ Command$
-syn keyword basicFunction	DATE$ date$ Date$ ENVIRON$ environ$ Environ$
-syn keyword basicFunction	ERDEV$ erdev$ Erdev$ HEX$ hex$ Hex$
-syn keyword basicFunction	INKEY$ inkey$ Inkey$ INPUT$ input$ Input$
-syn keyword basicFunction	IOCTL$ ioctl$ Ioctl$ LCASES$ lcases$ Lcases$
-syn keyword basicFunction	LAFT$ laft$ Laft$ LTRIM$ ltrim$ Ltrim$
-syn keyword basicFunction	MID$ mid$ Mid$ MKDMBF$ mkdmbf$ Mkdmbf$
-syn keyword basicFunction	MKD$ mkd$ Mkd$ MKI$ mki$ Mki$
-syn keyword basicFunction	MKL$ mkl$ Mkl$ MKSMBF$ mksmbf$ Mksmbf$
-syn keyword basicFunction	MKS$ mks$ Mks$ OCT$ oct$ Oct$
-syn keyword basicFunction	RIGHT$ right$ Right$ RTRIM$ rtrim$ Rtrim$
-syn keyword basicFunction	SPACE$ space$ Space$ STR$ str$ Str$
-syn keyword basicFunction	STRING$ string$ String$ TIME$ time$ Time$
-syn keyword basicFunction	UCASE$ ucase$ Ucase$ VARPTR$ varptr$ Varptr$
+" Whitespace Errors {{{1
+if exists("basic_space_errors")
+  if !exists("basic_no_trail_space_error")
+    syn match basicSpaceError display excludenl "\s\+$"
+  endif
+  if !exists("basic_no_tab_space_error")
+    syn match basicSpaceError display " \+\t"me=e-1
+  endif
+endif
+
+" Comment Errors {{{1
+if !exists("basic_no_comment_errors")
+  syn match basicCommentError "\<REM\>.*"
+endif
+
+" Not Top Cluster {{{1
+syn cluster basicNotTop contains=@basicLineIdentifier,basicDataString,basicDataSeparator,basicTodo
+
+" Statements {{{1
+
+syn cluster basicStatements contains=basicStatement,basicDataStatement,basicMetaRemStatement,basicPutStatement,basicRemStatement
+
+let s:statements =<< trim EOL " {{{2
+  beep
+  bload
+  bsave
+  call
+  calls
+  case
+  chain
+  chdir
+  circle
+  clear
+  close
+  cls
+  color
+  com
+  common
+  const
+  declare
+  def
+  def\s\+seg
+  defdbl
+  defint
+  deflng
+  defsng
+  defstr
+  dim
+  do
+  draw
+  elseif
+  end
+  end\s\+\%(def\|function\|if\|select\|sub\|type\)
+  environ
+  erase
+  error
+  exit\s\+\%(def\|do\|for\|function\|sub\)
+  field
+  files
+  for
+  function
+  get
+  gosub
+  goto
+  if
+  input
+  ioctl
+  key
+  kill
+  let
+  line
+  line\s\+input
+  locate
+  lock
+  loop
+  lprint
+  lset
+  mkdir
+  name
+  next
+  on
+  on\s\+error
+  on\s\+uevent
+  open
+  open\s\+com
+  option
+  out
+  paint
+  palette
+  palette\s\+using
+  pcopy
+  pen
+  pmap
+  poke
+  preset
+  print
+  pset
+  randomize
+  read
+  redim
+  reset
+  restore
+  resume
+  return
+  rmdir
+  rset
+  run
+  select\s\+case
+  shared
+  shell
+  sleep
+  sound
+  static
+  stop
+  strig
+  sub
+  swap
+  system
+  troff
+  tron
+  type
+  uevent
+  unlock
+  using
+  view
+  view\s\+print
+  wait
+  wend
+  while
+  width
+  window
+  write
+EOL
+" }}}
+
+for s in s:statements
+  exe 'syn match basicStatement "\<' .. s .. '\>" contained'
+endfor
+
+syn match basicStatement "\<\%(then\|else\)\>" nextgroup=@basicStatements skipwhite
+
+" DATA Statement
+syn match  basicDataSeparator "," contained
+syn region basicDataStatement matchgroup=basicStatement start="\<data\>" matchgroup=basicStatementSeparator end=":\|$" contained contains=basicDataSeparator,basicDataString,basicNumber,basicFloat,basicString
+
+if !exists("basic_no_data_fold")
+  syn region basicMultilineData start="^\s*\<data\>.*\n\%(^\s*\<data\>\)\@=" end="^\s*\<data\>.*\n\%(^\s*\<data\>\)\@!" contains=basicDataStatement transparent fold keepend
+endif
+
+" PUT File I/O and Graphics statements - needs special handling for graphics
+" action verbs
+syn match  basicPutAction "\<\%(pset\|preset\|and\|or\|xor\)\>" contained
+syn region basicPutStatement matchgroup=basicStatement start="\<put\>" matchgroup=basicStatementSeparator end=":\|$" contained contains=basicKeyword,basicPutAction,basicFilenumber
+
+" Keywords {{{1
+let s:keywords =<< trim EOL " {{{2
+  absolute
+  access
+  alias
+  append
+  as
+  base
+  binary
+  byval
+  cdecl
+  com
+  def
+  do
+  for
+  function
+  gosub
+  goto
+  input
+  int86old
+  int86xold
+  interrupt
+  interruptx
+  is
+  key
+  len
+  list
+  local
+  lock
+  lprint
+  next
+  off
+  on
+  output
+  pen
+  play
+  random
+  read
+  resume
+  screen
+  seg
+  shared
+  signal
+  static
+  step
+  stop
+  strig
+  sub
+  timer
+  to
+  until
+  using
+  while
+  write
+EOL
+" }}}
+
+for k in s:keywords
+  exe 'syn match basicKeyword "\<' .. k .. '\>"'
+endfor
+
+" Functions {{{1
+syn keyword basicFunction abs asc atn cdbl chr$ cint clng command$ cos csng
+syn keyword basicFunction csrlin cvd cvdmbf cvi cvl cvs cvsmbf environ$ eof
+syn keyword basicFunction erdev erdev$ erl err exp fileattr fix fre freefile
+syn keyword basicFunction hex$ inkey$ inp input$ instr int ioctl$ left$ lbound
+syn keyword basicFunction lcase$ len loc lof log lpos ltrim$ mkd$ mkdmbf$ mki$
+syn keyword basicFunction mkl$ mks$ mksmbf$ oct$ peek pen point pos right$ rnd
+syn keyword basicFunction rtrim$ sadd setmem sgn sin space$ spc sqr stick str$
+syn keyword basicFunction strig string$ tab tan ubound ucase$ val valptr
+syn keyword basicFunction valseg varptr varptr$ varseg
+
+" Functions and statements (same name) {{{1
+syn match   basicStatement "\<\%(date\$\|mid\$\|play\|screen\|seek\|time\$\|timer\)\>" contained
+syn match   basicFunction  "\<\%(date\$\|mid\$\|play\|screen\|seek\|time\$\|timer\)\>"
+
+" Types {{{1
+syn keyword basicType integer long single double string any
+
+" Strings {{{1
+
+" Unquoted DATA strings - anything except [:,] and leading or trailing whitespace
+" Needs lower priority than numbers
+syn match basicDataString "[^[:space:],:]\+\%(\s\+[^[:space:],:]\+\)*" contained
+
+syn region basicString start=+"+ end=+"+ oneline
+
+" Booleans {{{1
+if exists("basic_booleans")
+  syn keyword basicBoolean true false
+endif
 
 " Numbers {{{1
-" Integer number, or floating point number without a dot.
-syn match  basicNumber		"\<\d\+\>"
-" Floating point number, with dot
-syn match  basicNumber		"\<\d\+\.\d*\>"
-" Floating point number, starting with a dot
-syn match  basicNumber		"\.\d\+\>"
 
-" String and Character constants {{{1
-syn match   basicSpecial	"\\\d\d\d\|\\." contained
-syn region  basicString		start=+"+  skip=+\\\\\|\\"+  end=+"+	contains=basicSpecial
+" Integers
+syn match basicNumber "-\=&o\=\o\+[%&]\=\>"
+syn match basicNumber "-\=&h\x\+[%&]\=\>"
+syn match basicNumber "-\=\<\d\+[%&]\=\>"
 
-" Line numbers {{{1
-syn region  basicLineNumber	start="^\d" end="\s"
+" Floats
+syn match basicFloat "-\=\<\d\+\.\=\d*\%(\%([ed][+-]\=\d*\)\|[!#]\)\=\>"
+syn match basicFloat      "-\=\<\.\d\+\%(\%([ed][+-]\=\d*\)\|[!#]\)\=\>"
 
-" Data-type suffixes {{{1
-syn match   basicTypeSpecifier	"[a-zA-Z0-9][$%&!#]"ms=s+1
-" Used with OPEN statement
-syn match   basicFilenumber  "#\d\+"
+" Statement anchors {{{1
+syn match basicLineStart	  "^" nextgroup=@basicStatements,@basicLineIdentifier skipwhite
+syn match basicStatementSeparator ":" nextgroup=@basicStatements		      skipwhite
 
-" Mathematical operators {{{1
-" syn match   basicMathsOperator "[<>+\*^/\\=-]"
-syn match   basicMathsOperator	 "-\|=\|[:<>+\*^/\\]\|AND\|OR"
+" Line numbers and labels {{{1
+
+" QuickBASIC limits these to 65,529 and 40 chars respectively
+syn match basicLineNumber "\d\+"		  nextgroup=@basicStatements skipwhite contained
+syn match basicLineLabel  "\a[[:alnum:]]*\ze\s*:" nextgroup=@basicStatements skipwhite contained
+
+syn cluster basicLineIdentifier contains=basicLineNumber,basicLineLabel
+
+" Line Continuation {{{1
+syn match basicLineContinuation "\s*\zs_\ze\s*$"
+
+" Type suffixes {{{1
+if exists("basic_type_suffixes")
+  syn match basicTypeSuffix "\a[[:alnum:].]*\zs[$%&!#]"
+endif
+
+" File numbers {{{1
+syn match basicFilenumber "#\d\+"
+syn match basicFilenumber "#\a[[:alnum:].]*[%&!#]\="
+
+" Operators {{{1
+if exists("basic_operators")
+  syn match basicArithmeticOperator "[-+*/\\^]"
+  syn match basicRelationalOperator "<>\|<=\|>=\|[><=]"
+endif
+syn match basicLogicalOperator	  "\<\%(not\|and\|or\|xor\|eqv\|imp\)\>"
+syn match basicArithmeticOperator "\<mod\>"
+
+" Metacommands {{{1
+" Note: No trailing word boundaries.  Text may be freely mixed however there
+" must be only leading whitespace prior to the first metacommand
+syn match basicMetacommand "$INCLUDE\s*:\s*'[^']\+'" contained containedin=@basicMetaComments
+syn match basicMetacommand "$\%(DYNAMIC\|STATIC\)"   contained containedin=@basicMetaComments
 
 " Comments {{{1
-syn keyword basicTodo		TODO FIXME XXX NOTE contained
-syn region  basicComment	start="^\s*\zsREM\>" start="\%(:\s*\)\@<=REM\>" end="$" contains=basicTodo
-syn region  basicComment	start="'"					end="$" contains=basicTodo
+syn keyword basicTodo TODO FIXME XXX NOTE contained
+
+syn region basicRemStatement matchgroup=basicStatement start="REM\>" end="$" contains=basicTodo,@Spell contained
+syn region basicComment				       start="'"     end="$" contains=basicTodo,@Spell
+
+if !exists("basic_no_comment_fold")
+  syn region basicMultilineComment start="^\s*'.*\n\%(\s*'\)\@=" end="^\s*'.*\n\%(\s*'\)\@!" contains=@basicComments transparent fold keepend
+endif
+
+" Metacommands
+syn region  basicMetaRemStatement matchgroup=basicStatement start="REM\>\s*\$\@=" end="$" contains=basicTodo contained
+syn region  basicMetaComment				    start="'\s*\$\@="	  end="$" contains=basicTodo
+
+syn cluster basicMetaComments contains=basicMetaComment,basicMetaRemStatement
+syn cluster basicComments     contains=basicComment,basicMetaComment
 
 "syn sync ccomment basicComment
 
 " Default Highlighting {{{1
-hi def link basicLabel		Label
-hi def link basicConditional	Conditional
-hi def link basicRepeat		Repeat
-hi def link basicLineNumber	Comment
-hi def link basicNumber		Number
-hi def link basicError		Error
-hi def link basicStatement	Statement
-hi def link basicString		String
-hi def link basicComment	Comment
-hi def link basicSpecial	Special
-hi def link basicTodo		Todo
-hi def link basicFunction	Identifier
-hi def link basicTypeSpecifier	Type
-hi def link basicFilenumber	basicTypeSpecifier
-"hi basicMathsOperator term=bold cterm=bold gui=bold
+hi def link basicArithmeticOperator basicOperator
+hi def link basicBoolean	    Boolean
+hi def link basicComment	    Comment
+hi def link basicCommentError	    Error
+hi def link basicDataString	    basicString
+hi def link basicFilenumber	    basicTypeSuffix " TODO: better group
+hi def link basicFloat		    Float
+hi def link basicFunction	    Identifier
+hi def link basicKeyword	    Keyword
+hi def link basicLineIdentifier	    LineNr
+hi def link basicLineContinuation   Special
+hi def link basicLineLabel	    basicLineIdentifier
+hi def link basicLineNumber	    basicLineIdentifier
+hi def link basicLogicalOperator    basicOperator
+hi def link basicMetacommand	    SpecialComment
+hi def link basicMetaComment	    Comment
+hi def link basicMetaRemStatement   Comment
+hi def link basicNumber		    Number
+hi def link basicOperator	    Operator
+hi def link basicPutAction	    Keyword
+hi def link basicRelationalOperator basicOperator
+hi def link basicRemStatement	    Comment
+hi def link basicSpaceError	    Error
+hi def link basicStatementSeparator Special
+hi def link basicStatement	    Statement
+hi def link basicString		    String
+hi def link basicTodo		    Todo
+hi def link basicType		    Type
+hi def link basicTypeSuffix	    Special
+if exists("basic_legacy_syntax_groups")
+  hi def link basicTypeSpecifier      Type
+  hi def link basicTypeSuffix	      basicTypeSpecifier
+endif
 
 " Postscript {{{1
 let b:current_syntax = "basic"