Name:-Lavkumar Narendrabhai Patel ENROLLMENT NO.: - 190160116087 Subject: - Ai Practicals Branch: - It (A3) Email
Name:-Lavkumar Narendrabhai Patel ENROLLMENT NO.: - 190160116087 Subject: - Ai Practicals Branch: - It (A3) Email
1 | Page
AI 190160116087
TABLE OF CONTENTS
Contents
PRACTICAL 1 ................................................................................................................ 3
(ii) : Find the last element of a list. ............................................................................. 3
(iii) : Find the K'th element of a list. ............................................................................ 3
(iv) : Find the number of elements of alist. ................................................................... 4
(v) : Reverse a given list ............................................................................................ 4
PRACTICAL 2 ............................................................................................................... 5
(i) : Find out whether a list is apalindrome. ............................................................... 5
(ii) : Duplicate the elements of a list agiven number of times. ...................................... 5
(iii) : Split a list into two parts; thelength of the first part is given. .................................... 6
(iv) : Remove the K'th element from alist. .................................................................... 7
(v) : Insert an element at a givenposition into a list. ..................................................... 7
PRACTICAL 3 ............................................................................................................... 8
(i) : Determine whether a given integernumber is prime or not. .................................... 8
(ii) : Determine the prime factors of agiven positive integer. .......................................... 9
(iii) : Determine whether two positiveinteger numbers are co-prime or not. ............... 10
PRACTICAL 4 ............................................................................................................. 11
Aim: Write a program to implementTic-Tac-Toe game problem. ...................................... 11
PRACTICAL 5 ............................................................................................................. 16
( i ) : Write a program to implement BFS(for 8 puzzle problem or Water Jug problem or any AI
search problem). ........................................................................................................ 16
( ii ): Write a program to implement BFS(for 8 puzzle problem or Water Jug problem or any AI
search problem). ........................................................................................................ 18
PRACTICAL 6 ............................................................................................................. 20
Aim: Write a program to implementSingle Player Game (Using Heuristic Function).......... 20
PRACTICAL 7 ............................................................................................................. 25
Aim: Write a program to solve A*Algorithm.................................................................. 25
PRACTICAL 8 ............................................................................................................. 31
Aim: Write a program to solve N-Queensproblem using Prolog. ................................. 31
PRACTICAL 9 ............................................................................................................. 33
Aim: Write a program to solve 8 puzzleproblem using Prolog. .................................... 33
PRACTICAL 10 ............................................................................................................ 36
Aim: Write a program to solve travellingsalesman problem using Prolog. ...................... 36
PRACTICAL 11 ............................................................................................................. 38
Aim: Develop an expert system for medical diagnosis of childhood diseasesusing prolog.38
2 | Page
AI 190160116087
PRACTICAL 1
(ii) : Find the last element of a list.
PROGRAM
lastelement([X],X).
lastelement([_|T],Y):-lastelement(T,Y).
OUTPUT
element_at(X,[X|_],1).
element_at(X,[_|L],K) :- K > 1, K1 is K - 1, element_a
t(X,L,K1).
OUTPUT
3 | Page
AI 190160116087
OUTPUT
4 | Page
AI 190160116087
PRACTICAL 2
(i) : Find out whether a
list is apalindrome.
PROGRAM
is_palindrome(L) :- reverse(L,L).
OUTPUT
5 | Page
AI 190160116087
OUTPUT
OUTPUT
6 | Page
AI 190160116087
OUTPUT
OUTPUT
7 | Page
AI 190160116087
PRACTICAL 3
(i) : Determine whether a given integer
number is prime or not.
PROGRAM : p1.pl
is_prime(2).
is_prime(3).
is_prime(P) :- integer(P), P > 3, P mod 2 =\= 0, \+ ha
s_factor(P,3).
OUTPUT
8 | Page
AI 190160116087
p2.pl
:- ensure_loaded(p1).
prime_factors_mult(N,L) :- N > 0, prime_factors_mult(N
,L,2).
prime_factors_mult(1,[],_) :- !.
prime_factors_mult(N,[[F,M]|L],F) :- divide(N,F,M,R),
!,
next_factor(R,F,NF), prime_factors_mult(R,L,NF).
prime_factors_mult(N,L,F) :- !,
next_factor(N,F,NF), prime_factors_mult(N,L,NF).
divi(N,F,M,R,K) :- S is N // F, N =:= S * F, !,
K1 is K + 1, divi(S,F,M,R,K1).
divi(N,_,M,N,M).
OUTPUT
9 | Page
AI 190160116087
coprime(X,Y) :- gcd(X,Y,1).
OUTPUT
10 | P a g e
AI 190160116087
PRACTICAL 4
Aim: Write a program to implement
Tic-Tac-Toe game problem.
PROGRAM
win(Brd, Plyr) :- rwin(Brd, Plyr);
cwin(Brd, Plyr);
dwin(Brd, Plyr).
11 | P a g e
AI 190160116087
xmove([a,B,C,D,E,F,G,H,I], 1, [x,B,C,D,E,F,G,H,I]).
xmove([A,a,C,D,E,F,G,H,I], 2, [A,x,C,D,E,F,G,H,I]).
xmove([A,B,a,D,E,F,G,H,I], 3, [A,B,x,D,E,F,G,H,I]).
xmove([A,B,C,a,E,F,G,H,I], 4, [A,B,C,x,E,F,G,H,I]).
xmove([A,B,C,D,a,F,G,H,I], 5, [A,B,C,D,x,F,G,H,I]).
xmove([A,B,C,D,E,a,G,H,I], 6, [A,B,C,D,E,x,G,H,I]).
xmove([A,B,C,D,E,F,a,H,I], 7, [A,B,C,D,E,F,x,H,I]).
xmove([A,B,C,D,E,F,G,a,I], 8, [A,B,C,D,E,F,G,x,I]).
xmove([A,B,C,D,E,F,G,H,a], 9, [A,B,C,D,E,F,G,H,x]).
xmove(Brd, _, Brd) :- write('Illegal move.'), nl.
disp([A,B,C,D,E,F,G,H,I]) :-
write('|'),
write([A,B,C]),write('|'),nl,
write('|'),
write([D,E,F]),write('|'),nl, write('|'),
write([G,H,I]),write('|'),nl,nl.
go :- how_to_play, strt([a,a,a,a,a,a,a,a,a]).
how_to_play :-
write('You are x player, enter positions followed by
a period.'),
nl,
disp([1,2,3,4,5,6,7,8,9]).
12 | P a g e
AI 190160116087
disp(NewBrd),
oplay(NewBrd, NewnewBrd),
disp(NewnewBrd),
strt(NewnewBrd).
oplay(Brd,NewBrd) :-
omove(Brd, o, NewBrd),
win(NewBrd, o),!.
oplay(Brd,NewBrd) :-
omove(Brd, o, NewBrd),
not(can_x_win(NewBrd)).
oplay(Brd,NewBrd) :-
omove(Brd, o, NewBrd).
oplay(Brd,NewBrd) :-
not(member(a,Brd)),!,
write('Game Ended without Winner!'), nl,
NewBrd = Brd.
13 | P a g e
AI 190160116087
OUTPUT
14 | P a g e
AI 190160116087
15 | P a g e
AI 190160116087
PRACTICAL 5
( i ) : Write a program to implement BFS
(for 8 puzzle problem or Water Jug
problem or any AI search problem).
PROGRAM
%connected(+Start, +Goal, -Weight)
connected(1,7,1).
connected(1,8,1).
connected(1,3,1).
connected(7,4,1).
connected(7,20,1).
connected(7,17,1).
connected(8,6,1).
connected(3,9,1).
connected(3,12,1).
connected(9,19,1).
connected(4,42,1).
connected(20,28,1).
connected(17,10,1).
connected2(X,Y,D) :- connected(X,Y,D).
connected2(X,Y,D) :- connected(Y,X,D).
16 | P a g e
AI 190160116087
write(Visited), nl,
append(Visited, [T|Extend], Visited2),
append(Path, [T|Extend], [Next|Path2]),
breadth_first(Next, Goal, Visited2, Path2).
OUTPUT
17 | P a g e
AI 190160116087
connected2(X,Y,D) :- connected(X,Y,D).
connected2(X,Y,D) :- connected(Y,X,D).
18 | P a g e
AI 190160116087
OUTPUT
19 | P a g e
AI 190160116087
PRACTICAL 6
Aim: Write a program to implement
Single Player Game (Using Heuristic
Function).
PROGRAM
win(Brd, Plyr) :- rwin(Brd, Plyr);
cwin(Brd, Plyr);
dwin(Brd, Plyr).
20 | P a g e
AI 190160116087
xmove([a,B,C,D,E,F,G,H,I], 1, [x,B,C,D,E,F,G,H,I]).
xmove([A,a,C,D,E,F,G,H,I], 2, [A,x,C,D,E,F,G,H,I]).
xmove([A,B,a,D,E,F,G,H,I], 3, [A,B,x,D,E,F,G,H,I]).
xmove([A,B,C,a,E,F,G,H,I], 4, [A,B,C,x,E,F,G,H,I]).
xmove([A,B,C,D,a,F,G,H,I], 5, [A,B,C,D,x,F,G,H,I]).
xmove([A,B,C,D,E,a,G,H,I], 6, [A,B,C,D,E,x,G,H,I]).
xmove([A,B,C,D,E,F,a,H,I], 7, [A,B,C,D,E,F,x,H,I]).
xmove([A,B,C,D,E,F,G,a,I], 8, [A,B,C,D,E,F,G,x,I]).
xmove([A,B,C,D,E,F,G,H,a], 9, [A,B,C,D,E,F,G,H,x]).
xmove(Brd, _, Brd) :- write('Illegal move.'), nl.
disp([A,B,C,D,E,F,G,H,I]) :-
write('|'),
write([A,B,C]),write('|'),nl,
write('|'),
write([D,E,F]),write('|'),nl, write('|'),
write([G,H,I]),write('|'),nl,nl.
go :- how_to_play, strt([a,a,a,a,a,a,a,a,a]).
how_to_play :-
write('You are x player, enter positions followed by
a period.'),
nl,
disp([1,2,3,4,5,6,7,8,9]).
21 | P a g e
AI 190160116087
strt(Brd) :- read(N),
xmove(Brd, N, NewBrd),
disp(NewBrd),
oplay(NewBrd, NewnewBrd),
disp(NewnewBrd),
strt(NewnewBrd).
oplay(Brd,NewBrd) :-
omove(Brd, o, NewBrd),
win(NewBrd, o),!.
oplay(Brd,NewBrd) :-
omove(Brd, o, NewBrd),
not(can_x_win(NewBrd)).
oplay(Brd,NewBrd) :-
omove(Brd, o, NewBrd).
oplay(Brd,NewBrd) :-
not(member(a,Brd)),!,
write('Game Ended without Winner!'), nl,
NewBrd = Brd.
22 | P a g e
AI 190160116087
OUTPUT
23 | P a g e
AI 190160116087
24 | P a g e
AI 190160116087
PRACTICAL 7
Aim: Write a program to solve A*
Algorithm.
PROGRAM
fluent(location(robbie, hallway)).
fluent(location(car-key, hallway)).
fluent(location(garage-key, hallway)).
fluent(location(vacuum-cleaner, kitchen)).
fluent(door(hallway-kitchen, unlocked)).
fluent(door(kitchen-garage, locked)).
fluent(door(garage-car, locked)).
fluent(holding(nothing)).
fluent(clean(car, false)).
fact(home(car-key, hallway)).
fact(home(garage-key, hallway)).
fact(home(vacuum-cleaner, kitchen)).
s0(Situation) :-
setof(S, fluent(S), Situation).
holds(Fluent, Situation) :-
ground(Fluent), ord_memberchk(Fluent, Situation),
!.
holds(Fluent, Situation) :-
member(Fluent, Situation).
25 | P a g e
AI 190160116087
poss(goto(L), S) :-
% If robbie is in X and the door is unlocked
holds(location(robbie, X), S),
( holds(door(X-L, unlocked), S)
; holds(door(L-X, unlocked), S)
).
poss(pickup(X), S) :-
holds(holding(X), S),
fact(home(X, L)),
holds(location(robbie, L), S).
poss(drop(X), S) :-
dif(X, nothing),
holds(holding(X), S).
poss(unlock(R1-R2), S) :-
26 | P a g e
AI 190160116087
( holds(location(robbie, R1), S)
; holds(location(robbie, R2), S)
).
poss(clean_car, S) :-
holds(location(robbie, car), S),
holds(holding(vacuum-cleaner), S).
27 | P a g e
AI 190160116087
goal(clean(car, true)).
goal(door(garage-car, locked)).
goal(door(kitchen-garage, locked)).
goal(location(X, L)) :- fact(home(X, L)).
goal(holding(nothing)).
goal_situation(S) :-
setof(G, goal(G), S).
reached_goal(GoalSituation, Situation) :-
ord_subtract(GoalSituation, Situation, []). % [] -
> no goals not in Situation
list([]).
list([_|T]) :-
list(T).
iterative_deepening_search(Process) :-
s0(S0),
goal_situation(GoalSituation),
list(Process),
execute_process(S0, Process, Result),
reached_goal(GoalSituation, Result).
:- use_module(library(heaps)).
heuristic_distance_to_goal(GoalSituation, Situation, D
istance) :-
ord_subtract(GoalSituation, Situation, Dif),
length(Dif, Distance).
28 | P a g e
AI 190160116087
a_star(Sit, Process) :-
s0(S0),
goal_situation(GoalSituation),
a_star(S0, GoalSituation, Sit-Answer),
reverse(Answer, Process).
a_star(StartSituation, GoalSituation, Answer) :-
% Create heap of open search nodes
heuristic_distance_to_goal(GoalSituation, StartSit
uation, D),
singleton_heap(Open, D, 0-StartSituation-[]),
% Do the search
a_star(Open, GoalSituation, [StartSituation], Answ
er).
a_star(Open, GoalSituation, Closed, Answer) :-
get_from_open_nodes(Open, AccCost-Sit-Process, Rem
ainingSearch),
( reached_goal(GoalSituation, Sit), Answer = Sit
-Process
29 | P a g e
AI 190160116087
OUTPUT
30 | P a g e
AI 190160116087
PRACTICAL 8
Aim: Write a program to solve N-Queens
problem using Prolog.
PROGRAM
queens(N, Queens) :-
length(Queens, N),
board(Queens, Board, 0, N, _, _),
queens(Board, 0, Queens).
constraints(0, _, _, _) :- !.
constraints(N, Row, [R|Rs], [C|Cs]) :-
arg(N, Row, R-C),
M is N-1,
constraints(M, Row, Rs, Cs).
queens([], _, []).
queens([C|Cs], Row0, [Col|Solution]) :-
Row is Row0+1,
select(Col-Vars, [C|Cs], Board),
arg(Row, Vars, Row-Row),
queens(Board, Row, Solution).
OUTPUT
31 | P a g e
AI 190160116087
32 | P a g e
AI 190160116087
PRACTICAL 9
Aim: Write a program to solve 8 puzzle
problem using Prolog.
PROGRAM
goal([1,2,3,
4,0,5,
6,7,8]).
move([X1,0,X3, X4,X5,X6, X7,X8,X9],
[0,X1,X3, X4,X5,X6, X7,X8,X9]).
move([X1,X2,0, X4,X5,X6, X7,X8,X9],
[X1,0,X2, X4,X5,X6, X7,X8,X9]).
33 | P a g e
AI 190160116087
34 | P a g e
AI 190160116087
OUTPUT
35 | P a g e
AI 190160116087
PRACTICAL 10
Aim: Write a program to solve travelling
salesman problem using Prolog.
PROGRAM
road(birmingham,bristol, 9).
road(london,birmingham, 3).
road(london,bristol, 6).
road(london,plymouth, 5).
road(plymouth,london, 5).
road(portsmouth,london, 4).
road(portsmouth,plymouth, 8).
OUTPUT
36 | P a g e
AI 190160116087
37 | P a g e
AI 190160116087
PRACTICAL 11
Aim: Develop an expert system for
medical diagnosis of childhood diseases
using prolog.
PROGRAM
:- use_module(library(jpl)).
start :-sleep(0.4),
write('
'),nl,
sleep(0.4),
write('***************************************
**************************'),nl,
sleep(0.2),
write("###################||| EXPERT SYSTEM ||
|#########################"),nl,
sleep(0.4),
write('***************************************
**************************'),nl,
sleep(0.4),
write('
'),nl,nl,nl,
interface2.
/* hypothesis(Patient,Disease),
write(Patient),write(', you '), write(' probab
ly have '),write(Disease),write('.'),undo,
nl,nl,nl,
sleep(0.7),
38 | P a g e
AI 190160116087
write('***************************************
**************************'),nl,
sleep(0.4),
write("################||| THANK YOU FOR USE M
E |||#####################"),nl,
sleep(0.4),
write('***************************************
**************************'),nl.*/
symptom(Patient,runny_nose) :- verify(Patient," ha
ve a runny_nose (y/n) ?").
symptom(Patient,conjunctivitis) :- verify(Patient,
" have a conjunctivitis (y/n) ?").
symptom(Patient,sore_throat) :- verify(Patient," h
ave a sore_throat (y/n) ?").
39 | P a g e
AI 190160116087
symptom(Patient,swollen_glands) :- verify(Patient,
" have a swollen_glands (y/n) ?").
hypothesis(Patient,measles) :-
symptom(Patient,fever),
symptom(Patient,cough),
symptom(Patient,conjunctivitis),
symptom(Patient,runny_nose),
symptom(Patient,rash).
hypothesis(Patient,german_measles) :-
symptom(Patient,fever),
symptom(Patient,headache),
symptom(Patient,runny_nose),
symptom(Patient,rash).
hypothesis(Patient,flu) :-
symptom(Patient,fever),
symptom(Patient,headache),
symptom(Patient,body_ache),
symptom(Patient,conjunctivitis),
symptom(Patient,chills),
symptom(Patient,sore_throat),
symptom(Patient,runny_nose),
symptom(Patient,cough).
hypothesis(Patient,common_cold) :-
symptom(Patient,headache),
40 | P a g e
AI 190160116087
symptom(Patient,sneezing),
symptom(Patient,sore_throat),
symptom(Patient,runny_nose),
symptom(Patient,chills).
hypothesis(Patient,mumps) :-
symptom(Patient,fever),
symptom(Patient,swollen_glands).
hypothesis(Patient,chicken_pox) :-
symptom(Patient,fever),
symptom(Patient,chills),
symptom(Patient,body_ache),
symptom(Patient,rash).
hypothesis(Patient,measles) :-
symptom(Patient,cough),
symptom(Patient,sneezing),
symptom(Patient,runny_nose).
response(Reply) :-
read(Reply),
write(Reply),nl.
ask(Patient,Question) :-
write(Patient),write(', do you'),write(Question),
/*read(N),
( (N == yes ; N == y)
->
assert(yes(Question)) ;
assert(no(Question)), fail),*/
interface(', do you',Patient,Question),
41 | P a g e
AI 190160116087
write('Loading.'),nl,
sleep(1),
write('Loading..'),nl,
sleep(1),
write('Loading...'),nl,
sleep(1),
nl.
:- dynamic yes/1,no/1.
verify(P,S) :-
(yes(S)
->
true ;
(no(S)
->
fail ;
ask(P,S))).
undo :- retract(yes(_)),fail.
undo :- retract(no(_)),fail.
undo.
pt(Patient):-
hypothesis(Patient,Disease),
interface3(Patient,', you probably have ',Dise
ase,'.'),
write(Patient),write(', you probably have '),w
rite(Disease),write('.'),undo,end.
end :-
nl,nl,nl,
sleep(0.7),
write('***************************************
**************************'),nl,
42 | P a g e
AI 190160116087
sleep(0.4),
write("################||| THANK YOU FOR USE M
E |||#####################"),nl,
sleep(0.4),
write('***************************************
**************************'),nl.
interface(X,Y,Z) :-
atom_concat(Y,X, FAtom),
atom_concat(FAtom,Z,FinalAtom),
jpl_new('javax.swing.JFrame', ['Expert System'], F
),
jpl_new('javax.swing.JLabel',['--- MEDICAL EXPERT
SYSTEM ---'],LBL),
jpl_new('javax.swing.JPanel',[],Pan),
jpl_call(Pan,add,[LBL],_),
jpl_call(F,add,[Pan],_),
jpl_call(F, setLocation, [400,300], _),
jpl_call(F, setSize, [400,300], _),
jpl_call(F, setVisible, [@(true)], _),
jpl_call(F, toFront, [], _),
jpl_call('javax.swing.JOptionPane', showInputDialo
g, [F,FinalAtom], N),
jpl_call(F, dispose, [], _),
write(N),nl,
( (N == yes ; N == y)
->
assert(yes(Z)) ;
assert(no(Z)), fail).
interface2 :-
jpl_new('javax.swing.JFrame', ['Expert System'], F
),
jpl_new('javax.swing.JLabel',['--- MEDICAL EXPERT
SYSTEM ---'],LBL),
jpl_new('javax.swing.JPanel',[],Pan),
43 | P a g e
AI 190160116087
jpl_call(Pan,add,[LBL],_),
jpl_call(F,add,[Pan],_),
jpl_call(F, setLocation, [400,300], _),
jpl_call(F, setSize, [400,300], _),
jpl_call(F, setVisible, [@(true)], _),
jpl_call(F, toFront, [], _),
jpl_call('javax.swing.JOptionPane', showInputDialo
g, [F,'Hi. How are you? First of all tell me your name
please'], N),
jpl_call(F, dispose, [], _),
/*write(N),nl,*/
( N == @(null)
-> write('you cancelled'),interface3('you can
celled. ','Thank you ','for use ','me.'),end,fail
; write("Hi. How are you? First of all tell
me your name please : "),write(N),nl,pt(N)
).
interface3(P,W1,D,W2) :-
atom_concat(P,W1, A),
atom_concat(A,D,B),
atom_concat(B,W2,W3),
jpl_new('javax.swing.JFrame', ['Expert System'], F
),
jpl_new('javax.swing.JLabel',['--- MEDICAL EXPERT
SYSTEM ---'],LBL),
jpl_new('javax.swing.JPanel',[],Pan),
jpl_call(Pan,add,[LBL],_),
jpl_call(F,add,[Pan],_),
jpl_call(F, setLocation, [400,300], _),
jpl_call(F, setSize, [400,300], _),
jpl_call(F, setVisible, [@(true)], _),
jpl_call(F, toFront, [], _),
jpl_call('javax.swing.JOptionPane', showMessageDia
log, [F,W3], N),
44 | P a g e
AI 190160116087
45 | P a g e
AI 190160116087
OUTPUT
46 | P a g e
AI 190160116087
47 | P a g e
AI 190160116087
48 | P a g e
AI 190160116087
49 | P a g e
AI 190160116087
50 | P a g e
AI 190160116087
51 | P a g e