Skip to content

Commit a919b8b

Browse files
committed
Alternate fix for the URL split issue
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
1 parent 4140527 commit a919b8b

File tree

7 files changed

+45
-21
lines changed

7 files changed

+45
-21
lines changed

CHANGES.md

+6
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,9 @@
1+
Unreleased
2+
----------
3+
4+
Bugs fixed
5+
- Man page renderer fails to output pages that have children (@jonludlam, @Julow, #766)
6+
17
2.0.0
28
-----
39
Breaking changes

src/document/url.ml

+8-7
Original file line numberDiff line numberDiff line change
@@ -179,17 +179,18 @@ module Path = struct
179179
inner None l
180180

181181
let split :
182-
is_dir:(kind -> bool) ->
182+
is_dir:(kind -> [ `Always | `Never | `IfNotLast ]) ->
183183
(kind * string) list ->
184184
(kind * string) list * (kind * string) list =
185185
fun ~is_dir l ->
186-
let rec inner = function
187-
| ((kind, _) as x) :: xs when is_dir kind ->
188-
let dirs, files = inner xs in
189-
(x :: dirs, files)
190-
| xs -> ([], xs)
186+
let rec inner dirs = function
187+
| [ ((kind, _) as x) ] when is_dir kind = `IfNotLast ->
188+
(List.rev dirs, [ x ])
189+
| ((kind, _) as x) :: xs when is_dir kind <> `Never ->
190+
inner (x :: dirs) xs
191+
| xs -> (List.rev dirs, xs)
191192
in
192-
inner l
193+
inner [] l
193194
end
194195

195196
module Anchor = struct

src/document/url.mli

+10-1
Original file line numberDiff line numberDiff line change
@@ -38,9 +38,18 @@ module Path : sig
3838
val of_list : (kind * string) list -> t option
3939

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

4655
module Anchor : sig

src/html/link.ml

+2-2
Original file line numberDiff line numberDiff line change
@@ -16,8 +16,8 @@ module Path = struct
1616
let get_dir_and_file url =
1717
let l = Url.Path.to_list url in
1818
let is_dir =
19-
if !flat then function `Page -> true | _ -> false
20-
else function `LeafPage -> false | `File -> false | _ -> true
19+
if !flat then function `Page -> `Always | _ -> `Never
20+
else function `LeafPage -> `Never | `File -> `Never | _ -> `Always
2121
in
2222
let dir, file = Url.Path.split ~is_dir l in
2323
let dir = List.map segment_to_string dir in

src/latex/generator.ml

+3-10
Original file line numberDiff line numberDiff line change
@@ -42,18 +42,11 @@ module Link = struct
4242
let get_dir_and_file url =
4343
let open Odoc_document in
4444
let l = Url.Path.to_list url in
45-
let is_dir = function `Page -> true | _ -> false in
45+
let is_dir = function `Page -> `IfNotLast | _ -> `Never in
4646
let dir, file = Url.Path.split ~is_dir l in
4747
let segment_to_string (_kind, name) = name in
48-
let dir = List.map segment_to_string dir in
49-
match (dir, file) with
50-
| [], [] -> assert false
51-
| dir, [] ->
52-
let rev_dir = List.rev dir in
53-
let file' = List.hd rev_dir in
54-
let dir' = List.tl rev_dir |> List.rev in
55-
(dir', file')
56-
| _, xs -> (dir, String.concat "." (List.map segment_to_string xs))
48+
( List.map segment_to_string dir,
49+
String.concat "." (List.map segment_to_string file) )
5750

5851
let filename url =
5952
let dir, file = get_dir_and_file url in

src/manpage/link.ml

+3-1
Original file line numberDiff line numberDiff line change
@@ -10,7 +10,9 @@ let segment_to_string (kind, name) =
1010
let as_filename (url : Url.Path.t) =
1111
let components = Url.Path.to_list url in
1212
let dir, path =
13-
Url.Path.split ~is_dir:(function `Page -> true | _ -> false) components
13+
Url.Path.split
14+
~is_dir:(function `Page -> `IfNotLast | _ -> `Never)
15+
components
1416
in
1517
let dir = List.map segment_to_string dir in
1618
let path = String.concat "." (List.map segment_to_string path) in

test/pages/parents.t/run.t

+13
Original file line numberDiff line numberDiff line change
@@ -34,3 +34,16 @@ file 'package.mld' should be written to the file 'package/index.html'.
3434
$ find html -type f | sort
3535
html/package/Test/index.html
3636
html/package/index.html
37+
38+
Let's make sure the manpage and latex renderers work too
39+
40+
$ for i in *.odocl; do odoc man-generate $i -o man; odoc latex-generate $i -o latex; done
41+
42+
$ find man -type f | sort
43+
man/package.3o
44+
man/package/Test.3o
45+
46+
$ find latex -type f | sort
47+
latex/package.tex
48+
latex/package/Test.tex
49+

0 commit comments

Comments
 (0)