/*****************************************************************************/ /* THE CONVERSION OF THE XML SPECIFICATION INTO PROLOG */ /*****************************************************************************/ /* The converter translates specifications structured under the the data type definition (DTD) contained in a separate file. We assume that the specification of some statute may be a very long text therefore the program reads, recognises and translates the input text in portions. One portion may be: a) the initial portion together with the first ELEMENT of the specification (it ends with the marker ), b) a portion containing the next ELEMENT, c) the final portion (the text after the last ELEMENT of the specification). The program is initiated by means of the procedure 'start'. A window with two areas of edition and with two pull down menus is displayed. In the 'File' menu, the operations on files are provided. By means of the 'Operation' menu it is possible to start the lexical analyser or the syntax analyser. The lexical analysis is performed on the text situated in the upper editing area and the result is generated into the lower editing area. The syntax analyser works on the text situated in the lower editing area and generates the result into the file 'result.txt' and into the lower editing area. In the case a syntax error appeared in some portion of the text, the wrong portion and the comment is displayed in the lower editing area*/ /*****************************************************************************/ /* DIALOG ENVIRONMENT MODULE */ /*****************************************************************************/ :- pce_autoload(finder,library(find_file)). :- pce_global(@finder,new(finder)). start:- new(@frame,frame('Translator')), send(@frame,append,new(D,dialog)), send(new(@view1,view),below,D), send(new(@view2,view),below,@view1), send(@view1,font,font(win, system)), send(@view2,font,font(win, system)), send(@view1,wrap,word), send(@view2,wrap,word), send(D,append,new(MB,menu_bar)), send(MB,append,new(File,popup(file))), send(MB,append,new(Operation,popup(operation))), send_list(File,append, [menu_item(open,message(@prolog,openfile)), menu_item('save upper',message(@prolog,savefile1)), menu_item('save lower',message(@prolog,savefile2)), menu_item('clear both',message(@prolog,clearview)), menu_item(quit,message(@prolog,quit))]), send_list(Operation,append, [menu_item('lexical analysis',message(@prolog,la_start)), menu_item('translation',message(@prolog,t_start))]), send(@frame,open), send(@frame,status,full_screen). openfile:- get(@finder,file,@on,txt,Opfile), send(@view1,load,Opfile). savefile1:- get(@finder,file,@off,txt,Clfile), send(@view1,save,Clfile). savefile2:- get(@finder,file,@off,txt,Clfile), send(@view2,save,Clfile). clearview:- send(@view1,clear), send(@view2,clear). quit:- send(@frame,destroy). /**************************************************************************/ /* SYNTAX ANALYSIS AND TRANSLATION MODULE */ /**************************************************************************/ t_start:- pce_open(@view2,read,H1), open('result.txt',write,H2), read_portion(H1,[],L1), remove_blank(L1,L), catch(statute(Res,Option,Signal,L,[]),_,Signal=error), generate(H2,Res,L1,Signal), read_generate(H1,H2,Option,Signal), close(H1), close(H2), send(@view2,clear), send(@view2,load,'result.txt'). read_generate(_,_,_,error):-!. read_generate(_,_,_,stop):-!. read_generate(H1,H2,Option,_):- read_portion(H1,[],L1), remove_blank(L1,L), catch(text_portion(Res,Option,Signal,L,[]),_,Signal=error), generate(H2,Res,L1,Signal), read_generate(H1,H2,Option,Signal). read_portion(H,L1,L):- read(H,W), L2 = [W|L1], read1(H,L2,L). read1(_,L1,[]):- eof_list(L1),!. read1(_,L1,L):- end(L1),!, reverse(L1,L). read1(H,L1,L):- read_portion(H,L1,L). end([p(62),w("ELEMENT"),p(47),p(60)|_]):-!. end([p(62),w("STATUTE"),p(47),p(60)|_]). eof_list([end_of_file|_]). remove_blank([],[]):-!. remove_blank([b(_)|R1],R):-!, remove_blank(R1,R). remove_blank([E|R1],[E|R]):- remove_blank(R1,R). generate(H,_,L1,error):-!, nl(H), write(H,'Syntax error in the following text portion:'), nl(H),nl(H), writing(H,L1). generate(_,[],_,_):-!. generate(H,[E|R],_,_):- generate1(H,E,[quoted(true)]), write(H,'.'), nl(H), generate(H,R,[],ok). generate1(H,statute(X,Y,Z),O):-!, string_to_list(S,Z), write_term(H,statute(X,Y,S),O). generate1(H,full_text(X,Y),O):-!, string_to_list(S,Y), write_term(H,full_text(X,S),O). generate1(H,cla(He,true),O):-!, write_term(H,He,O). generate1(H,cla(He,Bo),O):-!, write_term(H,He:-Bo,O). generate1(H,E,O):- write_term(H,E,O). tra_term(Sterm,Term):- string_to_atom(Sterm,A), term_to_atom(Term,A). append3(X1,X2,X3,R):- append(X1,X2,R1), append(R1,X3,R). appendli([],[]):-!. appendli([E|L],Res):- appendli(L,Res1), append(E,Res1,Res). add_quotation(R1,R):- appendli([[34],R1,[34]],R). add_apostrophes(R1,R):- appendli([[39],R1,[39]],R). writing(_,[]). writing(H,[E|R]):- writing1(H,E), writing(H,R). writing1(H,w(L)):-!, put_list(H,L). writing1(H,n(L)):-!, put_list(H,L). writing1(H,b(L)):-!, put_list(H,L). writing1(H,s(L)):-!, put(H,'"'), put_list(H,L), put(H,'"'). writing1(H,t(L)):-!, put(H,'#'), put_list(H,L), put(H,'#'). writing1(H,p(P)):- put(H,P). put_list(_,[]):-!. put_list(H,[E|L]):- put(H,E), put_list(H,L). numerical([E|R]):- digit(E), empty_num(R). empty_num([]):-!. empty_num([E|R]):- digit(E), empty_num(R). ident([E|R]):- letter(E), identre(R). identre([]):-!. identre([E|R]):- letter(E),!, identre(R). identre([E|R]):- digit(E), identre(R). /*****************************************************************************/ /* Grammar of the initial portion of the text */ /* (including the first ELEMENT of the specification) */ /*****************************************************************************/ statute(Res,Option,ok)--> beg_marker("STATUTE"), statute_option(Res,Option). statute([],error,error,_,[]). statute_option(Res,main)--> statute_main(Res). statute_option(Res,amending)--> statute_amending(Res). statute_option(Res,introductory)--> statute_introductory(Res). statute_main(Res)--> beg_marker_atr("MAIN_STATUTE"), attribute("NR",nmtoken,required,Res1), attribute("NAME",cdata,required,Res2), end_marker_atr, element(Res3), {add_quotation(Res2,Res4), appendli(["statute(",Res1,",main,",Res4,")"],R1), tra_term(R1,T1), append([T1],Res3,Res)}. statute_amending(Res)--> beg_marker_atr("AMENDING_STATUTE"), attribute("NR",nmtoken,required,Res1), attribute("NAME",cdata,required,Res2), attribute("AMENDS",nmtoken,required,Res3), end_marker_atr, element(Res4), {add_quotation(Res2,Res5), appendli(["statute(",Res1,",amending,",Res5,")"],R1), appendli(["amends(",Res1,",",Res3,")"],R2), tra_term(R1,T1), tra_term(R2,T2), append3([T1],[T2],Res4,Res)}. statute_introductory(Res)--> beg_marker_atr("INTRODUCTORY_STATUTE"), attribute("NR",nmtoken,required,Res1), attribute("NAME",cdata,required,Res2), attribute("INTRODUCES",nmtoken,required,Res3), end_marker_atr, element(Res4), {add_quotation(Res2,Res5), appendli(["statute(",Res1,",introductory,",Res5,")"],R1), appendli(["introduces(",Res1,",",Res3,")"],R2), tra_term(R1,T1), tra_term(R2,T2), append3([T1],[T2],Res4,Res)}. element(Res)--> beg_marker("ELEMENT"), provision_text(Res1), provision_name(Res2), meta_norms(Res3), end_marker("ELEMENT"), {append3(Res1,Res2,Res3,Res)}. provision_text(Res)--> beg_marker_atr("PROVISION_TEXT"), attribute("TEXT_ID",cdata,required,Res1), end_marker_atr, pcdata(Res2), end_marker("PROVISION_TEXT"), {add_quotation(Res2,Res3), appendli(["full_text(",Res1,",",Res3,")"],R1), tra_term(R1,T), Res = [T]}. provision_name(Res)--> beg_marker_atr("PROVISION_NAME"),!, attribute("PROVISION_ID",cdata,required,Res1), end_marker_atr, pcdata(Res2), end_marker("PROVISION_NAME"), {add_apostrophes(Res2,Res3), appendli(["index(",Res1,",",Res3,")"],R1), tra_term(R1,T), Res = [T]}. provision_name([])-->[]. meta_norms(Res)--> beg_marker("META_NORMS"), meta_norms_seq(Res), end_marker("META_NORMS"). meta_norms_seq(Res)--> ia_meta_norm(Res). meta_norms_seq(Res)--> da_meta_norm(Res). meta_norms_seq(Res)--> ia_meta_norm(Res1), meta_norms_seq(Res2), {append(Res1,Res2,Res)}. meta_norms_seq(Res)--> da_meta_norm(Res1), meta_norms_seq(Res2), {append(Res1,Res2,Res)}. ia_meta_norm(Res)--> beg_marker_atr("IA_META_NORM"), attribute("PROVISION_ID",cdata,required,Res1), attribute("EVENT",cdata,required,Res2), attribute("CONDITIONS",cdata,required,Res3), end_marker_atr, inst_action(Res4), end_marker("IA_META_NORM"), {appendli(["cla(mn(",Res1,",",Res2,",",Res4,"),",Res3,")"],R1), tra_term(R1,T), Res = [T]}. da_meta_norm(Res)--> beg_marker_atr("DA_META_NORM"), attribute("PROVISION_ID",cdata,required,Res1), attribute("EVENT",cdata,required,Res2), attribute("CONDITIONS",cdata,required,Res3), attribute("LIMITARY_EVENT",cdata,required,Res4), attribute("LIM_EVENT_DESCRIPTION",nmtoken,required,Res5), end_marker_atr, durative_action(Res6), end_marker("DA_META_NORM"), {appendli(["cla(mn(",Res1,",",Res2,",",Res4,",",Res5,",", Res6,"),",Res3,")"],R1), tra_term(R1,T), Res = [T]}. inst_action(Res)--> beg_marker("INSTANTANEOUS_ACTION"), ia_option(Res), end_marker("INSTANTANEOUS_ACTION"). ia_option(Res)--> provision_enactment(Res). ia_option(Res)--> suspended_provision_enactment(Res). ia_option(Res)--> provision_change(Res). ia_option(Res)--> statute_repealing(Res). ia_option(Res)--> provision_repealing(Res). ia_option(Res)--> prolongated_provision_repealing(Res). ia_option(Res)--> retroactivity_recording(Res). ia_option(Res)--> limit_event_time_change(Res). provision_enactment(Res)--> beg_marker_atr("PROVISION_ENACTMENT"), attribute("PROVISION_ID",cdata,required,Res1), attribute("TEXT",cdata,required,Res2), attribute("NEW_FACTS",cdata,required,Res3), end_marker_atr_end, {appendli(["provision_enactment(",Res1,",",Res2,",",Res3,")"],Res)}. suspended_provision_enactment(Res)--> beg_marker_atr("SUSPENDED_PROVISION_ENACTMENT"), attribute("PROVISION_ID",cdata,required,Res1), attribute("TEXT",cdata,required,Res2), attribute("NEW_FACTS",cdata,required,Res3), end_marker_atr_end, {appendli(["suspended_provision_enactment(",Res1,",",Res2,",", Res3,")"],Res)}. provision_change(Res)--> beg_marker_atr("PROVISION_CHANGE"), attribute("PROVISION_ID",cdata,required,Res1), attribute("TEXT",cdata,required,Res2), end_marker_atr_end, {appendli(["provision_change(",Res1,",",Res2,")"],Res)}. statute_repealing(Res)--> beg_marker_atr("STATUTE_REPEALING"), attribute("STATUTE_NR",nmtoken,required,Res1), end_marker_atr_end, {appendli(["statute_repealing(",Res1,")"],Res)}. provision_repealing(Res)--> beg_marker_atr("PROVISION_REPEALING"), attribute("PROVISION_ID",cdata,required,Res1), end_marker_atr_end, {appendli(["provision_repealing(",Res1,")"],Res)}. prolongated_provision_repealing(Res)--> beg_marker_atr("PROLONGATED_PROVISION_REPEALING"), attribute("PROVISION_ID",cdata,required,Res1), end_marker_atr_end, {appendli(["prolongated_provision_repealing(",Res1,")"],Res)}. retroactivity_recording(Res)--> beg_marker_atr("RETROACTIVITY_RECORDING"), attribute("PROVISION_ID",cdata,required,Res1), end_marker_atr_end, {appendli(["retroactivity_recording(",Res1,")"],Res)}. limit_event_time_change(Res)--> beg_marker_atr("LIMIT_EVENT_TIME_CHANGE"), attribute("LIMITARY_EVENT",cdata,required,Res1), attribute("LIM_EVENT_DESCRIPTION",nmtoken,required,Res2), end_marker_atr_end, {appendli(["limit_event_time_change(",Res1,",",Res2,")"],Res)}. durative_action(Res)--> beg_marker("DURATIVE_ACTION"), da_option(Res), end_marker("DURATIVE_ACTION"). da_option(Res)--> temporary_holding_in_force(Res). da_option(Res)--> vacatio_legis(Res). da_option(Res)--> provision_prolongation(Res). da_option(Res)--> provision_suspension(Res). da_option(Res)--> retroactive_provision_enactment(Res). temporary_holding_in_force(Res)--> beg_marker_atr("TEMPORARY_HOLDING_IN_FORCE"), attribute("STATUTE_NR",nmtoken,required,Res1), end_marker_atr_end, {appendli(["temporary_holding_in_force(",Res1,")"],Res)}. vacatio_legis(Res)--> beg_marker_atr("VACATIO_LEGIS"), attribute("STATUTE_NR",nmtoken,required,Res1), end_marker_atr_end, {appendli(["vacatio_legis(",Res1,")"],Res)}. provision_prolongation(Res)--> beg_marker_atr("PROVISION_PROLONGATION"), attribute("PROVISION_ID",cdata,required,Res1), end_marker_atr_end, {appendli(["provision_prolongation(",Res1,")"],Res)}. provision_suspension(Res)--> beg_marker_atr("PROVISION_SUSPENSION"), attribute("PROVISION_ID",cdata,required,Res1), end_marker_atr_end, {appendli(["provision_suspension(",Res1,")"],Res)}. retroactive_provision_enactment(Res)--> beg_marker_atr("RETROACTIVE_PROVISION_ENACTMENT"), attribute("PROVISION_ID",cdata,required,Res1), end_marker_atr_end, {appendli(["retroactive_provision_enactment(",Res1,")"],Res)}. beg_marker(Name)--> [p(60),w(Name),p(62)]. end_marker(Name)--> [p(60),p(47),w(Name),p(62)]. beg_marker_atr(Name)--> [p(60),w(Name)]. end_marker_atr--> [p(62)]. end_marker_atr_end--> [p(47),p(62)]. attribute(Name,cdata,required,String)--> [w(Name),p(61),s(String)]. attribute(Name,nmtoken,required,String)--> [w(Name),p(61),s(String)], {numerical(String)}. attribute(Name,id,required,String)--> [w(Name),p(61),s(String)], {ident(String)}. pcdata(Res)--> [t(Res)]. /******************************************************************************/ /* Grammar for the portion with the next specification element */ /* and for the final portion of the text */ /******************************************************************************/ text_portion([],main,stop)--> end_marker("MAIN_STATUTE"), end_marker("STATUTE"). text_portion([],amending,stop)--> end_marker("AMENDING_STATUTE"), end_marker("STATUTE"). text_portion([],introductory,stop)--> end_marker("INTRODUCTORY_STATUTE"), end_marker("STATUTE"). text_portion(Res,_,ok)--> element(Res). text_portion([],_,error,_,[]). /******************************************************************************/ /* LEXICAL ANALYSIS MODULE */ /******************************************************************************/ /*The lexical analysis module recognises lexical units in an arbitrary text available in the input stream (In). The result of the analysis is sent to the output stream (Out). The following lexical units are recognised: a) a word containing letters which is represented by the term w( on the output (note that the underscore character belongs to letters), b) a number built from digits which is represented by the term n(), c) a punctuation sign represented by the term p(), d) a sequence of invisible characters represented by the term b(), e) an arbitrary sequence of characters written between “” which is represented by the term s(), f) an arbitrary sequence of characters written between ## represented by the term t(). In the output file every term of the lexical unit representation is followed by the point and the new line.*/ la_start:- pce_open(@view1,read,H1), pce_open(@view2,write,H2), lexical_an(H1,H2), close(H1), close(H2). lexical_an(In,Out):- get0(In,Char), a(start,In,Out,Char,[]). letter(X):- X<123,X>96,!; X>64,X<91,!; X=140,!;X=143,!;X=156,!;X=159,!;X=163,!;X=165,!; X=175,!;X=179,!;X=185,!;X=191,!;X=198,!;X=202,!; X=209,!;X=211,!;X=230,!;X=234,!;X=241,!;X=243,!; X=95. digit(X):- X<58,X>47. invisible(32). invisible(9). invisible(10). quotation_mark(34). hash_mark(35). a(start,_,_,Char,_):- file_end(Char),!. a(start,In,Out,Char,_):- letter(Char),!, get0(In,Char1), a(word,In,Out,Char1,[Char]). a(start,In,Out,Char,_):- digit(Char),!, get0(In,Char1), a(number,In,Out,Char1,[Char]). a(start,In,Out,Char,_):- quotation_mark(Char),!, get0(In,Char1), a(string,In,Out,Char1,[]). a(start,In,Out,Char,_):- hash_mark(Char),!, get0(In,Char1), a(text,In,Out,Char1,[]). a(start,In,Out,Char,_):- invisible(Char),!, get0(In,Char1), a(invisible,In,Out,Char1,[Char]). a(start,In,Out,Char,_):- get0(In,Char1), write_pun(Out,Char), a(start,In,Out,Char1,[]). a(word,_,Out,Char,M):- file_end(Char),!, write_mag_w(Out,M). a(word,In,Out,Char,M):- letter(Char),!, get0(In,Char1), a(word,In,Out,Char1,[Char|M]). a(word,In,Out,Char,M):- digit(Char),!, get0(In,Char1), write_mag_w(Out,M), a(number,In,Out,Char1,[Char]). a(word,In,Out,Char,M):- quotation_mark(Char),!, get0(In,Char1), write_mag_w(Out,M), a(string,In,Out,Char1,[]). a(word,In,Out,Char,M):- hash_mark(Char),!, get0(In,Char1), write_mag_w(Out,M), a(text,In,Out,Char1,[]). a(word,In,Out,Char,M):- invisible(Char),!, get0(In,Char1), write_mag_w(Out,M), a(invisible,In,Out,Char1,[Char]). a(word,In,Out,Char,M):- get0(In,Char1), write_mag_w(Out,M), write_pun(Out,Char), a(start,In,Out,Char1,[]). a(number,_,Out,Char,M):- file_end(Char),!, write_mag_n(Out,M). a(number,In,Out,Char,M):- letter(Char),!, get0(In,Char1), write_mag_n(Out,M), a(word,In,Out,Char1,[Char]). a(number,In,Out,Char,M):- digit(Char),!, get0(In,Char1), a(number,In,Out,Char1,[Char|M]). a(number,In,Out,Char,M):- quotation_mark(Char),!, get0(In,Char1), write_mag_n(Out,M), a(string,In,Out,Char1,[]). a(number,In,Out,Char,M):- hash_mark(Char),!, get0(In,Char1), write_mag_n(Out,M), a(text,In,Out,Char1,[]). a(number,In,Out,Char,M):- invisible(Char),!, get0(In,Char1), write_mag_n(Out,M), a(invisible,In,Out,Char1,[Char]). a(number,In,Out,Char,M):- get0(In,Char1), write_mag_n(Out,M), write_pun(Out,Char), a(start,In,Out,Char1,[]). a(invisible,_,Out,Char,M):- file_end(Char),!, write_mag_b(Out,M). a(invisible,In,Out,Char,M):- letter(Char),!, get0(In,Char1), write_mag_b(Out,M), a(word,In,Out,Char1,[Char]). a(invisible,In,Out,Char,M):- digit(Char),!, get0(In,Char1), write_mag_b(Out,M), a(number,In,Out,Char1,[Char]). a(invisible,In,Out,Char,M):- quotation_mark(Char),!, get0(In,Char1), write_mag_b(Out,M), a(string,In,Out,Char1,[]). a(invisible,In,Out,Char,M):- hash_mark(Char),!, get0(In,Char1), write_mag_b(Out,M), a(text,In,Out,Char1,[]). a(invisible,In,Out,Char,M):- invisible(Char),!, get0(In,Char1), a(invisible,In,Out,Char1,[Char|M]). a(invisible,In,Out,Char,M):- get0(In,Char1), write_mag_b(Out,M), write_pun(Out,Char), a(start,In,Out,Char1,[]). a(string,_,Out,Char,M):- file_end(Char),!, write_mag_s(Out,M). a(string,In,Out,Char,M):- quotation_mark(Char),!, get0(In,Char1), write_mag_s(Out,M), a(start,In,Out,Char1,[]). a(string,In,Out,Char,M):- get0(In,Char1), a(string,In,Out,Char1,[Char|M]). a(text,_,Out,Char,M):- file_end(Char),!, write_mag_t(Out,M). a(text,In,Out,Char,M):- hash_mark(Char),!, get0(In,Char1), write_mag_t(Out,M), a(start,In,Out,Char1,[]). a(text,In,Out,Char,M):- get0(In,Char1), a(text,In,Out,Char1,[Char|M]). file_end(-1). write_pun(Out,Char):- write(Out,p(Char)), put(Out,'.'), nl(Out). write_mag_w(Out,M):- put(Out,'w'), write_rest(Out,M). write_mag_n(Out,M):- put(Out,'n'), write_rest(Out,M). write_rest(Out,M):- write_mag(Out,['(','"']), reverse(M,M1), write_mag(Out,M1), write_mag(Out,['"',')','.']), nl(Out). write_mag_b(Out,M):- put(Out,'b'), put(Out,'('), reverse(M,M1), write(Out,M1), put(Out,')'), put(Out,'.'), nl(Out). write_mag_s(Out,M):- put(Out,'s'), write_rest(Out,M). write_mag_t(Out,M):- put(Out,'t'), write_rest(Out,M). write_mag(_,[]):-!. write_mag(Out,[A|R]):- put(Out,A), write_mag(Out,R).