File: cset.ml

package info (click to toggle)
ocaml 4.05.0-11
  • links: PTS, VCS
  • area: main
  • in suites: buster
  • size: 27,060 kB
  • sloc: ml: 199,255; ansic: 44,187; sh: 5,611; makefile: 4,958; lisp: 4,223; asm: 4,220; awk: 306; perl: 87; fortran: 21; cs: 9; sed: 9
file content (97 lines) | stat: -rw-r--r-- 2,787 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
95
96
97
(**************************************************************************)
(*                                                                        *)
(*                                 OCaml                                  *)
(*                                                                        *)
(*             Luc Maranget, Jerome Vouillon projet Cristal,              *)
(*                          INRIA Rocquencourt                            *)
(*                                                                        *)
(*   Copyright 2002 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.          *)
(*                                                                        *)
(**************************************************************************)

exception Bad

type t = (int * int) list


let empty = []
let is_empty = function
  | [] -> true
  | _  -> false

let singleton c = [c,c]

let interval c1 c2 =
  if c1 <= c2 then [c1,c2]
  else [c2,c1]


let rec union s1 s2 = match s1,s2 with
| [],_ -> s2
| _,[] -> s1
| (c1,d1) as p1::r1, (c2,d2)::r2 ->
    if c1 > c2 then
      union s2 s1
    else begin (* c1 <= c2 *)
      if d1+1 < c2 then
        p1::union r1 s2
      else if d1 < d2 then
        union ((c1,d2)::r2) r1
      else
        union s1 r2
    end

let rec inter l l' =  match l, l' with
    _, [] -> []
  | [], _ -> []
  | (c1, c2)::r, (c1', c2')::r' ->
      if c2 < c1' then
        inter r l'
      else if c2' < c1 then
        inter l r'
      else if c2 < c2' then
        (max c1 c1', c2)::inter r l'
      else
        (max c1 c1', c2')::inter l r'

let rec diff l l' =  match l, l' with
    _, [] -> l
  | [], _ -> []
  | (c1, c2)::r, (c1', c2')::r' ->
      if c2 < c1' then
        (c1, c2)::diff r l'
      else if c2' < c1 then
        diff l r'
      else
        let r'' = if c2' < c2 then (c2' + 1, c2) :: r else r in
        if c1 < c1' then
          (c1, c1' - 1)::diff r'' r'
        else
          diff r'' r'


let eof = singleton 256
and all_chars = interval 0 255
and all_chars_eof = interval 0 256

let complement s = diff all_chars s

let env_to_array env = match env with
| []         -> assert false
| (_,x)::rem ->
    let res = Array.make 257 x in
    List.iter
      (fun (c,y) ->
        List.iter
          (fun (i,j) ->
            for k=i to j do
              res.(k) <- y
            done)
          c)
      rem ;
    res