This module defines reusable code to colourise Prolog source.
- To be done
- - : The one-term version
- prolog_colourise_stream(+Stream, +SourceID, :ColourItem) is det
- prolog_colourise_stream(+Stream, +SourceID, :ColourItem, +Opts) is det
- Determine colour fragments for the data on Stream. SourceID is
the canonical identifier of the input as known to the
cross-referencer, i.e., as created using
xref_source(SourceID)
.
ColourItem is a closure that is called for each identified
fragment with three additional arguments:
- The syntactical category
- Start position (character offset) of the fragment
- Length of the fragment (in characters).
Options
- operators(+Ops)
- Provide an initial list of additional operators.
- source_module(+State, -Module) is semidet[private]
- True when Module is the module context into which the file is
loaded. This is the module of the file if File is a module file,
or the load context of File if File is not included or the
module context of the file into which the file was included.
- read_error(+Error, +TB, +Start, +Stream) is failure[private]
- If this is a syntax error, create a syntax-error fragment.
- warnable_singletons(+Singletons, -Warn) is det[private]
- Warn is the subset of the singletons that we warn about.
- colour_item(+Class, +TB, +Pos) is det[private]
- safe_push_op(+Prec, +Type, :Name, +State)[private]
- Define operators into the default source module and register
them to be undone by pop_operators/0.
- fix_operators(+Term, +Module, +State) is det[private]
- Fix flags that affect the syntax, such as operators and some
style checking options. Src is the canonical source as required
by the cross-referencer.
- process_use_module1(+Imports, +Src)[private]
- Get the exported operators from the referenced files.
- prolog_colourise_query(+Query:string, +SourceId, :ColourItem)
- Colourise a query, to be executed in the context of SourceId.
- Arguments:
-
SourceId | - Execute Query in the context of
the cross-referenced environment SourceID. |
- prolog_colourise_term(+Stream, +SourceID, :ColourItem, +Options)
- Colourise the next term on Stream. Unlike
prolog_colourise_stream/3, this predicate assumes it is reading
a single term rather than the entire stream. This implies that
it cannot adjust syntax according to directives that precede it.
Options:
- subterm_positions(-TermPos)
- Return complete term-layout. If an error is read, this is a
term
error_position(StartClause, EndClause, ErrorPos)
- colourise_term(+Term, +TB, +Termpos, +Comments)[private]
- Colourise the next Term.
- bug
- - The colour spec is closed with
fullstop
, but the
position information does not include the full stop
location, so all we can do is assume it is behind the
term.
- structured_comment_start(-Start)[private]
- Copied from library(pldoc/doc_process). Unfortunate, but we do
not want to force loading pldoc.
- colourise_term(+Term, +TB, +Pos)[private]
- Colorise a file toplevel term.
- colourise_extended_head(+Head, +ExtraArgs, +TB, +Pos) is det[private]
- Colourise a clause-head that is extended by term_expansion,
getting ExtraArgs more arguments (e.g., DCGs add two more
arguments.
- colourise_extern_head(+Head, +Module, +TB, +Pos)[private]
- Colourise the head specified as Module:Head. Normally used for
adding clauses to multifile predicates in other modules.
- functor_position(+Term, -FunctorPos, -ArgPosList)[private]
- Get the position of a functor and its argument. Unfortunately
this goes wrong for lists, who have two `functor-positions'.
- colourise_directive(+Body, +TB, +Pos)[private]
- Colourise the body of a directive.
- colourise_method_body(+MethodBody, +TB, +Pos)[private]
- Colourise the optional "comment":: as
pce(comment)
and proceed
with the body.
- To be done
- - Get this handled by a hook.
- colourise_goals(+Body, +Origin, +TB, +Pos)[private]
- Colourise the goals in a body.
- colourise_dcg(+Body, +Head, +TB, +Pos)[private]
- Breaks down to colourise_dcg_goal/3.
- colourise_goal(+Goal, +Origin, +TB, +Pos)[private]
- Colourise access to a single goal.
- To be done
- - Quasi Quotations are coloured as a general term argument.
Possibly we should do something with the goal information it
refers to, in particular if this goal is not defined.
- colourise_goal_args(+Goal, +TB, +Pos)[private]
- Colourise the arguments to a goal. This predicate deals with
meta- and database-access predicates.
- meta_args(+Goal, +TB, -ArgSpec) is semidet[private]
- Return a copy of Goal, where each meta-argument is an integer
representing the number of extra arguments or the atom // for
indicating a DCG body. The non-meta arguments are unbound
variables.
E.g. meta_args(maplist(foo,x,y), X)
--> X = maplist(2,_,_)
NOTE: this could be cached if performance becomes an issue.
- expand_meta(+MetaSpec, +Goal, -Expanded) is semidet[private]
- Add extra arguments to the goal if the meta-specifier is an
integer (see above).
- colourise_setof(+Term, +TB, +Pos)[private]
- Colourise the 2nd argument of setof/bagof
- colourise_option_args(+Goal, +Module, +Arg:integer, +TB, +ArgPos) is semidet[private]
- Colourise predicate options for the Arg-th argument of
Module:Goal
- colourise_files(+Arg, +TB, +Pos, +Why)[private]
- Colourise the argument list of one of the file-loading predicates.
- Arguments:
-
Why | - is one of any or imported |
- colourise_file_list(+Files, +TB, +ElmPos, +TailPos, +Why)[private]
- colourise_directory(+Arg, +TB, +Pos)[private]
- Colourise argument that should be an existing directory.
- colourise_langoptions(+Term, +TB, +Pos) is det[private]
- Colourise the 3th argument of module/3
- colourise_class(ClassName, TB, Pos)[private]
- Colourise an XPCE class.
- classify_class(+SourceId, +ClassName, -Classification)[private]
- Classify an XPCE class. As long as this code is in this module
rather than using hooks, we do not want to load xpce unless it
is already loaded.
- colourise_term_args(+Term, +TB, +Pos)[private]
- colourise head/body principal terms.
- colourise_term_arg(+Term, +TB, +Pos)[private]
- Colourise an arbitrary Prolog term without context of its semantical
role.
- colourise_expression(+Term, +TB, +Pos)[private]
- colourise arithmetic expressions.
- colourise_qq_type(+QQType, +TB, +QQTypePos)[private]
- Colouring the type part of a quasi quoted term
- colourise_dict_kv(+Dict, +TB, +KVPosList)[private]
- Colourise the name-value pairs in the dict
- colourise_exports(+List, +TB, +Pos)[private]
- Colourise the module export-list (or any other list holding
terms of the form Name/Arity referring to predicates).
- colourise_imports(+List, +File, +TB, +Pos)[private]
- Colourise import list from use_module/2, importing from File.
- colourise_declaration(+Decl, ?Which, +TB, +Pos) is det[private]
- Colourise declaration sequences as used by module/2, dynamic/1,
etc.
- colourise_declarations(+Term, +Which, +TB, +Pos)[private]
- Colourise specification for dynamic/1, table/1, etc. Includes
processing options such as
:- dynamic p/1 as incremental.
.
- colourise_op_declaration(Op, TB, Pos) is det[private]
- colourise_prolog_flag_name(+Name, +TB, +Pos)[private]
- Colourise the name of a Prolog flag
- expand_macro(+TB, +Macro, -Expanded) is semidet[private]
-
- To be done
- - This only works if the code is compiled. Ideally we'd also make
this work for not compiled code.
- goal_classification(+TB, +Goal, +Origin, -Class)[private]
- Classify Goal appearing in TB and called from a clause with head
Origin. For directives, Origin is [].
- goal_classification(+Goal, +Module, -Class)[private]
- Multifile hookable classification for non-local goals.
- vararg_goal_classification(+Name, +Arity, -Class) is semidet[multifile]
- Multifile hookable classification for vararg predicates.
- qualified_goal_classification(:Goal, +TB, -Class)[private]
- Classify an explicitly qualified goal.
- classify_head(+TB, +Head, -Class)[private]
- Classify a clause head
- def_style(+Pattern, -Style)[private]
- Define the style used for the given pattern. Definitions here
can be overruled by defining rules for
style/2
- syntax_colour(?Class, ?Attributes) is nondet
- True when a range classified Class must be coloured using
Attributes. Attributes is a list of:
colour(ColourName)
background(ColourName)
bold(Boolean)
underline(Boolean)
Attributes may be the empty list. This is used for cases where
-for example- a menu is associated with the fragment. If
syntax_colour/2 fails, no fragment is created for the region.
- term_colours(+Term, -FunctorColour, -ArgColours)[private]
- Define colourisation for specific terms.
- specified_item(+Specified, +Term, +TB, +TermPosition) is det[private]
- Colourise an item that is explicitly classified by the user using
term_colours/2 or goal_colours/2.
- specified_items(+Spec, +Term, +TB, +PosList)[private]
- specified_dict_kv(+PosList, +Term, +TB, +Specs)[private]
-
- Arguments:
-
Specs | - is a list of dict_kv(+Key, +KeySpec, +ArgSpec) |
Undocumented predicates
The following predicates are exported, but not or incorrectly documented.
- syntax_message(Arg1, Arg2, Arg3)