@@ -149,6 +149,30 @@ let take_code l =
149
149
in
150
150
(c, rest)
151
151
152
+ let rec acc_text (l : Block.t ) : string =
153
+ match l with
154
+ | [] -> " "
155
+ | h :: rest -> (
156
+ match h.desc with Paragraph i -> inline_text i ^ acc_text rest | _ -> " " )
157
+
158
+ and inline_text (i : Inline.t ) =
159
+ match i with
160
+ | [] -> " "
161
+ | h :: rest -> (
162
+ match h.desc with
163
+ | Text s -> s ^ inline_text rest
164
+ | Source s ->
165
+ let rec source_text (s' : Source.t ) =
166
+ match s' with
167
+ | [] -> " "
168
+ | t :: rest_t -> (
169
+ match t with
170
+ | Elt i -> inline_text i ^ source_text rest_t
171
+ | _ -> " " )
172
+ in
173
+ code_span (source_text s)
174
+ | _ -> " " )
175
+
152
176
let rec documented_src (l : DocumentedSrc.t ) args nbsps =
153
177
let nbsps' = nbsps ++ (nbsp ++ nbsp) in
154
178
let noop = paragraph noop in
@@ -176,7 +200,11 @@ let rec documented_src (l : DocumentedSrc.t) args nbsps =
176
200
| _ -> Stop_and_keep )
177
201
in
178
202
let f (content , doc , (anchor : Odoc_document.Url.t option )) =
179
- let doc = match doc with [] -> noop | doc -> block doc args in
203
+ let doc =
204
+ match doc with
205
+ | [] -> noop
206
+ | doc -> paragraph (text (acc_text doc))
207
+ in
180
208
let content =
181
209
match content with
182
210
| `D code (* for record fields and polymorphic variants *) ->
@@ -216,22 +244,18 @@ and item (l : Item.t list) args nbsps =
216
244
| Heading h -> blocks (heading' h args) (continue rest)
217
245
| Declaration { attr = _ ; anchor; content; doc } ->
218
246
let decl = documented_src content args nbsps in
219
- let doc = match doc with [] -> noop | doc -> block doc args in
247
+ let doc =
248
+ match doc with [] -> noop | doc -> paragraph (text (acc_text doc))
249
+ in
220
250
let item' = blocks decl doc in
221
251
if args.generate_links then
222
252
let anchor = match anchor with Some x -> x.anchor | None -> " " in
223
253
blocks (blocks (paragraph (anchor' anchor)) item') (continue rest)
224
254
else blocks item' (continue rest)
225
- | Include
226
- { attr = _; anchor = _; content = { summary; status; content }; doc }
227
- ->
255
+ | Include { content = { summary; status; content } ; _ } ->
228
256
let d =
229
257
if inline_subpage status then item content args nbsps
230
- else
231
- let s = source_code summary args in
232
- match doc with
233
- | [] -> paragraph s
234
- | doc -> blocks (paragraph s) (block doc args)
258
+ else paragraph (source_code summary args)
235
259
in
236
260
blocks d (continue rest))
237
261
0 commit comments