Skip to content

Commit

Permalink
[stdune] add scanf module (#2820)
Browse files Browse the repository at this point in the history
[stdune] add scanf module
  • Loading branch information
rgrinberg authored Nov 5, 2019
2 parents 06e8745 + 38f6bdd commit d49e16e
Show file tree
Hide file tree
Showing 9 changed files with 62 additions and 12 deletions.
14 changes: 13 additions & 1 deletion src/dune/build.ml
Original file line number Diff line number Diff line change
Expand Up @@ -118,7 +118,19 @@ let contents p = Contents p

let lines_of p = Lines_of p

let strings p = Map ((fun l -> List.map l ~f:Scanf.unescaped), lines_of p)
let strings p =
let f x =
match Scanf.unescaped x with
| Error () ->
User_error.raise
[ Pp.textf "Unable to parse %s" (Path.to_string_maybe_quoted p)
; Pp.textf
"This file must be a list of lines escaped using OCaml's \
conventions"
]
| Ok s -> s
in
Map ((fun l -> List.map l ~f), lines_of p)

let read_sexp p =
let+ s = contents p in
Expand Down
5 changes: 3 additions & 2 deletions src/dune/context.ml
Original file line number Diff line number Diff line change
Expand Up @@ -626,8 +626,9 @@ let opam_version =
let+ version =
Process.run_capture_line Strict ~env opam [ "--version" ]
in
try Scanf.sscanf version "%d.%d.%d" (fun a b c -> (a, b, c))
with _ ->
match Scanf.sscanf version "%d.%d.%d" (fun a b c -> (a, b, c)) with
| Ok s -> s
| Error () ->
User_error.raise
[ Pp.textf "`%s config --version' returned invalid output:"
(Path.to_string_maybe_quoted opam)
Expand Down
4 changes: 2 additions & 2 deletions src/dune/dune_load.ml
Original file line number Diff line number Diff line change
Expand Up @@ -55,8 +55,8 @@ module Dune_files = struct
let check_no_requires path str =
List.iteri (String.split str ~on:'\n') ~f:(fun n line ->
match Scanf.sscanf line "#require %S" (fun x -> x) with
| exception _ -> ()
| (_ : string) ->
| Error () -> ()
| Ok (_ : string) ->
let loc : Loc.t =
let start : Lexing.position =
{ pos_fname = Path.to_string path
Expand Down
5 changes: 3 additions & 2 deletions src/dune_lang/syntax.ml
Original file line number Diff line number Diff line change
Expand Up @@ -32,8 +32,9 @@ module Version = struct
raw
>>| function
| Atom (loc, A s) -> (
try Scanf.sscanf s "%u.%u" (fun a b -> (a, b))
with _ ->
match Scanf.sscanf s "%u.%u" (fun a b -> (a, b)) with
| Ok s -> s
| Error () ->
User_error.raise ~loc [ Pp.text "Atom of the form NNN.NNN expected" ] )
| sexp -> User_error.raise ~loc:(Ast.loc sexp) [ Pp.text "Atom expected" ]

Expand Down
16 changes: 11 additions & 5 deletions src/ocaml-config/ocaml_config.ml
Original file line number Diff line number Diff line change
Expand Up @@ -377,7 +377,15 @@ let make vars =
in
let version_string = get vars "version" in
let version =
Scanf.sscanf version_string "%u.%u.%u" (fun a b c -> (a, b, c))
match
Scanf.sscanf version_string "%u.%u.%u" (fun a b c -> (a, b, c))
with
| Ok t -> t
| Error () ->
User_error.raise
[ Pp.textf "Unable to parse ocamlc -config version: %s"
version_string
]
in
let os_type = get vars "os_type" in
let standard_library_default = get vars "standard_library_default" in
Expand Down Expand Up @@ -512,7 +520,5 @@ let make vars =
| exception Vars.E (origin, msg) -> Error (origin, msg)

let is_dev_version t =
try
Scanf.sscanf t.version_string "%u.%u.%u+dev" (fun _ _ _ -> ());
true
with _ -> false
Scanf.sscanf t.version_string "%u.%u.%u+dev" (fun _ _ _ -> ())
|> Result.is_ok
1 change: 1 addition & 0 deletions src/stdune/caml/dune_caml.ml
Original file line number Diff line number Diff line change
Expand Up @@ -12,3 +12,4 @@ module ListLabels = ListLabels
module List = List
module MoreLabels = MoreLabels
module ArrayLabels = ArrayLabels
module Scanf = Scanf
12 changes: 12 additions & 0 deletions src/stdune/scanf.ml
Original file line number Diff line number Diff line change
@@ -0,0 +1,12 @@
module Scanf = Dune_caml.Scanf

let unescaped x =
match Scanf.unescaped x with
| exception Scanf.Scan_failure _ -> Error ()
| x -> Ok x

exception E
let sscanf x fmt f =
match Scanf.ksscanf x (fun _ _ -> raise_notrace E) fmt f with
| exception E -> Error ()
| x -> Ok x
16 changes: 16 additions & 0 deletions src/stdune/scanf.mli
Original file line number Diff line number Diff line change
@@ -0,0 +1,16 @@
(** Safe version of Scanf from the stdlib. Does not raise parsing errors
errors. *)

val unescaped : string -> (string, unit) Result.t

val sscanf :
string
-> ( 'a
, Dune_caml.Scanf.Scanning.in_channel
, 'b
, 'c -> 'd
, 'a -> 'e
, 'e )
format6
-> 'c
-> ('d, unit) result
1 change: 1 addition & 0 deletions src/stdune/stdune.ml
Original file line number Diff line number Diff line change
Expand Up @@ -58,6 +58,7 @@ module User_error = User_error
module User_message = User_message
module User_warning = User_warning
module Lexbuf = Lexbuf
module Scanf = Scanf

(* Pervasives is deprecated in 4.08 in favor of Stdlib, however we are
currently compatible with OCaml >= 4.02 so for now we simply disable the
Expand Down

0 comments on commit d49e16e

Please sign in to comment.