Skip to content

Commit

Permalink
Raname Utils map_files into map_md_files (#2515)
Browse files Browse the repository at this point in the history
* Raname Utils map_files into map_md_files

* Rename function definition

---------

Co-authored-by: Cuihtlauac ALVARADO <[email protected]>
  • Loading branch information
cuihtlauac and Cuihtlauac ALVARADO authored Jun 14, 2024
1 parent 66641c6 commit 6eeaa2c
Show file tree
Hide file tree
Showing 17 changed files with 20 additions and 19 deletions.
2 changes: 1 addition & 1 deletion tool/ood-gen/lib/academic_institution.ml
Original file line number Diff line number Diff line change
Expand Up @@ -22,7 +22,7 @@ let decode (fpath, (head, body_md)) =
in
Result.map (of_metadata ~body_md ~body_html) metadata

let all () = Utils.map_files decode "academic_institutions/*.md"
let all () = Utils.map_md_files decode "academic_institutions/*.md"

let template () =
Format.asprintf {|
Expand Down
2 changes: 1 addition & 1 deletion tool/ood-gen/lib/book.ml
Original file line number Diff line number Diff line change
Expand Up @@ -29,7 +29,7 @@ let decode (fpath, (head, body)) =
Result.map (of_metadata ~body_md ~body_html) metadata

let all () =
Utils.map_files decode "books/*.md"
Utils.map_md_files decode "books/*.md"
|> List.sort (fun (b1 : t) (b2 : t) ->
(* Sort the books by reversed publication date. *)
String.compare b2.published b1.published)
Expand Down
2 changes: 1 addition & 1 deletion tool/ood-gen/lib/changelog.ml
Original file line number Diff line number Diff line change
Expand Up @@ -76,7 +76,7 @@ let decode (fname, (head, body)) =
metadata

let all () =
Utils.map_files decode "changelog/*/*.md"
Utils.map_md_files decode "changelog/*/*.md"
|> List.sort (fun a b -> String.compare b.slug a.slug)

module ChangelogFeed = struct
Expand Down
2 changes: 1 addition & 1 deletion tool/ood-gen/lib/cookbook.ml
Original file line number Diff line number Diff line change
Expand Up @@ -117,7 +117,7 @@ let all_categories_and_tasks () =
let tasks, top_categories = all_categories_and_tasks ()

let all () =
Utils.map_files (decode tasks) "cookbook/*/*.ml"
Utils.map_md_files (decode tasks) "cookbook/*/*.ml"
|> List.sort (fun (a : t) (b : t) -> String.compare b.slug a.slug)
|> List.rev

Expand Down
2 changes: 1 addition & 1 deletion tool/ood-gen/lib/event.ml
Original file line number Diff line number Diff line change
Expand Up @@ -128,7 +128,7 @@ let decode (recurring_events : RecurringEvent.t list) (fpath, (head, body_md)) =
metadata

let all () =
Utils.map_files (decode (RecurringEvent.all ())) "events/*.md"
Utils.map_md_files (decode (RecurringEvent.all ())) "events/*.md"
|> List.sort (fun e1 e2 ->
(* Sort the events by reversed start date. *)
let t1 =
Expand Down
2 changes: 1 addition & 1 deletion tool/ood-gen/lib/exercise.ml
Original file line number Diff line number Diff line change
Expand Up @@ -55,7 +55,7 @@ let compare_by_slug =
fun (x : t) (y : t) -> compare (key x) (key y)

let all () =
Utils.map_files decode "exercises/*.md" |> List.sort compare_by_slug
Utils.map_md_files decode "exercises/*.md" |> List.sort compare_by_slug

let template () =
Format.asprintf {|
Expand Down
2 changes: 1 addition & 1 deletion tool/ood-gen/lib/industrial_user.ml
Original file line number Diff line number Diff line change
Expand Up @@ -22,7 +22,7 @@ let decode (fpath, (head, body_md)) =
in
Result.map (of_metadata ~body_md ~body_html) metadata

let all () = Utils.map_files decode "industrial_users/*.md"
let all () = Utils.map_md_files decode "industrial_users/*.md"

let template () =
Format.asprintf {|
Expand Down
2 changes: 1 addition & 1 deletion tool/ood-gen/lib/is_ocaml_yet.ml
Original file line number Diff line number Diff line change
Expand Up @@ -43,7 +43,7 @@ let decode (fpath, (head, body_md)) =
in
Result.map (metadata_to_t ~body_html ~modify_categories) metadata

let all () = Utils.map_files decode "is_ocaml_yet/*.md"
let all () = Utils.map_md_files decode "is_ocaml_yet/*.md"

let template () =
Format.asprintf {|
Expand Down
2 changes: 1 addition & 1 deletion tool/ood-gen/lib/news.ml
Original file line number Diff line number Diff line change
Expand Up @@ -35,7 +35,7 @@ let decode (fname, (head, body)) =
Result.map (of_metadata ~slug ~body_html) metadata

let all () =
Utils.map_files decode "news/*/*.md"
Utils.map_md_files decode "news/*/*.md"
|> List.sort (fun a b -> String.compare b.date a.date)

let template () =
Expand Down
2 changes: 1 addition & 1 deletion tool/ood-gen/lib/page.ml
Original file line number Diff line number Diff line change
Expand Up @@ -31,7 +31,7 @@ let decode (file, (head, body_md)) =
in
Result.map (of_metadata ~slug ~body_md ~body_html) metadata

let all () = Utils.map_files decode "pages/*.md"
let all () = Utils.map_md_files decode "pages/*.md"

let template () =
Format.asprintf
Expand Down
4 changes: 2 additions & 2 deletions tool/ood-gen/lib/planet.ml
Original file line number Diff line number Diff line change
Expand Up @@ -116,7 +116,7 @@ module Local = struct
|> Result.map (of_metadata ~slug ~source ~body_html)

let all () : post list =
Utils.map_files decode "planet-local-blogs/*/*.md"
Utils.map_md_files decode "planet-local-blogs/*/*.md"
|> List.sort (fun (a : post) b -> String.compare b.date a.date)
end
end
Expand Down Expand Up @@ -234,7 +234,7 @@ module External = struct
|> Result.map (of_metadata ~source ~body_html)

let all () : post list =
Utils.map_files decode "planet/*/*.md"
Utils.map_md_files decode "planet/*/*.md"
|> List.sort (fun (a : post) b -> String.compare b.date a.date)
end
end
Expand Down
3 changes: 2 additions & 1 deletion tool/ood-gen/lib/release.ml
Original file line number Diff line number Diff line change
Expand Up @@ -67,7 +67,8 @@ let decode (fpath, (head, body_md)) =
Result.map (of_metadata ~body_md ~body_html) metadata

let all () =
Utils.map_files decode "releases/*.md" |> List.sort sort_by_decreasing_version
Utils.map_md_files decode "releases/*.md"
|> List.sort sort_by_decreasing_version

let template () =
let all = all () in
Expand Down
2 changes: 1 addition & 1 deletion tool/ood-gen/lib/success_story.ml
Original file line number Diff line number Diff line change
Expand Up @@ -34,7 +34,7 @@ let decode (fpath, (head, body_md)) =
in
Result.map (of_metadata ~body_md ~body_html) metadata

let all () = Utils.map_files decode "success_stories/*.md"
let all () = Utils.map_md_files decode "success_stories/*.md"

let template () =
Format.asprintf
Expand Down
2 changes: 1 addition & 1 deletion tool/ood-gen/lib/tool_page.ml
Original file line number Diff line number Diff line change
Expand Up @@ -43,7 +43,7 @@ let decode (fpath, (head, body_md)) =
Result.map (of_metadata ~fpath ~toc ~body_md ~body_html) metadata

let all () =
Utils.map_files decode "tool_pages/*/*.md"
Utils.map_md_files decode "tool_pages/*/*.md"
|> List.sort (fun t1 t2 -> String.compare t1.fpath t2.fpath)

let template () =
Expand Down
4 changes: 2 additions & 2 deletions tool/ood-gen/lib/tutorial.ml
Original file line number Diff line number Diff line change
Expand Up @@ -109,7 +109,7 @@ let decode (fpath, (head, body_md)) =
Result.map (of_metadata ~fpath ~section ~toc ~body_md ~body_html) metadata

let all () =
Utils.map_files decode "tutorials/*/*.md"
Utils.map_md_files decode "tutorials/*/*.md"
|> List.sort (fun t1 t2 -> String.compare t1.fpath t2.fpath)

module TutorialSearch = struct
Expand Down Expand Up @@ -160,7 +160,7 @@ module TutorialSearch = struct
| Error msg -> Error msg

let all () : search_document list =
Utils.map_files decode_search_document "tutorials/*/*.md" |> List.flatten
Utils.map_md_files decode_search_document "tutorials/*/*.md" |> List.flatten
end

let template () =
Expand Down
2 changes: 1 addition & 1 deletion tool/ood-gen/lib/utils.ml
Original file line number Diff line number Diff line change
Expand Up @@ -53,7 +53,7 @@ let read_from_dir glob =

let where path (`Msg err) = `Msg (path ^ ": " ^ err)

let map_files f glob =
let map_md_files f glob =
let f (path, data) =
let* metadata =
extract_metadata_body path data |> Result.map_error (where path)
Expand Down
2 changes: 1 addition & 1 deletion tool/ood-gen/lib/workshop.ml
Original file line number Diff line number Diff line change
Expand Up @@ -92,7 +92,7 @@ let decode (fpath, (head, body_md)) =
Result.map (of_metadata ~body_md ~body_html) metadata

let all () =
Utils.map_files decode "workshops/*.md"
Utils.map_md_files decode "workshops/*.md"
|> List.sort (fun w1 w2 -> String.compare w2.date w1.date)

let template () =
Expand Down

0 comments on commit 6eeaa2c

Please sign in to comment.