Skip to content

Commit

Permalink
Merge pull request #106 from AltGr/blog-redirect
Browse files Browse the repository at this point in the history
Add an html redirect for /blog to get to the latest post
  • Loading branch information
AltGr committed Aug 11, 2014
2 parents dc1ddd7 + 160a26e commit e8f8baf
Show file tree
Hide file tree
Showing 3 changed files with 36 additions and 13 deletions.
44 changes: 31 additions & 13 deletions src/o2wBlog.ml
Expand Up @@ -235,19 +235,19 @@ let make_menu entries =
text = OpamMisc.Option.default entry.blog_title text;
href = "blog/" ^ entry.blog_name ^ "/";
} in
let menu =
List.map2 (fun entry page ->
{ menu_link = link entry;
menu_item = No_menu (2, page) })
entries pages
in
let latest = match entries, pages with
| [], _ | _, [] -> []
| first_entry::_, first_page::_ ->
[{ menu_link = link ~text:"Blog" first_entry;
menu_item = Internal (2, first_page) }]
in
latest, menu
match entries, pages with
| [], _ | _, [] -> [], []
| first_entry::entries, first_page::pages ->
let first =
[{ menu_link = link ~text:"Blog" first_entry;
menu_item = Internal (2, first_page) }] in
let others =
List.map2 (fun entry page ->
{ menu_link = link entry;
menu_item = No_menu (2, page) })
entries pages
in
first, others

let make_news entries =
let oldest = Unix.time() -. 3600.*.24.*.365. in
Expand All @@ -265,6 +265,24 @@ let make_news entries =
in
List.fold_left (fun h e -> <:html< $h$ $mk e$ >>) <:html< >> news

let make_redirect ~root entries =
match entries with
| [] -> <:html< No blog pages >>
| first_entry::_ ->
let blog_uri =
Uri.(resolve "http" root (of_string "blog/"))
in
let post_uri =
Uri.(resolve "http" blog_uri (of_string (first_entry.blog_name^"/")))
in
let redirect = Printf.sprintf "0;url=%s" (Uri.to_string post_uri) in
<:html<
<html><head>
<title>Latest blog entry (redirect)</title>
<meta http-equiv="refresh" content="$str:redirect$" />
</head><body></body></html>
>>

let make_feed ~root entries =
let open Cow.Atom in
let to_atom_date date =
Expand Down
2 changes: 2 additions & 0 deletions src/o2wBlog.mli
Expand Up @@ -36,3 +36,5 @@ val make_news: post list -> Cow.Xml.t
(** Atom feed *)
val make_feed: root:Uri.t -> post list -> Cow.Xml.t

(** Generate an html redirect to the latest post *)
val make_redirect: root:Uri.t -> post list -> Cow.Xml.t
3 changes: 3 additions & 0 deletions src/opam2web.ml
Expand Up @@ -143,6 +143,9 @@ let make_website user_options universe =
OpamFilename.write
(OpamFilename.OP.(OpamFilename.Dir.of_string user_options.out_dir / "blog" // "feed.xml"))
(Cow.Xml.to_string blog_feed);
OpamFilename.write
(OpamFilename.OP.(OpamFilename.Dir.of_string user_options.out_dir / "blog" // "index.html"))
(Cow.Xml.to_string (O2wBlog.make_redirect ~root:user_options.root_uri blog_entries));
match statistics with
| None -> ()
| Some s ->
Expand Down

0 comments on commit e8f8baf

Please sign in to comment.