Agent Programming in Ciao Prolog F. Bueno and the CLIP Group http://www.clip.dia.fi.upm.es/ CLIP Group School of Computer Science Technical University of Madrid (UPM) 2010 (c) CLIP/FIM/UPM, F. Bueno – Agent Programming in Ciao Prolog – 2010
Slide 1 Getting Closer to Agents • Agency from the point of view of a programmer: ⋄ autonomy : state and its encapsulation ⋄ independence : concurrent execution ⋄ reactiveness : message passing – synchronization ⋄ individuality : distributed execution • and, of course: ⋄ reasoning : logic programming! (c) CLIP/FIM/UPM, F. Bueno – Agent Programming in Ciao Prolog – 2010
Slide 2 Global Outline • Ciao Prolog Modules and Packages. • State and Reactivity: Objects. • Agency: Concurrency and Synchronization. • Communicating Agents. • Distribution. • Example Applications and Conclusions. (c) CLIP/FIM/UPM, F. Bueno – Agent Programming in Ciao Prolog – 2010
Slide 3 The Ciao Module System • Ciao implements a module system which meets a number of objectives: ⋄ High extensibility in syntax and functionality. ⋄ Amenability to modular (separate) processing of program components. ⋄ Amenability to (modular) global analysis. ⋄ Greatly enhanced error detection (e.g., undefined predicates). ⋄ Support for meta-programming and higher-order. ⋄ Compatibility with official and de-facto standards. ⋄ Backward compatible with files which are not modules. (c) CLIP/FIM/UPM, F. Bueno – Agent Programming in Ciao Prolog – 2010
Slide 4 Ciao Module System: Strict :- module(aggregates, :- module(update,[update/1]). [ setof/3, bagof/3, :- use_module(aggregates). findall/3 :- use_module(data1,[d/2]). ], :- use_module(data2,[d/2]). [ assertions,isomodes ]). update(X) :- findall(Fi,data_(X,Fi), :- use_module(library(sort)). Fs), :- use_module(library(lists), ... [length/2]). data_(X,Fi):- data1:d(X,Fi). :- meta_predicate data_(X,Fi):- data2:d(X,Fi). bagof(?,goal,?), setof(?,goal,?), % compilation error!! findall(?,goal,?). data_(X,Fi):- data1:e(X,Fi). (c) CLIP/FIM/UPM, F. Bueno – Agent Programming in Ciao Prolog – 2010
Slide 5 Ciao Module System: Locality • Some more specific characteristics: ⋄ Syntax, flags, expansions, etc. are local to modules. ⋄ Compile-time and run-time code is clearly separated (e.g., expansion code is compile-time and does not go into executables). ⋄ “Built-ins” are in libraries and can be loaded into and/or unloaded from the context of a given module. ⋄ Dynamic parts are more isolated. ⋄ Directives are not queries. ⋄ The entry points to modules are statically defined. ⋄ Module qualification used only for disambiguating predicate names. ⋄ All module text must be available or in related parts. • A resulting notion: packages . (c) CLIP/FIM/UPM, F. Bueno – Agent Programming in Ciao Prolog – 2010
Slide 6 Example: Prolog-like Rules with Certainty Factors • foo (c) CLIP/FIM/UPM, F. Bueno – Agent Programming in Ciao Prolog – 2010
Slide 7 Example: Prolog-like Rules with Certainty Factors :- module(certainty_rules,[...], [c_f_rules]). :- use_module(c_factor, [c_factor/3, min_of/2]). success(high) with 0.6 <- publicity(low), success(high,F) :- developing_area(yes), demand(quite), publicity(low,F1), investment(medium). developing_area(yes,F2), demand(quite,F3), investment(medium,F4), opdefs, expansions, ... min_of([F1,F2,F3,F4],F0), c_factor(F0,0.6,F). :- use_module(c_factor, [c_factor/3, min_of/2]). (c) CLIP/FIM/UPM, F. Bueno – Agent Programming in Ciao Prolog – 2010
Slide 8 Packages • Libraries defining extensions to the language. • Made possible thanks to: ⋄ Local nature of syntax extensions. ⋄ Clear distinction between compile-time and run-time code. • Typically consist of: ⋄ A main source file to be included as part of the file using the library, with declarations ( op , new declaration , etc . . . ). ⋄ Code needed at compile time to make translations (loaded by a load compilation module directive). ⋄ Code to be used at run-time (loaded using use module directives). • Examples: dcg (definite clause grammars), argnames (accessing term/predicate arguments by name), iso (ISO-Prolog compatibility package), functions (functional syntax), class (object oriented extension), persdb (persistent database), assertions (to include program assertions), . . . (c) CLIP/FIM/UPM, F. Bueno – Agent Programming in Ciao Prolog – 2010
Slide 9 Example: A Posibilistic Reasoning Model :- use_package(c_f_model). :- use_module(aggregates). :- use_module(c_factor,[min_of/2, success(high) with 0.6 <- max_of/2, c_factor/3]). publicity(low), developing_area(yes), success(X,F) :- demand(quite), findall(Fi,success_(X,Fi), investment(medium). Fs), max_of(Fs,F). :- op(1200,xfx,[(<-)]). :- op( 700,xfx,[with]). success_(high,F) :- :- load_compilation_module( publicity(low,F1), expand_c_factors). developing_area(yes,F2), :- add_sentence_trans(expand/2). demand(quite,F3), :- use_module(aggregates). investment(medium,F4), :- use_module(c_factor,[min_of/2, min_of([F1,F2,F3,F4],F0), max_of/2, c_factor/3]). c_factor(F0,0.6,F). (c) CLIP/FIM/UPM, F. Bueno – Agent Programming in Ciao Prolog – 2010
Slide 10 Fuzzy Prolog :- use_package(fuzzy). small :# fuzzy_predicate([(1,1),(2,1),(3,0.7),(4,0.3),(5,0),(6,0)]). large :# fuzzy_predicate([(1,0),(2,0),(3,0.3),(4,0.7),(5,1),(6,1)]). dice1(X,T) :˜ small(X,T). opdefs, expansions, ... dice2(X,T) :˜ large(X,T). :- use_module(library(faggr)). :- aggr min. :- aggr max. two_dice(X,Y,T):˜ luka :- aggr luka. :- aggr dluka. dice1(X,T1), :- aggr prod. :- aggr dprod. dice2(Y,T2). :- module(faggr,[inject/3, sum(S,T) :˜ all/3], all(max(S),( two_dice(X,Y,_), [clpr,hiord]). X+Y.=.S ), T). (c) CLIP/FIM/UPM, F. Bueno – Agent Programming in Ciao Prolog – 2010
Slide 11 Programming Inference Engines: Meta-Programming • Ciao Prolog has a “builtin” inference engine: unification + resolution (“depth-first search”). • Metaprogramming allows implementing other inference engines: ⋄ Reasoning under uncertainty. ⋄ Different kinds of search methods (e.g. breadth-first, best-first search, hill-climbing, A ∗ ). ⋄ Forward-chaining production systems. ⋄ Frame systems and semantic networks. ⋄ etc. (c) CLIP/FIM/UPM, F. Bueno – Agent Programming in Ciao Prolog – 2010
Slide 12 State and its Encapsulation Using the Module System • State through dynamic predicates (via assert , retract , etc.). • Encapsulation of state through the module system . (Dynamic predicates are local to a module provided they are not exported.) • Each module is the sole responsible for its state. • Example: :- module(deck,[addcard/1,drawcard/1]). :- module(main1,[main/0]). :- use_module(deck). :- dynamic card/2. % initial state main :- card(1,hearts). deck:drawcard(C), card(8,diamonds). deck:addcard(C). addcard(card(X,Y)) :- asserta(card(X,Y)). drawcard(card(X,Y)) :- retract(card(X,Y)). (c) CLIP/FIM/UPM, F. Bueno – Agent Programming in Ciao Prolog – 2010
Slide 13 Replication: From Modules to Objects • Add new/2 : conceptually creates a dynamic “copy” of a module. (But implemented more efficiently!) • Effectively, implements a very useful notion of classes/objects ⋄ Objects allow replicating agents. ⋄ Each object has the behaviour of the class plus its own internal state. • Example: :- class(deck,[addcard/1,drawcard/1]). :- module(main,[main/0]). :- use_class(deck). :- attribute card/2. % initial state main :- card(1,hearts). S1 new deck, card(8,diamonds). S2 new deck, S1:drawcard(C), addcard(card(X,Y)) :- asserta(card(X,Y)). S2:addcard(C). drawcard(card(X,Y)) :- retract(card(X,Y)). (c) CLIP/FIM/UPM, F. Bueno – Agent Programming in Ciao Prolog – 2010
Slide 14 Ciao Instantiable Modules → Classes/Objects • The Ciao approach: classes=modules+instantiation. • Same calling syntax as for the module system. • Visibility controlled by the same rules as in the module system. • Object state is represented by the state of the dynamic predicates. • Additional notions of inheritance. • Implemented basically on top of Standard Prolog. • Similar capabilities in other designs (e.g., SICStus objects). But typically unrelated to the module structure. (c) CLIP/FIM/UPM, F. Bueno – Agent Programming in Ciao Prolog – 2010
Slide 15 Agency: Active Modules / Active Objects • A module/object can be made active by allowing it to run separately. • Modules to which computational resources are attached. • High-level model of client-server interaction. • An active module is a network-wide server for the predicates it exports. • Any module or application can be converted into an “active module” (active object) by using a special compiler option. • Procedures can be imported from remote “active modules” via a simple declaration: :- use active module(Name, [P 1 /N 1 , P 2 /N 2 ,...]). • Calls to such imported procedures are executed remotely in a transparent way. • Several protocols for locating the active modules are provided (in Ciao library actmods ). (c) CLIP/FIM/UPM, F. Bueno – Agent Programming in Ciao Prolog – 2010
Recommend
More recommend