@@ -4,6 +4,7 @@ module RGB8 : sig
4
4
val to_dyn : t -> Dyn .t
5
5
val of_int : int -> t
6
6
val to_int : t -> int
7
+ val compare : t -> t -> Ordering .t
7
8
8
9
(* * This is only used internally. *)
9
10
val write_to_buffer : Buffer .t -> t -> unit
@@ -13,6 +14,7 @@ end = struct
13
14
let to_dyn t = Dyn. Int (int_of_char t)
14
15
let of_int t = char_of_int (t land 0xFF )
15
16
let to_int t = int_of_char t
17
+ let compare t1 t2 = Char. compare t1 t2
16
18
17
19
let write_to_buffer buf c =
18
20
Buffer. add_string buf " 38;5;" ;
@@ -24,6 +26,7 @@ module RGB24 : sig
24
26
type t
25
27
26
28
val to_dyn : t -> Dyn .t
29
+ val compare : t -> t -> Ordering .t
27
30
val red : t -> int
28
31
val green : t -> int
29
32
val blue : t -> int
@@ -34,6 +37,7 @@ module RGB24 : sig
34
37
end = struct
35
38
type t = int
36
39
40
+ let compare = Int. compare
37
41
let red t = Int. shift_right t 16 land 0xFF
38
42
let green t = Int. shift_right t 8 land 0xFF
39
43
let blue t = t land 0xFF
@@ -186,6 +190,134 @@ module Style = struct
186
190
| `Underline -> Dyn. variant " Underline" []
187
191
;;
188
192
193
+ let compare (t1 : t ) (t2 : t ) : Ordering.t =
194
+ match t1, t2 with
195
+ | `Fg_default , `Fg_default -> Eq
196
+ | `Fg_default , _ -> Lt
197
+ | _ , `Fg_default -> Gt
198
+ | `Fg_black , `Fg_black -> Eq
199
+ | `Fg_black , _ -> Lt
200
+ | _ , `Fg_black -> Gt
201
+ | `Fg_red , `Fg_red -> Eq
202
+ | `Fg_red , _ -> Lt
203
+ | _ , `Fg_red -> Gt
204
+ | `Fg_green , `Fg_green -> Eq
205
+ | `Fg_green , _ -> Lt
206
+ | _ , `Fg_green -> Gt
207
+ | `Fg_yellow , `Fg_yellow -> Eq
208
+ | `Fg_yellow , _ -> Lt
209
+ | _ , `Fg_yellow -> Gt
210
+ | `Fg_blue , `Fg_blue -> Eq
211
+ | `Fg_blue , _ -> Lt
212
+ | _ , `Fg_blue -> Gt
213
+ | `Fg_magenta , `Fg_magenta -> Eq
214
+ | `Fg_magenta , _ -> Lt
215
+ | _ , `Fg_magenta -> Gt
216
+ | `Fg_cyan , `Fg_cyan -> Eq
217
+ | `Fg_cyan , _ -> Lt
218
+ | _ , `Fg_cyan -> Gt
219
+ | `Fg_white , `Fg_white -> Eq
220
+ | `Fg_white , _ -> Lt
221
+ | _ , `Fg_white -> Gt
222
+ | `Fg_bright_black , `Fg_bright_black -> Eq
223
+ | `Fg_bright_black , _ -> Lt
224
+ | _ , `Fg_bright_black -> Gt
225
+ | `Fg_bright_red , `Fg_bright_red -> Eq
226
+ | `Fg_bright_red , _ -> Lt
227
+ | _ , `Fg_bright_red -> Gt
228
+ | `Fg_bright_green , `Fg_bright_green -> Eq
229
+ | `Fg_bright_green , _ -> Lt
230
+ | _ , `Fg_bright_green -> Gt
231
+ | `Fg_bright_yellow , `Fg_bright_yellow -> Eq
232
+ | `Fg_bright_yellow , _ -> Lt
233
+ | _ , `Fg_bright_yellow -> Gt
234
+ | `Fg_bright_blue , `Fg_bright_blue -> Eq
235
+ | `Fg_bright_blue , _ -> Lt
236
+ | _ , `Fg_bright_blue -> Gt
237
+ | `Fg_bright_magenta , `Fg_bright_magenta -> Eq
238
+ | `Fg_bright_magenta , _ -> Lt
239
+ | _ , `Fg_bright_magenta -> Gt
240
+ | `Fg_bright_cyan , `Fg_bright_cyan -> Eq
241
+ | `Fg_bright_cyan , _ -> Lt
242
+ | _ , `Fg_bright_cyan -> Gt
243
+ | `Fg_bright_white , `Fg_bright_white -> Eq
244
+ | `Fg_bright_white , _ -> Lt
245
+ | _ , `Fg_bright_white -> Gt
246
+ | `Fg_8_bit_color c1 , `Fg_8_bit_color c2 -> RGB8. compare c1 c2
247
+ | `Fg_8_bit_color _ , _ -> Lt
248
+ | _ , `Fg_8_bit_color _ -> Gt
249
+ | `Fg_24_bit_color c1 , `Fg_24_bit_color c2 -> RGB24. compare c1 c2
250
+ | `Fg_24_bit_color _ , _ -> Lt
251
+ | _ , `Fg_24_bit_color _ -> Gt
252
+ | `Bg_default , `Bg_default -> Eq
253
+ | `Bg_default , _ -> Lt
254
+ | _ , `Bg_default -> Gt
255
+ | `Bg_black , `Bg_black -> Eq
256
+ | `Bg_black , _ -> Lt
257
+ | _ , `Bg_black -> Gt
258
+ | `Bg_red , `Bg_red -> Eq
259
+ | `Bg_red , _ -> Lt
260
+ | _ , `Bg_red -> Gt
261
+ | `Bg_green , `Bg_green -> Eq
262
+ | `Bg_green , _ -> Lt
263
+ | _ , `Bg_green -> Gt
264
+ | `Bg_yellow , `Bg_yellow -> Eq
265
+ | `Bg_yellow , _ -> Lt
266
+ | _ , `Bg_yellow -> Gt
267
+ | `Bg_blue , `Bg_blue -> Eq
268
+ | `Bg_blue , _ -> Lt
269
+ | _ , `Bg_blue -> Gt
270
+ | `Bg_magenta , `Bg_magenta -> Eq
271
+ | `Bg_magenta , _ -> Lt
272
+ | _ , `Bg_magenta -> Gt
273
+ | `Bg_cyan , `Bg_cyan -> Eq
274
+ | `Bg_cyan , _ -> Lt
275
+ | _ , `Bg_cyan -> Gt
276
+ | `Bg_white , `Bg_white -> Eq
277
+ | `Bg_white , _ -> Lt
278
+ | _ , `Bg_white -> Gt
279
+ | `Bg_bright_black , `Bg_bright_black -> Eq
280
+ | `Bg_bright_black , _ -> Lt
281
+ | _ , `Bg_bright_black -> Gt
282
+ | `Bg_bright_red , `Bg_bright_red -> Eq
283
+ | `Bg_bright_red , _ -> Lt
284
+ | _ , `Bg_bright_red -> Gt
285
+ | `Bg_bright_green , `Bg_bright_green -> Eq
286
+ | `Bg_bright_green , _ -> Lt
287
+ | _ , `Bg_bright_green -> Gt
288
+ | `Bg_bright_yellow , `Bg_bright_yellow -> Eq
289
+ | `Bg_bright_yellow , _ -> Lt
290
+ | _ , `Bg_bright_yellow -> Gt
291
+ | `Bg_bright_blue , `Bg_bright_blue -> Eq
292
+ | `Bg_bright_blue , _ -> Lt
293
+ | _ , `Bg_bright_blue -> Gt
294
+ | `Bg_bright_magenta , `Bg_bright_magenta -> Eq
295
+ | `Bg_bright_magenta , _ -> Lt
296
+ | _ , `Bg_bright_magenta -> Gt
297
+ | `Bg_bright_cyan , `Bg_bright_cyan -> Eq
298
+ | `Bg_bright_cyan , _ -> Lt
299
+ | _ , `Bg_bright_cyan -> Gt
300
+ | `Bg_bright_white , `Bg_bright_white -> Eq
301
+ | `Bg_bright_white , _ -> Lt
302
+ | _ , `Bg_bright_white -> Gt
303
+ | `Bg_8_bit_color c1 , `Bg_8_bit_color c2 -> RGB8. compare c1 c2
304
+ | `Bg_8_bit_color _ , _ -> Lt
305
+ | _ , `Bg_8_bit_color _ -> Gt
306
+ | `Bg_24_bit_color c1 , `Bg_24_bit_color c2 -> RGB24. compare c1 c2
307
+ | `Bg_24_bit_color _ , _ -> Lt
308
+ | _ , `Bg_24_bit_color _ -> Gt
309
+ | `Bold , `Bold -> Eq
310
+ | `Bold , _ -> Lt
311
+ | _ , `Bold -> Gt
312
+ | `Dim , `Dim -> Eq
313
+ | `Dim , _ -> Lt
314
+ | _ , `Dim -> Gt
315
+ | `Italic , `Italic -> Eq
316
+ | `Italic , _ -> Lt
317
+ | _ , `Italic -> Gt
318
+ | `Underline , `Underline -> Eq
319
+ ;;
320
+
189
321
module Of_ansi_code = struct
190
322
type code = t
191
323
0 commit comments