diff --git a/src/ocamlorg_data/data.ml b/src/ocamlorg_data/data.ml index e9f99a39f0..13e7df0994 100644 --- a/src/ocamlorg_data/data.ml +++ b/src/ocamlorg_data/data.ml @@ -76,8 +76,8 @@ module Planet = struct include Planet let all_tags = - "all" - :: List.sort_uniq compare (List.concat_map (fun item -> item.tags) all) + List.sort_uniq compare + (List.map (fun (item : Planet.t) -> item.source.tag) all) let featured = List.filter (fun x -> x.featured) all let get_by_slug slug = List.find_opt (fun x -> String.equal slug x.slug) all diff --git a/src/ocamlorg_data/data.mli b/src/ocamlorg_data/data.mli index d28f0e4032..129f0c2f59 100644 --- a/src/ocamlorg_data/data.mli +++ b/src/ocamlorg_data/data.mli @@ -264,7 +264,7 @@ end module Planet : sig module Source : sig - type t = { id : string option; name : string; url : string } + type t = { id : string option; name : string; url : string; tag : string } end type t = { @@ -278,7 +278,6 @@ module Planet : sig preview_image : string option; featured : bool; body_html : string; - tags : string list; } val all_tags : string list diff --git a/src/ocamlorg_frontend/pages/blog.eml b/src/ocamlorg_frontend/pages/blog.eml index 2f958d1dd4..4a44e003e7 100644 --- a/src/ocamlorg_frontend/pages/blog.eml +++ b/src/ocamlorg_frontend/pages/blog.eml @@ -5,7 +5,7 @@ Layout.render ~canonical:(Url.blog ^ if planet_page = 1 then "" else "?p=" ^ string_of_int planet_page) ~active_top_nav_item:Header.Blog @@
-
+

OCaml Blog

@@ -93,4 +93,4 @@ Layout.render
-
\ No newline at end of file + diff --git a/src/ocamlorg_web/lib/handler.ml b/src/ocamlorg_web/lib/handler.ml index 7770ecfbf5..00ebd8fb3b 100644 --- a/src/ocamlorg_web/lib/handler.ml +++ b/src/ocamlorg_web/lib/handler.ml @@ -208,9 +208,8 @@ let blog req = let filtred_items_by_tags = if filter = "all" then Data.Planet.all else - List.filter - (fun item -> List.mem filter item.Data.Planet.tags) - Data.Planet.all + Data.Planet.all + |> List.filter (fun (item : Data.Planet.t) -> filter = item.source.tag) in let page, number_of_pages, current_items = paginate ~req ~n:10 diff --git a/tool/ood-gen/lib/planet.ml b/tool/ood-gen/lib/planet.ml index 3b9b78ccf7..5ca71f00c1 100644 --- a/tool/ood-gen/lib/planet.ml +++ b/tool/ood-gen/lib/planet.ml @@ -1,5 +1,5 @@ module Source = struct - type t = { id : string option; name : string; url : string } + type t = { id : string option; name : string; url : string; tag : string } [@@deriving yaml, show { with_path = false }] type sources = t list [@@deriving yaml] @@ -34,11 +34,10 @@ type t = { preview_image : string option; featured : bool; body_html : string; - tags : string list; } [@@deriving stable_record ~version:metadata ~modify:[ featured; source ] - ~remove:[ slug; body_html; tags ], + ~remove:[ slug; body_html ], show { with_path = false }] let all_sources = Source.all () @@ -66,6 +65,7 @@ let decode (path, (head, body)) = id = Some "ocamlorg"; name = "OCaml.org Blog"; url = "https://ocaml.org/blog"; + tag = "all"; } else failwith ("No source found for: " ^ path)) | _ -> @@ -74,10 +74,9 @@ let decode (path, (head, body)) = ^ " but there path is not long enough (should start with \ data/SOURCE_NAME/...)") in - let tags = [ List.nth (String.split_on_char '/' path) 1 ] in metadata |> Result.map_error (fun (`Msg m) -> `Msg ("In " ^ path ^ ": " ^ m)) - |> Result.map (of_metadata ~source ~body_html ~tags) + |> Result.map (of_metadata ~source ~body_html) let all () = Utils.map_files decode "planet/*/*.md" @@ -94,7 +93,7 @@ let template () = Format.asprintf {| module Source = struct - type t = { id : string option; name : string; url : string } + type t = { id : string option; name : string; url : string; tag : string } end type t = @@ -108,7 +107,6 @@ type t = ; preview_image : string option ; featured : bool ; body_html : string - ;tags : string list; } let all = %a @@ -234,7 +232,8 @@ module Scraper = struct let scrape () = let sources = Source.all () in sources - |> List.map (fun ({ id; url; name } : Source.t) : (string * River.source) -> + |> List.map + (fun ({ id; url; name; _ } : Source.t) : (string * River.source) -> (Option.get id, { name; url })) |> List.filter_map fetch_feed |> List.iter scrape_feed end