diff options
author | John MacFarlane <jgm@berkeley.edu> | 2017-01-23 15:18:34 +0100 |
---|---|---|
committer | John MacFarlane <jgm@berkeley.edu> | 2017-01-23 15:18:34 +0100 |
commit | 41f4476aabe4eacec06e47c5d6dba2503b1eb1f0 (patch) | |
tree | fccc6ca75bd4b75d4859f44e8156041377e7c697 | |
parent | faf4f7818bae59700a9184ae20d1a0f13be255a5 (diff) | |
download | pandoc-41f4476aabe4eacec06e47c5d6dba2503b1eb1f0.tar.gz |
OpenDocument writer: don't profilerate text styles unnecessarily.
This change makes the writer create only as many temporary
text styles as are absolutely necessary. It also consolidates
adjacent nodes with the same style.
Closes #3371.
-rw-r--r-- | src/Text/Pandoc/Writers/OpenDocument.hs | 87 | ||||
-rw-r--r-- | tests/writer.opendocument | 152 |
2 files changed, 102 insertions, 137 deletions
diff --git a/src/Text/Pandoc/Writers/OpenDocument.hs b/src/Text/Pandoc/Writers/OpenDocument.hs index dec394797..5107cb499 100644 --- a/src/Text/Pandoc/Writers/OpenDocument.hs +++ b/src/Text/Pandoc/Writers/OpenDocument.hs @@ -41,8 +41,11 @@ import Text.Printf ( printf ) import Control.Arrow ( (***), (>>>) ) import Control.Monad.State hiding ( when ) import Data.Char (chr) +import qualified Data.Set as Set import qualified Data.Map as Map import Text.Pandoc.Writers.Shared +import Data.List (sortBy) +import Data.Ord (comparing) -- | Auxiliary function to convert Plain block to Para. plainToPara :: Block -> Block @@ -58,8 +61,8 @@ data WriterState = , stTableStyles :: [Doc] , stParaStyles :: [Doc] , stListStyles :: [(Int, [Doc])] - , stTextStyles :: [Doc] - , stTextStyleAttr :: Map.Map TextStyle [(String,String)] + , stTextStyles :: Map.Map (Set.Set TextStyle) (String, Doc) + , stTextStyleAttr :: Set.Set TextStyle , stIndentPara :: Int , stInDefinition :: Bool , stTight :: Bool @@ -73,8 +76,8 @@ defaultWriterState = , stTableStyles = [] , stParaStyles = [] , stListStyles = [] - , stTextStyles = [] - , stTextStyleAttr = Map.empty + , stTextStyles = Map.empty + , stTextStyleAttr = Set.empty , stIndentPara = 0 , stInDefinition = False , stTight = False @@ -94,14 +97,13 @@ addNote i = modify $ \s -> s { stNotes = i : stNotes s } addParaStyle :: Doc -> State WriterState () addParaStyle i = modify $ \s -> s { stParaStyles = i : stParaStyles s } -addTextStyle :: Doc -> State WriterState () -addTextStyle i = modify $ \s -> s { stTextStyles = i : stTextStyles s } +addTextStyle :: Set.Set TextStyle -> (String, Doc) -> State WriterState () +addTextStyle attrs i = modify $ \s -> + s { stTextStyles = Map.insert attrs i (stTextStyles s) } -addTextStyleAttr :: (TextStyle, [(String,String)]) -> State WriterState () -addTextStyleAttr (ts, xs) = modify $ \s -> s { stTextStyleAttr = Map.insert ts xs (stTextStyleAttr s) } - -rmTextStyleAttr :: TextStyle -> State WriterState () -rmTextStyleAttr ts = modify $ \s -> s { stTextStyleAttr = Map.delete ts (stTextStyleAttr s) } +addTextStyleAttr :: TextStyle -> State WriterState () +addTextStyleAttr t = modify $ \s -> + s { stTextStyleAttr = Set.insert t (stTextStyleAttr s) } increaseIndent :: State WriterState () increaseIndent = modify $ \s -> s { stIndentPara = 1 + stIndentPara s } @@ -136,20 +138,33 @@ inSpanTags :: String -> Doc -> Doc inSpanTags s = inTags False "text:span" [("text:style-name",s)] withTextStyle :: TextStyle -> State WriterState a -> State WriterState a -withTextStyle s f = addTextStyleAttr (s,textStyleAttr s) >> - f >>= \r -> rmTextStyleAttr s >> return r +withTextStyle s f = do + oldTextStyleAttr <- gets stTextStyleAttr + addTextStyleAttr s + res <- f + modify $ \st -> st{ stTextStyleAttr = oldTextStyleAttr } + return res inTextStyle :: Doc -> State WriterState Doc inTextStyle d = do at <- gets stTextStyleAttr - if Map.null at + if Set.null at then return d else do - tn <- (+) 1 . length <$> gets stTextStyles - addTextStyle $ inTags False "style:style" [("style:name" , "T" ++ show tn) - ,("style:family", "text" )] - $ selfClosingTag "style:text-properties" (concatMap snd $ Map.toList at) - return $ inTags False "text:span" [("text:style-name","T" ++ show tn)] d + styles <- gets stTextStyles + case Map.lookup at styles of + Just (styleName, _) -> return $ + inTags False "text:span" [("text:style-name",styleName)] d + Nothing -> do + let styleName = "T" ++ show (Map.size styles + 1) + addTextStyle at (styleName, + inTags False "style:style" + [("style:name", styleName) + ,("style:family", "text")] + $ selfClosingTag "style:text-properties" + (concatMap textStyleAttr (Set.toList at))) + return $ inTags False + "text:span" [("text:style-name",styleName)] d inHeaderTags :: Int -> Doc -> State WriterState Doc inHeaderTags i d = @@ -188,7 +203,9 @@ writeOpenDocument opts (Pandoc meta blocks) = meta b <- render' `fmap` blocksToOpenDocument opts blocks return (b, m) - styles = stTableStyles s ++ stParaStyles s ++ stTextStyles s + styles = stTableStyles s ++ stParaStyles s ++ + map snd (reverse $ sortBy (comparing fst) $ + Map.elems (stTextStyles s)) listStyle (n,l) = inTags True "text:list-style" [("style:name", "L" ++ show n)] (vcat l) listStyles = map listStyle (stListStyles s) @@ -371,20 +388,40 @@ tableItemToOpenDocument o tn (n,i) = -- | Convert a list of inline elements to OpenDocument. inlinesToOpenDocument :: WriterOptions -> [Inline] -> State WriterState Doc -inlinesToOpenDocument o l = hcat <$> mapM (inlineToOpenDocument o) l +inlinesToOpenDocument o l = hcat <$> toChunks o l + +toChunks :: WriterOptions -> [Inline] -> State WriterState [Doc] +toChunks _ [] = return [] +toChunks o (x : xs) + | isChunkable x = do + contents <- (inTextStyle . hcat) =<< + mapM (inlineToOpenDocument o) (x:ys) + rest <- toChunks o zs + return (contents : rest) + | otherwise = do + contents <- inlineToOpenDocument o x + rest <- toChunks o xs + return (contents : rest) + where (ys, zs) = span isChunkable xs + +isChunkable :: Inline -> Bool +isChunkable (Str _) = True +isChunkable Space = True +isChunkable SoftBreak = True +isChunkable _ = False -- | Convert an inline element to OpenDocument. inlineToOpenDocument :: WriterOptions -> Inline -> State WriterState Doc inlineToOpenDocument o ils = case ils of - Space -> inTextStyle space + Space -> return space SoftBreak | writerWrapText o == WrapPreserve - -> inTextStyle (preformatted "\n") - | otherwise -> inTextStyle space + -> return $ preformatted "\n" + | otherwise -> return $ space Span _ xs -> inlinesToOpenDocument o xs LineBreak -> return $ selfClosingTag "text:line-break" [] - Str s -> inTextStyle $ handleSpaces $ escapeStringForXML s + Str s -> return $ handleSpaces $ escapeStringForXML s Emph l -> withTextStyle Italic $ inlinesToOpenDocument o l Strong l -> withTextStyle Bold $ inlinesToOpenDocument o l Strikeout l -> withTextStyle Strike $ inlinesToOpenDocument o l diff --git a/tests/writer.opendocument b/tests/writer.opendocument index 6c84ae31b..d613ab5b8 100644 --- a/tests/writer.opendocument +++ b/tests/writer.opendocument @@ -632,73 +632,13 @@ </text:list-level-style-number> </text:list-style> <style:style style:name="T1" 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="T2" 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="T3" 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="T4" 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="T5" 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="T6" style:family="text"><style:text-properties fo:font-weight="bold" style:font-weight-asian="bold" style:font-weight-complex="bold" /></style:style> - <style:style style:name="T7" 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="T8" 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="T9" 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="T10" 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="T11" style:family="text"><style:text-properties fo:font-weight="bold" style:font-weight-asian="bold" style:font-weight-complex="bold" /></style:style> - <style:style style:name="T12" style:family="text"><style:text-properties fo:font-weight="bold" style:font-weight-asian="bold" style:font-weight-complex="bold" /></style:style> - <style:style style:name="T13" style:family="text"><style:text-properties fo:font-weight="bold" style:font-weight-asian="bold" style:font-weight-complex="bold" /></style:style> - <style:style style:name="T14" style:family="text"><style:text-properties fo:font-weight="bold" style:font-weight-asian="bold" style:font-weight-complex="bold" /></style:style> - <style:style style:name="T15" 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="T16" 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="T17" 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="T18" 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="T19" 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="T20" 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="T21" 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="T22" 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="T23" 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="T24" 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="T25" 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="T26" 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="T27" 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="T28" 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="T29" 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="T30" 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="T31" 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="T32" 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="T33" 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="T34" 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="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: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-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 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 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 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="T2" style:family="text"><style:text-properties fo:font-weight="bold" style:font-weight-asian="bold" style:font-weight-complex="bold" /></style:style> + <style:style style:name="T3" 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="T4" style:family="text"><style:text-properties style:text-line-through-style="solid" /></style:style> + <style:style style:name="T5" 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="T6" style:family="text"><style:text-properties style:text-position="super 58%" /></style:style> + <style:style style:name="T7" 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="T8" style:family="text"><style:text-properties style:text-position="sub 58%" /></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> @@ -871,7 +811,7 @@ link</text:span></text:a></text:h> <text:h text:style-name="Heading_20_5" text:outline-level="5">Level 5</text:h> <text:h text:style-name="Heading_20_1" text:outline-level="1">Level 1</text:h> <text:h text:style-name="Heading_20_2" text:outline-level="2">Level 2 with -<text:span text:style-name="T2">emphasis</text:span></text:h> +<text:span text:style-name="T1">emphasis</text:span></text:h> <text:h text:style-name="Heading_20_3" text:outline-level="3">Level 3</text:h> <text:p text:style-name="First_20_paragraph">with no blank line</text:p> <text:h text:style-name="Heading_20_2" text:outline-level="2">Level 2</text:h> @@ -1244,11 +1184,11 @@ fruit</text:p> <text:p text:style-name="Definition_20_Definition">yellow fruit</text:p> <text:p text:style-name="First_20_paragraph">Multiple blocks with italics:</text:p> -<text:p text:style-name="Definition_20_Term"><text:span text:style-name="T3">apple</text:span></text:p> +<text:p text:style-name="Definition_20_Term"><text:span text:style-name="T1">apple</text:span></text:p> <text:p text:style-name="Definition_20_Definition">red fruit</text:p><text:p text:style-name="Definition_20_Definition">contains seeds, crisp, pleasant to taste</text:p> -<text:p text:style-name="Definition_20_Term"><text:span text:style-name="T4">orange</text:span></text:p> +<text:p text:style-name="Definition_20_Term"><text:span text:style-name="T1">orange</text:span></text:p> <text:p text:style-name="Definition_20_Definition">orange fruit</text:p><text:p text:style-name="P42">{ orange code block }</text:p><text:p text:style-name="P43">orange block quote</text:p> <text:p text:style-name="First_20_paragraph">Multiple definitions, @@ -1295,9 +1235,9 @@ indentation:</text:p> <text:p text:style-name="Text_20_body">Interpreted markdown in a table:</text:p> <text:p text:style-name="Text_20_body">This is -<text:span text:style-name="T5">emphasized</text:span></text:p> +<text:span text:style-name="T1">emphasized</text:span></text:p> <text:p text:style-name="Text_20_body">And this is -<text:span text:style-name="T6">strong</text:span></text:p> +<text:span text:style-name="T2">strong</text:span></text:p> <text:p text:style-name="Text_20_body">Here’s a simple block:</text:p> <text:p text:style-name="Text_20_body">foo</text:p> <text:p text:style-name="Text_20_body">This should be a code block, @@ -1323,47 +1263,38 @@ spaces on the line:</text:p> <text:h text:style-name="Heading_20_1" text:outline-level="1">Inline Markup</text:h> <text:p text:style-name="First_20_paragraph">This is -<text:span text:style-name="T7">emphasized</text:span>, and so -<text:span text:style-name="T8">is</text:span><text:span text:style-name="T9"> -</text:span><text:span text:style-name="T10">this</text:span>.</text:p> +<text:span text:style-name="T1">emphasized</text:span>, and so +<text:span text:style-name="T1">is this</text:span>.</text:p> <text:p text:style-name="Text_20_body">This is -<text:span text:style-name="T11">strong</text:span>, and so -<text:span text:style-name="T12">is</text:span><text:span text:style-name="T13"> -</text:span><text:span text:style-name="T14">this</text:span>.</text:p> +<text:span text:style-name="T2">strong</text:span>, and so +<text:span text:style-name="T2">is this</text:span>.</text:p> <text:p text:style-name="Text_20_body">An -<text:a xlink:type="simple" xlink:href="/url" office:name=""><text:span text:style-name="Definition"><text:span text:style-name="T15">emphasized</text:span><text:span text:style-name="T16"> -</text:span><text:span text:style-name="T17">link</text:span></text:span></text:a>.</text:p> -<text:p text:style-name="Text_20_body"><text:span text:style-name="T18">This</text:span><text:span text:style-name="T19"> -</text:span><text:span text:style-name="T20">is</text:span><text:span text:style-name="T21"> -</text:span><text:span text:style-name="T22">strong</text:span><text:span text:style-name="T23"> -</text:span><text:span text:style-name="T24">and</text:span><text:span text:style-name="T25"> -</text:span><text:span text:style-name="T26">em.</text:span></text:p> +<text:a xlink:type="simple" xlink:href="/url" office:name=""><text:span text:style-name="Definition"><text:span text:style-name="T1">emphasized +link</text:span></text:span></text:a>.</text:p> +<text:p text:style-name="Text_20_body"><text:span text:style-name="T3">This is +strong and em.</text:span></text:p> <text:p text:style-name="Text_20_body">So is -<text:span text:style-name="T27">this</text:span> word.</text:p> -<text:p text:style-name="Text_20_body"><text:span text:style-name="T28">This</text:span><text:span text:style-name="T29"> -</text:span><text:span text:style-name="T30">is</text:span><text:span text:style-name="T31"> -</text:span><text:span text:style-name="T32">strong</text:span><text:span text:style-name="T33"> -</text:span><text:span text:style-name="T34">and</text:span><text:span text:style-name="T35"> -</text:span><text:span text:style-name="T36">em.</text:span></text:p> +<text:span text:style-name="T3">this</text:span> word.</text:p> +<text:p text:style-name="Text_20_body"><text:span text:style-name="T3">This is +strong and em.</text:span></text:p> <text:p text:style-name="Text_20_body">So is -<text:span text:style-name="T37">this</text:span> word.</text:p> +<text:span text:style-name="T3">this</text:span> word.</text:p> <text:p text:style-name="Text_20_body">This is code: <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"><text:span text:style-name="T4">This is +</text:span><text:span text:style-name="T5">strikeout</text:span><text:span text:style-name="T4">.</text:span></text:p> <text:p text:style-name="Text_20_body">Superscripts: -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> +a<text:span text:style-name="T6">bc</text:span>d +a<text:span text:style-name="T7">hello</text:span> +a<text:span text:style-name="T6">hello there</text:span>.</text:p> <text:p text:style-name="Text_20_body">Subscripts: -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> +H<text:span text:style-name="T8">2</text:span>O, +H<text:span text:style-name="T8">23</text:span>O, +H<text:span text:style-name="T8">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" /> @@ -1395,16 +1326,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="T50">x</text:span> ∈ <text:span text:style-name="T51">y</text:span></text:p> + <text:p text:style-name="P51"><text:span text:style-name="T1">x</text:span> ∈ <text:span text:style-name="T1">y</text:span></text:p> </text:list-item> <text:list-item> - <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:p text:style-name="P51"><text:span text:style-name="T1">α</text:span> ∧ <text:span text:style-name="T1">ω</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="T54">p</text:span>-Tree</text:p> + <text:p text:style-name="P51"><text:span text:style-name="T1">p</text:span>-Tree</text:p> </text:list-item> <text:list-item> <text:p text:style-name="P51">Here’s some display math: @@ -1412,7 +1343,7 @@ 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="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:span text:style-name="T1">α</text:span> + <text:span text:style-name="T1">ω</text:span> × <text:span text:style-name="T1">x</text:span><text:span text:style-name="T6">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> @@ -1423,7 +1354,7 @@ five.</text:p> </text:list-item> <text:list-item> <text:p text:style-name="P52">$22,000 is a - <text:span text:style-name="T59">lot</text:span> of money. So is $34,000. + <text:span text:style-name="T1">lot</text:span> of money. So is $34,000. (It worked if “lot” is emphasized.)</text:p> </text:list-item> <text:list-item> @@ -1432,10 +1363,7 @@ five.</text:p> <text:list-item> <text:p text:style-name="P52">Escaped <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> + <text:span text:style-name="T1">this should be emphasized</text:span> 23$.</text:p> </text:list-item> </text:list> @@ -1585,10 +1513,10 @@ 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="T67">not</text:span> be a footnote +should <text:span text:style-name="T1">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="T68">easier</text:span> to type. Inline notes +is <text:span text:style-name="T1">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="Source_Text">]</text:span> verbatim |