49594233-simeioseis-texnitis-noimosinis

95
ΕΘΝΙΚΟ ΜΕΤΣΟΒΙΟ ΠΟΛΥΤΕΧΝΕΙΟ ΤΜΗΜΑ ΗΛΕΚΤΡΟΛΟΓΩΝ ΜΗΧΑΝΙΚΩΝ ΚΑΙ ΜΗΧΑΝΙΚΩΝ ΥΠΟΛΟΓΙΣΤΩΝ ΤΟΜΕΑΣ ΠΛΗΡΟΦΟΡΙΚΗΣ ΤΕΧΝΗΤΗ ΝΟΗΜΟΣΥΝΗ ΣΥΜΠΛΗΡΩΜΑΤΙΚΕΣ ΣΗΜΕΙΩΣΕΙΣ ΤΙΜΟΣ ΣΕΛΛΗΣ - ΑΡΗΣ ΤΣΩΗΣ

Transcript of 49594233-simeioseis-texnitis-noimosinis

-

PROLOG -

1 : ________________________________________________ 11.1 ________________ 5 1.2 ____________________ 5 1.3 _____________________________________ 6

2 : PROLOG _______________________________________________ 112.1 (unification) ____________________________________________ 14 2.2 PROLOG _____________________ 15 2.3 ________________________ 15 2.4 ___________________________________________ 15 2.5 PROLOG _______________________________ 16 2.6 (Unification) __________________ 18 2.7 SUBGOALS _____________________________________________ 19 2.8 PROLOG; ________________________________________ 19 2.9 PROLOG; _________________________ 21 2.10 PROLOG ____________________________________ 22 2.11 PROLOG____________________________________ 24 2.12 _____________ 29 2.13 ! _______________________________________________ 31

3 - ____________________________________ 373.1 _________________________________________________________ 37 3.2 ________________________________________ 38 3.3 ______________________________ 42 3.4 ________________________ 43 3.5 __________________________________________ 47 3.6 ______________________________ 48 3.7 _____________________________________________ 56 3.8 ___________________ 58 3.9 _____________________________________________ 63

4 : _____________________________ 754.1 _________________________________________________________ 75 4.2 ____________________________________________________________ 75 4.3 ____________________________ 76 4.4 _____________ 79 4.5 ___________________________ 80 4.6 ______________________________ 86 4.7 B ____________________________________________________ 87

(Planning)

1

1 : . , , , . , ( : , , , ) . () (Artificial Intelligence - AI) / . , : , , , . ( ): , , (Herbert Simon). . . (science) (engineering) (Nils Nilsson). . () , () .

1

1

. , . , . , . ; ; ; , , , , . , , : , . , . : . , . . :

2

1

1 (REASONING)

2 ( )

3 (BEHAVIOUR) 1.

4

(cognitive science)

(I/O), . : GPS (General Problem Solver):

. 3. Turing Test. 3 ,

. . . . . : Eliza: Turing Test. : : Eliza: : Eliza: ; .. ..

3

1

Eliza . (pattern matcher) . , if sentence = ..mother.. then respond with Tell me about your family , Eliza . . 2 4. . 2.

. : () : . . : . - . 4.

, .. robot arm. :

4

1

1.1 Puzzle, , . , .. MACSYMA 500 , , , . (expert systems) MYCIN () EL ( ) PROSPECTOR () XCON (hardware configuration) INTELLECT LIFER LOQUI (Learning) - -> .. (block world - ) ROBOT , , , . . , , .

1.2 :5

1

, , : : - .. : Time flies like an arrow : : The spirit is willing but the flesh is weak : vodka !

1.3 Newell & Simon: . . . . ( ) . . . : ; ; (knowledge) ( - belief). ; ;

6

1

..

: ; ;

pixels ;

; (explicit) (implicit) ; : . : . 5 17 3 . . ; (. ) ( ). . (17 5) 6000 . , (6 3) , 20 . 17-5=12 4 , , 2 ! ; (Problem Solving) - (Search) (Logic) - (Theorem Proving) (Planning) (Knowledge Representation) (Machine Learning) (Natural Language Understanding) (Neural Networks)

7

1

LISP, PROLOG. : ( ). ( ) ; . ( ). , , ( ). . ; . . , . . ; , , ( ) . , . ; ( , , )

8

1

. . . ' . : , , . "" ; 1. ( , , ...) "" . 2. (search) . . . "crack" (password) . 8 . (~708) . (.. ) ( "crack" , ). . . , , 9

1

. 3. (representation) . . Fibonaci ( Pascal C) ' GOTO ( Pascal Fibonaci if ... goto ....). . 1 ' . . 4. (planning) , . . .

10

2

2 : PROLOG PROLOG . .. . married (,). (facts). child (,). child (,). child (,). child (,). male (). male (). female (). married (, ). child (,). child (, ). child (, ). child (,). male (). male (). female (). married (, ).

married (, ). married (, ). : ?- child (, ). YES ?- child (, ). NO ?- child (X, ). X= ?- child (,X). X= ; X= ?- child (X,Y). X= Y= ; X= Y= ;

11

2

?- child (X,), child (,Y). X= Y= ; (rules) / . grandchild (X,Y) :- child (X,Z), child (Z,Y). 1: parent (X,Y) :- child (X,Y). mother (X,Y) :- parent (X,Y), female (X). father (X,Y) :- parent (X,Y), male (X). sibling (X,Y) :- child (X,Z), child (Y,Z), notequal (X,Y). sister (X,Y) :- sibling (X,Y), female (X). 2: related (X,X). related (X,Y) :- married (X,Y). related (X,Y) :- child (X,Z), related (Z,Y). related (X,Y) :- child (Y,Z), related (Z,X). . (goal). , . (verifier goals) (finder goals). - . : : : ?- child (,). ?- child (X,Y).

(recursive rules) PROLOG. D D P , : descendant (D,A) :- child (D,A). descendant (D,A) :- child (D,P), descendant (P,A).

12

2

: uncle (U,N) :- child (N,P), sibling (P,U), male (U). uncle (U,N) :- child (N,P), sibling (P,Q), married (Q,U), male (U). H PROLOG : = + . . PROLOG PROLOG. PROLOG : . : grandchild (X,Y) :- child (X,Z), child (Z,Y). () , . () Y. : literal : P (t1, t2, ,tn) P ti (predicate) n (terms) . , m (function) f(x1, x2, ,xm). (substitution) : (x1=t1, x2=t2, , xN=tN) xi= ti= .

( - executor)

13

2

PROLOG Horn Clauses P Q1, Q2, Q3, ., Qn. P Qi literals. P (consequent) (antecedents). clause (assertion). clause (goal). L literal L L L xi ti : = {X=son(), Y=U} L = child(X,Y) L = child(son(), U) L = child(son(X), son()) L = child(son(son()), son())

2.1 (unification) (unifies) literals L1 L2 L1 = L2. .. L1=child(X,Y) L2=child(son(),U) ={ = son(),Y=U} L1 = L2 = child(son(),U). () , . : parent(X,Y) unify parent(son(X), X)

: parent(X,Y) unify parent(son(Z), Z).

14

2

2.2 PROLOG PROLOG (firstorder predicate logic formulas) quantifiers, Horn clause , . .

2.3 f (g (Ab, 2), 100) s (np (art (Ta), n ()), vp (v() n ()))

f

s

g

100

np

vp

Ab

2

art

n

v

n

2.4 .. Pascal type person = record name: string; address: string; birth: array[1..3] of integer; sex: boolean end PROLOG person(name(N), address(A), birth(D.M.Y), sex(S)).

15

2

2.5 PROLOG (dot) . .. (a.(b.(c.d))) a . b . c . d . nil [a,b,c,d] nil ab.nil nil.nil.nil (a.nil) . (b.nil) . nil ((ab.nil) . nil) . nil) 1. nil nil 2. , (head, tail) head, tail . .. total (nil, 0). total (Head.Tail, T) :- total (Tail, Subtotal), T=Head+Subtotal. total(L,N) . : length (L,N) length (nil,0). length (Head.Tail,N) :- length (Tail,M), N=M+1. length ([],0). length ([H | Tail], N) :- length (Tail,M), N=M+1. [] [ab] [ [], [] ] [ [a],[b] ] [ [ [ab] ] ]

16

2

: member (X,L) member (X, [X | Tail]). member (X, [Head | Tail]) :- member (X,Tail). : pick (X,L1,L2) pick (X, [X | Tail], Tail). pick (X, [Head | Tail], [Head | Rem]) :- pick (X, Tail, Rem). : append (L1,L2,L3) ( L1 L2 L3) append (nil, L, L). append ([H | T], L, [H | P]) :- append (T,L,P). : ?- append (L, L, [a,b,d,a,b,d]). L = [a,b,d] ?- append ([a,b], [c], L3). L3 = [a,b,c] ?- append (X, [b,c], [a,d,b,c]). X = [a,d]. input output . : QUICKSORT 1. qsort ([],[]). 2. , Head . qsort ([ H | T ], S) :partition(H,T,L1,L2), qsort (L1,S1), qsort (L2,S2), append (S1, [H | S2], S).

17

2

partition (P, [H | T], [H | L1], L2) :- gt (H,P), partition (P,T,L1,L2). partition (P, [H | T], T1, [H | L2]) :- le (H,P), partition (P,T,L1,L2). partition ( _ , [], [], []). partition P (pivot) Head L. L1 L2. H

2.6 (Unification) , ( unifiers); 1. literals (L1 clause C1 L2 clause C2) . 2. unifier literals L1 = P(t1, t2, ., tk) L2 = P(t1, t2, ., tk) t1 t1, t1 t2, ., tk tk . 3. t1 t2 : () () t1 ( t2) : =t2 t1 = f (q1, q2, , qm) t2 = f (r1, r2, , rm)

q1 r1, q2 r2, . . : L1 = parent (X,Y) L2 = parent (Y,son(Z)) parent (W,son(Z)) = {X=W, Y=son(Z)}

18

2

2.7 SUBGOALS goal :- A1, A2, , Ai, , Am (m >=1) clause B :- B1, B2,., Bk . goal unifier Ai B :- A1, A2, , B1, B2,., Bk, , Am (m >=1) : :- parent (X, ), parent (, Y) parent(U,V) :- spouse(U,W), parent (W,V) {U=, V=Y}

:- parent (X, ), spouse(,W), parent (W,V).

2.8 PROLOG; . : P, goal G, R PROLOG : 1. G 2. goal 3. A1, A2, , Am, , An , R Am. T A :- B1, B2, ., Bl Am A , (A1,,Am-1, B1, ,Bl, Am+1, , An) A1, A2, , An. 4. clause ( ) .

19

2

: r1 r2 descendant (D,A) :- child (D,A). descendant (D,A) :- child (D,P), descendant (P,A).

child (,). child (,). child (,). child (,). child (,). : ?- descendant (, )

descendant (, )

r1

r2

child (, )

child (, ) descendant (X, )

X= [ ]

r1

child (, ) child (, )

[ ]

20

2

2.9 PROLOG; : LEFT TO RIGHT TOP TO BOTTOM PROLOG ! : (1) (2) (3) (4) : p(a,b). p(c,b). p(X,Z) :- p(X,Y), p(Y,Z). p(X,Y) :- p(Y,X). :- p(a,c):-p(a,c) 3 p(a,Y), p(Y,c) 1 p(b,c) 3 p(b,Y), p(Y,c) 3 4 ... 4 p(c,b) 2 [] 3 4 ... ... 3 4 p(a,Y1), p(Y1,Y), p(Y,c) ... p(Y,a),p(Y,c) ... 4 p(c,a) ...

p(b,Y'),p(Y',Y),p(Y,c)

...

!

21

2

2.10 PROLOG Goal literals left-to-right goal literal, top-to-bottom clause (consequent) (unifies). , , body clause goal list. , goal backtracking (. goal literals goal list). goals . : ;

: walk pushbox climbbox reach

22

2

4-tuple: (, , , )

(states)

: = = (pm, pb, bbox bgrasp?) pm = position of monkey - pb = position of box - bbox = boolean, monkey on box? - ; bgrasp? = boolean, monkey has banana? - ; pi {X | X Room} bi {yes,no} = (atdoor, atwindow, no, no) = { ( _ , _ , _ , yes) }

PROLOG state (X, Y, Z, W) move (S1, M, S2) S1 = M = S2 = : move (state (middle, middle, yes, no), reach, state (middle, middle, yes, yes)). move (state (P, P, no, H), climbbox, state (P, P, yes, H)). move (state (P1, P1, no, H), pushbox(P1,P2), state (P2, P2, no, H)). move (state (P1, B, no, H), walk(P1,P2), state (P2, B, no, H)). :

23

2

canget (state ( _ , _ , _ , yes)). canget (S1) :- move (S1, M, S2), canget (S2). : ?- canget (state (atdoor, atwindow, no, no)).

state (atdoor, atwindow, no, no)

reach

climb

push

walk(atdoor,P2)

no

no

no

state (atdoor, atwindow, no, no) reach

no

climb

backtrack

push (P2, P2')

state (atdoor, atwindow, yes, no)

state (atdoor, atwindow, no, no)

reach climb

walk push

reach

climb

no

no

no

no

no

state (P2', P2; yes, no)

reach P2' = middle

state (middle, midle, yes, yes)

2.11 PROLOG Prolog . . Prolog ISO. Prolog . %

24

2

. /* */ . . : % this is a comment that ends at the end of the line /* this is a multiple line comment *-()-()-/-/-()-()-* ..that ends here */ () (atoms) Prolog. : (a..z) . '_' (underscore) . . : hello, mother, f15_x7_sky, 'don''t panic', m88, 'Athens'.

'this is an atom',

Prolog . . : 123, 12.4, Prolog . '_'. , (..) '_' , '_'. '_' . 814, -0.01, -93, 97.0

25

2

: X, Fire_987, Prolog , literal. ( ) . .. halt. . : . ( . ,. , , . ). : child(oidipous, iokasti) male(oidipous) bought(Student, book(title(Programming in Prolog),author(W.F.C. C.S.M.))) Unusual name(X, 98,0.09876) . .. , , [ , ] |. [] ( nil). . . : [] nil [] John, _big_variable, X13, _98765

26

2

.(a, []) .(a, b)

(a.nil) (a.b)

[a] [a | b] [a,b] [a,b | c]

.(a, .(b, [])) (a.(b.nil)) .(a, .(b, c)) (a.(b.c))

, , , . : [1, 2, 74, hello, 93, male(oidipous)] [this is the head of the list, this list is a list of atoms , last atom] [ [a1,a2,[ b1 | b2] ],c2,c3 | [d1,d2]] ((a1.(a2.((b1,b2).[]))).(c2.(c3.(d1.(d2.[]))))) . Prolog . . = =(,) . . 2*7+3 +(*(2,7),3)) *(2,+(7,3)). : x1 :- x2 x;y x,y x1 = x2 x1 \= x2 x1 == x2 x1 \== x2 x1 is x2 x1 =:= x2 . 1200 1100 1000 700 700 700 700 700 700 x2 x1 (Horn Cause). x OR y ( x y) x AND y ( x y) x1 x2 x1 x2 x1 x2 x1 x2 x1 x2 x1 .

27

2

x2 x1 =\= x2 x1 < x2 y+x y*x y // x y mod x 700 700 500 400 400 400 . x1 . x2 x1 x2 ( >, ==) x1 x2 ( x - y) y x ( y / x ) y x y x

: 10 + 20 X is 30 + 4 * 4 / 9.5 30*2+5=:=65 85//2=\=42.5 30*2+5\==65 a(X,L):- b(X,Z), c(Z,L) a(X) = a(3) b(3,4) \= b(3,5) - (, , , ) . . 2(+)2 . . AND . . . true/0 , . (: true/0 true 0 )

28

2

false/0 (backtracking). repeat/0 . repeat goal literal repeat repeat. Prolog repeat ( ) goal literal repeat. repeat : repeat. repeat :- repeat. ! ( cut) . (side effects). ! goal literal ! . cut .

2.12 X,Y X;Y (X.Y) X=Y X\=Y X==Y X\==Y var(X) nonvar(X) atom(X) integer(X) float(X) var(X) [: real(X)] X Y X { : [|] }

29

2

atomic(X) name(A,L)

L .

! repeat true false not(X) call(X) halt X is Y X+Y X-Y X*Y X/Y // X mod Y XY X =< Y X >= Y X =:= Y X =\= Y + - *

( : cos, sin, abs, log, ...) - get0(X) get(X) read(X) put(X) nl . ASCII >=32. X . .

30

2

tab(X) write(X) display(X) see(X) seeing(X) seen tell(X) telling(X) told

. . . . ( user ) . . . . .

asserta(X) assertz(X) retract(X) functor(T,F,N) arg(N,T,A) X=..L . . . T F . - . L . consult(X) reconsult(X) - . . - . . listing listing(A)

2.13 ! ! ( cut) Prolog. .

31

2

: A :- B, C , D. :- E, F. B, C D E F. (goal) Prolog1 A B, C, D E F. B, C, D, E, F . Prolog . , C D. Prolog (backtracking point) ( E F). . : B :- B1. B :- B2. . Prolog B1 . 1 , . Prolog, , C D. C D . D Prolog (backtrack) . B2. 2 E F. C !. : A :- B, ! , D. A :- E, F.

32

2

Prolog . , Prolog 1. B1 . Prolog !. . !. . , D B2, E F. ! ( !) ! . !. ! . ! . . ! : . sum_to(, S) : sum_to(1,1) :- !. sum_to(,S) :- = - 1 , sum_to(, R) , S=R + M. 1 . ! 1 1 1 . ,

1

: Prolog Prolog

33

2

. ! sum_to(3,7) . IF THEN ELSE !. IF THEN ELSE A :- B, ! , C. A :- D. C D. ! C D. . . , , . . : (FamilyMembers, Income, Grade, Athens, Money) :- B(FamilyMembers, ncome, X), C(Grade,Y), Money = X * Y * 1.7. (FamilyMembers, Income, Grade, Patra, Money) :- B(FamilyMembers, ncome, X), C(Grade,Y), Money = X * Y * 1.2. (FamilyMembers, Income, Grade, Larisa, Money) :- B(FamilyMembers, Income, X), C(Grade,Y), Money = X * Y * 3.7. . , (Grade) 7, . . ! fail

34

2

. 7, . (FamilyMembers, Income, Grade, City, Money) :- Grade < 7.0, !, fail. (FamilyMembers, Income, Grade, Athens, Money) :- B(FamilyMembers, Income, X), C(Grade,Y), Money = X * Y * 1.7. (FamilyMembers, Income, Grades, Patra, Money) :- B(FamilyMembers, Income, X), C(Grade,Y), Money = X * Y * 1.2. (FamilyMembers, Income, Grades, Larisa, Money) :- B(FamilyMembers, Income, X), C(Grade,Y), Money = X * Y * 3.7. . Grade < 7.0 ! . !. fail . . ! . ! .

35

3

3 - 3.1 . ( ) . , . . 2 () 100 . 1 1 40 . 4 10000 2 45 . 8 , 3 . , , . , , . 8 . , . . . - .

37

3

. , , . , .

3.2 (missionaries & cannibals) 3 3 . 2 . : . , . . .A B

canniba l

canniba l

canniba l

missionar y missionar y

missionar y

8 (8 puzzle) 3 x 3 (9 ). 1 8. .

38

3

: . :

1 8 7

2 6

3 4 5

:

2 1 7

8 6

3 4 5

(block world) 3 : , B, C. C B . ( ). . C , B C .

A C B A B C

39

3

(Traveling Salesman Problem - TSP) . . . , .

C

C1 C2 C3 C4

C5

BC6 C7 C9 C10 C8

FC12 C11

AC14

C13

DC15

E

12 (12 coins) 12 ( ). 3 . . .

40

3

(Road-map) , , .

50

150 141 197 100 210

144 120 80 60 26 40

60 80 92

120

140 100 45 80

212

90

80

75

8 (8 queens) 8 . . , , . : 2 .

41

3

3.3 . . (.. 8 ). () (.. ). . , , . . . . .

42

3

. , . (.. , ) . . , . . .

3.4 : 1. 2. 3. 4. 5. 4 . . . , . , . . . d(s) . . 43

3

. . . . 7 : 3 , 3 1 . . 3 . . . . . . : (x, y, z) : (x=0 x y) (3-x = 0 3-x >= 3-y) . 1: (x, y, ) (x-1, y, B) x > 0. 2: (x, y, ) (x-2, y, B) x > 1. 3: (x, y, ) (x, y1, B) y > 0. 4: (x, y, ) (x, y2, B) y > 1.

44

3

5: (x, y, ) (x-1, y-1, B) x > 0 y > 0. 6: (x, y, B) (x+1, y, A) x < 3. 7: (x, y, B) (x+2, y, A) x < 2. 8: (x, y, B) (x, y+1, A) y < 3. 9: (x, y, B) (x, y+2, A) y < 2. 10: (x, y, B) (x+1, y+1, A) x Val1, ! ; max_to_move(Pos0), Val01, NewN is N - 1, play_at_N_pos(Tail,NewN, Player, NewTail). % All the winning states staticval(state(_,[x,x,x,_,_,_,_,_,_]),V):- !, V=3. staticval(state(_,[_,_,_,x,x,x,_,_,_]),V):- !, V=3. staticval(state(_,[_,_,_,_,_,_,x,x,x]),V):- !, V=3. staticval(state(_,[x,_,_,x,_,_,x,_,_]),V):- !, V=3. staticval(state(_,[_,x,_,_,x,_,_,x,_]),V):- !, V=3. staticval(state(_,[_,_,x,_,_,x,_,_,x]),V):- !, V=3. staticval(state(_,[x,_,_,_,x,_,_,_,x]),V):- !, V=3. staticval(state(_,[_,_,x,_,x,_,x,_,_]),V):- !, V=3. staticval(state(_,[o,o,o,_,_,_,_,_,_]),V):- !, V=1. staticval(state(_,[_,_,_,o,o,o,_,_,_]),V):- !, V=1. staticval(state(_,[_,_,_,_,_,_,o,o,o]),V):- !, V=1.

70

3

staticval(state(_,[o,_,_,o,_,_,o,_,_]),V):- !, V=1. staticval(state(_,[_,o,_,_,o,_,_,o,_]),V):- !, V=1. staticval(state(_,[_,_,o,_,_,o,_,_,o]),V):- !, V=1. staticval(state(_,[o,_,_,_,o,_,_,_,o]),V):- !, V=1. staticval(state(_,[_,_,o,_,o,_,o,_,_]),V):- !, V=1. % else we have a draw staticval(_,2).

lfa-Beta Alfa-Beta . Alfa-Beta MIN-MAX . , : (1, 2, ..., Xk-1, Xk) = MIN (1, 2, ..., Xk-1) i 0