For the last couple of months I have been working on a rule-based lemmatizer for the KU Leuven's CCL. It isn't language specific, but the language I had in mind developing is Dutch, and there exists only one ruleset at the moment---for Dutch, of course. Surprisingly, it actually works, which is quite odd if you think about my non-existing Dutch skills.
Anyway, I wrote my program in Lisp, while the rest of CCL works in Perl. This was sort of a problem, because delivering executables in SBCL is funny, and I don't know any smart way of compiling libraries so that they can be called from other languages. Also, loading all Common Lisp and a few libraries just to lemmatize a small token would be a bit impractical.
So, I had to find a way of letting Python, Perl and friends to talk with my lispy lemmatizer. Maciek suggested me I could use XML-RPC, and that was a good idea. I asdf-installed S-XML-RPC, wrote the server, wrote a client in Python (to see if it really works), and everything seemed fine.
It seemed so until a couple of days ago, when I wrote the Perl client. My Perl skills are as impressing as my Dutch skills, but this didn't ruin my self-confidence. After all, I just had written a whole lemmatizer for Dutch, so a tiny script in a language I don't know shouldn't be a challenge.
And at first it wasn't. I downloaded the right library, had them installed. I wrote what I thought I should have written, and there weren't any syntax errors. But then I run it, and all I could get was “Bad request.”
Well, I took another XML-RPC Perl library, wrote what the tutorials said I should have written... And got the same frustrating “Bad request.”
Well, I tried lots of tricks. I threatened the computer with a screw-driver. I read the Perl source. I made the XML requests be printed, and run them through Python and Lisp---successfully. As for Perl---nothing better than “Bad request.”
Finally, when looking through the source of S-XML-RPC, I found it is checking whether the URL is ending with “/RPC2”. I change appropriately the URL... And it started working. With both libraries. Apparently, Lisp and Python libraries were doing that implicitly, but Perl was too straight forward for it.
In principle the whole affair wasn't Perl's fault---the XML-RPC specification doesn't specify how should the first line of the request look like. On the other hand, life would be a lot easier if Perl libraries did what other expect them to do. Like the Python version ;-)
Friday, June 15, 2007
Abductive reasoning
During my first semester in KU Leuven I took a course “Logic as Foundations for AI”. There were only 4 participants, so instead of taking we could prepare an assignment.
One of the exercises consisted of performing some abductive reasoning, about boolean circuits where some logical gates could be broken (there were ~5 gates in the circuit). And it was tedious... And I was always making an error somewhere... So I decided: “enough is enough,” and wrote a Prolog program to solve this task for me.
And it was a great success: it took me only a day to write a program that solves a task it would take two hours to solve it (provided you were extremely pedantic).
(However, I've included my program into the assignment and I suspect it may have boosted the mark I received.) ;-)
One of the exercises consisted of performing some abductive reasoning, about boolean circuits where some logical gates could be broken (there were ~5 gates in the circuit). And it was tedious... And I was always making an error somewhere... So I decided: “enough is enough,” and wrote a Prolog program to solve this task for me.
And it was a great success: it took me only a day to write a program that solves a task it would take two hours to solve it (provided you were extremely pedantic).
(However, I've included my program into the assignment and I suspect it may have boosted the mark I received.) ;-)
:- op(1200, xfx, ====>).
% Give all the possible explanations for Goal in KB, as conjunctive clauses
explanations(Goal, KB, Explanations) :-
prime_implicates(KB, Implications),
no_goal(Goal, Implications, NoGs),
findall(Explanation, (member(X, NoGs), negate_all(X, Explanation)), Explanations).
% find all the prime implicates from KB
prime_implicates(KB, Implicates) :-
resolution(KB, Cons),
findall(Imp, (member(Imp, Cons), prime_implicate_(Imp, Cons)), Implicates).
prime_implicate_(_, []).
prime_implicate_(I, [H|Set]) :-
( \+subset(H,I)
; I ==H),
prime_implicate_(I, Set).
% resolution(KB, AllResolvents).
resolution(List, Solution) :-
% we have to sort the clauses in order to obtain the
% “canonical” form (useful to remove duplicates).
findall(Sorted, (member(L,List), sort(L,Sorted)), SortedList),
resolution2(SortedList, Solution).
resolution2(List,Solution) :-
member(A, List),
member(B, List),
A \==B,
print(A),
resolve(A, B, R1),
sort(R1, R),
\+ smember(R, List),
pretty(A,B,R),
resolution2([R|List], Solution)
;
List=Solution.
resolve(XX,YY,Z) :-
new_var(XX,X),
new_var(YY,Y),
member(Rx,X),
member(Ry, Y),
% ( Rx=not(Ry)
% ; Ry=not(Rx)),
% We must use sound unification (no cyclic terms)
( unify_with_occurs_check(Rx, not(Ry))
; unify_with_occurs_check(Ry, not(Rx))),
select(Ry,Y, NewY),
select(Rx, X, NewX),
sunion(NewX, NewY, Z).
% prover by resolution for Horn Clauses
% hresolution(+Goal, +KB, -ResolutionTrail)
% prove Goal in KB
hresolution(Goal, KB, Sol) :-
negate(Goal, NG),
hresolution_(NG, KB, Sol).
hresolution_(_,[],[]).
hresolution_(X, KB, [X/Y====>Resolvent|Rest]) :-
member(Y,KB),
resolve(X,Y, Resolvent),
( Resolvent = [],
Rest=[]
;
select(Y,KB, NewKB),
hresolution_(Resolvent, NewKB, Rest)).
/* *************************
* *
* Tool predicates: *
* *
***************************/
% put brand new new variables in the clause
new_var(X,Y) :-
assert(p(X)),
retract(p(Y)).
pretty(A,B,C) :- print(A/B====>C), nl, nl.
% like select, but uses sound unification and succeeds if El is not in
% the List
minus(_, [], []).
minus(X, [X1|Tail], Tail) :-
sunifiable(X, X1).
minus(Elem, [Head|Tail], [Head|Rest]) :-
minus(Elem, Tail, Rest).
% sound-unifiable
sunifiable(X,Y) :-
\+ \+ unify_with_occurs_check(X,Y).
% like member, but tests identity instead of unification (we don't
% want to instantiate X in f(X) to 1 by checking if f(r) is already in
% the KB)
smember(X,[H|_]) :-
%X==H.
sunifiable(X, H).
smember(X, [_|Rest]) :-
smember(X, Rest).
sunion([], L, L1) :-
unify_with_occurs_check(L, L1),
!.
sunion([H|T], L, R) :-
smember(H, L), !,
sunion(T, L, R).
sunion([H|T], L, [H|R]) :-
sunion(T, L, R).
negate(not(X), X) :- !.
negate(X,not(X)).
% negate all literals in an disjunctive clause, giving a conjunctive clause
negate_all([],[]).
negate_all([H|T],[NH|NT]) :-
negate(H, NH),
negate_all(T, NT).
% eliminate the goal Goal form the clause
no_goal(_, [], []).
no_goal(Goal, [H|T], [NH|NT]) :-
minus(Goal, H, NH),
no_goal(Goal, T, NT).
test(Z):-
List = [
[not(tennis_elbow), sore_elbow],
[not(tennis_elbow), tennis_player],
[not(arthritis), treated, sore_joints],
[sore_elbow, not(sore_joints)],
[not(sore_joints), sore_hips]
],
List2 = [
[not(p), not(q), not(r), g],
[p, not(q), g],
[q, not(r), g]
],
explanations(g, List2,Z).
test_nonprovable(A) :-
List = [[p(X)], [p(X)]],
resolution(List, A).
test_plus(Solution, Result) :-
A=[
[rplus(W,0,W)],
[rplus(X, s(Y), s(Z)), not(rplus(X,Y,Z))]
],
Goal = [rplus(s(s(s(0))), s(s(0)), Result)],%s(s(s(s(s(0))))))],
hresolution(Goal, A, Solution).
Tuesday, April 03, 2007
A simple regular language recognizer
There are some programs that you just have to write in order to have the feeling that you know a bit of the programming language you are learning. For me such a program is a regular expression recognizer.
Both strings and regular expressions are represented by lists of Lisp symbols (a regexp description may be also a nested list)
Let me introduce my notation of regexp-s by example:
Both strings and regular expressions are represented by lists of Lisp symbols (a regexp description may be also a nested list)
Let me introduce my notation of regexp-s by example:
- (* a b c d) is the same as (a b c d)* in the usual notation
- (+ a b c d) is (a b c d)+
- (or a b c d) is (a|b|c|d)
(defun recognize (regexp string)
"T if string matches to regexp, nil otherwise."
(let ((end (list (gensym))))
(if (null regexp)
;; the language {\sigma} must be a special case because nil is
;; the value returned by reg-eval on failure
(null string)
(equal end (reg-eval regexp (append string end))))))
(defun reg-eval (regexp string)
"If string has a prefix matching regexp, returns the part that doesn't match (nil otherwise)."
(when string
(cond ((null regexp)
string)
((not (listp (car regexp)))
(when (equal (car string) (car regexp))
(reg-eval (cdr regexp) (cdr string))))
(t (let ((prefix (caar regexp))
(body (cdar regexp)))
(case prefix
((*)
(reg-eval (cdr regexp) (let ((match (reg-eval body string)))
(if (not match)
string
(reg-eval (list (car regexp)) match)))))
((+)
(reg-eval (nconc (list (cons 'subexp body) (cons '* body)) (cdr regexp)) string))
((or)
(some #'(lambda (x) (reg-eval x string)) body))
((subexp)
(reg-eval (cdr regexp) (reg-eval body string)))))))))
(defun test ()
(let ((cases '((recognize '(a b c d) '(a b c d))
(recognize '((* a b c)) '(a b c a b c))
(recognize '((or ((+ 1) 2) (2 1))) '(1 1 1 2))
(recognize '((or (1 2) (2 1))) '(1 2)))))
(dolist (cas cases)
(format t "~&~s => ~s." cas (eval cas)))))
Tuesday, March 06, 2007
Lisprolog
As someone has observed on comp.lang.prolog, there's a strange tendency among Lisp enthusiasts (some of whom I profoundly respect) to enthusiastically depreciate Prolog. Symptomatic for this imperialistic approach are the lots of toy Prolog interpreters written in Lisp you can find in the Internet (just try google).
For a long time, poor Prolog guys didn't have a good answer. However, this annoying situation has changed, thanks to Marcus Triska. Let me present, ladies and gentlemen, Lisprolog, the toy Lisp interpreter written in Prolog! It's very small (~200 lines of code), very clean and very neat. Maybe the language in it is a bit underimplemented, but that seems to be a part of the joke (a really complete implementation wouldn't be a good revenge for all that toy interpreters).
Personally, I find Lisprolog absolutely cute. I like very much both Lisp and Prolog, and implementing some of the missing features seems like a good exercise, allowing to learn something about Lisp and not forget Prolog, at the same time (I am reading Essentials of Programming Languages by Friedman, Wand & Haynes at the moment).
For a long time, poor Prolog guys didn't have a good answer. However, this annoying situation has changed, thanks to Marcus Triska. Let me present, ladies and gentlemen, Lisprolog, the toy Lisp interpreter written in Prolog! It's very small (~200 lines of code), very clean and very neat. Maybe the language in it is a bit underimplemented, but that seems to be a part of the joke (a really complete implementation wouldn't be a good revenge for all that toy interpreters).
Personally, I find Lisprolog absolutely cute. I like very much both Lisp and Prolog, and implementing some of the missing features seems like a good exercise, allowing to learn something about Lisp and not forget Prolog, at the same time (I am reading Essentials of Programming Languages by Friedman, Wand & Haynes at the moment).
Sunday, March 04, 2007
Moving from wordpress to blogger
I have been maintaining my Polish blog on Wordpress.com server for more than half a year and become quite fed up of it. Paid upgrades, no access to the source of the style-sheet, and, last but not least, problems with logging in under firefox helped me a lot making my decision.
There's quite a lot written about moving your blog archive from blogger to wordpress. I, however, wanted to do just the opposite, which this turned to be a bit less trivial: Blogger is still beta and doesn't have any of the import/export facilities wordpress can be proud of.
Fortunately, I found a very nice python script which allowed me to make the move without any excessive pain: wordpress2blogger. Many thanks to the author!
There's quite a lot written about moving your blog archive from blogger to wordpress. I, however, wanted to do just the opposite, which this turned to be a bit less trivial: Blogger is still beta and doesn't have any of the import/export facilities wordpress can be proud of.
Fortunately, I found a very nice python script which allowed me to make the move without any excessive pain: wordpress2blogger. Many thanks to the author!
Thursday, December 07, 2006
Prolog and regular expressions
Some time ago I started writing a lemmatizer (i.e. a program that receives as input a word and some tags that describe it ad outputs the dictionary form of the word) for Dutch. I have been programming nearly exclusively in Prolog for the last three months, so the choice of language was quite obvious (also, I have the feeling that trying to write something serious in a new programming language helps you learn it a lot better than writing even a gazillion of text-book exercises). However, not everything was so simple. When you are doing any text-processing, you surely want to use regular expressions.
Both Prologs I usually use --SWI and Sicstus-- allow you of course to use DCG, but that was not quite what I was looking for. I wanted normal, Posix style regular expressions. First of all, it is what I know and I'm used to. Secondly, it is what the majority of people who will have anything to do with my program will be used to and will understand. And, last but not least, I don't really feel like writing and naming a new predicate every time I have to match something.
A good place for starting my quest for perl-style regexp was this. It is a quite extensive list of resources related to regular expressions. My first idea was finding a library that I could use with SWI or Sicstus. However (you may call me dumb) I didn't manage to compile or put to work any of the things I found on Van Nord's page. So, I decided to try to find a Prolog implementation that comes with regexp out of the box.
The two Prologs I tested were Ciao and Yap.
Ciao at first makes a good impression (even though it's web-page is *really* ugly), however, the regexp implemented are quite lame: the don't support extracting found groups (or at least I didn't find it), which rendered it quite useless.
In Yap (which stands for Yet Another Prolog and it's developed in Portugal), however, regexp finally worked. It's regexp library is a direct port of the FreeBSD regex library, so it's pleasantly plain and normal. The only drawback is that it is very poorly documented. For example, I spent quite a long time wondering who and why would implement regular expressions without back-references. And I would still wonder if not a lucky typo, which revealed that in Yap regexp you access groups found earlier not by a backslash followed by number, but by a *double* backslash followed by a number (maybe for some reason this should be obvious, but it wasn't for me).
So, if you want to have a regular expression that matches all strings of the form "X=X", where X may be any string, you have to write:
Apart from that strange incident, Yap turned to be a nice and fast Prolog implementation. I appreciate especially the SWI-Prolog compatibility module, which allows me to write exactly the way I'm used to (btw, there also exists a SICstus compatibility module). It's only a pity that Yap depends on some non-free elements (exactly, “free for non-commercial use”) which causes that Yap binaries aren't shipped in any major Linux distribution.
(Oh, and one last problem---the binaries from binaries.tar.gz crash after you try to import the library regexp... Luckily, the RPM version for Fedora works fine on Ubuntu, after you convert it to DEB with alien.)
Both Prologs I usually use --SWI and Sicstus-- allow you of course to use DCG, but that was not quite what I was looking for. I wanted normal, Posix style regular expressions. First of all, it is what I know and I'm used to. Secondly, it is what the majority of people who will have anything to do with my program will be used to and will understand. And, last but not least, I don't really feel like writing and naming a new predicate every time I have to match something.
A good place for starting my quest for perl-style regexp was this. It is a quite extensive list of resources related to regular expressions. My first idea was finding a library that I could use with SWI or Sicstus. However (you may call me dumb) I didn't manage to compile or put to work any of the things I found on Van Nord's page. So, I decided to try to find a Prolog implementation that comes with regexp out of the box.
The two Prologs I tested were Ciao and Yap.
Ciao at first makes a good impression (even though it's web-page is *really* ugly), however, the regexp implemented are quite lame: the don't support extracting found groups (or at least I didn't find it), which rendered it quite useless.
In Yap (which stands for Yet Another Prolog and it's developed in Portugal), however, regexp finally worked. It's regexp library is a direct port of the FreeBSD regex library, so it's pleasantly plain and normal. The only drawback is that it is very poorly documented. For example, I spent quite a long time wondering who and why would implement regular expressions without back-references. And I would still wonder if not a lucky typo, which revealed that in Yap regexp you access groups found earlier not by a backslash followed by number, but by a *double* backslash followed by a number (maybe for some reason this should be obvious, but it wasn't for me).
So, if you want to have a regular expression that matches all strings of the form "X=X", where X may be any string, you have to write:
   ?- use_module(library(regexp)).
   ?- regexp("^(.+)=\\1$", "a=a", []).
yes
Apart from that strange incident, Yap turned to be a nice and fast Prolog implementation. I appreciate especially the SWI-Prolog compatibility module, which allows me to write exactly the way I'm used to (btw, there also exists a SICstus compatibility module). It's only a pity that Yap depends on some non-free elements (exactly, “free for non-commercial use”) which causes that Yap binaries aren't shipped in any major Linux distribution.
(Oh, and one last problem---the binaries from binaries.tar.gz crash after you try to import the library regexp... Luckily, the RPM version for Fedora works fine on Ubuntu, after you convert it to DEB with alien.)
Thursday, November 16, 2006
Sudoku
In the last week Prolog classes writing a sudoku solver was one of the exercises. Of course, this is not such a small task, so we concentrated on writing just a part of the solver. However, when I came home I felt the very strange feeling that I want to write my own sudoku solver. So here it is.
The representation I chose is a bit different from the ones I have seen in class and in the Internet. It is neither an array (Prolog emulation of an array using arg/3) of numbers, nor a plain list of numbers. It is a list of triples of the form X/Y/Value, where X and Y are the horizontal/vertical coordinates, and Value the number in the square. At first such a representation may seem a bit strange. However, it allows us (for example) to extract whole columns and rows through unification, which simplifies things a bit.
I have written the whole program with readability and conceptual simplicity in mind. This means it is not very efficient. I planned it to be as general as possible, so in principle it should be able to sort 27x27 sudoku. However, due to the lack of efficiency this may take quite a long time (provided you had a 27x27 grid partially filled with integers from 1 to 81, of course).
I also wrote print_su/1, a sudoku pretty-printer. It is not very interesting, and I used findall/3 to iterate through a list and print its elements (which may be considered abusive), so I decided not to publish it here :).
Now, we can use Prolog to run the following query:
and voilĂ , your sudoku is ready!
(I think that it may be sensible using constraint logic programming for solving sudoku... However, I haven't reached the chapter about CLP in my book yet, so I didn't use it. ;-))
The representation I chose is a bit different from the ones I have seen in class and in the Internet. It is neither an array (Prolog emulation of an array using arg/3) of numbers, nor a plain list of numbers. It is a list of triples of the form X/Y/Value, where X and Y are the horizontal/vertical coordinates, and Value the number in the square. At first such a representation may seem a bit strange. However, it allows us (for example) to extract whole columns and rows through unification, which simplifies things a bit.
I have written the whole program with readability and conceptual simplicity in mind. This means it is not very efficient. I planned it to be as general as possible, so in principle it should be able to sort 27x27 sudoku. However, due to the lack of efficiency this may take quite a long time (provided you had a 27x27 grid partially filled with integers from 1 to 81, of course).
%
% all the elements in a column, row, 3x3 box.
%
column(X/_, Sudoku, Column) :-
findall(X/Y/Z , (member(X/Y/Z, Sudoku), nonvar(Z)), Column).
row(_/Y, Sudoku, Row) :-
findall(X/Y/Z, (member(X/Y/Z, Sudoku), nonvar(Z)), Row).
% believe me or not, this was the most difficult predicate to write.
box(Base, X/Y, Sudoku, Box) :- % Base: size of the puzzle
DiffX is (X-1) mod (Base/3),
DiffY is (Y-1) mod (Base/3),
StartX is X - DiffX,
StartY is Y - DiffY,
EndX is StartX + (Base/3) - 1,
EndY is StartY + (Base/3)-1,
findall(X1/Y1/Z,
(
between(StartX,EndX,X1),
between(StartY, EndY, Y1),
member(X1/Y1/Z, Sudoku),
nonvar(Z)
),
Box).
%
% We can assign the value Possible to X/Y without
% violating the rules of the sudoku.
%
possible(_,X/Y/Possible, Sudoku) :-
member(X/Y/Possible, Sudoku),
nonvar(Possible), !.
possible(Base, X/Y/Possible, Sudoku) :-
column(X/Y, Sudoku, Column),
row(X/Y, Sudoku, Row),
box(Base, X/Y, Sudoku, Box),
between(1,Base, Possible),
\+member(_/_/Possible, Column),
\+member(_/_/Possible, Row),
\+member(_/_/Possible, Box).
% solve the puzzle, iterating through each grid
solve(_,N,N,_).
solve(Base,N,K,Solution) :-
nth1(N, Solution, X/Y/Z),
possible(Base, X/Y/Z, Solution),
NewN is N+1,
solve(Base, NewN, K, Solution).
solve(Base,Solution) :-
N is Base*Base+1,
solve(Base,1, N, Solution).
% the main predicate
%
sudoku(Base,Constraints, Solution) :-
findall(X/Y/_, (between(1,Base,X), between(1,Base,Y)), Solution),
subset(Constraints, Solution),
solve(Base,Solution).
/*
And some example puzzles to solve:
*/
s3([3/1/3, 2/2/8,
5/1/4, 4/2/6, 6/2/3, 4/3/5,
8/1/9, 8/3/4,
1/4/5, 1/6/2, 3/6/7,
4/4/9, 5/4/1, 4/5/2, 6/5/7, 5/6/8, 6/6/6,
7/4/3, 9/4/7, 9/6/5,
2/7/3, 2/9/5,
4/8/7, 5/9/6, 6/7/5, 6/8/1,
7/9/4, 8/8/5]).
% the sudoku from class
s1([1/4/2, 1/5/3, 1/9/5,
2/2/4, 2/3/2, 2/5/9, 2/9/3,
3/1/3, 3/6/8, 3/7/7,
4/3/7, 4/8/5, 4/9/6,
5/2/9, 5/4/7, 5/5/2, 5/8/1, 5/9/4,
6/1/5, 6/4/9,
7/1/6, 7/6/2, 7/7/8, 7/8/4, 7/9/9,
8/3/8, 8/6/1, 8/9/7,
9/1/2, 9/2/5, 9/6/9, 9/7/6]).
s2([4/1/2, 5/1/3, 9/1/5,
2/2/4, 3/2/2, 5/2/9, 9/2/3,
1/3/3, 6/3/8, 7/3/7,
3/4/7, 8/4/5, 9/4/6,
2/5/9, 4/5/7, 5/5/2, 8/5/1, 9/5/4,
1/6/5, 4/6/9,
1/7/6, 6/7/2, 7/7/8, 8/7/4, 9/7/9,
3/8/8, 6/8/1, 9/8/7,
1/9/2, 2/9/5, 6/9/9, 7/9/6]).
I also wrote print_su/1, a sudoku pretty-printer. It is not very interesting, and I used findall/3 to iterate through a list and print its elements (which may be considered abusive), so I decided not to publish it here :).
Now, we can use Prolog to run the following query:
?- s1(Constraints),sudoku(9,Constraints,Sudoku), print_su(Sudoku).
1 7 3 || 4 8 5 || 6 9 2
8 4 6 || 2 9 1 || 7 3 5
9 2 5 || 7 6 3 || 1 8 4
==============================
2 5 4 || 1 7 9 || 3 6 8
3 9 1 || 8 2 6 || 5 4 7
7 6 8 || 3 5 4 || 2 1 9
==============================
4 1 7 || 9 3 2 || 8 5 6
6 8 9 || 5 1 7 || 4 2 3
5 3 2 || 6 4 8 || 9 7 1
Constraints = [1/4/2, 1/5/3, 1/9/5, 2/2/4, 2/3/2, 2/5/9, 2/9/3, ... /... /3, ... /...|...]
Sudoku = [1/1/1, 1/2/8, 1/3/9, 1/4/2, 1/5/3, 1/6/7, 1/7/4, ... /... /6, ... /...|...]
and voilĂ , your sudoku is ready!
(I think that it may be sensible using constraint logic programming for solving sudoku... However, I haven't reached the chapter about CLP in my book yet, so I didn't use it. ;-))
Subscribe to:
Comments (Atom)
 
