jupyter
This commit is contained in:
@@ -4,12 +4,12 @@
|
||||
* @brief Prolog completer.
|
||||
*/
|
||||
|
||||
:- module( completer,
|
||||
[completions/2 ]).
|
||||
%% %% :- module( completer,
|
||||
%% %% [completions/2 ]).
|
||||
|
||||
:- use_module(library(lists)).
|
||||
:- use_module(library(maplist)).
|
||||
:- use_module(library(python)).
|
||||
:- use_module(library(python)).
|
||||
|
||||
%% completions( +Text, +PythonCell )
|
||||
%
|
||||
|
@@ -6,36 +6,38 @@
|
||||
*/
|
||||
|
||||
:- yap_flag(gc_trace,verbose).
|
||||
|
||||
/*
|
||||
:- module( jupyter,
|
||||
[jupyter_query/3,
|
||||
blank/1
|
||||
blank/1,
|
||||
streams/1
|
||||
]
|
||||
).
|
||||
*/
|
||||
:- use_module(library(hacks)).
|
||||
|
||||
:- use_module(library(lists)).
|
||||
:- use_module(library(maplist)).
|
||||
|
||||
:- reexport(library(python)).
|
||||
:- reexport(library(yapi)).
|
||||
:- reexport(library(complete)).
|
||||
:- reexport(library(verify)).
|
||||
%% :- reexport(library(python)).
|
||||
%% :- reexport(library(yapi)).
|
||||
%% :- reexport(library(complete)).
|
||||
%% :- reexport(library(verify)).
|
||||
|
||||
|
||||
:- python_import(sys).
|
||||
|
||||
jupyter_query(Caller, Cell, Line ) :-
|
||||
jupyter_cell(Caller, Cell, Line).
|
||||
jupyter_cell(Caller, Cell, Line).
|
||||
|
||||
jupyter_cell(_Caller, Cell, _Line) :-
|
||||
jupyter_consult(Cell), %stack_dump,
|
||||
fail.
|
||||
jupyter_cell( _Caller, _, '' ) :- !.
|
||||
jupyter_cell( _Caller, _, `` ) :- !.
|
||||
jupyter_cell( _Caller, _, Line ) :-
|
||||
blank( Line ),
|
||||
!.
|
||||
jupyter_cell( Caller, _, Line ) :-
|
||||
Self := Caller.query,
|
||||
jupyter_cell(Self, _, Line ) :-
|
||||
catch(
|
||||
python_query(Self,Line),
|
||||
E=error(A,B),
|
||||
@@ -83,7 +85,8 @@ blank(Text) :-
|
||||
string_codes(Text, L),
|
||||
maplist( code_type(space), L).
|
||||
|
||||
streams(false) :-
|
||||
|
||||
streams(false) :-
|
||||
close(user_input),
|
||||
close(user_output),
|
||||
close(user_error).
|
||||
@@ -109,4 +112,4 @@ plot_inline :-
|
||||
|
||||
:- endif.
|
||||
|
||||
%:- ( start_low_level_trace ).
|
||||
%y:- ( start_low_level_trace ).
|
||||
|
@@ -5,19 +5,22 @@
|
||||
*/
|
||||
|
||||
|
||||
:- module( verify,
|
||||
[errors/2,q
|
||||
ready/2]
|
||||
).
|
||||
%% :- module( verify,
|
||||
%% [errors/2,
|
||||
%% ready/2]
|
||||
%% ).
|
||||
:- use_module(library(hacks)).
|
||||
:- use_module(library(jupyter)).
|
||||
%% :- use_module(library(jupyter)).
|
||||
|
||||
|
||||
:- use_module(library(lists)).
|
||||
:- use_module(library(maplist)).
|
||||
|
||||
:- use_module(library(python)).
|
||||
:- use_module(library(yapi)).
|
||||
:- use_module(library(python)).
|
||||
%% :- use_module(library(yapi)).
|
||||
|
||||
:- dynamic jupyter/1.
|
||||
jupyter( []).
|
||||
|
||||
ready( Engine, Query) :-
|
||||
errors( Engine , Cell ),
|
||||
@@ -27,10 +30,10 @@ ready( Engine, Query) :-
|
||||
|
||||
|
||||
errors( _Engine , Text ) :-
|
||||
blank(Text).
|
||||
blank(Text),
|
||||
!.
|
||||
errors( Engine , Text ) :-
|
||||
jupyter..shell := Engine,
|
||||
%start_low_level_trace,
|
||||
setup_call_cleanup(
|
||||
open_esh( Engine , Text, Stream, Name ),
|
||||
esh(Engine , Name, Stream),
|
||||
@@ -40,50 +43,55 @@ errors( Engine , Text ) :-
|
||||
errors( _Engine , _Text ).
|
||||
|
||||
open_esh(Engine , Text, Stream, Name) :-
|
||||
Engine.errors := [],
|
||||
Engine.errors := [],
|
||||
retractall(jupyter(_)),
|
||||
assertz(jupyter(Engine)),
|
||||
b_setval( jupyter, Engine),
|
||||
Name := Engine.stream_name,
|
||||
open_mem_read_stream( Text, Stream ).
|
||||
|
||||
esh(Engine , Name, Stream) :-
|
||||
b_setval(code,python),
|
||||
repeat,
|
||||
catch(
|
||||
( read_clause(Stream, Cl, [ syntax_errors(fail)]),
|
||||
writeln(cl:Cl),
|
||||
read_clause(Stream, Cl, [ syntax_errors(dec10)]),
|
||||
error(C,E),
|
||||
p_message(C,E)
|
||||
|
||||
p3_message(C,Engine,E)
|
||||
),
|
||||
Cl == end_of_file,
|
||||
!.
|
||||
|
||||
user:print_message() :- p_message
|
||||
|
||||
:- multifile user:portray_message/2.
|
||||
|
||||
user:portray_message(S,E) :-
|
||||
jupyter(En),
|
||||
En \= [],
|
||||
python_clear_errors,
|
||||
p3_message(S,En,E).
|
||||
|
||||
close_esh( _Engine , Stream ) :-
|
||||
b_delete
|
||||
retractall(jupyter(_)),
|
||||
assertz(jupyter([])),
|
||||
close(Stream).
|
||||
|
||||
|
||||
p_message(Severity, Error) :-
|
||||
writeln((Severity->Error)),
|
||||
p_message(Severity, Engine, Error).
|
||||
|
||||
p_message( _Severity, Engine, error(syntax_error(Cause),info(between(_,LN,_), _FileName, CharPos, Details))) :-
|
||||
%% nb_getval(jupyter_cell, on),
|
||||
%% assert( syntax_error(Cause,LN,CharPos,Details) ).
|
||||
%% user:portray_message(_Severity, error(style_check(_),_) ) :-
|
||||
%% nb_getval(jupyter_cell, on).
|
||||
Engine.errors := [t(Cause,LN,CharPos,Details)] + Engine.errors,
|
||||
!.
|
||||
p_message(error, Engine, E) :-
|
||||
writeln(E),
|
||||
!.
|
||||
p_message(warning, Engine, E) :-
|
||||
p3_message( _Severity, Engine, error(syntax_error(Cause),info(between(_,LN,_), _FileName, CharPos, Details))) :-
|
||||
python_clear_errors,
|
||||
!,
|
||||
writeln(E),
|
||||
NE := [t(Cause,LN,CharPos,Details)]+Engine.errors,
|
||||
writeln(E),
|
||||
writeln(NE),
|
||||
Engine.errors := NE.
|
||||
p3_message(error, Engine, E) :-
|
||||
python_clear_errors,
|
||||
!.
|
||||
p3_message(warning, Engine, E) :-
|
||||
!.
|
||||
p_message(error, Engine, E) :-
|
||||
p3_message(error, Engine, E) :-
|
||||
Engine.errors := [E] + Engine.errors.
|
||||
p_message(warning, Engine, E) :-
|
||||
p3_message(warning, Engine, E) :-
|
||||
Engine.errors := [E] + Engine.errors.
|
||||
%% ready(_Self, Line ) :-
|
||||
%% blank( Line ),
|
||||
@@ -173,3 +181,4 @@ p_message( _Severity, Engine, error(syntax_error(Cause),info(between(_,LN,_), _
|
||||
%% Self.errors := [t(C,L,N,A)] + Self.errors,
|
||||
%% fail.
|
||||
%% close_events( _ ).
|
||||
|
||||
|
@@ -113,424 +113,9 @@ class YAPInputSplitter(InputSplitter):
|
||||
return True
|
||||
if not line:
|
||||
line = text.rstrip()
|
||||
engine.errors = []
|
||||
engine.goal(errors(engine, text),True)
|
||||
print(engine.errors)
|
||||
return engine.errors != []
|
||||
|
||||
|
||||
def reset(self):
|
||||
"""Reset the input buffer and associated state."""
|
||||
#super(YAPInputSplitter, self).reset()
|
||||
self._buffer_raw[:] = []
|
||||
self.source_raw = ''
|
||||
self.transformer_accumulating = False
|
||||
|
||||
for t in self.transforms:
|
||||
try:
|
||||
t.reset()
|
||||
except SyntaxError:
|
||||
# Nothing that calls reset() expects to handle transformer
|
||||
# errors
|
||||
pass
|
||||
|
||||
def flush_transformers(self):
|
||||
def _flush(transform, outs):
|
||||
"""yield transformed lines
|
||||
|
||||
always strings, never None
|
||||
|
||||
transform: the current transform
|
||||
outs: an iterable of previously transformed inputs.
|
||||
Each may be multiline, which will be passed
|
||||
one line at a time to transform.
|
||||
"""
|
||||
for out in outs:
|
||||
for line in out.splitlines():
|
||||
# push one line at a time
|
||||
tmp = transform.push(line)
|
||||
if tmp is not None:
|
||||
yield tmp
|
||||
|
||||
# reset the transform
|
||||
tmp = transform.reset()
|
||||
if tmp is not None:
|
||||
yield tmp
|
||||
|
||||
out = []
|
||||
|
||||
for t in self.transforms:
|
||||
out = _flush(t, out)
|
||||
|
||||
out = list(out)
|
||||
if out:
|
||||
self._store('\n'.join(out))
|
||||
|
||||
def raw_reset(self):
|
||||
"""Return raw input only and perform a full reset.
|
||||
"""
|
||||
out = self.source_raw
|
||||
self.reset()
|
||||
return out
|
||||
|
||||
def source_reset(self):
|
||||
try:
|
||||
self.flush_transformers()
|
||||
return self.source
|
||||
finally:
|
||||
self.reset()
|
||||
|
||||
def push_accepts_more(self):
|
||||
if self.transformer_accumulating:
|
||||
return True
|
||||
else:
|
||||
return self.validQuery(self.source, engine, self.shell)
|
||||
|
||||
def transform_cell(self, cell):
|
||||
"""Process and translate a cell of input.
|
||||
"""
|
||||
self.reset()
|
||||
try:
|
||||
self.push(cell)
|
||||
self.flush_transformers()
|
||||
return self.source
|
||||
finally:
|
||||
self.reset()
|
||||
|
||||
def push(self, lines):
|
||||
"""Push one or more lines of yap_ipython input.
|
||||
|
||||
This stores the given lines and returns a status code indicating
|
||||
whether the code forms a complete Python block or not, after processing
|
||||
all input lines for special yap_ipython syntax.
|
||||
|
||||
Any exceptions generated in compilation are swallowed, but if an
|
||||
exception was produced, the method returns True.
|
||||
|
||||
Parameters
|
||||
----------
|
||||
lines : string
|
||||
One or more lines of Python input.
|
||||
|
||||
Returns
|
||||
-------
|
||||
is_complete : boolean
|
||||
True if the current input source (the result of the current input
|
||||
plus prior inputs) forms a complete Python execution block. Note that
|
||||
this value is also stored as a private attribute (_is_complete), so it
|
||||
can be queried at any time.
|
||||
"""
|
||||
|
||||
# We must ensure all input is pure unicode
|
||||
lines = cast_unicode(lines, self.encoding)
|
||||
# ''.splitlines() --> [], but we need to push the empty line to transformers
|
||||
lines_list = lines.splitlines()
|
||||
if not lines_list:
|
||||
lines_list = ['']
|
||||
|
||||
# Store raw source before applying any transformations to it. Note
|
||||
# that this must be done *after* the reset() call that would otherwise
|
||||
# flush the buffer.
|
||||
self._store(lines, self._buffer_raw, 'source_raw')
|
||||
|
||||
transformed_lines_list = []
|
||||
for line in lines_list:
|
||||
transformed = self._transform_line(line)
|
||||
if transformed is not None:
|
||||
transformed_lines_list.append(transformed)
|
||||
if transformed_lines_list:
|
||||
transformed_lines = '\n'.join(transformed_lines_list)
|
||||
else:
|
||||
# Got nothing back from transformers - they must be waiting for
|
||||
# more input.
|
||||
return False
|
||||
|
||||
def _transform_line(self, line):
|
||||
"""Push a line of input code through the various transformers.
|
||||
|
||||
Returns any output from the transformers, or None if a transformer
|
||||
is accumulating lines.
|
||||
|
||||
Sets self.transformer_accumulating as a side effect.
|
||||
"""
|
||||
def _accumulating(dbg):
|
||||
#print(dbg)
|
||||
self.transformer_accumulating = True
|
||||
return None
|
||||
|
||||
for transformer in self.physical_line_transforms:
|
||||
line = transformer.push(line)
|
||||
if line is None:
|
||||
return _accumulating(transformer)
|
||||
|
||||
for transformer in self.logical_line_transforms:
|
||||
line = transformer.push(line)
|
||||
if line is None:
|
||||
return _accumulating(transformer)
|
||||
|
||||
|
||||
#print("transformers clear") #debug
|
||||
self.transformer_accumulating = False
|
||||
return line
|
||||
|
||||
|
||||
class YAPCompleter(Completer):
|
||||
|
||||
greedy = Bool(False,
|
||||
help="""Activate greedy completion
|
||||
PENDING DEPRECTION. this is now mostly taken care of with Jedi.
|
||||
|
||||
This will enable completion on elements of lists, self.results of function calls, etc.,
|
||||
but can be unsafe because the code is actually evaluated on TAB.
|
||||
"""
|
||||
).tag(config=True)
|
||||
|
||||
debug = Bool(default_value=False,
|
||||
help='Enable debug for the Completer. Mostly print extra '
|
||||
'information for experimental jedi integration.') \
|
||||
.tag(config=True)
|
||||
|
||||
backslash_combining_completions = Bool(True,
|
||||
help="Enable unicode completions, e.g. \\alpha<tab> . "
|
||||
"Includes completion of latex commands, unicode names, and expanding "
|
||||
"unicode characters back to latex commands.").tag(config=True)
|
||||
|
||||
|
||||
|
||||
def __init__(self, namespace=None, global_namespace=None, shell=None, **kwargs):
|
||||
"""Create a new completer for the command line.
|
||||
|
||||
Completer(namespace=ns, global_namespace=ns2) -> completer instance.
|
||||
|
||||
"""
|
||||
|
||||
self.shell = shell
|
||||
self.magic_escape = ESC_MAGIC
|
||||
super(Completer, self).__init__(**kwargs)
|
||||
|
||||
def complete(self, text, line=None, cursor_pos=None):
|
||||
"""Return the completed text and a list of completions.
|
||||
|
||||
Parameters
|
||||
----------
|
||||
|
||||
text : string
|
||||
A string of text to be completed on. It can be given as empty and
|
||||
instead a line/position pair are given. In this case, the
|
||||
completer itself will split the line like readline does.
|
||||
|
||||
This is called successively with state == 0, 1, 2, ... until it
|
||||
returns None. The completion should begin with 'text'.
|
||||
|
||||
line : string, optional
|
||||
The complete line that text is part of.
|
||||
|
||||
cursor_pos : int, optional
|
||||
The position of the cursor on the input line.
|
||||
|
||||
Returns
|
||||
-------
|
||||
text : string
|
||||
The actual text that was completed.
|
||||
|
||||
matches : list
|
||||
A sorted list with all possible completions.
|
||||
|
||||
The optional arguments allow the completion to take more context into
|
||||
account, and are part of the low-level completion API.
|
||||
|
||||
This is a wrapper around the completion mechanism, similar to what
|
||||
readline does at the command line when the TAB key is hit. By
|
||||
exposing it as a method, it can be used by other non-readline
|
||||
environments (such as GUIs) for text completion.
|
||||
|
||||
Simple usage example:
|
||||
|
||||
In [1]: x = 'hello'
|
||||
|
||||
In [2]: _ip.complete('x.l')
|
||||
Out[2]: ('x.l', ['x.ljust', 'x.lower', 'x.lstrip'])
|
||||
"""
|
||||
if not text:
|
||||
text = line[:cursor_pos]
|
||||
return self.completions(text, cursor_pos)
|
||||
|
||||
|
||||
def magic_matches(self, text):
|
||||
"""Match magics"""
|
||||
# Get all shell magics now rather than statically, so magics loaded at
|
||||
# runtime show up too.
|
||||
lsm = self.shell.magics_manager.lsmagic()
|
||||
line_magics = lsm['line']
|
||||
cell_magics = lsm['cell']
|
||||
pre = self.magic_escape
|
||||
pre2 = pre+pre
|
||||
|
||||
explicit_magic = text.startswith(pre)
|
||||
|
||||
# Completion logic:
|
||||
# - user gives %%: only do cell magics
|
||||
# - user gives %: do both line and cell magics
|
||||
# - no prefix: do both
|
||||
# In other words, line magics are skipped if the user gives %% explicitly
|
||||
#
|
||||
# We also exclude magics that match any currently visible names:
|
||||
# https://github.com/ipython/ipython/issues/4877, unless the user has
|
||||
# typed a %:
|
||||
# https://github.com/ipython/ipython/issues/10754
|
||||
bare_text = text.lstrip(pre)
|
||||
global_matches = []
|
||||
if not explicit_magic:
|
||||
def matches(magic):
|
||||
"""
|
||||
Filter magics, in particular remove magics that match
|
||||
a name present in global namespace.
|
||||
"""
|
||||
return ( magic.startswith(bare_text) and
|
||||
magic not in global_matches )
|
||||
else:
|
||||
def matches(magic):
|
||||
return magic.startswith(bare_text)
|
||||
|
||||
comp = [ pre2+m for m in cell_magics if matches(m)]
|
||||
if not text.startswith(pre2):
|
||||
comp += [ pre+m for m in line_magics if matches(m)]
|
||||
|
||||
return comp
|
||||
|
||||
def magic_config_matches(self, text): #:str) -> List[str]:
|
||||
""" Match class names and attributes for %config magic """
|
||||
texts = text.strip().split()
|
||||
|
||||
if len(texts) > 0 and (texts[0] == 'config' or texts[0] == '%config'):
|
||||
# get all configuration classes
|
||||
classes = sorted(set([ c for c in self.shell.configurables
|
||||
if c.__class__.class_traits(config=True)
|
||||
]), key=lambda x: x.__class__.__name__)
|
||||
classnames = [ c.__class__.__name__ for c in classes ]
|
||||
|
||||
# return all classnames if config or %config is given
|
||||
if len(texts) == 1:
|
||||
return classnames
|
||||
|
||||
# match classname
|
||||
classname_texts = texts[1].split('.')
|
||||
classname = classname_texts[0]
|
||||
classname_matches = [ c for c in classnames
|
||||
if c.startswith(classname) ]
|
||||
|
||||
# return matched classes or the matched class with attributes
|
||||
if texts[1].find('.') < 0:
|
||||
return classname_matches
|
||||
elif len(classname_matches) == 1 and \
|
||||
classname_matches[0] == classname:
|
||||
cls = classes[classnames.index(classname)].__class__
|
||||
help = cls.class_get_help()
|
||||
# strip leading '--' from cl-args:
|
||||
help = re.sub(re.compile(r'^--', re.MULTILINE), '', help)
|
||||
return [ attr.split('=')[0]
|
||||
for attr in help.strip().splitlines()
|
||||
if attr.startswith(texts[1]) ]
|
||||
return []
|
||||
|
||||
|
||||
def magic_color_matches(self, text): #:str) -> List[str] :
|
||||
""" Match color schemes for %colors magic"""
|
||||
texts = text.split()
|
||||
if text.endswith(' '):
|
||||
# .split() strips off the trailing whitespace. Add '' back
|
||||
# so that: '%colors ' -> ['%colors', '']
|
||||
texts.append('')
|
||||
|
||||
if len(texts) == 2 and (texts[0] == 'colors' or texts[0] == '%colors'):
|
||||
prefix = texts[1]
|
||||
return [ color for color in InspectColors.keys()
|
||||
if color.startswith(prefix) ]
|
||||
return []
|
||||
|
||||
|
||||
|
||||
|
||||
def completions(self, text, offset):
|
||||
"""
|
||||
Returns an iterator over the possible completions
|
||||
|
||||
.. warning:: Unstable
|
||||
|
||||
This function is unstable, API may change without warning.
|
||||
It will also raise unless use in proper context manager.
|
||||
|
||||
Parameters
|
||||
----------
|
||||
|
||||
text:str
|
||||
Full text of the current input, multi line string.
|
||||
offset:int
|
||||
Integer representing the position of the cursor in ``text``. Offset
|
||||
is 0-based indexed.
|
||||
|
||||
Yields
|
||||
------
|
||||
:any:`Completion` object
|
||||
|
||||
|
||||
The cursor on a text can either be seen as being "in between"
|
||||
characters or "On" a character depending on the interface visible to
|
||||
the user. For consistency the cursor being on "in between" characters X
|
||||
and Y is equivalent to the cursor being "on" character Y, that is to say
|
||||
the character the cursor is on is considered as being after the cursor.
|
||||
|
||||
Combining characters may span more that one position in the
|
||||
text.
|
||||
|
||||
|
||||
.. note::
|
||||
|
||||
If ``IPCompleter.debug`` is :any:`True` will yield a ``--jedi/ipython--``
|
||||
fake Completion token to distinguish completion returned by Jedi
|
||||
and usual yap_ipython completion.
|
||||
|
||||
.. note::
|
||||
|
||||
Completions are not completely deduplicated yet. If identical
|
||||
completions are coming from different sources this function does not
|
||||
ensure that each completion object will only be present once.
|
||||
"""
|
||||
self.matches = []
|
||||
prolog_res = self.shell.yapeng.goal(completions(text, self),True)
|
||||
if self.matches:
|
||||
return text, self.matches
|
||||
magic_res = self.magic_matches(text)
|
||||
return text, magic_res
|
||||
|
||||
|
||||
|
||||
|
||||
class YAPRun:
|
||||
"""An enhanced, interactive shell for YAP."""
|
||||
|
||||
def __init__(self, shell):
|
||||
self.shell = shell
|
||||
self.yapeng = JupyterEngine()
|
||||
global engine
|
||||
engine = self.yapeng
|
||||
self.query = None
|
||||
self.os = None
|
||||
self.it = None
|
||||
self.shell.yapeng = self.yapeng
|
||||
self._get_exc_info = shell._get_exc_info
|
||||
|
||||
def syntaxErrors(self, text):
|
||||
"""Return whether a legal query
|
||||
"""
|
||||
if not text:
|
||||
return []
|
||||
if text == self.os:
|
||||
return self.yapeng.errors
|
||||
(text,_,_,_) = self.clean_end(text)
|
||||
self.yapeng.goal(errors(self.yapeng,text),True)
|
||||
print( self.yapeng.errors )
|
||||
return self.yapeng.errors != []
|
||||
self.errors = []
|
||||
engine.mgoal(errors(self, line),"user",True)
|
||||
return self.errors != []
|
||||
|
||||
|
||||
def reset(self):
|
||||
@@ -911,7 +496,7 @@ class YAPCompleter(Completer):
|
||||
ensure that each completion object will only be present once.
|
||||
"""
|
||||
self.matches = []
|
||||
prolog_res = self.shell.yapeng.goal(completions(text, self),True)
|
||||
prolog_res = self.shell.yapeng.mgoal(completions(text, self), "user",True)
|
||||
if self.matches:
|
||||
return text, self.matches
|
||||
magic_res = self.magic_matches(text)
|
||||
@@ -940,11 +525,11 @@ class YAPRun:
|
||||
if not text:
|
||||
return []
|
||||
if text == self.os:
|
||||
return self.yapeng.errors
|
||||
return self.errors
|
||||
self.errors=[]
|
||||
(text,_,_,_) = self.clean_end(text)
|
||||
self.yapeng.goal(errors(self.yapeng,text),True)
|
||||
print( self.yapeng.errors )
|
||||
return self.yapeng.errors
|
||||
self.yapeng.mgoal(errors(self,text),"user",True)
|
||||
return self.errors
|
||||
|
||||
def jupyter_query(self, s):
|
||||
#
|
||||
@@ -1027,6 +612,7 @@ class YAPRun:
|
||||
# you can print it out, the left-side is the variable name,
|
||||
# the right side wraps a handle to a variable
|
||||
#import pdb; pdb.set_trace()
|
||||
# #pdb.set_trace()
|
||||
# atom match either symbols, or if no symbol exists, strings, In this case
|
||||
# variable names should match strings
|
||||
# ask = True
|
||||
@@ -1067,9 +653,7 @@ class YAPRun:
|
||||
# except SyntaxError:
|
||||
# preprocessing_exc_tuple = self.shell.syntax_error() # sys.exc_info()
|
||||
cell = raw_cell # cell has to exist so it can be stored/logged
|
||||
self.yapeng.goal(streams(True), True)
|
||||
errors = self.syntaxErrors(raw_cell)
|
||||
for i in errors:
|
||||
for i in self.syntaxErrors(raw_cell):
|
||||
try:
|
||||
(what,lin,_,text) = i
|
||||
e = SyntaxError(what, ("<string>", lin, 1, text))
|
||||
@@ -1095,7 +679,6 @@ class YAPRun:
|
||||
# compiler
|
||||
# compiler = self.shell.compile if shell_futures else CachingCompiler()
|
||||
cell_name = str( self.shell.execution_count)
|
||||
engine.stream_name = cell_name
|
||||
if cell[0] == '%':
|
||||
if cell[1] == '%':
|
||||
linec = False
|
||||
@@ -1124,6 +707,7 @@ class YAPRun:
|
||||
self.shell.displayhook.exec_result = self.result
|
||||
has_raised = False
|
||||
try:
|
||||
self.yapeng.mgoal(streams(True),"user", True)
|
||||
self.bindings = dicts = []
|
||||
if cell.strip('\n \t'):
|
||||
#create a Trace object, telling it what to ignore, and whether to
|
||||
@@ -1148,9 +732,9 @@ class YAPRun:
|
||||
except Exception as e:
|
||||
has_raised = True
|
||||
self.result.result = False
|
||||
self.yapeng.goal(streams(False), True)
|
||||
self.yapeng.mgoal(streams(False),"user", True)
|
||||
|
||||
self.yapeng.goal(ODstreams(False), True)
|
||||
self.yapeng.mgoal(streams(False),"user", True)
|
||||
self.shell.last_execution_succeeded = not has_raised
|
||||
|
||||
# Reset this so later displayed values do not modify the
|
||||
|
Reference in New Issue
Block a user