Install vim73
[git/jnareb-git.git] / share / vim / vim73 / syntax / maple.vim
blobb6e4ae92431832078b0d2d3c50691e7b9bb7052b
1 " Vim syntax file
2 " Language:     Maple V (based on release 4)
3 " Maintainer:   Dr. Charles E. Campbell, Jr. <NdrOchipS@PcampbellAfamily.Mbiz>
4 " Last Change:  Jan 05, 2010
5 " Version:      10
6 " URL:  http://mysite.verizon.net/astronaut/vim/index.html#vimlinks_syntax
8 " Package Function Selection: {{{1
9 " Because there are a lot of packages, and because of the potential for namespace
10 " clashes, this version of <maple.vim> needs the user to select which, if any,
11 " package functions should be highlighted.  Select your packages and put into your
12 " <.vimrc> none or more of the lines following let ...=1 lines:
14 "   if exists("mvpkg_all")
15 "    ...
16 "   endif
18 " *OR* let mvpkg_all=1
20 " This syntax file contains all the keywords and top-level packages of Maple 9.5
21 " but only the contents of packages of Maple V Release 4, and the top-level
22 " routines of Release 4.  <Jacques Carette - carette@mcmaster.ca>
24 " For version 5.x: Clear all syntax items
25 " For version 6.x: Quit when a syntax file was already loaded
26 if version < 600
27   syntax clear
28 elseif exists("b:current_syntax")
29   finish
30 endif
32 " Iskeyword Effects: {{{1
33 if version < 600
34   set iskeyword=$,48-57,_,a-z,@-Z
35 else
36   setlocal iskeyword=$,48-57,_,a-z,@-Z
37 endif
39 " Package Selection: {{{1
40 " allow user to simply select all packages for highlighting
41 if exists("mvpkg_all")
42   let mv_DEtools    = 1
43   let mv_Galois     = 1
44   let mv_GaussInt   = 1
45   let mv_LREtools   = 1
46   let mv_combinat   = 1
47   let mv_combstruct = 1
48   let mv_difforms   = 1
49   let mv_finance    = 1
50   let mv_genfunc    = 1
51   let mv_geometry   = 1
52   let mv_grobner    = 1
53   let mv_group      = 1
54   let mv_inttrans   = 1
55   let mv_liesymm    = 1
56   let mv_linalg     = 1
57   let mv_logic      = 1
58   let mv_networks   = 1
59   let mv_numapprox  = 1
60   let mv_numtheory  = 1
61   let mv_orthopoly  = 1
62   let mv_padic      = 1
63   let mv_plots      = 1
64   let mv_plottools  = 1
65   let mv_powseries  = 1
66   let mv_process    = 1
67   let mv_simplex    = 1
68   let mv_stats      = 1
69   let mv_student    = 1
70   let mv_sumtools   = 1
71   let mv_tensor     = 1
72   let mv_totorder   = 1
73 endif
75 " Parenthesis/curly/brace sanity checker: {{{1
76 syn case match
78 " parenthesis/curly/brace sanity checker
79 syn region mvZone       matchgroup=Delimiter start="(" matchgroup=Delimiter end=")" transparent contains=ALLBUT,mvError,mvBraceError,mvCurlyError
80 syn region mvZone       matchgroup=Delimiter start="{" matchgroup=Delimiter end="}" transparent contains=ALLBUT,mvError,mvBraceError,mvParenError
81 syn region mvZone       matchgroup=Delimiter start="\[" matchgroup=Delimiter end="]" transparent contains=ALLBUT,mvError,mvCurlyError,mvParenError
82 syn match  mvError              "[)\]}]"
83 syn match  mvBraceError "[)}]"  contained
84 syn match  mvCurlyError "[)\]]" contained
85 syn match  mvParenError "[\]}]" contained
86 syn match  mvComma              "[,;:]"
87 syn match  mvSemiError  "[;:]"  contained
88 syn match  mvDcolon             "::"
90 " Maple Packages, updated for Maple 9.5
91 syn keyword mvPackage   algcurves       ArrayTools      Cache   codegen
92 syn keyword mvPackage   CodeGeneration  CodeTools       combinat        combstruct
93 syn keyword mvPackage   ContextMenu     CurveFitting    DEtools diffalg
94 syn keyword mvPackage   difforms        DiscreteTransforms      Domains ExternalCalling
95 syn keyword mvPackage   FileTools       finance GaussInt        genfunc
96 syn keyword mvPackage   geom3d  geometry        gfun    Groebner
97 syn keyword mvPackage   group   hashmset        IntegerRelations        inttrans
98 syn keyword mvPackage   LargeExpressions        LibraryTools    liesymm linalg
99 syn keyword mvPackage   LinearAlgebra   LinearFunctionalSystems LinearOperators
100 syn keyword mvPackage   ListTools       Logic   LREtools        Maplets
101 syn keyword mvPackage   MathematicalFunctions   MathML  Matlab
102 syn keyword mvPackage   MatrixPolynomialAlgebra MmaTranslator   networks
103 syn keyword mvPackage   numapprox       numtheory       Optimization    OreTools
104 syn keyword mvPackage   Ore_algebra     OrthogonalSeries        orthopoly       padic
105 syn keyword mvPackage   PDEtools        plots   plottools       PolynomialIdeals
106 syn keyword mvPackage   PolynomialTools powseries       process QDifferenceEquations
107 syn keyword mvPackage   RandomTools     RationalNormalForms     RealDomain      RootFinding
108 syn keyword mvPackage   ScientificConstants     ScientificErrorAnalysis simplex
109 syn keyword mvPackage   Slode   SNAP    Sockets SoftwareMetrics
110 syn keyword mvPackage   SolveTools      Spread  stats   StringTools
111 syn keyword mvPackage   Student student sumtools        SumTools
112 syn keyword mvPackage   tensor  TypeTools       Units   VariationalCalculus
113 syn keyword mvPackage   VectorCalculus  Worksheet       XMLTools
115 " Language Support: {{{1
116 syn keyword mvTodo      contained       COMBAK  FIXME   TODO    XXX
117 if exists("g:mapleversion") && g:mapleversion < 9
118  syn region  mvString   start=+`+ skip=+``+ end=+`+     keepend contains=mvTodo,@Spell
119  syn region  mvString   start=+"+ skip=+""+ end=+"+     keepend contains=@Spell
120  syn region  mvDelayEval        start=+'+ end=+'+       keepend contains=ALLBUT,mvError,mvBraceError,mvCurlyError,mvParenError,mvSemiError
121  syn match   mvVarAssign        "[a-zA-Z_][a-zA-Z_0-9]*[ \t]*:=" contains=mvAssign
122  syn match   mvAssign   ":="    contained
123 else
124  syn region  mvName             start=+`+ skip=+``+ end=+`+     keepend contains=mvTodo
125  syn region  mvString   start=+"+ skip=+""+ end=+"+     keepend contains=@Spell
126  syn region  mvDelayEval        start=+'+ end=+'+       keepend contains=ALLBUT,mvError,mvBraceError,mvCurlyError,mvParenError
127  syn match   mvDelim            "[;:]"  display
128  syn match   mvAssign   ":="
129 endif
131 " Lower-Priority Operators: {{{1
132 syn match mvOper        "\."
134 " Number handling: {{{1
135 syn match mvNumber      "\<\d\+"                " integer
136  syn match mvNumber     "[-+]\=\.\d\+"          " . integer
137 syn match mvNumber      "\<\d\+\.\d\+"          " integer . integer
138 syn match mvNumber      "\<\d\+\."              " integer .
139 syn match mvNumber      "\<\d\+\.\."    contains=mvRange        " integer ..
141 syn match mvNumber      "\<\d\+e[-+]\=\d\+"             " integer e [-+] integer
142 syn match mvNumber      "[-+]\=\.\d\+e[-+]\=\d\+"       " . integer e [-+] integer
143 syn match mvNumber      "\<\d\+\.\d*e[-+]\=\d\+"        " integer . [integer] e [-+] integer
145 syn match mvNumber      "[-+]\d\+"              " integer
146 syn match mvNumber      "[-+]\d\+\.\d\+"                " integer . integer
147 syn match mvNumber      "[-+]\d\+\."            " integer .
148 syn match mvNumber      "[-+]\d\+\.\."  contains=mvRange        " integer ..
150 syn match mvNumber      "[-+]\d\+e[-+]\=\d\+"   " integer e [-+] integer
151 syn match mvNumber      "[-+]\d\+\.\d*e[-+]\=\d\+"      " integer . [integer] e [-+] integer
153 syn match mvRange       "\.\."
155 " Operators: {{{1
156 syn keyword mvOper      and not or xor implies union intersect subset minus mod
157 syn match   mvOper      "<>\|[<>]=\|[<>]\|="
158 syn match   mvOper      "&+\|&-\|&\*\|&\/\|&"
159 syn match   mvError     "\.\.\."
161 " MapleV Statements: ? statement {{{1
163 " MapleV Statements: ? statement
164 " Split into booleans, conditionals, operators, repeat-logic, etc
165 syn keyword mvBool      true    false   FAIL
166 syn keyword mvCond      elif    else    fi      if      then
167 syn match   mvCond      "end\s\+if"
169 syn keyword mvRepeat    by      for     in      to
170 syn keyword mvRepeat    do      from    od      while
171 syn match   mvRepeat    "end\s\+do"
173 syn keyword mvSpecial   NULL
174 syn match   mvSpecial   "\[\]\|{}"
176 if exists("g:mapleversion") && g:mapleversion < 9
177  syn keyword mvStatement        Order   fail    options read    save
178  syn keyword mvStatement        break   local   point   remember        stop
179  syn keyword mvStatement        done    mod     proc    restart with
180  syn keyword mvStatement        end     mods    quit    return
181  syn keyword mvStatement        error   next
182 else
183  syn keyword mvStatement        option  options read    save
184  syn keyword mvStatement        break   local   remember        stop
185  syn keyword mvStatement        done    mod     proc    restart
186  syn keyword mvStatement        end     mods    quit    return
187  syn keyword mvStatement        error   next    try     catch
188  syn keyword mvStatement        finally assuming        global  export
189  syn keyword mvStatement        module  description     use
190 endif
192 " Builtin Constants: ? constants {{{1
193 syn keyword mvConstant  Catalan I       gamma   infinity
194 syn keyword mvConstant  Pi
196 " Comments:  DEBUG, if in a comment, is specially highlighted. {{{1
197 syn keyword mvDebug     contained       DEBUG
198 syn cluster mvCommentGroup      contains=mvTodo,mvDebug,@Spell
199 syn match mvComment "#.*$"      contains=@mvCommentGroup
201 " Basic Library Functions: ? index[function]
202 syn keyword mvLibrary $ @       @@      ERROR
203 syn keyword mvLibrary AFactor   KelvinHer       arctan  factor  log     rhs
204 syn keyword mvLibrary AFactors  KelvinKei       arctanh factors log10   root
205 syn keyword mvLibrary AiryAi    KelvinKer       argument        fclose  lprint  roots
206 syn keyword mvLibrary AiryBi    LambertW        array   feof    map     round
207 syn keyword mvLibrary AngerJ    Lcm     assign  fflush  map2    rsolve
208 syn keyword mvLibrary Berlekamp LegendreE       assigned        filepos match   savelib
209 syn keyword mvLibrary BesselI   LegendreEc      asspar  fixdiv  matrix  scanf
210 syn keyword mvLibrary BesselJ   LegendreEc1     assume  float   max     searchtext
211 syn keyword mvLibrary BesselK   LegendreF       asubs   floor   maximize        sec
212 syn keyword mvLibrary BesselY   LegendreKc      asympt  fnormal maxnorm sech
213 syn keyword mvLibrary Beta      LegendreKc1     attribute       fopen   maxorder        select
214 syn keyword mvLibrary C LegendrePi      bernstein       forget  member  seq
215 syn keyword mvLibrary Chi       LegendrePic     branches        fortran min     series
216 syn keyword mvLibrary Ci        LegendrePic1    bspline fprintf minimize        setattribute
217 syn keyword mvLibrary CompSeq   Li      cat     frac    minpoly shake
218 syn keyword mvLibrary Content   Linsolve        ceil    freeze  modp    showprofile
219 syn keyword mvLibrary D MOLS    chrem   fremove modp1   showtime
220 syn keyword mvLibrary DESol     Maple_floats    close   frontend        modp2   sign
221 syn keyword mvLibrary Det       MeijerG close   fscanf  modpol  signum
222 syn keyword mvLibrary Diff      Norm    coeff   fsolve  mods    simplify
223 syn keyword mvLibrary Dirac     Normal  coeffs  galois  msolve  sin
224 syn keyword mvLibrary DistDeg   Nullspace       coeftayl        gc      mtaylor singular
225 syn keyword mvLibrary Divide    Power   collect gcd     mul     sinh
226 syn keyword mvLibrary Ei        Powmod  combine gcdex   nextprime       sinterp
227 syn keyword mvLibrary Eigenvals Prem    commutat        genpoly nops    solve
228 syn keyword mvLibrary EllipticCE        Primfield       comparray       harmonic        norm    sort
229 syn keyword mvLibrary EllipticCK        Primitive       compoly has     normal  sparse
230 syn keyword mvLibrary EllipticCPi       Primpart        conjugate       hasfun  numboccur       spline
231 syn keyword mvLibrary EllipticE ProbSplit       content hasoption       numer   split
232 syn keyword mvLibrary EllipticF Product convergs        hastype op      splits
233 syn keyword mvLibrary EllipticK Psi     convert heap    open    sprem
234 syn keyword mvLibrary EllipticModulus   Quo     coords  history optimize        sprintf
235 syn keyword mvLibrary EllipticNome      RESol   copy    hypergeom       order   sqrfree
236 syn keyword mvLibrary EllipticPi        Randpoly        cos     iFFT    parse   sqrt
237 syn keyword mvLibrary Eval      Randprime       cosh    icontent        pclose  sscanf
238 syn keyword mvLibrary Expand    Ratrecon        cost    identity        pclose  ssystem
239 syn keyword mvLibrary FFT       Re      cot     igcd    pdesolve        stack
240 syn keyword mvLibrary Factor    Rem     coth    igcdex  piecewise       sturm
241 syn keyword mvLibrary Factors   Resultant       csc     ilcm    plot    sturmseq
242 syn keyword mvLibrary FresnelC  RootOf  csch    ilog    plot3d  subs
243 syn keyword mvLibrary FresnelS  Roots   csgn    ilog10  plotsetup       subsop
244 syn keyword mvLibrary Fresnelf  SPrem   dawson  implicitdiff    pochhammer      substring
245 syn keyword mvLibrary Fresnelg  Searchtext      define  indets  pointto sum
246 syn keyword mvLibrary Frobenius Shi     degree  index   poisson surd
247 syn keyword mvLibrary GAMMA     Si      denom   indexed polar   symmdiff
248 syn keyword mvLibrary GaussAGM  Smith   depends indices polylog symmetric
249 syn keyword mvLibrary Gaussejord        Sqrfree diagonal        inifcn  polynom system
250 syn keyword mvLibrary Gausselim Ssi     diff    ininame powmod  table
251 syn keyword mvLibrary Gcd       StruveH dilog   initialize      prem    tan
252 syn keyword mvLibrary Gcdex     StruveL dinterp insert  prevprime       tanh
253 syn keyword mvLibrary HankelH1  Sum     disassemble     int     primpart        testeq
254 syn keyword mvLibrary HankelH2  Svd     discont interface       print   testfloat
255 syn keyword mvLibrary Heaviside TEXT    discrim interp  printf  thaw
256 syn keyword mvLibrary Hermite   Trace   dismantle       invfunc procbody        thiele
257 syn keyword mvLibrary Im        WeberE  divide  invztrans       procmake        time
258 syn keyword mvLibrary Indep     WeierstrassP    dsolve  iostatus        product translate
259 syn keyword mvLibrary Interp    WeierstrassPPrime       eliminate       iperfpow        proot   traperror
260 syn keyword mvLibrary Inverse   WeierstrassSigma        ellipsoid       iquo    property        trigsubs
261 syn keyword mvLibrary Irreduc   WeierstrassZeta entries iratrecon       protect trunc
262 syn keyword mvLibrary Issimilar Zeta    eqn     irem    psqrt   type
263 syn keyword mvLibrary JacobiAM  abs     erf     iroot   quo     typematch
264 syn keyword mvLibrary JacobiCD  add     erfc    irreduc radnormal       unames
265 syn keyword mvLibrary JacobiCN  addcoords       eulermac        iscont  radsimp unapply
266 syn keyword mvLibrary JacobiCS  addressof       eval    isdifferentiable        rand    unassign
267 syn keyword mvLibrary JacobiDC  algebraic       evala   isolate randomize       unload
268 syn keyword mvLibrary JacobiDN  algsubs evalapply       ispoly  randpoly        unprotect
269 syn keyword mvLibrary JacobiDS  alias   evalb   isqrfree        range   updatesR4
270 syn keyword mvLibrary JacobiNC  allvalues       evalc   isqrt   rationalize     userinfo
271 syn keyword mvLibrary JacobiND  anames  evalf   issqr   ratrecon        value
272 syn keyword mvLibrary JacobiNS  antisymm        evalfint        latex   readbytes       vector
273 syn keyword mvLibrary JacobiSC  applyop evalgf  lattice readdata        verify
274 syn keyword mvLibrary JacobiSD  arccos  evalhf  lcm     readlib whattype
275 syn keyword mvLibrary JacobiSN  arccosh evalm   lcoeff  readline        with
276 syn keyword mvLibrary JacobiTheta1      arccot  evaln   leadterm        readstat        writebytes
277 syn keyword mvLibrary JacobiTheta2      arccoth evalr   length  realroot        writedata
278 syn keyword mvLibrary JacobiTheta3      arccsc  exp     lexorder        recipoly        writeline
279 syn keyword mvLibrary JacobiTheta4      arccsch expand  lhs     rem     writestat
280 syn keyword mvLibrary JacobiZeta        arcsec  expandoff       limit   remove  writeto
281 syn keyword mvLibrary KelvinBei arcsech expandon        ln      residue zip
282 syn keyword mvLibrary KelvinBer arcsin  extract lnGAMMA resultant       ztrans
283 syn keyword mvLibrary KelvinHei arcsinh
286 " ==  PACKAGES  ======================================================= {{{1
287 " Note: highlighting of package functions is now user-selectable by package.
289 " Package: DEtools     differential equations tools {{{2
290 if exists("mv_DEtools")
291   syn keyword mvPkg_DEtools     DEnormal        Dchangevar      autonomous      dfieldplot      reduceOrder     untranslate
292   syn keyword mvPkg_DEtools     DEplot  PDEchangecoords convertAlg      indicialeq      regularsp       varparam
293   syn keyword mvPkg_DEtools     DEplot3d        PDEplot convertsys      phaseportrait   translate
294 endif
296 " Package: Domains: create domains of computation {{{2
297 if exists("mv_Domains")
298 endif
300 " Package: GF: Galois Fields {{{2
301 if exists("mv_GF")
302   syn keyword mvPkg_Galois      galois
303 endif
305 " Package: GaussInt: Gaussian Integers {{{2
306 if exists("mv_GaussInt")
307   syn keyword mvPkg_GaussInt    GIbasis GIfactor        GIissqr GInorm  GIquadres       GIsmith
308   syn keyword mvPkg_GaussInt    GIchrem GIfactors       GIlcm   GInormal        GIquo   GIsqrfree
309   syn keyword mvPkg_GaussInt    GIdivisor       GIgcd   GImcmbine       GIorder GIrem   GIsqrt
310   syn keyword mvPkg_GaussInt    GIfacpoly       GIgcdex GInearest       GIphi   GIroots GIunitnormal
311   syn keyword mvPkg_GaussInt    GIfacset        GIhermite       GInodiv GIprime GIsieve
312 endif
314 " Package: LREtools: manipulate linear recurrence relations {{{2
315 if exists("mv_LREtools")
316   syn keyword mvPkg_LREtools    REcontent       REprimpart      REtodelta       delta   hypergeomsols   ratpolysols
317   syn keyword mvPkg_LREtools    REcreate        REreduceorder   REtoproc        dispersion      polysols        shift
318   syn keyword mvPkg_LREtools    REplot  REtoDE  constcoeffsol
319 endif
321 " Package: combinat: combinatorial functions {{{2
322 if exists("mv_combinat")
323   syn keyword mvPkg_combinat    Chi     composition     graycode        numbcomb        permute randperm
324   syn keyword mvPkg_combinat    bell    conjpart        inttovec        numbcomp        powerset        stirling1
325   syn keyword mvPkg_combinat    binomial        decodepart      lastpart        numbpart        prevpart        stirling2
326   syn keyword mvPkg_combinat    cartprod        encodepart      multinomial     numbperm        randcomb        subsets
327   syn keyword mvPkg_combinat    character       fibonacci       nextpart        partition       randpart        vectoint
328   syn keyword mvPkg_combinat    choose  firstpart
329 endif
331 " Package: combstruct: combinatorial structures {{{2
332 if exists("mv_combstruct")
333   syn keyword mvPkg_combstruct  allstructs      draw    iterstructs     options specification   structures
334   syn keyword mvPkg_combstruct  count   finished        nextstruct
335 endif
337 " Package: difforms: differential forms {{{2
338 if exists("mv_difforms")
339   syn keyword mvPkg_difforms    const   defform formpart        parity  scalarpart      wdegree
340   syn keyword mvPkg_difforms    d       form    mixpar  scalar  simpform        wedge
341 endif
343 " Package: finance: financial mathematics {{{2
344 if exists("mv_finance")
345   syn keyword mvPkg_finance     amortization    cashflows       futurevalue     growingperpetuity       mv_finance      presentvalue
346   syn keyword mvPkg_finance     annuity effectiverate   growingannuity  levelcoupon     perpetuity      yieldtomaturity
347   syn keyword mvPkg_finance     blackscholes
348 endif
350 " Package: genfunc: rational generating functions {{{2
351 if exists("mv_genfunc")
352   syn keyword mvPkg_genfunc     rgf_charseq     rgf_expand      rgf_hybrid      rgf_pfrac       rgf_sequence    rgf_term
353   syn keyword mvPkg_genfunc     rgf_encode      rgf_findrecur   rgf_norm        rgf_relate      rgf_simp        termscale
354 endif
356 " Package: geometry: Euclidean geometry {{{2
357 if exists("mv_geometry")
358   syn keyword mvPkg_geometry    circle  dsegment        hyperbola       parabola        segment triangle
359   syn keyword mvPkg_geometry    conic   ellipse line    point   square
360 endif
362 " Package: grobner: Grobner bases {{{2
363 if exists("mv_grobner")
364   syn keyword mvPkg_grobner     finduni gbasis  leadmon normalf solvable        spoly
365   syn keyword mvPkg_grobner     finite  gsolve
366 endif
368 " Package: group: permutation and finitely-presented groups {{{2
369 if exists("mv_group")
370   syn keyword mvPkg_group       DerivedS        areconjugate    cosets  grouporder      issubgroup      permrep
371   syn keyword mvPkg_group       LCS     center  cosrep  inter   mulperms        pres
372   syn keyword mvPkg_group       NormalClosure   centralizer     derived invperm normalizer      subgrel
373   syn keyword mvPkg_group       RandElement     convert grelgroup       isabelian       orbit   type
374   syn keyword mvPkg_group       Sylow   core    groupmember     isnormal        permgroup
375 endif
377 " Package: inttrans: integral transforms {{{2
378 if exists("mv_inttrans")
379   syn keyword mvPkg_inttrans    addtable        fouriercos      hankel  invfourier      invlaplace      mellin
380   syn keyword mvPkg_inttrans    fourier fouriersin      hilbert invhilbert      laplace
381 endif
383 " Package: liesymm: Lie symmetries {{{2
384 if exists("mv_liesymm")
385   syn keyword mvPkg_liesymm     &^      TD      depvars getform mixpar  vfix
386   syn keyword mvPkg_liesymm     &mod    annul   determine       hasclosure      prolong wcollect
387   syn keyword mvPkg_liesymm     Eta     autosimp        dvalue  hook    reduce  wdegree
388   syn keyword mvPkg_liesymm     Lie     close   extvars indepvars       setup   wedgeset
389   syn keyword mvPkg_liesymm     Lrank   d       getcoeff        makeforms       translate       wsubs
390 endif
392 " Package: linalg: Linear algebra {{{2
393 if exists("mv_linalg")
394   syn keyword mvPkg_linalg      GramSchmidt     coldim  equal   indexfunc       mulcol  singval
395   syn keyword mvPkg_linalg      JordanBlock     colspace        exponential     innerprod       multiply        smith
396   syn keyword mvPkg_linalg      LUdecomp        colspan extend  intbasis        norm    stack
397   syn keyword mvPkg_linalg      QRdecomp        companion       ffgausselim     inverse normalize       submatrix
398   syn keyword mvPkg_linalg      addcol  cond    fibonacci       ismith  orthog  subvector
399   syn keyword mvPkg_linalg      addrow  copyinto        forwardsub      issimilar       permanent       sumbasis
400   syn keyword mvPkg_linalg      adjoint crossprod       frobenius       iszero  pivot   swapcol
401   syn keyword mvPkg_linalg      angle   curl    gausselim       jacobian        potential       swaprow
402   syn keyword mvPkg_linalg      augment definite        gaussjord       jordan  randmatrix      sylvester
403   syn keyword mvPkg_linalg      backsub delcols geneqns kernel  randvector      toeplitz
404   syn keyword mvPkg_linalg      band    delrows genmatrix       laplacian       rank    trace
405   syn keyword mvPkg_linalg      basis   det     grad    leastsqrs       references      transpose
406   syn keyword mvPkg_linalg      bezout  diag    hadamard        linsolve        row     vandermonde
407   syn keyword mvPkg_linalg      blockmatrix     diverge hermite matadd  rowdim  vecpotent
408   syn keyword mvPkg_linalg      charmat dotprod hessian matrix  rowspace        vectdim
409   syn keyword mvPkg_linalg      charpoly        eigenval        hilbert minor   rowspan vector
410   syn keyword mvPkg_linalg      cholesky        eigenvect       htranspose      minpoly scalarmul       wronskian
411   syn keyword mvPkg_linalg      col     entermatrix     ihermite
412 endif
414 " Package: logic: Boolean logic {{{2
415 if exists("mv_logic")
416   syn keyword mvPkg_logic       MOD2    bsimp   distrib environ randbool        tautology
417   syn keyword mvPkg_logic       bequal  canon   dual    frominert       satisfy toinert
418 endif
420 " Package: networks: graph networks {{{2
421 if exists("mv_networks")
422   syn keyword mvPkg_networks    acycpoly        connect dinic   graph   mincut  show
423   syn keyword mvPkg_networks    addedge connectivity    djspantree      graphical       mindegree       shrink
424   syn keyword mvPkg_networks    addvertex       contract        dodecahedron    gsimp   neighbors       span
425   syn keyword mvPkg_networks    adjacency       countcuts       draw    gunion  new     spanpoly
426   syn keyword mvPkg_networks    allpairs        counttrees      duplicate       head    octahedron      spantree
427   syn keyword mvPkg_networks    ancestor        cube    edges   icosahedron     outdegree       tail
428   syn keyword mvPkg_networks    arrivals        cycle   ends    incidence       path    tetrahedron
429   syn keyword mvPkg_networks    bicomponents    cyclebase       eweight incident        petersen        tuttepoly
430   syn keyword mvPkg_networks    charpoly        daughter        flow    indegree        random  vdegree
431   syn keyword mvPkg_networks    chrompoly       degreeseq       flowpoly        induce  rank    vertices
432   syn keyword mvPkg_networks    complement      delete  fundcyc isplanar        rankpoly        void
433   syn keyword mvPkg_networks    complete        departures      getlabel        maxdegree       shortpathtree   vweight
434   syn keyword mvPkg_networks    components      diameter        girth
435 endif
437 " Package: numapprox: numerical approximation {{{2
438 if exists("mv_numapprox")
439   syn keyword mvPkg_numapprox   chebdeg chebsort        fnorm   laurent minimax remez
440   syn keyword mvPkg_numapprox   chebmult        chebyshev       hornerform      laurent pade    taylor
441   syn keyword mvPkg_numapprox   chebpade        confracform     infnorm minimax
442 endif
444 " Package: numtheory: number theory {{{2
445 if exists("mv_numtheory")
446   syn keyword mvPkg_numtheory   B       cyclotomic      invcfrac        mcombine        nthconver       primroot
447   syn keyword mvPkg_numtheory   F       divisors        invphi  mersenne        nthdenom        quadres
448   syn keyword mvPkg_numtheory   GIgcd   euler   isolve  minkowski       nthnumer        rootsunity
449   syn keyword mvPkg_numtheory   J       factorEQ        isprime mipolys nthpow  safeprime
450   syn keyword mvPkg_numtheory   L       factorset       issqrfree       mlog    order   sigma
451   syn keyword mvPkg_numtheory   M       fermat  ithprime        mobius  pdexpand        sq2factor
452   syn keyword mvPkg_numtheory   bernoulli       ifactor jacobi  mroot   phi     sum2sqr
453   syn keyword mvPkg_numtheory   bigomega        ifactors        kronecker       msqrt   pprimroot       tau
454   syn keyword mvPkg_numtheory   cfrac   imagunit        lambda  nearestp        prevprime       thue
455   syn keyword mvPkg_numtheory   cfracpol        index   legendre        nextprime
456 endif
458 " Package: orthopoly: orthogonal polynomials {{{2
459 if exists("mv_orthopoly")
460   syn keyword mvPkg_orthopoly   G       H       L       P       T       U
461 endif
463 " Package: padic: p-adic numbers {{{2
464 if exists("mv_padic")
465   syn keyword mvPkg_padic       evalp   function        orderp  ratvaluep       rootp   valuep
466   syn keyword mvPkg_padic       expansion       lcoeffp ordp
467 endif
469 " Package: plots: graphics package {{{2
470 if exists("mv_plots")
471   syn keyword mvPkg_plots       animate coordplot3d     gradplot3d      listplot3d      polarplot       setoptions3d
472   syn keyword mvPkg_plots       animate3d       cylinderplot    implicitplot    loglogplot      polygonplot     spacecurve
473   syn keyword mvPkg_plots       changecoords    densityplot     implicitplot3d  logplot polygonplot3d   sparsematrixplot
474   syn keyword mvPkg_plots       complexplot     display inequal matrixplot      polyhedraplot   sphereplot
475   syn keyword mvPkg_plots       complexplot3d   display3d       listcontplot    odeplot replot  surfdata
476   syn keyword mvPkg_plots       conformal       fieldplot       listcontplot3d  pareto  rootlocus       textplot
477   syn keyword mvPkg_plots       contourplot     fieldplot3d     listdensityplot pointplot       semilogplot     textplot3d
478   syn keyword mvPkg_plots       contourplot3d   gradplot        listplot        pointplot3d     setoptions      tubeplot
479   syn keyword mvPkg_plots       coordplot
480 endif
482 " Package: plottools: basic graphical objects {{{2
483 if exists("mv_plottools")
484   syn keyword mvPkg_plottools   arc     curve   dodecahedron    hyperbola       pieslice        semitorus
485   syn keyword mvPkg_plottools   arrow   cutin   ellipse icosahedron     point   sphere
486   syn keyword mvPkg_plottools   circle  cutout  ellipticArc     line    polygon tetrahedron
487   syn keyword mvPkg_plottools   cone    cylinder        hemisphere      octahedron      rectangle       torus
488   syn keyword mvPkg_plottools   cuboid  disk    hexahedron
489 endif
491 " Package: powseries: formal power series {{{2
492 if exists("mv_powseries")
493   syn keyword mvPkg_powseries   compose multiply        powcreate       powlog  powsolve        reversion
494   syn keyword mvPkg_powseries   evalpow negative        powdiff powpoly powsqrt subtract
495   syn keyword mvPkg_powseries   inverse powadd  powexp  powseries       quotient        tpsform
496   syn keyword mvPkg_powseries   multconst       powcos  powint  powsin
497 endif
499 " Package: process: (Unix)-multi-processing {{{2
500 if exists("mv_process")
501   syn keyword mvPkg_process     block   fork    pclose  pipe    popen   wait
502   syn keyword mvPkg_process     exec    kill
503 endif
505 " Package: simplex: linear optimization {{{2
506 if exists("mv_simplex")
507   syn keyword mvPkg_simplex     NONNEGATIVE     cterm   dual    maximize        pivoteqn        setup
508   syn keyword mvPkg_simplex     basis   define_zero     equality        minimize        pivotvar        standardize
509   syn keyword mvPkg_simplex     convexhull      display feasible        pivot   ratio
510 endif
512 " Package: stats: statistics {{{2
513 if exists("mv_stats")
514   syn keyword mvPkg_stats       anova   describe        fit     random  statevalf       statplots
515 endif
517 " Package: student: student calculus {{{2
518 if exists("mv_student")
519   syn keyword mvPkg_student     D       Product distance        isolate middlesum       rightsum
520   syn keyword mvPkg_student     Diff    Sum     equate  leftbox midpoint        showtangent
521   syn keyword mvPkg_student     Doubleint       Tripleint       extrema leftsum minimize        simpson
522   syn keyword mvPkg_student     Int     changevar       integrand       makeproc        minimize        slope
523   syn keyword mvPkg_student     Limit   combine intercept       maximize        powsubs trapezoid
524   syn keyword mvPkg_student     Lineint completesquare  intparts        middlebox       rightbox        value
525   syn keyword mvPkg_student     Point
526 endif
528 " Package: sumtools: indefinite and definite sums {{{2
529 if exists("mv_sumtools")
530   syn keyword mvPkg_sumtools    Hypersum        extended_gosper hyperrecursion  hyperterm       sumrecursion    sumtohyper
531   syn keyword mvPkg_sumtools    Sumtohyper      gosper  hypersum        simpcomb
532 endif
534 " Package: tensor: tensor computations and General Relativity {{{2
535 if exists("mv_tensor")
536   syn keyword mvPkg_tensor      Christoffel1    Riemann connexF display_allGR   get_compts      partial_diff
537   syn keyword mvPkg_tensor      Christoffel2    RiemannF        contract        dual    get_rank        permute_indices
538   syn keyword mvPkg_tensor      Einstein        Weyl    convertNP       entermetric     invars  petrov
539   syn keyword mvPkg_tensor      Jacobian        act     cov_diff        exterior_diff   invert  prod
540   syn keyword mvPkg_tensor      Killing_eqns    antisymmetrize  create  exterior_prod   lin_com raise
541   syn keyword mvPkg_tensor      Levi_Civita     change_basis    d1metric        frame   lower   symmetrize
542   syn keyword mvPkg_tensor      Lie_diff        commutator      d2metric        geodesic_eqns   npcurve tensorsGR
543   syn keyword mvPkg_tensor      Ricci   compare directional_diff        get_char        npspin  transform
544   syn keyword mvPkg_tensor      Ricciscalar     conj    displayGR
545 endif
547 " Package: totorder: total orders on names {{{2
548 if exists("mv_totorder")
549   syn keyword mvPkg_totorder    forget  init    ordering        tassume tis
550 endif
551 " =====================================================================
553 " Highlighting: Define the default highlighting. {{{1
554 " For version 5.7 and earlier: only when not done already
555 " For version 5.8 and later: only when an item doesn't have highlighting yet
556 if version >= 508 || !exists("did_maplev_syntax_inits")
557   if version < 508
558     let did_maplev_syntax_inits = 1
559     command -nargs=+ HiLink hi link <args>
560   else
561     command -nargs=+ HiLink hi def link <args>
562   endif
564   " Maple->Maple Links {{{2
565   HiLink mvBraceError   mvError
566   HiLink mvCurlyError   mvError
567   HiLink mvDebug                mvTodo
568   HiLink mvParenError   mvError
569   HiLink mvPkg_DEtools  mvPkgFunc
570   HiLink mvPkg_Galois   mvPkgFunc
571   HiLink mvPkg_GaussInt mvPkgFunc
572   HiLink mvPkg_LREtools mvPkgFunc
573   HiLink mvPkg_combinat mvPkgFunc
574   HiLink mvPkg_combstruct       mvPkgFunc
575   HiLink mvPkg_difforms mvPkgFunc
576   HiLink mvPkg_finance  mvPkgFunc
577   HiLink mvPkg_genfunc  mvPkgFunc
578   HiLink mvPkg_geometry mvPkgFunc
579   HiLink mvPkg_grobner  mvPkgFunc
580   HiLink mvPkg_group    mvPkgFunc
581   HiLink mvPkg_inttrans mvPkgFunc
582   HiLink mvPkg_liesymm  mvPkgFunc
583   HiLink mvPkg_linalg   mvPkgFunc
584   HiLink mvPkg_logic    mvPkgFunc
585   HiLink mvPkg_networks mvPkgFunc
586   HiLink mvPkg_numapprox        mvPkgFunc
587   HiLink mvPkg_numtheory        mvPkgFunc
588   HiLink mvPkg_orthopoly        mvPkgFunc
589   HiLink mvPkg_padic    mvPkgFunc
590   HiLink mvPkg_plots    mvPkgFunc
591   HiLink mvPkg_plottools        mvPkgFunc
592   HiLink mvPkg_powseries        mvPkgFunc
593   HiLink mvPkg_process  mvPkgFunc
594   HiLink mvPkg_simplex  mvPkgFunc
595   HiLink mvPkg_stats    mvPkgFunc
596   HiLink mvPkg_student  mvPkgFunc
597   HiLink mvPkg_sumtools mvPkgFunc
598   HiLink mvPkg_tensor   mvPkgFunc
599   HiLink mvPkg_totorder mvPkgFunc
600   HiLink mvRange                mvOper
601   HiLink mvSemiError    mvError
602   HiLink mvDelim                Delimiter
604   " Maple->Standard Links {{{2
605   HiLink mvAssign               Delimiter
606   HiLink mvBool         Boolean
607   HiLink mvComma                Delimiter
608   HiLink mvComment              Comment
609   HiLink mvCond         Conditional
610   HiLink mvConstant             Number
611   HiLink mvDelayEval    Label
612   HiLink mvDcolon               Delimiter
613   HiLink mvError                Error
614   HiLink mvLibrary              Statement
615   HiLink mvNumber               Number
616   HiLink mvOper         Operator
617   HiLink mvAssign               Delimiter
618   HiLink mvPackage              Type
619   HiLink mvPkgFunc              Function
620   HiLink mvPktOption    Special
621   HiLink mvRepeat               Repeat
622   HiLink mvSpecial              Special
623   HiLink mvStatement    Statement
624   HiLink mvName         String
625   HiLink mvString               String
626   HiLink mvTodo         Todo
628   delcommand HiLink
629 endif
631 " Current Syntax: {{{1
632 let b:current_syntax = "maple"
633 " vim: ts=20 fdm=marker