The predicates in this section deal with MS-Windows `Dynamic Data Exchange' or DDE protocol. (50) A Windows DDE conversation is a form of interprocess communication based on sending reserved window-events between the communicating processes.
See also section 7.4 for loading Windows DLL's into SWI-Prolog.
The DDE client interface allows Prolog to talk to DDE server programs. We will demonstrate the use of the DDE interface using the Windows PROGMAN (Program Manager) application:
1 ?- open_dde_conversation(progman, progman, C). C = 0 2 ?- dde_request(0, groups, X) --> Unifies X with description of groups 3 ?- dde_execute(0, '[CreateGroup("DDE Demo")]'). Yes 4 ?- close_dde_conversation(0). Yes |
For details on interacting with progman, use the SDK online
manual section on the Shell DDE interface. See also the Prolog
library(progman)
, which may be used to write simple Windows
setup scripts in Prolog.
CF_TEXT
data in DDE parlance) representing that data, if the request is
successful. If unsuccessful, Value will be unified with a
term of form
error(<Reason>), identifying the problem. This
call uses SWI-Prolog string objects to return the value rather then
atoms to reduce the load on the atom-space. See section
4.23 for a discussion on this data type.
POKE
command to the server on the specified Item.
Command is passed as data of type CF_TEXT
.
The (autoload) library(dde)
defines primitives to
realise simple DDE server applications in SWI-Prolog. These features are
provided as of version 2.0.6 and should be regarded prototypes. The
C-part of the DDE server can handle some more primitives, so if you need
features not provided by this interface, please study library(dde)
.
+Service(+Topic, +Item, +Value)Service is the name of the DDE service provided (like progman in the client example above). Topic is either an atom, indicating Goal only handles requests on this topic or a variable that also appears in Goal. Item and Value are variables that also appear in Goal. Item represents the request data as a Prolog atom. (51)
The example below registers the Prolog current_prolog_flag/2 predicate to be accessible from other applications. The request may be given from the same Prolog as well as from another application.
?- dde_register_service(prolog(current_prolog_flag, F, V), current_prolog_flag(F, V)). ?- open_dde_conversation(prolog, current_prolog_flag, Handle), dde_request(Handle, home, Home), close_dde_conversation(Handle). Home = '/usr/local/lib/pl-2.0.6/' |
Handling DDE execute
requests is very similar. In this
case the template is of the form:
+Service(+Topic, +Item)
Passing a Value argument is not needed as execute requests either succeed or fail. If Goal fails, a `not processed' is passed back to the caller of the DDE request.