| 123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619 | // CodeMirror, copyright (c) by Marijn Haverbeke and others// Distributed under an MIT license: https://codemirror.net/LICENSE/*jshint unused:true, eqnull:true, curly:true, bitwise:true *//*jshint undef:true, latedef:true, trailing:true *//*global CodeMirror:true */// erlang mode.// tokenizer -> token types -> CodeMirror styles// tokenizer maintains a parse stack// indenter uses the parse stack// TODO indenter://   bit syntax//   old guard/bif/conversion clashes (e.g. "float/1")//   type/spec/opaque(function(mod) {  if (typeof exports == "object" && typeof module == "object") // CommonJS    mod(require("../../lib/codemirror"));  else if (typeof define == "function" && define.amd) // AMD    define(["../../lib/codemirror"], mod);  else // Plain browser env    mod(CodeMirror);})(function(CodeMirror) {"use strict";CodeMirror.defineMIME("text/x-erlang", "erlang");CodeMirror.defineMode("erlang", function(cmCfg) {  "use strict";/////////////////////////////////////////////////////////////////////////////// constants  var typeWords = [    "-type", "-spec", "-export_type", "-opaque"];  var keywordWords = [    "after","begin","catch","case","cond","end","fun","if",    "let","of","query","receive","try","when"];  var separatorRE    = /[\->,;]/;  var separatorWords = [    "->",";",","];  var operatorAtomWords = [    "and","andalso","band","bnot","bor","bsl","bsr","bxor",    "div","not","or","orelse","rem","xor"];  var operatorSymbolRE    = /[\+\-\*\/<>=\|:!]/;  var operatorSymbolWords = [    "=","+","-","*","/",">",">=","<","=<","=:=","==","=/=","/=","||","<-","!"];  var openParenRE    = /[<\(\[\{]/;  var openParenWords = [    "<<","(","[","{"];  var closeParenRE    = /[>\)\]\}]/;  var closeParenWords = [    "}","]",")",">>"];  var guardWords = [    "is_atom","is_binary","is_bitstring","is_boolean","is_float",    "is_function","is_integer","is_list","is_number","is_pid",    "is_port","is_record","is_reference","is_tuple",    "atom","binary","bitstring","boolean","function","integer","list",    "number","pid","port","record","reference","tuple"];  var bifWords = [    "abs","adler32","adler32_combine","alive","apply","atom_to_binary",    "atom_to_list","binary_to_atom","binary_to_existing_atom",    "binary_to_list","binary_to_term","bit_size","bitstring_to_list",    "byte_size","check_process_code","contact_binary","crc32",    "crc32_combine","date","decode_packet","delete_module",    "disconnect_node","element","erase","exit","float","float_to_list",    "garbage_collect","get","get_keys","group_leader","halt","hd",    "integer_to_list","internal_bif","iolist_size","iolist_to_binary",    "is_alive","is_atom","is_binary","is_bitstring","is_boolean",    "is_float","is_function","is_integer","is_list","is_number","is_pid",    "is_port","is_process_alive","is_record","is_reference","is_tuple",    "length","link","list_to_atom","list_to_binary","list_to_bitstring",    "list_to_existing_atom","list_to_float","list_to_integer",    "list_to_pid","list_to_tuple","load_module","make_ref","module_loaded",    "monitor_node","node","node_link","node_unlink","nodes","notalive",    "now","open_port","pid_to_list","port_close","port_command",    "port_connect","port_control","pre_loaded","process_flag",    "process_info","processes","purge_module","put","register",    "registered","round","self","setelement","size","spawn","spawn_link",    "spawn_monitor","spawn_opt","split_binary","statistics",    "term_to_binary","time","throw","tl","trunc","tuple_size",    "tuple_to_list","unlink","unregister","whereis"];// upper case: [A-Z] [Ø-Þ] [À-Ö]// lower case: [a-z] [ß-ö] [ø-ÿ]  var anumRE       = /[\w@Ø-ÞÀ-Öß-öø-ÿ]/;  var escapesRE    =    /[0-7]{1,3}|[bdefnrstv\\"']|\^[a-zA-Z]|x[0-9a-zA-Z]{2}|x{[0-9a-zA-Z]+}/;/////////////////////////////////////////////////////////////////////////////// tokenizer  function tokenizer(stream,state) {    // in multi-line string    if (state.in_string) {      state.in_string = (!doubleQuote(stream));      return rval(state,stream,"string");    }    // in multi-line atom    if (state.in_atom) {      state.in_atom = (!singleQuote(stream));      return rval(state,stream,"atom");    }    // whitespace    if (stream.eatSpace()) {      return rval(state,stream,"whitespace");    }    // attributes and type specs    if (!peekToken(state) &&        stream.match(/-\s*[a-zß-öø-ÿ][\wØ-ÞÀ-Öß-öø-ÿ]*/)) {      if (is_member(stream.current(),typeWords)) {        return rval(state,stream,"type");      }else{        return rval(state,stream,"attribute");      }    }    var ch = stream.next();    // comment    if (ch == '%') {      stream.skipToEnd();      return rval(state,stream,"comment");    }    // colon    if (ch == ":") {      return rval(state,stream,"colon");    }    // macro    if (ch == '?') {      stream.eatSpace();      stream.eatWhile(anumRE);      return rval(state,stream,"macro");    }    // record    if (ch == "#") {      stream.eatSpace();      stream.eatWhile(anumRE);      return rval(state,stream,"record");    }    // dollar escape    if (ch == "$") {      if (stream.next() == "\\" && !stream.match(escapesRE)) {        return rval(state,stream,"error");      }      return rval(state,stream,"number");    }    // dot    if (ch == ".") {      return rval(state,stream,"dot");    }    // quoted atom    if (ch == '\'') {      if (!(state.in_atom = (!singleQuote(stream)))) {        if (stream.match(/\s*\/\s*[0-9]/,false)) {          stream.match(/\s*\/\s*[0-9]/,true);          return rval(state,stream,"fun");      // 'f'/0 style fun        }        if (stream.match(/\s*\(/,false) || stream.match(/\s*:/,false)) {          return rval(state,stream,"function");        }      }      return rval(state,stream,"atom");    }    // string    if (ch == '"') {      state.in_string = (!doubleQuote(stream));      return rval(state,stream,"string");    }    // variable    if (/[A-Z_Ø-ÞÀ-Ö]/.test(ch)) {      stream.eatWhile(anumRE);      return rval(state,stream,"variable");    }    // atom/keyword/BIF/function    if (/[a-z_ß-öø-ÿ]/.test(ch)) {      stream.eatWhile(anumRE);      if (stream.match(/\s*\/\s*[0-9]/,false)) {        stream.match(/\s*\/\s*[0-9]/,true);        return rval(state,stream,"fun");      // f/0 style fun      }      var w = stream.current();      if (is_member(w,keywordWords)) {        return rval(state,stream,"keyword");      }else if (is_member(w,operatorAtomWords)) {        return rval(state,stream,"operator");      }else if (stream.match(/\s*\(/,false)) {        // 'put' and 'erlang:put' are bifs, 'foo:put' is not        if (is_member(w,bifWords) &&            ((peekToken(state).token != ":") ||             (peekToken(state,2).token == "erlang"))) {          return rval(state,stream,"builtin");        }else if (is_member(w,guardWords)) {          return rval(state,stream,"guard");        }else{          return rval(state,stream,"function");        }      }else if (lookahead(stream) == ":") {        if (w == "erlang") {          return rval(state,stream,"builtin");        } else {          return rval(state,stream,"function");        }      }else if (is_member(w,["true","false"])) {        return rval(state,stream,"boolean");      }else{        return rval(state,stream,"atom");      }    }    // number    var digitRE      = /[0-9]/;    var radixRE      = /[0-9a-zA-Z]/;         // 36#zZ style int    if (digitRE.test(ch)) {      stream.eatWhile(digitRE);      if (stream.eat('#')) {                // 36#aZ  style integer        if (!stream.eatWhile(radixRE)) {          stream.backUp(1);                 //"36#" - syntax error        }      } else if (stream.eat('.')) {       // float        if (!stream.eatWhile(digitRE)) {          stream.backUp(1);        // "3." - probably end of function        } else {          if (stream.eat(/[eE]/)) {        // float with exponent            if (stream.eat(/[-+]/)) {              if (!stream.eatWhile(digitRE)) {                stream.backUp(2);            // "2e-" - syntax error              }            } else {              if (!stream.eatWhile(digitRE)) {                stream.backUp(1);            // "2e" - syntax error              }            }          }        }      }      return rval(state,stream,"number");   // normal integer    }    // open parens    if (nongreedy(stream,openParenRE,openParenWords)) {      return rval(state,stream,"open_paren");    }    // close parens    if (nongreedy(stream,closeParenRE,closeParenWords)) {      return rval(state,stream,"close_paren");    }    // separators    if (greedy(stream,separatorRE,separatorWords)) {      return rval(state,stream,"separator");    }    // operators    if (greedy(stream,operatorSymbolRE,operatorSymbolWords)) {      return rval(state,stream,"operator");    }    return rval(state,stream,null);  }/////////////////////////////////////////////////////////////////////////////// utilities  function nongreedy(stream,re,words) {    if (stream.current().length == 1 && re.test(stream.current())) {      stream.backUp(1);      while (re.test(stream.peek())) {        stream.next();        if (is_member(stream.current(),words)) {          return true;        }      }      stream.backUp(stream.current().length-1);    }    return false;  }  function greedy(stream,re,words) {    if (stream.current().length == 1 && re.test(stream.current())) {      while (re.test(stream.peek())) {        stream.next();      }      while (0 < stream.current().length) {        if (is_member(stream.current(),words)) {          return true;        }else{          stream.backUp(1);        }      }      stream.next();    }    return false;  }  function doubleQuote(stream) {    return quote(stream, '"', '\\');  }  function singleQuote(stream) {    return quote(stream,'\'','\\');  }  function quote(stream,quoteChar,escapeChar) {    while (!stream.eol()) {      var ch = stream.next();      if (ch == quoteChar) {        return true;      }else if (ch == escapeChar) {        stream.next();      }    }    return false;  }  function lookahead(stream) {    var m = stream.match(/([\n\s]+|%[^\n]*\n)*(.)/,false);    return m ? m.pop() : "";  }  function is_member(element,list) {    return (-1 < list.indexOf(element));  }  function rval(state,stream,type) {    // parse stack    pushToken(state,realToken(type,stream));    // map erlang token type to CodeMirror style class    //     erlang             -> CodeMirror tag    switch (type) {      case "atom":        return "atom";      case "attribute":   return "attribute";      case "boolean":     return "atom";      case "builtin":     return "builtin";      case "close_paren": return null;      case "colon":       return null;      case "comment":     return "comment";      case "dot":         return null;      case "error":       return "error";      case "fun":         return "meta";      case "function":    return "tag";      case "guard":       return "property";      case "keyword":     return "keyword";      case "macro":       return "variable-2";      case "number":      return "number";      case "open_paren":  return null;      case "operator":    return "operator";      case "record":      return "bracket";      case "separator":   return null;      case "string":      return "string";      case "type":        return "def";      case "variable":    return "variable";      default:            return null;    }  }  function aToken(tok,col,ind,typ) {    return {token:  tok,            column: col,            indent: ind,            type:   typ};  }  function realToken(type,stream) {    return aToken(stream.current(),                 stream.column(),                 stream.indentation(),                 type);  }  function fakeToken(type) {    return aToken(type,0,0,type);  }  function peekToken(state,depth) {    var len = state.tokenStack.length;    var dep = (depth ? depth : 1);    if (len < dep) {      return false;    }else{      return state.tokenStack[len-dep];    }  }  function pushToken(state,token) {    if (!(token.type == "comment" || token.type == "whitespace")) {      state.tokenStack = maybe_drop_pre(state.tokenStack,token);      state.tokenStack = maybe_drop_post(state.tokenStack);    }  }  function maybe_drop_pre(s,token) {    var last = s.length-1;    if (0 < last && s[last].type === "record" && token.type === "dot") {      s.pop();    }else if (0 < last && s[last].type === "group") {      s.pop();      s.push(token);    }else{      s.push(token);    }    return s;  }  function maybe_drop_post(s) {    if (!s.length) return s    var last = s.length-1;    if (s[last].type === "dot") {      return [];    }    if (last > 1 && s[last].type === "fun" && s[last-1].token === "fun") {      return s.slice(0,last-1);    }    switch (s[last].token) {      case "}":    return d(s,{g:["{"]});      case "]":    return d(s,{i:["["]});      case ")":    return d(s,{i:["("]});      case ">>":   return d(s,{i:["<<"]});      case "end":  return d(s,{i:["begin","case","fun","if","receive","try"]});      case ",":    return d(s,{e:["begin","try","when","->",                                  ",","(","[","{","<<"]});      case "->":   return d(s,{r:["when"],                               m:["try","if","case","receive"]});      case ";":    return d(s,{E:["case","fun","if","receive","try","when"]});      case "catch":return d(s,{e:["try"]});      case "of":   return d(s,{e:["case"]});      case "after":return d(s,{e:["receive","try"]});      default:     return s;    }  }  function d(stack,tt) {    // stack is a stack of Token objects.    // tt is an object; {type:tokens}    // type is a char, tokens is a list of token strings.    // The function returns (possibly truncated) stack.    // It will descend the stack, looking for a Token such that Token.token    //  is a member of tokens. If it does not find that, it will normally (but    //  see "E" below) return stack. If it does find a match, it will remove    //  all the Tokens between the top and the matched Token.    // If type is "m", that is all it does.    // If type is "i", it will also remove the matched Token and the top Token.    // If type is "g", like "i", but add a fake "group" token at the top.    // If type is "r", it will remove the matched Token, but not the top Token.    // If type is "e", it will keep the matched Token but not the top Token.    // If type is "E", it behaves as for type "e", except if there is no match,    //  in which case it will return an empty stack.    for (var type in tt) {      var len = stack.length-1;      var tokens = tt[type];      for (var i = len-1; -1 < i ; i--) {        if (is_member(stack[i].token,tokens)) {          var ss = stack.slice(0,i);          switch (type) {              case "m": return ss.concat(stack[i]).concat(stack[len]);              case "r": return ss.concat(stack[len]);              case "i": return ss;              case "g": return ss.concat(fakeToken("group"));              case "E": return ss.concat(stack[i]);              case "e": return ss.concat(stack[i]);          }        }      }    }    return (type == "E" ? [] : stack);  }/////////////////////////////////////////////////////////////////////////////// indenter  function indenter(state,textAfter) {    var t;    var unit = cmCfg.indentUnit;    var wordAfter = wordafter(textAfter);    var currT = peekToken(state,1);    var prevT = peekToken(state,2);    if (state.in_string || state.in_atom) {      return CodeMirror.Pass;    }else if (!prevT) {      return 0;    }else if (currT.token == "when") {      return currT.column+unit;    }else if (wordAfter === "when" && prevT.type === "function") {      return prevT.indent+unit;    }else if (wordAfter === "(" && currT.token === "fun") {      return  currT.column+3;    }else if (wordAfter === "catch" && (t = getToken(state,["try"]))) {      return t.column;    }else if (is_member(wordAfter,["end","after","of"])) {      t = getToken(state,["begin","case","fun","if","receive","try"]);      return t ? t.column : CodeMirror.Pass;    }else if (is_member(wordAfter,closeParenWords)) {      t = getToken(state,openParenWords);      return t ? t.column : CodeMirror.Pass;    }else if (is_member(currT.token,[",","|","||"]) ||              is_member(wordAfter,[",","|","||"])) {      t = postcommaToken(state);      return t ? t.column+t.token.length : unit;    }else if (currT.token == "->") {      if (is_member(prevT.token, ["receive","case","if","try"])) {        return prevT.column+unit+unit;      }else{        return prevT.column+unit;      }    }else if (is_member(currT.token,openParenWords)) {      return currT.column+currT.token.length;    }else{      t = defaultToken(state);      return truthy(t) ? t.column+unit : 0;    }  }  function wordafter(str) {    var m = str.match(/,|[a-z]+|\}|\]|\)|>>|\|+|\(/);    return truthy(m) && (m.index === 0) ? m[0] : "";  }  function postcommaToken(state) {    var objs = state.tokenStack.slice(0,-1);    var i = getTokenIndex(objs,"type",["open_paren"]);    return truthy(objs[i]) ? objs[i] : false;  }  function defaultToken(state) {    var objs = state.tokenStack;    var stop = getTokenIndex(objs,"type",["open_paren","separator","keyword"]);    var oper = getTokenIndex(objs,"type",["operator"]);    if (truthy(stop) && truthy(oper) && stop < oper) {      return objs[stop+1];    } else if (truthy(stop)) {      return objs[stop];    } else {      return false;    }  }  function getToken(state,tokens) {    var objs = state.tokenStack;    var i = getTokenIndex(objs,"token",tokens);    return truthy(objs[i]) ? objs[i] : false;  }  function getTokenIndex(objs,propname,propvals) {    for (var i = objs.length-1; -1 < i ; i--) {      if (is_member(objs[i][propname],propvals)) {        return i;      }    }    return false;  }  function truthy(x) {    return (x !== false) && (x != null);  }/////////////////////////////////////////////////////////////////////////////// this object defines the mode  return {    startState:      function() {        return {tokenStack: [],                in_string:  false,                in_atom:    false};      },    token:      function(stream, state) {        return tokenizer(stream, state);      },    indent:      function(state, textAfter) {        return indenter(state,textAfter);      },    lineComment: "%"  };});});
 |