Opendocument writer: support new templates.
Also, don't generate unneeded style declarations. git-svn-id: https://pandoc.googlecode.com/svn/trunk@1731 788f1e2b-df1e-0410-8736-df70ead52e1b
This commit is contained in:
parent
9eb4107af9
commit
e0ab935353
4 changed files with 895 additions and 1291 deletions
|
@ -32,6 +32,7 @@ module Text.Pandoc.Writers.OpenDocument ( writeOpenDocument ) where
|
|||
import Text.Pandoc.Definition
|
||||
import Text.Pandoc.Shared
|
||||
import Text.Pandoc.XML
|
||||
import Text.Pandoc.Templates (renderTemplate)
|
||||
import Text.Pandoc.Readers.TeXMath
|
||||
import Text.PrettyPrint.HughesPJ hiding ( Str )
|
||||
import Text.Printf ( printf )
|
||||
|
@ -39,7 +40,6 @@ import Control.Applicative ( (<$>) )
|
|||
import Control.Arrow ( (***), (>>>) )
|
||||
import Control.Monad.State hiding ( when )
|
||||
import Data.Char (chr)
|
||||
import Data.List (intercalate)
|
||||
|
||||
-- | Auxiliary function to convert Plain block to Para.
|
||||
plainToPara :: Block -> Block
|
||||
|
@ -156,53 +156,37 @@ handleSpaces s
|
|||
rm ( x:xs) = char x <> rm xs
|
||||
rm [] = empty
|
||||
|
||||
-- | Convert list of authors to a docbook <author> section
|
||||
authorToOpenDocument :: [Char] -> Doc
|
||||
authorToOpenDocument name =
|
||||
if ',' `elem` name
|
||||
then -- last name first
|
||||
let (lastname, rest) = break (==',') name
|
||||
firstname = removeLeadingSpace rest
|
||||
in inParagraphTagsWithStyle "Author" $
|
||||
(text $ escapeStringForXML firstname) <+>
|
||||
(text $ escapeStringForXML lastname)
|
||||
else -- last name last
|
||||
let namewords = words name
|
||||
lengthname = length namewords
|
||||
(firstname, lastname) = case lengthname of
|
||||
0 -> ("","")
|
||||
1 -> ("", name)
|
||||
n -> (intercalate " " (take (n-1) namewords), last namewords)
|
||||
in inParagraphTagsWithStyle "Author" $
|
||||
(text $ escapeStringForXML firstname) <+>
|
||||
(text $ escapeStringForXML lastname)
|
||||
|
||||
-- | Convert Pandoc document to string in OpenDocument format.
|
||||
writeOpenDocument :: WriterOptions -> Pandoc -> String
|
||||
writeOpenDocument opts (Pandoc (Meta title authors date) blocks) =
|
||||
"" -- TODO
|
||||
-- let root = inTags True "office:document-content" openDocumentNameSpaces
|
||||
-- header = when (writerStandalone opts) $ text (writerHeader opts)
|
||||
-- title' = case runState (wrap opts title) defaultWriterState of
|
||||
-- (t,_) -> if isEmpty t then empty else inHeaderTags 1 t
|
||||
-- authors' = when (authors /= []) $ vcat (map authorToOpenDocument authors)
|
||||
-- date' = when (date /= []) $
|
||||
-- inParagraphTagsWithStyle "Date" (text $ escapeStringForXML date)
|
||||
-- meta = when (writerStandalone opts) $ title' $$ authors' $$ date'
|
||||
-- before = writerIncludeBefore opts
|
||||
-- after = writerIncludeAfter opts
|
||||
-- (doc, s) = runState (blocksToOpenDocument opts blocks) defaultWriterState
|
||||
-- body = (if null before then empty else text before) $$
|
||||
-- doc $$
|
||||
-- (if null after then empty else text after)
|
||||
-- body' = if writerStandalone opts
|
||||
-- then inTagsIndented "office:body" $
|
||||
-- inTagsIndented "office:text" (meta $$ body)
|
||||
-- else body
|
||||
-- styles = stTableStyles s ++ stParaStyles s ++ stTextStyles s
|
||||
-- listStyle (n,l) = inTags True "text:list-style" [("style:name", "L" ++ show n)] (vcat l)
|
||||
-- listStyles = map listStyle (stListStyles s)
|
||||
-- in render $ header $$ root (generateStyles (styles ++ listStyles) $$ body' $$ text "")
|
||||
let ((doc, title', authors', date'),s) = flip runState
|
||||
defaultWriterState $ do
|
||||
title'' <- inlinesToOpenDocument opts title
|
||||
authors'' <- mapM (inlinesToOpenDocument opts) authors
|
||||
date'' <- inlinesToOpenDocument opts date
|
||||
doc'' <- blocksToOpenDocument opts blocks
|
||||
return (doc'', title'', authors'', date'')
|
||||
before = writerIncludeBefore opts
|
||||
after = writerIncludeAfter opts
|
||||
body = (if null before then empty else text before) $$
|
||||
doc $$
|
||||
(if null after then empty else text after)
|
||||
body' = render body
|
||||
styles = stTableStyles s ++ stParaStyles s ++ stTextStyles s
|
||||
listStyle (n,l) = inTags True "text:list-style"
|
||||
[("style:name", "L" ++ show n)] (vcat l)
|
||||
listStyles = map listStyle (stListStyles s)
|
||||
automaticStyles = inTagsIndented "office:automatic-styles" $ vcat $
|
||||
reverse $ styles ++ listStyles
|
||||
context = writerVariables opts ++
|
||||
[ ("body", body')
|
||||
, ("automatic-styles", render automaticStyles)
|
||||
, ("title", render title')
|
||||
, ("date", render date') ] ++
|
||||
[ ("author", render a) | a <- authors' ]
|
||||
in if writerStandalone opts
|
||||
then renderTemplate context $ writerTemplate opts
|
||||
else body'
|
||||
|
||||
withParagraphStyle :: WriterOptions -> String -> [Block] -> State WriterState Doc
|
||||
withParagraphStyle o s (b:bs)
|
||||
|
@ -405,16 +389,6 @@ inlineToOpenDocument o ils
|
|||
addNote nn
|
||||
return nn
|
||||
|
||||
generateStyles :: [Doc] -> Doc
|
||||
generateStyles acc =
|
||||
let scripts = selfClosingTag "office:scripts" []
|
||||
fonts = inTagsIndented "office:font-face-decls"
|
||||
(vcat $ map font ["Lucida Sans Unicode", "Tahoma", "Times New Roman"])
|
||||
font fn = selfClosingTag "style:font-face"
|
||||
[ ("style:name" , "'" ++ fn ++ "'")
|
||||
, ("svg:font-family", fn )]
|
||||
in scripts $$ fonts $$ inTagsIndented "office:automatic-styles" (vcat $ reverse acc)
|
||||
|
||||
bulletListStyle :: Int -> State WriterState (Int,(Int,[Doc]))
|
||||
bulletListStyle l =
|
||||
let doStyles i = inTags True "text:list-level-style-bullet"
|
||||
|
@ -536,30 +510,3 @@ textStyleAttr s
|
|||
| SmallC <- s = [("fo:font-variant" ,"small-caps")]
|
||||
| otherwise = []
|
||||
|
||||
openDocumentNameSpaces :: [(String, String)]
|
||||
openDocumentNameSpaces =
|
||||
[ ("xmlns:office" , "urn:oasis:names:tc:opendocument:xmlns:office:1.0" )
|
||||
, ("xmlns:style" , "urn:oasis:names:tc:opendocument:xmlns:style:1.0" )
|
||||
, ("xmlns:text" , "urn:oasis:names:tc:opendocument:xmlns:text:1.0" )
|
||||
, ("xmlns:table" , "urn:oasis:names:tc:opendocument:xmlns:table:1.0" )
|
||||
, ("xmlns:draw" , "urn:oasis:names:tc:opendocument:xmlns:drawing:1.0" )
|
||||
, ("xmlns:fo" , "urn:oasis:names:tc:opendocument:xmlns:xsl-fo-compatible:1.0")
|
||||
, ("xmlns:xlink" , "http://www.w3.org/1999/xlink" )
|
||||
, ("xmlns:dc" , "http://purl.org/dc/elements/1.1/" )
|
||||
, ("xmlns:meta" , "urn:oasis:names:tc:opendocument:xmlns:meta:1.0" )
|
||||
, ("xmlns:number" , "urn:oasis:names:tc:opendocument:xmlns:datastyle:1.0" )
|
||||
, ("xmlns:svg" , "urn:oasis:names:tc:opendocument:xmlns:svg-compatible:1.0" )
|
||||
, ("xmlns:chart" , "urn:oasis:names:tc:opendocument:xmlns:chart:1.0" )
|
||||
, ("xmlns:dr3d" , "urn:oasis:names:tc:opendocument:xmlns:dr3d:1.0" )
|
||||
, ("xmlns:math" , "http://www.w3.org/1998/Math/MathML" )
|
||||
, ("xmlns:form" , "urn:oasis:names:tc:opendocument:xmlns:form:1.0" )
|
||||
, ("xmlns:script" , "urn:oasis:names:tc:opendocument:xmlns:script:1.0" )
|
||||
, ("xmlns:ooo" , "http://openoffice.org/2004/office" )
|
||||
, ("xmlns:ooow" , "http://openoffice.org/2004/writer" )
|
||||
, ("xmlns:oooc" , "http://openoffice.org/2004/calc" )
|
||||
, ("xmlns:dom" , "http://www.w3.org/2001/xml-events" )
|
||||
, ("xmlns:xforms" , "http://www.w3.org/2002/xforms" )
|
||||
, ("xmlns:xsd" , "http://www.w3.org/2001/XMLSchema" )
|
||||
, ("xmlns:xsi" , "http://www.w3.org/2001/XMLSchema-instance" )
|
||||
, ("office:version", "1.0" )
|
||||
]
|
||||
|
|
|
@ -1,75 +1,21 @@
|
|||
<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN" "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd">
|
||||
<html xmlns="http://www.w3.org/1999/xhtml"
|
||||
><head
|
||||
><title
|
||||
>title</title
|
||||
><meta http-equiv="Content-Type" content="text/html; charset=UTF-8"
|
||||
/><meta name="generator" content="pandoc"
|
||||
/><meta name="author" content="$authors$"
|
||||
/><meta name="date" content="$date$"
|
||||
/>$header-includes$
|
||||
</head
|
||||
><body
|
||||
>
|
||||
<h1 class="title"
|
||||
><span class="math"
|
||||
><em
|
||||
>title</em
|
||||
></span
|
||||
></h1
|
||||
><div id="TOC"
|
||||
><ul
|
||||
><li
|
||||
><a href="#section-oen"
|
||||
>section oen</a
|
||||
></li
|
||||
></ul
|
||||
></div
|
||||
><div id="section-oen"
|
||||
><h1
|
||||
><a href="#TOC"
|
||||
>section oen</a
|
||||
></h1
|
||||
><ol style="list-style-type: decimal;"
|
||||
><li
|
||||
>one<ol style="list-style-type: lower-alpha;"
|
||||
><li
|
||||
>two<ol start="3" style="list-style-type: lower-roman;"
|
||||
><li
|
||||
>three</li
|
||||
></ol
|
||||
></li
|
||||
></ol
|
||||
></li
|
||||
></ol
|
||||
><pre class="haskell"
|
||||
><code
|
||||
>hi
|
||||
</code
|
||||
></pre
|
||||
><p
|
||||
>footnote<a href="#fn1" class="footnoteRef" id="fnref1"
|
||||
><sup
|
||||
>1</sup
|
||||
></a
|
||||
></p
|
||||
></div
|
||||
><div class="footnotes"
|
||||
><hr
|
||||
/><ol
|
||||
><li id="fn1"
|
||||
><p
|
||||
>with code</p
|
||||
><pre
|
||||
><code
|
||||
>code
|
||||
</code
|
||||
></pre
|
||||
> <a href="#fnref1" class="footnoteBackLink" title="Jump back to footnote 1">↩</a></li
|
||||
></ol
|
||||
></div
|
||||
>
|
||||
</body
|
||||
></html
|
||||
>
|
||||
|
||||
<?xml version="1.0" encoding="utf-8" ?>
|
||||
<office:document-content xmlns:office="urn:oasis:names:tc:opendocument:xmlns:office:1.0" xmlns:style="urn:oasis:names:tc:opendocument:xmlns:style:1.0" xmlns:text="urn:oasis:names:tc:opendocument:xmlns:text:1.0" xmlns:table="urn:oasis:names:tc:opendocument:xmlns:table:1.0" xmlns:draw="urn:oasis:names:tc:opendocument:xmlns:drawing:1.0" xmlns:fo="urn:oasis:names:tc:opendocument:xmlns:xsl-fo-compatible:1.0" xmlns:xlink="http://www.w3.org/1999/xlink" xmlns:dc="http://purl.org/dc/elements/1.1/" xmlns:meta="urn:oasis:names:tc:opendocument:xmlns:meta:1.0" xmlns:number="urn:oasis:names:tc:opendocument:xmlns:datastyle:1.0" xmlns:svg="urn:oasis:names:tc:opendocument:xmlns:svg-compatible:1.0" xmlns:chart="urn:oasis:names:tc:opendocument:xmlns:chart:1.0" xmlns:dr3d="urn:oasis:names:tc:opendocument:xmlns:dr3d:1.0" xmlns:math="http://www.w3.org/1998/Math/MathML" xmlns:form="urn:oasis:names:tc:opendocument:xmlns:form:1.0" xmlns:script="urn:oasis:names:tc:opendocument:xmlns:script:1.0" xmlns:ooo="http://openoffice.org/2004/office" xmlns:ooow="http://openoffice.org/2004/writer" xmlns:oooc="http://openoffice.org/2004/calc" xmlns:dom="http://www.w3.org/2001/xml-events" xmlns:xforms="http://www.w3.org/2002/xforms" xmlns:xsd="http://www.w3.org/2001/XMLSchema" xmlns:xsi="http://www.w3.org/2001/XMLSchema-instance" office:version="1.0">
|
||||
$automatic-styles$
|
||||
$for(header-includes)$
|
||||
$header-includes$
|
||||
$endfor$
|
||||
<office:body>
|
||||
<office:text>
|
||||
$if(title)$
|
||||
<text:h text:style-name="Heading_20_1" text:outline-level="1">$title$</text:h>
|
||||
$endif$
|
||||
$for(author)$
|
||||
<text:p text:style-name="Author">$author$</text:p>
|
||||
$endfor$
|
||||
$if(date)$
|
||||
<text:p text:style-name="Date">$date$</text:p>
|
||||
$endif$
|
||||
$body$
|
||||
</office:text>
|
||||
</office:body>
|
||||
</office:document-content>
|
||||
|
|
|
@ -1,442 +1,300 @@
|
|||
<office:document-content xmlns:office="urn:oasis:names:tc:opendocument:xmlns:office:1.0" xmlns:style="urn:oasis:names:tc:opendocument:xmlns:style:1.0" xmlns:text="urn:oasis:names:tc:opendocument:xmlns:text:1.0" xmlns:table="urn:oasis:names:tc:opendocument:xmlns:table:1.0" xmlns:draw="urn:oasis:names:tc:opendocument:xmlns:drawing:1.0" xmlns:fo="urn:oasis:names:tc:opendocument:xmlns:xsl-fo-compatible:1.0" xmlns:xlink="http://www.w3.org/1999/xlink" xmlns:dc="http://purl.org/dc/elements/1.1/" xmlns:meta="urn:oasis:names:tc:opendocument:xmlns:meta:1.0" xmlns:number="urn:oasis:names:tc:opendocument:xmlns:datastyle:1.0" xmlns:svg="urn:oasis:names:tc:opendocument:xmlns:svg-compatible:1.0" xmlns:chart="urn:oasis:names:tc:opendocument:xmlns:chart:1.0" xmlns:dr3d="urn:oasis:names:tc:opendocument:xmlns:dr3d:1.0" xmlns:math="http://www.w3.org/1998/Math/MathML" xmlns:form="urn:oasis:names:tc:opendocument:xmlns:form:1.0" xmlns:script="urn:oasis:names:tc:opendocument:xmlns:script:1.0" xmlns:ooo="http://openoffice.org/2004/office" xmlns:ooow="http://openoffice.org/2004/writer" xmlns:oooc="http://openoffice.org/2004/calc" xmlns:dom="http://www.w3.org/2001/xml-events" xmlns:xforms="http://www.w3.org/2002/xforms" xmlns:xsd="http://www.w3.org/2001/XMLSchema" xmlns:xsi="http://www.w3.org/2001/XMLSchema-instance" office:version="1.0">
|
||||
<office:scripts />
|
||||
<office:font-face-decls>
|
||||
<style:font-face style:name="&apos;Lucida Sans Unicode&apos;" svg:font-family="Lucida Sans Unicode" />
|
||||
<style:font-face style:name="&apos;Tahoma&apos;" svg:font-family="Tahoma" />
|
||||
<style:font-face style:name="&apos;Times New Roman&apos;" svg:font-family="Times New Roman" />
|
||||
</office:font-face-decls>
|
||||
<office:automatic-styles>
|
||||
<style:style style:name="P1" style:family="paragraph" style:parent-style-name="Table_20_Heading">
|
||||
<style:paragraph-properties fo:text-align="end" style:justify-single-word="false" />
|
||||
</style:style>
|
||||
<style:style style:name="P2" style:family="paragraph" style:parent-style-name="Table_20_Heading">
|
||||
<style:paragraph-properties fo:text-align="center" style:justify-single-word="false" />
|
||||
</style:style>
|
||||
<style:style style:name="P3" style:family="paragraph" style:parent-style-name="Table_20_Contents">
|
||||
<style:paragraph-properties fo:text-align="end" style:justify-single-word="false" />
|
||||
</style:style>
|
||||
<style:style style:name="P4" style:family="paragraph" style:parent-style-name="Table_20_Contents">
|
||||
<style:paragraph-properties fo:text-align="center" style:justify-single-word="false" />
|
||||
</style:style>
|
||||
<style:style style:name="P5" style:family="paragraph" style:parent-style-name="Table_20_Heading">
|
||||
<style:paragraph-properties fo:text-align="end" style:justify-single-word="false" />
|
||||
</style:style>
|
||||
<style:style style:name="P6" style:family="paragraph" style:parent-style-name="Table_20_Heading">
|
||||
<style:paragraph-properties fo:text-align="center" style:justify-single-word="false" />
|
||||
</style:style>
|
||||
<style:style style:name="P7" style:family="paragraph" style:parent-style-name="Table_20_Contents">
|
||||
<style:paragraph-properties fo:text-align="end" style:justify-single-word="false" />
|
||||
</style:style>
|
||||
<style:style style:name="P8" style:family="paragraph" style:parent-style-name="Table_20_Contents">
|
||||
<style:paragraph-properties fo:text-align="center" style:justify-single-word="false" />
|
||||
</style:style>
|
||||
<style:style style:name="P9" style:family="paragraph" style:parent-style-name="Table_20_Heading">
|
||||
<style:paragraph-properties fo:text-align="end" style:justify-single-word="false" />
|
||||
</style:style>
|
||||
<style:style style:name="P10" style:family="paragraph" style:parent-style-name="Table_20_Heading">
|
||||
<style:paragraph-properties fo:text-align="center" style:justify-single-word="false" />
|
||||
</style:style>
|
||||
<style:style style:name="P11" style:family="paragraph" style:parent-style-name="Table_20_Contents">
|
||||
<style:paragraph-properties fo:text-align="end" style:justify-single-word="false" />
|
||||
</style:style>
|
||||
<style:style style:name="P12" style:family="paragraph" style:parent-style-name="Table_20_Contents">
|
||||
<style:paragraph-properties fo:text-align="center" style:justify-single-word="false" />
|
||||
</style:style>
|
||||
<style:style style:name="P13" style:family="paragraph" style:parent-style-name="Table_20_Heading">
|
||||
<style:paragraph-properties fo:text-align="center" style:justify-single-word="false" />
|
||||
</style:style>
|
||||
<style:style style:name="P14" style:family="paragraph" style:parent-style-name="Table_20_Heading">
|
||||
<style:paragraph-properties fo:text-align="end" style:justify-single-word="false" />
|
||||
</style:style>
|
||||
<style:style style:name="P15" style:family="paragraph" style:parent-style-name="Table_20_Contents">
|
||||
<style:paragraph-properties fo:text-align="center" style:justify-single-word="false" />
|
||||
</style:style>
|
||||
<style:style style:name="P16" style:family="paragraph" style:parent-style-name="Table_20_Contents">
|
||||
<style:paragraph-properties fo:text-align="end" style:justify-single-word="false" />
|
||||
</style:style>
|
||||
<style:style style:name="P17" style:family="paragraph" style:parent-style-name="Table_20_Heading">
|
||||
<style:paragraph-properties fo:text-align="center" style:justify-single-word="false" />
|
||||
</style:style>
|
||||
<style:style style:name="P18" style:family="paragraph" style:parent-style-name="Table_20_Heading">
|
||||
<style:paragraph-properties fo:text-align="end" style:justify-single-word="false" />
|
||||
</style:style>
|
||||
<style:style style:name="P19" style:family="paragraph" style:parent-style-name="Table_20_Contents">
|
||||
<style:paragraph-properties fo:text-align="center" style:justify-single-word="false" />
|
||||
</style:style>
|
||||
<style:style style:name="P20" style:family="paragraph" style:parent-style-name="Table_20_Contents">
|
||||
<style:paragraph-properties fo:text-align="end" style:justify-single-word="false" />
|
||||
</style:style>
|
||||
<style:style style:name="Table1">
|
||||
<style:table-properties table:align="center" />
|
||||
</style:style>
|
||||
<style:style style:name="Table1.A" style:family="table-column" />
|
||||
<style:style style:name="Table1.B" style:family="table-column" />
|
||||
<style:style style:name="Table1.C" style:family="table-column" />
|
||||
<style:style style:name="Table1.D" style:family="table-column" />
|
||||
<style:style style:name="Table1.A1" style:family="table-cell">
|
||||
<style:table-cell-properties fo:border="none" />
|
||||
</style:style>
|
||||
<style:style style:name="Table2">
|
||||
<style:table-properties table:align="center" />
|
||||
</style:style>
|
||||
<style:style style:name="Table2.A" style:family="table-column" />
|
||||
<style:style style:name="Table2.B" style:family="table-column" />
|
||||
<style:style style:name="Table2.C" style:family="table-column" />
|
||||
<style:style style:name="Table2.D" style:family="table-column" />
|
||||
<style:style style:name="Table2.A1" style:family="table-cell">
|
||||
<style:table-cell-properties fo:border="none" />
|
||||
</style:style>
|
||||
<style:style style:name="Table3">
|
||||
<style:table-properties table:align="center" />
|
||||
</style:style>
|
||||
<style:style style:name="Table3.A" style:family="table-column" />
|
||||
<style:style style:name="Table3.B" style:family="table-column" />
|
||||
<style:style style:name="Table3.C" style:family="table-column" />
|
||||
<style:style style:name="Table3.D" style:family="table-column" />
|
||||
<style:style style:name="Table3.A1" style:family="table-cell">
|
||||
<style:table-cell-properties fo:border="none" />
|
||||
</style:style>
|
||||
<style:style style:name="Table4">
|
||||
<style:table-properties table:align="center" />
|
||||
</style:style>
|
||||
<style:style style:name="Table4.A" style:family="table-column">
|
||||
<style:table-column-properties style:rel-column-width="9830*" />
|
||||
</style:style>
|
||||
<style:style style:name="Table4.B" style:family="table-column">
|
||||
<style:table-column-properties style:rel-column-width="9011*" />
|
||||
</style:style>
|
||||
<style:style style:name="Table4.C" style:family="table-column">
|
||||
<style:table-column-properties style:rel-column-width="10649*" />
|
||||
</style:style>
|
||||
<style:style style:name="Table4.D" style:family="table-column">
|
||||
<style:table-column-properties style:rel-column-width="22118*" />
|
||||
</style:style>
|
||||
<style:style style:name="Table4.A1" style:family="table-cell">
|
||||
<style:table-cell-properties fo:border="none" />
|
||||
</style:style>
|
||||
<style:style style:name="Table5">
|
||||
<style:table-properties table:align="center" />
|
||||
</style:style>
|
||||
<style:style style:name="Table5.A" style:family="table-column">
|
||||
<style:table-column-properties style:rel-column-width="9830*" />
|
||||
</style:style>
|
||||
<style:style style:name="Table5.B" style:family="table-column">
|
||||
<style:table-column-properties style:rel-column-width="9011*" />
|
||||
</style:style>
|
||||
<style:style style:name="Table5.C" style:family="table-column">
|
||||
<style:table-column-properties style:rel-column-width="10649*" />
|
||||
</style:style>
|
||||
<style:style style:name="Table5.D" style:family="table-column">
|
||||
<style:table-column-properties style:rel-column-width="22118*" />
|
||||
</style:style>
|
||||
<style:style style:name="Table5.A1" style:family="table-cell">
|
||||
<style:table-cell-properties fo:border="none" />
|
||||
</style:style>
|
||||
</office:automatic-styles>
|
||||
<text:p text:style-name="Text_20_body">Simple table with
|
||||
caption:</text:p>
|
||||
<table:table table:name="Table1" table:style-name="Table1">
|
||||
<table:table-column table:style-name="Table1.A" />
|
||||
<table:table-column table:style-name="Table1.B" />
|
||||
<table:table-column table:style-name="Table1.C" />
|
||||
<table:table-column table:style-name="Table1.D" />
|
||||
<table:table-header-rows>
|
||||
<table:table-row>
|
||||
<table:table-cell table:style-name="Table1.A1" office:value-type="string">
|
||||
<text:p text:style-name="P1">Right</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table1.A1" office:value-type="string">
|
||||
<text:p text:style-name="Table_20_Heading">Left</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table1.A1" office:value-type="string">
|
||||
<text:p text:style-name="P2">Center</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table1.A1" office:value-type="string">
|
||||
<text:p text:style-name="Table_20_Heading">Default</text:p>
|
||||
</table:table-cell>
|
||||
</table:table-row>
|
||||
</table:table-header-rows>
|
||||
<text:p text:style-name="Text_20_body">Simple table with caption:</text:p>
|
||||
<table:table table:name="Table1" table:style-name="Table1">
|
||||
<table:table-column table:style-name="Table1.A" />
|
||||
<table:table-column table:style-name="Table1.B" />
|
||||
<table:table-column table:style-name="Table1.C" />
|
||||
<table:table-column table:style-name="Table1.D" />
|
||||
<table:table-header-rows>
|
||||
<table:table-row>
|
||||
<table:table-cell table:style-name="Table1.A1" office:value-type="string">
|
||||
<text:p text:style-name="P3">12</text:p>
|
||||
<text:p text:style-name="P1">Right</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table1.A1" office:value-type="string">
|
||||
<text:p text:style-name="Table_20_Contents">12</text:p>
|
||||
<text:p text:style-name="Table_20_Heading">Left</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table1.A1" office:value-type="string">
|
||||
<text:p text:style-name="P4">12</text:p>
|
||||
<text:p text:style-name="P2">Center</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table1.A1" office:value-type="string">
|
||||
<text:p text:style-name="Table_20_Contents">12</text:p>
|
||||
<text:p text:style-name="Table_20_Heading">Default</text:p>
|
||||
</table:table-cell>
|
||||
</table:table-row>
|
||||
<table:table-row>
|
||||
<table:table-cell table:style-name="Table1.A1" office:value-type="string">
|
||||
<text:p text:style-name="P3">123</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table1.A1" office:value-type="string">
|
||||
<text:p text:style-name="Table_20_Contents">123</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table1.A1" office:value-type="string">
|
||||
<text:p text:style-name="P4">123</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table1.A1" office:value-type="string">
|
||||
<text:p text:style-name="Table_20_Contents">123</text:p>
|
||||
</table:table-cell>
|
||||
</table:table-row>
|
||||
<table:table-row>
|
||||
<table:table-cell table:style-name="Table1.A1" office:value-type="string">
|
||||
<text:p text:style-name="P3">1</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table1.A1" office:value-type="string">
|
||||
<text:p text:style-name="Table_20_Contents">1</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table1.A1" office:value-type="string">
|
||||
<text:p text:style-name="P4">1</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table1.A1" office:value-type="string">
|
||||
<text:p text:style-name="Table_20_Contents">1</text:p>
|
||||
</table:table-cell>
|
||||
</table:table-row>
|
||||
</table:table>
|
||||
<text:p text:style-name="Caption">Demonstration of simple table syntax.</text:p>
|
||||
<text:p text:style-name="Text_20_body">Simple table without
|
||||
caption:</text:p>
|
||||
<table:table table:name="Table2" table:style-name="Table2">
|
||||
<table:table-column table:style-name="Table2.A" />
|
||||
<table:table-column table:style-name="Table2.B" />
|
||||
<table:table-column table:style-name="Table2.C" />
|
||||
<table:table-column table:style-name="Table2.D" />
|
||||
<table:table-header-rows>
|
||||
<table:table-row>
|
||||
<table:table-cell table:style-name="Table2.A1" office:value-type="string">
|
||||
<text:p text:style-name="P5">Right</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table2.A1" office:value-type="string">
|
||||
<text:p text:style-name="Table_20_Heading">Left</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table2.A1" office:value-type="string">
|
||||
<text:p text:style-name="P6">Center</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table2.A1" office:value-type="string">
|
||||
<text:p text:style-name="Table_20_Heading">Default</text:p>
|
||||
</table:table-cell>
|
||||
</table:table-row>
|
||||
</table:table-header-rows>
|
||||
</table:table-header-rows>
|
||||
<table:table-row>
|
||||
<table:table-cell table:style-name="Table1.A1" office:value-type="string">
|
||||
<text:p text:style-name="P3">12</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table1.A1" office:value-type="string">
|
||||
<text:p text:style-name="Table_20_Contents">12</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table1.A1" office:value-type="string">
|
||||
<text:p text:style-name="P4">12</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table1.A1" office:value-type="string">
|
||||
<text:p text:style-name="Table_20_Contents">12</text:p>
|
||||
</table:table-cell>
|
||||
</table:table-row>
|
||||
<table:table-row>
|
||||
<table:table-cell table:style-name="Table1.A1" office:value-type="string">
|
||||
<text:p text:style-name="P3">123</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table1.A1" office:value-type="string">
|
||||
<text:p text:style-name="Table_20_Contents">123</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table1.A1" office:value-type="string">
|
||||
<text:p text:style-name="P4">123</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table1.A1" office:value-type="string">
|
||||
<text:p text:style-name="Table_20_Contents">123</text:p>
|
||||
</table:table-cell>
|
||||
</table:table-row>
|
||||
<table:table-row>
|
||||
<table:table-cell table:style-name="Table1.A1" office:value-type="string">
|
||||
<text:p text:style-name="P3">1</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table1.A1" office:value-type="string">
|
||||
<text:p text:style-name="Table_20_Contents">1</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table1.A1" office:value-type="string">
|
||||
<text:p text:style-name="P4">1</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table1.A1" office:value-type="string">
|
||||
<text:p text:style-name="Table_20_Contents">1</text:p>
|
||||
</table:table-cell>
|
||||
</table:table-row>
|
||||
</table:table>
|
||||
<text:p text:style-name="Caption">Demonstration of simple table syntax.</text:p>
|
||||
<text:p text:style-name="Text_20_body">Simple table without caption:</text:p>
|
||||
<table:table table:name="Table2" table:style-name="Table2">
|
||||
<table:table-column table:style-name="Table2.A" />
|
||||
<table:table-column table:style-name="Table2.B" />
|
||||
<table:table-column table:style-name="Table2.C" />
|
||||
<table:table-column table:style-name="Table2.D" />
|
||||
<table:table-header-rows>
|
||||
<table:table-row>
|
||||
<table:table-cell table:style-name="Table2.A1" office:value-type="string">
|
||||
<text:p text:style-name="P7">12</text:p>
|
||||
<text:p text:style-name="P5">Right</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table2.A1" office:value-type="string">
|
||||
<text:p text:style-name="Table_20_Contents">12</text:p>
|
||||
<text:p text:style-name="Table_20_Heading">Left</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table2.A1" office:value-type="string">
|
||||
<text:p text:style-name="P8">12</text:p>
|
||||
<text:p text:style-name="P6">Center</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table2.A1" office:value-type="string">
|
||||
<text:p text:style-name="Table_20_Contents">12</text:p>
|
||||
<text:p text:style-name="Table_20_Heading">Default</text:p>
|
||||
</table:table-cell>
|
||||
</table:table-row>
|
||||
<table:table-row>
|
||||
<table:table-cell table:style-name="Table2.A1" office:value-type="string">
|
||||
<text:p text:style-name="P7">123</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table2.A1" office:value-type="string">
|
||||
<text:p text:style-name="Table_20_Contents">123</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table2.A1" office:value-type="string">
|
||||
<text:p text:style-name="P8">123</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table2.A1" office:value-type="string">
|
||||
<text:p text:style-name="Table_20_Contents">123</text:p>
|
||||
</table:table-cell>
|
||||
</table:table-row>
|
||||
<table:table-row>
|
||||
<table:table-cell table:style-name="Table2.A1" office:value-type="string">
|
||||
<text:p text:style-name="P7">1</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table2.A1" office:value-type="string">
|
||||
<text:p text:style-name="Table_20_Contents">1</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table2.A1" office:value-type="string">
|
||||
<text:p text:style-name="P8">1</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table2.A1" office:value-type="string">
|
||||
<text:p text:style-name="Table_20_Contents">1</text:p>
|
||||
</table:table-cell>
|
||||
</table:table-row>
|
||||
</table:table>
|
||||
<text:p text:style-name="Text_20_body">Simple table indented two
|
||||
spaces:</text:p>
|
||||
<table:table table:name="Table3" table:style-name="Table3">
|
||||
<table:table-column table:style-name="Table3.A" />
|
||||
<table:table-column table:style-name="Table3.B" />
|
||||
<table:table-column table:style-name="Table3.C" />
|
||||
<table:table-column table:style-name="Table3.D" />
|
||||
<table:table-header-rows>
|
||||
<table:table-row>
|
||||
<table:table-cell table:style-name="Table3.A1" office:value-type="string">
|
||||
<text:p text:style-name="P9">Right</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table3.A1" office:value-type="string">
|
||||
<text:p text:style-name="Table_20_Heading">Left</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table3.A1" office:value-type="string">
|
||||
<text:p text:style-name="P10">Center</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table3.A1" office:value-type="string">
|
||||
<text:p text:style-name="Table_20_Heading">Default</text:p>
|
||||
</table:table-cell>
|
||||
</table:table-row>
|
||||
</table:table-header-rows>
|
||||
</table:table-header-rows>
|
||||
<table:table-row>
|
||||
<table:table-cell table:style-name="Table2.A1" office:value-type="string">
|
||||
<text:p text:style-name="P7">12</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table2.A1" office:value-type="string">
|
||||
<text:p text:style-name="Table_20_Contents">12</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table2.A1" office:value-type="string">
|
||||
<text:p text:style-name="P8">12</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table2.A1" office:value-type="string">
|
||||
<text:p text:style-name="Table_20_Contents">12</text:p>
|
||||
</table:table-cell>
|
||||
</table:table-row>
|
||||
<table:table-row>
|
||||
<table:table-cell table:style-name="Table2.A1" office:value-type="string">
|
||||
<text:p text:style-name="P7">123</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table2.A1" office:value-type="string">
|
||||
<text:p text:style-name="Table_20_Contents">123</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table2.A1" office:value-type="string">
|
||||
<text:p text:style-name="P8">123</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table2.A1" office:value-type="string">
|
||||
<text:p text:style-name="Table_20_Contents">123</text:p>
|
||||
</table:table-cell>
|
||||
</table:table-row>
|
||||
<table:table-row>
|
||||
<table:table-cell table:style-name="Table2.A1" office:value-type="string">
|
||||
<text:p text:style-name="P7">1</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table2.A1" office:value-type="string">
|
||||
<text:p text:style-name="Table_20_Contents">1</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table2.A1" office:value-type="string">
|
||||
<text:p text:style-name="P8">1</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table2.A1" office:value-type="string">
|
||||
<text:p text:style-name="Table_20_Contents">1</text:p>
|
||||
</table:table-cell>
|
||||
</table:table-row>
|
||||
</table:table>
|
||||
<text:p text:style-name="Text_20_body">Simple table indented two spaces:</text:p>
|
||||
<table:table table:name="Table3" table:style-name="Table3">
|
||||
<table:table-column table:style-name="Table3.A" />
|
||||
<table:table-column table:style-name="Table3.B" />
|
||||
<table:table-column table:style-name="Table3.C" />
|
||||
<table:table-column table:style-name="Table3.D" />
|
||||
<table:table-header-rows>
|
||||
<table:table-row>
|
||||
<table:table-cell table:style-name="Table3.A1" office:value-type="string">
|
||||
<text:p text:style-name="P11">12</text:p>
|
||||
<text:p text:style-name="P9">Right</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table3.A1" office:value-type="string">
|
||||
<text:p text:style-name="Table_20_Contents">12</text:p>
|
||||
<text:p text:style-name="Table_20_Heading">Left</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table3.A1" office:value-type="string">
|
||||
<text:p text:style-name="P12">12</text:p>
|
||||
<text:p text:style-name="P10">Center</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table3.A1" office:value-type="string">
|
||||
<text:p text:style-name="Table_20_Contents">12</text:p>
|
||||
<text:p text:style-name="Table_20_Heading">Default</text:p>
|
||||
</table:table-cell>
|
||||
</table:table-row>
|
||||
<table:table-row>
|
||||
<table:table-cell table:style-name="Table3.A1" office:value-type="string">
|
||||
<text:p text:style-name="P11">123</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table3.A1" office:value-type="string">
|
||||
<text:p text:style-name="Table_20_Contents">123</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table3.A1" office:value-type="string">
|
||||
<text:p text:style-name="P12">123</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table3.A1" office:value-type="string">
|
||||
<text:p text:style-name="Table_20_Contents">123</text:p>
|
||||
</table:table-cell>
|
||||
</table:table-row>
|
||||
<table:table-row>
|
||||
<table:table-cell table:style-name="Table3.A1" office:value-type="string">
|
||||
<text:p text:style-name="P11">1</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table3.A1" office:value-type="string">
|
||||
<text:p text:style-name="Table_20_Contents">1</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table3.A1" office:value-type="string">
|
||||
<text:p text:style-name="P12">1</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table3.A1" office:value-type="string">
|
||||
<text:p text:style-name="Table_20_Contents">1</text:p>
|
||||
</table:table-cell>
|
||||
</table:table-row>
|
||||
</table:table>
|
||||
<text:p text:style-name="Caption">Demonstration of simple table syntax.</text:p>
|
||||
<text:p text:style-name="Text_20_body">Multiline table with
|
||||
caption:</text:p>
|
||||
<table:table table:name="Table4" table:style-name="Table4">
|
||||
<table:table-column table:style-name="Table4.A" />
|
||||
<table:table-column table:style-name="Table4.B" />
|
||||
<table:table-column table:style-name="Table4.C" />
|
||||
<table:table-column table:style-name="Table4.D" />
|
||||
<table:table-header-rows>
|
||||
<table:table-row>
|
||||
<table:table-cell table:style-name="Table4.A1" office:value-type="string">
|
||||
<text:p text:style-name="P13">Centered Header</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table4.A1" office:value-type="string">
|
||||
<text:p text:style-name="Table_20_Heading">Left Aligned</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table4.A1" office:value-type="string">
|
||||
<text:p text:style-name="P14">Right Aligned</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table4.A1" office:value-type="string">
|
||||
<text:p text:style-name="Table_20_Heading">Default aligned</text:p>
|
||||
</table:table-cell>
|
||||
</table:table-row>
|
||||
</table:table-header-rows>
|
||||
</table:table-header-rows>
|
||||
<table:table-row>
|
||||
<table:table-cell table:style-name="Table3.A1" office:value-type="string">
|
||||
<text:p text:style-name="P11">12</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table3.A1" office:value-type="string">
|
||||
<text:p text:style-name="Table_20_Contents">12</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table3.A1" office:value-type="string">
|
||||
<text:p text:style-name="P12">12</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table3.A1" office:value-type="string">
|
||||
<text:p text:style-name="Table_20_Contents">12</text:p>
|
||||
</table:table-cell>
|
||||
</table:table-row>
|
||||
<table:table-row>
|
||||
<table:table-cell table:style-name="Table3.A1" office:value-type="string">
|
||||
<text:p text:style-name="P11">123</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table3.A1" office:value-type="string">
|
||||
<text:p text:style-name="Table_20_Contents">123</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table3.A1" office:value-type="string">
|
||||
<text:p text:style-name="P12">123</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table3.A1" office:value-type="string">
|
||||
<text:p text:style-name="Table_20_Contents">123</text:p>
|
||||
</table:table-cell>
|
||||
</table:table-row>
|
||||
<table:table-row>
|
||||
<table:table-cell table:style-name="Table3.A1" office:value-type="string">
|
||||
<text:p text:style-name="P11">1</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table3.A1" office:value-type="string">
|
||||
<text:p text:style-name="Table_20_Contents">1</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table3.A1" office:value-type="string">
|
||||
<text:p text:style-name="P12">1</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table3.A1" office:value-type="string">
|
||||
<text:p text:style-name="Table_20_Contents">1</text:p>
|
||||
</table:table-cell>
|
||||
</table:table-row>
|
||||
</table:table>
|
||||
<text:p text:style-name="Caption">Demonstration of simple table syntax.</text:p>
|
||||
<text:p text:style-name="Text_20_body">Multiline table with caption:</text:p>
|
||||
<table:table table:name="Table4" table:style-name="Table4">
|
||||
<table:table-column table:style-name="Table4.A" />
|
||||
<table:table-column table:style-name="Table4.B" />
|
||||
<table:table-column table:style-name="Table4.C" />
|
||||
<table:table-column table:style-name="Table4.D" />
|
||||
<table:table-header-rows>
|
||||
<table:table-row>
|
||||
<table:table-cell table:style-name="Table4.A1" office:value-type="string">
|
||||
<text:p text:style-name="P15">First</text:p>
|
||||
<text:p text:style-name="P13">Centered Header</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table4.A1" office:value-type="string">
|
||||
<text:p text:style-name="Table_20_Contents">row</text:p>
|
||||
<text:p text:style-name="Table_20_Heading">Left Aligned</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table4.A1" office:value-type="string">
|
||||
<text:p text:style-name="P16">12.0</text:p>
|
||||
<text:p text:style-name="P14">Right Aligned</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table4.A1" office:value-type="string">
|
||||
<text:p text:style-name="Table_20_Contents">Example of a row that spans multiple lines.</text:p>
|
||||
<text:p text:style-name="Table_20_Heading">Default aligned</text:p>
|
||||
</table:table-cell>
|
||||
</table:table-row>
|
||||
<table:table-row>
|
||||
<table:table-cell table:style-name="Table4.A1" office:value-type="string">
|
||||
<text:p text:style-name="P15">Second</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table4.A1" office:value-type="string">
|
||||
<text:p text:style-name="Table_20_Contents">row</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table4.A1" office:value-type="string">
|
||||
<text:p text:style-name="P16">5.0</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table4.A1" office:value-type="string">
|
||||
<text:p text:style-name="Table_20_Contents">Here's another one. Note the blank line between rows.</text:p>
|
||||
</table:table-cell>
|
||||
</table:table-row>
|
||||
</table:table>
|
||||
<text:p text:style-name="Caption">Here's the caption. It may span multiple lines.</text:p>
|
||||
<text:p text:style-name="Text_20_body">Multiline table without
|
||||
caption:</text:p>
|
||||
<table:table table:name="Table5" table:style-name="Table5">
|
||||
<table:table-column table:style-name="Table5.A" />
|
||||
<table:table-column table:style-name="Table5.B" />
|
||||
<table:table-column table:style-name="Table5.C" />
|
||||
<table:table-column table:style-name="Table5.D" />
|
||||
<table:table-header-rows>
|
||||
<table:table-row>
|
||||
<table:table-cell table:style-name="Table5.A1" office:value-type="string">
|
||||
<text:p text:style-name="P17">Centered Header</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table5.A1" office:value-type="string">
|
||||
<text:p text:style-name="Table_20_Heading">Left Aligned</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table5.A1" office:value-type="string">
|
||||
<text:p text:style-name="P18">Right Aligned</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table5.A1" office:value-type="string">
|
||||
<text:p text:style-name="Table_20_Heading">Default aligned</text:p>
|
||||
</table:table-cell>
|
||||
</table:table-row>
|
||||
</table:table-header-rows>
|
||||
</table:table-header-rows>
|
||||
<table:table-row>
|
||||
<table:table-cell table:style-name="Table4.A1" office:value-type="string">
|
||||
<text:p text:style-name="P15">First</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table4.A1" office:value-type="string">
|
||||
<text:p text:style-name="Table_20_Contents">row</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table4.A1" office:value-type="string">
|
||||
<text:p text:style-name="P16">12.0</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table4.A1" office:value-type="string">
|
||||
<text:p text:style-name="Table_20_Contents">Example of a row that spans multiple lines.</text:p>
|
||||
</table:table-cell>
|
||||
</table:table-row>
|
||||
<table:table-row>
|
||||
<table:table-cell table:style-name="Table4.A1" office:value-type="string">
|
||||
<text:p text:style-name="P15">Second</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table4.A1" office:value-type="string">
|
||||
<text:p text:style-name="Table_20_Contents">row</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table4.A1" office:value-type="string">
|
||||
<text:p text:style-name="P16">5.0</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table4.A1" office:value-type="string">
|
||||
<text:p text:style-name="Table_20_Contents">Here's another one. Note the blank line between rows.</text:p>
|
||||
</table:table-cell>
|
||||
</table:table-row>
|
||||
</table:table>
|
||||
<text:p text:style-name="Caption">Here's the caption. It may span multiple lines.</text:p>
|
||||
<text:p text:style-name="Text_20_body">Multiline table without caption:</text:p>
|
||||
<table:table table:name="Table5" table:style-name="Table5">
|
||||
<table:table-column table:style-name="Table5.A" />
|
||||
<table:table-column table:style-name="Table5.B" />
|
||||
<table:table-column table:style-name="Table5.C" />
|
||||
<table:table-column table:style-name="Table5.D" />
|
||||
<table:table-header-rows>
|
||||
<table:table-row>
|
||||
<table:table-cell table:style-name="Table5.A1" office:value-type="string">
|
||||
<text:p text:style-name="P19">First</text:p>
|
||||
<text:p text:style-name="P17">Centered Header</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table5.A1" office:value-type="string">
|
||||
<text:p text:style-name="Table_20_Contents">row</text:p>
|
||||
<text:p text:style-name="Table_20_Heading">Left Aligned</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table5.A1" office:value-type="string">
|
||||
<text:p text:style-name="P20">12.0</text:p>
|
||||
<text:p text:style-name="P18">Right Aligned</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table5.A1" office:value-type="string">
|
||||
<text:p text:style-name="Table_20_Contents">Example of a row that spans multiple lines.</text:p>
|
||||
<text:p text:style-name="Table_20_Heading">Default aligned</text:p>
|
||||
</table:table-cell>
|
||||
</table:table-row>
|
||||
<table:table-row>
|
||||
<table:table-cell table:style-name="Table5.A1" office:value-type="string">
|
||||
<text:p text:style-name="P19">Second</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table5.A1" office:value-type="string">
|
||||
<text:p text:style-name="Table_20_Contents">row</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table5.A1" office:value-type="string">
|
||||
<text:p text:style-name="P20">5.0</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table5.A1" office:value-type="string">
|
||||
<text:p text:style-name="Table_20_Contents">Here's another one. Note the blank line between rows.</text:p>
|
||||
</table:table-cell>
|
||||
</table:table-row>
|
||||
</table:table>
|
||||
|
||||
</office:document-content>
|
||||
</table:table-header-rows>
|
||||
<table:table-row>
|
||||
<table:table-cell table:style-name="Table5.A1" office:value-type="string">
|
||||
<text:p text:style-name="P19">First</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table5.A1" office:value-type="string">
|
||||
<text:p text:style-name="Table_20_Contents">row</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table5.A1" office:value-type="string">
|
||||
<text:p text:style-name="P20">12.0</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table5.A1" office:value-type="string">
|
||||
<text:p text:style-name="Table_20_Contents">Example of a row that spans multiple lines.</text:p>
|
||||
</table:table-cell>
|
||||
</table:table-row>
|
||||
<table:table-row>
|
||||
<table:table-cell table:style-name="Table5.A1" office:value-type="string">
|
||||
<text:p text:style-name="P19">Second</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table5.A1" office:value-type="string">
|
||||
<text:p text:style-name="Table_20_Contents">row</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table5.A1" office:value-type="string">
|
||||
<text:p text:style-name="P20">5.0</text:p>
|
||||
</table:table-cell>
|
||||
<table:table-cell table:style-name="Table5.A1" office:value-type="string">
|
||||
<text:p text:style-name="Table_20_Contents">Here's another one. Note the blank line between rows.</text:p>
|
||||
</table:table-cell>
|
||||
</table:table-row>
|
||||
</table:table>
|
||||
|
|
File diff suppressed because it is too large
Load diff
Loading…
Add table
Reference in a new issue