123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671(** Sexp_intf: interface specification for handling S-expressions (I/O, etc.) *)openFormatopenBigarraymoduletypeS=sig(** Type of S-expressions *)typet=Type.t=Atomofstring|Listoftlist(** Type of bigstrings *)typebigstring=(char,int8_unsigned_elt,c_layout)Array1.tvalcompare:t->t->int(** {6 Defaults} *)valdefault_indent:intref(** [default_indent] reference to default indentation level for
human-readable conversions. Initialisation value: 2. *)(** {6 S-expression size} *)valsize:t->int*int(** [size sexp] @return [(n_atoms, n_chars)], where [n_atoms] is
the number of atoms in S-expression [sexp], and [n_chars] is the
number of characters in the atoms of the S-expression. *)(** {6 Scan functions} *)valscan_sexp:?buf:Buffer.t->Lexing.lexbuf->t(** [scan_sexp ?buf lexbuf] scans an S-expression from lex buffer
[lexbuf] using the optional string buffer [buf] for storing
intermediate strings. *)valscan_sexps:?buf:Buffer.t->Lexing.lexbuf->tlist(** [scan_sexps ?buf lexbuf] reads a list of whitespace separated
S-expressions from lex buffer [lexbuf] using the optional string
buffer [buf] for storing intermediate strings. *)valscan_rev_sexps:?buf:Buffer.t->Lexing.lexbuf->tlist(** [scan_rev_sexps ?buf lexbuf] same as {!scan_sexps}, but returns the
reversed list and is slightly more efficient. *)valscan_sexp_opt:?buf:Buffer.t->Lexing.lexbuf->toption(** [scan_sexp_opt ?buf lexbuf] is equivalent to [scan_sexp ?buf lexbuf]
except that it returns [None] when the eof is reached. *)valscan_iter_sexps:?buf:Buffer.t->f:(t->unit)->Lexing.lexbuf->unit(** [scan_iter_sexps ?buf ~f lexbuf] iterates over all whitespace
separated S-expressions scanned from lex buffer [lexbuf] using
function [f], and the optional string buffer [buf] for storing
intermediate strings. *)valscan_fold_sexps:?buf:Buffer.t->f:('a->t->'a)->init:'a->Lexing.lexbuf->'a(** [scan_fold_sexps ?buf ~f ~init lexbuf] folds over all whitespace
separated S-expressions scanned from lex buffer [lexbuf] using
function [f], initial state [init], and the optional string buffer
[buf] for storing intermediate strings. *)valscan_sexps_conv:?buf:Buffer.t->f:(t->'a)->Lexing.lexbuf->'alist(** [scan_sexps_conv ?buf ~f lexbuf] maps all whitespace separated
S-expressions scanned from lex buffer [lexbuf] to some list using
function [f], and the optional string buffer [buf] for storing
intermediate strings. *)(** {6 Type and exception definitions for (partial) parsing} *)moduleParse_pos:sig(** Position information after complete parse *)typet=Pre_sexp.Parse_pos.t=private{mutabletext_line:int;(** Line position in parsed text *)mutabletext_char:int;(** Character position in parsed text *)mutableglobal_offset:int;(** Global/logical offset *)mutablebuf_pos:int;(** Read position in string buffer *)}valcreate:?text_line:int->?text_char:int->?buf_pos:int->?global_offset:int->unit->t(** [create ?text_line ?text_char ?buf_pos ?global_offset ()] @return
a parse position with the given parameters.
@param text_line default = [1]
@param text_char default = [0]
@param global_offset default = [0]
@param buf_pos default = [0]
*)valwith_buf_pos:t->int->t(** [with_buf_pos t pos] @return a copy of the parse position [t] where
[buf_pos] is set to [pos]. *)endmoduleCont_state:sig(** State of parser continuations *)typet=Pre_sexp.Cont_state.t=|Parsing_toplevel_whitespace|Parsing_nested_whitespace|Parsing_atom|Parsing_list|Parsing_sexp_comment|Parsing_block_commentvalto_string:t->string(** [to_string cont_state] converts state of parser continuation
[cont_state] to a string. *)end(** Type of result from calling {!Sexp.parse}. *)type('a,'t)parse_result=('a,'t)Pre_sexp.parse_result=|Doneof't*Parse_pos.t(** [Done (t, parse_pos)] finished parsing
an S-expression. Current parse position
is [parse_pos]. *)|ContofCont_state.t*('a,'t)parse_fun(** [Cont (cont_state, parse_fun)] met the end of input before completely
parsing an S-expression. The user has to call [parse_fun] to
continue parsing the S-expression in another buffer. [cont_state]
is the current parsing state of the continuation.
NOTE: the continuation may only be called once and will raise
[Failure] otherwise! *)(** Type of parsing functions with given offsets and lengths. *)and('a,'t)parse_fun=pos:int->len:int->'a->('a,'t)parse_result(** Module for parsing S-expressions annotated with location information *)moduleAnnotated:sig(** Position information for annotated S-expressions *)typepos=Pre_sexp.Annotated.pos={line:int;col:int;offset:int;}(** Range information for annotated S-expressions *)typerange=Pre_sexp.Annotated.range={start_pos:pos;end_pos:pos}(** S-expression annotated with location information *)typet=Pre_sexp.Annotated.t=|Atomofrange*Type.t|Listofrange*tlist*Type.t(** Type of conversion results of annotated S-expressions. *)type'aconv=[`Resultof'a|`Errorofexn*t](** Exception associated with conversion errors. First argument describes
the location, the second the reason. *)exceptionConv_exnofstring*exn(** Stack used by annotation parsers *)typestack=Pre_sexp.Annotated.stack={mutablepositions:poslist;mutablestack:tlistlist;}valget_sexp:t->Type.t(** [get_sexp annot_sexp] @return S-expression associated with annotated
S-expression [annot_sexp]. *)valget_range:t->range(** [get_range annot_sexp] @return the range associated with annotated
S-expression [annot_sexp]. *)valfind_sexp:t->Type.t->toption(** [find_sexp annot_sexp sexp] @return [Some res] where [res] is the
annotated S-expression that is physically equivalent to [sexp] in
[annot_sexp], or [None] if there is no such S-expression. *)(** {6 Annotated (partial) parsing} *)valparse:?parse_pos:Parse_pos.t->?len:int->string->(string,t)parse_result(** [parse ?parse_pos ?len str] same as {!parse}, but returns an
S-expression annotated with location information. *)valparse_bigstring:?parse_pos:Parse_pos.t->?len:int->bigstring->(bigstring,t)parse_result(** [parse_bigstring ?parse_pos ?len str] same as {!parse_bigstring},
but returns an S-expression annotated with location information. *)valinput_sexp:?parse_pos:Parse_pos.t->in_channel->t(** [input_sexp ?parse_pos ic] like {!input_sexp}, but returns an
annotated S-expression instead. *)valinput_sexps:?parse_pos:Parse_pos.t->?buf:bytes->in_channel->tlist(** [input_sexps ?parse_pos ?buf ic] like {!input_sexps}, but returns
a list of annotated S-expressions. *)valinput_rev_sexps:?parse_pos:Parse_pos.t->?buf:bytes->in_channel->tlist(** [input_sexps ?parse_pos ?buf ic] like {!input_rev_sexps}, but
returns a list of annotated S-expressions. *)(** {6 Loading of annotated S-expressions} *)(** NOTE: these functions should only be used if an annotated S-expression
is required. *)valload_sexp:?strict:bool->?buf:bytes->string->t(** [load_sexp ?strict ?buf file] like {!load_sexp}, but returns an
annotated S-expression. *)valload_sexps:?buf:bytes->string->tlist(** [load_sexps ?buf file] like {!load_sexps}, but returns a list of
annotated S-expressions. *)valload_rev_sexps:?buf:bytes->string->tlist(** [load_rev_sexps ?buf file] like {!load_rev_sexps}, but returns a
list of annotated S-expressions. *)(** {6 String and bigstring conversions} *)valof_string:string->t(** [of_string str] same as {!of_string}, but returns an annotated
S-expression. *)valof_bigstring:bigstring->t(** [of_bigstring bstr] same as {!of_string}, but operates on bigstrings. *)(** Converters using annotations for determining error locations *)valconv:(Type.t->'a)->t->'aconv(** [conv f annot_sexp] converts the S-expression associated with
annotated S-expression [annot_sexp] using [f]. @return [`Result
res] on success, or [`Error (exn, sub_annot_sexp)] otherwise, where
[exn] is the exception associated with the conversion error, and
[sub_annot_sexp] is the annotated S-expression on which conversion
failed. *)valget_conv_exn:file:string->exc:exn->t->exn(** [get_conv_exn ~file ~exc annot_sexp] @return the exception that
would be raised for a given [file] and exception [exc]
if conversion had failed on annotated S-expression [annot_sexp].
The format of the exception message is "file:line:col" *)end(** Type of state maintained during parsing *)type'tparse_state='tPre_sexp.parse_state=private{parse_pos:Parse_pos.t;(** Current parse position *)mutablepstack:'t;(** Stack of found S-expression lists *)pbuf:Buffer.t;(** Current atom buffer *)}(** Type of parse errors *)typeparse_error=Pre_sexp.parse_error={location:string;(** Function in which the parse failed *)err_msg:string;(** Reason why parsing failed *)parse_state:[|`Sexpoftlistlistparse_state|`AnnotofAnnotated.stackparse_state](** State of parser *)}(** Exception raised during partial parsing *)exceptionParse_errorofparse_error(** {6 Unannotated (partial) parsing} *)valparse:?parse_pos:Parse_pos.t->?len:int->string->(string,t)parse_result(** [parse ?parse_pos ?len str] (partially) parses an S-expression in string buffer
[str] starting out with position information provided in [parse_pos] and reading at
most [len] characters. To parse a single atom that is not delimited by whitespace
it is necessary to call this function a second time with the returned continuation,
and a dummy buffer that contains whitespace.
[parse] starts parsing [str] at position [parse_pos.buf_pos]. Each subsequent
[parse_fun] from a [Cont] uses the [buf] and [pos] that is supplied to it. The
final [parse_fun] that returns [Done] mutates the [buf_pos] in the originally
supplied [parse_pos], and then returns it.
@param parse_pos default = [Parse_pos.create ()]
@param len default = [String.length str - parse_pos.Parse_pos.buf_pos]
*)valparse_bigstring:?parse_pos:Parse_pos.t->?len:int->bigstring->(bigstring,t)parse_result(** [parse_bigstring ?parse_pos ?len str] same as {!parse}, but operates on
bigstrings. *)valinput_sexp:?parse_pos:Parse_pos.t->in_channel->t(** [input_sexp ?parse_pos ic] parses an S-expression from input channel
[ic] using initial position information in [parse_pos]. NOTE: this
function is not as fast on files as {!Sexp.load_sexp}, and is also
slightly slower than the scan-functions. But it is guaranteed that
[input_sexp] is only going to read data parseable as an S-expression.
Thus, subsequent input functions will see the data immediately
following it.
@param parse_pos default = [Parse_pos.create ()]
*)valinput_sexps:?parse_pos:Parse_pos.t->?buf:bytes->in_channel->tlist(** [input_sexps ?parse_pos ?buf ic] parses whitespace separated
S-expressions from input channel [ic] until EOF is reached. Faster than
the scan-functions.
@param parse_pos default = [Parse_pos.create ()]
*)valinput_rev_sexps:?parse_pos:Parse_pos.t->?buf:bytes->in_channel->tlist(** [input_rev_sexps ?parse_pos ?buf ic] same as {!Sexp.input_sexps},
but returns a reversed list of S-expressions, which is slightly more
efficient. *)(** {6 Loading of (converted) S-expressions} *)valload_sexp:?strict:bool->?buf:bytes->string->t(** [load_sexp ?strict ?buf file] reads one S-expression from [file] using
buffer [buf] for storing intermediate data. Faster than the
scan-functions.
@raise Parse_error if the S-expression is unparseable.
@raise Failure if parsing reached the end of file before one S-expression
could be read.
@raise Failure if [strict] is true and there is more than one
S-expression in the file.
@param strict default = [true]
*)valload_sexps:?buf:bytes->string->tlist(** [load_sexps ?buf file] reads a list of whitespace separated S-expressions
from [file] using buffer [buf] for storing intermediate data.
Faster than the scan-functions.
@raise Parse_error if there is unparseable data in the file.
@raise Failure if parsing reached the end of file before the last
S-expression could be fully read.
*)valload_rev_sexps:?buf:bytes->string->tlist(** [load_rev_sexps ?buf file] same as {!Sexp.load_sexps}, but returns a
reversed list of S-expressions, which is slightly more efficient. *)valload_sexp_conv:?strict:bool->?buf:bytes->string->(t->'a)->'aAnnotated.conv(** [load_sexp_conv ?strict ?buf file f] like {!Sexp.load_sexp}, but
performs a conversion on the fly using [f]. Performance is equivalent
to executing {!Sexp.load_sexp} and performing conversion when there
are no errors. In contrast to the plain S-expression loader, this
function not only performs the conversion, it will give exact error
ranges for conversion errors.
@raise Parse_error if there is unparseable data in the file.
@raise Failure if parsing reached the end of file before the last
S-expression could be fully read.
*)valload_sexp_conv_exn:?strict:bool->?buf:bytes->string->(t->'a)->'a(** [load_sexp_conv_exn ?strict ?buf file f] like {!load_sexp_conv},
but returns the converted value or raises [Of_sexp_error] with exact
location information in the case of a conversion error. *)valload_sexps_conv:?buf:bytes->string->(t->'a)->'aAnnotated.convlist(** [load_sexps_conv ?buf file f] like {!Sexp.load_sexps}, but performs
a conversion on the fly using [f]. Performance is equivalent to
executing {!Sexp.load_sexps} and performing conversion when there
are no errors. In contrast to the plain S-expression loader, this
function not only performs the conversion, it will give exact error
ranges for conversion errors.
@raise Parse_error if there is unparseable data in the file.
@raise Failure if parsing reached the end of file before the last
S-expression could be fully read.
*)valload_sexps_conv_exn:?buf:bytes->string->(t->'a)->'alist(** [load_sexps_conv_exn ?buf file f] like {!load_sexps_conv}, but returns
the converted value or raises [Of_sexp_error] with exact location
information in the case of a conversion error. *)(** {6 Output of S-expressions to I/O-channels} *)(** NOTE: for performance reasons these output functions may need to
allocate large strings to write out huge S-expressions. This may
cause problems on 32-bit platforms. If you think that you may need to
write huge S-expressions on such platforms, you might want to use the
pretty-printers that write to formatters instead (see further below). *)valoutput_hum:out_channel->t->unit(** [output_hum oc sexp] outputs S-expression [sexp] to output channel
[oc] in human readable form. *)valoutput_hum_indent:int->out_channel->t->unit(** [output_hum_indent indent oc sexp] outputs S-expression [sexp]
to output channel [oc] in human readable form using indentation level
[indent].
*)valoutput_mach:out_channel->t->unit(** [output_mach oc sexp] outputs S-expression [sexp] to output channel
[oc] in machine readable (i.e. most compact) form. *)valoutput:out_channel->t->unit(** [output oc sexp] same as [output_mach]. *)(** {6 Output of S-expressions to file} *)(** All save-functions write to a temporary file before moving it into
place to avoid intermittent garbling of existing files, which may
cause problems for other processes that try to read. *)valsave_hum:?perm:int->string->t->unit(** [save_hum ?perm file sexp] outputs S-expression [sexp] to [file] in human
readable form.
@param perm default = umask
*)valsave_mach:?perm:int->string->t->unit(** [save_mach ?perm file sexp] outputs S-expression [sexp] to [file]
in machine readable (i.e. most compact) form.
@param perm default = umask
*)valsave:?perm:int->string->t->unit(** [save ?perm file sexp] same as {!save_mach}. *)valsave_sexps_hum:?perm:int->string->tlist->unit(** [save_sexps_hum ?perm file sexps] outputs S-expression list [sexps] to
[file] in human readable form, each sexp being followed by a newline.
@param perm default = umask
*)valsave_sexps_mach:?perm:int->string->tlist->unit(** [save_sexps_mach ?perm file sexps] outputs S-expression list [sexps] to
[file] in machine readable form, each sexp being followed by a
newline.
@param perm default = umask
*)valsave_sexps:?perm:int->string->tlist->unit(** [save_sexps ?perm file sexp] same as {!save_sexps_mach}. *)(** {6 Output of S-expressions to formatters} *)valpp_hum:formatter->t->unit(** [pp_hum ppf sexp] outputs S-expression [sexp] to formatter [ppf]
in human readable form. *)valpp_hum_indent:int->formatter->t->unit(** [pp_hum_indent n ppf sexp] outputs S-expression [sexp] to formatter
[ppf] in human readable form and indentation level [n]. *)valpp_mach:formatter->t->unit(** [pp_mach ppf sexp] outputs S-expression [sexp] to formatter [ppf]
in machine readable (i.e. most compact) form. *)valpp:formatter->t->unit(** [pp ppf sexp] same as [pp_mach]. *)(** {6 String and bigstring conversions} *)(** Module encapsulating the exception raised by string converters when
type conversions fail. *)moduleOf_string_conv_exn:sigtypet={exc:exn;sexp:Type.t;sub_sexp:Type.t}exceptionEoftendvalof_string:string->t(** [of_string str] converts string [str] to an S-expression. NOTE:
trailing whitespace is considered an error, which may be overly
strict for some applications. Either strip the string of trailing
whitespace first, or, even cheaper, use {!parse} instead. *)valof_string_conv:string->(t->'a)->'aAnnotated.conv(** [of_string_conv str conv] like {!of_string}, but performs type conversion
with [conv]. @return conversion result. *)valof_string_conv_exn:string->(t->'a)->'a(** [of_string_conv_exn str conv] like {!of_string_conv}, but raises
{!Of_string_conv_exn.E} if type conversion fails. @return converted
value. *)valof_bigstring:bigstring->t(** [of_bigstring bstr] same as {!of_string}, but operates on bigstrings. *)valof_bigstring_conv:bigstring->(t->'a)->'aAnnotated.conv(** [of_bigstring_conv bstr conv] like {!of_bigstring}, but performs
type conversion with [conv]. @return conversion result. *)valof_bigstring_conv_exn:bigstring->(t->'a)->'a(** [of_bigstring_conv_exn bstr conv] like {!of_bigstring_conv}, but raises
{!Of_string_conv_exn.E} if type conversion fails. @return converted
value. *)valto_string_hum:?indent:int->t->string(** [to_string_hum ?indent sexp] converts S-expression [sexp] to a
string in human readable form with indentation level [indent].
@param indent default = [!default_indent]
*)valto_string_mach:t->string(** [to_string_mach sexp] converts S-expression [sexp] to a string in
machine readable (i.e. most compact) form. *)valto_string:t->string(** [to_string sexp] same as [to_string_mach]. *)(** {6 Buffer conversions} *)valto_buffer_hum:buf:Buffer.t->?indent:int->t->unit(** [to_buffer_hum ~buf ?indent sexp] outputs the S-expression [sexp]
converted to a string in human readable form to buffer [buf].
@param indent default = [!default_indent]
*)valto_buffer_mach:buf:Buffer.t->t->unit(** [to_buffer_mach ~buf sexp] outputs the S-expression [sexp] converted
to a string in machine readable (i.e. most compact) form to buffer [buf].
*)valto_buffer:buf:Buffer.t->t->unit(** [to_buffer ~buf sexp] same as {!to_buffer_mach}. *)valto_buffer_gen:buf:'buffer->add_char:('buffer->char->unit)->add_string:('buffer->string->unit)->t->unit(** [to_buffer_gen ~buf ~add_char ~add_string sexp] outputs the S-expression
[sexp] converted to a string to buffer [buf] using the output functions
[add_char] and [add_string]. *)(** {6 Utilities for automated type conversions} *)valunit:t(** [unit] the unit-value as expressed by an S-expression. *)valis_unit:t->boolvalsexp_of_t:t->t(** [sexp_of_t sexp] maps S-expressions which are part of a type with
automated S-expression conversion to themselves. *)valt_of_sexp:t->t(** [t_of_sexp sexp] maps S-expressions which are part of a type with
automated S-expression conversion to themselves. *)(** {6 Utilities for conversion error handling} *)typefound=[`Found|`Posofint*found](** Type of successful search results. [`Found] means that an
S-expression was found at the immediate position, and [`Pos (pos,
found)] indicates that it was found at position [pos] within a
structure (= S-expression list) where [found] describes recursively
where it was found in that structure. *)typesearch_result=[`Not_found|found](** Type of search results. [`Not_found] means that an
S-expression was not found within another S-expression. *)valsearch_physical:t->contained:t->search_result(** [search_physical sexp ~contained] @return the search result
indicating whether, and if, where the S-expression [contained]
was found within S-expression [sexp]. *)valsubst_found:t->subst:t->found->t(** [subst_found sexp ~subst found] @return the S-expression that
results from substituting [subst] within S-expression [sexp]
at the location described by [found]. *)(** S-expressions annotated with relative source positions and comments *)moduleWith_layout:sig(* relative source positions *)typepos=Src_pos.Relative.t={row:int;col:int}valsexp_of_pos:pos->Type.t(** S-expressions annotated with relative source positions and comments. All the
positions are relative to the opening paren of the enclosing list, or the first
character of the file. *)typet=Type_with_layout.t=|Atomofpos*string*stringoption(* second is quoted representation *)|Listofpos*t_or_commentlist*pos(* positions of left and right parens *)andt_or_comment=Type_with_layout.t_or_comment=|Sexpoft|Commentofcommentandcomment=Type_with_layout.comment=|Plain_commentofpos*string(* line or block comment *)|Sexp_commentofpos*commentlist*t(* position of #; *)valsexp_of_t:t->Type.tvalsexp_of_comment:comment->Type.tvalsexp_of_t_or_comment:t_or_comment->Type.tmoduleForget:sigvalt:t->Type.tvalt_or_comment:t_or_comment->Type.toptionvalt_or_comments:t_or_commentlist->Type.tlistendmoduleRender:sigtypeasexptype'at(* monad for position-respecting asexp rendering *)valreturn:'a->'atvalbind:'at->f:('a->'bt)->'btvalsexp:asexp->unitt(* assumes that positions in [asexp] are relative *)valrun:(char->unit)->unitt->unitendwithtypeasexp:=t_or_commentmoduleParser:sigtypetokenvalsexp:(Lexing.lexbuf->token)->Lexing.lexbuf->t_or_commentvalsexp_opt:(Lexing.lexbuf->token)->Lexing.lexbuf->t_or_commentoptionvalsexps:(Lexing.lexbuf->token)->Lexing.lexbuf->t_or_commentlistvalrev_sexps:(Lexing.lexbuf->token)->Lexing.lexbuf->t_or_commentlist(* for debugging only, cannot be used otherwise anyway *)valsexps_abs:(Lexing.lexbuf->token)->Lexing.lexbuf->Type_with_layout.Parsed.t_or_commentlistendmoduleLexer:sigvalmain:?buf:Buffer.t->Lexing.lexbuf->Parser.tokenendendend