1%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
    2/*	Nan.Numerics.Prime
    3	A simple prime number library
    4	Copyright 2016 Julio P. Di Egidio
    5	<mailto:julio@diegidio.name>
    6	<http://julio.diegidio.name/Projects/Nan.Numerics.Prime/>
    7	
    8	This file is part of Nan.Numerics.Prime.
    9	
   10	Nan.Numerics.Prime is free software: you can redistribute it and/or modify
   11	it under the terms of the GNU General Public License as published by
   12	the Free Software Foundation, either version 3 of the License, or
   13	(at your option) any later version.
   14	
   15	Nan.Numerics.Prime is distributed in the hope that it will be useful,
   16	but WITHOUT ANY WARRANTY; without even the implied warranty of
   17	MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
   18	GNU General Public License for more details.
   19	
   20	You should have received a copy of the GNU General Public License
   21	along with Nan.Numerics.Prime.  If not, see <http://www.gnu.org/licenses/>.
   22*/

   23%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   24
   25% (SWI-Prolog 7.3.25)
   26
   27% TODO: Improve leveraging of library(pio)?
   28
   29:- module(prime_pio, []).
   30
   31:- public
   32	open_/3,		% +File:file, +Mode:oneof(read,write), :Goal:callable
   33	read_/2,		% +Stream:stream, :GAdd:callable
   34	write_/2.		% +Stream:stream, :GGen:callable

A simple prime number library :: pure I/O

Module prime_pio provides low-level predicates to read/write from/to a file or stream all consecutive prime numbers starting from 2 and up to a certain limit that is determined by the caller.

The accepted file format is a comma-separated list of the consecutive prime numbers starting from 2 and terminated by a period.

NOTE: Predicates in this module are not meant for public use.

author
- Julio P. Di Egidio
version
- 1.2.5-beta
license
- GNU GPLv3 */
   53:- use_module(library(dcg/basics)).
   54:- use_module(library(pio)).
   55
   56%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   57
   58file__opts(read,
   59	[	lock(read),
   60		eof_action(error)
   61	|	BaseOpts
   62	]) :-
   63	file__opts(BaseOpts).
   64file__opts(write,
   65	[	lock(write),
   66		buffer(full)
   67	|	BaseOpts
   68	]) :-
   69	file__opts(BaseOpts).
   70
   71stream__opts(read,
   72	[	eof_action(error)
   73	|	BaseOpts
   74	]) :-
   75	stream__opts(BaseOpts).
   76stream__opts(write,
   77	[	buffer(full),
   78		representation_errors(error)
   79	|	BaseOpts
   80	]) :-
   81	stream__opts(BaseOpts).
   82
   83file__opts(
   84	[	bom(false),
   85		encoding(ascii),
   86		type(text)
   87	]).
   88
   89stream__opts(
   90	[	encoding(ascii),
   91		type(text),
   92		record_position(true),	% NOTE: Must be true for pio:stream_to_lazy_list/2.
   93		buffer_size(1024)		% TODO: Review this. #####
   94	]).
   95
   96%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 open_(+File:file, +Mode:oneof(read,write), :Goal:callable) is det
Opens File in Mode and calls back Goal(Stream) where Stream is the opened I/O stream. Mode can be one of read or write. File is automatically closed after Goal is finished.

Encoding of file is ascii, type is text, buffering is full.

Errors
- Errors from open/4.
  108:- meta_predicate
  109	open_(+, +, 1).
  110
  111open_(File, Mode, Goal) :-
  112	file__opts(Mode, Opts),
  113	setup_call_cleanup(
  114		open(File, Mode, Stream, [wait(false)| Opts]),
  115		call(Goal, Stream),
  116		close(Stream, [force(false)])
  117	).
 read_(+Stream:stream, :GAdd:callable) is det
Reads consecutive prime numbers from Stream. The file must not be empty and numbers must start at 2. For every read number greater than 2 calls GAdd(+P0:prime +P:prime), where P0 is the previously read number and P is the current number. Stops reading either at end-of-stream or when the call to GAdd fails.

Encoding of stream is ascii, type is text, buffer size is 1024.

NOTE: Does not check that the numbers read from the stream are consecutive prime numbers starting from 2.

Errors
- syntax_error(invalid_format) Input format is invalid.
- syntax_error(invalid_start) Input values must start at 2.
- syntax_error(invalid_value) Input values must be posint.
- Errors from read/2.
To be done
- Improve parse errors?
  138:- meta_predicate
  139	read_(+, 2).
  140
  141read_(Stream, GAdd) :-
  142	set_stream_(Stream, read),
  143	stream_to_lazy_list(Stream, List),
  144	phrase(parse_(GAdd), List, _).
  145
  146:- meta_predicate
  147	parse_(2, +, -),
  148	parse__p(2, +, +, -),
  149	parse__add(2, +, +, +, -),
  150	parse__sel(2, +, +, -).
  151
  152parse_(GAdd) --> "2", !,
  153	parse__sel(GAdd, 2).
  154parse_(_) -->
  155	syntax_error(invalid_start).
  156
  157parse__p(GAdd, P0) --> integer(P), { P > 0 }, !,
  158	parse__add(GAdd, P0, P).
  159parse__p(_, _) -->
  160	syntax_error(invalid_value).
  161
  162parse__add(GAdd, P0, P) -->
  163	{ call(GAdd, P0, P) }, !,
  164	parse__sel(GAdd, P).
  165parse__add(_, _, _) --> [].
  166
  167parse__sel(GAdd, P0) --> ",", !,
  168	parse__p(GAdd, P0).
  169parse__sel(_, _) --> ".", eos, !.
  170parse__sel(_, _) -->
  171	syntax_error(invalid_format).
 write_(+Stream:stream, :GGen:callable) is det
Writes consecutive prime numbers to Stream. Always writes the number 2, then writes all numbers generated by calling GGen(-P:prime), where P shall be greater than 2. Stops writing when bactracking on GGen terminates.

Encoding of stream is ascii, type is text, buffering is full, buffer size is 1024.

NOTE: Does not check that the numbers generated by GGen are consecutive prime numbers starting from 3.

Errors
- Errors from write/2.
  188:- meta_predicate
  189	write_(+, 1).
  190
  191write_(Stream, GGen) :-
  192	set_stream_(Stream, write),
  193	write(Stream, 2),
  194	ignore(forall(
  195		call(GGen, P),
  196		(	write(Stream, ','),
  197			write(Stream, P)
  198		)
  199	)),
  200	write(Stream, '.').
  201
  202set_stream_(Stream, Mode) :-
  203	stream__opts(Mode, Opts),
  204	set_stream__do(Stream, Opts).
  205
  206set_stream__do(_, []) :- !.
  207set_stream__do(Stream, [Opt| Opts]) :-
  208	set_stream(Stream, Opt),
  209	set_stream__do(Stream, Opts).
  210
  211%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%