Skip to content

Commit

Permalink
Less hardwired redirects
Browse files Browse the repository at this point in the history
  • Loading branch information
Cuihtlauac ALVARADO committed Oct 9, 2024
1 parent f7f82dc commit d6e3690
Show file tree
Hide file tree
Showing 42 changed files with 65 additions and 120 deletions.
1 change: 0 additions & 1 deletion .dockerignore
Original file line number Diff line number Diff line change
Expand Up @@ -10,4 +10,3 @@
!tailwind.config.js
!init-cache
!.git
!v2
2 changes: 1 addition & 1 deletion Dockerfile
Original file line number Diff line number Diff line change
Expand Up @@ -35,7 +35,7 @@ COPY --from=build /home/opam/_build/default/src/ocamlorg_web/bin/main.exe /bin/s
COPY playground/asset playground/asset

RUN git clone https://github.com/ocaml-web/html-compiler-manuals /manual
ADD v2 /v2
ADD data/v2 /v2

RUN git config --global --add safe.directory /var/opam-repository

Expand Down
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
2 changes: 2 additions & 0 deletions src/ocamlorg_data/data.ml
Original file line number Diff line number Diff line change
Expand Up @@ -238,3 +238,5 @@ module Conference = struct
let all = Conference.all
let get_by_slug slug = List.find_opt (fun x -> String.equal slug x.slug) all
end

module V2 = V2
4 changes: 4 additions & 0 deletions src/ocamlorg_data/data.mli
Original file line number Diff line number Diff line change
Expand Up @@ -211,3 +211,7 @@ module Conference : sig
val all : t list
val get_by_slug : string -> t option
end

module V2 : sig
include module type of V2
end
19 changes: 19 additions & 0 deletions src/ocamlorg_data/dune
Original file line number Diff line number Diff line change
Expand Up @@ -340,3 +340,22 @@
(with-stdout-to
%{target}
(run %{ood_gen} conferences)))))

(rule
(target v2.ml)
(deps
(:v2
(source_tree %{workspace_root}/data/v2)))
(action
(chdir
%{workspace_root}/data/v2
(with-stdout-to
%{target}
(progn
(echo "let assets = [")
(pipe-stdout
(run find . -type f)
(run cut -b 2-)
(run sed "s/^/\"/")
(run sed "s/$/\";/"))
(echo "]"))))))
2 changes: 1 addition & 1 deletion src/ocamlorg_web/lib/config.ml
Original file line number Diff line number Diff line change
Expand Up @@ -8,4 +8,4 @@ let http_port = env_with_default "OCAMLORG_HTTP_PORT" "8080" |> int_of_string
let manual_path =
env_with_default "OCAMLORG_MANUAL_PATH" "http-compiler-manuals"

let v2_path = env_with_default "OCAMLORG_V2_PATH" "v2"
let v2_path = env_with_default "OCAMLORG_V2_PATH" "data/v2"
155 changes: 38 additions & 117 deletions src/ocamlorg_web/lib/redirection.ml
Original file line number Diff line number Diff line change
@@ -1,19 +1,28 @@
open Ocamlorg

let rec files path =
if Sys.is_regular_file path then [ path ]
else
Sys.readdir path |> Array.to_list
|> List.concat_map (fun p -> files @@ path ^ "/" ^ p)

let v2_assets =
let f p =
let p = String.concat "/" p in
("meetings/" ^ p, Url.conference p)
let confs =
[ "/conference/"; "/meetings/"; "/meeting/"; "/workshops/"; "/workshop/" ]
in
let redirects confs target source =
let f s = (s ^ source, target) in
List.map f confs
in
let f path =
let open String in
if starts_with ~prefix:"/conferences/" path && ends_with ~suffix:".pdf" path
then redirects confs path (sub path 13 (length path - 13))
else []
in
Config.v2_path |> files
|> List.map (fun s ->
s |> String.split_on_char '/' |> List.tl |> List.tl |> f)
let g conf =
let year = String.sub conf.Data.Conference.date 0 4 in
[ ""; "/index.html" ]
|> List.concat_map (fun s ->
redirects ("/conferences/" :: confs)
("/conferences/" ^ conf.slug)
("ocaml/" ^ year ^ s))
in
List.concat_map f Data.V2.assets @ List.concat_map g Data.Conference.all

let from_v2 =
[
Expand Down Expand Up @@ -207,88 +216,27 @@ let from_v2 =
("/meetings/index.fr.html", Url.conferences);
("/meetings/index.html", Url.conferences);
("/meetings", Url.conferences);
( "/meetings/ocaml/2008/index.html",
Url.conference "ocaml-users-and-developers-conference-2008" );
( "/meetings/ocaml/2008",
Url.conference "ocaml-users-and-developers-conference-2008" );
( "/meetings/ocaml/2008/index.html",
Url.conference "ocaml-users-and-developers-conference-2008" );
( "/meetings/ocaml/2008",
Url.conference "ocaml-users-and-developers-conference-2008" );
( "/meetings/ocaml/2009/index.html",
Url.conference "ocaml-users-and-developers-conference-2009" );
( "/meetings/ocaml/2009",
Url.conference "ocaml-users-and-developers-conference-2009" );
( "/meetings/ocaml/2010/index.html",
Url.conference "ocaml-users-and-developers-conference-2010" );
( "/meetings/ocaml/2010",
Url.conference "ocaml-users-and-developers-conference-2010" );
( "/meetings/ocaml/2011/index.html",
Url.conference "ocaml-users-and-developers-conference-2011" );
( "/meetings/ocaml/2011",
Url.conference "ocaml-users-and-developers-conference-2011" );
( "/meetings/ocaml/2012/index.html",
Url.conference "ocaml-users-and-developers-conference-2012" );
( "/meetings/ocaml/2013/call.html",
Url.conference "ocaml-users-and-developers-conference-2013" );
( "/meetings/ocaml/2013",
Url.conference "ocaml-users-and-developers-conference-2013" );
( "/meetings/ocaml/2013/index.html",
Url.conference "ocaml-users-and-developers-conference-2013" );
( "/meetings/ocaml/2013/program.html",
Url.conference "ocaml-users-and-developers-conference-2013" );
( "/meetings/ocaml/2013",
Url.conference "ocaml-users-and-developers-conference-2013" );
( "/meetings/ocaml/2013/talks/index.html",
Url.conference "ocaml-users-and-developers-conference-2013" );
( "/meetings/ocaml/2014/cfp.html",
Url.conference "ocaml-users-and-developers-conference-2014" );
( "/meetings/ocaml/2014",
Url.conference "ocaml-users-and-developers-conference-2014" );
( "/meetings/ocaml/2014/index.html",
Url.conference "ocaml-users-and-developers-conference-2014" );
( "/meetings/ocaml/2014/ocaml2014_10.html",
Url.conference "ocaml-users-and-developers-conference-2014" );
( "/meetings/ocaml/2014/program.html",
Url.conference "ocaml-users-and-developers-conference-2014" );
( "/meetings/ocaml/2015/cfp.html",
Url.conference "ocaml-users-and-developers-conference-2015" );
( "/meetings/ocaml/2015",
Url.conference "ocaml-users-and-developers-conference-2015" );
( "/meetings/ocaml/2015/index.html",
Url.conference "ocaml-users-and-developers-conference-2015" );
( "/meetings/ocaml/2015",
Url.conference "ocaml-users-and-developers-conference-2015" );
( "/meetings/ocaml/2015/program.html",
Url.conference "ocaml-users-and-developers-conference-2015" );
( "/meetings/ocaml/2015",
Url.conference "ocaml-users-and-developers-conference-2015" );
( "/meetings/ocaml/2015/program.txt",
Url.conference "ocaml-users-and-developers-conference-2015" );
( "/meetings/ocaml/2015",
Url.conference "ocaml-users-and-developers-conference-2015" );
( "/meetings/ocaml/2016/index.html",
Url.conference "ocaml-users-and-developers-conference-2016" );
( "/meetings/ocaml/2016",
Url.conference "ocaml-users-and-developers-conference-2016" );
( "/meetings/ocaml/2017/index.html",
Url.conference "ocaml-users-and-developers-conference-2017" );
( "/meetings/ocaml/2017",
Url.conference "ocaml-users-and-developers-conference-2017" );
( "/meetings/ocaml/2018/index.html",
Url.conference "ocaml-users-and-developers-conference-2018" );
( "/meetings/ocaml/2018",
Url.conference "ocaml-users-and-developers-conference-2018" );
( "/meetings/ocaml/2019/index.html",
Url.conference "ocaml-users-and-developers-conference-2019" );
( "/meetings/ocaml/2019",
Url.conference "ocaml-users-and-developers-conference-2019" );
( "/meetings/ocaml/2020/index.html",
Url.conference "ocaml-users-and-developers-conference-2020" );
( "/meetings/ocaml/2020",
Url.conference "ocaml-users-and-developers-conference-2020" );
("/meetings/ocaml/index.html", Url.conferences);
("/meetings/ocaml", Url.conferences);
("/workshops", Url.conferences);
("/ocamllabs/index.html", Url.index);
("/ocamllabs", Url.index);
("/platform/index.html", Url.learn_platform);
Expand Down Expand Up @@ -316,30 +264,6 @@ let make ?(permanent = false) t =
Some (Dream.get origin (fun req -> Dream.redirect ~status req new_)))
t)

let ocaml_workshops =
List.map
(fun (slug : string) ->
make ~permanent:true [ ("/workshop/" ^ slug, Url.conference slug) ])
[
"ocaml-users-and-developers-conference-2008";
"ocaml-users-and-developers-conference-2009";
"ocaml-users-and-developers-conference-2010";
"ocaml-users-and-developers-conference-2011";
"ocaml-users-and-developers-conference-2012";
"ocaml-users-and-developers-conference-2013";
"ocaml-users-and-developers-conference-2014";
"ocaml-users-and-developers-conference-2015";
"ocaml-users-and-developers-conference-2016";
"ocaml-users-and-developers-conference-2017";
"ocaml-users-and-developers-conference-2018";
"ocaml-users-and-developers-conference-2019";
"ocaml-users-and-developers-conference-2020";
"ocaml-users-and-developers-conference-2020";
"ocaml-users-and-developers-conference-2021";
"ocaml-users-and-developers-conference-2022";
"ocaml-users-and-developers-conference-2023";
]

let package req =
let package = Dream.param req "name" in
Dream.redirect req (Url.Package.overview package)
Expand All @@ -350,22 +274,19 @@ let package_docs req =

let t =
Dream.scope "" []
([
make ~permanent:true [ ("feed.xml", "planet.xml") ];
make from_v2;
make ~permanent:true v2_assets;
make [ ("/blog", "/ocaml-planet") ];
make ~permanent:true [ ("/opportunities", "/jobs") ];
make ~permanent:true
[ ("/carbon-footprint", "/policies/carbon-footprint") ];
make ~permanent:true [ ("/privacy-policy", "/policies/privacy-policy") ];
make ~permanent:true
[ ("/code-of-conduct", "/policies/code-of-conduct") ];
make ~permanent:true [ ("/opportunities", "/jobs") ];
(* make ~permanent:false [ (Url.conferences, Url.community ^
"#conferences") ]; *)
Dream.get "/p/:name" package;
Dream.get "/u/:hash/p/:name" package;
Dream.get "/p/:name/doc" package_docs;
]
@ ocaml_workshops)
[
make ~permanent:true [ ("feed.xml", "planet.xml") ];
make ~permanent:true from_v2;
make ~permanent:true v2_assets;
make ~permanent:true [ ("/blog", "/ocaml-planet") ];
make ~permanent:true [ ("/opportunities", "/jobs") ];
make ~permanent:true
[ ("/carbon-footprint", "/policies/carbon-footprint") ];
make ~permanent:true [ ("/privacy-policy", "/policies/privacy-policy") ];
make ~permanent:true [ ("/code-of-conduct", "/policies/code-of-conduct") ];
(* make ~permanent:false [ (Url.conferences, Url.community ^
"#conferences") ]; *)
Dream.get "/p/:name" package;
Dream.get "/u/:hash/p/:name" package;
Dream.get "/p/:name/doc" package_docs;
]

0 comments on commit d6e3690

Please sign in to comment.