Code cleanup only.
git-svn-id: https://pandoc.googlecode.com/svn/trunk@1255 788f1e2b-df1e-0410-8736-df70ead52e1b
This commit is contained in:
parent
ee644ddda0
commit
d2643c25e2
1 changed files with 35 additions and 32 deletions
|
@ -1,7 +1,7 @@
|
||||||
{-# OPTIONS_GHC -Wall #-}
|
{-# OPTIONS_GHC -Wall #-}
|
||||||
{-# LANGUAGE PatternGuards #-}
|
{-# LANGUAGE PatternGuards #-}
|
||||||
{-
|
{-
|
||||||
Copyright (C) 2008 Andrea Rossato <andrea.rossato@unibz.it>
|
Copyright (C) 2008 Andrea Rossato <andrea.rossato@ing.unitn.it>
|
||||||
|
|
||||||
This program is free software; you can redistribute it and/or modify
|
This program is free software; you can redistribute it and/or modify
|
||||||
it under the terms of the GNU General Public License as published by
|
it under the terms of the GNU General Public License as published by
|
||||||
|
@ -23,7 +23,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
|
||||||
Copyright : Copyright (C) 2008 Andrea Rossato
|
Copyright : Copyright (C) 2008 Andrea Rossato
|
||||||
License : GNU GPL, version 2 or above
|
License : GNU GPL, version 2 or above
|
||||||
|
|
||||||
Maintainer : Andrea Rossato <andrea.rossato@unibz.it>
|
Maintainer : Andrea Rossato <andrea.rossato@ing.unitn.it>
|
||||||
Stability : alpha
|
Stability : alpha
|
||||||
Portability : portable
|
Portability : portable
|
||||||
|
|
||||||
|
@ -50,12 +50,12 @@ plainToPara x = x
|
||||||
--
|
--
|
||||||
|
|
||||||
data WriterState =
|
data WriterState =
|
||||||
WriterState { stNotes :: [Doc]
|
WriterState { stNotes :: [Doc]
|
||||||
, stTableStyles :: [Doc]
|
, stTableStyles :: [Doc]
|
||||||
, stParaStyles :: [Doc]
|
, stParaStyles :: [Doc]
|
||||||
, stListStyles :: [(Int, [Doc])]
|
, stListStyles :: [(Int, [Doc])]
|
||||||
, indentPara :: Int
|
, indentPara :: Int
|
||||||
} deriving Show
|
}
|
||||||
|
|
||||||
defaultWriterState :: WriterState
|
defaultWriterState :: WriterState
|
||||||
defaultWriterState =
|
defaultWriterState =
|
||||||
|
@ -222,7 +222,7 @@ blockToOpenDocument o bs
|
||||||
| Plain b <- bs = wrap o b
|
| Plain b <- bs = wrap o b
|
||||||
| Para b <- bs = inParagraphTags <$> wrap o b
|
| Para b <- bs = inParagraphTags <$> wrap o b
|
||||||
| Header i b <- bs = inHeaderTags i <$> wrap o b
|
| Header i b <- bs = inHeaderTags i <$> wrap o b
|
||||||
| BlockQuote b <- bs = doBlockQuote b
|
| BlockQuote b <- bs = mkBlockQuote b
|
||||||
| CodeBlock _ s <- bs = preformatted s
|
| CodeBlock _ s <- bs = preformatted s
|
||||||
| RawHtml _ <- bs = return empty
|
| RawHtml _ <- bs = return empty
|
||||||
| DefinitionList b <- bs = defList b
|
| DefinitionList b <- bs = defList b
|
||||||
|
@ -235,7 +235,7 @@ blockToOpenDocument o bs
|
||||||
where
|
where
|
||||||
defList b = vcat <$> mapM (deflistItemToOpenDocument o) b
|
defList b = vcat <$> mapM (deflistItemToOpenDocument o) b
|
||||||
preformatted s = vcat <$> mapM (inPreformattedTags . escapeStringForXML) (lines s)
|
preformatted s = vcat <$> mapM (inPreformattedTags . escapeStringForXML) (lines s)
|
||||||
doBlockQuote b = do increaseIndent
|
mkBlockQuote b = do increaseIndent
|
||||||
i <- paraStyle "Quotations" []
|
i <- paraStyle "Quotations" []
|
||||||
inBlockQuote o i (map plainToPara b)
|
inBlockQuote o i (map plainToPara b)
|
||||||
orderedList a b = do (ln,pn) <- newOrderedListStyle a
|
orderedList a b = do (ln,pn) <- newOrderedListStyle a
|
||||||
|
@ -275,7 +275,7 @@ tableRowToOpenDocument o tn ns cs =
|
||||||
|
|
||||||
tableItemToOpenDocument :: WriterOptions -> String -> (String,[Block])-> State WriterState Doc
|
tableItemToOpenDocument :: WriterOptions -> String -> (String,[Block])-> State WriterState Doc
|
||||||
tableItemToOpenDocument o tn (n,i) =
|
tableItemToOpenDocument o tn (n,i) =
|
||||||
let a = [ ("table:style-name" , tn ++ ".A1" )
|
let a = [ ("table:style-name" , tn ++ ".A1" )
|
||||||
, ("office:value-type", "string" )
|
, ("office:value-type", "string" )
|
||||||
]
|
]
|
||||||
in inTags True "table:table-cell" a <$>
|
in inTags True "table:table-cell" a <$>
|
||||||
|
@ -310,13 +310,13 @@ inlineToOpenDocument o ils
|
||||||
| Code s <- ils = preformatted s
|
| Code s <- ils = preformatted s
|
||||||
| Math s <- ils = inlinesToOpenDocument o (readTeXMath s)
|
| Math s <- ils = inlinesToOpenDocument o (readTeXMath s)
|
||||||
| TeX s <- ils = preformatted s
|
| TeX s <- ils = preformatted s
|
||||||
| HtmlInline _ <- ils = return empty
|
| HtmlInline s <- ils = preformatted s
|
||||||
| Link l (s,t) <- ils = mkLink s t <$> inlinesToOpenDocument o l
|
| Link l (s,t) <- ils = mkLink s t <$> inlinesToOpenDocument o l
|
||||||
| Image l (s,t) <- ils = mkLink s t <$> inlinesToOpenDocument o l
|
| Image l (s,t) <- ils = mkLink s t <$> inlinesToOpenDocument o l
|
||||||
| Note l <- ils = mkNote l
|
| Note l <- ils = mkNote l
|
||||||
| otherwise = return empty
|
| otherwise = return empty
|
||||||
where
|
where
|
||||||
preformatted = return . inSpanTags "Teletype" . text . escapeStringForXML
|
preformatted = return . inSpanTags "Teletype" . text . escapeStringForXML
|
||||||
mkLink s t = inTags False "text:a" [ ("xlink:type" , "simple")
|
mkLink s t = inTags False "text:a" [ ("xlink:type" , "simple")
|
||||||
, ("xlink:href" , s )
|
, ("xlink:href" , s )
|
||||||
, ("office:name", t )
|
, ("office:name", t )
|
||||||
|
@ -368,39 +368,45 @@ orderedListLevelStyle (s,n, d) (l,ls) =
|
||||||
LowerRoman -> "i"
|
LowerRoman -> "i"
|
||||||
_ -> "1"
|
_ -> "1"
|
||||||
listStyle = inTags True "text:list-level-style-number"
|
listStyle = inTags True "text:list-level-style-number"
|
||||||
([ ("text:level" , show $ 1 + length ls )
|
([ ("text:level" , show $ 1 + length ls )
|
||||||
, ("text:style-name" , "Numbering_20_Symbols")
|
, ("text:style-name" , "Numbering_20_Symbols")
|
||||||
, ("style:num-format", format )
|
, ("style:num-format", format )
|
||||||
, ("text:start-value", show s )
|
, ("text:start-value", show s )
|
||||||
] ++ suffix) (listLevelStyle (1 + length ls))
|
] ++ suffix) (listLevelStyle (1 + length ls))
|
||||||
in (l, ls ++ [listStyle])
|
in (l, ls ++ [listStyle])
|
||||||
|
|
||||||
listLevelStyle :: Int -> Doc
|
listLevelStyle :: Int -> Doc
|
||||||
listLevelStyle i =
|
listLevelStyle i =
|
||||||
|
let indent = show (0.25 * fromIntegral i :: Double) in
|
||||||
selfClosingTag "style:list-level-properties"
|
selfClosingTag "style:list-level-properties"
|
||||||
[ ("text:space-before" , show (0.25 * fromIntegral i :: Double) ++ "in")
|
[ ("text:space-before" , indent ++ "in")
|
||||||
, ("text:min-label-width","0.25in")]
|
, ("text:min-label-width", "0.25in")]
|
||||||
|
|
||||||
tableStyle :: Int -> [(Char,Float)] -> Doc
|
tableStyle :: Int -> [(Char,Float)] -> Doc
|
||||||
tableStyle num wcs =
|
tableStyle num wcs =
|
||||||
let tableId = "Table" ++ show (num + 1)
|
let tableId = "Table" ++ show (num + 1)
|
||||||
table = inTags True "style:style" [("style:name", tableId)] $
|
table = inTags True "style:style"
|
||||||
selfClosingTag "style:table-properties" [ ("style:rel-width", "100%" )
|
[("style:name", tableId)] $
|
||||||
, ("table:align" , "center")]
|
selfClosingTag "style:table-properties"
|
||||||
colStyle (c,w) = inTags True "style:style" [ ("style:name" , tableId ++ "." ++ [c])
|
[ ("style:rel-width", "100%" )
|
||||||
, ("style:family", "table-column" )] $
|
, ("table:align" , "center")]
|
||||||
selfClosingTag "style:table-column-properties" [("style:column-width", show (7 * w) ++ "in")]
|
colStyle (c,w) = inTags True "style:style"
|
||||||
cellStyle = inTags True "style:style" [ ("style:name" , tableId ++ ".A1")
|
[ ("style:name" , tableId ++ "." ++ [c])
|
||||||
, ("style:family", "table-cell" )] $
|
, ("style:family", "table-column" )] $
|
||||||
selfClosingTag "style:table-cell-properties" [ ("fo:border", "none")]
|
selfClosingTag "style:table-column-properties"
|
||||||
|
[("style:column-width", show (7 * w) ++ "in")]
|
||||||
|
cellStyle = inTags True "style:style"
|
||||||
|
[ ("style:name" , tableId ++ ".A1")
|
||||||
|
, ("style:family", "table-cell" )] $
|
||||||
|
selfClosingTag "style:table-cell-properties"
|
||||||
|
[ ("fo:border", "none")]
|
||||||
columnStyles = map colStyle wcs
|
columnStyles = map colStyle wcs
|
||||||
|
|
||||||
in table $$ vcat columnStyles $$ cellStyle
|
in table $$ vcat columnStyles $$ cellStyle
|
||||||
|
|
||||||
paraStyle :: String -> [(String,String)] -> State WriterState Int
|
paraStyle :: String -> [(String,String)] -> State WriterState Int
|
||||||
paraStyle parent attrs = do
|
paraStyle parent attrs = do
|
||||||
pn <- (+) 1 . length <$> gets stParaStyles
|
pn <- (+) 1 . length <$> gets stParaStyles
|
||||||
i <- (*) 0.5 . fromIntegral <$> gets indentPara :: State WriterState Double
|
i <- (*) 0.5 . fromIntegral <$> gets indentPara :: State WriterState Double
|
||||||
let styleAttr = [ ("style:name" , "P" ++ show pn)
|
let styleAttr = [ ("style:name" , "P" ++ show pn)
|
||||||
, ("style:family" , "paragraph" )
|
, ("style:family" , "paragraph" )
|
||||||
, ("style:parent-style-name", parent )]
|
, ("style:parent-style-name", parent )]
|
||||||
|
@ -415,8 +421,7 @@ paraStyle parent attrs = do
|
||||||
return pn
|
return pn
|
||||||
|
|
||||||
paraListStyle :: Int -> State WriterState Int
|
paraListStyle :: Int -> State WriterState Int
|
||||||
paraListStyle l =
|
paraListStyle l = paraStyle "Text_20_body" [("style:list-style-name", "L" ++ show l )]
|
||||||
paraStyle "Text_20_body" [("style:list-style-name", "L" ++ show l )]
|
|
||||||
|
|
||||||
paraTableStyles :: String -> Int -> [Alignment] -> [(String, Doc)]
|
paraTableStyles :: String -> Int -> [Alignment] -> [(String, Doc)]
|
||||||
paraTableStyles _ _ [] = []
|
paraTableStyles _ _ [] = []
|
||||||
|
@ -428,12 +433,10 @@ paraTableStyles t s (a:xs)
|
||||||
res sn x = inTags True "style:style"
|
res sn x = inTags True "style:style"
|
||||||
[ ("style:name" , pName sn )
|
[ ("style:name" , pName sn )
|
||||||
, ("style:family" , "paragraph" )
|
, ("style:family" , "paragraph" )
|
||||||
, ("style:parent-style-name", "Table_20_" ++ t)
|
, ("style:parent-style-name", "Table_20_" ++ t)] $
|
||||||
] $
|
|
||||||
selfClosingTag "style:paragraph-properties"
|
selfClosingTag "style:paragraph-properties"
|
||||||
[ ("fo:text-align", x)
|
[ ("fo:text-align", x)
|
||||||
, ("style:justify-single-word", "false")
|
, ("style:justify-single-word", "false")]
|
||||||
]
|
|
||||||
|
|
||||||
openDocumentNameSpaces :: [(String, String)]
|
openDocumentNameSpaces :: [(String, String)]
|
||||||
openDocumentNameSpaces =
|
openDocumentNameSpaces =
|
||||||
|
|
Loading…
Add table
Reference in a new issue