Skip to content

Commit

Permalink
Merge pull request ocaml#3 from tmattio/embed-html
Browse files Browse the repository at this point in the history
Embed HTML files to serve the documentation
  • Loading branch information
tmattio committed Jul 25, 2021
2 parents 744f7bd + 1d2f82d commit f54781e
Show file tree
Hide file tree
Showing 1,806 changed files with 2,361 additions and 2,018 deletions.
7 changes: 0 additions & 7 deletions TODO.md
@@ -1,25 +1,18 @@
# To Do

Blockers:
- [ ] Fix documentation link issues
- [ ] Fix documentation design issues
- [ ] The titles are all the same
- [ ] Fix issue when package doc can't be found (error 500)
- [ ] Fix marshalling error on prod data

Waiting:
- [ ] Retrieve statistics
- [ ] Handle package universes
- [ ] Add rev-deps in the package overview

Nice to have:
- [ ] Cache the documentation
- [ ] Remove dependency on git-unix
- [ ] Add Opam publish documentation

Feedback:
- [ ] Should add the meta descriptions for search engine
- [ ] The heading section for the packages looks.. lifeless
- [ ] Add a search in the docs feature
- [ ] Add an overlow scroll to the TOC in the documentation
- [ ] Mobile view of the documentation looks off
62 changes: 62 additions & 0 deletions asset/doc.css
@@ -0,0 +1,62 @@
div.odoc {
margin-left: auto;
margin-right: auto;
max-width: 37.5rem /* 600px */;
position: relative;
}

div.odoc div.spec {
border-left-width: 4px;
border-color: rgba(251, 146, 60, 1);
border-radius: 0.25rem /* 4px */;
background-color: rgba(243, 244, 246, 1);
padding-left: 1rem /* 16px */;
padding-right: 1rem /* 16px */;
padding-top: 0.5rem /* 16px */;
padding-bottom: 0.5rem /* 16px */;
margin-top: 1rem /* 16px */;
}

div.odoc div.spec code::before,
div.odoc div.spec code::after {
content: "";
}

div.odoc a.anchor {
position: absolute;
left: 0px;
opacity: 0;
text-decoration: none;
margin-left: -1em;
padding-right: 0.5em;
box-shadow: none;
color: rgb(161, 161, 170);
}

div.odoc *:hover > a.anchor {
opacity: 1;
}

div.odoc a.anchor::after {
content: "#";
}

div.odoc div.spec table {
margin-top: 0px;
margin-bottom: 0px;
font-size: 1em;
line-height: 1.75;
}

div.odoc div.spec tbody td {
padding-top: 0px;
padding-bottom: 0px;
}

div.odoc div.spec tbody td.def {
padding-left: 1.25rem /* 20px */;
}

div.odoc div.spec tbody tr {
border-width: 0px;
}
5 changes: 3 additions & 2 deletions dune-project
Expand Up @@ -27,10 +27,11 @@
dream
dream-cli
dream-livereload
odoc
fpath
fmt
opam-format
logs
omd
bos
tyxml
yojson
(alcotest :with-test)))
7 changes: 1 addition & 6 deletions lib/ocamlorg/dune
@@ -1,10 +1,5 @@
(library
(name ocamlorg)
(libraries
opam-format
lwt
lwt.unix
odoc_thtml
odoc.odoc))
(libraries opam-format bos fpath logs fmt lwt lwt.unix yojson))

(include_subdirs unqualified)
File renamed without changes.
File renamed without changes.
84 changes: 66 additions & 18 deletions lib/ocamlorg/package/package.ml → lib/ocamlorg/package.ml
Expand Up @@ -2,7 +2,6 @@ module Name = OpamPackage.Name
module Name_map = Map.Make (Name)
module Version = OpamPackage.Version
module Version_map = Map.Make (Version)
module Opam_repository = Package_opam_repository

module Info = struct
type url =
Expand Down Expand Up @@ -204,25 +203,74 @@ let get_package name version =
Option.bind x (OpamPackage.Version.Map.find_opt version)
|> Option.map (fun info -> { version; info; name })

let documentation t =
try
Package_documentation.load_package
(Name.to_string t.name)
(Version.to_string t.version)
with
| Sys_error _ | Invalid_argument _ ->
Hashtbl.create 0

let readme t =
try
Package_documentation.load_readme
(Name.to_string t.name)
(Version.to_string t.version)
with
| Sys_error _ | Invalid_argument _ ->
module Documentation = struct
type toc =
{ title : string
; href : string
; children : toc list
}

type t =
{ toc : toc list
; content : string
}

let rec toc_of_json = function
| `Assoc
[ ("title", `String title)
; ("href", `String href)
; ("children", `List children)
] ->
{ title; href; children = List.map toc_of_json children }
| _ ->
raise (Invalid_argument "malformed toc file")

let toc_from_file path =
match Yojson.Safe.from_file path with
| `List xs ->
List.map toc_of_json xs
| _ ->
raise (Invalid_argument "the toplevel json is not a list")
end

let package_path name version =
Fpath.(Config.documentation_path / "packages" / name / version)

let documentation_page t path =
let root =
package_path (Name.to_string t.name) (Version.to_string t.version)
|> Fpath.to_string
in
let fpath = Fpath.(v (root ^ "/" ^ path)) in
let path = Fpath.to_string fpath in
if Sys.file_exists path then
let content =
let ic = open_in path in
let s = really_input_string ic (in_channel_length ic) in
close_in ic;
s
in
let toc_path = Fpath.(rem_ext fpath |> add_ext ".toc.json" |> to_string) in
let toc =
if Sys.file_exists toc_path then (
try Documentation.toc_from_file toc_path with
| Invalid_argument err ->
Logs.err (fun m -> m "Invalid toc: %s" err);
[])
else
[]
in
Some Documentation.{ content; toc }
else
None

let documentation_page _t = failwith "TODO"
let readme_file t =
let doc = documentation_page t "README.md.html" in
match doc with None -> None | Some { content; _ } -> Some content

let license_file t =
let doc = documentation_page t "LICENSE.md.html" in
match doc with None -> None | Some { content; _ } -> Some content

let search_package pattern =
let pattern = String.lowercase_ascii pattern in
Expand Down
35 changes: 19 additions & 16 deletions lib/ocamlorg/package/package.mli → lib/ocamlorg/package.mli
Expand Up @@ -49,6 +49,19 @@ module Info : sig
}
end

module Documentation : sig
type toc =
{ title : string
; href : string
; children : toc list
}

type t =
{ toc : toc list
; content : string
}
end

type t

val name : t -> Name.t
Expand All @@ -60,25 +73,15 @@ val version : t -> Version.t
val info : t -> Info.t
(** Get the info of a package. *)

val documentation : t -> (string, string) Hashtbl.t
(** Get the documentation of a package.
The key of the hash table correspond to the URL relative to the root page of
the documentation, and they key is the content of the documentation,
rendered in HTML. *)

val readme : t -> string option
val readme_file : t -> string option
(** Get the readme of a package *)

val documentation_page : t -> string -> string
(** Get the rendered content of an HTML page for a package given its URL
relative to the root page of the documentation.
val license_file : t -> string option
(** Get the license of a package *)

Example:
[documentation_page package "lib/ocaml/compiler-libs/Afl_instrument/"] will
return the HTML corresponding to the file at
["lib/ocaml/compiler-libs/Afl_instrument.odocl"]. *)
val documentation_page : t -> string -> Documentation.t option
(** Get the rendered content of an HTML page for a package given its URL
relative to the root page of the documentation. *)

val all_packages_latest : unit -> t list
(** Get the list of the latest version of every opam packages.
Expand Down
75 changes: 0 additions & 75 deletions lib/ocamlorg/package/package_documentation.ml

This file was deleted.

8 changes: 0 additions & 8 deletions lib/ocamlorg/package/package_documentation.mli

This file was deleted.

0 comments on commit f54781e

Please sign in to comment.