@@ -299,71 +299,23 @@ module Lookup = struct
299299
300300end
301301
302- (* Packing up everything in two modules of similar signature:
303- [Without_locations] and [With_locations]. In the toplevel signature, only
304- [With_locations] appears, and [Without_locations] contents are directly
305- included at the toplevel.
306- *)
307-
308- module Without_locations = struct
309- include No_locs
310-
311- let parse_lx lexbuf = erase_locs (parse_lx lexbuf)
312- let of_string s = erase_locs (of_string s)
313-
314- let pp = pp
315- let to_formatter = pp
316-
317- let to_string = to_string
318-
319- let rec fold ~string ~section ~escaped ~unescaped ~partial ~comment ~concat t =
320- let go = fold ~string ~section ~escaped ~unescaped ~partial ~comment ~concat in
321- match t with
322- | String s -> string s
323- | Escaped s -> escaped s
324- | Unescaped s -> unescaped s
325- | Comment s -> comment s
326- | Section { name; contents } ->
327- section ~inverted: false name (go contents)
328- | Inverted_section { name; contents } ->
329- section ~inverted: true name (go contents)
330- | Concat ms ->
331- concat (List. map ms ~f: go)
332- | Partial p -> partial p.indent p.name p.contents
333-
334- module Infix = struct
335- let (^) y x = Concat [x; y]
336- end
337-
338- let raw s = String s
339- let escaped s = Escaped s
340- let unescaped s = Unescaped s
341- let section n c = Section { name = n ; contents = c }
342- let inverted_section n c = Inverted_section { name = n ; contents = c }
343- let partial ?(indent = 0 ) n c = Partial { indent ; name = n ; contents = c }
344- let concat t = Concat t
345- let comment s = Comment s
346-
347- let rec expand_partials (partials : name -> t option ) : t -> t =
348- let section ~inverted =
349- if inverted then inverted_section else section
350- in
351- let partial indent name contents =
352- let contents' = lazy (
353- match Lazy. force contents with
354- | None -> option_map (partials name) (expand_partials partials)
355- | Some t_opt -> Some t_opt
356- )
357- in
358- partial ~indent name contents'
359- in
360- fold ~string: raw ~section ~escaped ~unescaped ~partial ~comment ~concat
361-
362- (* Rendering: defined on the ast without locations. *)
363-
364- let render_buf
302+ module Render = struct
303+ (* Rendering is defined on the ast without locations. *)
304+
305+ open No_locs
306+
307+ (* Render a template whose partials have already been expanded.
308+
309+ Note: the reason we expand partials once before rendering,
310+ instead of expanding on the fly during rendering, is to avoid
311+ expanding many times the partials that are inside a list. However,
312+ this as the consequence that some partials that may not be used
313+ in a given rendering may be expanded, and that partial expansion
314+ cannot have access to the specific context of each partial usage
315+ -- some other Mustache APIs pass this context information to the
316+ partial-resolution function. *)
317+ let render_expanded
365318 ?(strict = true )
366- ?(partials = fun _ -> None )
367319 (buf : Buffer.t ) (m : No_locs.t ) (js : Json.t )
368320 =
369321 let print_indent indent =
@@ -394,7 +346,7 @@ module Without_locations = struct
394346 ) (List. tl lines)
395347 in
396348
397- let rec render ' indent m (ctxs : Contexts.t ) = match m with
349+ let rec render indent m (ctxs : Contexts.t ) = match m with
398350
399351 | String s ->
400352 print_indented_string indent s
@@ -409,10 +361,10 @@ module Without_locations = struct
409361
410362 | Inverted_section s ->
411363 if Lookup. inverted ctxs s.name
412- then render' indent s.contents ctxs
364+ then render indent s.contents ctxs
413365
414366 | Section s ->
415- let enter ctx = render' indent s.contents (Contexts. add ctxs ctx) in
367+ let enter ctx = render indent s.contents (Contexts. add ctxs ctx) in
416368 begin match Lookup. section ~strict ctxs ~key: s.name with
417369 | `Bool false -> ()
418370 | `A elems -> List. iter enter elems
@@ -421,17 +373,82 @@ module Without_locations = struct
421373
422374 | Partial { indent = partial_indent ; name; contents } ->
423375 begin match (Lazy. force contents, strict) with
424- | Some p , _ -> render' (indent + partial_indent) p ctxs
376+ | Some p , _ -> render (indent + partial_indent) p ctxs
425377 | None , false -> ()
426378 | None , true -> raise (Missing_partial name)
427379 end
428380
429381 | Comment _c -> ()
430382
431383 | Concat templates ->
432- List. iter (fun x -> render' indent x ctxs) templates
384+ List. iter (fun x -> render indent x ctxs) templates
385+
386+ in render 0 m (Contexts. start (Json. value js))
387+ end
388+
389+ (* Packing up everything in two modules of similar signature:
390+ [Without_locations] and [With_locations]. In the toplevel signature, only
391+ [With_locations] appears, and [Without_locations] contents are directly
392+ included at the toplevel.
393+ *)
394+
395+ module Without_locations = struct
396+ include No_locs
397+
398+ let parse_lx lexbuf = erase_locs (parse_lx lexbuf)
399+ let of_string s = erase_locs (of_string s)
400+
401+ let pp = pp
402+ let to_formatter = pp
403+
404+ let to_string = to_string
405+
406+ let rec fold ~string ~section ~escaped ~unescaped ~partial ~comment ~concat t =
407+ let go = fold ~string ~section ~escaped ~unescaped ~partial ~comment ~concat in
408+ match t with
409+ | String s -> string s
410+ | Escaped s -> escaped s
411+ | Unescaped s -> unescaped s
412+ | Comment s -> comment s
413+ | Section { name; contents } ->
414+ section ~inverted: false name (go contents)
415+ | Inverted_section { name; contents } ->
416+ section ~inverted: true name (go contents)
417+ | Concat ms ->
418+ concat (List. map ms ~f: go)
419+ | Partial p -> partial p.indent p.name p.contents
420+
421+ module Infix = struct
422+ let (^) y x = Concat [x; y]
423+ end
424+
425+ let raw s = String s
426+ let escaped s = Escaped s
427+ let unescaped s = Unescaped s
428+ let section n c = Section { name = n ; contents = c }
429+ let inverted_section n c = Inverted_section { name = n ; contents = c }
430+ let partial ?(indent = 0 ) n c = Partial { indent ; name = n ; contents = c }
431+ let concat t = Concat t
432+ let comment s = Comment s
433+
434+ let rec expand_partials (partials : name -> t option ) : t -> t =
435+ let section ~inverted =
436+ if inverted then inverted_section else section
437+ in
438+ let partial indent name contents =
439+ let contents' = lazy (
440+ match Lazy. force contents with
441+ | None -> option_map (partials name) (expand_partials partials)
442+ | Some t_opt -> Some t_opt
443+ )
444+ in
445+ partial ~indent name contents'
446+ in
447+ fold ~string: raw ~section ~escaped ~unescaped ~partial ~comment ~concat
448+
433449
434- in render' 0 (expand_partials partials m) (Contexts. start (Json. value js))
450+ let render_buf ?strict ?(partials = fun _ -> None ) buf (m : t ) (js : Json.t ) =
451+ Render. render_expanded buf ?strict (expand_partials partials m) js
435452
436453 let render ?strict ?partials (m : t ) (js : Json.t ) =
437454 let buf = Buffer. create 0 in
0 commit comments