Skip to content

Commit

Permalink
Single type for Book (#2488)
Browse files Browse the repository at this point in the history
* Single type for Book

* Include Intf in Data

---------

Co-authored-by: Cuihtlauac ALVARADO <[email protected]>
  • Loading branch information
cuihtlauac and Cuihtlauac ALVARADO authored Jun 7, 2024
1 parent c0f8a27 commit e08d869
Show file tree
Hide file tree
Showing 3 changed files with 42 additions and 80 deletions.
20 changes: 1 addition & 19 deletions src/ocamlorg_data/data.mli
Original file line number Diff line number Diff line change
Expand Up @@ -6,25 +6,7 @@ module Academic_institution : sig
end

module Book : sig
type difficulty = Beginner | Intermediate | Advanced
type link = { description : string; uri : string }

type t = {
title : string;
slug : string;
description : string;
recommendation : string option;
authors : string list;
language : string list;
published : string;
cover : string;
isbn : string option;
links : link list;
difficulty : difficulty;
pricing : string;
body_md : string;
body_html : string;
}
include module type of Data_intf.Book

val all : t list
val get_by_slug : string -> t option
Expand Down
34 changes: 34 additions & 0 deletions src/ocamlorg_data/data_intf.ml
Original file line number Diff line number Diff line change
Expand Up @@ -23,6 +23,40 @@ module Academic_institution = struct
[@@deriving show]
end

module Book = struct
type difficulty = Beginner | Intermediate | Advanced [@@deriving show]

let difficulty_of_string = function
| "beginner" -> Ok Beginner
| "intermediate" -> Ok Intermediate
| "advanced" -> Ok Advanced
| s -> Error (`Msg ("Unknown difficulty type: " ^ s))

let difficulty_of_yaml = function
| `String s -> difficulty_of_string s
| _ -> Error (`Msg "Expected a string for difficulty type")

type link = { description : string; uri : string } [@@deriving of_yaml, show]

type t = {
title : string;
slug : string;
description : string;
recommendation : string option;
authors : string list;
language : string list;
published : string;
cover : string;
isbn : string option;
links : link list;
difficulty : difficulty;
pricing : string;
body_md : string;
body_html : string;
}
[@@deriving show]
end

module Outreachy = struct
type project = {
title : string;
Expand Down
68 changes: 7 additions & 61 deletions tool/ood-gen/lib/book.ml
Original file line number Diff line number Diff line change
@@ -1,18 +1,4 @@
module Difficulty = struct
type t = Beginner | Intermediate | Advanced
[@@deriving show { with_path = false }]

let of_string = function
| "beginner" -> Ok Beginner
| "intermediate" -> Ok Intermediate
| "advanced" -> Ok Advanced
| s -> Error (`Msg ("Unknown difficulty type: " ^ s))

let of_yaml = Utils.of_yaml of_string "Expected a string for difficulty type"
end

type link = { description : string; uri : string }
[@@deriving of_yaml, show { with_path = false }]
open Data_intf.Book

type metadata = {
title : string;
Expand All @@ -25,32 +11,12 @@ type metadata = {
cover : string;
isbn : string option;
links : link list;
difficulty : Difficulty.t;
pricing : string;
}
[@@deriving of_yaml, show { with_path = false }]

type t = {
title : string;
slug : string;
description : string;
recommendation : string option;
authors : string list;
language : string list;
published : string;
cover : string;
isbn : string option;
links : link list;
difficulty : Difficulty.t;
difficulty : difficulty;
pricing : string;
body_md : string;
body_html : string;
}
[@@deriving
stable_record ~version:metadata ~remove:[ body_md; body_html ],
show { with_path = false }]
[@@deriving of_yaml, stable_record ~version:t ~add:[ body_md; body_html ]]

let of_metadata m = of_metadata m
let of_metadata m = metadata_to_t m

let decode (fpath, (head, body)) =
let metadata =
Expand All @@ -64,33 +30,13 @@ let decode (fpath, (head, body)) =

let all () =
Utils.map_files decode "books/*.md"
|> List.sort (fun b1 b2 ->
|> List.sort (fun (b1 : t) (b2 : t) ->
(* Sort the books by reversed publication date. *)
String.compare b2.published b1.published)

let template () =
Format.asprintf
{|
type difficulty = Beginner | Intermediate | Advanced
type link = { description : string; uri : string }

type t =
{ title : string
; slug : string
; description : string
; recommendation : string option
; authors : string list
; language : string list
; published : string
; cover : string
; isbn : string option
; links : link list
; difficulty : difficulty
; pricing : string
; body_md : string
; body_html : string
}

Format.asprintf {|
include Data_intf.Book
let all = %a
|}
(Fmt.brackets (Fmt.list pp ~sep:Fmt.semi))
Expand Down

0 comments on commit e08d869

Please sign in to comment.