[comp.lang.prolog] converting ascii character lists to functors

eiverson@nmsu.edu (Eric Iverson) (04/20/91)

The following is a letter I just wrote to Quintus:
To: teksup@quintus.com
Subject: converting ascii character lists to functors
--text follows this line--

I called today about converting ascii character lists into functors
which could be unified with other functors.  I need to do this because
I need to use a character based read function for my file I/O.  Here's
what I came up with:

functor_chars(Functor,Chars):-
    atom_chars(Char1,Chars),
    tell('functor_chars'),
    format('~w.~n',Char1),
    see('functor_chars'),
    read(Functor),
    close('functor_chars'),
    unix(system('rm functor_chars')).

Here's a demo:

Quintus Prolog Release 3.0 (Sun-4, SunOS 4.1)
Copyright (C) 1990, Quintus Computer Systems, Inc.  All rights reserved.
1310 Villa Street, Mountain View, California U.S.A. (415) 965-7700

| ?- % compiling file /tmp_mnt/home/thrinakia1/eiverson/prolog/functor_chars.pl
% functor_chars.pl compiled in module user, 0.067 sec 516 bytes

yes
| ?- name('loves(John,Mary,John)',X),functor_chars(F,X).

X = [108,111,118,101,115,40,74,111,104,110,44,77,97,114,121,44,74,111,104,110,41],
F = loves(_3569,_3590,_3569) ;

no
| ?- 

Can you think of a way to do this which does not involve writing to,
reading from, and then removing a file?  The current routine is rather
slow.  Is there some way that I could just open up a stream, write
things to it, and then read from it?  In other words, how can I read
from buffers in Quintus Prolog?  Any help would be appreciated.
--
------------------------------------------------------------------------
Eric Iverson				Internet: eiverson@nmsu.edu
Computing Research Lab
Box 30001/3CRL				Life is something to do when
New Mexico State University		you can't get to sleep.
Las Cruces, NM 88003-0001			-Fran Lebowitz
VOICE: (505) 646-5711	
FAX:   (505) 646-6218

notscott@sanjuan (Scott Notenberg 8792) (04/21/91)

eiverson@nmsu.edu (Eric Iverson) writes:

>I called today about converting ascii character lists into functors
>which could be unified with other functors.  I need to do this because
>I need to use a character based read function for my file I/O.

>| ?- name('loves(John,Mary,John)',X),functor_chars(F,X).
>X = [108,111,118,101,115,40,74,111,104,110,44,77,97,114,121,44,74,111,104,110,41],
>F = loves(_3569,_3590,_3569) ;
>------------------------------------------------------------------------
>Eric Iverson				Internet: eiverson@nmsu.edu

ASSUMPTION:
    The predicate concat(A,B,AB) is available for symbols (quoted strings).

Why not simply do the following...

?- name('loves(John,Mary,John)',X), collectUntil(X,40,F) which concats
    characters (recursively backwards so functor name isn't backwards)
    to an Accumulator until the ascii '40' is found from the list X.
    This should work, but who knows I don't use Quintus.

Hope this helps...

 +----------------------------+ +-----------------------------------------+
/| Scott Notenberg (notscott) | | INTERNET : notscott@sanjuan.UVic.ca     |
$| Department of Comp Science |-| BITNET : notscott@uvunix.bitnet         |
$| University of Victoria     |-| UUCP :  {ubc-vision,uw-beaver}!uvicctr! |
$| Home   : (604) 384-8632    |-| SNAIL :  416-1243 Bay Street,           |
$| Office : (604) 721-8792    | |          Victoria, BC Canada V8T 4X4    |
$+----------------------------+ +-----------------------------------------+
$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$/

Ray.Nickson@comp.vuw.ac.nz (Ray Nickson) (04/21/91)

In article <EIVERSON.91Apr19200202@aigyptos.nmsu.edu> eiverson@nmsu.edu (Eric Iverson) writes:

   Is there some way that I could just open up a stream, write
   things to it, and then read from it?  In other words, how can I read
   from buffers in Quintus Prolog?  Any help would be appreciated.

I wrote an interface to Unix pipe(2) using SICStus' foreign
functions.  You could do it in Quintus too, though there may be a
better way.

I tried two versions; for one, I added an fdopen/3 buitin to SICStus;
SICS implemented this with a source extension to open/3 so that if the
first argument is a small integer, it does an fdopen.

For the second version, which would have worked without source
changes, I opened two streams in Prolog and passed their stream_codes
(which under SICStus are UNIX file descriptors!) to the foreign
function; the f.f. called pipe(2) and dup(2)d the resulting descriptors
onto the ones passed in.

Both methods seem a bit tacky; with Quintus, there's probably one of
those fancy C functions you can call from within your foreign function
to turn a C stream (fdopen(3) the results of pipe(2)) into a Prolog
stream.

Anyway, here's my term_chars/2 written in terms of pipe/2, and the
open(FD, Mode, Stream) version of my pipe/2 for SICStus.  Your
criticism is solicited. 

---start term_chars.pl---
/*
    Converting between terms and chars-lists.

    Copyright (C) 1990 by Ray Nickson (Ray.Nickson@comp.vuw.ac.nz)

    This program is free software; you can redistribute it and/or modify
    it under the terms of the GNU General Public License as published by
    the Free Software Foundation; either version 1, or (at your option)
    any later version.

    This program is distributed in the hope that it will be useful,
    but WITHOUT ANY WARRANTY; without even the implied warranty of
    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
    GNU General Public License for more details.

    You should have received a copy of the GNU General Public License
    along with this program; if not, write to the Free Software
    Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA.
*/

%%%% 
%% term_chars(?Term, ?Chars) when ground(Term) or ground(Chars).
%% format_to_chars(-Chars, +Format, +Args).
%%%% 

:- dynamic('_$term_chars_streams'/2).

term_chars(T, C) :-
    (
        '_$term_chars_streams'(IS, OS) ->
            retract('_$term_chars_streams'(IS, OS))  %% so it's re-entrant!
    ;
        pipe(IS, OS)
    ),
    !,
    (
        nonvar(T) ->
            format_to_chars(C, "~p", [T]),
            Stat = success
    ;
        nonvar(C), C=[C1|_], integer(C1) ->
            format(OS, "~s.~n", [C]),
            flush_output(OS),
            read(IS, T),
            Stat = success
    ;
        format("Error: term_chars(~p, ~p): bad args.~n", [T, C]),
        Stat = failure
    ),
    assert('_$term_chars_streams'(IS, OS)),
    !,
    Stat = success.

format_to_chars(C, F, A) :-
    (
        '_$term_chars_streams'(IS, OS) ->
            retract('_$term_chars_streams'(IS, OS))  %% so it's re-entrant!
    ;
        pipe(IS, OS)
    ),
    !,
    append(F, [16'7f], LF),
    format(OS, LF, A),
    flush_output(OS),
    read_chars(IS, C0),
    C = C0,
    assert('_$term_chars_streams'(IS, OS)).


read_chars(S, C) :-
    get0(S, C0),
    (
        C0 = 16'7f ->
            C = ""
    ;
        read_chars(S, CR),
        C = [C0|CR]
    ).

write_chars(_, "").
write_chars(S, [C0|CR]) :-
    put(S, C0),
    write_chars(S, CR).
---end term_chars.pl---

---start unix.pl---
/*
    UNIX System Call Interface

    Copyright (C) 1990 by Ray Nickson (Ray.Nickson@comp.vuw.ac.nz)

    This program is free software; you can redistribute it and/or modify
    it under the terms of the GNU General Public License as published by
    the Free Software Foundation; either version 1, or (at your option)
    any later version.

    This program is distributed in the hope that it will be useful,
    but WITHOUT ANY WARRANTY; without even the implied warranty of
    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
    GNU General Public License for more details.

    You should have received a copy of the GNU General Public License
    along with this program; if not, write to the Free Software
    Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA.
*/

/* stuff for other system cals omitted   -rgn */
foreign('Pipe', c, pipe(-integer, -integer, [-integer])).
%%%% 
%% pipe(-InStream, -OutStream) 
%%%% 
pipe(IS, OS) :-
    pipe(ID, OD, Status),
    !,
    (
        Status = 0 ->
            open(ID, read, IS),
            open(OD, write, OS)
    ;
        format(" {ERROR: ~w: call failed.~n", [pipe(IS, OS)])
    ).

foreign_file(library('pipe.o'), ['Pipe']).

:- load_foreign_files([ library('pipe.o') ], []),
  abolish([foreign/3, foreign_file/2]).
---end unix.pl---

---start pipe.c---
#include <stdio.h>

#ifdef __GNUC__  /* not a real ANSI compiler */
extern int perror (char *);
#endif

extern int pipe (int []);

long Pipe (long *ind, long *outd)
{
  int pipedes[2];

  if (pipe (pipedes))
    {
      perror ("pipe");
      return 1;
    }
  else
    {
      *ind = pipedes[0];
      *outd = pipedes[1];
      return 0;
    }
}
---end pipe.c---

imlah@canon.co.uk (Bill Imlah) (04/22/91)

eiverson@nmsu.edu (Eric Iverson) writes:

>>| ?- name('loves(John,Mary,John)',X),functor_chars(F,X).
>X = [108,111,118,101,115,40,74,111,104,110,44,77,97,114,121,44,74,111,104,110,41],
>F = loves(_3569,_3590,_3569) ;

>Can you think of a way to do this which does not involve writing to,
>reading from, and then removing a file? 

      From the unification of args 1 & 3 in your example output,
      I assume you want to parse the whole term rather than just 
      get the functor.

      If you can't force Quintus to parse it, you could analyse 
      the term yourself and avoid i/o completely. However, if the form 
      of the term is unconstrained you will find yourself implementing 
      a prolog parser (you may be able to get hold of such code in a s/w 
      library or textbook).

      Alternatively, some prologs provide access to the parser.
      Eg. BIMprolog's sread/2 reads a term from an atom. 

--------------------------------------------------------
Bill Imlah                             imlah@canon.co.uk
Canon Research Centre Europe,  17/20 Frederick Sanger Rd.
The Surrey Research Park, Guildford, Surrey, GU2 5YD, UK.
Disclaimer: I ain't no Quintus expert.

micha@ecrc.de (Micha Meier) (04/22/91)

In article <EIVERSON.91Apr19200202@aigyptos.nmsu.edu> eiverson@nmsu.edu (Eric Iverson) writes:
>Can you think of a way to do this which does not involve writing to,
>reading from, and then removing a file?  The current routine is rather
>slow.  Is there some way that I could just open up a stream, write
>things to it, and then read from it?

The string streams available in Sepia have proven to be a very useful
feature to implement such types of algorithms. They basically allow the user to
write data into a string and read it back or modify. It then looks like

	:- open(S, string, s),		% open the stream s into the string S
	   write(s, Data),		% write Data there
	   seek(s, 0),			% start reading from the beginning
	   read(s, NewData),		% read the written stuff back
	   close(s).			% get rid of the string stream

Sepia has also a built-in predicate term_string(?Term, ?String) which
makes the conversion between any term and its string form, which is
implemented using string streams. The advantage of using string streams
over pipes is that the string streams are completely processed withing the
Prolog system, without system calls, and the current form of the string
can be always obtained with :- current_stream(String, string, s).
Note that although one can also write into a given string, e.g. with
	:- open("abcdef", string, s),
	   put(s, 0'b).
the original string is not destructed, and so the logical semantics
is preserved.

--Micha
--
E-MAIL  micha@ecrc.de            	MAIL	Micha Meier
						ECRC, Arabellastr. 17
                     				8000 Munich 81
						Germany

pereira@alice.att.com (Fernando Pereira) (04/22/91)

In article <EIVERSON.91Apr19200202@aigyptos.nmsu.edu> eiverson@nmsu.edu (Eric Iverson) writes:
>
>The following is a letter I just wrote to Quintus:
> [...]
>I called today about converting ascii character lists into functors
>which could be unified with other functors.

Quintus Prolog comes with an excellent source library, mostly due to Richard
O'Keefe. When in doubt, look in the documentation or in the library
directory. What you want is provided by library(charsio). Here's an example:

Quintus Prolog Release 3.1 (Sun-4, SunOS 4.1)
Copyright (C) 1990, Quintus Corporation.  All rights reserved.
2100 Geng Road, Palo Alto, California U.S.A. (415) 813-3800

| ?- use_module(library(charsio)).
% loading file /usr/local/newprolog/generic/qplib3.1/library/charsio.qof
% charsio.qof loaded, 0.417 sec 6,456 bytes
% module charsio imported into user

yes
| ?- with_output_to_chars(write(foo(bar,moo,3)),C), format('~s',[C]).
foo(bar,moo,3)
C = [102,111,111,40,98,97,114,44,109,111,111,44,51,41] 

| ?- 

Fernando Pereira
2D-447, AT&T Bell Laboratories
600 Mountain Ave, Murray Hill, NJ 07974
pereira@research.att.com

dave@quintus.UUCP (David Bowen) (04/24/91)

A more efficient way to do this is with library(charsio):

| ?- use_module(library(charsio)).

| ?- with_output_to_chars(
         portray_clause(loves(John,Mary,John)), L),
     with_input_from_chars(
         read(Term), L).

John = _6327,
Mary = _6346,
L = [108,111,118,101,115,40,65,44,66,44,65,41,46,10],
Term = loves(_6768,_6785,_6768)

with_output_to_chars(+Goal, -Chars) executes Goal with current output
effectively being directed to the character list Chars.  

with_input_from_chars(+Goal, +Chars) executes Goal with current input
effectively being directed to Chars.

(portray_clause is a built-in predicate which writes clauses the way that
listing does.  In particular it takes care of putting the period and newline
at the end.)

Implementationally, with_output_to_chars creates a stream which writes to a
buffer in C.  (The buffer is expanded as necessary.)  Then it executes the
goal which is its first argument with the current output set to that stream.
Finally it reads the characters in the buffer and creates a list.  No real
I/O is involved, so this will be much faster than writing to an intermediate
file.

ok@goanna.cs.rmit.oz.au (Richard A. O'Keefe) (04/24/91)

In article <EIVERSON.91Apr19200202@aigyptos.nmsu.edu>, eiverson@nmsu.edu (Eric Iverson) writes:
> The following is a letter I just wrote to Quintus:
> To: teksup@quintus.com
> Subject: converting ascii character lists to functors
> --text follows this line--
> 
> I called today about converting ascii character lists into functors
> which could be unified with other functors.  I need to do this because
> I need to use a character based read function for my file I/O.  Here's
> what I came up with:
> 
> functor_chars(Functor,Chars):-
>     atom_chars(Char1,Chars),
>     tell('functor_chars'),
>     format('~w.~n',Char1),
>     see('functor_chars'),
>     read(Functor),
>     close('functor_chars'),
>     unix(system('rm functor_chars')).

I'm sorry, but you haven't made it clear what you want this thing to
do.  The code is rather strange.  If you have a list of character codes
that you want to write to a file, that's precisely what the format
code "~s" is for.  So you should have done something like

	:- use_module(library(files), [
		remove_file/1
	   ]).

	functor_chars(Functor, Chars) :-
		SratchFileName = functor_chars,
		open(StratchFileName, write, OutputStream),
		format(OutputStream, "~s .~n", [Chars]),
		close(OutputStream),
		open(StratchFileName, read, InputStream),
		read(InputStream, Term),
		close(InputStream),
		remove_file(StratchFileName),
		Functor = Term.

And *now* I see what you want to do.  Why in the name of sanity are
you abusing the word "functor" (which means a pair consisting of a
function symbol and an arity, e.g. fred/2) when you mean "term"?

What you have here is not something that interconverts functors and
character lists, but a one-way conversion from character lists to
terms.  The operation should thus be called

	chars_to_term(+Chars, -Term)

and if you look in the library you will find that it already exists.
There are lots of useful things in the library, and you are expected
to look there _first_.

library(charsio) exports the following operations:

	chars_to_stream(Chars, Stream)

		Chars must be a ground list of character codes.
		A new input stream is created whose contents are the
		Chars, and Stream is bound to the new stream.  This
		should probably be renamed to open_string_stream/2
		or something like that.

	with_input_from_chars(Goal, Chars)

		Opens an input stream whose contents are given by the
		list of Chars, makes that the current input stream,
		and executes once(Goal).  When the Goal has finished,
		it restores the original input stream, and closes the
		character input stream it created.  Then it succeeds
		or fails the same way that once(Goal) succeeded or failed.

	with_input_from_chars(Goal, Stream, Chars)

		Opens an input stream whose contents are given by the
		list of Chars and binds Stream to the new stream.  It
		then calls once(Goal), then closes Stream before
		succeeding or failing just as once(Goal) did.

	with_output_to_chars(Goal, Chars)

		Creates a new output stream, makes that the current
		output stream, and executes once(Goal).  The idea is
		that when Goal writes to current output the characters
		are held internally.  When Goal has finished, the
		characters written by Goal are gathered up as a list
		of Chars, and the command succeeds or fails just as
		once(Goal) did.  Thus with_output_to_chars/2 can fail
		if Goal fails or if you guessed wrong about Chars, but
		in either case the stream is closed.

	with_output_to_chars(Goal, Stream, Chars)

		Creates a new output stream and binds Stream to that
		new stream, then executes once(Goal).  Goal having
		finished, the characters written to Stream are gathered
		up, Stream is closed, and the character list unified with
		Chars.  The command fails if Goal fails.

	chars_to_term(Chars, Term)

		is almost the same as
			with_input_from_chars(read(Term), Chars)
		except that it takes care of adding a clause terminator
		" . " if necessary.  For example,
		chars_to_term("fred", Term) ==> Term = fred
		chars_to_term("f(r,e(d))", Term) ==> Term = f(r,e(d))
		chars_to_term("f(X,g(X))", Term) ==> Term = f(_23,g(_23))

	term_to_chars(Term, Chars)

		is essentially the same as
			with_output_to_chars(write_canonical(Term), Chars)
		If that's not the conversion you want (and you can rely on
		no other conversion to give you something you can read back)
		then just do
			with_output_to_chars(print(Term), Chars)
		or whatever takes your fancy.  It can be quite convenient
		to do
			with_output_to_chars(format(Format,ArgList), Chars)

I _think_ library(charsio) was provided in release 1.6; it has been around
for quite a while.  The streams it manipulates are the same kind of thing
as Lisp "string streams", and do not involve external files.  The characters
you write using with_output_to_chars/[2,3] or term_to_chars/2 are held in
memory, so don't expect to write millions of them.

But *PLEASE*, 
	if you mean "term", _say_ "term"
	if you mean (function symbol/arity) pair, say "functor",
	and _only_ then
	if you mean function symbol, say "function symbol".
	DON'T say "functor" when you mean "term", it only confuses people.

-- 
Bad things happen periodically, and they're going to happen to somebody.
Why not you?					-- John Allen Paulos.

ok@goanna.cs.rmit.oz.au (Richard A. O'Keefe) (04/24/91)

In article <1991Apr21.061943.28184@comp.vuw.ac.nz,
Ray.Nickson@comp.vuw.ac.nz (Ray Nickson) writes:
: In article <EIVERSON.91Apr19200202@aigyptos.nmsu.edu
: eiverson@nmsu.edu (Eric Iverson) writes:
:    Is there some way that I could just open up a stream, write
:    things to it, and then read from it?  In other words, how can I read
:    from buffers in Quintus Prolog?  Any help would be appreciated.
: I wrote an interface to Unix pipe(2) using SICStus' foreign
: functions.  You could do it in Quintus too, though there may be a
: better way.

The Quintus Prolog library includes library(popen).  One of the features
of Quintus Prolog for a long time has been that users can define their
own types of streams.  library(popen) and library(charsio) are built on
top of that facility.  In QP3.0 this is improved and enhanced.
-- 
Bad things happen periodically, and they're going to happen to somebody.
Why not you?					-- John Allen Paulos.