This repository has been archived on 2023-08-20. You can view files and clone it, but cannot push or open issues or pull requests.
yap-6.3/packages/python/python.pl

229 lines
5.9 KiB
Perl
Raw Normal View History

2012-10-08 23:58:22 +01:00
%%% -*- Mode: Prolog; -*-
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
2012-10-17 10:56:44 +01:00
% Author: Vitor Santos Costa
% E-mail: vsc@dcc.fc.up.pt
% Copyright (C): Universidade do Porto
2012-10-08 23:58:22 +01:00
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%
2012-10-17 10:56:44 +01:00
% This file is part of the YAP Python Interface
2012-10-08 23:58:22 +01:00
% distributed according to Perl Artistic License
% check LICENSE file for distribution license
%
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
/** <module> python
A C-based Prolog interface to python.
@author Vitor Santos Costa
2012-10-17 10:56:44 +01:00
@version 0:0:5, 2012/10/8
2012-10-08 23:58:22 +01:00
@license Perl Artistic License
*/
%%%
2012-10-17 10:56:44 +01:00
:- module(python, [
init_python/0,
end_python/0,
python_command/1,
2012-10-25 00:33:02 +01:00
python_assign/3,
2012-10-26 00:24:07 +01:00
python_import/1,
2012-10-25 00:33:02 +01:00
python/2,
op(100,fy,$),
op(950,fy,:=),
op(950,yfx,:=),
(:=)/2,
(:=)/1
2012-10-17 10:56:44 +01:00
]).
2012-10-25 00:33:02 +01:00
/************************************************************************************************************
Python interface
Data types are
Python Prolog
string atoms
numbers numbers
lists lists
2012-10-26 00:24:07 +01:00
tuples t(...)
2012-10-25 00:33:02 +01:00
generic objs __pointer__(Address)
2012-10-26 00:24:07 +01:00
$var refers to the attribute __main__.var
2012-10-25 00:33:02 +01:00
*************************************************************************************************************/
2012-10-17 10:56:44 +01:00
:- use_module(library(shlib)).
:- use_module(library(lists)).
:- use_module(library(apply_macros)).
:- use_module(library(charsio)).
2012-12-01 14:28:25 +00:00
:- dynamic python_mref_cache/2, python_obj_cache/2.
2012-10-25 00:33:02 +01:00
:= F :- python(F,_).
V := F :- var(V), !, python(F,V).
2012-11-02 22:37:27 +00:00
A := F :- python(F, F1), python_assign(A, F1).
2012-10-25 00:33:02 +01:00
2012-10-26 00:24:07 +01:00
python_import(Module) :-
python_do_import(Module, _).
2012-10-25 00:33:02 +01:00
python_do_import(Module, MRef) :-
python_mref_cache(Module, MRef), !.
python_do_import(Module, MRef) :-
python_import(Module, MRef),
assert( python_mref_cache(Module, MRef) ).
2012-10-26 00:24:07 +01:00
fetch_module(M:E, M1, E1, MRef) :-
atom(M),
python_import(M, MRef0),
module_extend(M, E, M1, E1, MRef0, MRef).
%
% extend the module as much as we can.
%
module_extend(M0, M:E, MF, EF, MRef0, MRef) :-
atom(M),
atom_concat([M0,'.',M], MM),
python_import(MM, MRef1), !,
module_extend(MM, E, MF, EF, MRef1, MRef).
module_extend(M, E, M, E, MRef, MRef).
2012-12-01 14:28:25 +00:00
object_prefix('__obj__'(_)).
object_prefix('$'(_)).
object_prefix('__obj__'(_):_).
object_prefix('$'(_):_).
% from an exp take an object, and its corresponding Prolog representation
descend_exp(V, _Obj, _F, _S) :-
var(V), !,
throw(error(instantiation_error,_)).
descend_exp(Exp, Obj, F, S) :-
object_prefix(Exp),
!,
python_field(Exp, Obj, F, S).
descend_exp(Exp, Obj, F, S) :-
python_mref_cache(_, MObj),
python_field(MObj:Exp, Obj, F, S), !.
descend_exp(Mod:Exp, Obj, F, S) :-
atom(Mod),
python_import(Mod, MObj),
python_field(MObj:Exp, Obj, F, S), !.
python_class(Obj) :-
python_obj_cache(inspect:isclass(_), F),
python_apply(F, isclass(Obj), {}, true).
process_obj(Obj, _, S, Obj, NS, Dict) :-
python_callable(Obj), !,
2012-12-03 12:39:25 +00:00
python_check_args(S, NS, Dict).
2012-12-01 14:28:25 +00:00
process_obj(Obj, _, S, Obj, NS, Dict) :-
python_class(Obj),
descend_object(Obj:'__init__', FObj, _, _),
2012-12-03 12:39:25 +00:00
python_check_args(S, NS, Dict).
2012-12-01 14:28:25 +00:00
python_eval_term(Obj, Obj) :-
var(Obj), !.
python_eval_term('__obj__'(Obj), '__obj__'(Obj)) :- !.
python_eval_term($Name, Obj) :- !,
python_is($Name, Obj).
python_eval_term([H|T], [NH|NT]) :- !,
python_eval_term(H, NH),
python_eval_term(T, NT).
python_eval_term(N, N) :- atomic(N), !.
python_eval_term(Exp, O) :-
descend_exp(Exp, Obj, Old, S), !,
2012-12-03 12:39:25 +00:00
(functor(S, _, 0) ->
O = Obj
;
python_check_args(S, NS, Dict),
python_apply(Obj, NS, Dict, O)
).
2012-12-01 14:28:25 +00:00
python_eval_term(S, O) :-
2012-12-03 12:39:25 +00:00
python_check_args(S, NS, {}),
2012-12-01 14:28:25 +00:00
python_is(NS, O).
2012-10-25 00:33:02 +01:00
python_check_args(Exp, t, {}) :-
2012-12-01 14:28:25 +00:00
Exp =.. [_,V], var(V), !.
python_check_args(Exp, NExp, Dict) :-
2012-11-05 13:49:15 +00:00
functor(Exp, _, Arity),
2012-12-01 14:28:25 +00:00
arg(Arity, Exp, A), nonvar(A), A = (_=_), !,
Exp =.. [_F|LArgs],
match_args(LArgs, NLArgs, Dict),
2012-12-01 14:28:25 +00:00
NExp =.. [t|NLArgs].
python_check_args(Exp, NExp, {}) :-
2012-12-01 14:28:25 +00:00
Exp =.. [F|L],
maplist(python_eval_term, L, LF),
NExp =.. [F|LF].
% in case it is __init__ from __new__
splice_class(Ref, Ref, ArgNames, ArgNames) :- !.
splice_class(_FRef, _Ref, [_|ArgNames], ArgNames).
match_args([], [], {}).
match_args([V=A|LArgs], [], Dict) :- !,
match_named_args([V=A|LArgs], Map),
2012-12-01 14:28:25 +00:00
map_to_dict(Map, Dict).
match_args([A|LArgs], [VA|NLArgs], Dict) :-
2012-12-01 14:28:25 +00:00
python_eval_term(A, VA),
match_args(LArgs, NLArgs, Dict).
2012-12-01 14:28:25 +00:00
match_named_args([], []).
match_named_args([K=A|LArgs], [K=VA|Map]) :-
2012-12-01 14:28:25 +00:00
python_eval_term(A, VA),
match_named_args(LArgs, Map).
2012-12-01 14:28:25 +00:00
map_to_dict([X=V], {X:V}) :- !.
map_to_dict([X=V|Map], {X:V,NDict}) :-
map_to_dict(Map, {NDict}).
match_from_anames([K|_ArgNames], K, VA, [_|Defaults], [VA|Defaults]) :- !.
match_from_anames([_|ArgNames], K, VA, [V|Defaults], [V|NDefaults]) :-
match_from_anames(ArgNames, K, VA, Defaults, NDefaults).
fetch_args(FRef, Args, Kwd, Defaults) :-
FRef = '__obj__'(_), !,
python_mref_cache('inspect', M),
python_obj_cache(inspect:getargspec(_), F),
python_apply(F, getargspec(FRef), {}, ExtraArgs),
ExtraArgs=t(Args, _, Kwd, Defaults).
fetch_args(_, []).
2012-11-05 13:49:15 +00:00
2012-10-25 00:33:02 +01:00
python(Obj, Out) :-
2012-11-27 12:10:41 +00:00
python_eval_term(Obj, Out).
2012-10-17 10:56:44 +01:00
2012-10-08 23:58:22 +01:00
python_command(Cmd) :-
2012-10-25 00:33:02 +01:00
python_run_command(Cmd).
2012-10-08 23:58:22 +01:00
start_python :-
use_foreign_library(foreign(python)),
2012-10-23 10:18:24 +01:00
init_python,
2012-12-01 14:28:25 +00:00
python_main_module(MRef),
assert(python_mref_cache('__main__', MRef)),
2012-11-05 13:49:15 +00:00
python_command('import sys'),
2012-12-01 14:28:25 +00:00
python_import('inspect'),
python_mref_cache(inspect, InspRef),
python_field(InspRef:isclass(_), IsClass, _, _),
assert(python_obj_cache(inspect:isclass(_), IsClass)),
python_field(InspRef:getargspec(_), GetArgSpec, _, _),
assert(python_obj_cache(inspect:getargspec(_), GetArgSpec)),
at_halt(end_python).
2012-10-25 00:33:02 +01:00
add_cwd_to_python :-
2012-10-23 10:18:24 +01:00
unix(getcwd(Dir)),
atom_concat(['sys.path.append(\"',Dir,'\")'], Command),
2012-11-02 22:37:27 +00:00
python_command(Command),
python_command("sys.argv = [\"yap\"]").
2012-10-08 23:58:22 +01:00
% done
2012-10-25 00:33:02 +01:00
python_assign(Name, Exp, '$'(Name)) :-
python_assign(Name, Exp).
2012-10-08 23:58:22 +01:00
:- initialization(start_python, now).
2012-10-25 00:33:02 +01:00
:- initialization(add_cwd_to_python).