1995-11-09 03:04:31 -08:00
|
|
|
(***********************************************************************)
|
|
|
|
(* *)
|
1996-04-30 07:53:58 -07:00
|
|
|
(* Objective Caml *)
|
1995-11-09 03:04:31 -08:00
|
|
|
(* *)
|
|
|
|
(* Daniel de Rauglaudre, projet Cristal, INRIA Rocquencourt *)
|
|
|
|
(* *)
|
1996-04-30 07:53:58 -07:00
|
|
|
(* Copyright 1996 Institut National de Recherche en Informatique et *)
|
1995-11-09 03:04:31 -08:00
|
|
|
(* Automatique. Distributed only by permission. *)
|
|
|
|
(* *)
|
|
|
|
(***********************************************************************)
|
|
|
|
|
|
|
|
(* $Id$ *)
|
|
|
|
|
|
|
|
(* Module [Stream]: streams and stream parsers operations *)
|
|
|
|
|
|
|
|
type 'a t
|
|
|
|
(* The type of streams containing values of type ['a]. *)
|
|
|
|
|
|
|
|
exception Parse_failure
|
1995-11-09 07:08:44 -08:00
|
|
|
(* Raised by parsers when none of the first components of the stream
|
|
|
|
patterns is accepted. *)
|
1995-11-09 03:04:31 -08:00
|
|
|
exception Parse_error of string
|
|
|
|
(* Raised by parsers when the first component of a stream pattern is
|
1995-11-09 07:08:44 -08:00
|
|
|
accepted, but one of the following components is rejected. *)
|
1995-11-09 03:04:31 -08:00
|
|
|
|
1995-11-10 07:15:12 -08:00
|
|
|
(** Stream builders *)
|
1995-12-07 11:44:19 -08:00
|
|
|
(* Warning: these functions create streams with fast access; it is illegal
|
1995-12-29 05:15:44 -08:00
|
|
|
to mix them with streams built with [[< >]]; would raise [Failure]
|
1995-12-07 11:44:19 -08:00
|
|
|
when accessing such mixed streams. *)
|
1995-11-09 03:04:31 -08:00
|
|
|
|
|
|
|
val from : (int -> 'a option) -> 'a t
|
1995-11-09 07:08:44 -08:00
|
|
|
(* [Stream.from f] returns a stream built from the function [f].
|
|
|
|
To create a new stream element, the function [f] is called with
|
|
|
|
the current stream count. The user function [f] must return either
|
|
|
|
[Some <value>] for a value or [None] to specify the end of the
|
|
|
|
stream. *)
|
1995-11-09 03:04:31 -08:00
|
|
|
val of_list : 'a list -> 'a t
|
1995-11-13 05:29:51 -08:00
|
|
|
(* Return the stream holding the elements of the list in the same
|
1995-11-09 03:04:31 -08:00
|
|
|
order. *)
|
|
|
|
val of_string : string -> char t
|
1995-11-13 05:29:51 -08:00
|
|
|
(* Return the stream of the characters of the string parameter. *)
|
1995-11-09 03:04:31 -08:00
|
|
|
val of_channel : in_channel -> char t
|
1995-11-13 05:29:51 -08:00
|
|
|
(* Return the stream of the characters read from the input channel. *)
|
1995-11-09 03:04:31 -08:00
|
|
|
|
1995-11-10 07:15:12 -08:00
|
|
|
(** Stream iterator *)
|
|
|
|
|
|
|
|
val iter : ('a -> 'b) -> 'a t -> unit
|
|
|
|
(* [Stream.iter f s] scans the whole stream s, applying function [f]
|
|
|
|
in turn to each stream element encountered. *)
|
|
|
|
|
|
|
|
(** Predefined parsers *)
|
|
|
|
|
|
|
|
val next : 'a t -> 'a
|
1995-11-13 05:29:51 -08:00
|
|
|
(* Return the first element of the stream and remove it from the
|
|
|
|
stream. Raise [Parse_failure] if the stream is empty. *)
|
1995-11-10 07:15:12 -08:00
|
|
|
val empty : 'a t -> unit
|
1995-11-13 05:29:51 -08:00
|
|
|
(* Return [()] if the stream is empty, else raise [Parse_failure]. *)
|
1995-11-10 07:15:12 -08:00
|
|
|
|
1995-12-06 07:46:34 -08:00
|
|
|
(** Useful functions *)
|
1995-11-10 07:15:12 -08:00
|
|
|
|
|
|
|
val peek : 'a t -> 'a option
|
1996-04-29 06:23:25 -07:00
|
|
|
(* Return [Some c] where [c] is the first element of the stream,
|
|
|
|
or [None] if the stream is empty. *)
|
1995-11-13 05:29:51 -08:00
|
|
|
val junk : 'a t -> unit
|
|
|
|
(* Remove the first element of the stream, possibly unfreezing
|
|
|
|
it before. *)
|
1995-11-10 07:15:12 -08:00
|
|
|
val count : 'a t -> int
|
1995-11-13 05:29:51 -08:00
|
|
|
(* Return the current count of the stream elements, i.e. the number
|
1995-11-10 07:15:12 -08:00
|
|
|
of the stream elements discarded. *)
|
|
|
|
|
1995-11-09 03:04:31 -08:00
|
|
|
(*--*)
|
|
|
|
|
|
|
|
(*** For system use only, not for the casual user *)
|
|
|
|
|
|
|
|
val sempty : 'a t
|
|
|
|
val scons : (unit -> 'a) -> 'a t -> 'a t
|
|
|
|
val sapp : (unit -> 'a t) -> 'a t -> 'a t
|
|
|
|
val dump : ('a -> unit) -> 'a t -> unit
|