Skip to content

Commit

Permalink
Alternate fix for the URL split issue
Browse files Browse the repository at this point in the history
This fixes an issue where the man page renderer would fail to output
pages that have children. Based on @Julow's pull request #747.

Fixes #765
  • Loading branch information
jonludlam committed Oct 27, 2021
1 parent 4140527 commit a919b8b
Show file tree
Hide file tree
Showing 7 changed files with 45 additions and 21 deletions.
6 changes: 6 additions & 0 deletions CHANGES.md
Original file line number Diff line number Diff line change
@@ -1,3 +1,9 @@
Unreleased
----------

Bugs fixed
- Man page renderer fails to output pages that have children (@jonludlam, @Julow, #766)

2.0.0
-----
Breaking changes
Expand Down
15 changes: 8 additions & 7 deletions src/document/url.ml
Original file line number Diff line number Diff line change
Expand Up @@ -179,17 +179,18 @@ module Path = struct
inner None l

let split :
is_dir:(kind -> bool) ->
is_dir:(kind -> [ `Always | `Never | `IfNotLast ]) ->
(kind * string) list ->
(kind * string) list * (kind * string) list =
fun ~is_dir l ->
let rec inner = function
| ((kind, _) as x) :: xs when is_dir kind ->
let dirs, files = inner xs in
(x :: dirs, files)
| xs -> ([], xs)
let rec inner dirs = function
| [ ((kind, _) as x) ] when is_dir kind = `IfNotLast ->
(List.rev dirs, [ x ])
| ((kind, _) as x) :: xs when is_dir kind <> `Never ->
inner (x :: dirs) xs
| xs -> (List.rev dirs, xs)
in
inner l
inner [] l
end

module Anchor = struct
Expand Down
11 changes: 10 additions & 1 deletion src/document/url.mli
Original file line number Diff line number Diff line change
Expand Up @@ -38,9 +38,18 @@ module Path : sig
val of_list : (kind * string) list -> t option

val split :
is_dir:(kind -> bool) ->
is_dir:(kind -> [ `Always | `Never | `IfNotLast ]) ->
(kind * string) list ->
(kind * string) list * (kind * string) list
(** [split is_dir path] splits the list [path] into a directory
and filename, based on the [is_dir] function. The function
[is_dir] should return whether or not the path element [kind]
should be a directory or not. If the function [is_dir] returns
[`IfNotLast] then the element will be a directory only if it
is not the last element in the path. The return value is a tuple
of directory-type elements and filename-type elements. If the
[is_dir] function can return [`Always], the caller must be prepared
to handle the case where the filename part is empty. *)
end

module Anchor : sig
Expand Down
4 changes: 2 additions & 2 deletions src/html/link.ml
Original file line number Diff line number Diff line change
Expand Up @@ -16,8 +16,8 @@ module Path = struct
let get_dir_and_file url =
let l = Url.Path.to_list url in
let is_dir =
if !flat then function `Page -> true | _ -> false
else function `LeafPage -> false | `File -> false | _ -> true
if !flat then function `Page -> `Always | _ -> `Never
else function `LeafPage -> `Never | `File -> `Never | _ -> `Always
in
let dir, file = Url.Path.split ~is_dir l in
let dir = List.map segment_to_string dir in
Expand Down
13 changes: 3 additions & 10 deletions src/latex/generator.ml
Original file line number Diff line number Diff line change
Expand Up @@ -42,18 +42,11 @@ module Link = struct
let get_dir_and_file url =
let open Odoc_document in
let l = Url.Path.to_list url in
let is_dir = function `Page -> true | _ -> false in
let is_dir = function `Page -> `IfNotLast | _ -> `Never in
let dir, file = Url.Path.split ~is_dir l in
let segment_to_string (_kind, name) = name in
let dir = List.map segment_to_string dir in
match (dir, file) with
| [], [] -> assert false
| dir, [] ->
let rev_dir = List.rev dir in
let file' = List.hd rev_dir in
let dir' = List.tl rev_dir |> List.rev in
(dir', file')
| _, xs -> (dir, String.concat "." (List.map segment_to_string xs))
( List.map segment_to_string dir,
String.concat "." (List.map segment_to_string file) )

let filename url =
let dir, file = get_dir_and_file url in
Expand Down
4 changes: 3 additions & 1 deletion src/manpage/link.ml
Original file line number Diff line number Diff line change
Expand Up @@ -10,7 +10,9 @@ let segment_to_string (kind, name) =
let as_filename (url : Url.Path.t) =
let components = Url.Path.to_list url in
let dir, path =
Url.Path.split ~is_dir:(function `Page -> true | _ -> false) components
Url.Path.split
~is_dir:(function `Page -> `IfNotLast | _ -> `Never)
components
in
let dir = List.map segment_to_string dir in
let path = String.concat "." (List.map segment_to_string path) in
Expand Down
13 changes: 13 additions & 0 deletions test/pages/parents.t/run.t
Original file line number Diff line number Diff line change
Expand Up @@ -34,3 +34,16 @@ file 'package.mld' should be written to the file 'package/index.html'.
$ find html -type f | sort
html/package/Test/index.html
html/package/index.html

Let's make sure the manpage and latex renderers work too
$ for i in *.odocl; do odoc man-generate $i -o man; odoc latex-generate $i -o latex; done
$ find man -type f | sort
man/package.3o
man/package/Test.3o
$ find latex -type f | sort
latex/package.tex
latex/package/Test.tex

0 comments on commit a919b8b

Please sign in to comment.