{-# LANGUAGE OverloadedStrings #-} module Skylighting.Syntax.Octave (syntax) where import Skylighting.Types syntax :: Syntax syntax = read $! "Syntax {sName = \"Octave\", sFilename = \"octave.xml\", sShortname = \"Octave\", sContexts = fromList [(\"_adjoint\",Context {cName = \"_adjoint\", cSyntax = \"Octave\", cRules = [Rule {rMatcher = RegExpr (RE {reString = \"'+\", reCaseSensitive = True}), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]}], cAttribute = NormalTok, cLineEmptyContext = [], cLineEndContext = [Pop], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"_normal\",Context {cName = \"_normal\", cSyntax = \"Octave\", cRules = [Rule {rMatcher = RegExpr (RE {reString = \"\\\\b(for)\\\\b\", reCaseSensitive = True}), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\\b(endfor)\\\\b\", reCaseSensitive = True}), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\\b(if)\\\\b\", reCaseSensitive = True}), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\\b(endif)\\\\b\", reCaseSensitive = True}), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\\b(do)\\\\b\", reCaseSensitive = True}), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\\b(until)\\\\b\", reCaseSensitive = True}), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\\b(while)\\\\b\", reCaseSensitive = True}), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\\b(endwhile)\\\\b\", reCaseSensitive = True}), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\\b(function)\\\\b\", reCaseSensitive = True}), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\\b(endfunction)\\\\b\", reCaseSensitive = True}), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\\b(switch)\\\\b\", reCaseSensitive = True}), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\\b(endswitch)\\\\b\", reCaseSensitive = True}), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\\b(try)\\\\b\", reCaseSensitive = True}), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\\b(end_try_catch)\\\\b\", reCaseSensitive = True}), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\\b(end)\\\\b\", reCaseSensitive = True}), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"[a-zA-Z]\\\\w*(?=')\", reCaseSensitive = True}), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Octave\",\"_adjoint\")]},Rule {rMatcher = RegExpr (RE {reString = \"(\\\\d+(\\\\.\\\\d+)?|\\\\.\\\\d+)([eE][+-]?\\\\d+)?[ij]?(?=')\", reCaseSensitive = True}), rAttribute = FloatTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Octave\",\"_adjoint\")]},Rule {rMatcher = RegExpr (RE {reString = \"[\\\\)\\\\]}](?=')\", reCaseSensitive = True}), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Octave\",\"_adjoint\")]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\.'(?=')\", reCaseSensitive = True}), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Octave\",\"_adjoint\")]},Rule {rMatcher = RegExpr (RE {reString = \"'([^'\\\\\\\\]|''|\\\\\\\\'|\\\\\\\\[^'])*'(?=[^']|$)\", reCaseSensitive = True}), rAttribute = StringTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"'([^']|''|\\\\\\\\')*\", reCaseSensitive = True}), rAttribute = CharTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\"([^\\\"\\\\\\\\]|\\\"\\\"|\\\\\\\\\\\"|\\\\\\\\[^\\\"])*\\\"(?=[^\\\"]|$)\", reCaseSensitive = True}), rAttribute = StringTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\"([^\\\"]|\\\"\\\"|\\\\\\\\\\\")*\", reCaseSensitive = True}), rAttribute = CharTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = Keyword (KeywordAttr {keywordCaseSensitive = True, keywordDelims = fromList \"\\t\\n !%&()*+,-./:;<=>?[\\\\]^{|}~\"}) (CaseSensitiveWords (fromList [\"all_va_args\",\"break\",\"case\",\"continue\",\"else\",\"elseif\",\"end_unwind_protect\",\"global\",\"gplot\",\"gsplot\",\"otherwise\",\"persistent\",\"replot\",\"return\",\"static\",\"until\",\"unwind_protect\",\"unwind_protect_cleanup\",\"varargin\",\"varargout\"])), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = Keyword (KeywordAttr {keywordCaseSensitive = True, keywordDelims = fromList \"\\t\\n !%&()*+,-./:;<=>?[\\\\]^{|}~\"}) (CaseSensitiveWords (fromList [\"__end__\",\"casesen\",\"cd\",\"chdir\",\"clear\",\"dbclear\",\"dbstatus\",\"dbstop\",\"dbtype\",\"dbwhere\",\"diary\",\"echo\",\"edit_history\",\"format\",\"gset\",\"gshow\",\"help\",\"history\",\"hold\",\"iskeyword\",\"isvarname\",\"load\",\"ls\",\"mark_as_command\",\"mislocked\",\"mlock\",\"more\",\"munlock\",\"run_history\",\"save\",\"set\",\"show\",\"type\",\"unmark_command\",\"which\",\"who\",\"whos\"])), rAttribute = FunctionTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = Keyword (KeywordAttr {keywordCaseSensitive = True, keywordDelims = fromList \"\\t\\n !%&()*+,-./:;<=>?[\\\\]^{|}~\"}) (CaseSensitiveWords (fromList [\"DEMOcontrol\",\"ERRNO\",\"__abcddims__\",\"__axis_label__\",\"__bodquist__\",\"__end__\",\"__errcomm__\",\"__error_text__\",\"__errplot__\",\"__freqresp__\",\"__outlist__\",\"__plr1__\",\"__plr2__\",\"__plr__\",\"__plt1__\",\"__plt2__\",\"__plt2mm__\",\"__plt2mv__\",\"__plt2ss__\",\"__plt2vm__\",\"__plt2vv__\",\"__plt__\",\"__pltopt1__\",\"__pltopt__\",\"__print_symbol_info__\",\"__print_symtab_info__\",\"__stepimp__\",\"__syschnamesl__\",\"__sysconcat__\",\"__syscont_disc__\",\"__sysdefioname__\",\"__sysdefstname__\",\"__sysgroupn__\",\"__tf2sysl__\",\"__tfl__\",\"__token_count__\",\"__zgpbal__\",\"__zp2ssg2__\",\"abcddim\",\"abs\",\"acos\",\"acosh\",\"acot\",\"acoth\",\"acsc\",\"acsch\",\"airy\",\"all\",\"analdemo\",\"angle\",\"anova\",\"any\",\"append\",\"arch_fit\",\"arch_rnd\",\"arch_test\",\"are\",\"arg\",\"argnames\",\"arma_rnd\",\"asctime\",\"asec\",\"asech\",\"asin\",\"asinh\",\"assignin\",\"atan\",\"atan2\",\"atanh\",\"atexit\",\"autocor\",\"autocov\",\"autoreg_matrix\",\"axis\",\"axis2dlim\",\"balance\",\"bar\",\"bartlett\",\"bartlett_test\",\"base2dec\",\"bddemo\",\"beep\",\"bessel\",\"besselh\",\"besseli\",\"besselj\",\"besselk\",\"bessely\",\"beta\",\"beta_cdf\",\"beta_inv\",\"beta_pdf\",\"beta_rnd\",\"betai\",\"betainc\",\"bin2dec\",\"bincoeff\",\"binomial_cdf\",\"binomial_inv\",\"binomial_pdf\",\"binomial_rnd\",\"bitand\",\"bitcmp\",\"bitget\",\"bitmax\",\"bitor\",\"bitset\",\"bitshift\",\"bitxor\",\"blackman\",\"blanks\",\"bode\",\"bode_bounds\",\"bottom_title\",\"bug_report\",\"buildssic\",\"c2d\",\"cart2pol\",\"cart2sph\",\"casesen\",\"cat\",\"cauchy_cdf\",\"cauchy_inv\",\"cauchy_pdf\",\"cauchy_rnd\",\"cd\",\"ceil\",\"cell\",\"cell2struct\",\"cellidx\",\"cellstr\",\"center\",\"char\",\"chdir\",\"chisquare_cdf\",\"chisquare_inv\",\"chisquare_pdf\",\"chisquare_rnd\",\"chisquare_test_homogeneity\",\"chisquare_test_independence\",\"chol\",\"circshift\",\"class\",\"clc\",\"clear\",\"clearplot\",\"clg\",\"clock\",\"cloglog\",\"close\",\"closeplot\",\"colloc\",\"colormap\",\"columns\",\"com2str\",\"comma\",\"common_size\",\"commutation_matrix\",\"compan\",\"complement\",\"completion_matches\",\"computer\",\"cond\",\"conj\",\"contour\",\"controldemo\",\"conv\",\"convmtx\",\"cor\",\"cor_test\",\"corrcoef\",\"cos\",\"cosh\",\"cot\",\"coth\",\"cov\",\"cputime\",\"create_set\",\"cross\",\"csc\",\"csch\",\"ctime\",\"ctrb\",\"cumprod\",\"cumsum\",\"cut\",\"d2c\",\"damp\",\"dare\",\"daspk\",\"daspk_options\",\"dasrt\",\"dasrt_options\",\"dassl\",\"dassl_options\",\"date\",\"dbclear\",\"dbstatus\",\"dbstop\",\"dbtype\",\"dbwhere\",\"dcgain\",\"deal\",\"deblank\",\"dec2base\",\"dec2bin\",\"dec2hex\",\"deconv\",\"delete\",\"demoquat\",\"det\",\"detrend\",\"dezero\",\"dftmtx\",\"dgkfdemo\",\"dgram\",\"dhinfdemo\",\"diag\",\"diary\",\"diff\",\"diffpara\",\"dir\",\"discrete_cdf\",\"discrete_inv\",\"discrete_pdf\",\"discrete_rnd\",\"disp\",\"dkalman\",\"dlqe\",\"dlqg\",\"dlqr\",\"dlyap\",\"dmr2d\",\"dmult\",\"do_string_escapes\",\"document\",\"dot\",\"double\",\"dre\",\"dump_prefs\",\"dup2\",\"duplication_matrix\",\"durbinlevinson\",\"echo\",\"edit_history\",\"eig\",\"empirical_cdf\",\"empirical_inv\",\"empirical_pdf\",\"empirical_rnd\",\"endgrent\",\"endpwent\",\"erf\",\"erfc\",\"erfinv\",\"error\",\"error_text\",\"errorbar\",\"etime\",\"eval\",\"evalin\",\"exec\",\"exist\",\"exit\",\"exp\",\"expm\",\"exponential_cdf\",\"exponential_inv\",\"exponential_pdf\",\"exponential_rnd\",\"eye\",\"f_cdf\",\"f_inv\",\"f_pdf\",\"f_rnd\",\"f_test_regression\",\"fclose\",\"fcntl\",\"fdisp\",\"feof\",\"ferror\",\"feval\",\"fflush\",\"fft\",\"fft2\",\"fftconv\",\"fftfilt\",\"fftn\",\"fftshift\",\"fftw_wisdom\",\"fgetl\",\"fgets\",\"fieldnames\",\"figure\",\"file_in_loadpath\",\"file_in_path\",\"fileparts\",\"filter\",\"find\",\"find_first_of_in_loadpath\",\"findstr\",\"finite\",\"fir2sys\",\"fix\",\"flipdim\",\"fliplr\",\"flipud\",\"floor\",\"flops\",\"fmod\",\"fnmatch\",\"fopen\",\"fork\",\"format\",\"formula\",\"fprintf\",\"fputs\",\"fractdiff\",\"frdemo\",\"fread\",\"freport\",\"freqchkw\",\"freqz\",\"freqz_plot\",\"frewind\",\"fscanf\",\"fseek\",\"fsolve\",\"fsolve_options\",\"ftell\",\"fullfile\",\"func2str\",\"functions\",\"fv\",\"fvl\",\"fwrite\",\"gamma\",\"gamma_cdf\",\"gamma_inv\",\"gamma_pdf\",\"gamma_rnd\",\"gammai\",\"gammainc\",\"gammaln\",\"gcd\",\"geometric_cdf\",\"geometric_inv\",\"geometric_pdf\",\"geometric_rnd\",\"getegid\",\"getenv\",\"geteuid\",\"getgid\",\"getgrent\",\"getgrgid\",\"getgrnam\",\"getpgrp\",\"getpid\",\"getppid\",\"getpwent\",\"getpwnam\",\"getpwuid\",\"getrusage\",\"getuid\",\"givens\",\"glob\",\"gls\",\"gmtime\",\"gram\",\"graw\",\"gray\",\"gray2ind\",\"grid\",\"gset\",\"gshow\",\"h2norm\",\"h2syn\",\"hamming\",\"hankel\",\"hanning\",\"help\",\"hess\",\"hex2dec\",\"hilb\",\"hinf_ctr\",\"hinfdemo\",\"hinfnorm\",\"hinfsyn\",\"hinfsyn_chk\",\"hinfsyn_ric\",\"hist\",\"history\",\"hold\",\"home\",\"horzcat\",\"hotelling_test\",\"hotelling_test_2\",\"housh\",\"hsv2rgb\",\"hurst\",\"hypergeometric_cdf\",\"hypergeometric_inv\",\"hypergeometric_pdf\",\"hypergeometric_rnd\",\"ifft\",\"ifft2\",\"ifftn\",\"imag\",\"image\",\"imagesc\",\"impulse\",\"imshow\",\"ind2gray\",\"ind2rgb\",\"ind2sub\",\"index\",\"inline\",\"input\",\"input_event_hook\",\"int16\",\"int2str\",\"int32\",\"int64\",\"int8\",\"intersection\",\"intmax\",\"intmin\",\"inv\",\"inverse\",\"invhilb\",\"ipermute\",\"iqr\",\"irr\",\"is_abcd\",\"is_bool\",\"is_complex\",\"is_controllable\",\"is_detectable\",\"is_dgkf\",\"is_digital\",\"is_duplicate_entry\",\"is_global\",\"is_leap_year\",\"is_list\",\"is_matrix\",\"is_nan_or_na\",\"is_observable\",\"is_sample\",\"is_scalar\",\"is_signal_list\",\"is_siso\",\"is_square\",\"is_stabilizable\",\"is_stable\",\"is_stream\",\"is_struct\",\"is_symmetric\",\"is_vector\",\"isa\",\"isalnum\",\"isalpha\",\"isascii\",\"isbool\",\"iscell\",\"iscellstr\",\"ischar\",\"iscntrl\",\"iscomplex\",\"isdefinite\",\"isdigit\",\"isempty\",\"isfield\",\"isfinite\",\"isglobal\",\"isgraph\",\"ishold\",\"isieee\",\"isinf\",\"iskeyword\",\"isletter\",\"islist\",\"islogical\",\"islower\",\"ismatrix\",\"isna\",\"isnan\",\"isnumeric\",\"ispc\",\"isprint\",\"ispunct\",\"isreal\",\"isscalar\",\"isspace\",\"issquare\",\"isstr\",\"isstream\",\"isstreamoff\",\"isstruct\",\"issymmetric\",\"isunix\",\"isupper\",\"isvarname\",\"isvector\",\"isxdigit\",\"jet707\",\"kbhit\",\"kendall\",\"keyboard\",\"kill\",\"kolmogorov_smirnov_cdf\",\"kolmogorov_smirnov_test\",\"kolmogorov_smirnov_test_2\",\"kron\",\"kruskal_wallis_test\",\"krylov\",\"krylovb\",\"kurtosis\",\"laplace_cdf\",\"laplace_inv\",\"laplace_pdf\",\"laplace_rnd\",\"lasterr\",\"lastwarn\",\"lcm\",\"length\",\"lgamma\",\"lin2mu\",\"link\",\"linspace\",\"list\",\"list_primes\",\"listidx\",\"load\",\"loadaudio\",\"loadimage\",\"localtime\",\"log\",\"log10\",\"log2\",\"logical\",\"logistic_cdf\",\"logistic_inv\",\"logistic_pdf\",\"logistic_regression\",\"logistic_regression_derivatives\",\"logistic_regression_likelihood\",\"logistic_rnd\",\"logit\",\"loglog\",\"loglogerr\",\"logm\",\"lognormal_cdf\",\"lognormal_inv\",\"lognormal_pdf\",\"lognormal_rnd\",\"logspace\",\"lower\",\"lpsolve\",\"lpsolve_options\",\"lqe\",\"lqg\",\"lqr\",\"ls\",\"lsim\",\"lsode\",\"lsode_options\",\"lstat\",\"ltifr\",\"lu\",\"lyap\",\"mahalanobis\",\"manova\",\"mark_as_command\",\"max\",\"mcnemar_test\",\"mean\",\"meansq\",\"median\",\"menu\",\"mesh\",\"meshdom\",\"meshgrid\",\"min\",\"minfo\",\"minmax\",\"mislocked\",\"mkdir\",\"mkfifo\",\"mkstemp\",\"mktime\",\"mlock\",\"mod\",\"moddemo\",\"moment\",\"more\",\"mplot\",\"mu2lin\",\"multiplot\",\"munlock\",\"nargchk\",\"nargin\",\"nargout\",\"native_float_format\",\"ndims\",\"nextpow2\",\"nichols\",\"norm\",\"normal_cdf\",\"normal_inv\",\"normal_pdf\",\"normal_rnd\",\"not\",\"nper\",\"npv\",\"nth\",\"ntsc2rgb\",\"null\",\"num2str\",\"numel\",\"nyquist\",\"obsv\",\"ocean\",\"octave_config_info\",\"octave_tmp_file_name\",\"odessa\",\"odessa_options\",\"ols\",\"oneplot\",\"ones\",\"ord2\",\"orth\",\"pack\",\"packedform\",\"packsys\",\"parallel\",\"paren\",\"pascal_cdf\",\"pascal_inv\",\"pascal_pdf\",\"pascal_rnd\",\"path\",\"pause\",\"pclose\",\"periodogram\",\"permute\",\"perror\",\"pinv\",\"pipe\",\"place\",\"playaudio\",\"plot\",\"plot_border\",\"pmt\",\"poisson_cdf\",\"poisson_inv\",\"poisson_pdf\",\"poisson_rnd\",\"pol2cart\",\"polar\",\"poly\",\"polyder\",\"polyderiv\",\"polyfit\",\"polyinteg\",\"polyout\",\"polyreduce\",\"polyval\",\"polyvalm\",\"popen\",\"popen2\",\"postpad\",\"pow2\",\"ppplot\",\"prepad\",\"printf\",\"probit\",\"prod\",\"prompt\",\"prop_test_2\",\"purge_tmp_files\",\"putenv\",\"puts\",\"pv\",\"pvl\",\"pwd\",\"pzmap\",\"qconj\",\"qcoordinate_plot\",\"qderiv\",\"qderivmat\",\"qinv\",\"qmult\",\"qqplot\",\"qr\",\"qtrans\",\"qtransv\",\"qtransvmat\",\"quad\",\"quad_options\",\"quaternion\",\"quit\",\"qz\",\"qzhess\",\"qzval\",\"rand\",\"randn\",\"randperm\",\"range\",\"rank\",\"ranks\",\"rate\",\"read_readline_init_file\",\"readdir\",\"readlink\",\"real\",\"record\",\"rectangle_lw\",\"rectangle_sw\",\"rehash\",\"rem\",\"rename\",\"repmat\",\"reshape\",\"residue\",\"reverse\",\"rgb2hsv\",\"rgb2ind\",\"rgb2ntsc\",\"rindex\",\"rldemo\",\"rlocus\",\"rmdir\",\"rmfield\",\"roots\",\"rot90\",\"rotdim\",\"rotg\",\"round\",\"rows\",\"run_cmd\",\"run_count\",\"run_history\",\"run_test\",\"save\",\"saveaudio\",\"saveimage\",\"scanf\",\"schur\",\"sec\",\"sech\",\"semicolon\",\"semilogx\",\"semilogxerr\",\"semilogy\",\"semilogyerr\",\"series\",\"set\",\"setaudio\",\"setgrent\",\"setpwent\",\"setstr\",\"shell_cmd\",\"shg\",\"shift\",\"shiftdim\",\"show\",\"sign\",\"sign_test\",\"sin\",\"sinc\",\"sinetone\",\"sinewave\",\"sinh\",\"size\",\"sizeof\",\"skewness\",\"sleep\",\"sombrero\",\"sort\",\"sortcom\",\"source\",\"spearman\",\"spectral_adf\",\"spectral_xdf\",\"spencer\",\"sph2cart\",\"splice\",\"split\",\"sprintf\",\"sqrt\",\"sqrtm\",\"squeeze\",\"ss\",\"ss2sys\",\"ss2tf\",\"ss2zp\",\"sscanf\",\"stairs\",\"starp\",\"stat\",\"statistics\",\"std\",\"stdnormal_cdf\",\"stdnormal_inv\",\"stdnormal_pdf\",\"stdnormal_rnd\",\"step\",\"stft\",\"str2func\",\"str2mat\",\"str2num\",\"strappend\",\"strcat\",\"strcmp\",\"streamoff\",\"strerror\",\"strftime\",\"strjust\",\"strptime\",\"strrep\",\"struct\",\"struct2cell\",\"struct_contains\",\"struct_elements\",\"studentize\",\"sub2ind\",\"subplot\",\"substr\",\"subwindow\",\"sum\",\"sumsq\",\"svd\",\"swap\",\"swapcols\",\"swaprows\",\"syl\",\"sylvester_matrix\",\"symlink\",\"synthesis\",\"sys2fir\",\"sys2ss\",\"sys2tf\",\"sys2zp\",\"sysadd\",\"sysappend\",\"syschnames\",\"syschtsam\",\"sysconnect\",\"syscont\",\"sysdimensions\",\"sysdisc\",\"sysdup\",\"sysgetsignals\",\"sysgettsam\",\"sysgettype\",\"sysgroup\",\"sysidx\",\"sysmin\",\"sysmult\",\"sysout\",\"sysprune\",\"sysreorder\",\"sysrepdemo\",\"sysscale\",\"syssetsignals\",\"syssub\",\"system\",\"sysupdate\",\"t_cdf\",\"t_inv\",\"t_pdf\",\"t_rnd\",\"t_test\",\"t_test_2\",\"t_test_regression\",\"table\",\"tan\",\"tanh\",\"tempdir\",\"tempname\",\"texas_lotto\",\"tf\",\"tf2ss\",\"tf2sys\",\"tf2zp\",\"tfout\",\"tic\",\"tilde_expand\",\"time\",\"title\",\"tmpfile\",\"tmpnam\",\"toascii\",\"toc\",\"toeplitz\",\"tolower\",\"top_title\",\"toupper\",\"trace\",\"triangle_lw\",\"triangle_sw\",\"tril\",\"triu\",\"type\",\"typeinfo\",\"tzero\",\"tzero2\",\"u_test\",\"ugain\",\"uint16\",\"uint32\",\"uint64\",\"uint8\",\"umask\",\"undo_string_escapes\",\"uniform_cdf\",\"uniform_inv\",\"uniform_pdf\",\"uniform_rnd\",\"union\",\"unix\",\"unlink\",\"unmark_command\",\"unpacksys\",\"unwrap\",\"upper\",\"usage\",\"usleep\",\"va_arg\",\"va_start\",\"values\",\"vander\",\"var\",\"var_test\",\"vec\",\"vech\",\"vectorize\",\"version\",\"vertcat\",\"vol\",\"vr_val\",\"waitpid\",\"warning\",\"warranty\",\"weibull_cdf\",\"weibull_inv\",\"weibull_pdf\",\"weibull_rnd\",\"welch_test\",\"wgt1o\",\"which\",\"who\",\"whos\",\"wiener_rnd\",\"wilcoxon_test\",\"xlabel\",\"xor\",\"ylabel\",\"yulewalker\",\"z_test\",\"z_test_2\",\"zeros\",\"zgfmul\",\"zgfslv\",\"zginit\",\"zgreduce\",\"zgrownorm\",\"zgscal\",\"zgsgiv\",\"zgshsr\",\"zlabel\",\"zp\",\"zp2ss\",\"zp2sys\",\"zp2tf\",\"zpout\"])), rAttribute = FunctionTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = Keyword (KeywordAttr {keywordCaseSensitive = True, keywordDelims = fromList \"\\t\\n !%&()*+,-./:;<=>?[\\\\]^{|}~\"}) (CaseSensitiveWords (fromList [\"DEFAULT_EXEC_PATH\",\"DEFAULT_LOADPATH\",\"EDITOR\",\"EXEC_PATH\",\"FFTW_WISDOM_PROGRAM\",\"F_DUPFD\",\"F_GETFD\",\"F_GETFL\",\"F_SETFD\",\"F_SETFL\",\"I\",\"IMAGEPATH\",\"INFO_FILE\",\"INFO_PROGRAM\",\"Inf\",\"J\",\"LOADPATH\",\"MAKEINFO_PROGRAM\",\"NA\",\"NaN\",\"OCTAVE_HOME\",\"OCTAVE_VERSION\",\"O_APPEND\",\"O_ASYNC\",\"O_CREAT\",\"O_EXCL\",\"O_NONBLOCK\",\"O_RDONLY\",\"O_RDWR\",\"O_SYNC\",\"O_TRUNC\",\"O_WRONLY\",\"PAGER\",\"PS1\",\"PS2\",\"PS4\",\"P_tmpdir\",\"SEEK_CUR\",\"SEEK_END\",\"SEEK_SET\",\"SIG\",\"__kluge_procbuf_delay__\",\"ans\",\"argv\",\"automatic_replot\",\"beep_on_error\",\"completion_append_char\",\"crash_dumps_octave_core\",\"current_script_file_name\",\"debug_on_error\",\"debug_on_interrupt\",\"debug_on_warning\",\"debug_symtab_lookups\",\"default_save_format\",\"e\",\"echo_executing_commands\",\"eps\",\"false\",\"filesep\",\"fixed_point_format\",\"gnuplot_binary\",\"gnuplot_command_axes\",\"gnuplot_command_end\",\"gnuplot_command_plot\",\"gnuplot_command_replot\",\"gnuplot_command_splot\",\"gnuplot_command_title\",\"gnuplot_command_using\",\"gnuplot_command_with\",\"gnuplot_has_frames\",\"history_file\",\"history_size\",\"i\",\"ignore_function_time_stamp\",\"inf\",\"j\",\"max_recursion_depth\",\"nan\",\"octave_core_file_format\",\"octave_core_file_limit\",\"octave_core_file_name\",\"output_max_field_width\",\"output_precision\",\"page_output_immediately\",\"page_screen_output\",\"pi\",\"print_answer_id_name\",\"print_empty_dimensions\",\"print_rhs_assign_val\",\"program_invocation_name\",\"program_name\",\"realmax\",\"realmin\",\"save_header_format_string\",\"save_precision\",\"saving_history\",\"sighup_dumps_octave_core\",\"sigterm_dumps_octave_core\",\"silent_functions\",\"split_long_rows\",\"stderr\",\"stdin\",\"stdout\",\"string_fill_char\",\"struct_levels_to_print\",\"suppress_verbose_help_message\",\"true\",\"variables_can_hide_functions\",\"warn_assign_as_truth_value\",\"warn_divide_by_zero\",\"warn_empty_list_elements\",\"warn_fortran_indexing\",\"warn_function_name_clash\",\"warn_future_time_stamp\",\"warn_imag_to_real\",\"warn_matlab_incompatible\",\"warn_missing_semicolon\",\"warn_neg_dim_as_zero\",\"warn_num_to_str\",\"warn_precedence_change\",\"warn_reload_forces_clear\",\"warn_resize_on_range_error\",\"warn_separator_insert\",\"warn_single_quote_string\",\"warn_str_to_num\",\"warn_undefined_return_values\",\"warn_variable_switch_label\",\"whos_line_format\"])), rAttribute = BaseNTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = Keyword (KeywordAttr {keywordCaseSensitive = True, keywordDelims = fromList \"\\t\\n !%&()*+,-./:;<=>?[\\\\]^{|}~\"}) (CaseSensitiveWords (fromList [\"BandToFull\",\"BandToSparse\",\"Chi\",\"Ci\",\"Contents\",\"ExampleEigenValues\",\"ExampleGenEigenValues\",\"FullToBand\",\"MakeShears\",\"OCTAVE_FORGE_VERSION\",\"SBBacksub\",\"SBEig\",\"SBFactor\",\"SBProd\",\"SBSolve\",\"Shi\",\"Si\",\"SymBand\",\"__ellip_ws\",\"__ellip_ws_min\",\"__grcla__\",\"__grclf__\",\"__grcmd__\",\"__grexit__\",\"__grfigure__\",\"__grgetstat__\",\"__grhold__\",\"__grinit__\",\"__grishold__\",\"__grnewset__\",\"__grsetgraph__\",\"__nlnewmark_fcn__\",\"__plt3__\",\"__power\",\"_errcore\",\"_gfweight\",\"aar\",\"aarmam\",\"ac2poly\",\"ac2rc\",\"acorf\",\"acovf\",\"addpath\",\"ademodce\",\"adim\",\"adsmax\",\"airy_Ai\",\"airy_Ai_deriv\",\"airy_Ai_deriv_scaled\",\"airy_Ai_scaled\",\"airy_Bi\",\"airy_Bi_deriv\",\"airy_Bi_deriv_scaled\",\"airy_Bi_scaled\",\"airy_zero_Ai\",\"airy_zero_Ai_deriv\",\"airy_zero_Bi\",\"airy_zero_Bi_deriv\",\"amodce\",\"anderson_darling_cdf\",\"anderson_darling_test\",\"anovan\",\"apkconst\",\"append_save\",\"applylut\",\"ar2poly\",\"ar2rc\",\"ar_spa\",\"arburg\",\"arcext\",\"arfit2\",\"aryule\",\"assert\",\"atanint\",\"au\",\"aucapture\",\"auload\",\"auplot\",\"aurecord\",\"ausave\",\"autumn\",\"average_moments\",\"awgn\",\"azimuth\",\"base64encode\",\"battery\",\"bchdeco\",\"bchenco\",\"bchpoly\",\"bessel_In\",\"bessel_In_scaled\",\"bessel_Inu\",\"bessel_Inu_scaled\",\"bessel_Jn\",\"bessel_Jnu\",\"bessel_Kn\",\"bessel_Kn_scaled\",\"bessel_Knu\",\"bessel_Knu_scaled\",\"bessel_Yn\",\"bessel_Ynu\",\"bessel_il_scaled\",\"bessel_jl\",\"bessel_kl_scaled\",\"bessel_lnKnu\",\"bessel_yl\",\"bessel_zero_J0\",\"bessel_zero_J1\",\"best_dir\",\"best_dir_cov\",\"bestblk\",\"beta_gsl\",\"betaln\",\"bfgs\",\"bfgsmin\",\"bfgsmin_example\",\"bi2de\",\"biacovf\",\"bilinear\",\"bisdemo\",\"bisectionstep\",\"bispec\",\"biterr\",\"blkdiag\",\"blkproc\",\"bmpwrite\",\"bone\",\"bound_convex\",\"boxcar\",\"boxplot\",\"brighten\",\"bs_gradient\",\"builtin\",\"butter\",\"buttord\",\"bwborder\",\"bweuler\",\"bwfill\",\"bwlabel\",\"bwmorph\",\"bwselect\",\"calendar\",\"cceps\",\"cdiff\",\"cell2csv\",\"celleval\",\"cellstr\",\"char\",\"cheb\",\"cheb1ord\",\"cheb2ord\",\"chebwin\",\"cheby1\",\"cheby2\",\"chirp\",\"chol\",\"clausen\",\"clf\",\"clip\",\"cmpermute\",\"cmunique\",\"cohere\",\"col2im\",\"colfilt\",\"colorgradient\",\"comms\",\"compand\",\"complex\",\"concat\",\"conicalP_0\",\"conicalP_1\",\"conicalP_half\",\"conicalP_mhalf\",\"conndef\",\"content\",\"contents\",\"contourf\",\"conv2\",\"convhull\",\"convmtx\",\"cool\",\"copper\",\"cordflt2\",\"corr2\",\"cosets\",\"count\",\"coupling_3j\",\"coupling_6j\",\"coupling_9j\",\"covm\",\"cplxpair\",\"cquadnd\",\"create_lookup_table\",\"crule\",\"crule2d\",\"crule2dgen\",\"csape\",\"csapi\",\"csd\",\"csv2cell\",\"csvconcat\",\"csvexplode\",\"csvread\",\"csvwrite\",\"ctranspose\",\"cumtrapz\",\"cyclgen\",\"cyclpoly\",\"czt\",\"d2_min\",\"datenum\",\"datestr\",\"datevec\",\"dawson\",\"dct\",\"dct2\",\"dctmtx\",\"de2bi\",\"deal\",\"debye_1\",\"debye_2\",\"debye_3\",\"debye_4\",\"decimate\",\"decode\",\"deg2rad\",\"del2\",\"delaunay\",\"delaunay3\",\"delta_method\",\"demo\",\"demodmap\",\"deref\",\"deriv\",\"detrend\",\"dfdp\",\"dftmtx\",\"dhbar\",\"dilate\",\"dispatch\",\"dispatch_help\",\"display_fixed_operations\",\"distance\",\"dlmread\",\"dlmwrite\",\"dos\",\"double\",\"drawnow\",\"durlev\",\"dxfwrite\",\"edge\",\"edit\",\"ellint_Ecomp\",\"ellint_Kcomp\",\"ellip\",\"ellipdemo\",\"ellipj\",\"ellipke\",\"ellipord\",\"encode\",\"eomday\",\"erf_Q\",\"erf_Z\",\"erf_gsl\",\"erfc_gsl\",\"erode\",\"eta\",\"eta_int\",\"example\",\"exp_mult\",\"expdemo\",\"expfit\",\"expint_3\",\"expint_E1\",\"expint_E2\",\"expint_Ei\",\"expm1\",\"exprel\",\"exprel_2\",\"exprel_n\",\"eyediagram\",\"fabs\",\"factor\",\"factorial\",\"fail\",\"fangle\",\"farg\",\"fatan2\",\"fceil\",\"fcnchk\",\"fconj\",\"fcos\",\"fcosh\",\"fcumprod\",\"fcumsum\",\"fdiag\",\"feedback\",\"fem_test\",\"fermi_dirac_3half\",\"fermi_dirac_half\",\"fermi_dirac_inc_0\",\"fermi_dirac_int\",\"fermi_dirac_mhalf\",\"fexp\",\"ff2n\",\"ffloor\",\"fftconv2\",\"fieldnames\",\"fill\",\"fill3\",\"filter2\",\"filtfilt\",\"filtic\",\"fimag\",\"findsym\",\"finitedifference\",\"fir1\",\"fir2\",\"fixed\",\"fixedpoint\",\"flag\",\"flag_implicit_samplerate\",\"flattopwin\",\"flix\",\"float\",\"flog\",\"flog10\",\"fmin\",\"fminbnd\",\"fmins\",\"fminunc\",\"fnder\",\"fnplt\",\"fnval\",\"fplot\",\"fprod\",\"freal\",\"freqs\",\"freqs_plot\",\"freshape\",\"fround\",\"fsin\",\"fsinh\",\"fsort\",\"fsqrt\",\"fsum\",\"fsumsq\",\"ftan\",\"ftanh\",\"full\",\"fullfact\",\"funm\",\"fzero\",\"gamma_gsl\",\"gamma_inc\",\"gamma_inc_P\",\"gamma_inc_Q\",\"gammainv_gsl\",\"gammaln\",\"gammastar\",\"gapTest\",\"gaussian\",\"gausswin\",\"gconv\",\"gconvmtx\",\"gdeconv\",\"gdet\",\"gdftmtx\",\"gdiag\",\"gen2par\",\"geomean\",\"getfield\",\"getfields\",\"gexp\",\"gf\",\"gfft\",\"gfilter\",\"gftable\",\"gfweight\",\"gget\",\"gifft\",\"ginput\",\"ginv\",\"ginverse\",\"glog\",\"glu\",\"gmm_estimate\",\"gmm_example\",\"gmm_obj\",\"gmm_results\",\"gmm_variance\",\"gmm_variance_inefficient\",\"gpick\",\"gprod\",\"gquad\",\"gquad2d\",\"gquad2d6\",\"gquad2dgen\",\"gquad6\",\"gquadnd\",\"grab\",\"grace_octave_path\",\"gradient\",\"grank\",\"graycomatrix\",\"grayslice\",\"grep\",\"greshape\",\"grid\",\"griddata\",\"groots\",\"grpdelay\",\"grule\",\"grule2d\",\"grule2dgen\",\"gsl_sf\",\"gsqrt\",\"gsum\",\"gsumsq\",\"gtext\",\"gzoom\",\"hadamard\",\"hammgen\",\"hankel\",\"hann\",\"harmmean\",\"hazard\",\"hilbert\",\"histeq\",\"histfit\",\"histo\",\"histo2\",\"histo3\",\"histo4\",\"hot\",\"houghtf\",\"hsv\",\"hup\",\"hyperg_0F1\",\"hzeta\",\"idct\",\"idct2\",\"idplot\",\"idsim\",\"ifftshift\",\"im2bw\",\"im2col\",\"imadjust\",\"imginfo\",\"imhist\",\"imnoise\",\"impad\",\"impz\",\"imread\",\"imrotate\",\"imshear\",\"imtranslate\",\"imwrite\",\"innerfun\",\"inputname\",\"interp\",\"interp1\",\"interp2\",\"interpft\",\"intersect\",\"invest0\",\"invest1\",\"invfdemo\",\"invfreq\",\"invfreqs\",\"invfreqz\",\"inz\",\"irsa_act\",\"irsa_actcore\",\"irsa_check\",\"irsa_dft\",\"irsa_dftfp\",\"irsa_genreal\",\"irsa_idft\",\"irsa_isregular\",\"irsa_jitsp\",\"irsa_mdsp\",\"irsa_normalize\",\"irsa_plotdft\",\"irsa_resample\",\"irsa_rgenreal\",\"is_complex_sparse\",\"is_real_sparse\",\"is_sparse\",\"isa\",\"isbw\",\"isdir\",\"isequal\",\"isfield\",\"isfixed\",\"isgalois\",\"isgray\",\"isind\",\"ismember\",\"isprime\",\"isprimitive\",\"isrgb\",\"issparse\",\"isunix\",\"jet\",\"jpgread\",\"jpgwrite\",\"kaiser\",\"kaiserord\",\"lambert_W0\",\"lambert_Wm1\",\"lambertw\",\"lattice\",\"lauchli\",\"leasqr\",\"leasqrdemo\",\"legend\",\"legendre\",\"legendre_Pl\",\"legendre_Plm\",\"legendre_Ql\",\"legendre_sphPlm\",\"legendre_sphPlm_array\",\"leval\",\"levinson\",\"lin2mu\",\"line_min\",\"listen\",\"lloyds\",\"lnbeta\",\"lncosh\",\"lngamma_gsl\",\"lnpoch\",\"lnsinh\",\"log_1plusx\",\"log_1plusx_mx\",\"log_erfc\",\"lookup\",\"lookup_table\",\"lp\",\"lp_test\",\"lpc\",\"mad\",\"magic\",\"make_sparse\",\"makelut\",\"map\",\"mark_for_deletion\",\"mat2gray\",\"mat2str\",\"mdsmax\",\"mean2\",\"medfilt1\",\"medfilt2\",\"meshc\",\"minimize\",\"minpol\",\"mkpp\",\"mktheta\",\"mle_estimate\",\"mle_example\",\"mle_obj\",\"mle_results\",\"mle_variance\",\"modmap\",\"mu2lin\",\"mvaar\",\"mvar\",\"mvfilter\",\"mvfreqz\",\"myfeval\",\"nanmax\",\"nanmean\",\"nanmedian\",\"nanmin\",\"nanstd\",\"nansum\",\"ncauer\",\"nchoosek\",\"ncrule\",\"ndims\",\"nelder_mead_min\",\"newmark\",\"newtonstep\",\"nlfilter\",\"nlnewmark\",\"nmsmax\",\"nnz\",\"nonzeros\",\"normplot\",\"now\",\"nrm\",\"nthroot\",\"numgradient\",\"numhessian\",\"nze\",\"ode23\",\"ode45\",\"ode78\",\"optimset\",\"ordfilt2\",\"orient\",\"pacf\",\"padarray\",\"parameterize\",\"parcor\",\"pareto\",\"pascal\",\"patch\",\"pburg\",\"pcg\",\"pchip\",\"pchip_deriv\",\"pcolor\",\"pcr\",\"peaks\",\"penddot\",\"pendulum\",\"perms\",\"pie\",\"pink\",\"plot3\",\"pngread\",\"pngwrite\",\"poch\",\"pochrel\",\"poly2ac\",\"poly2ar\",\"poly2mask\",\"poly2rc\",\"poly2sym\",\"poly2th\",\"poly_2_ex\",\"polyarea\",\"polyconf\",\"polyder\",\"polyderiv\",\"polygcd\",\"polystab\",\"ppval\",\"prctile\",\"pretty\",\"prettyprint\",\"prettyprint_c\",\"primes\",\"primpoly\",\"princomp\",\"print\",\"prism\",\"proplan\",\"psi\",\"psi_1_int\",\"psi_1piy\",\"psi_n\",\"pulstran\",\"pwelch\",\"pyulear\",\"qaskdeco\",\"qaskenco\",\"qtdecomp\",\"qtgetblk\",\"qtsetblk\",\"quad2dc\",\"quad2dcgen\",\"quad2dg\",\"quad2dggen\",\"quadc\",\"quadg\",\"quadl\",\"quadndg\",\"quantiz\",\"quiver\",\"rad2deg\",\"rainbow\",\"rand\",\"rande\",\"randerr\",\"randint\",\"randn\",\"randp\",\"randsrc\",\"rat\",\"rats\",\"rc2ac\",\"rc2ar\",\"rc2poly\",\"rceps\",\"read_options\",\"read_pdb\",\"rectpuls\",\"regexp\",\"remez\",\"resample\",\"reset_fixed_operations\",\"rgb2gray\",\"rk2fixed\",\"rk4fixed\",\"rk8fixed\",\"rmfield\",\"rmle\",\"rmpath\",\"roicolor\",\"rosser\",\"rotate_scale\",\"rotparams\",\"rotv\",\"rref\",\"rsdec\",\"rsdecof\",\"rsenc\",\"rsencof\",\"rsgenpoly\",\"samin\",\"samin_example\",\"save_vrml\",\"sbispec\",\"scale_data\",\"scatter\",\"scatterplot\",\"select_3D_points\",\"selmo\",\"setdiff\",\"setfield\",\"setfields\",\"setxor\",\"sftrans\",\"sgolay\",\"sgolayfilt\",\"sinc_gsl\",\"sinvest1\",\"slurp_file\",\"sortrows\",\"sound\",\"soundsc\",\"sp_test\",\"spabs\",\"sparse\",\"spdiags\",\"specgram\",\"speed\",\"speye\",\"spfind\",\"spfun\",\"sphcat\",\"spimag\",\"spinv\",\"spline\",\"splot\",\"splu\",\"spones\",\"sprand\",\"sprandn\",\"spreal\",\"spring\",\"spstats\",\"spsum\",\"sptest\",\"spvcat\",\"spy\",\"std2\",\"stem\",\"str2double\",\"strcmpi\",\"stretchlim\",\"strfind\",\"strmatch\",\"strncmp\",\"strncmpi\",\"strsort\",\"strtok\",\"strtoz\",\"struct\",\"strvcat\",\"summer\",\"sumskipnan\",\"surf\",\"surfc\",\"sym2poly\",\"symerr\",\"symfsolve\",\"synchrotron_1\",\"synchrotron_2\",\"syndtable\",\"tabulate\",\"tar\",\"taylorcoeff\",\"temp_name\",\"test\",\"test_d2_min_1\",\"test_d2_min_2\",\"test_d2_min_3\",\"test_ellipj\",\"test_fminunc_1\",\"test_inline_1\",\"test_min_1\",\"test_min_2\",\"test_min_3\",\"test_min_4\",\"test_minimize_1\",\"test_nelder_mead_min_1\",\"test_nelder_mead_min_2\",\"test_sncndn\",\"test_struct\",\"test_vmesh\",\"test_vrml_faces\",\"test_wpolyfit\",\"testimio\",\"text\",\"textread\",\"tf2zp\",\"tfe\",\"thfm\",\"tics\",\"toeplitz\",\"toggle_grace_use\",\"transport_2\",\"transport_3\",\"transport_4\",\"transport_5\",\"transpose\",\"trapz\",\"triang\",\"tril\",\"trimmean\",\"tripuls\",\"trisolve\",\"triu\",\"tsademo\",\"tsearchdemo\",\"ucp\",\"uintlut\",\"unique\",\"unix\",\"unmkpp\",\"unscale_parameters\",\"vec2mat\",\"view\",\"vmesh\",\"voronoi\",\"voronoin\",\"vrml_Background\",\"vrml_PointLight\",\"vrml_arrow\",\"vrml_browse\",\"vrml_cyl\",\"vrml_demo_tutorial_1\",\"vrml_demo_tutorial_2\",\"vrml_demo_tutorial_3\",\"vrml_demo_tutorial_4\",\"vrml_ellipsoid\",\"vrml_faces\",\"vrml_flatten\",\"vrml_frame\",\"vrml_group\",\"vrml_kill\",\"vrml_lines\",\"vrml_material\",\"vrml_parallelogram\",\"vrml_points\",\"vrml_select_points\",\"vrml_surf\",\"vrml_text\",\"vrml_thick_surf\",\"vrml_transfo\",\"waitbar\",\"wavread\",\"wavwrite\",\"weekday\",\"wgn\",\"white\",\"wilkinson\",\"winter\",\"wpolyfit\",\"wpolyfitdemo\",\"write_pdb\",\"wsolve\",\"xcorr\",\"xcorr2\",\"xcov\",\"xlsread\",\"xmlread\",\"xmlwrite\",\"y2res\",\"zero_count\",\"zeta\",\"zeta_int\",\"zoom\",\"zp2tf\",\"zplane\",\"zscore\"])), rAttribute = FunctionTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"[%#].*$\", reCaseSensitive = True}), rAttribute = CommentTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"[a-zA-Z]\\\\w*\", reCaseSensitive = True}), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"(\\\\d+(\\\\.\\\\d+)?|\\\\.\\\\d+)([eE][+-]?\\\\d+)?[ij]?\", reCaseSensitive = True}), rAttribute = FloatTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = AnyChar \"()[]{}\", rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = StringDetect \"...\", rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = StringDetect \"==\", rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = StringDetect \"~=\", rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = StringDetect \"!=\", rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = StringDetect \"<=\", rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = StringDetect \">=\", rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = StringDetect \"<>\", rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = StringDetect \"&&\", rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = StringDetect \"||\", rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = StringDetect \"++\", rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = StringDetect \"--\", rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = StringDetect \"**\", rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = StringDetect \".*\", rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = StringDetect \".**\", rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = StringDetect \".^\", rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = StringDetect \"./\", rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = StringDetect \".'\", rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = AnyChar \"!\\\"%(*+,/;=>[]|~#&)-:<>\\\\^\", rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []}], cAttribute = NormalTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False})], sAuthor = \"Luis Silvestre and Federico Zenith\", sVersion = \"2\", sLicense = \"GPL\", sExtensions = [\"*.octave\",\"*.m\",\"*.M\"], sStartingContext = \"_normal\"}"