Skip to content

Commit

Permalink
Get rid of exception in control flow
Browse files Browse the repository at this point in the history
Signed-off-by: Etienne Millon <me@emillon.org>
  • Loading branch information
emillon committed Aug 2, 2019
1 parent cdfcdec commit 9439062
Showing 1 changed file with 31 additions and 34 deletions.
65 changes: 31 additions & 34 deletions src/format_config.ml
Original file line number Diff line number Diff line change
Expand Up @@ -53,11 +53,13 @@ let enabled_for_to_dyn =
| Only l -> constr "only" (List.map ~f:language_to_dyn l)
| All -> string "all"

type t =
type 'enabled_for generic_t =
{ loc : Loc.t
; enabled_for : enabled_for
; enabled_for : 'enabled_for
}

type t = enabled_for generic_t

let to_dyn {enabled_for; loc = _} =
let open Dyn.Encoder in
record ["enabled_for", enabled_for_to_dyn enabled_for]
Expand Down Expand Up @@ -106,43 +108,38 @@ let field =

let loc t = t.loc

exception Delete

module Encoder = struct
open Dune_lang.Encoder

let encode_language = function
| Dune -> string "dune"
| Dialect d -> string d

let explicit_langs =
function
| Only l -> l
| All -> Exn.raise_notrace Delete

let encode_enabled_for ef =
explicit_langs ef
|> List.map ~f:encode_language

let encode_formatting {loc=_; enabled_for}=
record_fields
[ field_i "enabled_for" encode_enabled_for enabled_for
]

let conf conf =
[field_i "formatting" encode_formatting conf]
|> record_fields
|> List.hd
end
let encode_language =
let open Dune_lang.Encoder in
function
| Dune -> string "dune"
| Dialect d -> string d

let encode_formatting {loc=_; enabled_for}=
let open Dune_lang.Encoder in
record_fields
[ field_i "enabled_for" (List.map ~f:encode_language) enabled_for
]

let encode_explicit conf =
let open Dune_lang.Encoder in
[field_i "formatting" encode_formatting conf]
|> record_fields
|> List.hd

let to_explicit {loc;enabled_for} =
match enabled_for with
| All -> None
| Only l -> Some {loc; enabled_for = l}

let compat_error_message ext =
let suggestion =
match Encoder.conf ext with
| x ->
match to_explicit ext with
| Some explicit ->
let dlang = encode_explicit explicit in
[ Pp.textf "To port it to the new syntax, you can replace this part by:"
; Pp.tag ~tag:User_message.Style.Details (Dune_lang.pp x)
; Pp.tag ~tag:User_message.Style.Details (Dune_lang.pp dlang)
]
| exception Delete -> [ Pp.textf "To port it to the new syntax, you can delete this part."]
| None -> [ Pp.textf "To port it to the new syntax, you can delete this part."]
in
User_error.make
~loc:ext.loc
Expand Down

0 comments on commit 9439062

Please sign in to comment.