Skip to content

Commit

Permalink
Report parse errors with old opam-file-format
Browse files Browse the repository at this point in the history
The sentinel group of kind `#` is now processed correctly in
OpamFile.SyntaxFile. This allows, for example, opam 2.2 to use
opam-file-format 2.1 and still have `opam-version: "2.2"`.
  • Loading branch information
dra27 committed Apr 23, 2021
1 parent 2fb7926 commit ef8e743
Showing 1 changed file with 11 additions and 2 deletions.
13 changes: 11 additions & 2 deletions src/format/opamFile.ml
Original file line number Diff line number Diff line change
Expand Up @@ -1016,15 +1016,24 @@ module SyntaxFile(X: SyntaxFileArg) : IO_FILE with type t := X.t = struct
module IO = struct
let to_opamfile filename t = Pp.print X.pp (filename, t)

let catch_future_syntax_error = function
| {file_contents = [{pelem = Variable({pelem = "opam-version"; _}, {pelem = String ver; _}); _ };
{pelem = Section {section_kind = {pelem = "#"; _}; _}; pos}]; _}
when OpamVersion.(compare (nopatch (of_string ver)) (nopatch X.format_version)) <= 0 ->
raise (OpamPp.Bad_format (Some pos, "Parse error"))
| opamfile -> opamfile

let of_channel filename (ic:in_channel) =
Pp.parse X.pp ~pos:(pos_file filename) (Syntax.of_channel filename ic)
let opamfile = Syntax.of_channel filename ic |> catch_future_syntax_error in
Pp.parse X.pp ~pos:(pos_file filename) opamfile
|> snd

let to_channel filename oc t =
Syntax.to_channel filename oc (to_opamfile filename t)

let of_string (filename:filename) str =
Pp.parse X.pp ~pos:(pos_file filename) (Syntax.of_string filename str)
let opamfile = Syntax.of_string filename str |> catch_future_syntax_error in
Pp.parse X.pp ~pos:(pos_file filename) opamfile
|> snd

let to_string filename t =
Expand Down

0 comments on commit ef8e743

Please sign in to comment.