File: odoc_see_lexer.mll

package info (click to toggle)
ocaml 5.3.0-3
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 43,124 kB
  • sloc: ml: 355,439; ansic: 51,636; sh: 25,098; asm: 5,413; makefile: 3,673; python: 919; javascript: 273; awk: 253; perl: 59; fortran: 21; cs: 9
file content (94 lines) | stat: -rw-r--r-- 2,235 bytes parent folder | download | duplicates (2)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
{
(**************************************************************************)
(*                                                                        *)
(*                                 OCaml                                  *)
(*                                                                        *)
(*             Maxence Guesdon, projet Cristal, INRIA Rocquencourt        *)
(*                                                                        *)
(*   Copyright 2001 Institut National de Recherche en Informatique et     *)
(*     en Automatique.                                                    *)
(*                                                                        *)
(*   All rights reserved.  This file is distributed under the terms of    *)
(*   the GNU Lesser General Public License version 2.1, with the          *)
(*   special exception on linking described in the file LICENSE.          *)
(*                                                                        *)
(**************************************************************************)

(** the lexer for special comments. *)

open Odoc_parser

let buf = Buffer.create 32

}

rule main = parse
  [' ' '\013' '\009' '\012'] +
  {
    main lexbuf
  }

  | [ '\010' ]
      {
        main lexbuf
      }

  | "<"
      {
        url lexbuf
      }

  | "\""
      {
        doc lexbuf
      }


  | '\''
      {
        file lexbuf
      }

  | eof
      {
        EOF
      }

  | _
      {
        Buffer.reset buf ;
        Buffer.add_string buf (Lexing.lexeme lexbuf);
        desc lexbuf
      }

and url = parse
  | ([^'>'] | '\n')+">"
      {
        let s = Lexing.lexeme lexbuf in
        See_url (String.sub s 0 ((String.length s) -1))
      }


and doc = parse
  | ([^'"'] | '\n' | "\\'")* "\""
      {
        let s = Lexing.lexeme lexbuf in
        See_doc (String.sub s 0 ((String.length s) -1))
      }

and file = parse
  | ([^'\''] | '\n' | "\\\"")* "'"
      {
        let s = Lexing.lexeme lexbuf in
        See_file (String.sub s 0 ((String.length s) -1))
      }


and desc = parse
    eof
      { Desc (Buffer.contents buf) }
  | _
      {
        Buffer.add_string buf (Lexing.lexeme lexbuf);
        desc lexbuf
      }