Pengines, the Semantic web and robots!

67 views
Skip to first unread message

Sam Neaves

unread,
Sep 2, 2016, 2:08:19 PM9/2/16
to SWI-Prolog
In yet another toy project, I have successfully installed swi-prolog 7 on a lego ev3, (http://www.lego.com/en-gb/mindstorms/products/mindstorms-ev3-31313)  this is quite fun!

I am using ev3dev http://www.ev3dev.org/ 

My idea is to run pengines on the ev3 and then to be able to send 'plans' or sequences of commands to the ev3 from a remote client machine.
I have run a basic pengine with 3 facts on the machine and can query this remotely however I have yet to control the robot functions.
In order to make simple actions on the robot I have python scripts that interact with the motors and sensors plugged into the ev3

For example:

import ev3dev.ev3 as ev3
from time import sleep
ev3.Sound.speak("hello world").wait()

m= ev3.LargeMotor('outA')
m2= ev3.LargeMotor('outB')
m.run_timed(time_sp=3000, duty_cycle_sp=-50)
m2.run_timed(time_sp=3000, duty_cycle_sp=-50)

print("duty cycle= " + str(m.duty_cycle))

sleep(5)
ev3.Sound.speak("good bye world").wait()

So by running 'python3 hello_world.py ' this makes the ev3 state "hello world" move both motors a little bit and then state "good bye world"

I can call the python script from prolog by using: 

test(Lines):-setup_call_cleanup(
        process_create(
            path(python3),
            ['hello_world.py'],[stdout(pipe(Out))]),
        read_lines(Out,Lines),
        close(Out)).


read_lines(Out, Lines) :-
        read_line_to_codes(Out, Line1),
        read_lines(Line1, Out, Lines).

read_lines(end_of_file, _, []) :- !.
read_lines(Codes, Out, [Line|Lines]) :-
        atom_codes(Line, Codes),
        read_line_to_codes(Out, Line2),
        read_lines(Line2, Out, Lines).

This works fine for controlling the robot locally by querying ?-test(Lines). However it does not work with pengines.

The full server code I have is:

:- use_module(library(pengines)).
:- use_module(library(http/http_unix_daemon)).

:- initialization http_daemon.

test(Lines):-setup_call_cleanup(
        process_create(
            path(python3),
            ['hello_world.py'],[stdout(pipe(Out))]),
        read_lines(Out,Lines),
        close(Out)).


read_lines(Out, Lines) :-
        read_line_to_codes(Out, Line1),
        read_lines(Line1, Out, Lines).

read_lines(end_of_file, _, []) :- !.
read_lines(Codes, Out, [Line|Lines]) :-
        atom_codes(Line, Codes),
        read_line_to_codes(Out, Line2),
        read_lines(Line2, Out, Lines).


my client code:

:- use_module(library(pengines)).

main :-
        pengine_create([
                        server('http://192.168.0.8:6357')
                       ]),
        pengine_event_loop(handle, []).

handle(create(ID, _)) :-
        pengine_ask(ID, test(_), []).
handle(success(_, [test(X)], false)) :-
        writeln(X).
handle(success(ID, [test(X)], true)) :-
        writeln(X),
        pengine_next(ID, []).


The error I have is a sandbox problem.  

Prolog_practise/pengines$ swipl -f client.pl -g "main,halt"
ERROR: Prolog initialisation failed:
ERROR: No permission to call sandboxed `'$current_module'(_G5787,_G5788)'
ERROR: Reachable from:
ERROR:  system:'$file_type_extensions'(A,B)
ERROR:  system:absolute_file_name(A,B,C)
ERROR:  process:absolute_file_name(A,B,C)
ERROR:  user:process_create(A,B,C)
ERROR:  '0e053f84-f83e-41c3-b0e1-a2ac59507ea3':test(A)

What is a good way to solve this problem? Can I change $current_modules sandbox property ? If so how do you do this ? or is that not a good idea? Or how do I use pengine_not_sandboxed/1? 

My thinking at the moment is to have short python scripts for set movements or to get sensor values, these can then be combined by the client to make more complex actions.

That is I could send small scripts or 'plans' to the robot using pengines. I think this is quite cool application.  As I have also succeed in running pengines on a raspberry pi and there is the possibility of using some sensors on that, I think this brings about some interesting opportunities. I could imagine a sensor network of multiple machines with sensors, and some 'mobile agents' . Each running a pengine. A client could query the sensor pengines and send plans to the 'mobile agent' pengines all from one client program. This could in theory be quite simple to program and be very flexible and powerful. 

I would be interested in hearing what people think about this and if there are any links to the literature/web for similar ideas of using prolog/pengines in this manner. 

Questions. 
If I have sensors connected to either a raspberry pi or an ev3 and I want to make querying these possible what do people recommend as names for predicates? get_sensor/1 seems a little imperative.. also what about movements? would something like location1_location2/2 and armposition1_armposition2/2  be a good idea? The python script would then actually make the low level control to make the robot move from one location to another? 

Secondly, clearly a pengine server would normally be able to serve multiple clients at the same time. This would still be fine for reading values of sensors, but if it is a robot it can only be controlled by one person at a time. What would be a good way to manage this?

Thanks for all the cool work into swi-prolog :)

Sam
              

Sam Neaves

unread,
Sep 15, 2016, 7:30:01 AM9/15/16
to SWI-Prolog
So I have built a prototype robot arm which can be controlled with pengines..

http://samneaves.ddns.net/ 

It suddenly starts moving just now seemingly on its own accord, so some one is controlling it ! I dont know how they found it, as it is not finished yet! Anyway this is great and fun, but I will need to secure it somehow, both to limit it so only one person is controlling it at a time and for general security.. so anyone have any ideas what is the best way to do this? 

Sam



Jan Wielemaker

unread,
Sep 15, 2016, 7:40:51 AM9/15/16
to Sam Neaves, SWI-Prolog
Cute! Of course it is a pity to secure it :) Basically, you have some
options:

- Use a firewall
- Bind the server to localhost using the --ip=localost option of
the daemon.pl script
- Load lib/authenticate.pl from SWISH. See comments in the file
how to setup users and passwords.

If you have users and passwords you can also ask for the current user
and you can implement some form of allocation of the robot to a
person. It is of course boring that the whole world can no longer
play together with your robot :(

Cheers --- Jan

On 15/09/16 13:29, Sam Neaves wrote:
> So I have built a prototype robot arm which can be controlled with
> pengines..
>
> http://samneaves.ddns.net/
>
> It suddenly starts moving just now seemingly on its own accord, so some
> one is controlling it ! I dont know how they found it, as it is not
> finished yet! Anyway this is great and fun, but I will need to secure it
> somehow, both to limit it so only one person is controlling it at a time
> and for general security.. so anyone have any ideas what is the best way
> to do this?
>
> Sam
>
>
>
>
> On Fri, Sep 2, 2016 at 7:08 PM, Sam Neaves <sam.n...@gmail.com
> <mailto:sam.n...@gmail.com>> wrote:
>
> In yet another toy project, I have successfully installed swi-prolog
> 7 on a lego ev3,
> (http://www.lego.com/en-gb/mindstorms/products/mindstorms-ev3-31313
> <http://www.lego.com/en-gb/mindstorms/products/mindstorms-ev3-31313>)
> Prolog_practise/pengines$ swipl -f client.pl <http://client.pl> -g
> --
> You received this message because you are subscribed to the Google
> Groups "SWI-Prolog" group.
> To unsubscribe from this group and stop receiving emails from it, send
> an email to swi-prolog+...@googlegroups.com
> <mailto:swi-prolog+...@googlegroups.com>.
> Visit this group at https://groups.google.com/group/swi-prolog.
> For more options, visit https://groups.google.com/d/optout.

Sam Neaves

unread,
Sep 15, 2016, 7:51:43 AM9/15/16
to Jan Wielemaker, SWI-Prolog
Thanks Jan, I will read up on authenticate library.
I think some of the things can be made quite open, like sensors, but the need for some sort of allocation procedure for the robot would need to have some kind of security, even if anyone can sign up to use it :) 

Anne Ogborn

unread,
Sep 16, 2016, 7:23:59 PM9/16/16
to Sam Neaves, SWI-Prolog
Yes, Sam, instead of securing the whole server, you could make a resource allocator.

Instead of safe_primitive-ing move_arm/1 safe_primitive auth_move_arm/1

which checks the IP address from http_current_request and decides if you're the current user.

There used to be a model railroad online. It had a good system - as long as you kept using it, sending a command within nn seconds, you retained control. Some steerable webcams use a similar system.


For your robot, it's probably appropriate that after nn seconds of use it times out and you can't use it for nn seconds to prevent automated users from hogging the bot.

::Annie is virtually in Sam's house, driving the robot around::

Also, you should run pldoc and turn off the localhost only restriction, so we can discover the public interface.

Jan, Torbjorn - couple observations - it might be good to have a current_pengine(-ID) and it'd definitely be good to start thinking about discovery.

Your robot's cool!

This is one of the cooler things I've seen in Prolog in a while. Bravo!

Sam Neaves

unread,
Sep 17, 2016, 7:38:42 AM9/17/16
to Anne Ogborn, SWI-Prolog
Thanks for the encouragement Annie. A pengine controlled train set is also a tempting distraction lol. 

Okay so I am a bit confused by the authentication. 

At the moment the basic site is running from a raspberry pi, all this does is produce a page with an iframe which links to the http://swish.swi-prolog.org/p/embed%20youtube%20test.swinb . The pi also runs an apache reverse proxy so that the site is available on the web. My router forwards port 80 traffic to the pi. The router also forwards port 6357 to the lego brick.

The webcam is handled by a separate pc, which sends the stream to youtube using OBS

So I think I want the authentication to be on the lego brick, so that any application on the web can connect. So I don't think lib/authenticate.pl is the right tool because I am not securing the swish server as that is not under my control and I want to be able to have other prolog applications connect to the robot. 

I am looking at your code here Annie  https://github.com/Anniepoo/swiplwebtut/blob/master/basic_authenticate_example.pl

My current code is at the end of this email.

Would I change for example color/1 to:

color(Lines):-
        http_current_request(Request),
        (   http_authenticate(basic(passwd), Request, _Fields)
->  true
;   throw(http_reply(authorise(basic, harbinger_realm))) %not sure what      harbinger_realm is..
),
        setup_call_cleanup(
        process_create(
            path(python3),
            ['python_ev3/color_test2.py'],[stdout(pipe(Out))]),
        read_lines(Out,Lines),
        close(Out)).

I would have made a password file on the lego brick using:

add_uname_pw(Uname, PW) :-
http_read_passwd_file(passwd, Users),
crypt(PW, Hash),
http_write_passwd_file(passwd, [passwd(Uname, Hash, []) | Users]).

% start the passwd file with user adminuser password adminpw
start_pw_file :-
crypt(adminpw, Hash),
atom_codes(AHash, Hash),
http_write_passwd_file(passwd, [passwd(adminuser, AHash, [])]).

But how would a user send a username and password to the pengine? I am missing something simple? I think I need color/1 to be color_username_password/3? but I don't think that would be securely sent? 

To make the pldoc available I guess I need to run doc_server(A_port_Number, [allow(X)]). on the brick, but what would X be and how would this need to be setup with the router? I am also not sure if the lego brick would cope with running two servers at the same time - its quite low powered. 

Thanks for your help :)


The server code is server.pl

:- use_module(library(pengines)).
:- use_module(library(http/http_unix_daemon)).
:- use_module(pengine_sandbox:test).
:- use_module(library(sandbox)).

:- multifile sandbox:safe_primitive/1.

sandbox:safe_primitive(test:open_claw(_)).
sandbox:safe_primitive(test:close_claw(_)).
sandbox:safe_primitive(test:arm_up(_)).
sandbox:safe_primitive(test:arm_down(_)).
sandbox:safe_primitive(test:centre(_)).
sandbox:safe_primitive(test:face_left(_)).
sandbox:safe_primitive(test:face_right(_)).
sandbox:safe_primitive(test:color(_)).

:- initialization http_daemon.


and test.pl

:- module(test,[centre/1,
                face_left/1,
                face_right/1,
                arm_up/1,
                arm_down/1,
                open_claw/1,
                close_claw/1,
                color/1
              ]).

color(Lines):-setup_call_cleanup(
        process_create(
            path(python3),
            ['python_ev3/color_test2.py'],[stdout(pipe(Out))]),
        read_lines(Out,Lines),
        close(Out)).

centre(Lines):-setup_call_cleanup(
        process_create(
            path(python3),
            ['python_ev3/centre.py'],[stdout(pipe(Out))]),
        read_lines(Out,Lines),
        close(Out)).

face_left(Lines):-setup_call_cleanup(
        process_create(
            path(python3),
            ['python_ev3/face_left.py'],[stdout(pipe(Out))]),
        read_lines(Out,Lines),
        close(Out)).

face_right(Lines):-setup_call_cleanup(
        process_create(
            path(python3),
            ['python_ev3/face_right.py'],[stdout(pipe(Out))]),
        read_lines(Out,Lines),
        close(Out)).
arm_up(Lines):-setup_call_cleanup(
        process_create(
            path(python3),
            ['python_ev3/arm_up.py'],[stdout(pipe(Out))]),
        read_lines(Out,Lines),
        close(Out)).

arm_down(Lines):-setup_call_cleanup(
        process_create(
            path(python3),
            ['python_ev3/arm_down.py'],[stdout(pipe(Out))]),
        read_lines(Out,Lines),
        close(Out)).

open_claw(Lines):-setup_call_cleanup(
        process_create(
            path(python3),
            ['python_ev3/open_claw.py'],[stdout(pipe(Out))]),
        read_lines(Out,Lines),
        close(Out)).
close_claw(Lines):-setup_call_cleanup(
        process_create(
            path(python3),
            ['python_ev3/close_claw.py'],[stdout(pipe(Out))]),
        read_lines(Out,Lines),
        close(Out)).



read_lines(Out, Lines) :-
        read_line_to_codes(Out, Line1),
        read_lines(Line1, Out, Lines).

read_lines(end_of_file, _, []) :- !.
read_lines(Codes, Out, [Line|Lines]) :-
        atom_codes(Line, Codes),
        read_line_to_codes(Out, Line2),
        read_lines(Line2, Out, Lines).

Anne Ogborn

unread,
Sep 18, 2016, 12:25:59 AM9/18/16
to Sam Neaves, SWI-Prolog
Hoping Jan looks over my shoulder as I answer this.

Most of this code is from him.

harbinger_realm is leftover from whatever I was doing. In basic/digest authentication you authenticate onto a 'realm', a set of web pages, so you don't have to answer the password dialog for each page. harbinger_realm is the one you authenticate onto with manual authentication (calling http_authenticate), unguent_realm demos the handy shortcut of passing an option in the handler -
authentication(basic(passwd, unguent_realm))

You want whatever's running the code at the end of the email to allocate use of the robot.

You don't actually need to authenticate. You don't care who'se using the robot. You just care how much a given IP has used the robot, and authorize use of the robot 'fairly'. And allow yourself to always get control of the robot.

I'd do this by adding three more safe primitives.

try_allocate_robot(-Allocate)

Which succeeds, binding success(Until) with Until bound to the utime to which you have the robot (say a minute into the future) if you can get the robot, and to a term already_allocated_til(Until) where Until is the unix time it's allocated until if you fail.
Presumably inside it checks the user's IP address and decides if the user gets to use the robot based on who else is calling allocate_robot, how long the current IP has had it allocated (maybe in the past hour).

You also need an unsafe predicate for yourself that terminates other allocations and gives you the robot. Since it's unsafe, you can only run it from the console, not from pengines.

allocate_robot_to_sam/0

Since some users will indeed be polite and want to release the robot, I'd provide safe predicate

release_robot/0

which deallocates the robot, and safe predicate

as_current_user/2

which runs the metapredicate first argument if it's IP has control of the robot, and the second if not. It's constructed this way so the user can depend on having control of the resource for an entire task. The args should be called with sandbox:safe_call/1

Then, you just need to modify your calls to control the robot. I'll use open_claw as an example.

sandbox:safe_primitive(test: open_claw(_)) :- is_current_user.

Of course you'll have to provide is_current_user/0.

Stupid question - what happens if a user tries to send commands faster than the robot can execute them? Don't you also need some way of blocking?

Jan Wielemaker

unread,
Sep 18, 2016, 6:08:02 AM9/18/16
to Anne Ogborn, Sam Neaves, SWI-Prolog
On 09/17/2016 01:23 AM, 'Anne Ogborn' via SWI-Prolog wrote:
> Jan, Torbjorn - couple observations - it might be good to have a
> current_pengine(-ID) and it'd definitely be good to start thinking
> about discovery.

There is already pengine_self(-ID). You can use pengine_property/2
to unemerate pengines. This predicate however is sandboxed as it
reveals information about the server that yoy may want to keep
secret.

Cheers --- Jan

> Your robot's cool!

I always liked robots :)

Jan Wielemaker

unread,
Sep 18, 2016, 6:26:07 AM9/18/16
to Anne Ogborn, Sam Neaves, SWI-Prolog
On 09/18/2016 06:24 AM, 'Anne Ogborn' via SWI-Prolog wrote:
> Hoping Jan looks over my shoulder as I answer this.

I'm a little unsure about the role of swish.swi-prolog.org in this.
Ideally you want the machine actually controlling the robot to identify
the user. As is, pengines do not have access to the HTTP context that
created them. You can hack that by rolling your own variation of
lib/authenticate.pl that `authenticates' a user as the peer IP address
(remove the pengines:not_sandboxed/2 definition as you do want to keep
the users sandboxed in this case).

But, as I understand it, life is even harder as we are dealing with one
pengine calling another, no? If you want that to work need the public
one to authenticate (by IP) the user and forward this along with the
request to the robot controlling one. You'd alsom need to setup trust
between the two pengine servers, either using authentication or using
a trusted network.

A little picture who is doing what and how the network is (or can be)
organised may help ...

Cheers --- Jan

Sam Neaves

unread,
Sep 18, 2016, 10:38:06 AM9/18/16
to Jan Wielemaker, Anne Ogborn, SWI-Prolog

Stupid question - what happens if a user tries to send commands faster than the robot can execute them? Don't you also need some way of blocking?

Yes this is a problem, I imagined maybe changing user submitted plans.
So say a user submits :

plan1 : arm_up(_), open_claw(_).

This gets changed to:

plan1 :- is_free(true), retractall(is_free(true)), assertz(is_free(false)), arm_up(_),open_claw(_), retractall(is_free(false)), assertz(is_free(true)). 

(this could perhaps be done by another pengine .. )

Then if they tried to execute another plan while that was being executed it would fail. Instead of is_free(true) you could change it to is_free(username). So that you can find out who is using it, and do the allocation time limits etc as you have discussed Annie.  

Its interesting to learn about the security aspects, because even though this is a toy, maybe one day ill make something that is not a toy! 

Jan :For security I imagine that I would have some code on the robot that checks if a user is authorised. I have made a picture: 

https://docs.google.com/drawings/d/1TH635ymoYJ2-jaqujIx3TV0Pm9jpW8s5CAtd2-jttjc/edit?usp=sharing 

I would imagine either having username and passwords on things like open_claw/1 so that it becomes open_claw_username_password/3 so that it would only execute if the username and password matched what was stored on the robot pengine, but as i understand it what is sent to the pengine is not sent securely? Or another way I would imagine would be have a different version of things like pengine_rpc/3 so that it had options for a username and password at that level.  

Sorry i don't fully understand how all of these things are meant to work! 

Jan Wielemaker

unread,
Sep 18, 2016, 11:19:44 AM9/18/16
to Sam Neaves, Anne Ogborn, SWI-Prolog
On 09/18/2016 04:38 PM, Sam Neaves wrote:
>
> Jan :For security I imagine that I would have some code on the robot
> that checks if a user is authorised. I have made a picture:
>
> https://docs.google.com/drawings/d/1TH635ymoYJ2-jaqujIx3TV0Pm9jpW8s5CAtd2-jttjc/edit?usp=sharing

I see. The problem is that although you can make RPC calls from
swish.swi-prolog.org,
it doesn't keep track of identity and as a public server won't. So, if
you want to
do this, I guess you need a SWISH server that does keep track of
identity (and is
otherwise a clone of swish.swi-prolog.org) and a trusted channel between
that
swish server and the robot pengine server (and the same for other clients).

> I would imagine either having username and passwords on things like
> open_claw/1 so that it becomes open_claw_username_password/3 so that it
> would only execute if the username and password matched what was stored
> on the robot pengine, but as i understand it what is sent to the pengine
> is not sent securely? Or another way I would imagine would be have a
> different version of things like pengine_rpc/3 so that it had options
> for a username and password at that level.

Of course you can have the (public) SWISH user send a username and password
as parameters to the pengine_rpc call. Note that these credentials will be
passed through and possibly stored in an insecure environment.

> Sorry i don't fully understand how all of these things are meant to work!

There are zillions of options. Pengines can use ordinary HTTP
authentication,
optionally over HTTPS to interact securely and authenticated.

Security is hard :( By far the simplest solution might be to run SWISH
on the
robot controlling Pengine server and add IP tracking to that.

Cheers --- Jan

Anne Ogborn

unread,
Sep 18, 2016, 3:18:04 PM9/18/16
to Sam Neaves, SWI-Prolog
Thanks for the diagram, it clears things up.

Yes, the authorization control needs to be on the "Robot, pengine server".

I'm still where I was - you have no reason to authenticate anybody or use any security operation.
You'll give the robot to anybody,
as long as nobody who'se used it less is waiting, and as long as you yourself aren't waiting.

All you need to enforce that is to give users persistant names they can't change easily. If you make some register for account, they can automatically register, so an account is no better than being open.

Jan, using the pengine ID seems useless - the abuser can just create a new pengine.

On the other hand, while a user could conceivably find a way to change their IP, IP's are a limited resource not usually available in quantity. Rebooting your DSL modem to keep playing with Sam's robot seems excessive. So, as a first cut, working off the IP seems sane.

Sam Neaves

unread,
Sep 19, 2016, 10:00:31 AM9/19/16
to Anne Ogborn, SWI-Prolog
Okay thanks both, I think I have a better understanding of what I can do now. 
For the moment ill just have some kind of allocation procedure and ill think about security 
more for the next project :)
Reply all
Reply to author
Forward
0 new messages