diff options
-rw-r--r-- | CHANGES | 1 | ||||
-rw-r--r-- | pygments/lexers/_mapping.py | 1 | ||||
-rw-r--r-- | pygments/lexers/other.py | 191 | ||||
-rw-r--r-- | tests/examplefiles/source.lgt | 343 |
4 files changed, 534 insertions, 2 deletions
@@ -19,6 +19,7 @@ Version 1.0 * NumPy * Python 3 * S, S-plus, R statistics languages + * Logtalk - In the LatexFormatter, the *commandprefix* option is now by default 'PY' instead of 'C', since the latter resulted in several collisions diff --git a/pygments/lexers/_mapping.py b/pygments/lexers/_mapping.py index 68781e53..995c0c30 100644 --- a/pygments/lexers/_mapping.py +++ b/pygments/lexers/_mapping.py @@ -70,6 +70,7 @@ LEXERS = { 'JspLexer': ('pygments.lexers.templates', 'Java Server Page', ('jsp',), ('*.jsp',), ('application/x-jsp',)), 'LiterateHaskellLexer': ('pygments.lexers.functional', 'Literate Haskell', ('lhs', 'literate-haskell'), ('*.lhs',), ('text/x-literate-haskell',)), 'LlvmLexer': ('pygments.lexers.asm', 'LLVM', ('llvm',), ('*.ll',), ('text/x-llvm',)), + 'LogtalkLexer': ('pygments.lexers.other', 'Logtalk', ('logtalk',), ('*.lgt',), ('text/x-logtalk',)), 'LuaLexer': ('pygments.lexers.agile', 'Lua', ('lua',), ('*.lua',), ('text/x-lua', 'application/x-lua')), 'MOOCodeLexer': ('pygments.lexers.other', 'MOOCode', ('moocode',), ('*.moo',), ('text/x-moocode',)), 'MakefileLexer': ('pygments.lexers.text', 'Makefile', ('make', 'makefile', 'mf', 'bsdmake'), ('*.mak', 'Makefile', 'makefile', 'Makefile.*'), ('text/x-makefile',)), diff --git a/pygments/lexers/other.py b/pygments/lexers/other.py index 65e147d5..f1f474e8 100644 --- a/pygments/lexers/other.py +++ b/pygments/lexers/other.py @@ -6,7 +6,7 @@ Lexers for other languages. :copyright: 2006-2008 by Georg Brandl, Tim Hatch <tim@timhatch.com>, - Stou Sandalski. + Stou Sandalski, Paulo Moura, Clara Dimene. :license: BSD, see LICENSE for more details. """ @@ -20,7 +20,7 @@ from pygments.util import shebang_matches __all__ = ['SqlLexer', 'MySqlLexer', 'BrainfuckLexer', 'BashLexer', 'BatchLexer', 'BefungeLexer', 'RedcodeLexer', 'MOOCodeLexer', - 'SmalltalkLexer', 'TcshLexer'] + 'SmalltalkLexer', 'TcshLexer', 'LogtalkLexer'] class SqlLexer(RegexLexer): @@ -620,3 +620,190 @@ class TcshLexer(RegexLexer): ], } + +class LogtalkLexer(RegexLexer): + """ + For `Logtalk <http://logtalk.org/>`_ source code. + + *New in Pygments 1.0.* + """ + + name = 'Logtalk' + aliases = ['logtalk'] + filenames = ['*.lgt'] + mimetypes = ['text/x-logtalk'] + + tokens = { + 'root': [ + # Directives + (r'^\s*:-\s',Punctuation,'directive'), + # Comments + (r'%.*?\n', Comment), + (r'/\*(.|\n)*?\*/',Comment), + # Whitespace + (r'\n', Text), + (r'\s+', Text), + # Numbers + (r"0'.", Number), + (r'0b[01]+', Number), + (r'0o[0-7]+', Number), + (r'0x[0-9a-fA-F]+', Number), + (r'\d+\.?\d*((e|E)(\+|-)?\d+)?', Number), + # Variables + (r'([A-Z_][a-zA-Z0-9_]*)', Name.Variable), + # Event handlers + (r'(after|before)(?=[(])', Keyword), + # Execution-context methods + (r'(parameter|this|se(lf|nder))(?=[(])', Keyword), + # Reflection + (r'(current_predicate|predicate_property)(?=[(])', Keyword), + # DCGs and term expansion + (r'(expand_term|(goal|term)_expansion|phrase)(?=[(])', Keyword), + # Entity + (r'(abolish|c(reate|urrent))_(object|protocol|category)(?=[(])', Keyword), + (r'(object|protocol|category)_property(?=[(])', Keyword), + # Entity relations + (r'complements_object(?=[(])', Keyword), + (r'extends_(object|protocol|category)(?=[(])', Keyword), + (r'imp(lements_protocol|orts_category)(?=[(])', Keyword), + (r'(instantiat|specializ)es_class(?=[(])', Keyword), + # Events + (r'(current_event|(abolish|define)_events)(?=[(])', Keyword), + # Flags + (r'(current|set)_logtalk_flag(?=[(])', Keyword), + # Compiling, loading, and library paths + (r'logtalk_(compile|l(ibrary_path|oad))(?=[(])', Keyword), + # Database + (r'(clause|retract(all)?)(?=[(])', Keyword), + (r'a(bolish|ssert(a|z))(?=[(])', Keyword), + # Control + (r'(ca(ll|tch)|throw)(?=[(])', Keyword), + (r'(fail|true)\b', Keyword), + # All solutions + (r'((bag|set)of|f(ind|or)all)(?=[(])', Keyword), + # Multi-threading meta-predicates + (r'threaded(_(call|once|ignore|exit|peek|wait|notify))?(?=[(])', Keyword), + # Term unification + (r'unify_with_occurs_check(?=[(])', Keyword), + # Term creation and decomposition + (r'(functor|arg|copy_term)(?=[(])', Keyword), + # Evaluable functors + (r'(rem|mod|abs|sign)(?=[(])', Keyword), + (r'float(_(integer|fractional)_part)?(?=[(])', Keyword), + (r'(floor|truncate|round|ceiling)(?=[(])', Keyword), + # Other arithmetic functors + (r'(cos|atan|exp|log|s(in|qrt))(?=[(])', Keyword), + # Term testing + (r'(var|atom(ic)?|integer|float|compound|n(onvar|umber))(?=[(])', Keyword), + # Stream selection and control + (r'(curren|se)t_(in|out)put(?=[(])', Keyword), + (r'(open|close)(?=[(])', Keyword), + (r'flush_output(?=[(])', Keyword), + (r'(at_end_of_stream|flush_output)\b', Keyword), + (r'(stream_property|at_end_of_stream|set_stream_position)(?=[(])', Keyword), + # Character and byte input/output + (r'(nl|(get|peek|put)_(byte|c(har|ode)))(?=[(])', Keyword), + (r'\bnl\b', Keyword), + # Term input/output + (r'read(_term)?(?=[(])', Keyword), + (r'write(q|_(canonical|term))?(?=[(])', Keyword), + (r'(current_)?op(?=[(])', Keyword), + (r'(current_)?char_conversion(?=[(])', Keyword), + # Atomic term processing + (r'atom_(length|c(hars|o(ncat|des)))(?=[(])', Keyword), + (r'(char_code|sub_atom)(?=[(])', Keyword), + (r'number_c(har|ode)s(?=[(])', Keyword), + # Implementation defined hooks functions + (r'(se|curren)t_prolog_flag(?=[(])', Keyword), + (r'\bhalt\b', Keyword), + (r'halt(?=[(])', Keyword), + # Message sending operators + (r'(::|:|\^\^)', Operator), + # External call + (r'[{}]', Keyword), + # Logic and control + (r'\bonce(?=[(])', Keyword), + (r'\brepeat\b', Keyword), + # Bitwise functors + (r'(>>|<<|/\\|\\\\|\\)', Operator), + # Arithemtic evaluation + (r'\bis\b', Keyword), + # Arithemtic comparison + (r'(=:=|=\\=|<|=<|>=|>)', Operator), + # Term creation and decomposition + (r'=\.\.', Operator), + # Term unification + (r'(=|\\=)', Operator), + # Term comparison + (r'(==|\\==|@=<|@<|@>=|@>)', Operator), + # Evaluable functors + (r'(//|[-+*/])', Operator), + (r'\b(mod|rem)\b', Operator), + # Other arithemtic functors + (r'\b\*\*\b', Operator), + # DCG rules + (r'-->', Operator), + # Control constructs + (r'([!;]|->)', Operator), + # Logic and control + (r'\\+', Operator), + # Mode operators + (r'[?@]', Operator), + # Strings + (r'"(\\\\|\\"|[^"])*"', String), + # Ponctuation + (r'[()\[\],.|]', Text), + # Atoms + (r"[a-z][a-zA-Z0-9_]*", Text), + (r"[']", String, 'quoted_atom'), + ], + + 'quoted_atom': [ + (r"['][']", String), + (r"[']", String, '#pop'), + (r'\\([\\abfnrtv"\']|(x[a-fA-F0-9]+|[0-7]+)\\)', String.Escape), + (r"[^\\'\n]+", String), + (r'\\', String), + ], + + 'directive': [ + # Entity directives + (r'(category|object|protocol)(?=[(])', Keyword, 'entityrelations'), + (r'(end_(category|object|protocol))[.]',Keyword, 'root'), + # Predicate scope directives + (r'(public|protected|private)(?=[(])', Keyword, 'root'), + # Other directives + (r'\be(ncoding|xport)(?=[(])', Keyword, 'root'), + (r'\bin(fo|itialization)(?=[(])', Keyword, 'root'), + (r'\b(dynamic|synchronized|threaded)[.]', Keyword, 'root'), + (r'\b(alias|d(ynamic|iscontiguous)|m(eta_predicate|ode|ultifile)|synchronized)(?=[(])', Keyword, 'root'), + (r'\bop(?=[(])', Keyword, 'root'), + (r'\b(calls|use(s|_module))(?=[(])', Keyword, 'root'), + ], + + 'entityrelations': [ + (r'(extends|i(nstantiates|mp(lements|orts))|specializes)(?=[(])', Keyword), + # Numbers + (r"0'.", Number), + (r'0b[01]+', Number), + (r'0o[0-7]+', Number), + (r'0x[0-9a-fA-F]+', Number), + (r'\d+\.?\d*((e|E)(\+|-)?\d+)?', Number), + # Variables + (r'([A-Z_][a-zA-Z0-9_]*)', Name.Variable), + # Atoms + (r"[a-z][a-zA-Z0-9_]*", Text), + (r"[']", String, 'quoted_atom'), + # Strings + (r'"(\\\\|\\"|[^"])*"', String), + # End of entity-opening directive + (r'([)]\.\n)', Text, 'root'), + # Scope operator + (r'(::)', Operator), + # Ponctuation + (r'[()\[\],.|]', Text), + # Whitespace + (r'\n', Text), + (r'\s+', Text), + ] + } diff --git a/tests/examplefiles/source.lgt b/tests/examplefiles/source.lgt new file mode 100644 index 00000000..ce5abced --- /dev/null +++ b/tests/examplefiles/source.lgt @@ -0,0 +1,343 @@ + +% this is a single-line comment + +/* +this is +a block +comment +*/ + + +:- encoding(some_encoding). +:- op(Precedence, Associativity, Operator). + + +:- object(prototype, + implements(protocol), + imports(category), + extends(parent)). + + :- info([ + version is 1.0, + author is 'Paulo Moura', + date is 2008/5/1, + comment is 'Sample prototype for testing syntax coloring.']). + :- threaded. + :- synchronized. + :- dynamic. + :- initialization(some_goal(X, Y)). + :- calls(some_other_protocol). + :- uses(another_object). + + :- alias(set, member/2, set_member/2). + :- alias(words, singular//0, peculiar//0). + + :- uses(list, [append/3, member/2]). + :- uses(queues, [new/1::new_queue/1]). + + :- public(aaa/2). + :- meta_predicate(aaa(::, *)). + :- discontiguous(aaa/2). + :- mode(aaa(+callable, ?integer), zero_or_one). + :- info(position/2, [ + comment is 'Predicate brief description.', + arguments is ['Arg1'-'Arg1 description', 'Arg2'-'Arg2 description']]). + + :- protected(bbb/2). + :- synchronized(bbb/2). + :- mode(bbb(+integer, -float), one). + :- info(bbb/2, [ + comment is 'Predicate brief description.', + argnames is ['Arg1', 'Arg2']]). + + :- private(ccc/2). + :- dynamic(ccc/2). + :- mode(ccc(@atom, ?atom), one_or_more). + :- info(ccc/2, [ + comment is 'Predicate brief description.', + argnames is ['Arg1', 'Arg2']]). + + enumerating_entities(Object, Protocol, Category) :- + current_category(Category), + current_object(Object), + current_protocol(Protocol). + + enumerating_properties :- + category_property(Category, Property), + object_property(Object, Property), + protocol_property(Protocol, Property). + + creating_entities(Object, Protocol, Category) :- + create_category(Category, Relations, Directives, Clauses), + create_object(Object, Relations, Directives, Clauses), + create_protocol(Protocol, Relations, Directives). + + abolishing_entities(Object, Protocol, Category) :- + abolish_category(Category), + abolish_object(Object), + abolish_protocol(Protocol). + + entity_relations :- + extends_object(Prototype, Parent, Scope), + extends_protocol(Protocol1, Protocol2, Scope), + extends_category(Category1, Category2, Scope), + implements_protocol(Object, Protocol, Scope), + imports_category(Object, Category, Scope), + instantiates_class(Instance, Class, Scope), + specializes_class(Class, Superclass, Scope), + complements_object(Category, Object). + + event_handling :- + abolish_events(Event, Object, Message, Sender, Monitor), + current_event(Event, Object, Message, Sender, Monitor), + define_events(Event, Object, Message, Sender, Monitor). + + multi_threading :- + threaded(Goals), + threaded_call(Goal), + threaded_once(Goal), + threaded_ignore(Goal), + threaded_exit(Goal), + threaded_peek(Goal), + threaded_wait(Goal), + threaded_notify(Notification). + + compiling_and_loading :- + logtalk_compile(File, Options), + logtalk_load(File, Options), + logtalk_library_path(Library, Path). + + flags :- + current_logtalk_flag(Flag, Value), + set_logtalk_flag(Flag, Value). + + execution_context_methods :- + parameter(N, Parameter), + self(Self), + sender(Sender), + this(This). + + reflection_methods :- + current_predicate(Predicate), + predicate_property(Predicate, Property). + + database_methods :- + abolish(Functor/Arity), + asserta(Clause), + assertz(Clause), + clause(Head, Body), + retract(Clause), + retractall(Head). + + meta_call_methods :- + call(Goal). + + all_solutions_methods :- + bagof(Term, Goal, List), + findall(Term, Goal, List), + forall(Generate, Test), + setof(Term, Goal, List). + + event_handler_methods :- + before(Object, Message, Sender), + after(Object, Message, Sender). + + dcg_rules_parsing_methods :- + phrase(NonTerminal, Input, Rest). + + term_expansion_methods :- + expand_term(Term, Expanded), + term_expansion(Term, Expanded), + goal_expansion(Goal, Expanded). + + message_sending :- + Object::Message, + ::Message, + ^^Message. + + calling_external_code :- + {goal1, goal2, goal3}. + + context_switching_calls :- + Object<<Goal. + + direct_calls_of_category_predicates :- + :Goal. + + if_then_else :- + ( If -> + Then + ; Else + ). + + numbers :- + X is 13, + Y is 13.13, + Z is 13.13e-23, + C1 is 0'A, C2 is 0'', C3 is 0'", + B is 0b1011101, + O is 0o1234560, + H is 0x1234567890abcDEF. + + functions :- + A is atan(3.14) + sin(0.77) - cos(123.23), + B is sign(-12) * abs(35/78), + C is truncate(3.14) + round(-7.8) - ceiling(111.88), + D is exp(3.8) - log(123.98) / sqrt(33) * 23 ** 4, + E is rem(3, 2) + mod(5, 3) * 2 rem 2 // 5 mod 3, + F is float_fractional_part(3.14) + float_integer_part(3.14), + G is float(33) + floor(99.99). + + bitwise :- + A is 16 >> 2, + B is 16 << 2, + C is 10 /\ 12, + D is 10 \/ 12, + E is \ 10. + + term_unification :- + Term1 = Term2, + Term1 \= Term2, + unify_with_occurs_check(Term1, Term2). + + term_testing :- + atom(Atom), + atomic(Atomic), + integer(Integer), + float(Float), + compound(Term), + nonvar(Term), + var(Term), + number(Number). + + term_comparison :- + Term1 == Term2, + Term1 \== Term2, + Term1 @< Term2, + Term1 @=< Term2, + Term1 @>= Term2, + Term1 @> Term2. + + term_creation_and_decomposition :- + functor(Term, Functor, Arity), + arg(N, Term, Arg), + Term =.. [Functor| Args], + copy_term(Term, Copy). + + arithemtic_evaluation :- + X is Expression. + + arithemtic_comparison :- + Exp1 =:= Exp2, + Exp1 =\= Exp2, + Exp1 < Exp2, + Exp1 =< Exp2, + Exp1 > Exp2, + Exp1 >= Exp2. + + stream_selection_and_control :- + current_input(Stream), + current_output(Stream), + set_input(Stream), + set_output(Stream), + open(Source, Mode, Stream, Options), + close(Stream), + flush_output(Stream), + stream_property(Stream, Property), + at_end_of_stream(Stream), + set_stream_position(Stream, Position), + flush_output, + at_end_of_stream. + + character_input_output :- + get_char(Char), + get_code(Code), + peek_char(Char), + peek_code(Code), + put_char(Char), + put_code(Code), + nl(Stream), + nl. + + byte_input_output :- + get_byte(Byte), + peek_byte(Byte), + put_byte(Byte). + + term_input_output :- + read(Term), + read_term(Term), + write(Term), + write(Term), + write_canonical(Term), + write_term(Stream, Term, Options), + current_op(Precedence, Associativity, Operator), + op(Precedence, Associativity, Operator), + current_char_conversion(InChar, OutChar), + char_conversion(InChar, OutChar). + + logic_and_control :- + \+ Goal, + once(Goal), + repeat, + !. + + atomic_term_processing :- + atom_length(Atom, Length), + atom_chars(Atom, Chars), + atom_codes(Atom, Codes), + atom_concat(Atom1, Atom2, Atom), + sub_atom(Atom, Before, Length, After, SubAtom), + char_code(Char, Code), + number_chars(Number, Chars), + number_codes(Number, Codes). + + implementation_defined_hooks :- + current_prolog_flag(Flag, Value), + set_prolog_flag(Flag, Value), + halt(ExitCode), + halt. + + number(C) --> "+", number(C). + number(C) --> "-", number(X), {C is -X}. + number(X) --> [C], {0'0 =< C, C =< 0'9, X is C - 0'0}. + +:- end_object. + + + +:- object(class, + implements(protocol), + imports(category), + instantiates(metaclass), + specializes(superclass)). + + +:- end_object. + + + +:- object(parametric(_Par1, _Par2), + implements(protocol), + imports(category), + extends(parent(_Par))). + + +:- end_object. + + + +:- category(category, + implements(protocol), + extends(other_category)). + + +:- end_category. + + + +:- protocol(extended, + extends(minimal)). + + +:- end_protocol. |