[comp.lang.prolog] PROLOG DIGEST V6 #39

restivo@POLYA.STANFORD.EDU (Chuck Restivo) (07/09/88)

From: Chuck Restivo (The Moderator) <PROLOG-REQUEST@POLYA.STANFORD.EDU>
Reply-to: PROLOG@POLYA.STANFORD.EDU>
US-Mail: P.O. Box 4584, Stanford CA  94305
Subject: PROLOG Digest   V6 #39
To: PROLOG@POLYA.STANFORD.EDU


PROLOG Digest           Friday, 8 July 1988      Volume 6 : Issue 39

Today's Topics:
			Query - Parallel Systems & Data Structures,
		        Implementation - Disjunction  & Screen Control
--------------------------------------------------------------------------------------------------------------------------

Date: 26 May 88 15:07:20 GMT
From: dartvax!eleazar.dartmouth.edu!fagin@bu-cs.bu.edu  (Barry S. Fagin)
Subject: Usable parallel logic programming systems

	I'm trying to gather information on existing or planned implementations
of parallel logic programming systems, preferably on existing
multiprocessors.  If you have any information on such a system, could 
you please send me mail about it?  Any pointers to documents would be 
greatly appreciated.  Thanks.

--Barry

------------------------------

Date: 25 May 88 08:43:43 GMT
From: mcvax!unido!ecrcvax!micha@uunet.uu.net  (Micha Meier)
Subject:  Clause fusion (Disjunctions)

In article <1001@cresswell.quintus.UUCP> ok@quintus.UUCP (Richard A. O'Keefe) writes:
>In article <539@ecrcvax.UUCP>, micha@ecrcvax.UUCP (Micha Meier) writes:
>> Richard proposes that nested if-then-else's are treated at the same level,
>> which leads to confusions since then the indentation is context dependent
>> (an if-then-else inside another one cannot be indented independently).
>
>I DO NOT!  I use exactly the same rule for indenting if->then;elses in
>Prolog that I use in Fortran 77, Pop, ADA, Algol 68, et cetera.  Namely
>
>	<IF> <condition> <THEN>
>	[1 indent] <body>
>	<ELIF> <condition> <THEN>
>	[1 indent] <body>
>	...
>	<ELSE>
>	[1 indent] <body>
>	<ENDIF>
>
	The problem with Prolog is that any of the term can be
	a conjunction, disjunction or if-then-else. What about

	(	(	C1 ->
			B1
		;
			B2
		) ->
		(	C2 ->
			B3
		;
			B4
		),
		B5
	;	B6,
		B7
	)

	I find it not much readable when the condition is difficult
	to distinguish from the other code.

>	( test1 ->
>	    body1
>	; test2 ->
>	    body2
>	; /*otherwise*/
>	    body3
>	)

	Here it is different - how exactly do you indent your procedures?
	This problem might seem to be a minor one, but should not there
	be at least a recommendation from the standard or from somebody
	else? Prolog does not have many syntactical structures and therefore
	it is extremely important to keep some programming style, e.g.
	to use names_like_that for procedures and LikeThat for variables,
	to put each goal on a separate line etc. I've been trying to
	port various external programs to Sepia and sometimes it's rather
	difficult to realize what the author really meant.

--Micha

------------------------------

Date: 27 May 88 00:28:28 GMT
From: quintus!ok@unix.sri.com  (Richard A. O'Keefe)
Subject:  Clause fusion 

In article <548@ecrcvax.UUCP>, micha@ecrcvax.UUCP (Micha Meier) writes:
> 	The problem with Prolog is that any of the term(s in an if->then;else)
>	can be a conjunction, disjunction or if-then-else.  What about
>       (   (   C1 ->
>               B1
>           ;
>               B2
>           ) ->
>           (   C2 ->
>               B3
>           ;
>               B4
>           ),
>           B5
> 	;   B6,
>           B7
> 	)
Algol 60, Algol 68, Lisp, Pop, Bourne shell, C shell, ML, ... have
exactly the same problem.  There's nothing special about Prolog in this
respect.  The answer is that it isn't a problem to have another if in a
then-part or else-part, and that programmers who care about readability
don't put ifs in if-parts.  The big lesson for Prolog programmers is
"don't be scared of introducing new predicates". Programmers who do not
care about readability will find obfuscatory ways despite standards.
(The famous "Indian Hills style sheet" for C has led to some of the most
unreadable C code it has ever been my misfortune to try to read.)

I basically agree with Meier's concern for readability.  But I think the
layout of the Prolog code as such is not the most important aspect.  It
is easy to write a reformatter (the editor I'm using to write this has one).
You can fix what is there, the trouble is what _isn't_ there.  I have
recently had occasion to look at two people's programs.  One of them
I repeatedly misunderstood because it was doing some very tricky things
in its control flow and had essentially no comments.  The other I still
do not understand because it is doing non-obvious things with its data
structures and has essentially no comments.

Rules of thumb for comments:
(1) Describe all major data structures.
(2) Comment every control trick.

------------------------------

Date: 28 May 88 06:14:00 GMT
From: mccaugh@m.cs.uiuc.edu
Subject: Re: Clause fusion (Disjunctions)


/* Written  1:14 am  May 28, 1988 by mccaugh@uiucdcsm.cs.uiuc.edu in uiucdcsm:comp.lang.prolog */
/* Written  3:43 am  May 25, 1988 by micha@ecrcvax.UUCP in uiucdcsm:comp.lang.prolog */
/* ---------- "Re: Clause fusion (Disjunctions)" ---------- */
In article <1001@cresswell.quintus.UUCP> ok@quintus.UUCP (Richard A. O'Keefe) writes:
>In article <539@ecrcvax.UUCP>, micha@ecrcvax.UUCP (Micha Meier) writes:
>> Richard proposes that nested if-then-else's are treated at the same level,
>> which leads to confusions since then the indentation is context dependent
>> (an if-then-else inside another one cannot be indented independently).
>
>I DO NOT!  I use exactly the same rule for indenting if->then;elses in
>Prolog that I use in Fortran 77, Pop, ADA, Algol 68, et cetera.  Namely
>
>	<IF> <condition> <THEN>
>	[1 indent] <body>
>	<ELIF> <condition> <THEN>
>	[1 indent] <body>
>	...
>	<ELSE>
>	[1 indent] <body>
>	<ENDIF>
>
	The problem with Prolog is that any of the term can be
	a conjunction, disjunction or if-then-else. What about

	(	(	C1 ->
			B1
		;
			B2
		) ->
		(	C2 ->
			B3
		;
			B4
		),
		B5
	;	B6,
		B7
	)

	I find it not much readable when the condition is difficult
	to distinguish from the other code.

>	( test1 ->
>	    body1
>	; test2 ->
>	    body2
>	; /*otherwise*/
>	    body3

>	)

	Here it is different - how exactly do you indent your procedures?
	This problem might seem to be a minor one, but should not there
	be at least a recommendation from the standard or from somebody
	else? Prolog does not have many syntactical structures and therefore
	it is extremely important to keep some programming style, e.g.
	to use names_like_that for procedures and LikeThat for variables,
	to put each goal on a separate line etc. I've been trying to
	port various external programs to Sepia and sometimes it's rather
	difficult to realize what the author really meant.

--Micha

------------------------------

Date: 28 May 88 06:14:00 GMT
From: mccaugh@m.cs.uiuc.edu
Subject: Clause Fusion

/* Written  3:43 am  May 25, 1988 by micha@ecrcvax.UUCP in uiucdcsm:comp.lang.prolog */
/* ---------- "Re: Clause fusion (Disjunctions)" ---------- */
In article <1001@cresswell.quintus.UUCP> ok@quintus.UUCP (Richard A. O'Keefe) writes:
>In article <539@ecrcvax.UUCP>, micha@ecrcvax.UUCP (Micha Meier) writes:
>> Richard proposes that nested if-then-else's are treated at the same level,
>> which leads to confusions since then the indentation is context dependent
>> (an if-then-else inside another one cannot be indented independently).
>
>I DO NOT!  I use exactly the same rule for indenting if->then;elses in
>Prolog that I use in Fortran 77, Pop, ADA, Algol 68, et cetera.  Namely
>
>	<IF> <condition> <THEN>
>	[1 indent] <body>
>	<ELIF> <condition> <THEN>
>	[1 indent] <body>
>	...
>	<ELSE>
>	[1 indent] <body>
>	<ENDIF>
>
	The problem with Prolog is that any of the term can be
	a conjunction, disjunction or if-then-else. What about

	(	(	C1 ->
			B1
		;
			B2
		) ->
		(	C2 ->
			B3
		;
			B4
		),
		B5
	;	B6,
		B7
	)

	I find it not much readable when the condition is difficult
	to distinguish from the other code.

>	( test1 ->
>	    body1
>	; test2 ->
>	    body2
>	; /*otherwise*/
>	    body3
>	)

	Here it is different - how exactly do you indent your procedures?
	This problem might seem to be a minor one, but should not there
	be at least a recommendation from the standard or from somebody
	else? Prolog does not have many syntactical structures and therefore
	it is extremely important to keep some programming style, e.g.
	to use names_like_that for procedures and LikeThat for variables,
	to put each goal on a separate line etc. I've been trying to
	port various external programs to Sepia and sometimes it's rather
	difficult to realize what the author really meant.

--Micha

------------------------------

Subject: Data Structures
Date: Fri, 27 May 88 14:10:54 -0700
From: Russ Abbott <abbott@aerospace.aero.org>

Date: 22 May 88 22:34:33 GMT
Can anyone refer me to a prolog (or other) system that does data structure
transformations?  The general problem is to define interfaces between
pre-exising tools in an environment.

A particular example is to use P-Nut, a petri net analyzer, on a system
produced by Teamwork, a data flow diagrammer.  Besides allowing one to draw
data flow diagrams, Teamwork also allows one to draw process activation tables.
For example, the following are two rows in a process activation table.

   1. The first row says that if condition C1 holds and condition C4 does
      not hold, the processes P1 and P4 should be started.  Once they
      finish, process P5 should be started.

   2. The second row says that if conditions C1 and C2 hold and condition
      C3 does not hold, processes P1 and P3 should be activated.  When P1
      and P3 complete, process P2 should be activated.  When it completes
      processes P1 and P3 should be reactivated.  When they complete a
      second time, processes P4 and P5 should be activated.

A complete process activation table would consist of any number of such rows,
each row having a unique distribution of +'s and -'s among the conditions.

                C1 | C2 | C3 | C4 || P1 | P2 | P3 | P4 | P5
               ----+----+----+----++----+----+----+----+----
                 + |    |    |  - ||    |  1 |    |  1 |  2
                 + |  + |  - |    || 1,3|  2 | 1,3|  4 |  4
                                 ....

The petri net input to say the same thing looks like the following.

    C1, not C4                        -> row({C1, not C4},1), P2s, P4s
    row({C1, not C4},1), P2f, P4f     -> row({C1, not C4},2), P5s
    row({C1, not C4},2), P5f          -> <empty>

    C1, C2, not C3                    -> row({C1, C2, not C3},1), P1s, P3s
    row({C1, C2, not C3},1), P1f, P3f -> row({C1, C2, not C3},2), P2s
    row({C1, C2, not C3},2), P2f      -> row({C1, C2, not C3},3), P1s, P3s
    row({C1, C2, not C3},3), P1f, P3f -> row({C1, C2, not C3},2), P4s, P5s
    row({C1, C2, not C3},3), P4f, P5f -> <empty>

    P1s                               -> P1f
    P2s                               -> P2f
    P3s                               -> P3f
    P4s                               -> P4f
    P5s                               -> P5f


where (a) P1s, P2s, P3s, P4s, and P5s stand for the start of P1, P2, P3, P4,
and P5; (b) P1f, P2f, P3f, P4f, and P5f stand for the finish of the same
processes; and (c) row(<conditions>, <level>) stands for the row identified by
the indicated set of conditions, executing at the indicated level.  Of course,
the actual row conditions are not needed to identify the row.  All that is
needed is some unique identifier for each row.

So the problem is to transform the information from table form into petri net
form.

The question, though, is not how to write a program for this particular
transformation, but to develop a more general system in which transformations
of this and similar kinds can be described and implemented.

I have already found the following work.

   1. IDL, an Interface Description Language by David Alex Lamb of Queens
      University.  IDL was developed as part of CMU's Production Quality
      Compiler Compiler project.  It allows one to describe abstractly the
      data structures that two system components agree on.  (Since the
      components agree on a data structure, this problem is not the same
      as the one I'm asking about.)  IDL then generates reader and writer
      code for that abstract data structure in whatever concrete terms the
      two components require.  IDL is described in "IDL: Sharing
      Intermediate Representations,", TOPLAS, July, 1987.

   2. FORMAL a system for transforming hierarchical databases.  In FORMAL,
      one provides a description of an input database along with a sketch
      of the desired output structure expressed in terms of the input
      structure.  Basically, this is what I'm asking for, but FORMAL is
      limited to hierarchical databases.  This work reminded me of Query
      By Example except that the output may be a (hierarchical) database
      structure and not just a list of tuples satisfying the sketched
      conditions.  FORMAL is described in "Automatic Data Transformation
      and Restructuring," by Nan C. Shu, Proc. 3rd Intl. Conf. on Data
      Engr., 1987.


   3. Stage, a system for generating application generators by J. Craig
      Cleaveland.  The application generators Stage generates are, in
      effect, data transformation systems.  The input to Stage is (a) a
      grammar describing the input to the desired application and (b) a
      sketch-like description of the desired output of the application
      expressed in terms of the parse tree of the input.  Stage then
      generates a program to perform such transformations.  Stage is
      described in a forthcoming article "Building Application
      Generators," in IEEE Software, July, 1988.

It is clear that the problem as posed it is not well formed.  That is, any
program could be described as a data structure transformer, so asking for a
system in which to describe more or less arbitrary transformations is asking
for too much.

One approach would be to limit the problem to a system for describing
transformations that operate on the structure of the data and that are not
dependent on the content.  That is not satisfactory for a couple of reasons.

   - For one thing the Teamwork/P-Nut example given above does not fit
     this description since the content of the data structure must be
     examined at least to the extent of determining concurrency and
     process sequencing.

   - Even worse, since a two counter machine is Turing equivalent, a
     system that deals generally with a pair of lists whose lengths (but
     not content) matter is equivalent to a general purpose programming
     language.

All that notwithstanding, there does seem to be some value in developing a
notation in which data structures and transformations on them can be
described--and then automatically implemented.  In addition, it seems that
prolog would be a suitable language in which to develop such a system.

As an experiment, a program has been written in C-Prolog that transforms data
transformation descriptions into corresponding data transformation programs.

The input to be transformed is assumed to be given as a set.  For this example,
each set element is a pair, where the first component is a set of positive and
negative conditions and the second is a set of processes and their execution
levels.  The input is stored on the file teamwork_to_pnut.

    [c1/(+), c4/(-)],         [p2/1, p4/1, p5/2].

    [c1/(+), c2/(+), c3/(-)], [p1/1, p1/3, p2/2, p3/1, p3/3, p4/4, p5/4].


These are intended to correspond to the two rows of the process activation
table.

In specifying the output, the transformation description (see below) includes
new symbols: start(Process) and finish(Process), corresponding to Ps and Pf,
for each Process P; and row(<Conditions>, <Level>) for each row and level.  The
actual (although manually formatted) output produced by the generated program
is as follows.

    Output =
                            /* The processes */

                           start(p1) -> finish(p1)
                           start(p2) -> finish(p2)
                           start(p3) -> finish(p3)
                           start(p4) -> finish(p4)
                           start(p5) -> finish(p5)


                             /* The first row */

    [c1, c2, not c3] -> [start(p1), start(p3), row([c1, c2, not c3], 1)]

    [finish(p1), finish(p3), row([c1, c2, not c3], 1)] ->
                         [start(p2), row([c1, c2, not c3], 2)]

    [finish(p2), row([c1, c2, not c3], 2)] ->
                         [start(p1), start(p3), row([c1, c2, not c3], 3)]

    [finish(p1), finish(p3), row([c1, c2, not c3], 3)] ->
                         [start(p4), start(p5), row([c1, c2, not c3], 4)]

    [finish(p4), finish(p5), row([c1, c2, not c3], 4)] -> []


                             /* The second row */
    [c1, not c4] -> [start(p2), start(p4), row([c1, not c4], 1)]

    [finish(p2), finish(p4), row([c1, not c4], 1)] ->
                                 [start(p5), row([c1, not c4], 2)]

    [finish(p5), row([c1, not c4], 2)] -> []



Here is the actual data transformaton specification.  The input file and its
structure is specified as follows.

    input = file teamwork_to_pnut.

    structure row = (conditions, processes).


The output is also described as a set--the set of Petri net transformations.
Four different kinds of transformations are generated.  Letting + stand for set
union:


    output(Input) =   output1(Input) + output2(Input) +
                      output3(Input) + output4(Input).


The individual transformations may be described as follows.

   1. Each row has a unique starting Petri Net transition.  Its LHS is the
      set of conditions that characterize the row.  Its RHS is the set of
      processes at level 1.

          output1(Input) =
                  {conditions(Row) -> rhs(Row, 1) | Row in Input}.


      where

          conditions(Row) = pos_conds(Row.conditions) +
                            neg_conds(Row.conditions).

          pos_conds(Conditions) =
                  {Condition     | Condition/(+) in Conditions}.
          neg_conds(Conditions) =
                  {not Condition | Condition/(-) in Conditions}.

          rhs(Row, Level) =
                  {start(Process) | Process/Level in Row.processes} +
                  {row(conditions(Row), Level)}.


   2. The second kind of transformation appears once for each Process.
      Each Process has an associated transformation from its start to its
      finish.

          output2(Input) =
           {start(Process) -> finish(Process) |
                                    Row in Input,
                                    Process/_ in Row.processes}.


      where

          lhs(Row, Level) =
                  {finish(Process) | Process/Level in Row.processes} +
                  {row(conditions(Row), Level)}.


   3. The third kind of transformation links the termination of Processes
      at one level to the start of Processes at the next level.

          output3(Input) =
           {lhs(Row, Level) -> rhs(Row, Level+1) |
                                      Row in Input,
                                      _/Level in Row.processes,
                                      _/(Level+1) in Row.processes}.

   4. The fourth kind of transformation terminates the processing of the
      rows.  There is one for each row.

          output4(Input) =
           {lhs(Row, Level) -> [] | Row in Input,
                                    _/Level in Row.processes,
                                    _/(Level+1) not in Row.processes}.


The preceding does the required transformations, but it has limitations.

   - The transformations are done abstractly.  In practice, the concrete
     representations of the input and output must be dealt with also.

   - The generated program is not optimized.

   - In this example, sets suffice.  For some other problem some data
     structure other than sets may be required.  But since any data
     structure can be mapped onto relations, perhaps this is all we need.

All in all, it doesn't seem like a bad start.  My question is whether anyone
knows of existing work along these or similar lines?

Thanks,

-- Russ Abbott

------------------------------

Date: 26 May 88 19:18:06 GMT
From: ulysses!terminus!rolls!mtuxo!mtfmi!dbrod@ucbvax.Berkeley.EDU  (D.BRODERICK)
Subject: screen control

If your version of Prolog does not have screen control predicates,
but you are familiar with the Unix(tm) tput(1) command 
(or willing to become so), there is a quick and dirty way to 
generate some character based screen control predicates.  
tput(1) makes use of the terminfo database to generate terminal 
specific escape sequences to control the screen.  For example, 
the following, invoked from the shell, will print out "hello" 
in standout mode:

tput smso; echo hello; tput rmso

As you can see, the argument names are intuitively obvious(?).
To use this information from Prolog, write a shell script 
called "get_tput" as follows:
--------------------------------------
echo "tput('$2',$1,'`tput -T$1 $2`')."
--------------------------------------
This is invoked, for example, as: 
	get_tput vt100 clear >> tput.pl
It is easy enough to use a for-loop to generate a prolog 
terminfo database for all the tput arguments/terminals you want.
For an interesting sight, cat the file. ("tput sgr0" sets to normal)
To use on a PC running an ansi.sys driver, generate a database 
for ansi and download.
To use: 
	consult('tput.pl'). 	and call 
	tput(clear).		, defined as:

tput(Cmd) :- tput(Cmd,_,EscSeq), atomic(EscSeq), write(EscSeq).
tput(Cmd) :- tput(Cmd,_,[Esc|Seq]), print_list([Esc|Seq]).
tput(Cmd) :- not tput(Cmd,_,_).

This assumes you have loaded info only for your current terminal.
The reason for the middle clause is that shell tput commands that
take more than one parameter return a sequence that needs further
parsing.  I have not written a general parser, but have done some
of these by hand.  In what follows, what looks like ^ followed by [ 
is actually a real Escape char (in case you retype this).

% cup - set cursor position.  this works for vt100 and ansi
tput(cup(Row,Col),att5425,['[',R1,';',C1,'H']) :- R1 is Row+1, C1 is Col+1.

% csr - change scroll region
tput(csr(Top,Bottom),att5425,['[',T1,';',B1,r]) :- 
	T1 is Top+1, B1 is Bottom+1.

% pln - set system function key  Not on many terminals
tput(pln(Key,Label,Command),att5425,
		['[',Key,';',Len,';0;0q',Label16,Command]) :-
	name(Command,CAscii),
	length(CAscii,Len),
	pad_atom(16,Label,Label16).

tput(user,att5425,'}'). % switch to user function keys
tput(system,att5425,'~'). % switch to system function keys

% tsl - write to status line
tput(tsl(Col),att5425,['7[25;',Col1,'H']) :- Col1 is Col + 8.

% auxiliary predicates

print_list([]).
print_list([X|Xs]) :- write(X), print_list(Xs).

pad_atom(Num,Atom,Padded) :-
	name(Atom,AAscii),
	length(AAscii,Len),
	Pads is Num - Len,
	pad_blanks(Pads,BString),
	append(AAscii,BString,PAscii),
	name(Padded,PAscii).

pad_blanks(0,[]).
pad_blanks(Num,[32|Blanks]) :-
	Num > 0,
	Num1 is Num-1,
	pad_blanks(Num1,Blanks).

% append/3 as usual

------------------------------

Date: 29 May 88 04:25:44 GMT
From: quintus!ok@sun.com  (Richard A. O'Keefe)
Subject: Screen Control

In article <701@mtfmi.UUCP>, dbrod@mtfmi.UUCP (D.BRODERICK) writes:
> If your version of Prolog does not have screen control predicates,
> but you are familiar with the Unix(tm) tput(1) command 

It's worth pointing out that
(a) tput is a System V feature, not present in most BSDs (but SunOS has it).
(b) There are some non-trivial differences between V.2 tput and V.3 tput
    (as I found the hard way when some scripts I wrote on a V.3 system
    didn't work on a V.2 system.)
(c) Some of the things tput returns are numbers, for example
	tput lines
    prints the number of lines on the screen.  Suppose that is 24.
    The "get_tput" script provided by D.BRODERICK will write this as '24',
    which is an atom.  You may want to have another script which writes
    things unquoted so that you can access such terminal properties.
(d) Some of the things tput reports are "boolean", for example
	tput hc		# is it a hard-copy terminal?
    always prints nothing.  Instead the answer is to be found in the exit
    code (0 means yes, non-zero means no).  You may want a third script
	if tput -T$1 $2 ; then
	    echo "tput($2, '$1', true)."
	else
	    echo "tput($2, '$1', false)."
	fi
    for use with boolean capabilities.
(e) tput writes things out verbatim, without escape characters.  Some
    Prolog systems may discard CRs or do other odd things with strange
    characters.  (Quintus Prolog is safe, but watch out for terminal
    capabilities containing apostrophes.)  

If the Prolog dialect you are using has an interface to C (as many have)
you would be better off writing an interface to 'curses'; since 'curses'
is available for IBM PCs and VAX/VMS as well as for UNIX this may be more
portable than using tput.  In particular, if you use curses, you don't
have to figure out how to parse the 'cup' capability (rather hairy).
Then too, I for one would rather hide the rather bizarre capability
names (quickly now:  what does eslok do?)  from my Prolog code.

------------------------------

End of PROLOG Digest