prolog - probleme

67
1 Prolog - Probleme Ciubotaru Ilinca – grupa 242 PROIECT 1 1. % Problema discreta a rucsacului % O persoana are un rucsac cu care poate transporta o greutate % maxima G. Persoana are la dispozitie N obiecte si cunoaste pt. % fiecare obiect greutatea si castigul (valoarea) care se obtine % in urma transportului sau la destinatie. Se cere sa se precizeze % ce obiecte trebuie sa transporte persoana astfel incat castigul % sa fie maxim, iar greutatea sa fie egala cu cea precizata. % Apel: % ?-solutieposibila(100,[ob(10,30),ob(28,30),ob(90,2)],R). % ?-solutieposibila(120,[ob(15,30),ob(105,30),ob(90,2),ob(15,5)],R). % predicatul subl() : extrage toate sublistele unei liste. subl([],[]). subl([H|T],[H|T1]):-subl(T,T1). subl(L,[_|T1]):-subl(L,T1). % ob(G,V) - obiectul cu greutatea G si valoarea V suma([],0,0). suma([ob(G,V)|T],R,R1):-suma(T,SGT,SVT),R is G+SGT,R1 is V+SVT. solutieposibila(G,L,R):-subl(R,L),suma(R,SGR,SVR),SGR=G. Interogari: | ?- solutieposibila(120,[ob(15,30),ob(105,30),ob(90,2),ob(15,5)],R) . R = [ob(15,30),ob(105,30)] R=[ob(15,30),ob(90,2),ob(15,5)] R=[ob(105,30),ob(15,5)] | ?- solutieposibila(100,[ob(10,30),ob(28,30),ob(90,2)],R) . R = [ob(10,30),ob(90,2)] ? | ?- solutieposibila(120,[ob(15,30),ob(40,30),ob(90,2),ob(15,5)],R) . R = [ob(15,30),ob(90,2),ob(15,5)] ? | ?- solutieposibila(120,[ob(15,30),ob(40,30),ob(90,2),ob(5,5)],R) .

Upload: pelin-arditi

Post on 03-Apr-2015

1.625 views

Category:

Documents


15 download

DESCRIPTION

Ciubotaru Ilinca (c)

TRANSCRIPT

Page 1: Prolog - Probleme

1

Prolog - Probleme

Ciubotaru Ilinca – grupa 242

PROIECT 1

1. % Problema discreta a rucsacului

% O persoana are un rucsac cu care poate transporta o greutate

% maxima G. Persoana are la dispozitie N obiecte si cunoaste pt.

% fiecare obiect greutatea si castigul (valoarea) care se obtine

% in urma transportului sau la destinatie. Se cere sa se precizeze

% ce obiecte trebuie sa transporte persoana astfel incat castigul

% sa fie maxim, iar greutatea sa fie egala cu cea precizata.

% Apel:

% ?-solutieposibila(100,[ob(10,30),ob(28,30),ob(90,2)],R).

% ?-solutieposibila(120,[ob(15,30),ob(105,30),ob(90,2),ob(15,5)],R).

% predicatul subl() : extrage toate sublistele unei liste.

subl([],[]).

subl([H|T],[H|T1]):-subl(T,T1).

subl(L,[_|T1]):-subl(L,T1).

% ob(G,V) - obiectul cu greutatea G si valoarea V

suma([],0,0).

suma([ob(G,V)|T],R,R1):-suma(T,SGT,SVT),R is G+SGT,R1 is V+SVT.

solutieposibila(G,L,R):-subl(R,L),suma(R,SGR,SVR),SGR=G.

Interogari:

| ?- solutieposibila(120,[ob(15,30),ob(105,30),ob(90,2),ob(15,5)],R) .

R = [ob(15,30),ob(105,30)]

R=[ob(15,30),ob(90,2),ob(15,5)]

R=[ob(105,30),ob(15,5)]

| ?- solutieposibila(100,[ob(10,30),ob(28,30),ob(90,2)],R) .

R = [ob(10,30),ob(90,2)] ?

| ?- solutieposibila(120,[ob(15,30),ob(40,30),ob(90,2),ob(15,5)],R) .

R = [ob(15,30),ob(90,2),ob(15,5)] ?

| ?- solutieposibila(120,[ob(15,30),ob(40,30),ob(90,2),ob(5,5)],R) .

Page 2: Prolog - Probleme

2

no

2.

% Determina daca un nr este sau nu prim.

prim(2) .

prim(3).

prim(P) :-

integer(P) ,

P > 3 ,

P mod 2 =\= 0,

\+ divide(P,3) .

% predicatul divide(P,L) :

% nr P se divide cu un nr F >= L

divide(N,L) :- N mod L =:= 0.

divide(N,L) :-

L * L < N,

L2 is L + 2,

divide(N,L2).

Interogari:

| ?- prim(13) .

yes

| ?- prim(55) .

no

| ?- prim(59) .

yes

| ?- prim(124367) .

yes

| ?- prim(3642156348) .

no

3 .

% Lista de nr prime intr-un anumit interval.

prim(2) .

prim(3).

Page 3: Prolog - Probleme

3

prim(P) :- integer(P) , P > 3 , P mod 2 =\= 0, \+ divide(P,3) .

divide(N,L) :- N mod L =:= 0.

divide(N,L) :- L * L < N, L2 is L + 2, divide(N,L2).

% prime_list(A,B,L) :- L este lista de nr prime P, unde A <= P <= B

prime_list(A,B,L) :- A =< 2, !, p_list(2,B,L).

prime_list(A,B,L) :- A1 is (A // 2) * 2 + 1, p_list(A1,B,L).

p_list(A,B,[]) :- A > B, !.

p_list(A,B,[A|L]) :- prim(A), !, next(A,A1), p_list(A1,B,L).

p_list(A,B,L) :- next(A,A1), p_list(A1,B,L).

next(2,3) :- !.

next(A,A1) :- A1 is A + 2.

Interogari:

| ?- prime_list(6,200,L) .

L = [7,11,13,17,19,23,29,31,37,41|...] ?

| ?- prime_list(1,24,L) .

L = [2,3,5,7,11,13,17,19,23] ?

| ?- prime_list(6,3,L) .

L = [] ?

| ?- prime_list(7,13,L) .

L = [7,11,13] ?

4.

% Conjectura lui Goldbach.

% Conjectura lui Goldbach afirma ca fiecare numar par mai mare ca 2 poate fi scris

% ca suma de 2 nr prime. Exemplu: 28 = 5 + 23 .

% Ea nu a fost demonstrata, dar a fost verificata pana la numere foarte mari.

prim(2) .

prim(3).

prim(P) :- integer(P) , P > 3 , P mod 2 =\= 0, \+ divide(P,3) .

Page 4: Prolog - Probleme

4

divide(N,L) :- N mod L =:= 0.

divide(N,L) :- L * L < N, L2 is L + 2, divide(N,L2).

% goldbach(N,L) :- L este lista de 2 nr prime care insumate, dau N.

goldbach(4,[2,2]) :- !.

goldbach(N,L) :- N mod 2 =:= 0, N > 4, goldbach(N,L,3).

goldbach(N,[P,Q],P) :- Q is N - P, prim(Q), !.

goldbach(N,L,P) :- P < N, next_prim(P,P1), goldbach(N,L,P1).

next_prim(P,P1) :- P1 is P + 2, prim(P1), !.

next_prim(P,P1) :- P2 is P + 2, next_prim(P2,P1).

Interogari:

| ?- goldbach(700,L) .

L = [17,683] ?

| ?- goldbach(4,L) .

L = [2,2] ?

| ?- goldbach(44,L) .

L = [3,41] ?

| ?- goldbach(15,L) .

no

| ?- goldbach(36,L) .

L = [5,31] ?

5.

% Tabela de adevar pentru expresii logice.

% Sa se defineasca predicatele and, or, nand, nor, xor, impl si equ (echivalenta)

% care reusesc sau esueaza in functie de operatori.

% Apoi sa se defineasca predicatul table care construieste

% tabela de adevar pentru o expresie logica data.

not(A) :- \+ A .

and(A,B) :- A, B.

or(A,_) :- A.

or(_,B) :- B.

Page 5: Prolog - Probleme

5

equ(A,B) :- or( and(A,B), and( not(A),not(B) ) ).

xor(A,B) :- not(equ(A,B)).

nor(A,B) :- not(or(A,B)).

nand(A,B) :- not(and(A,B)).

impl(A,B) :- or(not(A),B).

% bind(X) :- da valori de adevar variabilei X

bind(true).

bind(fail).

table(A,B,Expr) :- bind(A), bind(B), do(A,B,Expr), fail.

do(A,B,_) :- write(A), write(' '), write(B), write(' '), fail.

do(_,_,Expr) :- Expr, !, write(true), nl.

do(_,_,_) :- write(fail), nl.

Interogari:

?- table(A,B,and(A,or(A,B))).

true true true

true fail true

fail true fail

fail fail fail

| ?- table(A,B,and(A,B)) .

true true true

true fail fail

fail true fail

fail fail fail

| ?- table(A,B,xor(A,B)) .

true true fail

true fail true

fail true true

fail fail fail

| ?- table(A,B,or(A,B)) .

true true true

true fail true

fail true true

fail fail fail

Page 6: Prolog - Probleme

6

| ?- table(A,B,nor(A,B)) .

true true fail

true fail fail

fail true fail

fail fail true

| ?- table(A,B,equ(A,B)) .

true true true

true fail fail

fail true fail

fail fail true

| ?- table(A,B,impl(A,B)) .

true true true

true fail fail

fail true true

fail fail true

6.

% Se repeta elementele unei liste de n ori.

% Exemplu: repeta([a,b,c],2,L)

% L = ([a,a,b,b,c,c]) .

% predicatul repeta(L1,N,L2) :

% L2 este obtinut prin repetarea elementelor L1 de N ori

% predicatul repeta(L1,N,L2,K) :

% L2 este obtinut din L1 prin repetarea primului element al lui L1 de K ori,

% iar a restului elementelor de N ori.

repeta(L1,N,L2) :- repeta(L1,N,L2,N).

repeta([],_,[],_).

repeta([_|A],N,B,0) :- repeta(A,N,B,N).

repeta([X|A],N,[X|B],K) :- K > 0, K1 is K - 1, repeta([X|A],N,B,K1).

Interogari:

| ?- repeta([a,b,c],2,L) .

L = [a,a,b,b,c,c]

| ?- repeta([a,b,c],3,L) .

L = [a,a,a,b,b,b,c,c,c]

| ?- repeta([a,b,c,d],3,L) .

Page 7: Prolog - Probleme

7

L = [a,a,a,b,b,b,c,c,c,d|...]

| ?- repeta([a,b,c,d],1,L) .

L = [a,b,c,d]

| ?- repeta([a,b,c,d],0,L) .

L = []

| ?- repeta([],3,L) .

L = []

7.

% Extrage o sublista dintr-o lista.

% predicatul extrage(L1,I,K,L2) :

% lista L2 se obtine extragand elementele listei L1 intre indicii I si K

extrage([X|_],1,1,[X]) .

extrage([X|A],1,K,[X|B]) :-

K > 1,

K1 is K - 1 ,

extrage(A,1,K1,B) .

extrage([_|A],I,K,B) :-

I > 1 ,

I1 is I - 1 ,

K1 is K - 1 ,

extrage(A,I1,K1,B) .

Interogari:

| ?- extrage([a,b,c,d,e,f,g,h,i,j],2,5,L) .

L = [b,c,d,e] ?

yes

| ?- extrage([a,b,c,d,e,f,g,h,i,j],2,15,L) .

no

| ?- extrage([a,b,c,d,e,f,g,h,i,j],1,10,L) .

L = [a,b,c,d,e,f,g,h,i,j] ?

yes

| ?- extrage([a,b,c,d,e,f,g,h,i,j],1,6,L) .

L = [a,b,c,d,e,f] ?

Page 8: Prolog - Probleme

8

yes

| ?- extrage([a,b,c,d,e,f,g,h,i,j],6,3,L) .

no

| ?- extrage([a,b,c,d,e,f,g,h,i,j],6,6,L) .

L = [f] ?

yes

8.

% Puzzle aritmetic:

% Dandu-se o lista de nr intregi, sa se gaseasca o modalitate

% de inserarea a operatiilor aritmetice (+,-,*,/) astfel incat

% rezultatul sa fie o ecuatie corecta.

% Exemplu:

% Dandu-se lista de numere [2,3,5,7,11] se poate forma ecuatia

% 2-3+5+7 = 11 sau 2 = (3*5+7)/11 sau inca 10.

% equation(L,LT,RT) :-

% L este lista de numere care sunt frunzele in termenii aritmetici LT si RT,

% termenul stang si drept. Ecuatia va avea acelasi rezultat pt termenul stang si

% pentru cel drept.

equation(L,LT,RT) :-

split(L,LL,RL), % descompune lista L in LL si RL

term(LL,LT), % construieste termenul stang

term(RL,RT), % construieste termenul drept

LT =:= RT. % evalueaza si compara termenii

% term(L,T) :-

% L este lista nr care sunt frunze in termenul aritmetic T, de la stanga la dreapta

term([X],X). % un nr este un termen

% term([X],-X). % minus unar

term(L,T) :- % cazul general: termen binar

split(L,LL,RL), % descompune lista L

term(LL,LT), % construieste termenul din stanga

term(RL,RT), % construieste termenul din dreapta

binterm(LT,RT,T). % construieste prin combinare termenul binar

% binterm(LT,RT,T) :-

Page 9: Prolog - Probleme

9

% T este un termen binar combinat, construit din termenii stang, LT, si drept, RT

binterm(LT,RT,LT+RT).

binterm(LT,RT,LT-RT).

binterm(LT,RT,LT*RT).

binterm(LT,RT,LT/RT) :- RT =\= 0. % evita impartirea la 0

% split(L,L1,L2) :-

% imparte lista L in liste nevide L1 si L2 a.i. concatenate dau L

% append(L1,L2,L3) - concateneaza listele L1 si L2 in L3

append([],L,L).

append([X|L1],L2,[X|L3]) :-

append(L1,L2,L3).

split(L,L1,L2) :- append(L1,L2,L), L1 = [_|_], L2 = [_|_].

% do(L) :- gaseste toate solutiile ecuatiei date

do(L) :-

equation(L,LT,RT),

write(LT),write(' = '),write(RT),

nl,

fail.

do(_).

Interogari:

| ?- do([2,3,5,7,11]) .

2 = 3-(5+(7-11))

2 = 3-(5+7-11)

2 = 3-5-(7-11)

2 = 3-(5+7)+11

2 = 3-5-7+11

2 = (3*5+7)/11

2*(3-5) = 7-11

2-(3-(5+7)) = 11

2-(3-5-7) = 11

2-3+(5+7) = 11

2-(3-5)+7 = 11

2-3+5+7 = 11

yes

| ?- do([2,3,5,7]) .

yes

Page 10: Prolog - Probleme

10

| ?- do([2,3,5]) .

2+3 = 5

yes

| ?- do([23,3,5,21,3,14]) .

23 = 3+5*(21-(3+14))

23 = 3+5*(21-3-14)

23+3 = 5-(21-3*14)

23+3 = 5+(21/3+14)

23+3 = 5-21+3*14

23+3 = 5+21/3+14

23-3 = 5*(21-(3+14))

23-3 = 5*(21-3-14)

23+(3-5) = 21/3+14

23+3*5 = 21+(3+14)

23+3*5 = 21+3+14

23+3-5 = 21/3+14

(23-3)/5 = 21-(3+14)

(23-3)/5 = 21-3-14

23+(3-(5-21)) = 3*14

23+(3-5+21) = 3*14

23+(3*5-21) = 3+14

23+3-(5-21) = 3*14

23+(3-5)+21 = 3*14

23+3*5-21 = 3+14

23+3-5+21 = 3*14

23+(3-(5+21/3)) = 14

23+(3-5-21/3) = 14

23+(3*5-(21+3)) = 14

23+(3*5-21-3) = 14

23+3-(5+21/3) = 14

23+(3-5)-21/3 = 14

23+3*5-(21+3) = 14

23+3-5-21/3 = 14

(23+(3-(5-21)))/3 = 14

(23+(3-5+21))/3 = 14

23+(3*5-21)-3 = 14

(23+3-(5-21))/3 = 14

(23+(3-5)+21)/3 = 14

23+3*5-21-3 = 14

(23+3-5+21)/3 = 14

yes

9.

% Numere

Page 11: Prolog - Probleme

11

% Pe documentele oficiale, cum ar fi cecurile, numerele trebuie

% scrise cateodata si in cuvinte. De exemplu, 175 trebuie scris

% unu-sapte-cinci.

% cuvinte(N) :- scrie numerele in cuvinte

cuvinte(0) :- !, write(zero), nl.

cuvinte(N) :- integer(N), N > 0, cuvinte1(N), nl.

cuvinte1(0) :- !.

cuvinte1(N) :- N > 0,

Q is N // 10, R is N mod 10,

cuvinte1(Q), nr_cuvant(R,RW), liniuta(Q), write(RW).

liniuta(0) :- !.

liniuta(Q) :- Q > 0, write('-').

nr_cuvant(0,zero).

nr_cuvant(1,unu).

nr_cuvant(2,doi).

nr_cuvant(3,trei).

nr_cuvant(4,patru).

nr_cuvant(5,cinci).

nr_cuvant(6,sase).

nr_cuvant(7,sapte).

nr_cuvant(8,opt).

nr_cuvant(9,noua).

Interogari:

| ?- cuvinte(123) .

unu-doi-trei

yes

| ?- cuvinte(0) .

zero

yes

| ?- cuvinte(-56) .

no

| ?- cuvinte(35641) .

trei-cinci-sase-patru-unu

yes

Page 12: Prolog - Probleme

12

| ?- cuvinte(9854030) .

noua-opt-cinci-patru-zero-trei-zero

yes

10.

% Testul de inteligenta al lui Einstein

% Reguli:

% a.Britanicul locuieste in casa rosie

% b.Suedezul are un caine

% c.Danezul bea ceai

% d.Casa verde se afla in stanga casei albe

% e.Proprietarul casei verzi bea cafea

% f.Persoana care fumeaza Pall Mall are o pasare

% g.Proprietarul casei din mijloc bea lapte

% h.Proprietarul casei galbene fumeaza Dunhill

% i.Norvegianul locuieste in prima casa

% j.Fumatorul de Marlboro locuieste langa cel care are o pisica

% k.Proprietarul care are un cal locuiste langa cel care fumeaza Dunhill

% l.Fumatorul de Winfield bea bere

% m.Norvegianul locuieste langa casa albastra

% n.Germanul fumeaza Rothmans

% o.Fumatorul de Marlboro are un vecin care bea apa

% membru(X,L) - X este in lista L

membru(X,[X|_]).

membru(X,[_|T]) :- membru(X,T).

% dreapta(X,Y,L) : Y se afla in dreapta lui X in lista L

dreapta(L, R, [L | [R | _]]).

dreapta(L, R, [_ | Rest]) :- dreapta(L, R, Rest).

% langa(X,Y,L) : X se afla langa Y in lista L

langa(X, Y, List) :- dreapta(X, Y, List).

langa(X, Y, List) :- dreapta(Y, X, List).

einstein(Case, Prop_Peste) :-

=(Case, [[casa, norvegian, _, _, _, _], _, [casa, _, _, _, lapte, _], _, _]),

membru([casa, britanic, _, _, _, rosu], Case),

membru([casa, suedez, caine, _, _, _], Case),

membru([casa, danez, _, _, ceai, _], Case),

dreapta([casa, _, _, _, _, verde], [casa, _, _, _, _, alb], Case),

membru([casa, _, _, _, cafea, verde], Case),

membru([casa, _, pasare, pallmall, _, _], Case),

Page 13: Prolog - Probleme

13

membru([casa, _, _, dunhill, _, galben], Case),

langa([casa, _, _, marlboro, _, _], [casa, _, pisica, _, _, _], Case),

langa([casa, _, _, dunhill, _, _], [casa, _, cal, _, _, _], Case),

membru([casa, _, _, winfield, bere, _], Case),

langa([casa, norvegian, _, _, _, _], [casa, _, _, _, _, albastru], Case),

membru([casa, german, _, rothmans, _, _], Case),

langa([casa, _, _, marlboro, _, _], [casa, _, _, _, apa, _], Case),

membru([casa, Prop_Peste, peste, _, _, _], Case).

Interogare:

| ?- einstein(Case,Prop_Peste) .

Case = [[casa,norvegian,pisica,dunhill,apa,galben],

[casa,danez,cal,marlboro,ceai,albastru],

[casa,britanic,pasare,pallmall,lapte,rosu],

[casa,german,peste,rothmans,cafea,verde],

[casa,suedez,caine,winfield,bere,alb]],

Prop_Peste = german ?

Yes

PROIECT 2 1) MAIMUłA

EnunŃul problemei: Avem o maimuŃã într-o încapere. In mijlocul camerei se afla o banana atârnata de

tavan. MaimuŃa vrea sa ia banana dar nu poate ajunge pana la ea. In camera se mai afla o

cutie, poziŃionatã in dreptul ferestrei pe care maimuŃa o poate folosi. MaimuŃa poate

realiza urmãtoarele acŃiuni :

-sã meargã pe podea

-sã se urce pe cutie

-sã împingã cutia

-sã ia banana dacã stã pe cutie chiar sub bananã

Poate mamuŃa lua banana ?

Codul în Prolog: %starile

stare(la_usa, pe_podea , la_fereastra , nu_are).

stare(la_mijloc, pe_podea, la_fereastra, nu_are).

Page 14: Prolog - Probleme

14

stare(la_fereastra, pe_podea, la_fereastra , nu_are).

stare(la_fereastra, pe_cutie, la_fereastra, nu_are).

stare(mijloc, pe_podea, mijloc, nu_are).

stare(mijloc, pe_cutie, mijloc, nu_are).

stare(mijloc, pe_cutie, mijloc, are).

%miscarile

miscare(stare(mijloc, pe_cutie, mijloc, nu_are),

ia,

stare(mijloc, pe_cutie, mijloc , are)).

miscare(stare(P, pe_podea, P, H),

urca,

stare(P, pe_cutie, P, H)).

miscare(stare(P1, pe_podea, P1, H),

impinge,

stare(P2, pe_podea, P2, H)).

miscare(stare(P1,pe_podea,B,H),

merge(P1,P2),

stare(P2,pe_podea,B,H)).

%poate lua

poate_lua(stare(_,_,_,are)).

poate_lua(Stare1):- miscare(Stare1,M,Stare2),poate_lua(Stare2).

Interogãri:

2)SIMULAREA UNUI AUTOMAT NEDETERMINIST

EnunŃul problemei:

Page 15: Prolog - Probleme

15

Se dã un automat nedeterminist reprezentat prin stãri şi tranziŃii , şi un şir . Se cere sã

se verifice dacã şirul respectiv va fi acceptat sau nu de cãtre automat . Automatul dat va

accepta un şir dacã se terminã cu literele “ab” şi il respinge în caz contrar.

Codul în Prolog:

%reprezentarea automatului

final( s3).

trans( s1, a, s1).

trans( sl, a, s2).

trans( s1, b, s1).

trans( s2, b, s3).

trans( s3, b, s4).

nul( s2, s4).

nul( s3, s1).

%acceptarea

accept( S, [ ] ) :-final( S ).

accept( S, [ X | Rest ] ):-

trans( S, X, S1),

accept( S1, Rest).

accept( S, String) :-

nul( S , S1 ),

accept( S1, String).

Interogãri:

Page 16: Prolog - Probleme

16

3)PLANIFICAREA CALATORIILOR

EnunŃul problemei: Avem o baza de cunoştinŃe care reŃine zborurile de pe un aeroport. Se cere ca

programul nostru sã rãspundã la urmãtoarele întrebãri:

-In ce zile ale sãptãmânii existã zbor direct între Londra şi Bucureşti?

-Cum se poate ajunge din Bucureşti în Roma, joia?

-Vrea sã cizitez Milan, Bucureşti si Viena cu plecare din Londra marŃi si revenirea în

Londra vineri. In ce ordine ar trebui sa vizitez orasele astfel încât sã nu am mai mult de

un zbor pe zi?

Codul în Prolog:

%rutele zborurilor

:-op(50,xfy,:).

zbor( Loc1, Loc2, Ziua, Fnum, Plec, Sos) :-

tabel_timp( Loc1 , Loc2, Lista_zbor),

Page 17: Prolog - Probleme

17

membru( Plec / Sos / Fnum / Lista_zile , Lista_zbor),

ziua_zbor( Ziua, Lista_zile).

membru( X, [X|L] ).

membru( X, [Y|L] ) :- membru( X, L).

ziua_zbor( Ziua, Lista_zile) :-

membru( Ziua, Lista_zile).

ziua_zbor( Ziua, mereu) :-

membru( Ziua, [lu,ma,mi,jo,vi,sa,du] ).

ruta( P1, P2, Ziua, [P1-P2 : Fnum : Plec] ) :-

zbor( P1, P2, Ziua, Fnum, Plec, _).

ruta( P1, P2, Ziua, [P1-P3 : Fnum1 : Plec1 | Ruta ]):-

ruta( P3, P2, Ziua, Ruta),

zbor( P1, P3, Ziua, Fnum1, Plec1,Sos1),

timpplec( Ruta, Plec2),

transfer( Sos1, Plec2).

timpplec( [P1-P2 : Fnum : Plec | _ ], Plec).

transfer( Ore1 : Min1, Ore2 : Min2) :-

60 * (Ore2 - Ore1) + Min2 - Min1 >= 40.

%baza de date a zborurilor

tabel_timp( roma, londra,

[ 9:40 / 10:50 / ba4733 / mereu,

13:40 / 14:50 / ba4773 / mereu,

19:40 / 20:50 / ba4833 / [lu,ma,mi,jo,vi,du] ] ).

tabel_timp( londra, roma,

[ 9:40 / 10:50 / ba4732 / mereu,

11:40 / 12:50 / ba4752 / mereu,

18:40 / 19:50 / ba4822 / [lu,ma,mi,jo,vi] ] ).

tabel_timp( londra, bucuresti,

[ 13:20 / 16:20 / ju201 / [vi],

13:20 / 16:20 / ju213 / [du] ] ).

tabel_timp( londra, viena,

[ 9:10 / 11:45 / ba614 / mereu,

14:45 / 17:20 / sr805 / mereu ] ).

tabel_timp( londra, milan,

Page 18: Prolog - Probleme

18

[ 8:30 / 11:20 / ba510 / mereu,

11:10 / 13:50 / az459 / mereu ] ).

tabel_timp( bucuresti, viena,

[ 11:30 / 12:40 / ju322 / [ma,jo] ] ).

tabel_timp( bucuresti, londra,

[ 11:10 / 12:20 / yu200 / [vi],

11:25 / 12:20 / yu212 / [du] ] ).

tabel_timp( milan, londra,

[ 9:10 / 10:00 / az458 / mereu,

12:20 / 13:10 / ba511 / mereu ] ).

tabel_timp( milan, viena,

[ 9:25 / 10:15 / sr621 / mereu,

12:45 / 13:35 / sr623 / mereu ] ).

tabel_timp( viena, bucuresti,

[ 13:30 / 14:40 / yu323 / [ma,jo] ] ).

tabel_timp( viena, londra,

[ 9:00 / 9:40 / ba613 / [lu,ma,mi,jo,vi,sa],

16:10 / 16:55 / sr806 / [lu,ma,mi,jo,vi,du] ] ).

tabel_timp( viena, milan,

[ 7:55 / 8:45 / sr620 / mereu ] ).

del(X,[X|T],T).

perm([],[]).

del(X,[Y|T],[Y|T1]):-del(X,T,T1).

insert(X,L,L1):-del(X,L1,L).

perm([X|L],P):-perm(L,L1),insert(X,L1,P).

Interogãri:

Page 19: Prolog - Probleme

19

Page 20: Prolog - Probleme

20

4) PROBLEMA CELOR 8 DAME

EnunŃul problemei: Avem 8 dame şi trebuie sã le aşezãm pe o tablã de sah astfel încât sã nu se atace între

ele.

Codul în Prolog:

solutie( [] ).

solutie( [ X/Y | Altele] ) :-

solutie( Altele),

membru( Y, [1,2,3,4,5,6,7,8] ),

nu_ataca( X/Y, Altele).

nu_ataca( _, [] ).

nu_ataca( X/Y, [X1/Y1 | Altele] ):-

Y=\=Y1 ,

Y1-Y =\= X1-X,

Y1-Y =\= X-X1,

Y-Y1 =\=X1-X,

Page 21: Prolog - Probleme

21

Y-Y1 =\= X-X1,

nu_ataca( X/Y, Altele).

membru( X, [ X|L ] ).

membru( X, [ Y|L ] ):- membru( X, L).

template( [ 1/Y1 , 2/Y2 , 3/Y3 , 4/Y4 ,5/Y5 , 6/Y6 , 7/Y7, 8/Y8 ] ).

Interogãri:

.................

5)BUBBLESORT

Enuntul problemei: Am o listã de întregi şi vreau sã o sortez folosind interschimbãri.

Page 22: Prolog - Probleme

22

Codul în Prolog:

bubblesort(Lista, Sortat):- schimb(Lista,Lista1),!,

sort(Lista1,Sortat).

bubblesort(Sortat,Sortat).

schimb([X,Y|Rest],[Y,X|Rest]):-X>Y.

schimb([Z|Rest],[Z|Rest1]):-schimb(Rest,Rest1).

Interogãri:

6)QUICKSORT

EnunŃul problemei: Se dã o listã de întregi şi se cere sã se sorteze crescãtor.

Codul în Prolog:

quicksort( [] , [] ).

quicksort( [ X|Tail], Sortat) :-

desp( X, Tail, Mic, Mare),

quicksort( Mic, Sortatmic), quicksort( Mare, Sortatmare),

conc( Sortatmic, [X | Sortatmare], Sortat).

desp( X, [], [], [] ).

desp( X, [Y | Tail], [Y|Mic], Mare) :-

( X > Y), !,

desp( X, Tail, Mic, Mare).

desp( X, [ Y | Tail], Mic, [Y | Mare] ) :-

desp( X, Tail, Mic, Mare).

conc( [], L, L).

conc( [ X|L1 ], L2, [ X|L3 ] ) :-

conc( L1, L2, L3).

Page 23: Prolog - Probleme

23

Interogãri:

7) DERIVARE

EnunŃul problemei: Se dã o expresie si se cere sã se deriveze.

Codul în Prolog:

d(U+V,X,DU+DV) :-!,

d(U,X,DU),

d(V,X,DV).

d(U-V,X,DU-DV) :- !,

d(U,X,DU),

d(V,X,DV).

d(U*V,X,DU*V+U*DV) :-!,

d(U,X,DU),

d(V,X,DV).

d(U/V,X,(DU*V-U*DV)/(^(V,2))) :-!,

d(U,X,DU),

d(V,X,DV).

d(^(U,N),X,DU*N*(^(U,N1))) :- !, integer(N),

N1 is N-1,

d(U,X,DU).

d(-U,X,-DU) :- !,

d(U,X,DU).

d(exp(U),X,exp(U)*DU) :-!,

d(U,X,DU).

d(log(U),X,DU/U) :- !,

d(U,X,DU).

d(X,X,1) :- !.

d(_,_,0).

Page 24: Prolog - Probleme

24

Interogãri:

8)PROGRAMATORI

EnunŃul problemei:

James,Tim, Bob şi Jim, fiecare cunosc câte un limbaj de programare diferit şi

fiecare este specializat într-un domeniu diferit. Se cunosc urmãtoarele:

a)Cel ce programeazã în Java e specialist în biologie.

b)Tom nu ştie nici Prolog nici HTML, nici matematicã.

c)James nu cunoaşte nici Prolog, nici HTML, nici matematicã .

d)Specialistul în chimie nu programeazã în HTML.

e)Bob e specialist în fizicã şi nu programeazã in Prolog.

In ce limbaj şi în ce domeniu e specializat fiecare?

Codul în Prolog:

%fapte

nume(james).

Page 25: Prolog - Probleme

25

nume(tom).

nume(bob).

nume(jim).

limbaj(html).

limbaj(cpp).

limbaj(java).

limbaj(prolog).

domeniu(mate).

domeniu(fizica).

domeniu(chimie).

domeniu(bio).

%reguli

regula1(Y,Z):-Y=bio,!,Z=java.

regula1(_,_).

regula2(X,Y,Z):-X=tom,!,Y\==mate,Z\==prolog,Z\==html.

regula2(_,_,_).

regula3(X,Y,Z):-X=james,!,Y\==mate,Z\==prolog,Z\==html.

regula3(_,_,_).

regula4(Y,Z):-Y=chimie,!,Z\==html.

regula4(_,_).

regula5(X,Y,Z):-X=bob,!,Y=fizica,Z\==prolog.

regula5(_,_,_).

rezolva(X,Y,Z):-nume(X),

domeniu(Y),

limbaj(Z),

regula1(Y,Z),

regula2(X,Y,Z),

regula3(X,Y,Z),

regula4(Y,Z),

regula5(X,Y,Z).

diferit(X1,X2,X3,X4):-X1\==X2,X1\==X3,X1\==X4,X2\==X3,X2\==X4,X3\==X4.

solutie(Y1,Z1,Y2,Z2,Y3,Z3,Y4,Z4):-rezolva(james,Y1,Z1),

rezolva(tom,Y2,Z2),

rezolva(bob,Y3,Z3),

rezolva(jim,Y4,Z4),

diferit(Y1,Y2,Y3,Y4),

diferit(Z1,Z2,Z3,Z4).

Page 26: Prolog - Probleme

26

Interogãri:

9) DENSITATE

EnunŃul problemei: Se dã o bazã de cunoştinŃe, se cere sã se gãseascã Ńãrile cu denitatea populaŃiei

aproximativ egalã.

Codul în Prolog:

query :- query(_), fail.

query.

query([C1,D1,C2,D2]) :-

density(C1,D1),

density(C2,D2),

D1 > D2,

T1 is 20*D1,

T2 is 21*D2,

T1 < T2.

density(C,D) :-

pop(C,P),

area(C,A),

D is (P*100)//A.

% populations in 100000's

pop(china, 8250).

pop(india, 5863).

pop(ussr, 2521).

pop(usa, 2119).

pop(indonesia, 1276).

pop(japan, 1097).

Page 27: Prolog - Probleme

27

pop(brazil, 1042).

pop(bangladesh, 750).

pop(pakistan, 682).

pop(w_germany, 620).

pop(nigeria, 613).

pop(mexico, 581).

pop(uk, 559).

pop(italy, 554).

pop(france, 525).

pop(philippines, 415).

pop(thailand, 410).

pop(turkey, 383).

pop(egypt, 364).

pop(spain, 352).

pop(poland, 337).

pop(s_korea, 335).

pop(iran, 320).

pop(ethiopia, 272).

pop(argentina, 251).

% areas in 1000's of square miles

area(china, 3380).

area(india, 1139).

area(ussr, 8708).

area(usa, 3609).

area(indonesia, 570).

area(japan, 148).

area(brazil, 3288).

area(bangladesh, 55).

area(pakistan, 311).

area(w_germany, 96).

area(nigeria, 373).

area(mexico, 764).

area(uk, 86).

area(italy, 116).

area(france, 213).

area(philippines, 90).

area(thailand, 200).

area(turkey, 296).

area(egypt, 386).

area(spain, 190).

area(poland, 121).

area(s_korea, 37).

area(iran, 628).

area(ethiopia, 350).

area(argentina, 1080).

Page 28: Prolog - Probleme

28

Interogãri:

10)TESTUL LUI EINSTEIN

EnunŃul problemei: Prezumtii:

1.Exista 5 case fiecare de alta culoare.

2.In fiecare casa locuieste o singura persoana, fiecare de alta nationalitate

3.Fiecarui locatar ii place o anumita bautura, fumeaza o anumita marca de tigari si detine

un anumit animal de casa.

4.Nici una din cele 5 persoane nu bea aceeasi bautura, nu fumeaza aceeasi marca de

tigari, si nu detine acelasi animal de casa.

Page 29: Prolog - Probleme

29

Se dau urmatoarele:

a.Britanicul locuieste in casa rosie

b.Suedezul are un caine

c.Danezul bea ceai

d.Casa verde se afla in stanga casei albe

e.Locatarul casei verzi bea cafea

f.Persoana care fumeaza Pall Mall are o pasare

g.Locatarul casei din mijloc bea lapte

h.Locatarul casei galbene fumeaza Dunhill

i.Norvegianul locuieste in prima casa

j.Fumatorul de Marlboro locuieste langa cel care are o pisica

k.Locatarul care are un cal locuiste langa cel care fumeaza Dunhill

l.Fumatorul de Winfield bea bere

m.Norvegianul locuieste langa casa albastra

n.Germanul fumeaza Rothmans

o.Fumatorul de Marlboro are un vecin care bea apa

Cine are acvariul cu pesti??

Codul în Prolog:

next_to(X, Y, List) :- iright(X, Y, List).

next_to(X, Y, List) :- iright(Y, X, List).

iright(L, R, [L | [R | _]]).

iright(L, R, [_ | Rest]) :- iright(L, R, Rest).

member(X,[X|T]).

member(X,[H|T]):-member(X,T).

einstein(Houses, Fish_Owner) :-

Houses=( [[house, norwegian, _, _, _, _], _, [house, _, _, _, milk, _], _, _]),

member([house, brit, _, _, _, red], Houses),

member([house, swede, dog, _, _, _], Houses),

member([house, dane, _, _, tea, _], Houses),

iright([house, _, _, _, _, green], [house, _, _, _, _, white], Houses),

member([house, _, _, _, coffee, green], Houses),

member([house, _, bird, pallmall, _, _], Houses),

member([house, _, _, dunhill, _, yellow], Houses),

next_to([house, _, _, dunhill, _, _], [house, _, horse, _, _, _], Houses),

member([house, _, _, _, milk, _], Houses),

next_to([house, _, _, marlboro, _, _], [house, _, cat, _, _, _], Houses),

next_to([house, _, _, marlboro, _, _], [house, _, _, _, water, _], Houses),

member([house, _, _, winfield, beer, _], Houses),

Page 30: Prolog - Probleme

30

member([house, german, _, rothmans, _, _], Houses),

next_to([house, norwegian, _, _, _, _], [house, _, _, _, _, blue], Houses),

member([house, Fish_Owner, fish, _, _, _], Houses).

Interogãri:

PROIECT 3

Prolog – Teme Autor – Dumitru Ciubatîi , Grupa 243 .

Tema 1 – Sudoku. Enunt: Sudoku reprezinta un joc clasic in care este dat un tabel compus din 9 x 9 patratele, unite

la randul sau in 9 blocuri de marime 3 x 3 ca in exemplul de mai jos. Unele patratele

contin initial cate o cifra cuprinsa intre 1 si 9 inclusiv. Scopul jocului este de a completa

restul patratelelor libere cu cifre astfel incat fiecare linie, fiecare coloana si fiecare bloc 3

x 3 sa contina toate cifrele de la 1 la 9. Se cere un program prolog care sa rezolve acest joc.

Page 31: Prolog - Probleme

31

Solutie:

:- use_module(library(clpfd)).

sudoku(

A1, A2, A3, A4, A5, A6, A7, A8, A9,

B1, B2, B3, B4, B5, B6, B7, B8, B9,

C1, C2, C3, C4, C5, C6, C7, C8, C9,

D1, D2, D3, D4, D5, D6, D7, D8, D9,

E1, E2, E3, E4, E5, E6, E7, E8, E9,

F1, F2, F3, F4, F5, F6, F7, F8, F9,

G1, G2, G3, G4, G5, G6, G7, G8, G9,

H1, H2, H3, H4, H5, H6, H7, H8, H9,

I1, I2, I3, I4, I5, I6, I7, I8, I9

) :-

L = [ A1, A2, A3, A4, A5, A6, A7, A8, A9,

B1, B2, B3, B4, B5, B6, B7, B8, B9,

C1, C2, C3, C4, C5, C6, C7, C8, C9,

D1, D2, D3, D4, D5, D6, D7, D8, D9,

E1, E2, E3, E4, E5, E6, E7, E8, E9,

F1, F2, F3, F4, F5, F6, F7, F8, F9,

G1, G2, G3, G4, G5, G6, G7, G8, G9,

H1, H2, H3, H4, H5, H6, H7, H8, H9,

I1, I2, I3, I4, I5, I6, I7, I8, I9 ],

Page 32: Prolog - Probleme

32

domain(L, 1, 9),

% RANDURI

all_different([A1, A2, A3, A4, A5, A6, A7, A8, A9]),

all_different([B1, B2, B3, B4, B5, B6, B7, B8, B9]),

all_different([C1, C2, C3, C4, C5, C6, C7, C8, C9]),

all_different([D1, D2, D3, D4, D5, D6, D7, D8, D9]),

all_different([E1, E2, E3, E4, E5, E6, E7, E8, E9]),

all_different([F1, F2, F3, F4, F5, F6, F7, F8, F9]),

all_different([G1, G2, G3, G4, G5, G6, G7, G8, G9]),

all_different([H1, H2, H3, H4, H5, H6, H7, H8, H9]),

all_different([I1, I2, I3, I4, I5, I6, I7, I8, I9]),

% COLOANE

all_different([A1, B1, C1, D1, E1, F1, G1, H1, I1]),

all_different([A2, B2, C2, D2, E2, F2, G2, H2, I2]),

all_different([A3, B3, C3, D3, E3, F3, G3, H3, I3]),

all_different([A4, B4, C4, D4, E4, F4, G4, H4, I4]),

all_different([A5, B5, C5, D5, E5, F5, G5, H5, I5]),

all_different([A6, B6, C6, D6, E6, F6, G6, H6, I6]),

all_different([A7, B7, C7, D7, E7, F7, G7, H7, I7]),

all_different([A8, B8, C8, D8, E8, F8, G8, H8, I8]),

all_different([A9, B9, C9, D9, E9, F9, G9, H9, I9]),

% PATRATE 3x3

all_different([A1, A2, A3, B1, B2, B3, C1, C2, C3]),

all_different([A4, A5, A6, B4, B5, B6, C4, C5, C6]),

all_different([A7, A8, A9, B7, B8, B9, C7, C8, C9]),

all_different([D1, D2, D3, E1, E2, E3, F1, F2, F3]),

all_different([D4, D5, D6, E4, E5, E6, F4, F5, F6]),

all_different([D7, D8, D9, E7, E8, E9, F7, F8, F9]),

all_different([G1, G2, G3, H1, H2, H3, I1, I2, I3]),

all_different([G4, G5, G6, H4, H5, H6, I4, I5, I6]),

all_different([G7, G8, G9, H7, H8, H9, I7, I8, I9]),

labeling([], L),

afiseaza(L).

afiseaza(L) :- afiseaza(1,L).

afiseaza(X,[A|L]) :- X<81 -> write(A), Z is X mod 9 , ( Z=0,X>0 -> write('\n') ; write(',')

) , afiseaza(X+1,L) ; write(A) , write('\n') .

Page 33: Prolog - Probleme

33

% exemplu din enunt

joc1 :- sudoku(

_,4,_,1,_,3,5,_,_,

7,_,_,_,_,_,_,1,8,

9,_,1,6,_,8,3,_,_,

1,_,_,4,_,_,6,_,_,

_,8,_,2,_,6,_,9,_,

_,_,2,_,_,9,_,_,4,

_,_,7,9,_,1,4,_,6,

4,9,_,_,_,_,_,_,3,

_,_,6,3,_,7,_,2,_

).

joc2 :- sudoku(

_,4,3,_,8,_,2,5,_,

6,_,_,_,_,_,_,_,_,

_,_,_,_,_,1,_,9,4,

9,_,_,_,_,4,_,7,_,

_,_,_,6,_,8,_,_,_,

_,1,_,2,_,_,_,_,3,

8,2,_,5,_,_,_,_,_,

_,_,_,_,_,_,_,_,5,

_,3,4,_,9,_,7,1,_

).

joc3 :- sudoku(

_,_,_,3,_,_,4,6,_,

_,_,9,8,_,_,_,_,2,

1,4,8,_,_,_,_,_,_,

_,1,3,5,8,_,_,4,_,

8,5,_,_,_,_,_,1,3,

_,2,_,_,1,3,7,8,_,

_,_,_,_,_,_,3,2,1,

5,_,_,_,_,_,7,8,_,

_,8,1,_,_,9,_,_,_

).

joc4 :- sudoku(

_,_,_,2,_,_,_,9,_,

6,3,_,_,4,_,_,_,8,

_,_,9,6,_,_,_,1,_,

_,7,6,_,_,_,_,_,9,

Page 34: Prolog - Probleme

34

_,_,1,4,_,2,8,_,_,

3,_,_,_,_,_,1,7,_,

_,2,_,_,_,6,7,_,_,

9,_,_,_,2,_,_,5,1,

_,6,_,_,_,1,_,_,_

).

% un tabel curat

joc0 :- sudoku(

_,_,_,_,_,_,_,_,_,

_,_,_,_,_,_,_,_,_,

_,_,_,_,_,_,_,_,_,

_,_,_,_,_,_,_,_,_,

_,_,_,_,_,_,_,_,_,

_,_,_,_,_,_,_,_,_,

_,_,_,_,_,_,_,_,_,

_,_,_,_,_,_,_,_,_,

_,_,_,_,_,_,_,_,_

).

Exemple de rulare:

?- joc1.

2,4,8,1,7,3,5,6,9

7,6,3,5,9,4,2,1,8

9,5,1,6,2,8,3,4,7

1,7,9,4,8,5,6,3,2

5,8,4,2,3,6,7,9,1

6,3,2,7,1,9,8,5,4

3,2,7,9,5,1,4,8,6

4,9,5,8,6,2,1,7,3

8,1,6,3,4,7,9,2,5

?- joc2.

1,4,3,9,8,6,2,5,7

6,7,9,4,2,5,3,8,1

2,8,5,7,3,1,6,9,4

9,6,2,3,5,4,1,7,8

3,5,7,6,1,8,9,4,2

4,1,8,2,7,9,5,6,3

8,2,1,5,6,7,4,3,9

7,9,6,1,4,3,8,2,5

5,3,4,8,9,2,7,1,6

?- joc3.

Page 35: Prolog - Probleme

35

no

?- joc4.

4,1,8,2,5,7,3,9,6

6,3,7,1,4,9,5,2,8

2,5,9,6,8,3,4,1,7

8,7,6,3,1,5,2,4,9

5,9,1,4,7,2,8,6,3

3,4,2,9,6,8,1,7,5

1,2,5,8,9,6,7,3,4

9,8,3,7,2,4,6,5,1

7,6,4,5,3,1,9,8,2

?- joc0.

1,2,3,4,5,6,7,8,9

4,5,6,7,8,9,1,2,3

7,8,9,1,2,3,4,5,6

2,1,4,3,6,5,8,9,7

3,6,5,8,9,7,2,1,4

8,9,7,2,1,4,3,6,5

5,3,1,6,4,2,9,7,8

6,4,2,9,7,8,5,3,1

9,7,8,5,3,1,6,4,2

Page 36: Prolog - Probleme

36

Tema 2 – Numarul de componente conexe intr-un graf. Enunt: Se da un graf nedirectionat: se da lista de varfurilor sale si pentru fiecare varf se da lista

vecinilor sai.

Se cere un program prolog care sa afle si sa afiseze numarul de componente conexe din

graful dat.

Solutie:

% definirea grafurilor pentru teste

graf1:-abolish(nodes),abolish(vec),

asserta(nodes([a,b,c,d,e,f,g,h])),

asserta(vec(a,[b,c])),

asserta(vec(b,[a])),

asserta(vec(c,[a,d,e])),

asserta(vec(d,[c])),

asserta(vec(e,[c])),

asserta(vec(f,[g,h])),

asserta(vec(g,[f,h])),

asserta(vec(h,[f,g])).

graf2:-abolish(nodes),abolish(vec),

asserta(nodes([a,b,c,d,e,f,g,h,i,j,k,l,m])),

asserta(vec(a,[b,c,h])),

asserta(vec(b,[a])),

asserta(vec(c,[a])),

asserta(vec(d,[k,m])),

asserta(vec(e,[i,g])),

asserta(vec(f,[i,g])),

asserta(vec(g,[e,f])),

asserta(vec(h,[a])),

asserta(vec(i,[j,e,f])),

asserta(vec(j,[i,k])),

asserta(vec(k,[d,j])),

asserta(vec(l,[])),

asserta(vec(m,[d])).

% testele

test1:-graf1,comp.

test2:-graf2,comp.

Page 37: Prolog - Probleme

37

% programul

comp:-clear,init,loop,write_res.

init:-nodes(L),init(L).

init(L):-assert(total(0)),list_noduri(L).

clear:-clear_coada,nodes(L),clear(L).

clear(L):-retract(total(X)),clear(L).

clear([X|L]):-retract(liber(X)),clear(L).

clear(L).

clear_coada:-retract(coada(X)),clear_coada.

clear_coada.

write_res:-retract(total(X)),write(X).

list_noduri([X]):-assert(liber(X)).

list_noduri([X|Y]):-assert(liber(X)),list_noduri(Y).

% simulam un ciclu

loop:-retract(liber(X)),push(X),parcurge,retract(total(T)),T1 is T+1,assert(total(T1)),loop.

loop.

parcurge:-pop(X),vec(X,V),get_free(V,L),push(L),parcurge.

parcurge.

get_free([],[]).

get_free([X|L],[X|K]):- retract(liber(X)),get_free(L,K).

get_free([X|L],K):- get_free(L,K).

get_free(X,[X|K]):- retract(liber(X)).

get_free(X,K).

% simulam coada de noduri atinse in componenta curenta

push([]).

push([X]):-push(X).

push([X|L]):-push(X),push(L).

push(X):-assert(coada(X)).

pop(X):-retract(coada(X)).

Page 38: Prolog - Probleme

38

Exemple de rulare:

?- test1.

2

?- test2.

3

Page 39: Prolog - Probleme

39

Tema 3 –Cel mai scurt drum intre 2 varfuri intr-un graf. Enunt: Se da un graf nedirectionat: se da lista varfurilor sale si lista de muchii sub forma (a,b,c),

unde a si b sunt varfurile muchiei si c este costul ei.

Se cere un program prolog care sa afle si sa afiseze cel mai scurt drum de la un varf S la

un varf F in graful dat.

Solutie:

% definirea grafurilor utilizate

graf1:-abolish(nodes),abolish(vec),

assert(nodes([a,b,c,d,e])),

assert(vec(a,b,10)),

assert(vec(b,c,10)),

assert(vec(c,d,15)),

assert(vec(a,d,23)),

assert(vec(c,e,5)),

assert(vec(d,e,10)).

graf2:-abolish(nodes),abolish(vec),

assert(nodes([a,b,c,d,e,f,g,h])),

assert(vec(a,b,5)),

assert(vec(a,d,6)),

assert(vec(a,g,4)),

assert(vec(b,f,3)),

assert(vec(c,d,3)),

assert(vec(c,f,6)),

assert(vec(e,f,3)),

assert(vec(e,g,2)),

assert(vec(e,h,2)),

assert(vec(f,h,1)).

% testele

test1:-graf1,drum(a,c).

test2:-graf1,drum(d,b).

test3:-graf1,drum(a,e).

test4:-graf2,drum(b,e).

test5:-graf2,drum(h,b).

test6:-graf2,drum(d,e).

test7:-graf2,drum(a,h).

Page 40: Prolog - Probleme

40

% functii pentru muchii

is_connect(X,Y):-vec(X,Y,_);vec(Y,X,_).

cost(X,Y,Z):-vec(X,Y,C),Z is C;vec(Y,X,C),Z is C.

% initializare

clear:-nodes(L),clear_vl(L),clear_prec,clear_best(L),(retract(dst(X))->true;true).

clear_vl([X|L]):-set_vl(X,0),clear_vl(L).

clear_vl([]).

clear_best([X|L]):-set_best(X,1000000),clear_best(L).

clear_best([]):-set_best(z,1000000).

clear_prec:-abolish(prec).

clear_prec.

init(S):-set_vl(S,1),set_best(S,0).

drum(S,F):-clear,init(S),loop(F),get_best(F,Res),afiseaza_drum(S,F),write('\nLungimea

drumului - '),write(Res).

loop(F):-get_min(F) ; get_min(X), ( get_best(X,1000000) ; set_vl(X,2), update(X) ,

loop(F) ) .

afiseaza_drum(S,S):-write(S).

afiseaza_drum(S,F):-get_prec(F,X),afiseaza_drum(S,X),write(-),write(F).

% ---

get_min(X):-nodes(L),get_free_node(Y),get_min(Y,L,X).

get_min(X,[Y|L],X):-

get_vl(Y,C),C==1,get_best(Y,BY),get_best(X,BX),BY<BX,get_min(X,L,X).

get_min(X,[Y|L],Z):- get_min(X,L,Z).

get_min(X,[],X).

get_free_node(X):-nodes(L),get_free_node(X,L).

get_free_node(Y,[Y|L]):-get_vl(Y,V),V==1.

get_free_node(X,[Y|L]):-get_free_node(X,L).

% ---

update(X):-nodes(L),update(X,L).

update(X,[Y|L]):- ( X\==Y, get_best(X,BX) , get_vl(Y,VY) , cost(X,Y,C) , CCost is

BX+C , get_best(Y,BY) , (VY==0 ; VY==1 , CCost<BY) , set_vl(Y,1),

set_best(Y,CCost), set_prec(Y,X) ; true ) , update(X,L).

Page 41: Prolog - Probleme

41

update(X,[]).

% ---

set_vl(X,Y):-retract(vl(X,Z)),assert(vl(X,Y));assert(vl(X,Y)).

get_vl(X,Y):-retract(vl(X,Y)),assert(vl(X,Y)).

set_best(X,Y):-retract(best(X,Z)),assert(best(X,Y));assert(best(X,Y)).

get_best(X,Y):-retract(best(X,Y)),assert(best(X,Y)).

% seteaza Y ca nodul precedent al lui X

set_prec(X,Y):-retract(prec(X,Z)),assert(prec(X,Y));assert(prec(X,Y)).

get_prec(X,Y):-retract(prec(X,Y)),assert(prec(X,Y)).

Exemple de rulare:

?- test1.

a-b-c

Lungimea drumului - 20

yes

?- test2.

d-a-b

Lungimea drumului - 33

yes

?- test3.

a-b-c-e

Lungimea drumului - 25

yes

?- test4.

b-f-e

Lungimea drumului - 6

yes

?- test5.

h-f-b

Lungimea drumului - 4

yes

?- test6.

d-c-f-e

Lungimea drumului - 12

yes

Page 42: Prolog - Probleme

42

?- test7.

a-b-f-h

Lungimea drumului - 9

yes

PROIECT 4

Leuca Petrica

grupa 242

1. Vrificati daca 3 numere pot si laturile unui triunghi.

introdu:-

write('introdu a= '),read(A),

write('introdu b= '),read(B),

write('introdu c= '),read(C),

A>=0,B>=0,C>=0,A<(B+C),B<(C+A),C<(A+B),

write('Aceste numere sunt laturile unui triunghi '),nl.

Apelul se face astfel:

?- introdu.

introdu a= 3.

introdu b= 4.

introdu c= 5.

Aceste numere sunt laturile unui triunghi

yes

2. Scoaterea duplicatelor dintr-o lista

%verificam daca un element apartine unei liste

member(X,[X|_]).

member(X,[_|T]):- member(X,T).

%scoatem duplicatele dintr-o lista.

set1([],[]):- !.

set1([H|T],R):- member(H,T), set1(T,R), !.

Page 43: Prolog - Probleme

43

set1([H|T],[R|Rest]):- set1(T,Rest).

Apelul se face astfel :

?- set1([a,b,b,c,c],I).

I = [a,b,c] ?

yes

3. Rezolvarea ecuatiei de gradul al doilea

start:- citire(A,B,C),rezolvare(A,B,C),!,continuare.

% citim de la tastatura coeficientii

citire(A,B,C):-write('Dati coeficientii:'),nl,

write('A='),read(A),nl,

write('B='),read(B),nl,

write('C='),read(C),nl.

% calculam delta

delta(A,B,C,R):- D is (B*B-4*A*C),

D>=0,R is (sqrt(D)).

%rezolvarea efectiva a unei ecuatii

%pentru A diferit de 0

rezolvare(A,B,C):- A=\=0,delta(A,B,C,R),R>=0,

X1 is (-B+R)/(2*A), X2 is (-B-R)/(2*A),

write('Solutiile ecuatiei sunt '),

write('x1='),write(X1),write(' x2='),write(X2),nl.

%pentru A egal cu 0 ecuatia devine una de gradul 1

rezolvare(A,B,C):- A=0,X is (-C/B),

write('Solutia ec de gradul I este:'),

write(X),nl.

continuare:-write('Doriti sa continuam(da,yes)?='),read(X),

(X=da;X=d;X=a;X=y;X=ye;X=yes),start.

Apel :

Page 44: Prolog - Probleme

44

?- start.

Dati coeficientii:

A=1

.

B=2.

C=1.

Solutiile ecuatiei sunt x1=-1.0 x2=-1.0

4. Lucrul cu multimi

% Reuniunea si intersectia a 2 multimi

% predicatul membru

member(X,[X|_]).

member(X,[_|T]):-member(X,T).

% verifica daca o lista e multime.

set([]).

set([X|T]):-not member(X,T), set(T).

% reuniunea a 2 multimi

union([],X,X):-!.

union([X|R],Y,Z):-member(X,Y), union(R,Y,Z), !.

union([X|R],Y,[X|Z]):-union(R,Y,Z).

%intersectia a 2 multimi

intersect([],X,[]):-!.

intersect([X|R],Y,[X|T]):-member(X,Y), intersect(R,Y,T), !.

intersect([X|R],Y,L):-intersect(R,Y,L).

Apel:

?- union([a,b,c],[d],R).

R = [a,b,c,d] ?

yes

| ?- intersect([a,b,c],[a,c],R).

R = [a,c] ?

yes

5. utomat Finit Determinist

%Descrierea automatului: un automat AFD (automat finit determinist)

%care are patru stari {1,2,3,4} si cuvintele de intrare sunt peste

%Alfabetul={a,b}

Page 45: Prolog - Probleme

45

init(stare(1,C)).

final(stare(4,[])).

% automatul

% -1---a-->2--a-->3--a-->4-----

% ||----b--|--b---| |-a,b-|

% ||

% -b

arc(1,2,[a]).

arc(1,1,[b]).

arc(2,3,[a]).

arc(2,1,[b]).

arc(3,2,[b]).

arc(3,4,[a]).

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

go1:-write('da cuvant='),read(C),init(stare(S,C)),final(F),

drum(stare(S,C),F,Rez),write([stare(S,C)|Rez]).

de_la(stare(X,[H|T]),stare(Y,T)):-arc(X,Y,L),member(H,L).

drum(X,X,[]).

drum(X,Y,[Z|T]):-de_la(X,Z),drum(Z,Y,T).

member(X,[X|_]).

member(X,[_|T]):-member(X,T).

Apel:

?- go1.

da cuvant=[a,a,a,a,b,b].

[stare(1,[a,a,a,a,b,b]),stare(2,[a,a,a,b,b]),stare(3,[a,a,b,b]),stare(4,[a,b,b]),stare(4,[b,b]),sta

re(4,[b]),stare(4,[])]

yes

6.Testul lui Einstein

member(X,[X|T]).

member(X,[H|T]):-member(X,T).

next_to(X, Y, List) :- iright(X, Y, List).

next_to(X, Y, List) :- iright(Y, X, List).

iright(L, R, [L | [R | _]]).

Page 46: Prolog - Probleme

46

iright(L, R, [_ | Rest]) :- iright(L, R, Rest).

% predicatul einstein descrie regulile date de joc

einstein(Houses, Fish_Owner) :-

=(Houses, [[house, norwegian, _, _, _, _], _ , [house, _, _, _, milk, _], _, _]),

member([house, brit, _, _, _, red], Houses),

member([house, swede, dog, _, _, _], Houses),

member([house, dane, _, _, tea, _], Houses),

iright([house, _, _, _, _, green], [house, _, _, _, _, white], Houses),

member([house, _, _, _, coffee, green], Houses),

member([house, _, bird, pallmall, _, _], Houses),

member([house, _, _, dunhill, _, yellow], Houses),

next_to([house, _, _, dunhill, _, _], [house, _, horse, _, _, _], Houses),

member([house, _, _, _, milk, _], Houses),

next_to([house, _, _, marlboro, _, _], [house, _, cat, _, _, _], Houses),

next_to([house, _, _, marlboro, _, _], [house, _, _, _, water, _], Houses),

member([house, _, _, winfield, beer, _], Houses),

member([house, german, _, rothmans, _, _], Houses),

next_to([house, norwegian, _, _, _, _], [house, _, _, _, _, blue], Houses),

member([house, Fish_Owner, fish, _, _, _], Houses).

Apel:

?- einstein(X,Y).

X =

[[house,norwegian,cat,dunhill,water,yellow],[house,dane,horse,marlboro,tea,blue],[house

,brit,bird,pallmall,milk,red],[house,german,fish,rothmans,coffee,green],[house,swede,dog

,winfield,beer,white]],

Y = german ? ;

no

7.Sudoku

% Regula de joc: Casuta de 9*9 , impartita in 9 casute de 3*3. In fiecare casuta, pe linii si

pe coloane

% sunt cifre distincte de la 1 la 9.

:- use_module(library(clpfd)).

:- use_module(library(lists)).

test1 :-

L = [

Page 47: Prolog - Probleme

47

[_,6,_,1,_,4,_,5,_],

[_,_,8,3,_,5,6,_,_],

[2,_,_,_,_,_,_,_,1],

[8,_,_,4,_,7,_,_,6],

[_,_,6,_,_,_,3,_,_],

[7,_,_,9,_,1,_,_,4],

[5,_,_,_,_,_,_,_,2],

[_,_,7,2,_,6,9,_,_],

[_,4,_,5,_,8,_,7,_]],

sudoku(L),

pretty_print(L).

test2 :-

L = [

[_,_,4 ,_,_,3, _,7,_],

[_,8,_ ,_,7,_, _,_,_],

[_,7,_ ,_,_,8, 2,_,5],

[4,_,_ ,_,_,_, 3,1,_],

[9,_,_ ,_,_,_, _,_,8],

[_,1,5 ,_,_,_, _,_,4],

[1,_,6 ,9,_,_, _,3,_],

[_,_,_ ,_,2,_, _,6,_],

[_,2,_ ,4,_,_, 5,_,_]],

sudoku(L),

pretty_print(L).

test3 :-

L=

[

[_,4,3,_,8,_,2,5,_],

[6,_,_,_,_,_,_,_,_],

[_,_,_,_,_,1,_,9,4],

[9,_,_,_,_,4,_,7,_],

[_,_,_,6,_,8,_,_,_],

[_,1,_,2,_,_,_,_,3],

[8,2,_,5,_,_,_,_,_],

[_,_,_,_,_,_,_,_,5],

[_,3,4,_,9,_,7,1,_]

],

sudoku(L),

pretty_print(L).

test4 :-

Page 48: Prolog - Probleme

48

L=

[

[8,_,3,_,2,9,7,1,6],

[_,_,6,_,1,8,5,_,4],

[_,_,_,_,6,_,_,_,8],

[_,_,5,_,4,6,_,8,_],

[7,_,9,_,3,5,6,4,2],

[_,6,_,_,9,_,1,_,5],

[6,_,_,_,7,_,_,5,1],

[_,_,1,6,5,_,8,_,_],

[5,_,_,9,8,1,4,6,3]

],

sudoku(L),

pretty_print(L).

test5 :-

L=[

[_,_,_,1,5,_,_,7,_],

[1,_,6,_,_,_,8,2,_],

[3,_,_,8,6,_,_,4,_],

[9,_,_,4,_,_,5,6,7],

[_,_,4,7,_,8,3,_,_],

[7,3,2,_,_,6,_,_,4],

[_,4,_,_,8,1,_,_,9],

[_,1,7,_,_,_,2,_,8],

[_,5,_,_,3,7,_,_,_]

],

sudoku(L),

pretty_print(L).

%O lista de 9*9

sudoku(L) :-

flatten(L,AllVars),

domain(AllVars,1,9),

[R1,R2,R3,R4,R5,R6,R7,R8,R9] = L,

%fiecare linie e diferita

all_different(R1), all_different(R2), all_different(R3),

all_different(R4), all_different(R5), all_different(R6),

all_different(R7), all_different(R8), all_different(R9),

transpose(L,TL),

%fiecare coloana e diferita

[C1,C2,C3,C4,C5,C6,C7,C8,C9] = TL,

all_different(C1), all_different(C2), all_different(C3),

all_different(C4), all_different(C5), all_different(C6),

all_different(C7), all_different(C8), all_different(C9),

Page 49: Prolog - Probleme

49

%fiecare casuta de 3*3 trebuie sa aibe elemente distincte

[X11,X12,X13,X14,X15,X16,X17,X18,X19] = R1,

[X21,X22,X23,X24,X25,X26,X27,X28,X29] = R2,

[X31,X32,X33,X34,X35,X36,X37,X38,X39] = R3,

[X41,X42,X43,X44,X45,X46,X47,X48,X49] = R4,

[X51,X52,X53,X54,X55,X56,X57,X58,X59] = R5,

[X61,X62,X63,X64,X65,X66,X67,X68,X69] = R6,

[X71,X72,X73,X74,X75,X76,X77,X78,X79] = R7,

[X81,X82,X83,X84,X85,X86,X87,X88,X89] = R8,

[X91,X92,X93,X94,X95,X96,X97,X98,X99] = R9,

all_different([X11,X12,X13,X21,X22,X23,X31,X32,X33]),

all_different([X41,X42,X43,X51,X52,X53,X61,X62,X63]),

all_different([X71,X72,X73,X81,X82,X83,X91,X92,X93]),

all_different([X14,X15,X16,X24,X25,X26,X34,X35,X36]),

all_different([X44,X45,X46,X54,X55,X56,X64,X65,X66]),

all_different([X74,X75,X76,X84,X85,X86,X94,X95,X96]),

all_different([X17,X18,X19,X27,X28,X29,X37,X38,X39]),

all_different([X47,X48,X49,X57,X58,X59,X67,X68,X69]),

all_different([X77,X78,X79,X87,X88,X89,X97,X98,X99]),

labeling([ffc],AllVars).

flatten([],[]).

flatten([H|T],Vars) :-

flatten(T,TVars),

append(H,TVars,Vars).

% transpune o lista in liste

transpose([Word], Cs) :- !,

R = Word,

list2columns(R, Cs).

transpose([Word|Words], Cs) :- !,

transpose(Words, Cs0),

R=Word,

put_columns(R, Cs0, Cs).

list2columns([], []).

list2columns([X|Xs], [[X]|Zs]) :- list2columns(Xs, Zs).

put_columns([], Cs, Cs).

Page 50: Prolog - Probleme

50

put_columns([X|Xs], [C|Cs0], [[X|C]|Cs]) :- put_columns(Xs, Cs0, Cs).

pretty_print([]).

pretty_print([H|T]) :-

write(H),nl,

pretty_print(T).

Apel:

?- test1.

[9,6,3,1,7,4,2,5,8]

[1,7,8,3,2,5,6,4,9]

[2,5,4,6,8,9,7,3,1]

[8,2,1,4,3,7,5,9,6]

[4,9,6,8,5,2,3,1,7]

[7,3,5,9,6,1,8,2,4]

[5,8,9,7,1,3,4,6,2]

[3,1,7,2,4,6,9,8,5]

[6,4,2,5,9,8,1,7,3]

yes

8. Derivarea

% legile derivarii pentru suma, produs,logaritm

divide10 :- d(((((((((x/x)/x)/x)/x)/x)/x)/x)/x)/x,x,_).

d(U+V,X,DU+DV) :- !,

d(U,X,DU),

d(V,X,DV).

d(U-V,X,DU-DV) :- !,

d(U,X,DU),

d(V,X,DV).

d(U*V,X,DU*V+U*DV) :- !,

d(U,X,DU),

d(V,X,DV).

d(U/V,X,(DU*V-U*DV)/(^(V,2))) :- !,

d(U,X,DU),

d(V,X,DV).

d(^(U,N),X,DU*N*(^(U,N1))) :- !,

integer(N),

N1 is N-1,

d(U,X,DU).

d(-U,X,-DU) :- !,

d(U,X,DU).

d(exp(U),X,exp(U)*DU) :- !,

d(U,X,DU).

d(log(U),X,DU/U) :- !,

d(U,X,DU).

Page 51: Prolog - Probleme

51

d(X,X,1) :- !.

d(_,_,0).

Apel:

?- d(^(2*x,3),x,D).

D = (0*x+2*1)*3*(2*x)^2 ?

Yes

9. Anagrame

% Citeste un cuvant de la utilizator si afiseaza anagramele.

member(X,[X|_]).

member(X,[_|T]):-member(X,T).

adaug(X,L,[X|L]).

adaug(X,[L|H],[L|R]):-adaug(X,H,R).

permut([],[]).

permut([L|H],R):-permut(H,R1),adaug(L,R1,R).

anagrame:-write('Dati un cuvant='),read(X),nl,

name(X,L),permut(L,R),

name(Cuv,R),write(Cuv),tab(5),fail.

?- anagrame.

Dati un cuvant=mere.

mere emre erme erem mree rmee reme reem mree rmee reme

reem meer emer eemr eerm meer emer eemr eerm mere emre

erme erem

no

COMENTARII - Einstein's Riddle

The logic puzzle in question is the

Page 52: Prolog - Probleme

52

"fish problem":

Einstein's Riddle

There are 5 houses in 5 different colors. In each house lives a man with a different

nationality. The 5 owners drink a certain type of beverage, smoke a certain brand of

cigar, and keep a certain pet. No owners have the same pet, smoke the same brand of

cigar or drink the same beverage.

Who owns the fish? Hints:

The Brit lives in the red house.

The Swede keeps dogs as pets.

The Dane drinks tea.

The green house is on the left of the white house.

The green house's owner drinks coffee.

The person who smokes Pall Mall rears birds.

The owner of the yellow house smokes Dunhill.

The man living in the center house drinks milk.

The Norwegian lives in the first house.

The man who smokes Blends lives next to the one who keeps cats.

The man who keeps the horse lives next to the man who smokes Dunhill.

The owner who smokes Bluemasters drinks beer.

The German smokes Prince.

The Norwegian lives next to the blue house.

The man who smokes Blends has a neighbor who drinks water.

There are five houses in five different colours starting from left to right. In each house

lives a person of a different nationality. These owners all drink a certain type of beverage,

smoke a certain brand of cigarette and keep a certain type of pet. No two owners have the

same pet, smoke the same brand or drink the same beverage. The question is: WHO

OWNS THE FISH??? Hints:

1. The Brit lives in the red house

2. The Swede keeps dogs as pets

3. The Dane drinks tea

4. The green house is on the left of the white house

5. The green house's owner drinks coffee

6. The person who smokes Pall Mall rears birds

7. The owner of the yellow house smokes Dunhill

8. The man living in the centre house drinks milk

9. The Norwegian lives in the first house

10. The person who smokes Marlboro lives next to the one who keeps cats

11. The person who keeps horses lives next to the person who smokes Dunhill

12. The person who smokes Winfield drinks beer

Page 53: Prolog - Probleme

53

13. The German smokes Rothmans

14. The Norwegian lives next to the blue house

15. The person who smokes Marlboro has a neigbor who drinks water

==

REZOLVARE SISCTUS PROLOG:

% Einstein's Riddle

member(X,[X|T]).

member(X,[H|T]):-member(X,T).

next_to(X, Y, List) :- iright(X, Y, List).

next_to(X, Y, List) :- iright(Y, X, List).

iright(L, R, [L | [R | _]]).

iright(L, R, [_ | Rest]) :- iright(L, R, Rest).

einstein(Houses, Fish_Owner) :-

=(Houses, [[house, norwegian, _, _, _, _], _, [house, _, _, _, milk, _], _, _]),

member([house, brit, _, _, _, red], Houses),

member([house, swede, dog, _, _, _], Houses),

member([house, dane, _, _, tea, _], Houses),

iright([house, _, _, _, _, green], [house, _, _, _, _, white], Houses),

member([house, _, _, _, coffee, green], Houses),

member([house, _, bird, pallmall, _, _], Houses),

member([house, _, _, dunhill, _, yellow], Houses),

next_to([house, _, _, dunhill, _, _], [house, _, horse, _, _, _], Houses),

member([house, _, _, _, milk, _], Houses),

next_to([house, _, _, marlboro, _, _], [house, _, cat, _, _, _], Houses),

Page 54: Prolog - Probleme

54

next_to([house, _, _, marlboro, _, _], [house, _, _, _, water, _], Houses),

member([house, _, _, winfield, beer, _], Houses),

member([house, german, _, rothmans, _, _], Houses),

next_to([house, norwegian, _, _, _, _], [house, _, _, _, _, blue], Houses),

member([house, Fish_Owner, fish, _, _, _], Houses).

For a LISP solution to the problem, and a list of links to other programs solving the

problem, see the URL http://www.weitz.de/einstein.html.

The approach to this problem via supercompilation was as follows. A program

Fish.java (viewable at the URL

http://www.supercompilers.com/Fish.java.html) was written, which takes as input the

array

Page 55: Prolog - Probleme

55

In the unsupercompiled program, the checkAndPrint method is evaluated at all 525= 298023223876953125 possible property assignments. When the supercompiler is applied

to Fish.java, it is this method which is significantly optimized.

The Java method obtained by supercompiling this method may be seen at http://www.supercompilers.com/Fish.java.res.html. The first part of the method tells it to

return an exception in one after another situation. The second part of the method

explicitly contains the solution to the problem:

java.lang.System.out.println("the owner of a fish = German"); java.lang.System.out.println(""); java.lang.System.out.println("house 1: Norwegian Yellow Dunhill Cat

Water "); java.lang.System.out.println("house 2: Dane Blue Blend Horse Tea "); java.lang.System.out.println("house 3: Brit Red PallMall Bird Milk "); java.lang.System.out.println("house 4: German Green Prince Fish Coffee

"); java.lang.System.out.println("house 5: Swede White BlueMaster Dog Beer

"); return;

class Fish { public static final int nofHouses = 5; public static final int nofProperties = 5; public static final int NATIONALITY = 0; public static final int COLORS = 1; public static final int CIGAR = 2; public static final int PET = 3; public static final int DRINK = 4; static class State { final String[][] houses; State (String[][] houses) { this.houses = houses; } } public static void checkAndPrint(String[][] houses) throws Exception { String[][] houses1 = new String[nofHouses][nofProperties]; for (int i=0; i<nofHouses; i++) { for (int j=0; j<nofProperties; j++) { houses1[i][j] = houses[i][j]; } } State s = new State (houses1); condition9(s);

Page 56: Prolog - Probleme

56

condition13(s); condition4(s); condition7(s); condition1(s); condition2(s); condition3(s); condition5(s); condition6(s); condition8(s); condition14(s); condition12(s); condition10(s); condition11(s); condition15(s); int iHouse = iHouseWithFish(s); System.out.println("The owner of a fish is " + owner(s, iHouse)); for (int i=0; i<nofHouses; i++) { String out = "House " + (i+1) + ": "; for (int j=0; j<nofProperties; j++) { out+=(s.houses[i][j]+" "); } System.out.println(out); } } public static String owner(State s, int iHouse) { return s.houses[iHouse][NATIONALITY]; } // 1. The Brit lives in a red house. public static void condition1(State s) throws Exception { inOneHouse(s, "Brit", "Red"); } // 2. The Swede keeps dogs as pets. public static void condition2(State s) throws Exception { inOneHouse(s, "Swede", "Dog"); } // 3. The Dane drinks tea. public static void condition3(State s) throws Exception { inOneHouse(s, "Dane", "Tea"); } // 4. The green house is on the left of the white house. public static void condition4(State s) throws Exception { for (int i=0; i<nofHouses-1; i++) { if (s.houses[i] [COLORS]=="Green") { s.houses[i] [COLORS]= "Green";

Page 57: Prolog - Probleme

57

if (s.houses[i+1][COLORS]=="White") { s.houses[i+1][COLORS]= "White"; return; }} } throw new Exception(); } // 5. The green house owner drinks coffee. public static void condition5(State s) throws Exception { inOneHouse(s, "Green", "Coffee"); } // 6. The person who smokes Pall Mall rears birds. public static void condition6(State s) throws Exception { inOneHouse(s, "PallMall", "Bird"); } // 7. The man living in the house right in the centre drinks milk. public static void condition7(State s) throws Exception { if (s.houses[(nofHouses-1)/2][DRINK]=="Milk") { s.houses[(nofHouses-1)/2][DRINK]= "Milk"; return; } throw new Exception(); } // 8. The owner of the yellow house smokes Dunhill. public static void condition8(State s) throws Exception { inOneHouse(s, "Yellow", "Dunhill"); } // 9. The Norwegian lives in the first house. public static void condition9(State s) throws Exception { if (s.houses[0][NATIONALITY]=="Norwegian") { s.houses[0][NATIONALITY]= "Norwegian"; return; } throw new Exception(); } // 10. The man who smokes Blend lives next to the one who keeps cats. public static void condition10(State s) throws Exception { inNextHouse(s, "Blend", "Cat"); } // 11. The man who keeps horses lives next to the man who smokes Dunhill. public static void condition11(State s) throws Exception {

Page 58: Prolog - Probleme

58

inNextHouse(s, "Dunhill", "Horse"); } // 12. The owner who smokes Blue Master drinks beer. public static void condition12(State s) throws Exception { inOneHouse(s, "BlueMaster", "Beer"); } // 13. The Norwegian lives next to the blue house. public static void condition13(State s) throws Exception { inNextHouse(s, "Norwegian", "Blue"); } // 14. The German smokes Prince. public static void condition14(State s) throws Exception { inOneHouse(s, "German", "Prince"); } // 15. The man who smokes Blend has a neighbour who drinks water public static void condition15(State s) throws Exception { inNextHouse(s, "Blend", "Water"); } // Find the number of the house with a fish public static int iHouseWithFish(State s) throws Exception { for (int i=0; i<nofHouses; i++) { if (s.houses[i][PET]=="Fish") { s.houses[i][PET]= "Fish"; return i; } } throw new Exception(); } public static void inOneHouse(State s, String str1, String str2) throws Exception { for (int i=0; i<nofHouses; i++) { if (s.houses[i][index(str1)]==str1) { s.houses[i][index(str1)]= str1; if (s.houses[i][index(str2)]==str2) { s.houses[i][index(str2)]= str2; return; }} } throw new Exception(); } public static void inNextHouse(State s, String str1, String str2) throws Exception { for (int i=0; i<nofHouses-1; i++) { jscp_joinLabeled: { if (s.houses[i] [index(str1)]==str1) {

Page 59: Prolog - Probleme

59

s.houses[i] [index(str1)]= str1; if (s.houses[i+1][index(str2)]==str2) { s.houses[i+1][index(str2)]= str2; return; }} } if (s.houses[i+1][index(str1)]==str1) { s.houses[i+1][index(str1)]= str1; if (s.houses[i] [index(str2)]==str2) { s.houses[i] [index(str2)]= str2; return; }} } throw new Exception(); } public static int index(String str) throws Exception { if(str=="Norwegian" || str=="Dane" || str=="Brit" || str=="German" || str=="Swede" ) return NATIONALITY; if(str=="Yellow" || str=="Blue" || str=="Red" || str=="Green" || str=="White" ) return COLORS; if(str=="Dunhill" || str=="Blend" || str=="PallMall" || str=="Prince" || str=="BlueMaster" ) return CIGAR; if(str=="Cat" || str=="Horse" || str=="Bird" || str=="Fish" || str=="Dog" ) return PET; if(str=="Water" || str=="Tea" || str=="Milk" || str=="Coffee" || str=="Beer" ) return DRINK; throw new Exception(); } public static void main (String args[]) throws Exception { String[][] houses = { {"Norwegian", "Yellow", "Dunhill", "Cat", "Water" }, {"Dane", "Blue", "Blend", "Horse", "Tea" }, {"Brit", "Red", "PallMall", "Bird", "Milk" }, {"German", "Green", "Prince", "Fish", "Coffee"}, {"Swede", "White", "BlueMaster", "Dog", "Beer" }

Page 60: Prolog - Probleme

60

}; checkAndPrint (houses); } }

An Abstract Unification Machine

http://www.lambdassociates.org/aum.pdf

Copyright (c) 2005, Mark Tarver

Here is a semantic tableau ATP in Qi Prolog with loads of mode declarations.

(defprolog

"prop(A,C) :- pr([[~, C] | A]).

pr(A) :- member([~ P], A), member(P, A), !.

pr(A) :- consistent(A), !, fail().

pr((mode [[P,&,Q] | A] -)) :- !, pr([P,Q | A]).

pr((mode [[P,<=>,Q] | A] -)) :- !, pr([[P,=>,Q],[Q,=>,P] | A]).

pr((mode [[P,=>,Q] | A] -)) :- !, pr([[[~ P],v,Q] | A]).

pr((mode [[~ [P,v,Q]] | A] -)) :- !, pr([[~,P],[~,Q] | A]).

pr((mode [[~ [P,&,Q]] | A] -)) :- !, pr([[[~,P],v,[~,Q]] | A]).

pr((mode [[~ [P,=>,Q]] | A] -)) :- !, pr([P,[~,Q] | A]).

pr((mode [[~ [P,<=>,Q]] | A] -)) :- !, pr([[~,[[P,=>,Q],v,[~,[Q,=>,P]]]] | A]).

pr((mode [[P,&,Q] | A] -)) :- !, pr([P,Q | A]).

pr((mode [[P,v,Q] | A] -)) :- !, pr([P | A]), !, pr([Q | A]).

pr((mode [P | Ps] -)) :- append(Ps, [P], Qs), !, pr(Qs).

consistent([]).

consistent([P | Ps]) :- when((symbol? P)), !, consistent(Ps).

consistent([[~ P] | Ps]) :- when((symbol? P)), !, consistent(Ps).

append([], X, X).

append((mode [X | Y] -) W [X | Z]) :- append(Y, W, Z).

member(X, (mode [X | _] -)). member(X, (mode [_ | Y] -)) :- member(X, Y).")

(ask [prop [ ] [[[p <=> q] <=> r] <=> [p <=> [q <=> r]]]]) Real time: 0.0100144 sec. Run time: 0.0100144 sec. Space: 190472 Bytes 3985 logical inferences yes

Here is Einstein's Riddle in Qi Prolog (query who is the fish owner).

Page 61: Prolog - Probleme

61

(defprolog

"einsteins_riddle(Fish_Owner) :- einstein(Houses, Fish_Owner).

einstein(Houses, Fish_Owner) :-

=(Houses, [[house, norwegian, _, _, _, _], _, [house, _, _, _, milk, _], _, _]),

member([house, brit, _, _, _, red], Houses),

member([house, swede, dog, _, _, _], Houses),

member([house, dane, _, _, tea, _], Houses),

iright([house, _, _, _, _, green], [house, _, _, _, _, white], Houses),

member([house, _, _, _, coffee, green], Houses),

member([house, _, bird, pallmall, _, _], Houses),

member([house, _, _, dunhill, _, yellow], Houses),

next_to([house, _, _, dunhill, _, _], [house, _, horse, _, _, _], Houses),

member([house, _, _, _, milk, _], Houses),

next_to([house, _, _, marlboro, _, _], [house, _, cat, _, _, _], Houses),

next_to([house, _, _, marlboro, _, _], [house, _, _, _, water, _], Houses),

member([house, _, _, winfield, beer, _], Houses),

member([house, german, _, rothmans, _, _], Houses),

next_to([house, norwegian, _, _, _, _], [house, _, _, _, _, blue], Houses),

member([house, Fish_Owner, fish, _, _, _], Houses).

member(X,[X | _]).

member(X,[_ | Z]) :- member(X,Z).

next_to(X, Y, List) :- iright(X, Y, List).

next_to(X, Y, List) :- iright(Y, X, List).

iright(L, R, [L | [R | _]]). iright(L, R, [_ | Rest]) :- iright(L, R, Rest).")

(ask [einsteins_riddle X])

X = german

More? (y/n) n

Real time: 5.5379634 sec.

Run time: 1.2818432 sec.

Space: 34052456 Bytes

GC: 37, GC time: 0.2103024 sec.

144143 logical inferences yes

Here is quick sort in Qi Prolog.

(defprolog

"test(Y) :- data(X), qsort(X, Y, Z).

Page 62: Prolog - Probleme

62

data(X) :- =(X,

[27,74,17,33,94,18,46,83,65,2,32,53,28,85,99,47,28,82,6,11,55,29,39,81,90,37,10

,0,66,51,7,21,85,27,31,63,75,4,95,99,11,28,61,74,18, 92,40,53,59,8]).

qsort([], R, R).

qsort([X|L], R, R0) :- partition(L, X, L1, L2), qsort(L2, R1, R0), qsort(L1, R, [X|R1]).

partition([],_,[],[]).

partition([X|L],Y,[X|L1],L2) :- when((<= X Y)), partition(L,Y,L1,L2). partition([X|L],Y,L1,[X|L2]) :- partition(L,Y,L1,L2).")

The Zebra problem in Qi Prolog; this blows the stack in CLisp.

(defprolog

"solve(ZebraColour, WaterColour) :-

constraints(Colours,Drinks,Nationalities,Cigarettes,Pets),

candidate(Colours,Drinks,Nationalities,Cigarettes,Pets),

member((h water,WaterHouse), Drinks),

member((h WaterColour,WaterHouse), Colours),

member((h zebra,ZebraHouse), Pets),

member((h ZebraColour,ZebraHouse), Colours).

candidate(L1, L2, L3, L4, L5) :-

perm(L1),perm(L2),perm(L3),perm(L4),perm(L5).

perm(((h _,A),(h _,B),(h _,C),(h _,D),(h _,E))) :-

permutation([A,B,C,D,E],[1,2,3,4,5]).

constraints(Colours, Drinks, Nationalities, Cigarettes, Pets) :-

member((h englishman,H1), Nationalities),

member((h red,H1), Colours),

member((h spaniard,H2), Nationalities),

member((h dog,H2), Pets),

member((h norwegian,1), Nationalities),

member((h kools,H3), Cigarettes),

member((h yellow,H3), Colours),

member((h chesterfields,H4), Cigarettes),

next(H4, H5),

member((h fox,H5), Pets),

member((h norwegian,H6), Nationalities),

next(H6, H7),

member((h blue,H7), Colours),

member((h winston,H8), Cigarettes),

member((h snails,H8), Pets),

member((h lucky_strike,H9), Cigarettes),

member((h orange_juice,H9), Drinks),

member((h ukrainian,H10), Nationalities),

member((h tea,H10), Drinks),

member((h japanese,H11), Nationalities),

Page 63: Prolog - Probleme

63

member((h parliaments,H11), Cigarettes),

member((h kools,H12), Cigarettes),

next(H12, H13),

member((h horse,H13), Pets),

member((h coffee,H14), Drinks),

member((h green,H14), Colours),

member((h green,H15), Colours),

lleft(H16, H15),

member((h ivory,H16), Colours),

member((h milk,3), Drinks).

permutation([],[]).

permutation([A|X],Y) :- delete(A,Y,Y1), permutation(X,Y1).

delete(A,[A|X],X).

delete(A,[B|X],[B|Y]) :- delete(A,X,Y).

member(A,[A|_]).

member(A,[_|X]) :- member(A,X).

next(X,Y) :- lleft(X,Y).

next(X,Y) :- lleft(Y,X).

lleft(1,2).

lleft(2,3).

lleft(3,4). lleft(4,5).")

Copyright (c) 2005, Mark Tarver [email protected]

Einstein's Riddle

Yoann Padioleau padiolea at merlin.irisa.fr

Wed Mar 14 13:26:10 CET 2001

• Previous message: Einstein's Riddle

• Next message: Einstein's Riddle

• Messages sorted by: [ date ] [ thread ] [ subject ] [ author ]

Petasis George <petasis at iit.demokritos.gr> writes: > "Donal K. Fellows" wrote: > > > > Thaddeus L Olczyk wrote: > > > I also figure the fish thing was simply a typo, and that this guy (

Page 64: Prolog - Probleme

64

> > > who hasn't resdponded ) was probably given this as a homework > > > assignement, and is simply looking for a cheap way to get it done. > > > > That'd be a very lame homework assignment. Not unless you had to write > > a program in $FAVOURITE_LANGUAGE to compute the answer automatically > > (which is much more interesting, especially if you make the program > > start from the natural language expression of the problem! :^) > > > Well, try this:-) > Written by a friend of mine. Its amazing how small can programs be if you > know STL. To bad I don't know stl :-) > Of course it will need some time, as it randomly checks all combinations... But your program dont really do the job cos it is too slow. You first generate the permutations and then test, the pb is that there is too many permutations : p[nation][english] can be either 0 1 2 3 4 or 5, same for the other variables you have 5*(5!) possibililty = 24 883 200 000 if you are able to do 1 000 000 ValidConstraints per second (cos you have perhaps a very very fast computer) you will need 24 883 seconds =~ 6hours to compute (in the worst case i admit) the prolog program i propose take 0.1 second to find the solution :) who say that prolog is slower than c++ :)) > > George > > //A simple randomiser to find the solution to the riddle, by J. Y. Goulermas > > #include <vector> > #include <ctime> > #include <algorithm> > #include <fstream> > #include <iomanip> > #include <iostream> > > using namespace std; > > enum element_type { nation, colour, pet, drink, cigs }; > enum nation_type { english, swedish, danish, german, norwegian }; > enum colour_type { red, blue, yellow, green, white }; > enum pet_type { cat, bird, horse, dog, fish }; > enum drink_type { tea, water, milk, beer, coffee };

Page 65: Prolog - Probleme

65

> enum cigs_type { palmal, dunhill, bluemasters, prince, blends }; > > char* codes[][5] = { { "english", "swedish", "danish", "german", > "norwegian" }, > { "red", "blue", "yellow", "green", > "white" }, > { "cat", "bird", "horse", "dog", "fish" > }, > { "tea", "water", "milk", "beer", > "coffee" }, > { "palmal", "dunhill", "bluemasters", "prince", > "blends" } > }; > > inline bool ValidConstraints(const vector< vector<int> >& p) > { > return p[nation][norwegian] == 0 //Rule 9 > && > p[colour][blue] == 1 //Rule 14 > && > p[drink][milk] == 2 //Rule 8 > && > p[nation][english] == p[colour][red] //Rule 1 > && > p[nation][swedish] == p[pet][dog] //Rule 2 > && > p[nation][danish] == p[drink][tea] //Rule 3 > && > p[colour][yellow] == p[cigs][dunhill] //Rule 7 > && > p[pet][bird] == p[cigs][palmal] //Rule 6 > && > p[drink][beer] == p[cigs][bluemasters] //Rule 12 > && > p[nation][german] == p[cigs][prince] //Rule 13 > && > p[colour][green] == p[drink][coffee] //Rule 5 > && > abs(p[cigs][blends] - p[pet][cat]) == 1 //Rule 10 > && > abs(p[cigs][blends] - p[drink][water]) == 1 //Rule 15 > && > abs(p[pet][horse] - p[cigs][dunhill]) == 1 //Rule 11 > && > p[colour][green] < p[colour][white]; //Rule 4 > } > > void Output(const vector< vector<int> >& p, > unsigned c > ) > { > ofstream text("solution.txt"); > > for (int i = nation; i <= cigs; ++i) > {

Page 66: Prolog - Probleme

66

> for (int j = 0; j < p[i].size(); ++j) > text <<setw(20) > <<codes[i][ find(p[i].begin(), p[i].end(), j) - p[i].begin() ]; > //get inverse permutation > text <<endl; > } > text <<"\n\nTotal attempts: " <<c; > > text.close(); > } > > void main(void) > { > //srand( (unsigned) time(NULL) ); //optional RNG seeding > > int ramp[] = { 0, 1, 2, 3, 4 }; > vector< vector<int> > permutations; > unsigned counter(0); > for (int i = nation; i <= cigs; i++ ) > permutations.push_back( vector<int>(ramp, ramp + 5) ); > > do > { > for (int i = nation; i <= cigs; i++) > random_shuffle( permutations[i].begin(), permutations[i].end() ); > if ( ! (++counter % 100000) ) > cout <<"\rRe-Randomisations: " <<counter; > } > while ( ! ValidConstraints(permutations) ); > > Output(permutations, counter); > } -- Yoann Padioleau, INSA de Rennes, France, http://www.irisa.fr/prive/padiolea Opinions expressed here are only mine. Je n'écris qu'à titre personnel. **____ Get Free. Be Smart. Simply use Linux and Free Software. ____**

Einstein Project Management Tip #1: Goals Rule

To celebrate the one-year anniversary

of PMThink (yep, we've passed the

one-year mark and now have over

1,000 posts - meeting our goal for the

first year), I've decided to have a little

fun by tapping the mind of the greatest

"thinker" of all time----Albert Einstein.

To many, Albert Einstein is

synonymous with the word "genius,"

Page 67: Prolog - Probleme

67

and rightfully so. In fact, the part of his brain responsible for mathematical and

visual/spacial thinking was discovered to be 15% greater than the average human. In

addition, it lacked the usual groove that runs through that area, which supposedly enabled

his neurons to communicate more effectively. In other words, he's someone worth

learning from.

Over the next few weeks, I'll enter some posts highlighting his quotes as they apply to

project management. Think Einstein doesn't have anything to do with project

management? Think again. Here's the first one...

"Confusion of goals and perfection of means seems, in my opinion, to characterize our

age."

The same could be said for project management today. With all the focus on execution

and delivery, many project managers fail because they make a huge assumption that the

goals and requirements are clear. As we strive to perfect the ability to finish on-time and

on-budget, let's not forget the need to make sure that the goals of the sponsor are crystal

clear, since that's where most projects fall short.

Stay tuned for more "Einstein project management tips."

Labels: einstein, it-project, learning, project-manager, project-manager-tips

posted by Jerry Manas @ 7:36 PM, Read More...