@@ -104,10 +104,13 @@ module Config : sig
104104 val path : t -> string
105105 val of_string : string -> t
106106 val of_flags : string list -> t
107+
108+ (* * [recent] should be true if jsoo version is 6.0 or higher. *)
107109 val to_flags : recent :bool -> t -> string list
108- (* * [recent] should be true if jsoo version is 6.0 or higher. *)
109110end = struct
110- type effects_backend = Cps | Double_translation
111+ type effects_backend =
112+ | Cps
113+ | Double_translation
111114
112115 type t =
113116 { js_string : bool option
@@ -131,13 +134,13 @@ end = struct
131134 | "use-js-string" , `False -> { acc with js_string = Some false }
132135 | "effects" , `Effects backend -> { acc with effects = Some backend }
133136 | "effects" , `False ->
134- (* [--disable effects] *)
135- { acc with effects = None }
137+ (* [--disable effects] *)
138+ { acc with effects = None }
136139 | "effects" , `True ->
137- (* [--enable effects], used alone, implies [--effects=cps] *)
138- (match acc.effects with
139- | None -> { acc with effects = Some Cps }
140- | Some _ -> acc)
140+ (* [--enable effects], used alone, implies [--effects=cps] *)
141+ (match acc.effects with
142+ | None -> { acc with effects = Some Cps }
143+ | Some _ -> acc)
141144 | "toplevel" , `True -> { acc with toplevel = Some true }
142145 | "toplevel" , `False -> { acc with toplevel = Some false }
143146 | _ -> acc
@@ -146,18 +149,23 @@ end = struct
146149 let string_of_effects = function
147150 | Cps -> " cps"
148151 | Double_translation -> " double-translation"
152+ ;;
149153
150154 let path t =
151155 if t = default
152156 then " default"
153- else
154- let of_bool_opt key = Option. map ~f: (function true -> key | false -> " !" ^ key) in
157+ else (
158+ let of_bool_opt key =
159+ Option. map ~f: (function
160+ | true -> key
161+ | false -> " !" ^ key)
162+ in
155163 List. filter_opt
156164 [ of_bool_opt " use-js-string" t.js_string
157165 ; Option. map t.effects ~f: string_of_effects
158166 ; of_bool_opt " toplevel" t.toplevel
159167 ]
160- |> String. concat ~sep: " +"
168+ |> String. concat ~sep: " +" )
161169 ;;
162170
163171 let effects_of_string = function
@@ -171,15 +179,15 @@ end = struct
171179 | "default" -> default
172180 | _ ->
173181 List. fold_left (String. split ~on: '+' x) ~init: default ~f: (fun acc name ->
174- match ( String. drop_prefix ~prefix: " !" name
175- , String. drop_prefix ~prefix: " effects=" name ) with
182+ match
183+ String. drop_prefix ~prefix: " !" name, String. drop_prefix ~prefix: " effects=" name
184+ with
176185 | Some name , _ -> set acc name `False
177186 | None , None -> set acc name `True
178187 | None , Some backend ->
179- (match effects_of_string backend with
180- | Some backend -> set acc name (`Effects backend)
181- | None -> acc)
182- )
188+ (match effects_of_string backend with
189+ | Some backend -> set acc name (`Effects backend)
190+ | None -> acc))
183191 ;;
184192
185193 let of_flags l =
@@ -198,16 +206,16 @@ end = struct
198206 | "--toplevel" :: rest -> loop (set acc " toplevel" `True ) rest
199207 | "--effects" :: "cps" :: rest -> loop (set acc " effects" `Cps ) rest
200208 | "--effects" :: "double-translation" :: rest ->
201- loop (set acc " effects" `Double_translation ) rest
209+ loop (set acc " effects" `Double_translation ) rest
202210 | maybe_effects :: rest when String. is_prefix maybe_effects ~prefix: " --effects=" ->
203- let backend =
204- Option. bind
205- (String. drop_prefix maybe_effects ~prefix: " --effects=" )
206- ~f: effects_of_string
207- in
208- (match backend with
209- | Some backend -> set acc " effects" (`Effects backend)
210- | None -> loop acc rest)
211+ let backend =
212+ Option. bind
213+ (String. drop_prefix maybe_effects ~prefix: " --effects=" )
214+ ~f: effects_of_string
215+ in
216+ (match backend with
217+ | Some backend -> set acc " effects" (`Effects backend)
218+ | None -> loop acc rest)
211219 | _ :: rest -> loop acc rest
212220 in
213221 loop default l
@@ -216,29 +224,28 @@ end = struct
216224 let backward_compatible_effects ~recent str =
217225 match str with
218226 | None ->
219- (* For jsoo, this means unsupported effects. For wasmoo, this means effects go
220- through the Javascript Promise API. *)
221- None
222- | Some Cps ->
223- if recent then
224- Some " --effects=cps"
225- else
226- Some " --enable=effects"
227+ (* For jsoo, this means unsupported effects. For wasmoo, this means effects go
228+ through the Javascript Promise API. *)
229+ None
230+ | Some Cps -> if recent then Some " --effects=cps" else Some " --enable=effects"
227231 | Some Double_translation ->
228- (* For js_of_ocaml < 6.0, this flag does not exist and will raise an error,
229- which is fine. *)
230- Some " --effects=double-translation"
232+ (* For js_of_ocaml < 6.0, this flag does not exist and will raise an error,
233+ which is fine. *)
234+ Some " --effects=double-translation"
231235 ;;
232236
233237 let to_flags ~recent t =
234238 List. filter_opt
235- [ (match t.toplevel with Some true -> Some " --toplevel" | _ -> None )
239+ [ (match t.toplevel with
240+ | Some true -> Some " --toplevel"
241+ | _ -> None )
236242 ; backward_compatible_effects ~recent t.effects
237243 ; (match t.js_string with
238244 | Some true -> Some " --enable=use-js-string"
239245 | Some false -> Some " --disable=use-js-string"
240246 | None -> None )
241247 ]
248+ ;;
242249end
243250
244251let in_build_dir (ctx : Build_context.t ) ~config args =
@@ -338,7 +345,9 @@ let js_of_ocaml_rule
338345 let recent =
339346 match jsoo_version with
340347 | Some v ->
341- (match Version. compare v (6 , 0 ) with Gt | Eq -> true | Lt -> false )
348+ (match Version. compare v (6 , 0 ) with
349+ | Gt | Eq -> true
350+ | Lt -> false )
342351 | None -> false
343352 in
344353 Command.Args. S
0 commit comments