Prolog Code for the live Specification
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%
% spec_feb.pl
%
% CGI access to the executable
% specification.
%
%
% 11 February 1999
%
% Author. J.P.E. Hodgson
%
%
% include files for html
%
:- include('html.pl').
%
% This is a lightly modified version of the PiLLoW Library.
%
% files for special conversions between
% atoms and terms as well as the formal spec.
%
:- include('cgi_gnu_make.pl').
%
%
% Include special front ends for spec.
%
:- include('cgi_run_bip.pl').
%
%
% main does three things.
%
% 1. gets the INFO form the form and
% determines the values set.
% 2. Executes the application.
% 3. Generates the output
% and then halts.
%
main:-
html_get_form_input(Info),
get_arguments(Info, Button, FP, Goal, Expected, Prog),
doit(Button, FP,FreeProgram, Goal, Expected,Prog, Results),
output_html(
[ form_reply,
start,
title('WWW Interface for the Formal Specification of Prolog'),
start_body(white),
heading(3, 'WWW Interface for the Formal Specification of Prolog'),
form('http://macs.sju.edu/~jhodgson/cgi-bin/spec_feb11.cgi'),
heading(4, 'Choose your program'),
'Either enter the program',\\,
textarea(freeprogram, [cols=60, rows=10], FreeProgram), \\,
'Or ', submit(select, [name=chosen]), 'from list: ',
menu(progmenu, [single], ['use only builtins','user program', reverse, append, length, max]),
\\,
heading(4, 'Now choose your goal and specify the result you expect.'),
'Goal: ',
input(text, [name=goal, size=40, value=Goal]),
\\,
'Expected Result: ',
input(text, [name=expected, size=40, value=Expected]),\\,
'Here are some sample expected results', \\,
'failure, success, or ', \\,
' X <-- 1, Y <-- 2 ; X <-- 2, Y <-- 4',\\,
'You may also leave this field blank', \\,
submit(submit, [name=go]), ' ',reset,
heading(4,'The Results:'),
textarea(results, [cols=60, rows = 10], Results),\\,
end_form,
end_body,
end]
), nl,
halt.
%%%%%%%%%%%%%%%%%%%%%%%
%
%
% get_arguments(Info, Button, FP,Goal, Expected, Prog)
%
get_arguments(Info, Button, FP,G,E,Prog) :-
which_pressed(Info, Button),
html_get_value(Info, freeprogram, FP),
html_get_value(Info, goal, G),
html_get_value(Info, expected,E),
html_get_value(Info, progmenu, Prog).
%%%%%%%%%%%%%%%%%%%%%%%
%
% doit(+Button, +FP, -FreeProg, @Goal, @Expected,@Prog, -Results).
%
% If the button is select show the chosen program.
doit(select,_FP, FreeProg, _G,_E,Prog, []) :- !,
program(Prog, FreeProg).
doit(submit,'Uses only Built In Predicates' ,'Uses only Built In Predicates' ,
G,E, _, Results) :- !,
catch(
build_ex(G,E,Results),
B,
Results = ['Goal:', G,'Expected result:', E, B]
).
doit(submit,FreeProg, FreeProg,G,E,_, Results) :-
catch(
build_ex3(G,E,FreeProg, Results),
B,
Results=['Goal:', G, 'Expected result:', E,
'Program:', FreeProg, B]
).
doit(none, _FP,_F,_G,_E,_P,[]).
%%%%%%%%%%%%%%%%%%%%
%
%
% Predefined programs.
%
program('user program', []):- !.
program('use only builtins', ['Uses only Built In Predicates']).
program(length, ['length(List, Len) :- len1(List, 0, Len).',
'len1([],L,L).', 'len1([H|T], N, L) :- N1 is N + 1, len1(T, N1, L).']).
program(append, ['append([], L, L).', 'append([H|L1], L2, [H|L3]) :- append(L1,L2,L3).']).
program(reverse, ['reverse(L, Rev):- rev1(L, [], Rev).', 'rev1([], R,R).',
'rev1([H|T], S, R) :- rev1(T, [H|S], R).']).
program(max, ['max(X,Y, Max) :- X >= Y, !, Max = X.', 'max(X,Y, Max) :-X < Y, !, Max = Y.'] ).
which_pressed(Info, select) :-
html_get_value(Info, chosen, select).
which_pressed(Info, submit) :-
html_get_value(Info, go, submit).
which_pressed(_,none).
:- initialization((standard_environment,main)). % Needed for compiled standalone.
Author: J.P.E. Hodgson
Inria Rocquencourt
78153 Le Chesnay Cedex
France
Saint Joseph's University
Philadelphia PA 19131
USA
Last Changed: 1999/06/16