Do not continue searching after encountering (undefined) regexec error
[llpp.git] / main.ml
blobbf33a17c49a50b1d90b5f693d8e217117d4e7c27
1 open Format;;
3 let log fmt = Printf.kprintf prerr_endline fmt;;
4 let dolog fmt = Printf.kprintf prerr_endline fmt;;
6 external init : Unix.file_descr -> unit = "ml_init";;
7 external draw : int -> int -> int -> int -> string -> unit = "ml_draw";;
8 external preload : string -> unit = "ml_preload";;
9 external gettext : string -> (int * int * int * int) -> int -> bool -> unit =
10 "ml_gettext";;
11 external checklink : string -> int -> int -> bool = "ml_checklink";;
12 external getlink : string -> int -> int -> (int * int) option = "ml_getlink";;
13 external getpagewh : int -> float array = "ml_getpagewh";;
15 type mstate = Msel of ((int * int) * (int * int)) | Mnone;;
17 type te =
18 | TEstop
19 | TEdone of string
20 | TEcont of string
23 type 'a circbuf =
24 { store : 'a array
25 ; mutable rc : int
26 ; mutable wc : int
27 ; mutable len : int
31 let cbnew n v =
32 { store = Array.create n v
33 ; rc = 0
34 ; wc = 0
35 ; len = 0
39 let cblen b = Array.length b.store;;
41 let cbput b v =
42 let len = cblen b in
43 b.store.(b.wc) <- v;
44 b.wc <- (b.wc + 1) mod len;
45 b.len <- (b.len + 1) mod len;
48 let cbpeekw b = b.store.(b.wc);;
50 let cbget b =
51 let v = b.store.(b.rc) in
52 if b.len = 0
53 then
55 else (
56 let rc = if b.rc = 0 then b.len - 1 else b.rc - 1 in
57 b.rc <- rc;
62 let cbrfollowlen b =
63 b.rc <- b.len - 1;
66 type layout =
67 { pageno : int
68 ; pagedimno : int
69 ; pagew : int
70 ; pageh : int
71 ; pagedispy : int
72 ; pagey : int
73 ; pagevh : int
77 type conf =
78 { mutable scrollw : int
79 ; mutable scrollh : int
80 ; mutable rectsel : bool
81 ; mutable icase : bool
82 ; mutable preload : bool
83 ; mutable titletext : bool
84 ; mutable pagebias : int
85 ; mutable redispimm : bool
86 ; mutable verbose : bool
87 ; mutable scrollincr : int
88 ; mutable maxhfit : bool
92 type outline = string * int * int * int;;
93 type outlines = Oarray of outline array | Olist of outline list;;
95 type state =
96 { mutable csock : Unix.file_descr
97 ; mutable ssock : Unix.file_descr
98 ; mutable w : int
99 ; mutable h : int
100 ; mutable y : int
101 ; mutable prevy : int
102 ; mutable maxy : int
103 ; mutable layout : layout list
104 ; pagemap : ((int * int), string) Hashtbl.t
105 ; mutable pages : (int * int * int) list
106 ; mutable pagecount : int
107 ; pagecache : string circbuf
108 ; navhist : float circbuf
109 ; mutable inflight : int
110 ; mutable mstate : mstate
111 ; mutable searchpattern : string
112 ; mutable rects : (int * int * Gl.point2 * Gl.point2) list
113 ; mutable rects1 : (int * int * Gl.point2 * Gl.point2) list
114 ; mutable text : string
115 ; mutable fullscreen : (int * int) option
116 ; mutable textentry :
117 (char * string * (string -> int -> te) * (string -> unit)) option
118 ; mutable outlines : outlines
119 ; mutable outline : (bool * int * int * outline array * string) option
120 ; mutable bookmarks : outline list
121 ; mutable path : string
125 let conf =
126 { scrollw = 5
127 ; scrollh = 12
128 ; icase = true
129 ; rectsel = true
130 ; preload = false
131 ; titletext = false
132 ; pagebias = 0
133 ; redispimm = false
134 ; verbose = false
135 ; scrollincr = 18
136 ; maxhfit = true
140 let state =
141 { csock = Unix.stdin
142 ; ssock = Unix.stdin
143 ; w = 900
144 ; h = 900
145 ; y = 0
146 ; prevy = 0
147 ; layout = []
148 ; maxy = max_int
149 ; pagemap = Hashtbl.create 10
150 ; pagecache = cbnew 10 ""
151 ; pages = []
152 ; pagecount = 0
153 ; inflight = 0
154 ; mstate = Mnone
155 ; navhist = cbnew 100 0.0
156 ; rects = []
157 ; rects1 = []
158 ; text = ""
159 ; fullscreen = None
160 ; textentry = None
161 ; searchpattern = ""
162 ; outlines = Olist []
163 ; outline = None
164 ; bookmarks = []
165 ; path = ""
169 let vlog fmt =
170 if conf.verbose
171 then
172 Printf.kprintf prerr_endline fmt
173 else
174 Printf.kprintf ignore fmt
177 let writecmd fd s =
178 let len = String.length s in
179 let n = 4 + len in
180 let b = Buffer.create n in
181 Buffer.add_char b (Char.chr ((len lsr 24) land 0xff));
182 Buffer.add_char b (Char.chr ((len lsr 16) land 0xff));
183 Buffer.add_char b (Char.chr ((len lsr 8) land 0xff));
184 Buffer.add_char b (Char.chr ((len lsr 0) land 0xff));
185 Buffer.add_string b s;
186 let s' = Buffer.contents b in
187 let n' = Unix.write fd s' 0 n in
188 if n' != n then failwith "write failed";
191 let readcmd fd =
192 let s = "xxxx" in
193 let n = Unix.read fd s 0 4 in
194 if n != 4 then failwith "incomplete read(len)";
195 let len = 0
196 lor (Char.code s.[0] lsl 24)
197 lor (Char.code s.[1] lsl 16)
198 lor (Char.code s.[2] lsl 8)
199 lor (Char.code s.[3] lsl 0)
201 let s = String.create len in
202 let n = Unix.read fd s 0 len in
203 if n != len then failwith "incomplete read(data)";
207 let yratio y =
208 if y = state.maxy then 1.0
209 else float y /. float state.maxy
212 let makecmd s l =
213 let b = Buffer.create 10 in
214 Buffer.add_string b s;
215 let rec combine = function
216 | [] -> b
217 | x :: xs ->
218 Buffer.add_char b ' ';
219 let s =
220 match x with
221 | `b b -> if b then "1" else "0"
222 | `s s -> s
223 | `i i -> string_of_int i
224 | `f f -> string_of_float f
225 | `I f -> string_of_int (truncate f)
227 Buffer.add_string b s;
228 combine xs;
230 combine l;
233 let wcmd s l =
234 let cmd = Buffer.contents (makecmd s l) in
235 writecmd state.csock cmd;
238 let calcheight () =
239 let rec f pn ph fh l =
240 match l with
241 | (n, _, h) :: rest ->
242 let fh = fh + (n - pn) * ph in
243 f n h fh rest
245 | [] ->
246 let fh = fh + (ph * (state.pagecount - pn)) in
247 max 0 fh
249 let fh = f 0 0 0 state.pages in
253 let getpagey pageno =
254 let rec f pn ph y l =
255 match l with
256 | (n, _, h) :: rest ->
257 if n >= pageno
258 then
259 y + (pageno - pn) * ph
260 else
261 let y = y + (n - pn) * ph in
262 f n h y rest
264 | [] ->
265 y + (pageno - pn) * ph
267 f 0 0 0 state.pages;
270 let layout y sh =
271 let rec f pageno pdimno prev vy py dy l cacheleft accu =
272 if pageno = state.pagecount || cacheleft = 0
273 then accu
274 else
275 let ((_, w, h) as curr), rest, pdimno =
276 match l with
277 | ((pageno', _, _) as curr) :: rest when pageno' = pageno ->
278 curr, rest, pdimno + 1
279 | _ ->
280 prev, l, pdimno
282 let pageno' = pageno + 1 in
283 if py + h > vy
284 then
285 let py' = vy - py in
286 let vh = h - py' in
287 if dy + vh > sh
288 then
289 let vh = sh - dy in
290 if vh <= 0
291 then
292 accu
293 else
294 let e =
295 { pageno = pageno
296 ; pagedimno = pdimno
297 ; pagew = w
298 ; pageh = h
299 ; pagedispy = dy
300 ; pagey = py'
301 ; pagevh = vh
304 e :: accu
305 else
306 let e =
307 { pageno = pageno
308 ; pagedimno = pdimno
309 ; pagew = w
310 ; pageh = h
311 ; pagedispy = dy
312 ; pagey = py'
313 ; pagevh = vh
316 let accu = e :: accu in
317 f pageno' pdimno curr
318 (vy + vh) (py + h) (dy + vh + 2) rest
319 (pred cacheleft) accu
320 else
321 f pageno' pdimno curr vy (py + h) dy rest cacheleft accu
323 let accu = f 0 ~-1 (0,0,0) y 0 0 state.pages (cblen state.pagecache) [] in
324 state.maxy <- calcheight ();
325 List.rev accu
328 let clamp incr =
329 let y = state.y + incr in
330 let y = max 0 y in
331 let y = min y (state.maxy - (if conf.maxhfit then state.h else 0)) in
335 let gotoy y =
336 let y = max 0 y in
337 let y = min state.maxy y in
338 let pages = layout y state.h in
339 state.y <- y;
340 state.layout <- pages;
341 if conf.redispimm
342 then
343 Glut.postRedisplay ()
347 let addnav () =
348 cbput state.navhist (yratio state.y);
349 cbrfollowlen state.navhist;
352 let getnav () =
353 let y = cbget state.navhist in
354 truncate (y *. float state.maxy)
357 let gotopage n top =
358 let y = getpagey n in
359 addnav ();
360 state.y <- y + top;
361 gotoy state.y;
364 let reshape ~w ~h =
365 let ratio = float w /. float state.w in
366 let fixbookmark (s, l, pageno, pagey) =
367 let pagey = truncate (float pagey *. ratio) in
368 (s, l, pageno, pagey)
370 state.bookmarks <- List.map fixbookmark state.bookmarks;
371 state.w <- w;
372 state.h <- h;
373 GlDraw.viewport 0 0 w h;
374 GlMat.mode `modelview;
375 GlMat.load_identity ();
376 GlMat.mode `projection;
377 GlMat.load_identity ();
378 GlMat.rotate ~x:1.0 ~angle:180.0 ();
379 GlMat.translate ~x:~-.1.0 ~y:~-.1.0 ();
380 GlMat.scale3 (2.0 /. float w, 2.0 /. float state.h, 1.0);
381 GlClear.color (1., 1., 1.);
382 GlClear.clear [`color];
383 state.layout <- [];
384 state.pages <- [];
385 state.rects <- [];
386 state.text <- "";
387 wcmd "geometry" [`i (state.w - conf.scrollw); `i h];
390 let showtext c s =
391 if not conf.titletext
392 then (
393 GlDraw.color (0.0, 0.0, 0.0);
394 GlDraw.rect
395 (0.0, float (state.h - 18))
396 (float (state.w - conf.scrollw - 1), float state.h)
398 let font = Glut.BITMAP_8_BY_13 in
399 GlDraw.color (1.0, 1.0, 1.0);
400 GlPix.raster_pos ~x:0.0 ~y:(float (state.h - 5)) ();
401 Glut.bitmapCharacter ~font ~c:(Char.code c);
402 String.iter (fun c -> Glut.bitmapCharacter ~font ~c:(Char.code c)) s
404 else
405 let len = String.length s in
406 let dst = String.create (len + 1) in
407 dst.[0] <- c;
408 StringLabels.blit
409 ~src:s
410 ~dst
411 ~src_pos:0
412 ~dst_pos:1
413 ~len
415 Glut.setWindowTitle ~title:dst
418 let enttext () =
419 let len = String.length state.text in
420 match state.textentry with
421 | None ->
422 if len > 0 then showtext ' ' state.text
424 | Some (c, text, _, _) ->
425 let s =
426 if len > 0
427 then
428 text ^ " [" ^ state.text ^ "]"
429 else
430 text
432 showtext c s;
435 let act cmd =
436 match cmd.[0] with
437 | 'c' ->
438 state.pages <- []
440 | 'D' ->
441 state.rects <- state.rects1;
442 Glut.postRedisplay ()
444 | 'd' ->
445 state.rects <- state.rects1;
446 Glut.postRedisplay ()
448 | 'C' ->
449 let n = Scanf.sscanf cmd "C %d" (fun n -> n) in
450 state.pagecount <- n;
451 let rely = yratio state.y in
452 let maxy = calcheight () in
453 state.y <- truncate (float maxy *. rely);
454 let pages = layout state.y state.h in
455 state.layout <- pages;
456 Glut.postRedisplay ();
458 | 'T' ->
459 let s = Scanf.sscanf cmd "T %n"
460 (fun n -> String.sub cmd n (String.length cmd - n))
462 state.text <- s;
463 showtext ' ' s;
464 Glut.swapBuffers ();
465 (* Glut.postRedisplay () *)
467 | 'F' ->
468 let pageno, c, x0, y0, x1, y1 =
469 Scanf.sscanf cmd "F %d %d %f %f %f %f"
470 (fun p c x0 y0 x1 y1 -> (p, c, x0, y0, x1, y1))
472 let y = (getpagey pageno) + truncate y0 in
473 addnav ();
474 gotoy y;
475 state.rects1 <- [pageno, c, (x0, y0), (x1, y1)]
477 | 'R' ->
478 let pageno, c, x0, y0, x1, y1 =
479 Scanf.sscanf cmd "R %d %d %f %f %f %f"
480 (fun pageno c x0 y0 x1 y1 -> (pageno, c, x0, y0, x1, y1))
482 state.rects1 <- (pageno, c, (x0, y0), (x1, y1)) :: state.rects1
484 | 'r' ->
485 let n, w, h, p =
486 Scanf.sscanf cmd "r %d %d %d %s"
487 (fun n w h p -> (n, w, h, p))
489 Hashtbl.replace state.pagemap (n, w) p;
490 let evicted = cbpeekw state.pagecache in
491 if String.length evicted > 0
492 then begin
493 wcmd "free" [`s evicted];
494 let l = Hashtbl.fold (fun k p a ->
495 if evicted = p then k :: a else a) state.pagemap []
497 List.iter (fun k -> Hashtbl.remove state.pagemap k) l;
498 end;
499 cbput state.pagecache p;
500 state.inflight <- pred state.inflight;
501 Glut.postRedisplay ()
503 | 'l' ->
504 let (n, w, h) as pagelayout =
505 Scanf.sscanf cmd "l %d %d %d" (fun n w h -> n, w, h)
507 state.pages <- pagelayout :: state.pages
509 | 'o' ->
510 let (l, n, t, pos) =
511 Scanf.sscanf cmd "o %d %d %d %n" (fun l n t pos -> l, n, t, pos)
513 let s = String.sub cmd pos (String.length cmd - pos) in
514 let outline = (s, l, n, t) in
515 let outlines =
516 match state.outlines with
517 | Olist outlines -> Olist (outline :: outlines)
518 | Oarray _ -> Olist [outline]
520 state.outlines <- outlines
522 | _ ->
523 log "unknown cmd `%S'" cmd
526 let getopaque pageno =
527 try Some (Hashtbl.find state.pagemap (pageno + 1, state.w - conf.scrollw))
528 with Not_found -> None
531 let cache pageno opaque =
532 Hashtbl.replace state.pagemap (pageno + 1, state.w - conf.scrollw) opaque
535 let validopaque opaque = String.length opaque > 0;;
537 let preload l =
538 match getopaque l.pageno with
539 | Some opaque when validopaque opaque ->
540 preload opaque
542 | None when state.inflight < 2+0*(cblen state.pagecache) ->
543 state.inflight <- succ state.inflight;
544 cache l.pageno "";
545 wcmd "render" [`i (l.pageno + 1)
546 ;`i l.pagedimno
547 ;`i l.pagew
548 ;`i l.pageh];
550 | _ -> ()
553 let idle () =
554 if not conf.redispimm && state.y != state.prevy
555 then (
556 state.prevy <- state.y;
557 Glut.postRedisplay ();
559 else
560 let r, _, _ = Unix.select [state.csock] [] [] 0.02 in
562 begin match r with
563 | [] ->
564 if conf.preload then begin
565 let h = state.h in
566 let y = if state.y < state.h then 0 else state.y - state.h in
567 let pages = layout y (h*3) in
568 List.iter preload pages;
569 end;
571 | _ ->
572 let cmd = readcmd state.csock in
573 act cmd;
574 end;
577 let search pattern forward =
578 if String.length pattern > 0
579 then
580 let pn, py =
581 match state.layout with
582 | [] -> 0, 0
583 | l :: _ ->
584 l.pageno, (l.pagey + if forward then 0 else 0*l.pagevh)
586 let cmd =
587 let b = makecmd "search"
588 [`b conf.icase; `i pn; `i py; `i (if forward then 1 else 0)]
590 Buffer.add_char b ',';
591 Buffer.add_string b pattern;
592 Buffer.add_char b '\000';
593 Buffer.contents b;
595 writecmd state.csock cmd;
598 let intentry text key =
599 let c = Char.unsafe_chr key in
600 match c with
601 | '0' .. '9' ->
602 let s = "x" in s.[0] <- c;
603 let text = text ^ s in
604 TEcont text
606 | _ ->
607 state.text <- Printf.sprintf "invalid char (%d, `%c')" key c;
608 TEcont text
611 let addchar s c =
612 let b = Buffer.create (String.length s + 1) in
613 Buffer.add_string b s;
614 Buffer.add_char b c;
615 Buffer.contents b;
618 let textentry text key =
619 let c = Char.unsafe_chr key in
620 match c with
621 | _ when key >= 32 && key < 127 ->
622 let text = addchar text c in
623 TEcont text
625 | _ ->
626 log "unhandled key %d char `%c'" key (Char.unsafe_chr key);
627 TEcont text
630 let optentry text key =
631 let btos b = if b then "on" else "off" in
632 let c = Char.unsafe_chr key in
633 match c with
634 | 'r' ->
635 conf.rectsel <- not conf.rectsel;
636 TEdone ("rectsel " ^ (btos conf.rectsel))
638 | 'i' ->
639 conf.icase <- not conf.icase;
640 TEdone ("case insensitive search " ^ (btos conf.icase))
642 | 'p' ->
643 conf.preload <- not conf.preload;
644 TEdone ("preload " ^ (btos conf.preload))
646 | 't' ->
647 conf.titletext <- not conf.titletext;
648 TEdone ("titletext " ^ (btos conf.titletext))
650 | 'd' ->
651 conf.redispimm <- not conf.redispimm;
652 TEdone ("immediate redisplay " ^ (btos conf.redispimm))
654 | 'v' ->
655 conf.verbose <- not conf.verbose;
656 TEdone ("verbose " ^ (btos conf.verbose))
658 | 'h' ->
659 conf.maxhfit <- not conf.maxhfit;
660 state.maxy <- state.maxy + (if conf.maxhfit then -state.h else state.h);
661 TEdone ("maxhfit " ^ (btos conf.maxhfit))
663 | _ ->
664 state.text <- Printf.sprintf "bad option %d `%c'" key c;
665 TEstop
668 let maxoutlinerows () = (state.h - 31) / 16;;
670 let enterselector allowdel outlines errmsg =
671 if Array.length outlines = 0
672 then (
673 showtext ' ' errmsg;
674 Glut.swapBuffers ()
676 else
677 let pageno =
678 match state.layout with
679 | [] -> -1
680 | {pageno=pageno} :: rest -> pageno
682 let active =
683 let rec loop n =
684 if n = Array.length outlines
685 then 0
686 else
687 let (_, _, outlinepageno, _) = outlines.(n) in
688 if outlinepageno >= pageno then n else loop (n+1)
690 loop 0
692 state.outline <-
693 Some (allowdel, active, max 0 (active - maxoutlinerows ()), outlines, "");
694 Glut.postRedisplay ();
697 let enteroutlinemode () =
698 let outlines =
699 match state.outlines with
700 | Oarray a -> a
701 | Olist l ->
702 let a = Array.of_list (List.rev l) in
703 state.outlines <- Oarray a;
706 enterselector false outlines "Documents has no outline";
709 let enterbookmarkmode () =
710 let bookmarks = Array.of_list state.bookmarks in
711 enterselector true bookmarks "Documents has no bookmarks (yet)";
714 let viewkeyboard ~key ~x ~y =
715 let enttext te =
716 state.textentry <- te;
717 state.text <- "";
718 enttext ();
719 Glut.swapBuffers ()
721 match state.textentry with
722 | None ->
723 let c = Char.chr key in
724 begin match c with
725 | '\027' | 'q' ->
726 exit 0
728 | '\008' ->
729 let y = getnav () in
730 gotoy y
732 | 'o' ->
733 enteroutlinemode ()
735 | 'u' ->
736 state.rects <- [];
737 state.text <- "";
738 Glut.postRedisplay ()
740 | '/' | '?' ->
741 let ondone isforw s =
742 state.searchpattern <- s;
743 search s isforw
745 enttext (Some (c, "", textentry, ondone (c ='/')))
747 | '+' ->
748 let ondone s =
749 let n =
750 try int_of_string s with exc ->
751 state.text <- Printf.sprintf "bad integer `%s': %s"
752 s (Printexc.to_string exc);
753 max_int
755 if n != max_int
756 then (
757 conf.pagebias <- n;
758 state.text <- "page bias is now " ^ string_of_int n;
761 enttext (Some ('+', "", intentry, ondone))
763 | '-' ->
764 let ondone msg =
765 state.text <- msg;
767 enttext (Some ('-', "", optentry, ondone))
769 | '0' .. '9' ->
770 let ondone s =
771 let n =
772 try int_of_string s with exc ->
773 state.text <- Printf.sprintf "bad integer `%s': %s"
774 s (Printexc.to_string exc);
777 if n >= 0
778 then (
779 addnav ();
780 state.y <- y;
781 gotoy (getpagey (n + conf.pagebias - 1))
784 let pageentry text key =
785 match Char.unsafe_chr key with
786 | 'g' -> TEdone text
787 | _ -> intentry text key
789 let text = "x" in text.[0] <- c;
790 enttext (Some (':', text, pageentry, ondone))
792 | 'b' ->
793 conf.scrollw <- if conf.scrollw > 0 then 0 else 5;
794 reshape state.w state.h;
796 | 'f' ->
797 begin match state.fullscreen with
798 | None ->
799 state.fullscreen <- Some (state.w, state.h);
800 Glut.fullScreen ()
801 | Some (w, h) ->
802 state.fullscreen <- None;
803 Glut.reshapeWindow ~w ~h
806 | 'n' ->
807 search state.searchpattern true
809 | 'p' ->
810 search state.searchpattern false
812 | 't' ->
813 begin match state.layout with
814 | [] -> ()
815 | l :: _ ->
816 gotoy (state.y - l.pagey);
819 | ' ' | 'N' ->
820 begin match List.rev state.layout with
821 | [] -> ()
822 | l :: _ ->
823 gotoy (clamp (l.pageh - l.pagey))
826 | '\127' | 'P' ->
827 begin match state.layout with
828 | [] -> ()
829 | l :: _ ->
830 gotoy (clamp (-l.pageh));
833 | '=' ->
834 let f (fn, ln) l =
835 if fn = -1 then l.pageno, l.pageno else fn, l.pageno
837 let fn, ln = List.fold_left f (-1, -1) state.layout in
838 let s =
839 let maxy = state.maxy - (if conf.maxhfit then state.h else 0) in
840 let percent = (100. *. (float state.y /. float maxy)) in
841 if fn = ln
842 then
843 Printf.sprintf "Page %d of %d %.2f%%"
844 (fn+1) state.pagecount percent
845 else
846 Printf.sprintf
847 "Pages %d-%d of %d %.2f%%"
848 (fn+1) (ln+1) state.pagecount percent
850 showtext ' ' s;
851 Glut.swapBuffers ()
853 | 'w' ->
854 begin match state.layout with
855 | [] -> ()
856 | l :: _ ->
857 Glut.reshapeWindow (l.pagew + conf.scrollw) l.pageh;
858 Glut.postRedisplay ();
861 | '\'' ->
862 enterbookmarkmode ()
864 | 'm' ->
865 let ondone s =
866 match state.layout with
867 | l :: _ ->
868 state.bookmarks <- (s, 0, l.pageno, l.pagey) :: state.bookmarks
869 | _ -> ()
871 enttext (Some ('~', "", textentry, ondone))
874 | 'z' ->
875 begin match state.layout with
876 | l :: _ ->
877 let a = getpagewh l.pagedimno in
878 let w = truncate (a.(1) -. a.(0))
879 and h = truncate (a.(3) -. a.(0)) in
880 Glut.reshapeWindow (w + conf.scrollw) h;
881 Glut.postRedisplay ();
883 | [] -> ()
886 | _ ->
887 vlog "huh? %d %c" key (Char.chr key);
890 | Some (c, text, onkey, ondone) when key = 8 ->
891 let len = String.length text in
892 if len = 0 || len = 1
893 then (
894 state.textentry <- None;
895 Glut.postRedisplay ();
897 else (
898 let s = String.sub text 0 (len - 1) in
899 enttext (Some (c, s, onkey, ondone))
902 | Some (c, text, onkey, ondone) ->
903 begin match Char.unsafe_chr key with
904 | '\r' | '\n' ->
905 ondone text;
906 state.textentry <- None;
907 Glut.postRedisplay ()
909 | '\027' ->
910 state.textentry <- None;
911 Glut.postRedisplay ()
913 | _ ->
914 begin match onkey text key with
915 | TEdone text ->
916 state.textentry <- None;
917 ondone text;
918 Glut.postRedisplay ()
920 | TEcont text ->
921 enttext (Some (c, text, onkey, ondone));
923 | TEstop ->
924 state.textentry <- None;
925 Glut.postRedisplay ()
926 end;
927 end;
930 let outlinekeyboard ~key ~x ~y (allowdel, active, first, outlines, qsearch) =
931 let search active pattern incr =
932 let re = Str.regexp_case_fold pattern in
933 let rec loop n =
934 if n = Array.length outlines || n = -1 then None else
935 let (s, _, _, _) = outlines.(n) in
937 (try ignore (Str.search_forward re s 0); true
938 with Not_found -> false)
939 then (
940 let maxrows = maxoutlinerows () in
941 if first > n
942 then Some (n, max 0 (n - maxrows))
943 else Some (n, max first (n - maxrows))
945 else loop (n + incr)
947 loop active
949 match key with
950 | 27 ->
951 if String.length qsearch = 0
952 then (
953 state.text <- "";
954 state.outline <- None;
955 Glut.postRedisplay ();
957 else (
958 state.text <- "";
959 state.outline <- Some (allowdel, active, first, outlines, "");
960 Glut.postRedisplay ();
963 | 18 | 19 ->
964 let incr = if key = 18 then -1 else 1 in
965 let active, first =
966 match search (active + incr) qsearch incr with
967 | None -> active, first
968 | Some af -> af
970 state.outline <- Some (allowdel, active, first, outlines, qsearch);
971 Glut.postRedisplay ();
973 | 8 ->
974 let len = String.length qsearch in
975 if len = 0
976 then ()
977 else (
978 if len = 1
979 then (
980 state.text <- "";
981 state.outline <- Some (allowdel, active, first, outlines, "");
983 else
984 let qsearch = String.sub qsearch 0 (len - 1) in
985 state.text <- qsearch;
986 state.outline <- Some (allowdel, active, first, outlines, qsearch);
988 Glut.postRedisplay ()
990 | 13 ->
991 if active < Array.length outlines
992 then (
993 let (_, _, n, t) = outlines.(active) in
994 gotopage n t;
996 state.text <- "";
997 if allowdel then state.bookmarks <- Array.to_list outlines;
998 state.outline <- None;
999 Glut.postRedisplay ();
1001 | _ when key >= 32 && key < 127 ->
1002 let pattern = addchar qsearch (Char.chr key) in
1003 let pattern, active, first =
1004 match search active pattern 1 with
1005 | None -> qsearch, active, first
1006 | Some (active, first) -> (pattern, active, first)
1008 state.text <- pattern;
1009 state.outline <- Some (allowdel, active, first, outlines, pattern);
1010 Glut.postRedisplay ()
1012 | 127 when allowdel ->
1013 let len = Array.length outlines - 1 in
1014 if len = 0
1015 then (
1016 state.outline <- None;
1017 state.bookmarks <- [];
1019 else (
1020 let bookmarks = Array.init len
1021 (fun i ->
1022 let i = if i >= active then i + 1 else i in
1023 outlines.(i)
1026 state.outline <-
1027 Some (allowdel,
1028 min active (len-1),
1029 min first (len-1),
1030 bookmarks, qsearch)
1033 Glut.postRedisplay ()
1035 | _ -> log "unknown key %d" key
1038 let keyboard ~key ~x ~y =
1039 match state.outline with
1040 | None -> viewkeyboard ~key ~x ~y
1041 | Some outline -> outlinekeyboard ~key ~x ~y outline
1044 let special ~key ~x ~y =
1045 match state.outline with
1046 | None ->
1047 let y =
1048 match key with
1049 | Glut.KEY_F3 -> search state.searchpattern true; state.y
1050 | Glut.KEY_UP -> clamp (-conf.scrollincr)
1051 | Glut.KEY_DOWN -> clamp conf.scrollincr
1052 | Glut.KEY_PAGE_UP -> clamp (-state.h)
1053 | Glut.KEY_PAGE_DOWN -> clamp state.h
1054 | Glut.KEY_HOME -> addnav (); 0
1055 | Glut.KEY_END ->
1056 addnav ();
1057 state.maxy - (if conf.maxhfit then state.h else 0)
1058 | _ -> state.y
1060 state.text <- "";
1061 gotoy y
1063 | Some (allowdel, active, first, outlines, qsearch) ->
1064 let maxrows = maxoutlinerows () in
1065 let navigate incr =
1066 let active = active + incr in
1067 let active = max 0 (min active (Array.length outlines - 1)) in
1068 let first =
1069 if active > first
1070 then
1071 let rows = active - first in
1072 if rows > maxrows then first + incr else first
1073 else active
1075 state.outline <- Some (allowdel, active, first, outlines, qsearch);
1076 Glut.postRedisplay ()
1078 match key with
1079 | Glut.KEY_UP -> navigate ~-1
1080 | Glut.KEY_DOWN -> navigate 1
1081 | Glut.KEY_PAGE_UP -> navigate ~-maxrows
1082 | Glut.KEY_PAGE_DOWN -> navigate maxrows
1084 | Glut.KEY_HOME ->
1085 state.outline <- Some (allowdel, 0, 0, outlines, qsearch);
1086 Glut.postRedisplay ()
1088 | Glut.KEY_END ->
1089 let active = Array.length outlines - 1 in
1090 let first = max 0 (active - maxrows) in
1091 state.outline <- Some (allowdel, active, first, outlines, qsearch);
1092 Glut.postRedisplay ()
1094 | _ -> ()
1097 let drawplaceholder l =
1098 if true
1099 then (
1100 GlDraw.color (0.2, 0.2, 0.2);
1101 GlDraw.color (1.0, 1.0, 1.0);
1102 GlDraw.rect
1103 (0.0, float l.pagedispy)
1104 (float l.pagew, float (l.pagedispy + l.pagevh))
1106 let x = 0.0
1107 and y = float (l.pagedispy + 13) in
1108 let font = Glut.BITMAP_8_BY_13 in
1109 GlDraw.color (0.0, 0.0, 0.0);
1110 GlPix.raster_pos ~x ~y ();
1111 String.iter (fun c -> Glut.bitmapCharacter ~font ~c:(Char.code c))
1112 ("Loading " ^ string_of_int l.pageno);
1114 else (
1115 GlDraw.begins `quads;
1116 GlDraw.vertex2 (0.0, float l.pagedispy);
1117 GlDraw.vertex2 (float l.pagew, float l.pagedispy);
1118 GlDraw.vertex2 (float l.pagew, float (l.pagedispy + l.pagevh));
1119 GlDraw.vertex2 (0.0, float (l.pagedispy + l.pagevh));
1120 GlDraw.ends ();
1124 let now () = Unix.gettimeofday ();;
1126 let drawpage i l =
1127 begin match getopaque l.pageno with
1128 | Some opaque when validopaque opaque ->
1129 GlDraw.color (1.0, 1.0, 1.0);
1130 let a = now () in
1131 draw l.pagedispy l.pagew l.pagevh l.pagey opaque;
1132 let b = now () in
1133 let d = b-.a in
1134 vlog "draw %f sec" d;
1136 | Some _ ->
1137 drawplaceholder l
1139 | None ->
1140 drawplaceholder l;
1141 if state.inflight < cblen state.pagecache
1142 then (
1143 List.iter preload state.layout;
1145 else (
1146 vlog "inflight %d" state.inflight;
1148 end;
1149 GlDraw.color (0.5, 0.5, 0.5);
1150 GlDraw.rect
1151 (0., float i)
1152 (float (state.w - conf.scrollw), float (i + (l.pagedispy - i)))
1154 l.pagedispy + l.pagevh;
1157 let scrollindicator () =
1158 let maxy = state.maxy - (if conf.maxhfit then state.h else 0) in
1159 GlDraw.color (0.64 , 0.64, 0.64);
1160 GlDraw.rect
1161 (float (state.w - conf.scrollw), 0.)
1162 (float state.w, float state.h)
1164 GlDraw.color (0.0, 0.0, 0.0);
1165 let sh = (float (maxy + state.h) /. float state.h) in
1166 let sh = float state.h /. sh in
1167 let sh = max sh (float conf.scrollh) in
1169 let percent =
1170 if state.y = state.maxy
1171 then 1.0
1172 else float state.y /. float maxy
1174 let position = (float state.h -. sh) *. percent in
1176 let position =
1177 if position +. sh > float state.h
1178 then
1179 float state.h -. sh
1180 else
1181 position
1183 GlDraw.rect
1184 (float (state.w - conf.scrollw), position)
1185 (float state.w, position +. sh)
1189 let showsel () =
1190 match state.mstate with
1191 | Mnone ->
1194 | Msel ((x0, y0), (x1, y1)) ->
1195 let y0' = min y0 y1
1196 and y1 = max y0 y1 in
1197 let y0 = y0' in
1198 let f l =
1199 if (y0 >= l.pagedispy && y0 <= (l.pagedispy + l.pagevh))
1200 || ((y1 >= l.pagedispy)) (* && y1 <= (dy + vh))) *)
1201 then
1202 match getopaque l.pageno with
1203 | Some opaque when validopaque opaque ->
1204 let oy = -l.pagey + l.pagedispy in
1205 gettext opaque (min x0 x1, y0, max x1 x0, y1) oy conf.rectsel
1206 | _ -> ()
1208 List.iter f state.layout
1211 let showrects () =
1212 Gl.enable `blend;
1213 GlDraw.color (0.0, 0.0, 1.0) ~alpha:0.5;
1214 GlFunc.blend_func `src_alpha `one_minus_src_alpha;
1215 List.iter
1216 (fun (pageno, c, (x0, y0), (x1, y1)) ->
1217 List.iter (fun l ->
1218 if l.pageno = pageno
1219 then (
1220 let d = float (l.pagedispy - l.pagey) in
1221 GlDraw.color (0.0, 0.0, 1.0 /. float c) ~alpha:0.5;
1222 GlDraw.rect (x0, y0 +. d) (x1, y1 +. d)
1224 ) state.layout
1225 ) state.rects
1227 Gl.disable `blend;
1230 let showoutline = function
1231 | None -> ()
1232 | Some (allowdel, active, first, outlines, qsearch) ->
1233 Gl.enable `blend;
1234 GlFunc.blend_func `src_alpha `one_minus_src_alpha;
1235 GlDraw.color (0., 0., 0.) ~alpha:0.85;
1236 GlDraw.rect (0., 0.) (float state.w, float state.h);
1237 Gl.disable `blend;
1239 GlDraw.color (1., 1., 1.);
1240 let font = Glut.BITMAP_9_BY_15 in
1241 let draw_string x y s =
1242 GlPix.raster_pos ~x ~y ();
1243 String.iter (fun c -> Glut.bitmapCharacter ~font ~c:(Char.code c)) s
1245 let rec loop row =
1246 if row = Array.length outlines || (row - first) * 16 > state.h
1247 then ()
1248 else (
1249 let (s, l, _, _) = outlines.(row) in
1250 let y = (row - first) * 16 in
1251 let x = 5 + 5*l in
1252 if row = active
1253 then (
1254 Gl.enable `blend;
1255 GlDraw.polygon_mode `both `line;
1256 GlFunc.blend_func `src_alpha `one_minus_src_alpha;
1257 GlDraw.color (1., 1., 1.) ~alpha:0.9;
1258 GlDraw.rect (0., float (y + 1))
1259 (float (state.w - conf.scrollw - 1), float (y + 18));
1260 GlDraw.polygon_mode `both `fill;
1261 Gl.disable `blend;
1262 GlDraw.color (1., 1., 1.);
1264 draw_string (float x) (float (y + 16)) s;
1265 loop (row+1)
1268 loop first
1271 let display () =
1272 let lasty = List.fold_left drawpage 0 (state.layout) in
1273 GlDraw.color (0.5, 0.5, 0.5);
1274 GlDraw.rect
1275 (0., float lasty)
1276 (float (state.w - conf.scrollw), float state.h)
1278 showrects ();
1279 scrollindicator ();
1280 showsel ();
1281 showoutline state.outline;
1282 enttext ();
1283 Glut.swapBuffers ();
1286 let getlink x y =
1287 let rec f = function
1288 | l :: rest ->
1289 begin match getopaque l.pageno with
1290 | Some opaque when validopaque opaque ->
1291 let y = y - l.pagedispy in
1292 if y > 0
1293 then
1294 let y = l.pagey + y in
1295 match getlink opaque x y with
1296 | None -> f rest
1297 | some -> some
1298 else
1299 f rest
1300 | _ ->
1301 f rest
1303 | [] -> None
1305 f state.layout
1308 let checklink x y =
1309 let rec f = function
1310 | l :: rest ->
1311 begin match getopaque l.pageno with
1312 | Some opaque when validopaque opaque ->
1313 let y = y - l.pagedispy in
1314 if y > 0
1315 then
1316 let y = l.pagey + y in
1317 if checklink opaque x y then true else f rest
1318 else
1319 f rest
1320 | _ ->
1321 f rest
1323 | [] -> false
1325 f state.layout
1328 let mouse ~button ~bstate ~x ~y =
1329 match button with
1330 | Glut.OTHER_BUTTON n when n == 3 || n == 4 && bstate = Glut.UP ->
1331 let incr =
1332 if n = 3
1333 then
1334 -conf.scrollincr
1335 else
1336 conf.scrollincr
1338 let incr = incr * 2 in
1339 let y = clamp incr in
1340 gotoy y
1342 | Glut.LEFT_BUTTON when state.outline = None ->
1343 let dest = if bstate = Glut.DOWN then getlink x y else None in
1344 begin match dest with
1345 | Some (pageno, top) ->
1346 gotopage pageno top
1348 | None ->
1349 if bstate = Glut.DOWN
1350 then (
1351 Glut.setCursor Glut.CURSOR_CROSSHAIR;
1352 state.mstate <- Msel ((x, y), (x, y));
1353 Glut.postRedisplay ()
1355 else (
1356 Glut.setCursor Glut.CURSOR_RIGHT_ARROW;
1357 state.mstate <- Mnone;
1361 | _ ->
1364 let mouse ~button ~state ~x ~y = mouse button state x y;;
1366 let motion ~x ~y =
1367 if state.outline = None
1368 then
1369 match state.mstate with
1370 | Mnone -> ()
1371 | Msel (a, _) ->
1372 state.mstate <- Msel (a, (x, y));
1373 Glut.postRedisplay ()
1376 let pmotion ~x ~y =
1377 if state.outline = None
1378 then
1379 match state.mstate with
1380 | Mnone when (checklink x y) ->
1381 Glut.setCursor Glut.CURSOR_INFO
1383 | Mnone ->
1384 Glut.setCursor Glut.CURSOR_RIGHT_ARROW
1386 | Msel (a, _) ->
1390 let () =
1391 let statepath = (Sys.getenv "HOME") ^ "/.config/llpp" in
1392 let pstate =
1394 let ic = open_in_bin statepath in
1395 let hash = input_value ic in
1396 close_in ic;
1397 hash
1398 with exn ->
1399 if false
1400 then
1401 prerr_endline ("Error loading state " ^ Printexc.to_string exn)
1403 Hashtbl.create 1
1405 let savestate () =
1407 let w, h =
1408 match state.fullscreen with
1409 | None -> state.w, state.h
1410 | Some wh -> wh
1412 Hashtbl.replace pstate state.path (state.bookmarks, w, h);
1413 let oc = open_out_bin statepath in
1414 output_value oc pstate
1415 with exn ->
1416 if false
1417 then
1418 prerr_endline ("Error saving state " ^ Printexc.to_string exn)
1421 let setstate () =
1423 let statebookmarks, statew, stateh = Hashtbl.find pstate state.path in
1424 state.w <- statew;
1425 state.h <- stateh;
1426 state.bookmarks <- statebookmarks;
1427 with Not_found -> ()
1428 | exn ->
1429 prerr_endline ("Error setting state " ^ Printexc.to_string exn)
1432 Arg.parse [] (fun s -> state.path <- s) "options:";
1433 let name =
1434 if String.length state.path = 0
1435 then (prerr_endline "filename missing"; exit 1)
1436 else state.path
1439 setstate ();
1440 let _ = Glut.init Sys.argv in
1441 let () = Glut.initDisplayMode ~depth:false ~double_buffer:true () in
1442 let () = Glut.initWindowSize state.w state.h in
1443 let _ = Glut.createWindow ("llpp " ^ Filename.basename name) in
1445 let csock, ssock = Unix.socketpair Unix.PF_UNIX Unix.SOCK_STREAM 0 in
1447 init ssock;
1448 state.csock <- csock;
1449 state.ssock <- ssock;
1450 writecmd csock ("open " ^ name ^ "\000");
1452 let () = Glut.displayFunc display in
1453 let () = Glut.reshapeFunc reshape in
1454 let () = Glut.keyboardFunc keyboard in
1455 let () = Glut.specialFunc special in
1456 let () = Glut.idleFunc (Some idle) in
1457 let () = Glut.mouseFunc mouse in
1458 let () = Glut.motionFunc motion in
1459 let () = Glut.passiveMotionFunc pmotion in
1461 at_exit savestate;
1463 let rec handlelablglutbug () =
1465 Glut.mainLoop ();
1466 with Glut.BadEnum "key in special_of_int" ->
1467 showtext '!' " LablGlut bug: special key not recognized";
1468 Glut.swapBuffers ();
1469 handlelablglutbug ()
1471 handlelablglutbug ();