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

183 lines
4.3 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-10-25 00:33:02 +01:00
:- dynamic python_mref_cache/2.
:= 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).
% given an object, detect its len method
python_eval_term(Expression, O) :-
fetch_module(Expression, Module, Exp, MRef), !,
(
atom(Exp)
->
python_access(MRef, Exp, O)
2012-11-27 00:16:34 +00:00
;
Exp = Obj:Method
->
python_access(MRef, Exp, O)
2012-10-26 00:24:07 +01:00
;
functor(Exp, F, _),
python_f(MRef, F, FRef),
2012-11-05 13:49:15 +00:00
python_check_args(FRef, Exp, NExp),
python_apply(FRef, NExp, O)
2012-10-26 00:24:07 +01:00
).
python_eval_term(Obj:Field, O) :-
python_access(Obj, Field, O).
2012-10-25 00:33:02 +01:00
2012-11-05 13:49:15 +00:00
python_check_args(FRef, Exp, NExp) :-
functor(Exp, _, Arity),
arg(Arity, Exp, _=_), !,
fetch_args(FRef, Dict),
Exp =.. [F|LArgs],
match_args(LArgs, Dict, NLArgs, _),
NExp =.. [F|NLArgs].
2012-11-27 00:16:34 +00:00
python_check_args(FRef, Exp, Exp).
2012-11-05 13:49:15 +00:00
fetch_args(FRef, Args) :-
python_import('inspect', M),
python_f(M, getargspec, F),
2012-11-27 00:16:34 +00:00
python_apply(F, getargspec(FRef), Args),
2012-11-05 13:49:15 +00:00
ExtraArgs=t(Args, _, _, _).
match_args([], _, [], ok).
match_args([A=V|LArgs], Dict, [I=V|NLArgs], OK) :-
match_args(LArgs, Dict, NLArgs, ok), !,
( nth0(I, Dict, A) -> true ; throw(type_error(argument(A=V))) ).
match_args([A|LArgs], Dict, [A|NLArgs], not_ok) :-
match_args(LArgs, Dict, NLArgs, _).
2012-10-25 00:33:02 +01:00
python(Obj, Out) :-
python_eval_term(Obj, Out), !.
python(Obj, OArg) :-
python_do_is(Obj, Obj1),
python_is(Obj1, OArg).
python_do_is(A+B, NA+NB) :- !,
python_do_is(A, NA),
python_do_is(B, NB).
python_do_is(A-B, NA-NB) :- !,
python_do_is(A, NA),
python_do_is(B, NB).
python_do_is(A*B, NA*NB) :- !,
python_do_is(A, NA),
python_do_is(B, NB).
python_do_is(A/B, NA/NB) :- !,
python_do_is(A, NA),
python_do_is(B, NB).
python_do_is(A, NA) :-
python_eval_term(A, NA), !.
python_do_is(A, A).
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-11-05 13:49:15 +00:00
python_command('import sys'),
python_command('import inspect').
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).