@@ -716,52 +716,16 @@ let short_user_input ~prompt ?default ?on_eof f =
716716 let on_eof = OpamStd.Option.Op. (on_eof ++ default) in
717717 let prompt () = print_string prompt; flush stdout in
718718 try
719- if OpamStd.Sys. (not tty_out || os () = Win32 || os () = Cygwin ) then
720- let rec loop () =
721- prompt () ;
722- let input = match String. lowercase_ascii (read_line () ) with
723- | "" -> default
724- | s -> Some s
725- in
726- match OpamStd.Option.Op. (input >> = f) with
727- | Some a -> a
728- | None -> loop ()
729- in
730- loop ()
731- else
732- let open Unix in
733- prompt () ;
734- let buf = Bytes. create 3 in
735719 let rec loop () =
736- let input =
737- match
738- (* Some keystrokes, e.g. arrows, can return 3 chars *)
739- let nr = read stdin buf 0 3 in
740- if nr < 1 then raise End_of_file
741- else String. uncapitalize_ascii (Bytes. sub_string buf 0 nr)
742- with
743- | "\n " -> default
720+ prompt () ;
721+ let input = match String. lowercase_ascii (read_line () ) with
722+ | "" -> default
744723 | s -> Some s
745- | exception Unix. Unix_error (Unix. EINTR,_ ,_ ) -> None
746- | exception Unix. Unix_error _ -> raise End_of_file
747724 in
748- match input with
725+ match OpamStd.Option.Op. (input >> = f) with
726+ | Some a -> a
749727 | None -> loop ()
750- | Some i -> match f i with
751- | Some a when String. length i > 0 && i.[0 ] = '\027' ->
752- print_newline () ; a
753- | Some a -> print_endline i; a
754- | None -> loop ()
755- in
756- let attr = tcgetattr stdin in
757- let reset () =
758- tcsetattr stdin TCSAFLUSH attr;
759- tcflush stdin TCIFLUSH ;
760728 in
761- OpamStd.Exn. finally reset @@ fun () ->
762- tcsetattr stdin TCSAFLUSH
763- {attr with c_icanon = false ; c_echo = false };
764- tcflush stdin TCIFLUSH ;
765729 loop ()
766730 with
767731 | Sys. Break as e -> OpamStd.Exn. finalise e (fun () -> msg " \n " )
0 commit comments