Skip to content

Commit

Permalink
Single data type definition for Cookbook (#2490)
Browse files Browse the repository at this point in the history
Co-authored-by: Cuihtlauac ALVARADO <[email protected]>
  • Loading branch information
cuihtlauac and Cuihtlauac ALVARADO authored Jun 7, 2024
1 parent f2b13a4 commit e8b5724
Show file tree
Hide file tree
Showing 3 changed files with 52 additions and 101 deletions.
31 changes: 1 addition & 30 deletions src/ocamlorg_data/data.mli
Original file line number Diff line number Diff line change
Expand Up @@ -35,36 +35,7 @@ module Code_example : sig
end

module Cookbook : sig
type category = {
title : string;
slug : string;
subcategories : category list;
}

type task = {
title : string;
slug : string;
category_path : string list;
description : string option;
}

type code_block_with_explanation = { code : string; explanation : string }

type package = {
name : string;
tested_version : string;
used_libraries : string list;
}

type t = {
slug : string;
filepath : string;
task : task;
packages : package list;
code_blocks : code_block_with_explanation list;
code_plaintext : string;
discussion_html : string;
}
include module type of Data_intf.Cookbook

val top_categories : category list
val tasks : task list
Expand Down
38 changes: 38 additions & 0 deletions src/ocamlorg_data/data_intf.ml
Original file line number Diff line number Diff line change
Expand Up @@ -57,6 +57,44 @@ module Book = struct
[@@deriving show]
end

module Cookbook = struct
type category = {
title : string;
slug : string;
subcategories : category list;
}
[@@deriving show]

type task = {
title : string;
slug : string;
category_path : string list;
description : string option;
}
[@@deriving show]

type code_block_with_explanation = { code : string; explanation : string }
[@@deriving show]

type package = {
name : string;
tested_version : string;
used_libraries : string list;
}
[@@deriving of_yaml, show]

type t = {
slug : string;
filepath : string;
task : task;
packages : package list;
code_blocks : code_block_with_explanation list;
code_plaintext : string;
discussion_html : string;
}
[@@deriving show]
end

module Outreachy = struct
type project = {
title : string;
Expand Down
84 changes: 13 additions & 71 deletions tool/ood-gen/lib/cookbook.ml
Original file line number Diff line number Diff line change
@@ -1,3 +1,5 @@
open Data_intf.Cookbook

type task_metadata = {
title : string;
slug : string;
Expand All @@ -12,45 +14,14 @@ type category_metadata = {
}
[@@deriving of_yaml]

type category = { title : string; slug : string; subcategories : category list }
[@@deriving show { with_path = false }]

type task = {
title : string;
slug : string;
category_path : string list;
description : string option;
}
[@@deriving show { with_path = false }]

type code_block_with_explanation = { code : string; explanation : string }
[@@deriving show { with_path = false }]

type package = {
name : string;
tested_version : string;
used_libraries : string list;
}
[@@deriving of_yaml, show { with_path = false }]

type metadata = { packages : package list; discussion : string option }
[@@deriving of_yaml]

type t = {
filepath : string;
slug : string;
task : task;
packages : package list;
code_blocks : code_block_with_explanation list;
code_plaintext : string;
discussion_html : string;
}
[@@deriving
stable_record ~version:metadata
~remove:
[ slug; filepath; task; discussion_html; code_blocks; code_plaintext ]
~add:[ discussion ],
show { with_path = false }]
of_yaml,
stable_record ~version:t
~add:
[ slug; filepath; task; discussion_html; code_blocks; code_plaintext ]
~remove:[ discussion ],
show]

let decode (tasks : task list) (fpath, (head, body)) =
let ( let* ) = Result.bind in
Expand Down Expand Up @@ -106,7 +77,7 @@ let decode (tasks : task list) (fpath, (head, body)) =
let discussion_html =
metadata.discussion |> Option.value ~default:"" |> render_markdown
in
of_metadata ~slug ~filepath:fpath ~task ~discussion_html ~code_blocks
metadata_to_t ~slug ~filepath:fpath ~task ~discussion_html ~code_blocks
~code_plaintext:body metadata)
metadata
|> Result.map_error (Utils.where fpath)
Expand Down Expand Up @@ -147,46 +118,17 @@ let tasks, top_categories = all_categories_and_tasks ()

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

let template () =
Format.asprintf
{|
type category =
{ title : string
; slug : string
; subcategories : category list
}
type task =
{ title : string
; slug : string
; category_path : string list
; description : string option
}
type package =
{ name : string
; tested_version : string
; used_libraries : string list
}
type code_block_with_explanation =
{ code : string
; explanation : string
}
type t =
{ slug: string
; filepath: string
; task : task
; packages : package list
; code_blocks : code_block_with_explanation list
; code_plaintext : string
; discussion_html : string
}

{ocaml|
include Data_intf.Cookbook
let top_categories = %a
let tasks = %a
let all = %a
|}
|ocaml}
(Fmt.brackets (Fmt.list pp_category ~sep:Fmt.semi))
top_categories
(Fmt.brackets (Fmt.list pp_task ~sep:Fmt.semi))
Expand Down

0 comments on commit e8b5724

Please sign in to comment.