How do I load data from an arbitrary file format into prolog?

I have some data in a file in the following format:

A)B
B)C

It describes nodes in a graph. The above would look like this if it were drawn out:

A -> B -> C

I want to write a Prolog program that can tell me if A can get to C, but I can’t seem to figure out how to open files, nor parse them into facts/relations.

I thought I could follow an example of how to read a single line from a file like this:

:- set_prolog_flag(verbose, silent).
:- initialization(main).

main :-
    open('input/day06.example', read, Stream),
    read(Stream, One),
    close(Stream),
    write([One]), nl,
    halt.

main :- halt(1).

But this breaks because it seems that read/2 is only for reading from Prolog files.

How do I parse data of an arbitrary format in Prolog? In Python, you could do something like this, splitting the contents of a file on new lines and then split each line on your delimiter:

table = []
with open("input/day06.example") as f:
  for line in f.read().strip().split("\n"):
    left, right = line.split(")")
    table.append((left, right))

Is it possible to do something similar in Prolog?

Thanks!

You can write a simple parser for your file format using DCGs. For a nice tutorial, see:

http://www.pathwayslms.com/swipltuts/dcg/

SWI-Prolog has two sections in the documentation that cover reading of data. One is about using terms, which is not what you want and the other is about reading primitive data which is probably what you want and is closest to the Python example you understand.

As Paulo notes, using DCGs is the best way to parse such files, but one has to know DCGs and while they are sometimes easy to get simple examples working, on more complex examples they can have you pulling your hair out.

Dear cpdean,

DCGs are definitely worth studying. There are a number of examples
within the SWI sources. Such as in library(csv).

For something fast and dirty that depends on external packs (lib, & stoics_lib) :
file grapho.pl

:- use_module(library(lib)).

:- lib(stoics_lib).
:- debug(grapho).

grapho :-
    io_lines( 'abc.gra', Lists ),
    debug( grapho, 'Lines: ~w', [Lists] ),
    maplist( edge_line, Lists, Edges ),
    debug( grapho, 'Edges: ~w', [Edges] ).

edge_line( Codes, From->To ) :-
    append( PfxCs, [0')|PsfCs], Codes ),
    !,
    atom_codes( From, PfxCs ),
    atom_codes( To, PsfCs ).

file abc.gra
A)B
B)C

test:

κρότος;private/stoics% swipl -f grapho.pl 
Welcome to SWI-Prolog...
,,,,
For built-in help, use ?- help(Topic). or ?- apropos(Word).

?- grapho.
% Lines: [[65,41,66],[66,41,67]]
% Edges: [(A->B),(B->C)]
true.

Regards,

Nicos Angelopoulos

http://stoics.org.uk/~nicos

How do I run a prolog file as a script that exits?

swipl my_file.pl always leaves it open in a repl/interpreter.

Disclaimer: it is still more useful to learn how to do stuff from the toplevel, but it takes time to get used to it.

TL;DR: Use swipl -g <something> -g halt my_file.pl. But this depends on your “script”. I will use your previous question to make a small example.

For parsing almost any “structured text” file, DCGs are by far the best option. I am very shocked that no one above mentioned library(dcg/basics) and library(dcg/high_order) that are part of the standard distribution!

… and, I prefer to use modules. Here is the full code listing for a small module. It exports a single predicate that takes a file name and gives you the total number of From-->To “connections” (in your example, you have three connections, A-->B, B-->C, A-->C).

All the Prolog code is in a file orbits.pl:

:- module(orbits, [orbits_conncount/2]).
:- use_module(library(dcg/basics)).
:- use_module(library(dcg/high_order)).
:- use_module(library(ugraphs)).

orbits_conncount(File, N) :-
    phrase_from_file(sequence(orbit, "\n", Orbits), File),
    vertices_edges_to_ugraph([], Orbits, G),
    transitive_closure(G, C),
    pairs_values(C, Vs),
    maplist(length, Vs, Ns),
    sumlist(Ns, N).

orbit(A-B) -->
    string_without(")", Ac),
    ")",
    string_without("\n", Bc),
    {   atom_codes(A, Ac),
        atom_codes(B, Bc)
    }.

The input file is input:

$ cat input
A)B
B)C

This you can run on the command line (in Bash at least) like this:

$ swipl -g 'use_module(orbits),orbits_conncount(input,C),format("~w~n",[C])' -g halt
3

(I am ignoring any quoting issues you might run into…)

The reason why I made a module and put code on the command line is that I can use the same module from the top level, like this:

?- use_module(orbits).
true.

?- orbits_conncount(input, N).
N = 3.

The question in your first email: like @pmoura advised and @EricGT seemed to agree, use DCGs. The two libraries dcg/basics and dcg/high_order give you a lot of stuff for free. See the code in the example above and read the docs.

Finally (this got too long!), whenever you see a directed unweighted graph, try to see if library(ugraphs) can be useful. See the code in the example.

Hmmm … I use swipl -g <something> -t halt my_file.pl.
See SWI-Prolog -- Running goals from the command line and SWI-Prolog -- Initialisation files and goals

An alternative is to use the initialization directive in your script (the goal should end with halt). You can also “compile” the script so that you don’t need to specify swipl:

swipl --goal=<something> --stand_alone=true --undefined=error \
    --foreign=save -o <script-name> -c my_file.pl

Hi, I also get my “wisdom” from https://www.swi-prolog.org/pldoc/man?section=runoptions, I admit that I don’t truly undestand the difference between -g halt and -t halt. For the use case “run a prolog program as if it is a command line program, from the shell” it seems that the two are equivalent? Not sure.

PS: both behave identically in terms of exit codes, so 0 for success, 1 for failure, 2 for exception thrown.

What would be an example of -t halt and -g halt behaving differently? It seems it would be something in the -g <goal> that comes before the -g halt or -t halt?

-t halt replaces the top-level REPL (interactive top level). If the goal (specified by the first -g parameter) throws an exception, I suspect that there are some situations where the result could be different; but a quick experiment didn’t show anything significant.