1995-11-09 03:04:31 -08:00
|
|
|
(***********************************************************************)
|
|
|
|
(* *)
|
|
|
|
(* Caml Special Light *)
|
|
|
|
(* *)
|
|
|
|
(* Daniel de Rauglaudre, projet Cristal, INRIA Rocquencourt *)
|
|
|
|
(* *)
|
|
|
|
(* Copyright 1995 Institut National de Recherche en Informatique et *)
|
|
|
|
(* 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-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
|
|
|
|
(* Returns the stream holding the elements of the list in the same
|
|
|
|
order. *)
|
|
|
|
val of_string : string -> char t
|
1995-11-09 07:08:44 -08:00
|
|
|
(* Returns the character stream of the string parameter. *)
|
1995-11-09 03:04:31 -08:00
|
|
|
val of_channel : in_channel -> char t
|
|
|
|
(* Returns the characters stream read from the input channel. *)
|
|
|
|
|
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
|
|
|
|
(* Returns the first element of the stream and removes it from the
|
|
|
|
stream. Raises [Parse_failure] if the stream is empty. *)
|
|
|
|
val empty : 'a t -> unit
|
|
|
|
(* Returns [()] if the stream is empty, else raises [Parse_failure]. *)
|
|
|
|
|
|
|
|
(** Usefull functions *)
|
|
|
|
|
|
|
|
val peek : 'a t -> 'a option
|
|
|
|
(* Returns [Some] "the first element" of the stream, or [None] if the
|
|
|
|
stream is empty. *)
|
|
|
|
val count : 'a t -> int
|
|
|
|
(* Returns the current count of the stream elements, i.e. the number
|
|
|
|
of the stream elements discarded. *)
|
|
|
|
|
1995-11-09 03:04:31 -08:00
|
|
|
(*--*)
|
|
|
|
|
|
|
|
(*** For system use only, not for the casual user *)
|
|
|
|
|
|
|
|
val junk : 'a t -> unit
|
|
|
|
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
|