Module CCApp_parse

module CCApp_parse: sig .. end
Deprecated.CCParse is more expressive and stable

status: deprecated

Applicative Parser Combinators

Example: basic S-expr parser

  open Containers_string.App_parse;;

  type sexp = Atom of string | List of sexp list;;

  let mkatom a = Atom a;;
  let mklist l = List l;;

  let ident_char = alpha_num <+> any_of "|!;$#@%&-_/=*.:~+[]<>'" ;;
  let ident = many1 ident_char >|= str_of_l ;;
  let atom = (ident <+> quoted) >|= mkatom ;;

  let sexp = fix (fun sexp ->
    white >>
      (atom <+>
       ((char '(' >> many sexp << char ')') >|= mklist)
      )
  );;

  Str.parse_exn "(a (b c d) e)" sexp;;


Since 0.10

type ('a, 'b) result = [ `Error of 'b | `Ok of 'a ] 
type 'a t 
Parser that yields an error or a value of type 'a

Combinators

val return : 'a -> 'a t
Parser that succeeds with the given value
val pure : 'a -> 'a t
Synonym to CCApp_parse.return
val junk : unit t
Skip next char
val fail : string -> 'a t
fail msg fails with the given error message
val failf : ('a, unit, string, 'b t) Pervasives.format4 -> 'a
val app : ('a -> 'b) t -> 'a t -> 'b t
Applicative
val map : ('a -> 'b) -> 'a t -> 'b t
Map the parsed value
val int : int t
Parse an integer
val float : float t
Parse a floating point number
val bool : bool t
Parse "true" or "false"
val char : char -> char t
char c parses c and c only
val any_of : string -> char t
Parse any of the chars present in the given string
val alpha_lower : char t
val alpha_upper : char t
val alpha : char t
val symbols : char t
Symbols, such as "!-=_"...
val num : char t
val alpha_num : char t
val word : string t
word parses any identifier not starting with an integer and not containing any whitespace nor delimiter TODO: specify
val quoted : string t
Quoted string, following OCaml conventions
val str_of_l : char list -> string
Helper to build strings from lists of chars
val spaces : unit t
Parse a sequence of '\t' and ' '
val spaces1 : unit t
Same as CCApp_parse.spaces but requires at least one space
val white : unit t
Parse a sequence of '\t', '\n' and ' '
val white1 : unit t
val eof : unit t
Matches the end of input, fails otherwise
val many : ?sep:unit t -> 'a t -> 'a list t
0 or more parsed elements of the given type.
sep : separator between elements of the list (for instance, space)
val many1 : ?sep:unit t -> 'a t -> 'a list t
Same as CCApp_parse.many, but needs at least one element
val skip : 'a t -> unit t
Skip 0 or more instances of the given parser
val skip1 : 'a t -> unit t
val opt : 'a t -> 'a option t
opt x tries to parse x, and returns None otherwise
val filter : ('a -> bool) -> 'a t -> 'a t
filter f p parses the same as p, but fails if the returned value does not satisfy f
val switch_c : ?default:'a t ->
(char * 'a t) list -> 'a t
switch_c l matches the next char and uses the corresponding parser. Fails if the next char is not in the list, unless default is defined.
Raises Invalid_argument if some char occurs several times in l
default : parser to use if no char matches
val switch_s : (string * 'a t) list -> 'a t
switch_s l attempts to match matches any of the strings in l. If one of those strings matches, the corresponding parser is used from now on.
Raises Invalid_argument if some string is a prefix of another string, or is empty, or if the list is empty
val choice : 'a t list -> 'a t
choice l chooses between the parsers, unambiguously
Raises Invalid_argument if the list is empty, or if some parsers overlap, making the choice ambiguous
val fix : ('a t -> 'a t) -> 'a t
fix f makes a fixpoint
module Infix: sig .. end
include CCApp_parse.Infix

Signatures



Signatures



Parsing

type error = {
   line : int;
   col : int;
   msg : string;
}
val string_of_error : error -> string
exception Error of error
module type S = sig .. end

Parse


module type INPUT = sig .. end
module Make (I : INPUT) : S  with type source = I.t

Low-level interface


val print : Format.formatter -> 'a t -> unit
Print a parser structure, for debug purpose
type token = 
| Yield of char
| EOF
module type READER = sig .. end
module MakeFromReader (R : READER) : S  with type source = R.source

Defaults


module Str: S  with type source = string
module Chan: S  with type source = in_channel