aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--src/Text/Pandoc/Writers/ICML.hs154
-rw-r--r--test/command/5541-localLink.md149
-rw-r--r--test/command/5541-nesting.md97
-rw-r--r--test/command/5541-urlLink.md112
-rw-r--r--test/writer.icml34
5 files changed, 487 insertions, 59 deletions
diff --git a/src/Text/Pandoc/Writers/ICML.hs b/src/Text/Pandoc/Writers/ICML.hs
index 45970ad94..dbfbfff5b 100644
--- a/src/Text/Pandoc/Writers/ICML.hs
+++ b/src/Text/Pandoc/Writers/ICML.hs
@@ -136,10 +136,11 @@ writeICML opts (Pandoc meta blocks) = do
let colwidth = if writerWrapText opts == WrapAuto
then Just $ writerColumns opts
else Nothing
- renderMeta f s = fst <$> runStateT (f opts [] s) defaultWriterState
+ renderBlockMeta f s = fst <$> runStateT (f opts [] s) defaultWriterState
+ renderInlineMeta f s = fst <$> runStateT (f opts [] "" s) defaultWriterState
metadata <- metaToContext opts
- (renderMeta blocksToICML)
- (renderMeta inlinesToICML)
+ (renderBlockMeta blocksToICML)
+ (renderInlineMeta inlinesToICML)
meta
(main, st) <- runStateT (blocksToICML opts [] blocks) defaultWriterState
let context = defField "body" main
@@ -266,9 +267,17 @@ charStylesToDoc st = vcat $ map makeStyle $ Set.toAscList $ inlineStyles st
-- | Escape colon characters as %3a
escapeColons :: Text -> Text
-escapeColons = Text.concatMap $ \x -> case x of
- ':' -> "%3a"
- _ -> Text.singleton x
+escapeColons txt = Text.replace ":" "%3a" txt
+
+-- | figure out the link destination for a given URL
+-- | HyperlinkURLDestination with more than one colon crashes CS6
+makeDest :: Text -> Doc Text
+makeDest txt = literal $
+ if "#" `Text.isPrefixOf` txt
+ then "HyperlinkTextDestination/" <> escTxt
+ else "HyperlinkURLDestination/" <> escTxt
+ where
+ escTxt = escapeColons $ escapeStringForXML txt
-- | Convert a list of (identifier, url) pairs to the ICML listing of hyperlinks.
hyperlinksToDoc :: Hyperlink -> Doc Text
@@ -277,13 +286,15 @@ hyperlinksToDoc (x:xs) = hyp x $$ hyperlinksToDoc xs
where
hyp (ident, url) = hdest $$ hlink
where
- hdest = selfClosingTag "HyperlinkURLDestination"
+ hdest = if "#" `Text.isPrefixOf` url
+ then empty
+ else selfClosingTag "HyperlinkURLDestination"
[("Self", "HyperlinkURLDestination/"<>escapeColons url), ("Name","link"), ("DestinationURL",url), ("DestinationUniqueKey","1")] -- HyperlinkURLDestination with more than one colon crashes CS6
hlink = inTags True "Hyperlink" [("Self","uf-"<>tshow ident), ("Name",url),
("Source","htss-"<>tshow ident), ("Visible","true"), ("DestinationUniqueKey","1")]
$ inTags True "Properties" []
$ inTags False "BorderColor" [("type","enumeration")] (text "Black")
- $$ inTags False "Destination" [("type","object")] (literal $ "HyperlinkURLDestination/"<>escapeColons (escapeStringForXML url)) -- HyperlinkURLDestination with more than one colon crashes CS6
+ $$ inTags False "Destination" [("type","object")] (makeDest url)
-- | Key for specifying user-defined styles
dynamicStyleKey :: Text
@@ -297,16 +308,16 @@ blocksToICML opts style lst = do
-- | Convert a Pandoc block element to ICML.
blockToICML :: PandocMonad m => WriterOptions -> Style -> Block -> WS m (Doc Text)
-blockToICML opts style (Plain lst) = parStyle opts style lst
+blockToICML opts style (Plain lst) = parStyle opts style "" lst
-- title beginning with fig: indicates that the image is a figure
blockToICML opts style (Para img@[Image _ txt (_,Text.stripPrefix "fig:" -> Just _)]) = do
- figure <- parStyle opts (figureName:style) img
- caption <- parStyle opts (imgCaptionName:style) txt
+ figure <- parStyle opts (figureName:style) "" img
+ caption <- parStyle opts (imgCaptionName:style) "" txt
return $ intersperseBrs [figure, caption]
-blockToICML opts style (Para lst) = parStyle opts (paragraphName:style) lst
+blockToICML opts style (Para lst) = parStyle opts (paragraphName:style) "" lst
blockToICML opts style (LineBlock lns) =
blockToICML opts style $ linesToPara lns
-blockToICML opts style (CodeBlock _ str) = parStyle opts (codeBlockName:style) [Str str]
+blockToICML opts style (CodeBlock _ str) = parStyle opts (codeBlockName:style) "" [Str str]
blockToICML _ _ b@(RawBlock f str)
| f == Format "icml" = return $ literal str
| otherwise = do
@@ -316,12 +327,12 @@ blockToICML opts style (BlockQuote blocks) = blocksToICML opts (blockQuoteName:s
blockToICML opts style (OrderedList attribs lst) = listItemsToICML opts orderedListName style (Just attribs) lst
blockToICML opts style (BulletList lst) = listItemsToICML opts bulletListName style Nothing lst
blockToICML opts style (DefinitionList lst) = intersperseBrs `fmap` mapM (definitionListItemToICML opts style) lst
-blockToICML opts style (Header lvl (_, cls, _) lst) =
+blockToICML opts style (Header lvl (ident, cls, _) lst) =
let stl = (headerName <> tshow lvl <> unnumbered):style
unnumbered = if "unnumbered" `elem` cls
then " (unnumbered)"
else ""
- in parStyle opts stl lst
+ in parStyle opts stl ident lst
blockToICML _ _ HorizontalRule = return empty -- we could insert a page break instead
blockToICML opts style (Table _ blkCapt specs thead tbody tfoot) =
let (caption, aligns, widths, headers, rows) = toLegacyTable blkCapt specs thead tbody tfoot
@@ -366,8 +377,8 @@ blockToICML opts style (Table _ blkCapt specs thead tbody tfoot) =
, ("BodyRowCount", tshow nrRows)
, ("ColumnCount", tshow nrCols)
] (colDescs $$ cells)
- liftM2 ($$) tableDoc $ parStyle opts (tableCaptionName:style) caption
-blockToICML opts style (Div (_, _, kvs) lst) =
+ liftM2 ($$) tableDoc $ parStyle opts (tableCaptionName:style) "" caption
+blockToICML opts style (Div (_ident, _, kvs) lst) =
let dynamicStyle = maybeToList $ lookup dynamicStyleKey kvs
in blocksToICML opts (dynamicStyle <> style) lst
blockToICML _ _ Null = return empty
@@ -416,61 +427,65 @@ listItemToICML opts style isFirst attribs item =
definitionListItemToICML :: PandocMonad m => WriterOptions -> Style -> ([Inline],[[Block]]) -> WS m (Doc Text)
definitionListItemToICML opts style (term,defs) = do
- term' <- parStyle opts (defListTermName:style) term
+ term' <- parStyle opts (defListTermName:style) "" term
defs' <- mapM (blocksToICML opts (defListDefName:style)) defs
return $ intersperseBrs (term' : defs')
-- | Convert a list of inline elements to ICML.
-inlinesToICML :: PandocMonad m => WriterOptions -> Style -> [Inline] -> WS m (Doc Text)
-inlinesToICML opts style lst = vcat `fmap` mapM (inlineToICML opts style) (mergeStrings opts lst)
+inlinesToICML :: PandocMonad m => WriterOptions -> Style -> Text -> [Inline] -> WS m (Doc Text)
+inlinesToICML opts style ident lst = vcat `fmap` mapM (inlineToICML opts style ident) (mergeStrings opts lst)
-- | Convert an inline element to ICML.
-inlineToICML :: PandocMonad m => WriterOptions -> Style -> Inline -> WS m (Doc Text)
-inlineToICML _ style (Str str) = charStyle style $ literal $ escapeStringForXML str
-inlineToICML opts style (Emph lst) = inlinesToICML opts (emphName:style) lst
-inlineToICML opts style (Underline lst) = inlinesToICML opts (underlineName:style) lst
-inlineToICML opts style (Strong lst) = inlinesToICML opts (strongName:style) lst
-inlineToICML opts style (Strikeout lst) = inlinesToICML opts (strikeoutName:style) lst
-inlineToICML opts style (Superscript lst) = inlinesToICML opts (superscriptName:style) lst
-inlineToICML opts style (Subscript lst) = inlinesToICML opts (subscriptName:style) lst
-inlineToICML opts style (SmallCaps lst) = inlinesToICML opts (smallCapsName:style) lst
-inlineToICML opts style (Quoted SingleQuote lst) = inlinesToICML opts style $
+inlineToICML :: PandocMonad m => WriterOptions -> Style -> Text -> Inline -> WS m (Doc Text)
+inlineToICML _ style ident (Str str) = charStyle style ident $ literal $ escapeStringForXML str
+inlineToICML opts style ident (Emph lst) = inlinesToICML opts (emphName:style) ident lst
+inlineToICML opts style ident (Underline lst) = inlinesToICML opts (underlineName:style) ident lst
+inlineToICML opts style ident (Strong lst) = inlinesToICML opts (strongName:style) ident lst
+inlineToICML opts style ident (Strikeout lst) = inlinesToICML opts (strikeoutName:style) ident lst
+inlineToICML opts style ident (Superscript lst) = inlinesToICML opts (superscriptName:style) ident lst
+inlineToICML opts style ident (Subscript lst) = inlinesToICML opts (subscriptName:style) ident lst
+inlineToICML opts style ident (SmallCaps lst) = inlinesToICML opts (smallCapsName:style) ident lst
+inlineToICML opts style ident (Quoted SingleQuote lst) = inlinesToICML opts style ident $
mergeStrings opts $ [Str "‘"] ++ lst ++ [Str "’"]
-inlineToICML opts style (Quoted DoubleQuote lst) = inlinesToICML opts style $
+inlineToICML opts style ident (Quoted DoubleQuote lst) = inlinesToICML opts style ident $
mergeStrings opts $ [Str "“"] ++ lst ++ [Str "”"]
-inlineToICML opts style (Cite _ lst) = inlinesToICML opts (citeName:style) lst
-inlineToICML _ style (Code _ str) = charStyle (codeName:style) $ literal $ escapeStringForXML str
-inlineToICML _ style Space = charStyle style space
-inlineToICML opts style SoftBreak =
+inlineToICML opts style ident (Cite _ lst) = inlinesToICML opts (citeName:style) ident lst
+inlineToICML _ style ident (Code _ str) = charStyle (codeName:style) ident $ literal $ escapeStringForXML str
+inlineToICML _ style ident Space = charStyle style ident space
+inlineToICML opts style ident SoftBreak =
case writerWrapText opts of
- WrapAuto -> charStyle style space
- WrapNone -> charStyle style space
- WrapPreserve -> charStyle style cr
-inlineToICML _ style LineBreak = charStyle style $ literal lineSeparator
-inlineToICML opts style (Math mt str) =
+ WrapAuto -> charStyle style ident space
+ WrapNone -> charStyle style ident space
+ WrapPreserve -> charStyle style ident cr
+inlineToICML _ style ident LineBreak = charStyle style ident $ literal lineSeparator
+inlineToICML opts style ident (Math mt str) =
lift (texMathToInlines mt str) >>=
- (fmap mconcat . mapM (inlineToICML opts style))
-inlineToICML _ _ il@(RawInline f str)
+ (fmap mconcat . mapM (inlineToICML opts style ident))
+inlineToICML _ _ _ il@(RawInline f str)
| f == Format "icml" = return $ literal str
| otherwise = do
report $ InlineNotRendered il
return empty
-inlineToICML opts style (Link _ lst (url, title)) = do
- content <- inlinesToICML opts (linkName:style) lst
+inlineToICML opts style ident (Link _ lst (url, title)) = do
+ content <- inlinesToICML opts (linkName:style) ident lst
state $ \st ->
- let ident = if null $ links st
- then 1::Int
- else 1 + fst (head $ links st)
- newst = st{ links = (ident, url):links st }
+ let link_id = if null $ links st
+ then 1::Int
+ else 1 + fst (head $ links st)
+ newst = st{ links = (link_id, url):links st }
cont = inTags True "HyperlinkTextSource"
- [("Self","htss-"<>tshow ident), ("Name",title), ("Hidden","false")] content
+ [("Self","htss-"<>tshow link_id), ("Name",title), ("Hidden","false")] content
in (cont, newst)
-inlineToICML opts style (Image attr _ target) = imageICML opts style attr target
-inlineToICML opts style (Note lst) = footnoteToICML opts style lst
-inlineToICML opts style (Span (_, _, kvs) lst) =
+inlineToICML opts style _ident (Image attr _ target) = imageICML opts style attr target
+inlineToICML opts style _ (Note lst) = footnoteToICML opts style lst
+inlineToICML opts style _ (Span (ident, _, kvs) lst) =
let dynamicStyle = maybeToList $ lookup dynamicStyleKey kvs
- in inlinesToICML opts (dynamicStyle <> style) lst
+ in inlinesToICML opts (dynamicStyle <> style) ident lst
+-- ident will be the id of the span, that we need to use down in the hyperlink setter
+-- if T.null ident
+-- then
+-- else do
-- | Convert a list of block elements to an ICML footnote.
footnoteToICML :: PandocMonad m => WriterOptions -> Style -> [Block] -> WS m (Doc Text)
@@ -503,8 +518,8 @@ intersperseBrs :: [Doc Text] -> Doc Text
intersperseBrs = vcat . intersperse (selfClosingTag "Br" []) . filter (not . isEmpty)
-- | Wrap a list of inline elements in an ICML Paragraph Style
-parStyle :: PandocMonad m => WriterOptions -> Style -> [Inline] -> WS m (Doc Text)
-parStyle opts style lst =
+parStyle :: PandocMonad m => WriterOptions -> Style -> Text -> [Inline] -> WS m (Doc Text)
+parStyle opts style ident lst =
let slipIn x y = if Text.null y
then x
else x <> " > " <> y
@@ -523,15 +538,36 @@ parStyle opts style lst =
in ("NumberingStartAt", i) : ats
else [attrs]
in do
- content <- inlinesToICML opts [] lst
+ content <- inlinesToICML opts [] ident lst
let cont = inTags True "ParagraphStyleRange" attrs' content
state $ \st -> (cont, st{ blockStyles = Set.insert stlStr $ blockStyles st })
+-- | Create the destination name
+makeDestName :: Text -> Text
+makeDestName name = "#" <> Text.replace " " "-" name
+
+-- | Create a HyperlinkTextDestination for a given identifier
+makeLinkDest :: Text -> Doc Text -> Doc Text
+makeLinkDest ident cont = vcat [
+ selfClosingTag "HyperlinkTextDestination"
+ [("Self", "HyperlinkTextDestination/"<>makeDestName ident), ("Name","Destination"), ("DestinationUniqueKey","1")]
+ , inTagsSimple "Content" $ flush cont
+ ]
+
+-- | Create the markup for the content (incl. named destinations)
+-- | NOTE: since we have no easy way to get actual named dests, we just create them for any short content blocks
+makeContent :: Text -> Doc Text -> Doc Text
+makeContent ident cont
+ | isEmpty cont = empty
+ | not (Text.null ident) = makeLinkDest ident cont
+ | otherwise = inTagsSimple "Content" $ flush cont
+
-- | Wrap a Doc in an ICML Character Style.
-charStyle :: PandocMonad m => Style -> Doc Text -> WS m (Doc Text)
-charStyle style content =
+charStyle :: PandocMonad m => Style -> Text -> Doc Text -> WS m (Doc Text)
+charStyle style ident content =
let (stlStr, attrs) = styleToStrAttr style
- doc = inTags True "CharacterStyleRange" attrs $ inTagsSimple "Content" $ flush content
+ doc = inTags True "CharacterStyleRange" attrs
+ $ makeContent ident content
in
state $ \st ->
let styles = if Text.null stlStr
diff --git a/test/command/5541-localLink.md b/test/command/5541-localLink.md
new file mode 100644
index 000000000..924607b3b
--- /dev/null
+++ b/test/command/5541-localLink.md
@@ -0,0 +1,149 @@
+```
+% pandoc -f markdown -t icml -s
+
+# Header 1
+
+this is some text
+
+## Header 2
+
+some more text that [links to](#header-1) the first header. And this links to [some text](#spanner) in 2.1.
+
+## Header 2.1
+
+if you can read this text, [and it's linked]{#spanner} - all good!
+
+^D
+<?xml version="1.0" encoding="UTF-8" standalone="yes"?>
+<?aid style="50" type="snippet" readerVersion="6.0" featureSet="513" product="8.0(370)" ?>
+<?aid SnippetType="InCopyInterchange"?>
+<Document DOMVersion="8.0" Self="pandoc_doc">
+ <RootCharacterStyleGroup Self="pandoc_character_styles">
+ <CharacterStyle Self="$ID/NormalCharacterStyle" Name="Default" />
+ <CharacterStyle Self="CharacterStyle/Link" Name="Link">
+ <Properties>
+ <BasedOn type="object">$ID/NormalCharacterStyle</BasedOn>
+ </Properties>
+ </CharacterStyle>
+ </RootCharacterStyleGroup>
+ <RootParagraphStyleGroup Self="pandoc_paragraph_styles">
+ <ParagraphStyle Self="$ID/NormalParagraphStyle" Name="$ID/NormalParagraphStyle"
+ SpaceBefore="6" SpaceAfter="6"> <!-- paragraph spacing -->
+ <Properties>
+ <TabList type="list">
+ <ListItem type="record">
+ <Alignment type="enumeration">LeftAlign</Alignment>
+ <AlignmentCharacter type="string">.</AlignmentCharacter>
+ <Leader type="string"></Leader>
+ <Position type="unit">10</Position> <!-- first tab stop -->
+ </ListItem>
+ </TabList>
+ </Properties>
+ </ParagraphStyle>
+ <ParagraphStyle Self="ParagraphStyle/Header1" Name="Header1" LeftIndent="0" PointSize="36">
+ <Properties>
+ <BasedOn type="object">$ID/NormalParagraphStyle</BasedOn>
+ </Properties>
+ </ParagraphStyle>
+ <ParagraphStyle Self="ParagraphStyle/Header2" Name="Header2" LeftIndent="0" PointSize="30">
+ <Properties>
+ <BasedOn type="object">$ID/NormalParagraphStyle</BasedOn>
+ </Properties>
+ </ParagraphStyle>
+ <ParagraphStyle Self="ParagraphStyle/Paragraph" Name="Paragraph" LeftIndent="0">
+ <Properties>
+ <BasedOn type="object">$ID/NormalParagraphStyle</BasedOn>
+ </Properties>
+ </ParagraphStyle>
+ </RootParagraphStyleGroup>
+ <RootTableStyleGroup Self="pandoc_table_styles">
+ <TableStyle Self="TableStyle/Table" Name="Table" />
+ </RootTableStyleGroup>
+ <RootCellStyleGroup Self="pandoc_cell_styles">
+ <CellStyle Self="CellStyle/Cell" AppliedParagraphStyle="ParagraphStyle/$ID/[No paragraph style]" Name="Cell" />
+ </RootCellStyleGroup>
+ <Story Self="pandoc_story"
+ TrackChanges="false"
+ StoryTitle=""
+ AppliedTOCStyle="n"
+ AppliedNamedGrid="n" >
+ <StoryPreference OpticalMarginAlignment="true" OpticalMarginSize="12" />
+
+<!-- body needs to be non-indented, otherwise code blocks are indented too far -->
+<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Header1">
+ <CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
+ <HyperlinkTextDestination Self="HyperlinkTextDestination/#header-1" Name="Destination" DestinationUniqueKey="1" />
+ <Content>Header 1</Content>
+ </CharacterStyleRange>
+</ParagraphStyleRange>
+<Br />
+<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Paragraph">
+ <CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
+ <Content>this is some text</Content>
+ </CharacterStyleRange>
+</ParagraphStyleRange>
+<Br />
+<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Header2">
+ <CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
+ <HyperlinkTextDestination Self="HyperlinkTextDestination/#header-2" Name="Destination" DestinationUniqueKey="1" />
+ <Content>Header 2</Content>
+ </CharacterStyleRange>
+</ParagraphStyleRange>
+<Br />
+<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Paragraph">
+ <CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
+ <Content>some more text that </Content>
+ </CharacterStyleRange>
+ <HyperlinkTextSource Self="htss-1" Name="" Hidden="false">
+ <CharacterStyleRange AppliedCharacterStyle="CharacterStyle/Link">
+ <Content>links to</Content>
+ </CharacterStyleRange>
+ </HyperlinkTextSource>
+ <CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
+ <Content> the first header. And this links to </Content>
+ </CharacterStyleRange>
+ <HyperlinkTextSource Self="htss-2" Name="" Hidden="false">
+ <CharacterStyleRange AppliedCharacterStyle="CharacterStyle/Link">
+ <Content>some text</Content>
+ </CharacterStyleRange>
+ </HyperlinkTextSource>
+ <CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
+ <Content> in 2.1.</Content>
+ </CharacterStyleRange>
+</ParagraphStyleRange>
+<Br />
+<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Header2">
+ <CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
+ <HyperlinkTextDestination Self="HyperlinkTextDestination/#header-2.1" Name="Destination" DestinationUniqueKey="1" />
+ <Content>Header 2.1</Content>
+ </CharacterStyleRange>
+</ParagraphStyleRange>
+<Br />
+<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Paragraph">
+ <CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
+ <Content>if you can read this text, </Content>
+ </CharacterStyleRange>
+ <CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
+ <HyperlinkTextDestination Self="HyperlinkTextDestination/#spanner" Name="Destination" DestinationUniqueKey="1" />
+ <Content>and it’s linked</Content>
+ </CharacterStyleRange>
+ <CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
+ <Content> - all good!</Content>
+ </CharacterStyleRange>
+</ParagraphStyleRange>
+
+ </Story>
+ <Hyperlink Self="uf-2" Name="#spanner" Source="htss-2" Visible="true" DestinationUniqueKey="1">
+ <Properties>
+ <BorderColor type="enumeration">Black</BorderColor>
+ <Destination type="object">HyperlinkTextDestination/#spanner</Destination>
+ </Properties>
+ </Hyperlink>
+ <Hyperlink Self="uf-1" Name="#header-1" Source="htss-1" Visible="true" DestinationUniqueKey="1">
+ <Properties>
+ <BorderColor type="enumeration">Black</BorderColor>
+ <Destination type="object">HyperlinkTextDestination/#header-1</Destination>
+ </Properties>
+ </Hyperlink>
+</Document>
+``` \ No newline at end of file
diff --git a/test/command/5541-nesting.md b/test/command/5541-nesting.md
new file mode 100644
index 000000000..616184f5c
--- /dev/null
+++ b/test/command/5541-nesting.md
@@ -0,0 +1,97 @@
+```
+% pandoc -f html -t icml -s
+
+<div id="blockId">
+ <div id="blockId2">
+ <span id="inlineId">
+ <img id="inlineId2" src="lalune.jpg" />
+ </span>
+ </div>
+</div>
+
+^D
+<?xml version="1.0" encoding="UTF-8" standalone="yes"?>
+<?aid style="50" type="snippet" readerVersion="6.0" featureSet="513" product="8.0(370)" ?>
+<?aid SnippetType="InCopyInterchange"?>
+<Document DOMVersion="8.0" Self="pandoc_doc">
+ <RootCharacterStyleGroup Self="pandoc_character_styles">
+ <CharacterStyle Self="$ID/NormalCharacterStyle" Name="Default" />
+ <CharacterStyle Self="CharacterStyle/" Name="">
+ <Properties>
+ <BasedOn type="object">$ID/NormalCharacterStyle</BasedOn>
+ </Properties>
+ </CharacterStyle>
+ </RootCharacterStyleGroup>
+ <RootParagraphStyleGroup Self="pandoc_paragraph_styles">
+ <ParagraphStyle Self="$ID/NormalParagraphStyle" Name="$ID/NormalParagraphStyle"
+ SpaceBefore="6" SpaceAfter="6"> <!-- paragraph spacing -->
+ <Properties>
+ <TabList type="list">
+ <ListItem type="record">
+ <Alignment type="enumeration">LeftAlign</Alignment>
+ <AlignmentCharacter type="string">.</AlignmentCharacter>
+ <Leader type="string"></Leader>
+ <Position type="unit">10</Position> <!-- first tab stop -->
+ </ListItem>
+ </TabList>
+ </Properties>
+ </ParagraphStyle>
+ <ParagraphStyle Self="ParagraphStyle/" Name="" LeftIndent="0">
+ <Properties>
+ <BasedOn type="object">$ID/NormalParagraphStyle</BasedOn>
+ </Properties>
+ </ParagraphStyle>
+ </RootParagraphStyleGroup>
+ <RootTableStyleGroup Self="pandoc_table_styles">
+ <TableStyle Self="TableStyle/Table" Name="Table" />
+ </RootTableStyleGroup>
+ <RootCellStyleGroup Self="pandoc_cell_styles">
+ <CellStyle Self="CellStyle/Cell" AppliedParagraphStyle="ParagraphStyle/$ID/[No paragraph style]" Name="Cell" />
+ </RootCellStyleGroup>
+ <Story Self="pandoc_story"
+ TrackChanges="false"
+ StoryTitle=""
+ AppliedTOCStyle="n"
+ AppliedNamedGrid="n" >
+ <StoryPreference OpticalMarginAlignment="true" OpticalMarginSize="12" />
+
+<!-- body needs to be non-indented, otherwise code blocks are indented too far -->
+<ParagraphStyleRange AppliedParagraphStyle="">
+ <CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
+ <HyperlinkTextDestination Self="HyperlinkTextDestination/#inlineId" Name="Destination" DestinationUniqueKey="1" />
+ <Content> </Content>
+ </CharacterStyleRange>
+ <CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
+ <Rectangle Self="uec" StrokeWeight="0" ItemTransform="1 0 0 1 75 -75">
+ <Properties>
+ <PathGeometry>
+ <GeometryPathType PathOpen="false">
+ <PathPointArray>
+ <PathPointType Anchor="-75 -75" LeftDirection="-75 -75" RightDirection="-75 -75" />
+ <PathPointType Anchor="-75 75" LeftDirection="-75 75" RightDirection="-75 75" />
+ <PathPointType Anchor="75 75" LeftDirection="75 75" RightDirection="75 75" />
+ <PathPointType Anchor="75 -75" LeftDirection="75 -75" RightDirection="75 -75" />
+ </PathPointArray>
+ </GeometryPathType>
+ </PathGeometry>
+ </Properties>
+ <Image Self="ue6" ItemTransform="1 0 0 1 -75 -75">
+ <Properties>
+ <Profile type="string">
+ $ID/Embedded
+ </Profile>
+ </Properties>
+ <Link Self="ueb" LinkResourceURI="file:lalune.jpg" />
+ </Image>
+ </Rectangle>
+ </CharacterStyleRange>
+ <CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
+ <HyperlinkTextDestination Self="HyperlinkTextDestination/#inlineId" Name="Destination" DestinationUniqueKey="1" />
+ <Content> </Content>
+ </CharacterStyleRange>
+</ParagraphStyleRange>
+
+ </Story>
+
+</Document>
+``` \ No newline at end of file
diff --git a/test/command/5541-urlLink.md b/test/command/5541-urlLink.md
new file mode 100644
index 000000000..3c10490df
--- /dev/null
+++ b/test/command/5541-urlLink.md
@@ -0,0 +1,112 @@
+```
+% pandoc -f markdown -t icml -s
+
+# Header 1
+
+this is some text
+
+## Header 2
+
+some more text that [links to](https://www.pandoc.org) Pandoc.
+
+^D
+<?xml version="1.0" encoding="UTF-8" standalone="yes"?>
+<?aid style="50" type="snippet" readerVersion="6.0" featureSet="513" product="8.0(370)" ?>
+<?aid SnippetType="InCopyInterchange"?>
+<Document DOMVersion="8.0" Self="pandoc_doc">
+ <RootCharacterStyleGroup Self="pandoc_character_styles">
+ <CharacterStyle Self="$ID/NormalCharacterStyle" Name="Default" />
+ <CharacterStyle Self="CharacterStyle/Link" Name="Link">
+ <Properties>
+ <BasedOn type="object">$ID/NormalCharacterStyle</BasedOn>
+ </Properties>
+ </CharacterStyle>
+ </RootCharacterStyleGroup>
+ <RootParagraphStyleGroup Self="pandoc_paragraph_styles">
+ <ParagraphStyle Self="$ID/NormalParagraphStyle" Name="$ID/NormalParagraphStyle"
+ SpaceBefore="6" SpaceAfter="6"> <!-- paragraph spacing -->
+ <Properties>
+ <TabList type="list">
+ <ListItem type="record">
+ <Alignment type="enumeration">LeftAlign</Alignment>
+ <AlignmentCharacter type="string">.</AlignmentCharacter>
+ <Leader type="string"></Leader>
+ <Position type="unit">10</Position> <!-- first tab stop -->
+ </ListItem>
+ </TabList>
+ </Properties>
+ </ParagraphStyle>
+ <ParagraphStyle Self="ParagraphStyle/Header1" Name="Header1" LeftIndent="0" PointSize="36">
+ <Properties>
+ <BasedOn type="object">$ID/NormalParagraphStyle</BasedOn>
+ </Properties>
+ </ParagraphStyle>
+ <ParagraphStyle Self="ParagraphStyle/Header2" Name="Header2" LeftIndent="0" PointSize="30">
+ <Properties>
+ <BasedOn type="object">$ID/NormalParagraphStyle</BasedOn>
+ </Properties>
+ </ParagraphStyle>
+ <ParagraphStyle Self="ParagraphStyle/Paragraph" Name="Paragraph" LeftIndent="0">
+ <Properties>
+ <BasedOn type="object">$ID/NormalParagraphStyle</BasedOn>
+ </Properties>
+ </ParagraphStyle>
+ </RootParagraphStyleGroup>
+ <RootTableStyleGroup Self="pandoc_table_styles">
+ <TableStyle Self="TableStyle/Table" Name="Table" />
+ </RootTableStyleGroup>
+ <RootCellStyleGroup Self="pandoc_cell_styles">
+ <CellStyle Self="CellStyle/Cell" AppliedParagraphStyle="ParagraphStyle/$ID/[No paragraph style]" Name="Cell" />
+ </RootCellStyleGroup>
+ <Story Self="pandoc_story"
+ TrackChanges="false"
+ StoryTitle=""
+ AppliedTOCStyle="n"
+ AppliedNamedGrid="n" >
+ <StoryPreference OpticalMarginAlignment="true" OpticalMarginSize="12" />
+
+<!-- body needs to be non-indented, otherwise code blocks are indented too far -->
+<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Header1">
+ <CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
+ <HyperlinkTextDestination Self="HyperlinkTextDestination/#header-1" Name="Destination" DestinationUniqueKey="1" />
+ <Content>Header 1</Content>
+ </CharacterStyleRange>
+</ParagraphStyleRange>
+<Br />
+<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Paragraph">
+ <CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
+ <Content>this is some text</Content>
+ </CharacterStyleRange>
+</ParagraphStyleRange>
+<Br />
+<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Header2">
+ <CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
+ <HyperlinkTextDestination Self="HyperlinkTextDestination/#header-2" Name="Destination" DestinationUniqueKey="1" />
+ <Content>Header 2</Content>
+ </CharacterStyleRange>
+</ParagraphStyleRange>
+<Br />
+<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Paragraph">
+ <CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
+ <Content>some more text that </Content>
+ </CharacterStyleRange>
+ <HyperlinkTextSource Self="htss-1" Name="" Hidden="false">
+ <CharacterStyleRange AppliedCharacterStyle="CharacterStyle/Link">
+ <Content>links to</Content>
+ </CharacterStyleRange>
+ </HyperlinkTextSource>
+ <CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
+ <Content> Pandoc.</Content>
+ </CharacterStyleRange>
+</ParagraphStyleRange>
+
+ </Story>
+ <HyperlinkURLDestination Self="HyperlinkURLDestination/https%3a//www.pandoc.org" Name="link" DestinationURL="https://www.pandoc.org" DestinationUniqueKey="1" />
+ <Hyperlink Self="uf-1" Name="https://www.pandoc.org" Source="htss-1" Visible="true" DestinationUniqueKey="1">
+ <Properties>
+ <BorderColor type="enumeration">Black</BorderColor>
+ <Destination type="object">HyperlinkURLDestination/https%3a//www.pandoc.org</Destination>
+ </Properties>
+ </Hyperlink>
+</Document>
+``` \ No newline at end of file
diff --git a/test/writer.icml b/test/writer.icml
index 5c0b1813d..fa3e78fbf 100644
--- a/test/writer.icml
+++ b/test/writer.icml
@@ -444,16 +444,19 @@
<Br />
<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Header1">
<CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
+ <HyperlinkTextDestination Self="HyperlinkTextDestination/#headers" Name="Destination" DestinationUniqueKey="1" />
<Content>Headers</Content>
</CharacterStyleRange>
</ParagraphStyleRange>
<Br />
<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Header2">
<CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
+ <HyperlinkTextDestination Self="HyperlinkTextDestination/#level-2-with-an-embedded-link" Name="Destination" DestinationUniqueKey="1" />
<Content>Level 2 with an </Content>
</CharacterStyleRange>
<HyperlinkTextSource Self="htss-1" Name="" Hidden="false">
<CharacterStyleRange AppliedCharacterStyle="CharacterStyle/Link">
+ <HyperlinkTextDestination Self="HyperlinkTextDestination/#level-2-with-an-embedded-link" Name="Destination" DestinationUniqueKey="1" />
<Content>embedded link</Content>
</CharacterStyleRange>
</HyperlinkTextSource>
@@ -461,42 +464,50 @@
<Br />
<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Header3">
<CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
+ <HyperlinkTextDestination Self="HyperlinkTextDestination/#level-3-with-emphasis" Name="Destination" DestinationUniqueKey="1" />
<Content>Level 3 with </Content>
</CharacterStyleRange>
<CharacterStyleRange AppliedCharacterStyle="CharacterStyle/Italic">
+ <HyperlinkTextDestination Self="HyperlinkTextDestination/#level-3-with-emphasis" Name="Destination" DestinationUniqueKey="1" />
<Content>emphasis</Content>
</CharacterStyleRange>
</ParagraphStyleRange>
<Br />
<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Header4">
<CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
+ <HyperlinkTextDestination Self="HyperlinkTextDestination/#level-4" Name="Destination" DestinationUniqueKey="1" />
<Content>Level 4</Content>
</CharacterStyleRange>
</ParagraphStyleRange>
<Br />
<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Header5">
<CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
+ <HyperlinkTextDestination Self="HyperlinkTextDestination/#level-5" Name="Destination" DestinationUniqueKey="1" />
<Content>Level 5</Content>
</CharacterStyleRange>
</ParagraphStyleRange>
<Br />
<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Header1">
<CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
+ <HyperlinkTextDestination Self="HyperlinkTextDestination/#level-1" Name="Destination" DestinationUniqueKey="1" />
<Content>Level 1</Content>
</CharacterStyleRange>
</ParagraphStyleRange>
<Br />
<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Header2">
<CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
+ <HyperlinkTextDestination Self="HyperlinkTextDestination/#level-2-with-emphasis" Name="Destination" DestinationUniqueKey="1" />
<Content>Level 2 with </Content>
</CharacterStyleRange>
<CharacterStyleRange AppliedCharacterStyle="CharacterStyle/Italic">
+ <HyperlinkTextDestination Self="HyperlinkTextDestination/#level-2-with-emphasis" Name="Destination" DestinationUniqueKey="1" />
<Content>emphasis</Content>
</CharacterStyleRange>
</ParagraphStyleRange>
<Br />
<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Header3">
<CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
+ <HyperlinkTextDestination Self="HyperlinkTextDestination/#level-3" Name="Destination" DestinationUniqueKey="1" />
<Content>Level 3</Content>
</CharacterStyleRange>
</ParagraphStyleRange>
@@ -509,6 +520,7 @@
<Br />
<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Header2">
<CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
+ <HyperlinkTextDestination Self="HyperlinkTextDestination/#level-2" Name="Destination" DestinationUniqueKey="1" />
<Content>Level 2</Content>
</CharacterStyleRange>
</ParagraphStyleRange>
@@ -521,6 +533,7 @@
<Br />
<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Header1">
<CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
+ <HyperlinkTextDestination Self="HyperlinkTextDestination/#paragraphs" Name="Destination" DestinationUniqueKey="1" />
<Content>Paragraphs</Content>
</CharacterStyleRange>
</ParagraphStyleRange>
@@ -557,6 +570,7 @@
<Br />
<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Header1">
<CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
+ <HyperlinkTextDestination Self="HyperlinkTextDestination/#block-quotes" Name="Destination" DestinationUniqueKey="1" />
<Content>Block Quotes</Content>
</CharacterStyleRange>
</ParagraphStyleRange>
@@ -637,6 +651,7 @@
<Br />
<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Header1">
<CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
+ <HyperlinkTextDestination Self="HyperlinkTextDestination/#code-blocks" Name="Destination" DestinationUniqueKey="1" />
<Content>Code Blocks</Content>
</CharacterStyleRange>
</ParagraphStyleRange>
@@ -675,12 +690,14 @@ These should not be escaped: \$ \\ \&gt; \[ \{</Content>
<Br />
<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Header1">
<CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
+ <HyperlinkTextDestination Self="HyperlinkTextDestination/#lists" Name="Destination" DestinationUniqueKey="1" />
<Content>Lists</Content>
</CharacterStyleRange>
</ParagraphStyleRange>
<Br />
<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Header2">
<CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
+ <HyperlinkTextDestination Self="HyperlinkTextDestination/#unordered" Name="Destination" DestinationUniqueKey="1" />
<Content>Unordered</Content>
</CharacterStyleRange>
</ParagraphStyleRange>
@@ -831,6 +848,7 @@ These should not be escaped: \$ \\ \&gt; \[ \{</Content>
<Br />
<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Header2">
<CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
+ <HyperlinkTextDestination Self="HyperlinkTextDestination/#ordered" Name="Destination" DestinationUniqueKey="1" />
<Content>Ordered</Content>
</CharacterStyleRange>
</ParagraphStyleRange>
@@ -963,6 +981,7 @@ These should not be escaped: \$ \\ \&gt; \[ \{</Content>
<Br />
<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Header2">
<CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
+ <HyperlinkTextDestination Self="HyperlinkTextDestination/#nested" Name="Destination" DestinationUniqueKey="1" />
<Content>Nested</Content>
</CharacterStyleRange>
</ParagraphStyleRange>
@@ -1071,6 +1090,7 @@ These should not be escaped: \$ \\ \&gt; \[ \{</Content>
<Br />
<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Header2">
<CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
+ <HyperlinkTextDestination Self="HyperlinkTextDestination/#tabs-and-spaces" Name="Destination" DestinationUniqueKey="1" />
<Content>Tabs and spaces</Content>
</CharacterStyleRange>
</ParagraphStyleRange>
@@ -1101,6 +1121,7 @@ These should not be escaped: \$ \\ \&gt; \[ \{</Content>
<Br />
<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Header2">
<CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
+ <HyperlinkTextDestination Self="HyperlinkTextDestination/#fancy-list-markers" Name="Destination" DestinationUniqueKey="1" />
<Content>Fancy list markers</Content>
</CharacterStyleRange>
</ParagraphStyleRange>
@@ -1221,6 +1242,7 @@ These should not be escaped: \$ \\ \&gt; \[ \{</Content>
<Br />
<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Header1">
<CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
+ <HyperlinkTextDestination Self="HyperlinkTextDestination/#definition-lists" Name="Destination" DestinationUniqueKey="1" />
<Content>Definition Lists</Content>
</CharacterStyleRange>
</ParagraphStyleRange>
@@ -1533,6 +1555,7 @@ These should not be escaped: \$ \\ \&gt; \[ \{</Content>
<Br />
<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Header1">
<CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
+ <HyperlinkTextDestination Self="HyperlinkTextDestination/#html-blocks" Name="Destination" DestinationUniqueKey="1" />
<Content>HTML Blocks</Content>
</CharacterStyleRange>
</ParagraphStyleRange>
@@ -1691,6 +1714,7 @@ These should not be escaped: \$ \\ \&gt; \[ \{</Content>
<Br />
<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Header1">
<CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
+ <HyperlinkTextDestination Self="HyperlinkTextDestination/#inline-markup" Name="Destination" DestinationUniqueKey="1" />
<Content>Inline Markup</Content>
</CharacterStyleRange>
</ParagraphStyleRange>
@@ -1885,6 +1909,7 @@ These should not be escaped: \$ \\ \&gt; \[ \{</Content>
<Br />
<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Header1">
<CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
+ <HyperlinkTextDestination Self="HyperlinkTextDestination/#smart-quotes-ellipses-dashes" Name="Destination" DestinationUniqueKey="1" />
<Content>Smart quotes, ellipses, dashes</Content>
</CharacterStyleRange>
</ParagraphStyleRange>
@@ -2019,6 +2044,7 @@ These should not be escaped: \$ \\ \&gt; \[ \{</Content>
<Br />
<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Header1">
<CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
+ <HyperlinkTextDestination Self="HyperlinkTextDestination/#latex" Name="Destination" DestinationUniqueKey="1" />
<Content>LaTeX</Content>
</CharacterStyleRange>
</ParagraphStyleRange>
@@ -2198,6 +2224,7 @@ These should not be escaped: \$ \\ \&gt; \[ \{</Content>
<Br />
<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Header1">
<CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
+ <HyperlinkTextDestination Self="HyperlinkTextDestination/#special-characters" Name="Destination" DestinationUniqueKey="1" />
<Content>Special Characters</Content>
</CharacterStyleRange>
</ParagraphStyleRange>
@@ -2366,12 +2393,14 @@ These should not be escaped: \$ \\ \&gt; \[ \{</Content>
<Br />
<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Header1">
<CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
+ <HyperlinkTextDestination Self="HyperlinkTextDestination/#links" Name="Destination" DestinationUniqueKey="1" />
<Content>Links</Content>
</CharacterStyleRange>
</ParagraphStyleRange>
<Br />
<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Header2">
<CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
+ <HyperlinkTextDestination Self="HyperlinkTextDestination/#explicit" Name="Destination" DestinationUniqueKey="1" />
<Content>Explicit</Content>
</CharacterStyleRange>
</ParagraphStyleRange>
@@ -2468,6 +2497,7 @@ These should not be escaped: \$ \\ \&gt; \[ \{</Content>
<Br />
<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Header2">
<CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
+ <HyperlinkTextDestination Self="HyperlinkTextDestination/#reference" Name="Destination" DestinationUniqueKey="1" />
<Content>Reference</Content>
</CharacterStyleRange>
</ParagraphStyleRange>
@@ -2595,6 +2625,7 @@ These should not be escaped: \$ \\ \&gt; \[ \{</Content>
<Br />
<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Header2">
<CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
+ <HyperlinkTextDestination Self="HyperlinkTextDestination/#with-ampersands" Name="Destination" DestinationUniqueKey="1" />
<Content>With ampersands</Content>
</CharacterStyleRange>
</ParagraphStyleRange>
@@ -2657,6 +2688,7 @@ These should not be escaped: \$ \\ \&gt; \[ \{</Content>
<Br />
<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Header2">
<CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
+ <HyperlinkTextDestination Self="HyperlinkTextDestination/#autolinks" Name="Destination" DestinationUniqueKey="1" />
<Content>Autolinks</Content>
</CharacterStyleRange>
</ParagraphStyleRange>
@@ -2731,6 +2763,7 @@ These should not be escaped: \$ \\ \&gt; \[ \{</Content>
<Br />
<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Header1">
<CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
+ <HyperlinkTextDestination Self="HyperlinkTextDestination/#images" Name="Destination" DestinationUniqueKey="1" />
<Content>Images</Content>
</CharacterStyleRange>
</ParagraphStyleRange>
@@ -2815,6 +2848,7 @@ These should not be escaped: \$ \\ \&gt; \[ \{</Content>
<Br />
<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Header1">
<CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
+ <HyperlinkTextDestination Self="HyperlinkTextDestination/#footnotes" Name="Destination" DestinationUniqueKey="1" />
<Content>Footnotes</Content>
</CharacterStyleRange>
</ParagraphStyleRange>