OpenDocument writer: Allow references for internal links (#6774)
This commit adds two extensions to the OpenDocument writer, `xrefs_name` and `xrefs_number`. Links to headings, figures and tables inside the document are substituted with cross-references that will use the name or caption of the referenced item for `xrefs_name` or the number for `xrefs_number`. For the `xrefs_number` to be useful heading numbers must be enabled in the generated document and table and figure captions must be enabled using for example the `native_numbering` extension. In order for numbers and reference text to be updated the generated document must be refreshed. Co-authored-by: Nils Carlson <nils.carlson@ludd.ltu.se>
This commit is contained in:
parent
ddb76cb356
commit
c161893f44
4 changed files with 177 additions and 18 deletions
37
MANUAL.txt
37
MANUAL.txt
|
@ -3027,6 +3027,43 @@ This extension can be enabled/disabled for the following formats:
|
||||||
output formats
|
output formats
|
||||||
: `odt`, `opendocument`
|
: `odt`, `opendocument`
|
||||||
|
|
||||||
|
#### Extension: `xrefs_name` ####
|
||||||
|
|
||||||
|
Links to headings, figures and tables inside the document are
|
||||||
|
substituted with cross-references that will use the name or caption
|
||||||
|
of the referenced item. The original link text is replaced once
|
||||||
|
the generated document is refreshed. This extension can be combined
|
||||||
|
with `xrefs_number` in which case numbers will appear before the
|
||||||
|
name.
|
||||||
|
|
||||||
|
Text in cross-references is only made consistent with the referenced
|
||||||
|
item once the document has been refreshed.
|
||||||
|
|
||||||
|
This extension can be enabled/disabled for the following formats:
|
||||||
|
|
||||||
|
output formats
|
||||||
|
: `odt`, `opendocument`
|
||||||
|
|
||||||
|
#### Extension: `xrefs_number` ####
|
||||||
|
|
||||||
|
Links to headings, figures and tables inside the document are
|
||||||
|
substituted with cross-references that will use the number
|
||||||
|
of the referenced item. The original link text is discarded.
|
||||||
|
This extension can be combined with `xrefs_name` in which case
|
||||||
|
the name or caption numbers will appear after the number.
|
||||||
|
|
||||||
|
For the `xrefs_number` to be useful heading numbers must be enabled
|
||||||
|
in the generated document, also table and figure captions must be enabled
|
||||||
|
using for example the `native_numbering` extension.
|
||||||
|
|
||||||
|
Numbers in cross-references are only visible in the final document once
|
||||||
|
it has been refreshed.
|
||||||
|
|
||||||
|
This extension can be enabled/disabled for the following formats:
|
||||||
|
|
||||||
|
output formats
|
||||||
|
: `odt`, `opendocument`
|
||||||
|
|
||||||
#### Extension: `styles` #### {#ext-styles}
|
#### Extension: `styles` #### {#ext-styles}
|
||||||
|
|
||||||
When converting from docx, read all docx styles as divs (for
|
When converting from docx, read all docx styles as divs (for
|
||||||
|
|
|
@ -149,6 +149,8 @@ data Extension =
|
||||||
| Ext_tex_math_dollars -- ^ TeX math between $..$ or $$..$$
|
| Ext_tex_math_dollars -- ^ TeX math between $..$ or $$..$$
|
||||||
| Ext_tex_math_double_backslash -- ^ TeX math btw \\(..\\) \\[..\\]
|
| Ext_tex_math_double_backslash -- ^ TeX math btw \\(..\\) \\[..\\]
|
||||||
| Ext_tex_math_single_backslash -- ^ TeX math btw \(..\) \[..\]
|
| Ext_tex_math_single_backslash -- ^ TeX math btw \(..\) \[..\]
|
||||||
|
| Ext_xrefs_name -- ^ Use xrefs with names
|
||||||
|
| Ext_xrefs_number -- ^ Use xrefs with numbers
|
||||||
| Ext_yaml_metadata_block -- ^ YAML metadata block
|
| Ext_yaml_metadata_block -- ^ YAML metadata block
|
||||||
| Ext_gutenberg -- ^ Use Project Gutenberg conventions for plain
|
| Ext_gutenberg -- ^ Use Project Gutenberg conventions for plain
|
||||||
| Ext_attributes -- ^ Generic attribute syntax
|
| Ext_attributes -- ^ Generic attribute syntax
|
||||||
|
@ -465,6 +467,8 @@ getAllExtensions f = universalExtensions <> getAll f
|
||||||
getAll "opendocument" = extensionsFromList
|
getAll "opendocument" = extensionsFromList
|
||||||
[ Ext_empty_paragraphs
|
[ Ext_empty_paragraphs
|
||||||
, Ext_native_numbering
|
, Ext_native_numbering
|
||||||
|
, Ext_xrefs_name
|
||||||
|
, Ext_xrefs_number
|
||||||
]
|
]
|
||||||
getAll "odt" = getAll "opendocument" <> autoIdExtensions
|
getAll "odt" = getAll "opendocument" <> autoIdExtensions
|
||||||
getAll "muse" = autoIdExtensions <>
|
getAll "muse" = autoIdExtensions <>
|
||||||
|
|
|
@ -17,6 +17,7 @@ module Text.Pandoc.Writers.OpenDocument ( writeOpenDocument ) where
|
||||||
import Control.Arrow ((***), (>>>))
|
import Control.Arrow ((***), (>>>))
|
||||||
import Control.Monad.State.Strict hiding (when)
|
import Control.Monad.State.Strict hiding (when)
|
||||||
import Data.Char (chr)
|
import Data.Char (chr)
|
||||||
|
import Data.Foldable (find)
|
||||||
import Data.List (sortOn, sortBy, foldl')
|
import Data.List (sortOn, sortBy, foldl')
|
||||||
import qualified Data.Map as Map
|
import qualified Data.Map as Map
|
||||||
import Data.Maybe (fromMaybe, isNothing)
|
import Data.Maybe (fromMaybe, isNothing)
|
||||||
|
@ -35,6 +36,7 @@ import Text.DocLayout
|
||||||
import Text.Pandoc.Shared (linesToPara, tshow, blocksToInlines)
|
import Text.Pandoc.Shared (linesToPara, tshow, blocksToInlines)
|
||||||
import Text.Pandoc.Templates (renderTemplate)
|
import Text.Pandoc.Templates (renderTemplate)
|
||||||
import qualified Text.Pandoc.Translations as Term (Term(Figure, Table))
|
import qualified Text.Pandoc.Translations as Term (Term(Figure, Table))
|
||||||
|
import Text.Pandoc.Walk
|
||||||
import Text.Pandoc.Writers.Math
|
import Text.Pandoc.Writers.Math
|
||||||
import Text.Pandoc.Writers.Shared
|
import Text.Pandoc.Writers.Shared
|
||||||
import qualified Text.Pandoc.Writers.AnnotatedTable as Ann
|
import qualified Text.Pandoc.Writers.AnnotatedTable as Ann
|
||||||
|
@ -54,6 +56,11 @@ plainToPara x = x
|
||||||
|
|
||||||
type OD m = StateT WriterState m
|
type OD m = StateT WriterState m
|
||||||
|
|
||||||
|
data ReferenceType
|
||||||
|
= HeaderRef
|
||||||
|
| TableRef
|
||||||
|
| ImageRef
|
||||||
|
|
||||||
data WriterState =
|
data WriterState =
|
||||||
WriterState { stNotes :: [Doc Text]
|
WriterState { stNotes :: [Doc Text]
|
||||||
, stTableStyles :: [Doc Text]
|
, stTableStyles :: [Doc Text]
|
||||||
|
@ -69,6 +76,7 @@ data WriterState =
|
||||||
, stImageId :: Int
|
, stImageId :: Int
|
||||||
, stTableCaptionId :: Int
|
, stTableCaptionId :: Int
|
||||||
, stImageCaptionId :: Int
|
, stImageCaptionId :: Int
|
||||||
|
, stIdentTypes :: [(Text,ReferenceType)]
|
||||||
}
|
}
|
||||||
|
|
||||||
defaultWriterState :: WriterState
|
defaultWriterState :: WriterState
|
||||||
|
@ -86,6 +94,7 @@ defaultWriterState =
|
||||||
, stImageId = 1
|
, stImageId = 1
|
||||||
, stTableCaptionId = 1
|
, stTableCaptionId = 1
|
||||||
, stImageCaptionId = 1
|
, stImageCaptionId = 1
|
||||||
|
, stIdentTypes = []
|
||||||
}
|
}
|
||||||
|
|
||||||
when :: Bool -> Doc Text -> Doc Text
|
when :: Bool -> Doc Text -> Doc Text
|
||||||
|
@ -243,6 +252,12 @@ writeOpenDocument opts (Pandoc meta blocks) = do
|
||||||
meta
|
meta
|
||||||
((body, metadata),s) <- flip runStateT
|
((body, metadata),s) <- flip runStateT
|
||||||
defaultWriterState $ do
|
defaultWriterState $ do
|
||||||
|
let collectInlineIdent (Image (ident,_,_) _ _) = [(ident,ImageRef)]
|
||||||
|
collectInlineIdent _ = []
|
||||||
|
let collectBlockIdent (Header _ (ident,_,_) _) = [(ident,HeaderRef)]
|
||||||
|
collectBlockIdent (Table (ident,_,_) _ _ _ _ _) = [(ident,TableRef)]
|
||||||
|
collectBlockIdent _ = []
|
||||||
|
modify $ \s -> s{ stIdentTypes = query collectBlockIdent blocks ++ query collectInlineIdent blocks }
|
||||||
m <- metaToContext opts
|
m <- metaToContext opts
|
||||||
(blocksToOpenDocument opts)
|
(blocksToOpenDocument opts)
|
||||||
(fmap chomp . inlinesToOpenDocument opts)
|
(fmap chomp . inlinesToOpenDocument opts)
|
||||||
|
@ -411,7 +426,7 @@ blockToOpenDocument o bs
|
||||||
inTags True "text:list" [ ("text:style-name", "L" <> tshow ln)]
|
inTags True "text:list" [ ("text:style-name", "L" <> tshow ln)]
|
||||||
<$> orderedListToOpenDocument o pn b
|
<$> orderedListToOpenDocument o pn b
|
||||||
table :: PandocMonad m => Ann.Table -> OD m (Doc Text)
|
table :: PandocMonad m => Ann.Table -> OD m (Doc Text)
|
||||||
table (Ann.Table _ (Caption _ c) colspecs thead tbodies _) = do
|
table (Ann.Table (ident, _, _) (Caption _ c) colspecs thead tbodies _) = do
|
||||||
tn <- length <$> gets stTableStyles
|
tn <- length <$> gets stTableStyles
|
||||||
pn <- length <$> gets stParaStyles
|
pn <- length <$> gets stParaStyles
|
||||||
let genIds = map chr [65..]
|
let genIds = map chr [65..]
|
||||||
|
@ -433,7 +448,7 @@ blockToOpenDocument o bs
|
||||||
then return empty
|
then return empty
|
||||||
else inlinesToOpenDocument o (blocksToInlines c) >>=
|
else inlinesToOpenDocument o (blocksToInlines c) >>=
|
||||||
if isEnabled Ext_native_numbering o
|
if isEnabled Ext_native_numbering o
|
||||||
then numberedTableCaption
|
then numberedTableCaption ident
|
||||||
else unNumberedCaption "TableCaption"
|
else unNumberedCaption "TableCaption"
|
||||||
th <- colHeadsToOpenDocument o (map fst paraHStyles) thead
|
th <- colHeadsToOpenDocument o (map fst paraHStyles) thead
|
||||||
tr <- mapM (tableBodyToOpenDocument o (map fst paraStyles)) tbodies
|
tr <- mapM (tableBodyToOpenDocument o (map fst paraStyles)) tbodies
|
||||||
|
@ -442,36 +457,39 @@ blockToOpenDocument o bs
|
||||||
, ("table:style-name", name)
|
, ("table:style-name", name)
|
||||||
] (vcat columns $$ th $$ vcat tr)
|
] (vcat columns $$ th $$ vcat tr)
|
||||||
return $ captionDoc $$ tableDoc
|
return $ captionDoc $$ tableDoc
|
||||||
figure attr caption source title | null caption =
|
figure attr@(ident, _, _) caption source title | null caption =
|
||||||
withParagraphStyle o "Figure" [Para [Image attr caption (source,title)]]
|
withParagraphStyle o "Figure" [Para [Image attr caption (source,title)]]
|
||||||
| otherwise = do
|
| otherwise = do
|
||||||
imageDoc <- withParagraphStyle o "FigureWithCaption" [Para [Image attr caption (source,title)]]
|
imageDoc <- withParagraphStyle o "FigureWithCaption" [Para [Image attr caption (source,title)]]
|
||||||
captionDoc <- inlinesToOpenDocument o caption >>=
|
captionDoc <- inlinesToOpenDocument o caption >>=
|
||||||
if isEnabled Ext_native_numbering o
|
if isEnabled Ext_native_numbering o
|
||||||
then numberedFigureCaption
|
then numberedFigureCaption ident
|
||||||
else unNumberedCaption "FigureCaption"
|
else unNumberedCaption "FigureCaption"
|
||||||
return $ imageDoc $$ captionDoc
|
return $ imageDoc $$ captionDoc
|
||||||
|
|
||||||
|
|
||||||
numberedTableCaption :: PandocMonad m => Doc Text -> OD m (Doc Text)
|
numberedTableCaption :: PandocMonad m => Text -> Doc Text -> OD m (Doc Text)
|
||||||
numberedTableCaption caption = do
|
numberedTableCaption ident caption = do
|
||||||
id' <- gets stTableCaptionId
|
id' <- gets stTableCaptionId
|
||||||
modify (\st -> st{ stTableCaptionId = id' + 1 })
|
modify (\st -> st{ stTableCaptionId = id' + 1 })
|
||||||
capterm <- translateTerm Term.Table
|
capterm <- translateTerm Term.Table
|
||||||
return $ numberedCaption "TableCaption" capterm "Table" id' caption
|
return $ numberedCaption "TableCaption" capterm "Table" id' ident caption
|
||||||
|
|
||||||
numberedFigureCaption :: PandocMonad m => Doc Text -> OD m (Doc Text)
|
numberedFigureCaption :: PandocMonad m => Text -> Doc Text -> OD m (Doc Text)
|
||||||
numberedFigureCaption caption = do
|
numberedFigureCaption ident caption = do
|
||||||
id' <- gets stImageCaptionId
|
id' <- gets stImageCaptionId
|
||||||
modify (\st -> st{ stImageCaptionId = id' + 1 })
|
modify (\st -> st{ stImageCaptionId = id' + 1 })
|
||||||
capterm <- translateTerm Term.Figure
|
capterm <- translateTerm Term.Figure
|
||||||
return $ numberedCaption "FigureCaption" capterm "Illustration" id' caption
|
return $ numberedCaption "FigureCaption" capterm "Illustration" id' ident caption
|
||||||
|
|
||||||
numberedCaption :: Text -> Text -> Text -> Int -> Doc Text -> Doc Text
|
numberedCaption :: Text -> Text -> Text -> Int -> Text -> Doc Text -> Doc Text
|
||||||
numberedCaption style term name num caption =
|
numberedCaption style term name num ident caption =
|
||||||
let t = text $ T.unpack term
|
let t = text $ T.unpack term
|
||||||
r = num - 1
|
r = num - 1
|
||||||
s = inTags False "text:sequence" [ ("text:ref-name", "ref" <> name <> tshow r),
|
ident' = case ident of
|
||||||
|
"" -> "ref" <> name <> tshow r
|
||||||
|
_ -> ident
|
||||||
|
s = inTags False "text:sequence" [ ("text:ref-name", ident'),
|
||||||
("text:name", name),
|
("text:name", name),
|
||||||
("text:formula", "ooow:" <> name <> "+1"),
|
("text:formula", "ooow:" <> name <> "+1"),
|
||||||
("style:num-format", "1") ] $ text $ show num
|
("style:num-format", "1") ] $ text $ show num
|
||||||
|
@ -607,7 +625,9 @@ inlineToOpenDocument o ils
|
||||||
else do
|
else do
|
||||||
report $ InlineNotRendered ils
|
report $ InlineNotRendered ils
|
||||||
return empty
|
return empty
|
||||||
Link _ l (s,t) -> mkLink s t <$> inlinesToOpenDocument o l
|
Link _ l (s,t) -> do
|
||||||
|
identTypes <- gets stIdentTypes
|
||||||
|
mkLink o identTypes s t <$> inlinesToOpenDocument o l
|
||||||
Image attr _ (s,t) -> mkImg attr s t
|
Image attr _ (s,t) -> mkImg attr s t
|
||||||
Note l -> mkNote l
|
Note l -> mkNote l
|
||||||
where
|
where
|
||||||
|
@ -619,10 +639,6 @@ inlineToOpenDocument o ils
|
||||||
unhighlighted s = inlinedCode $ preformatted s
|
unhighlighted s = inlinedCode $ preformatted s
|
||||||
preformatted s = handleSpaces $ escapeStringForXML s
|
preformatted s = handleSpaces $ escapeStringForXML s
|
||||||
inlinedCode s = return $ inTags False "text:span" [("text:style-name", "Source_Text")] s
|
inlinedCode s = return $ inTags False "text:span" [("text:style-name", "Source_Text")] s
|
||||||
mkLink s t = inTags False "text:a" [ ("xlink:type" , "simple")
|
|
||||||
, ("xlink:href" , s )
|
|
||||||
, ("office:name", t )
|
|
||||||
] . inSpanTags "Definition"
|
|
||||||
mkImg (_, _, kvs) s _ = do
|
mkImg (_, _, kvs) s _ = do
|
||||||
id' <- gets stImageId
|
id' <- gets stImageId
|
||||||
modify (\st -> st{ stImageId = id' + 1 })
|
modify (\st -> st{ stImageId = id' + 1 })
|
||||||
|
@ -659,6 +675,45 @@ inlineToOpenDocument o ils
|
||||||
addNote nn
|
addNote nn
|
||||||
return nn
|
return nn
|
||||||
|
|
||||||
|
mkLink :: WriterOptions -> [(Text,ReferenceType)] -> Text -> Text -> Doc Text -> Doc Text
|
||||||
|
mkLink o identTypes s t d =
|
||||||
|
let maybeIdentAndType = case T.uncons s of
|
||||||
|
Just ('#', ident) -> find ((ident ==) . fst) identTypes
|
||||||
|
_ -> Nothing
|
||||||
|
d' = inSpanTags "Definition" d
|
||||||
|
ref refType format ident = inTags False refType
|
||||||
|
[ ("text:reference-format", format ),
|
||||||
|
("text:ref-name", ident) ]
|
||||||
|
inlineSpace = selfClosingTag "text:s" []
|
||||||
|
bookmarkRef = ref "text:bookmark-ref"
|
||||||
|
bookmarkRefNumber ident = bookmarkRef "number" ident mempty
|
||||||
|
bookmarkRefName ident = bookmarkRef "text" ident d
|
||||||
|
bookmarkRefNameNumber ident = bookmarkRefNumber ident <> inlineSpace <> bookmarkRefName ident
|
||||||
|
bookmarkRef'
|
||||||
|
| isEnabled Ext_xrefs_number o && isEnabled Ext_xrefs_name o = bookmarkRefNameNumber
|
||||||
|
| isEnabled Ext_xrefs_name o = bookmarkRefName
|
||||||
|
| otherwise = bookmarkRefNumber
|
||||||
|
sequenceRef = ref "text:sequence-ref"
|
||||||
|
sequenceRefNumber ident = sequenceRef "value" ident mempty
|
||||||
|
sequenceRefName ident = sequenceRef "caption" ident d
|
||||||
|
sequenceRefNameNumber ident = sequenceRefNumber ident <> inlineSpace <> sequenceRefName ident
|
||||||
|
sequenceRef'
|
||||||
|
| isEnabled Ext_xrefs_number o && isEnabled Ext_xrefs_name o = sequenceRefNameNumber
|
||||||
|
| isEnabled Ext_xrefs_name o = sequenceRefName
|
||||||
|
| otherwise = sequenceRefNumber
|
||||||
|
link = inTags False "text:a" [ ("xlink:type" , "simple")
|
||||||
|
, ("xlink:href" , s )
|
||||||
|
, ("office:name", t )
|
||||||
|
] d'
|
||||||
|
linkOrReference = case maybeIdentAndType of
|
||||||
|
Just (ident, HeaderRef) -> bookmarkRef' ident
|
||||||
|
Just (ident, TableRef) -> sequenceRef' ident
|
||||||
|
Just (ident, ImageRef) -> sequenceRef' ident
|
||||||
|
_ -> link
|
||||||
|
in if isEnabled Ext_xrefs_name o || isEnabled Ext_xrefs_number o
|
||||||
|
then linkOrReference
|
||||||
|
else link
|
||||||
|
|
||||||
bulletListStyle :: PandocMonad m => Int -> OD m (Int,(Int,[Doc Text]))
|
bulletListStyle :: PandocMonad m => Int -> OD m (Int,(Int,[Doc Text]))
|
||||||
bulletListStyle l = do
|
bulletListStyle l = do
|
||||||
let doStyles i = inTags True "text:list-level-style-bullet"
|
let doStyles i = inTags True "text:list-level-style-bullet"
|
||||||
|
|
63
test/command/6774.md
Normal file
63
test/command/6774.md
Normal file
|
@ -0,0 +1,63 @@
|
||||||
|
```
|
||||||
|
% pandoc -f native -t opendocument --quiet
|
||||||
|
[Header 1 ("chapter1",[],[]) [Str "The",Space,Str "Chapter"]
|
||||||
|
,Para [Str "Chapter",Space,Str "1",Space,Str "references",Space,Link ("",[],[]) [Str "The",Space,Str "Chapter"] ("#chapter1","")]]
|
||||||
|
^D
|
||||||
|
<text:h text:style-name="Heading_20_1" text:outline-level="1"><text:bookmark-start text:name="chapter1" />The
|
||||||
|
Chapter<text:bookmark-end text:name="chapter1" /></text:h>
|
||||||
|
<text:p text:style-name="First_20_paragraph">Chapter 1 references
|
||||||
|
<text:a xlink:type="simple" xlink:href="#chapter1" office:name=""><text:span text:style-name="Definition">The
|
||||||
|
Chapter</text:span></text:a></text:p>
|
||||||
|
```
|
||||||
|
```
|
||||||
|
% pandoc -f native -t opendocument+xrefs_name --quiet
|
||||||
|
[Header 1 ("chapter1",[],[]) [Str "The",Space,Str "Chapter"]
|
||||||
|
,Para [Str "Chapter",Space,Str "1",Space,Str "references",Space,Link ("",[],[]) [Str "The",Space,Str "Chapter"] ("#chapter1","")]
|
||||||
|
,Para [Image ("lalune",[],[]) [Str "lalune"] ("lalune.jpg","fig:Voyage dans la Lune")]
|
||||||
|
,Para [Str "Image",Space,Str "1",Space,Str "references",Space,Link ("",[],[]) [Str "La",Space,Str "Lune"] ("#lalune","")]]
|
||||||
|
^D
|
||||||
|
<text:h text:style-name="Heading_20_1" text:outline-level="1"><text:bookmark-start text:name="chapter1" />The
|
||||||
|
Chapter<text:bookmark-end text:name="chapter1" /></text:h>
|
||||||
|
<text:p text:style-name="First_20_paragraph">Chapter 1 references
|
||||||
|
<text:bookmark-ref text:reference-format="text" text:ref-name="chapter1">The
|
||||||
|
Chapter</text:bookmark-ref></text:p>
|
||||||
|
<text:p text:style-name="FigureWithCaption"><draw:frame draw:name="img1"><draw:image xlink:href="lalune.jpg" xlink:type="simple" xlink:show="embed" xlink:actuate="onLoad" /></draw:frame></text:p>
|
||||||
|
<text:p text:style-name="FigureCaption">lalune</text:p>
|
||||||
|
<text:p text:style-name="Text_20_body">Image 1 references
|
||||||
|
<text:sequence-ref text:reference-format="caption" text:ref-name="lalune">La
|
||||||
|
Lune</text:sequence-ref></text:p>
|
||||||
|
```
|
||||||
|
```
|
||||||
|
% pandoc -f native -t opendocument+xrefs_number --quiet
|
||||||
|
[Header 1 ("chapter1",[],[]) [Str "The",Space,Str "Chapter"]
|
||||||
|
,Para [Str "Chapter",Space,Str "1",Space,Str "references",Space,Link ("",[],[]) [Str "The",Space,Str "Chapter"] ("#chapter1","")]
|
||||||
|
,Para [Image ("lalune",[],[]) [Str "lalune"] ("lalune.jpg","fig:Voyage dans la Lune")]
|
||||||
|
,Para [Str "Image",Space,Str "1",Space,Str "references",Space,Link ("",[],[]) [Str "La",Space,Str "Lune"] ("#lalune","")]]
|
||||||
|
^D
|
||||||
|
<text:h text:style-name="Heading_20_1" text:outline-level="1"><text:bookmark-start text:name="chapter1" />The
|
||||||
|
Chapter<text:bookmark-end text:name="chapter1" /></text:h>
|
||||||
|
<text:p text:style-name="First_20_paragraph">Chapter 1 references
|
||||||
|
<text:bookmark-ref text:reference-format="number" text:ref-name="chapter1"></text:bookmark-ref></text:p>
|
||||||
|
<text:p text:style-name="FigureWithCaption"><draw:frame draw:name="img1"><draw:image xlink:href="lalune.jpg" xlink:type="simple" xlink:show="embed" xlink:actuate="onLoad" /></draw:frame></text:p>
|
||||||
|
<text:p text:style-name="FigureCaption">lalune</text:p>
|
||||||
|
<text:p text:style-name="Text_20_body">Image 1 references
|
||||||
|
<text:sequence-ref text:reference-format="value" text:ref-name="lalune"></text:sequence-ref></text:p>
|
||||||
|
```
|
||||||
|
```
|
||||||
|
% pandoc -f native -t opendocument+xrefs_number+xrefs_name --quiet
|
||||||
|
[Header 1 ("chapter1",[],[]) [Str "The",Space,Str "Chapter"]
|
||||||
|
,Para [Str "Chapter",Space,Str "1",Space,Str "references",Space,Link ("",[],[]) [Str "The",Space,Str "Chapter"] ("#chapter1","")]
|
||||||
|
,Para [Image ("lalune",[],[]) [Str "lalune"] ("lalune.jpg","fig:Voyage dans la Lune")]
|
||||||
|
,Para [Str "Image",Space,Str "1",Space,Str "references",Space,Link ("",[],[]) [Str "La",Space,Str "Lune"] ("#lalune","")]]
|
||||||
|
^D
|
||||||
|
<text:h text:style-name="Heading_20_1" text:outline-level="1"><text:bookmark-start text:name="chapter1" />The
|
||||||
|
Chapter<text:bookmark-end text:name="chapter1" /></text:h>
|
||||||
|
<text:p text:style-name="First_20_paragraph">Chapter 1 references
|
||||||
|
<text:bookmark-ref text:reference-format="number" text:ref-name="chapter1"></text:bookmark-ref><text:s /><text:bookmark-ref text:reference-format="text" text:ref-name="chapter1">The
|
||||||
|
Chapter</text:bookmark-ref></text:p>
|
||||||
|
<text:p text:style-name="FigureWithCaption"><draw:frame draw:name="img1"><draw:image xlink:href="lalune.jpg" xlink:type="simple" xlink:show="embed" xlink:actuate="onLoad" /></draw:frame></text:p>
|
||||||
|
<text:p text:style-name="FigureCaption">lalune</text:p>
|
||||||
|
<text:p text:style-name="Text_20_body">Image 1 references
|
||||||
|
<text:sequence-ref text:reference-format="value" text:ref-name="lalune"></text:sequence-ref><text:s /><text:sequence-ref text:reference-format="caption" text:ref-name="lalune">La
|
||||||
|
Lune</text:sequence-ref></text:p>
|
||||||
|
```
|
Loading…
Add table
Reference in a new issue