module MrMime_parser:sig..end
Most of this part is from angstrom project by Spiros Eliopoulos. But MrMime is not a parser combinator library! And if you want a good parser combinator library, angstrom is certainly the best in OCaml (what I know). However, angstrom is not as permissive as we want - we need to do some weird tricks and optimize (with ocamllex for example) some computations.
    We expose this part  if you want to play with some  explicit parsers for the
    email.  And for this way, we provide all combinators but, as we said, MrMime
    is not a parser combinator  library,  this module it's just some convenience
    combinators to deal between the rest of MrMime.
module Input:module type of RingBuffer.Committedwith type 'a t = 'a RingBuffer.Committed.t
types =Parser.s=
| | | Complete | (* | 
If the client has no data after. | *) | 
| | | Incomplete | (* | 
If the client can gave some data after. | *) | 
val pp : Format.formatter -> s -> unit
typeerr =Parser.err= ..
type('a, 'input)state =('a, 'input) Parser.state=
| | | Read of  | (* | 
The parser requires more input. | *) | 
| | | Done of  | (* | 
The parser succeeded. | *) | 
| | | Fail of  | (* | 
The parser failed. | *) | 
type('a, 'input)k ='input Input.t -> s -> 'a
type('a, 'input)fail =(string list -> err -> ('a, 'input) state,
'input)
k
type('a, 'r, 'input)success =('a -> ('r, 'input) state, 'input) k
type'at ='a Parser.t= {
|    | f :  | 
'a.val return : 'a -> 'a treturn v creates a parser that will always succeed and return v.val fail : err -> 'a t
val (>>=) : 'a t -> ('a -> 'b t) -> 'b tp >>= f creates a parser that will run p, pass its result to f, run
    the parser that f produces, and return its result.val (>>|) : 'a t -> ('a -> 'b) -> 'b tp >>| f creates a parser that will run p, and if it succeeds with result
    v, will return f v.val (<|>) : 'a t -> 'a t -> 'a tp <|> q runs p and returns the result if succeeds. If p fails, then
    the input will be reset and q will run instead.val (<$>) : ('a -> 'b) -> 'a t -> 'b tf <$> p is equivalent to p >>| f.val ( <* ) : 'a t -> 'b t -> 'a tp <* q runs p, then runs q, discards its result, and returns the
    result of p.val ( *> ) : 'a t -> 'b t -> 'b tp *> q runs p, discards its result and then runs q.val (<*>) : ('a -> 'b) t -> 'a t -> 'b tf <*> p is equivalent to f >>= fun f -> p >>| f.val fix : ('a t -> 'a t) -> 'a tfix f computes the fixpoint of f and runs the resultant parser. The
    argument that f receives is the result of fix f, which f must use,
    paradoxically, to define fix f.
    fix is useful when constructing parsers for inductively-defined types such
    as sequences, trees, etc (like `Multipart for MrMime).
val lift : ('a -> 'b) -> 'a t -> 'b t
val lift2 : ('a -> 'b -> 'c) ->
       'a t -> 'b t -> 'c t
val lift3 : ('a -> 'b -> 'c -> 'd) ->
       'a t ->
       'b t -> 'c t -> 'd tliftN family of functions promote functions to the parser monad. For
    any of theses functions, the following equivalence holds:
liftn f p ... pn = f <$> p1 <*> ... <*> pnval run : 'input Input.t ->
       'a t -> ('a, 'input) staterun input p runs p on input.val only : 'input Input.t ->
       'a t -> ('a, 'input) stateonly input p runs p on input. This compute consider input as already
    Complete, so this compute never returns Read.type | | | Satisfy | 
type | | | String | 
type | | | Repeat | 
val peek_chr : char option tpeek_chr accepts any char and return  it,  or returns None if the end of
    input has been reached.
    This parser does not advance the input. Use it for lookahead.
val peek_chr_exn : char tpeek_chr_exn accepts any  char and returnss it.  If end  of input has been
    reached, it will fail and returns End_of_flow.
    This parser does not advance the input. Use it for lookahead.
val advance : int -> unit tadvance n advances the input of n bytes.
    NOTE:  assert false  if you want to advance n  byte(s) but the input
    has not enough.
val satisfy : (char -> bool) -> char tsatisfy f accepts any character for which f returns true and returns
    the accepted character.val string : (string -> string) -> string -> string tstring f s ensures the input has String.length s (in another case,
    the parser fails with End_of_flow) and compare the string s' from the
    input and s with f s = f s' (in another case, the parser fails with
    MrMime_parser.String). The parser advances the input of String.length s byte(s).val store : Buffer.t -> (char -> bool) -> int tstore buf  f stores any  character for which  f returns true  in buf
    only on the continuous buffer  inside the input.  That means,  store buf f
    can't consume all character of the input.
    You need to use peek_chr to continue or  not to store the data if you want
    to consume all  character  which  respects  the  predicate f.  This parser
    returns of byte consumed (and it advance the input).
val recognize : (char -> bool) -> string trecognize f accepts input as long as f returns true and returns the
    accepted characters as a string.
    This parser does not fail. If f returns false on the first character, it
    will return the empty string.
val char : char -> char tchar c accepts c and return it.val many : 'a t -> 'a list tmany p runs p zero or more times and returns a list of results from
    the runs of p.val one : 'a t -> 'a list tone p runs p one or more times and returns a list of results from
    the runs of p.val option : 'a -> 'a t -> 'a toption v p runs p, returning the result of p if it succeeds and v if
    it fails.val take : int -> string ttake n accepts exactly n character(s) of input and returns them as a
    string.val list : 'a t list -> 'a list tlist ps runs each p in ps in sequence, returning a list of results of
    each p.val count : int -> 'a t -> 'a list tcount n p runs p n times, returning a list of the results.val repeat : int option -> int option -> (char -> bool) -> string trepeat      a      b      f       is      a      parser      from      the
    RFC5234 to recognize any
    character which respect the predicate f. The parser expects a characters
    and it is limited by b length.
repeat (Some 2) (Some 2) is_digit expects only 2 digit characters.repeat None (Some 2) is_digit expects at most 2 digit characters.repeat (Some 2) None is_digit expects at least 2 digit chracters.repeat None None is_digit is same as recognize is_digit.a and b, it fails with
    MrMime_parser.Repeat.