Inline code when text has a special style
When a piece of text has a text 'Source_Text' then we assume that this is a piece of the document that represents a code that needs to be inlined. Addapted an odt writer to also reflect that change; previously it was just writing a 'preformatted' text using a non-distinguishable font style. Code blocks are still not recognized by the ODT reader. That's a separate issue.
This commit is contained in:
parent
eced02d70e
commit
13bc573e7f
7 changed files with 85 additions and 69 deletions
|
@ -237,6 +237,13 @@ xmlns:css3t="http://www.w3.org/TR/css3-text/" office:version="1.2">
|
|||
style:font-name-complex="Courier New"
|
||||
style:font-size-complex="10pt" />
|
||||
</style:style>
|
||||
<style:style style:name="Source_Text" style:family="text">
|
||||
<style:text-properties style:font-name="Courier New"
|
||||
fo:font-size="10pt" style:font-name-asian="Courier New"
|
||||
style:font-size-asian="10pt"
|
||||
style:font-name-complex="Courier New"
|
||||
style:font-size-complex="10pt" />
|
||||
</style:style>
|
||||
<style:style style:name="Definition_20_Term"
|
||||
style:display-name="Definition Term" style:family="paragraph"
|
||||
style:parent-style-name="Standard"
|
||||
|
@ -381,6 +388,7 @@ xmlns:css3t="http://www.w3.org/TR/css3-text/" office:version="1.2">
|
|||
style:font-name-asian="Courier New"
|
||||
style:font-name-complex="Courier New" />
|
||||
</style:style>
|
||||
|
||||
<style:style style:name="Internet_20_link"
|
||||
style:display-name="Internet link" style:family="text">
|
||||
<style:text-properties fo:color="#000080"
|
||||
|
|
|
@ -44,7 +44,7 @@ import Control.Applicative hiding ( liftA, liftA2, liftA3 )
|
|||
|
||||
import qualified Data.ByteString.Lazy as B
|
||||
import qualified Data.Map as M
|
||||
import Data.List ( find )
|
||||
import Data.List ( find, intercalate )
|
||||
import Data.Maybe
|
||||
|
||||
import qualified Text.XML.Light as XML
|
||||
|
@ -263,8 +263,13 @@ getHeaderAnchor = proc title -> do
|
|||
--------------------------------------------------------------------------------
|
||||
|
||||
--
|
||||
readStyleByName :: OdtReader _x Style
|
||||
readStyleByName = findAttr NsText "style-name" >>? getStyleByName
|
||||
readStyleByName :: OdtReader _x (StyleName, Style)
|
||||
readStyleByName =
|
||||
findAttr NsText "style-name" >>? keepingTheValue getStyleByName >>^ liftE
|
||||
where
|
||||
liftE :: (StyleName, Fallible Style) -> Fallible (StyleName, Style)
|
||||
liftE (name, Right v) = Right (name, v)
|
||||
liftE (_, Left v) = Left v
|
||||
|
||||
--
|
||||
isStyleToTrace :: OdtReader Style Bool
|
||||
|
@ -275,7 +280,10 @@ withNewStyle :: OdtReaderSafe x Inlines -> OdtReaderSafe x Inlines
|
|||
withNewStyle a = proc x -> do
|
||||
fStyle <- readStyleByName -< ()
|
||||
case fStyle of
|
||||
Right style -> do
|
||||
Right (styleName, _) | isCodeStyle styleName -> do
|
||||
inlines <- a -< x
|
||||
arr inlineCode -<< inlines
|
||||
Right (_, style) -> do
|
||||
mFamily <- arr styleFamily -< style
|
||||
fTextProps <- arr ( maybeToChoice
|
||||
. textProperties
|
||||
|
@ -301,7 +309,13 @@ withNewStyle a = proc x -> do
|
|||
Left _ -> a -< x
|
||||
Left _ -> a -< x
|
||||
Left _ -> a -< x
|
||||
where
|
||||
isCodeStyle :: StyleName -> Bool
|
||||
isCodeStyle "Source_Text" = True
|
||||
isCodeStyle _ = False
|
||||
|
||||
inlineCode :: Inlines -> Inlines
|
||||
inlineCode = code . intercalate "" . map stringify . toList
|
||||
|
||||
type PropertyTriple = (ReaderState, TextProperties, Maybe StyleFamily)
|
||||
type InlineModifier = Inlines -> Inlines
|
||||
|
@ -327,7 +341,7 @@ modifierFromStyleDiff propertyTriple =
|
|||
let getVPos = Just . verticalPosition
|
||||
in case lookupPreviousValueM getVPos triple of
|
||||
Nothing -> ignore
|
||||
Just oldVPos -> getVPosModifier' (oldVPos,verticalPosition textProps)
|
||||
Just oldVPos -> getVPosModifier' (oldVPos, verticalPosition textProps)
|
||||
|
||||
getVPosModifier' (oldVPos , newVPos ) | oldVPos == newVPos = ignore
|
||||
getVPosModifier' ( _ , VPosSub ) = subscript
|
||||
|
@ -401,7 +415,7 @@ constructPara reader = proc blocks -> do
|
|||
fStyle <- readStyleByName -< blocks
|
||||
case fStyle of
|
||||
Left _ -> reader -< blocks
|
||||
Right style -> do
|
||||
Right (_, style) -> do
|
||||
let modifier = getParaModifier style
|
||||
blocks' <- reader -< blocks
|
||||
arr modifier -<< blocks'
|
||||
|
|
|
@ -392,7 +392,7 @@ inlineToOpenDocument o ils
|
|||
Subscript l -> withTextStyle Sub $ inlinesToOpenDocument o l
|
||||
SmallCaps l -> withTextStyle SmallC $ inlinesToOpenDocument o l
|
||||
Quoted t l -> inQuotes t <$> inlinesToOpenDocument o l
|
||||
Code _ s -> withTextStyle Pre $ inTextStyle $ preformatted s
|
||||
Code _ s -> inlinedCode $ preformatted s
|
||||
Math t s -> inlinesToOpenDocument o (texMathToInlines t s)
|
||||
Cite _ l -> inlinesToOpenDocument o l
|
||||
RawInline f s -> if f == Format "opendocument"
|
||||
|
@ -403,6 +403,7 @@ inlineToOpenDocument o ils
|
|||
Note l -> mkNote l
|
||||
where
|
||||
preformatted s = handleSpaces $ escapeStringForXML 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 )
|
||||
|
|
|
@ -149,6 +149,7 @@ namesOfTestsComparingToNative = [ "blockquote"
|
|||
, "image"
|
||||
, "imageIndex"
|
||||
, "imageWithCaption"
|
||||
, "inlinedCode"
|
||||
, "orderedListMixed"
|
||||
, "orderedListRoman"
|
||||
, "orderedListSimple"
|
||||
|
|
1
tests/odt/native/inlinedCode.native
Normal file
1
tests/odt/native/inlinedCode.native
Normal file
|
@ -0,0 +1 @@
|
|||
[Para [Str "Here",Space,Str "comes",Space,Code ("",[],[]) "inlined code",Space,Str "text",Space,Str "and",Space,Code ("",[],[]) "an another",Space,Str "one."]]
|
BIN
tests/odt/odt/inlinedCode.odt
Normal file
BIN
tests/odt/odt/inlinedCode.odt
Normal file
Binary file not shown.
|
@ -668,47 +668,37 @@
|
|||
<style:style style:name="T35" style:family="text"><style:text-properties fo:font-style="italic" style:font-style-asian="italic" style:font-style-complex="italic" fo:font-weight="bold" style:font-weight-asian="bold" style:font-weight-complex="bold" /></style:style>
|
||||
<style:style style:name="T36" style:family="text"><style:text-properties fo:font-style="italic" style:font-style-asian="italic" style:font-style-complex="italic" fo:font-weight="bold" style:font-weight-asian="bold" style:font-weight-complex="bold" /></style:style>
|
||||
<style:style style:name="T37" style:family="text"><style:text-properties fo:font-style="italic" style:font-style-asian="italic" style:font-style-complex="italic" fo:font-weight="bold" style:font-weight-asian="bold" style:font-weight-complex="bold" /></style:style>
|
||||
<style:style style:name="T38" style:family="text"><style:text-properties style:font-name="Courier New" style:font-name-asian="Courier New" style:font-name-complex="Courier New" /></style:style>
|
||||
<style:style style:name="T39" style:family="text"><style:text-properties style:font-name="Courier New" style:font-name-asian="Courier New" style:font-name-complex="Courier New" /></style:style>
|
||||
<style:style style:name="T40" style:family="text"><style:text-properties style:font-name="Courier New" style:font-name-asian="Courier New" style:font-name-complex="Courier New" /></style:style>
|
||||
<style:style style:name="T41" style:family="text"><style:text-properties style:font-name="Courier New" style:font-name-asian="Courier New" style:font-name-complex="Courier New" /></style:style>
|
||||
<style:style style:name="T42" style:family="text"><style:text-properties style:font-name="Courier New" style:font-name-asian="Courier New" style:font-name-complex="Courier New" /></style:style>
|
||||
<style:style style:name="T38" style:family="text"><style:text-properties style:text-line-through-style="solid" /></style:style>
|
||||
<style:style style:name="T39" style:family="text"><style:text-properties style:text-line-through-style="solid" /></style:style>
|
||||
<style:style style:name="T40" style:family="text"><style:text-properties style:text-line-through-style="solid" /></style:style>
|
||||
<style:style style:name="T41" style:family="text"><style:text-properties style:text-line-through-style="solid" /></style:style>
|
||||
<style:style style:name="T42" style:family="text"><style:text-properties fo:font-style="italic" style:font-style-asian="italic" style:font-style-complex="italic" style:text-line-through-style="solid" /></style:style>
|
||||
<style:style style:name="T43" style:family="text"><style:text-properties style:text-line-through-style="solid" /></style:style>
|
||||
<style:style style:name="T44" style:family="text"><style:text-properties style:text-line-through-style="solid" /></style:style>
|
||||
<style:style style:name="T45" style:family="text"><style:text-properties style:text-line-through-style="solid" /></style:style>
|
||||
<style:style style:name="T46" style:family="text"><style:text-properties style:text-line-through-style="solid" /></style:style>
|
||||
<style:style style:name="T47" style:family="text"><style:text-properties fo:font-style="italic" style:font-style-asian="italic" style:font-style-complex="italic" style:text-line-through-style="solid" /></style:style>
|
||||
<style:style style:name="T48" style:family="text"><style:text-properties style:text-line-through-style="solid" /></style:style>
|
||||
<style:style style:name="T49" style:family="text"><style:text-properties style:text-position="super 58%" /></style:style>
|
||||
<style:style style:name="T50" style:family="text"><style:text-properties fo:font-style="italic" style:font-style-asian="italic" style:font-style-complex="italic" style:text-position="super 58%" /></style:style>
|
||||
<style:style style:name="T51" style:family="text"><style:text-properties style:text-position="super 58%" /></style:style>
|
||||
<style:style style:name="T52" style:family="text"><style:text-properties style:text-position="sub 58%" /></style:style>
|
||||
<style:style style:name="T53" style:family="text"><style:text-properties style:text-position="sub 58%" /></style:style>
|
||||
<style:style style:name="T54" style:family="text"><style:text-properties style:text-position="sub 58%" /></style:style>
|
||||
<style:style style:name="T55" style:family="text"><style:text-properties style:font-name="Courier New" style:font-name-asian="Courier New" style:font-name-complex="Courier New" /></style:style>
|
||||
<style:style style:name="T44" style:family="text"><style:text-properties style:text-position="super 58%" /></style:style>
|
||||
<style:style style:name="T45" style:family="text"><style:text-properties fo:font-style="italic" style:font-style-asian="italic" style:font-style-complex="italic" style:text-position="super 58%" /></style:style>
|
||||
<style:style style:name="T46" style:family="text"><style:text-properties style:text-position="super 58%" /></style:style>
|
||||
<style:style style:name="T47" style:family="text"><style:text-properties style:text-position="sub 58%" /></style:style>
|
||||
<style:style style:name="T48" style:family="text"><style:text-properties style:text-position="sub 58%" /></style:style>
|
||||
<style:style style:name="T49" style:family="text"><style:text-properties style:text-position="sub 58%" /></style:style>
|
||||
<style:style style:name="T50" style:family="text"><style:text-properties fo:font-style="italic" style:font-style-asian="italic" style:font-style-complex="italic" /></style:style>
|
||||
<style:style style:name="T51" style:family="text"><style:text-properties fo:font-style="italic" style:font-style-asian="italic" style:font-style-complex="italic" /></style:style>
|
||||
<style:style style:name="T52" style:family="text"><style:text-properties fo:font-style="italic" style:font-style-asian="italic" style:font-style-complex="italic" /></style:style>
|
||||
<style:style style:name="T53" style:family="text"><style:text-properties fo:font-style="italic" style:font-style-asian="italic" style:font-style-complex="italic" /></style:style>
|
||||
<style:style style:name="T54" style:family="text"><style:text-properties fo:font-style="italic" style:font-style-asian="italic" style:font-style-complex="italic" /></style:style>
|
||||
<style:style style:name="T55" style:family="text"><style:text-properties fo:font-style="italic" style:font-style-asian="italic" style:font-style-complex="italic" /></style:style>
|
||||
<style:style style:name="T56" style:family="text"><style:text-properties fo:font-style="italic" style:font-style-asian="italic" style:font-style-complex="italic" /></style:style>
|
||||
<style:style style:name="T57" style:family="text"><style:text-properties fo:font-style="italic" style:font-style-asian="italic" style:font-style-complex="italic" /></style:style>
|
||||
<style:style style:name="T58" style:family="text"><style:text-properties fo:font-style="italic" style:font-style-asian="italic" style:font-style-complex="italic" /></style:style>
|
||||
<style:style style:name="T58" style:family="text"><style:text-properties style:text-position="super 58%" /></style:style>
|
||||
<style:style style:name="T59" style:family="text"><style:text-properties fo:font-style="italic" style:font-style-asian="italic" style:font-style-complex="italic" /></style:style>
|
||||
<style:style style:name="T60" style:family="text"><style:text-properties fo:font-style="italic" style:font-style-asian="italic" style:font-style-complex="italic" /></style:style>
|
||||
<style:style style:name="T61" style:family="text"><style:text-properties fo:font-style="italic" style:font-style-asian="italic" style:font-style-complex="italic" /></style:style>
|
||||
<style:style style:name="T62" style:family="text"><style:text-properties fo:font-style="italic" style:font-style-asian="italic" style:font-style-complex="italic" /></style:style>
|
||||
<style:style style:name="T63" style:family="text"><style:text-properties fo:font-style="italic" style:font-style-asian="italic" style:font-style-complex="italic" /></style:style>
|
||||
<style:style style:name="T64" style:family="text"><style:text-properties style:text-position="super 58%" /></style:style>
|
||||
<style:style style:name="T65" style:family="text"><style:text-properties style:font-name="Courier New" style:font-name-asian="Courier New" style:font-name-complex="Courier New" /></style:style>
|
||||
<style:style style:name="T64" style:family="text"><style:text-properties fo:font-style="italic" style:font-style-asian="italic" style:font-style-complex="italic" /></style:style>
|
||||
<style:style style:name="T65" style:family="text"><style:text-properties fo:font-style="italic" style:font-style-asian="italic" style:font-style-complex="italic" /></style:style>
|
||||
<style:style style:name="T66" style:family="text"><style:text-properties fo:font-style="italic" style:font-style-asian="italic" style:font-style-complex="italic" /></style:style>
|
||||
<style:style style:name="T67" style:family="text"><style:text-properties style:font-name="Courier New" style:font-name-asian="Courier New" style:font-name-complex="Courier New" /></style:style>
|
||||
<style:style style:name="T67" style:family="text"><style:text-properties fo:font-style="italic" style:font-style-asian="italic" style:font-style-complex="italic" /></style:style>
|
||||
<style:style style:name="T68" style:family="text"><style:text-properties fo:font-style="italic" style:font-style-asian="italic" style:font-style-complex="italic" /></style:style>
|
||||
<style:style style:name="T69" style:family="text"><style:text-properties fo:font-style="italic" style:font-style-asian="italic" style:font-style-complex="italic" /></style:style>
|
||||
<style:style style:name="T70" style:family="text"><style:text-properties fo:font-style="italic" style:font-style-asian="italic" style:font-style-complex="italic" /></style:style>
|
||||
<style:style style:name="T71" style:family="text"><style:text-properties fo:font-style="italic" style:font-style-asian="italic" style:font-style-complex="italic" /></style:style>
|
||||
<style:style style:name="T72" style:family="text"><style:text-properties fo:font-style="italic" style:font-style-asian="italic" style:font-style-complex="italic" /></style:style>
|
||||
<style:style style:name="T73" style:family="text"><style:text-properties fo:font-style="italic" style:font-style-asian="italic" style:font-style-complex="italic" /></style:style>
|
||||
<style:style style:name="T74" style:family="text"><style:text-properties fo:font-style="italic" style:font-style-asian="italic" style:font-style-complex="italic" /></style:style>
|
||||
<style:style style:name="T75" style:family="text"><style:text-properties style:font-name="Courier New" style:font-name-asian="Courier New" style:font-name-complex="Courier New" /></style:style>
|
||||
<style:style style:name="T76" style:family="text"><style:text-properties fo:font-style="italic" style:font-style-asian="italic" style:font-style-complex="italic" /></style:style>
|
||||
<style:style style:name="T77" style:family="text"><style:text-properties fo:font-style="italic" style:font-style-asian="italic" style:font-style-complex="italic" /></style:style>
|
||||
<style:style style:name="T78" style:family="text"><style:text-properties style:font-name="Courier New" style:font-name-asian="Courier New" style:font-name-complex="Courier New" /></style:style>
|
||||
<style:style style:name="P1" style:family="paragraph" style:parent-style-name="Quotations">
|
||||
<style:paragraph-properties fo:margin-left="0.5in" fo:margin-right="0in" fo:text-indent="0in" style:auto-text-indent="false" />
|
||||
</style:style>
|
||||
|
@ -1358,22 +1348,22 @@ Markup</text:h>
|
|||
<text:p text:style-name="Text_20_body">So is
|
||||
<text:span text:style-name="T37">this</text:span> word.</text:p>
|
||||
<text:p text:style-name="Text_20_body">This is code:
|
||||
<text:span text:style-name="T38">></text:span>,
|
||||
<text:span text:style-name="T39">$</text:span>,
|
||||
<text:span text:style-name="T40">\</text:span>,
|
||||
<text:span text:style-name="T41">\$</text:span>,
|
||||
<text:span text:style-name="T42"><html></text:span>.</text:p>
|
||||
<text:p text:style-name="Text_20_body"><text:span text:style-name="T43">This</text:span><text:span text:style-name="T44">
|
||||
</text:span><text:span text:style-name="T45">is</text:span><text:span text:style-name="T46">
|
||||
</text:span><text:span text:style-name="T47">strikeout</text:span><text:span text:style-name="T48">.</text:span></text:p>
|
||||
<text:span text:style-name="Source_Text">></text:span>,
|
||||
<text:span text:style-name="Source_Text">$</text:span>,
|
||||
<text:span text:style-name="Source_Text">\</text:span>,
|
||||
<text:span text:style-name="Source_Text">\$</text:span>,
|
||||
<text:span text:style-name="Source_Text"><html></text:span>.</text:p>
|
||||
<text:p text:style-name="Text_20_body"><text:span text:style-name="T38">This</text:span><text:span text:style-name="T39">
|
||||
</text:span><text:span text:style-name="T40">is</text:span><text:span text:style-name="T41">
|
||||
</text:span><text:span text:style-name="T42">strikeout</text:span><text:span text:style-name="T43">.</text:span></text:p>
|
||||
<text:p text:style-name="Text_20_body">Superscripts:
|
||||
a<text:span text:style-name="T49">bc</text:span>d
|
||||
a<text:span text:style-name="T50">hello</text:span>
|
||||
a<text:span text:style-name="T51">hello there</text:span>.</text:p>
|
||||
a<text:span text:style-name="T44">bc</text:span>d
|
||||
a<text:span text:style-name="T45">hello</text:span>
|
||||
a<text:span text:style-name="T46">hello there</text:span>.</text:p>
|
||||
<text:p text:style-name="Text_20_body">Subscripts:
|
||||
H<text:span text:style-name="T52">2</text:span>O,
|
||||
H<text:span text:style-name="T53">23</text:span>O,
|
||||
H<text:span text:style-name="T54">many of them</text:span>O.</text:p>
|
||||
H<text:span text:style-name="T47">2</text:span>O,
|
||||
H<text:span text:style-name="T48">23</text:span>O,
|
||||
H<text:span text:style-name="T49">many of them</text:span>O.</text:p>
|
||||
<text:p text:style-name="Text_20_body">These should not be superscripts or
|
||||
subscripts, because of the unescaped spaces: a^b c^d, a~b c~d.</text:p>
|
||||
<text:p text:style-name="Horizontal_20_Line" />
|
||||
|
@ -1387,7 +1377,7 @@ trees. So is ‘pine.’</text:p>
|
|||
<text:p text:style-name="Text_20_body">‘He said, “I want to go.”’ Were you
|
||||
alive in the 70’s?</text:p>
|
||||
<text:p text:style-name="Text_20_body">Here is some quoted
|
||||
‘<text:span text:style-name="T55">code</text:span>’ and a
|
||||
‘<text:span text:style-name="Source_Text">code</text:span>’ and a
|
||||
“<text:a xlink:type="simple" xlink:href="http://example.com/?foo=1&bar=2" office:name=""><text:span text:style-name="Definition">quoted
|
||||
link</text:span></text:a>”.</text:p>
|
||||
<text:p text:style-name="Text_20_body">Some dashes: one—two — three—four —
|
||||
|
@ -1405,16 +1395,16 @@ five.</text:p>
|
|||
<text:p text:style-name="P51">2 + 2 = 4</text:p>
|
||||
</text:list-item>
|
||||
<text:list-item>
|
||||
<text:p text:style-name="P51"><text:span text:style-name="T56">x</text:span> ∈ <text:span text:style-name="T57">y</text:span></text:p>
|
||||
<text:p text:style-name="P51"><text:span text:style-name="T50">x</text:span> ∈ <text:span text:style-name="T51">y</text:span></text:p>
|
||||
</text:list-item>
|
||||
<text:list-item>
|
||||
<text:p text:style-name="P51"><text:span text:style-name="T58">α</text:span> ∧ <text:span text:style-name="T59">ω</text:span></text:p>
|
||||
<text:p text:style-name="P51"><text:span text:style-name="T52">α</text:span> ∧ <text:span text:style-name="T53">ω</text:span></text:p>
|
||||
</text:list-item>
|
||||
<text:list-item>
|
||||
<text:p text:style-name="P51">223</text:p>
|
||||
</text:list-item>
|
||||
<text:list-item>
|
||||
<text:p text:style-name="P51"><text:span text:style-name="T60">p</text:span>-Tree</text:p>
|
||||
<text:p text:style-name="P51"><text:span text:style-name="T54">p</text:span>-Tree</text:p>
|
||||
</text:list-item>
|
||||
<text:list-item>
|
||||
<text:p text:style-name="P51">Here’s some display math:
|
||||
|
@ -1422,18 +1412,18 @@ five.</text:p>
|
|||
</text:list-item>
|
||||
<text:list-item>
|
||||
<text:p text:style-name="P51">Here’s one that has a line break in it:
|
||||
<text:span text:style-name="T61">α</text:span> + <text:span text:style-name="T62">ω</text:span> × <text:span text:style-name="T63">x</text:span><text:span text:style-name="T64">2</text:span>.</text:p>
|
||||
<text:span text:style-name="T55">α</text:span> + <text:span text:style-name="T56">ω</text:span> × <text:span text:style-name="T57">x</text:span><text:span text:style-name="T58">2</text:span>.</text:p>
|
||||
</text:list-item>
|
||||
</text:list>
|
||||
<text:p text:style-name="First_20_paragraph">These shouldn’t be math:</text:p>
|
||||
<text:list text:style-name="L27">
|
||||
<text:list-item>
|
||||
<text:p text:style-name="P52">To get the famous equation, write
|
||||
<text:span text:style-name="T65">$e = mc^2$</text:span>.</text:p>
|
||||
<text:span text:style-name="Source_Text">$e = mc^2$</text:span>.</text:p>
|
||||
</text:list-item>
|
||||
<text:list-item>
|
||||
<text:p text:style-name="P52">$22,000 is a
|
||||
<text:span text:style-name="T66">lot</text:span> of money. So is $34,000.
|
||||
<text:span text:style-name="T59">lot</text:span> of money. So is $34,000.
|
||||
(It worked if “lot” is emphasized.)</text:p>
|
||||
</text:list-item>
|
||||
<text:list-item>
|
||||
|
@ -1441,11 +1431,11 @@ five.</text:p>
|
|||
</text:list-item>
|
||||
<text:list-item>
|
||||
<text:p text:style-name="P52">Escaped
|
||||
<text:span text:style-name="T67">$</text:span>: $73
|
||||
<text:span text:style-name="T68">this</text:span><text:span text:style-name="T69">
|
||||
</text:span><text:span text:style-name="T70">should</text:span><text:span text:style-name="T71">
|
||||
</text:span><text:span text:style-name="T72">be</text:span><text:span text:style-name="T73">
|
||||
</text:span><text:span text:style-name="T74">emphasized</text:span>
|
||||
<text:span text:style-name="Source_Text">$</text:span>: $73
|
||||
<text:span text:style-name="T60">this</text:span><text:span text:style-name="T61">
|
||||
</text:span><text:span text:style-name="T62">should</text:span><text:span text:style-name="T63">
|
||||
</text:span><text:span text:style-name="T64">be</text:span><text:span text:style-name="T65">
|
||||
</text:span><text:span text:style-name="T66">emphasized</text:span>
|
||||
23$.</text:p>
|
||||
</text:list-item>
|
||||
</text:list>
|
||||
|
@ -1570,7 +1560,7 @@ link in pointy braces</text:span></text:a>.</text:p>
|
|||
<text:p text:style-name="P56">Blockquoted:
|
||||
<text:a xlink:type="simple" xlink:href="http://example.com/" office:name=""><text:span text:style-name="Definition">http://example.com/</text:span></text:a></text:p>
|
||||
<text:p text:style-name="First_20_paragraph">Auto-links should not occur here:
|
||||
<text:span text:style-name="T75"><http://example.com/></text:span></text:p>
|
||||
<text:span text:style-name="Source_Text"><http://example.com/></text:span></text:p>
|
||||
<text:p text:style-name="P57">or here: <http://example.com/></text:p>
|
||||
<text:p text:style-name="Horizontal_20_Line" />
|
||||
<text:h text:style-name="Heading_20_1" text:outline-level="1">Images</text:h>
|
||||
|
@ -1595,14 +1585,15 @@ indented to show that they belong to the footnote (as with list
|
|||
items).</text:p><text:p text:style-name="P58"><text:s text:c="2" />{ <code> }</text:p><text:p text:style-name="Footnote">If
|
||||
you want, you can indent every line, but you can also be lazy and just indent
|
||||
the first line of each block.</text:p></text:note-body></text:note> This
|
||||
should <text:span text:style-name="T76">not</text:span> be a footnote
|
||||
should <text:span text:style-name="T67">not</text:span> be a footnote
|
||||
reference, because it contains a space.[^my note] Here is an inline
|
||||
note.<text:note text:id="ftn2" text:note-class="footnote"><text:note-citation>3</text:note-citation><text:note-body><text:p text:style-name="Footnote">This
|
||||
is <text:span text:style-name="T77">easier</text:span> to type. Inline notes
|
||||
is <text:span text:style-name="T68">easier</text:span> to type. Inline notes
|
||||
may contain
|
||||
<text:a xlink:type="simple" xlink:href="http://google.com" office:name=""><text:span text:style-name="Definition">links</text:span></text:a>
|
||||
and <text:span text:style-name="T78">]</text:span> verbatim characters, as
|
||||
well as [bracketed text].</text:p></text:note-body></text:note></text:p>
|
||||
and <text:span text:style-name="Source_Text">]</text:span> verbatim
|
||||
characters, as well as [bracketed
|
||||
text].</text:p></text:note-body></text:note></text:p>
|
||||
<text:p text:style-name="P59">Notes can go in
|
||||
quotes.<text:note text:id="ftn3" text:note-class="footnote"><text:note-citation>4</text:note-citation><text:note-body><text:p text:style-name="Footnote">In
|
||||
quote.</text:p></text:note-body></text:note></text:p>
|
||||
|
|
Loading…
Reference in a new issue