aboutsummaryrefslogtreecommitdiff
path: root/src/Text
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text')
-rw-r--r--src/Text/Pandoc/Readers/Docx.hs8
-rw-r--r--src/Text/Pandoc/Readers/Docx/Parse.hs25
-rw-r--r--src/Text/Pandoc/Readers/HTML.hs7
-rw-r--r--src/Text/Pandoc/Writers/Docx.hs13
4 files changed, 33 insertions, 20 deletions
diff --git a/src/Text/Pandoc/Readers/Docx.hs b/src/Text/Pandoc/Readers/Docx.hs
index a1c16a03a..3e4ac9647 100644
--- a/src/Text/Pandoc/Readers/Docx.hs
+++ b/src/Text/Pandoc/Readers/Docx.hs
@@ -257,10 +257,10 @@ runStyleToTransform rPr
smallcaps . (runStyleToTransform rPr {isSmallCaps = Nothing})
| Just True <- isStrike rPr =
strikeout . (runStyleToTransform rPr {isStrike = Nothing})
- | isSuperScript rPr =
- superscript . (runStyleToTransform rPr {isSuperScript = False})
- | isSubScript rPr =
- subscript . (runStyleToTransform rPr {isSubScript = False})
+ | Just SupScrpt <- rVertAlign rPr =
+ superscript . (runStyleToTransform rPr {rVertAlign = Nothing})
+ | Just SubScrpt <- rVertAlign rPr =
+ subscript . (runStyleToTransform rPr {rVertAlign = Nothing})
| Just "single" <- rUnderline rPr =
emph . (runStyleToTransform rPr {rUnderline = Nothing})
| otherwise = id
diff --git a/src/Text/Pandoc/Readers/Docx/Parse.hs b/src/Text/Pandoc/Readers/Docx/Parse.hs
index 939fcde27..1775a19c3 100644
--- a/src/Text/Pandoc/Readers/Docx/Parse.hs
+++ b/src/Text/Pandoc/Readers/Docx/Parse.hs
@@ -43,6 +43,7 @@ module Text.Pandoc.Readers.Docx.Parse ( Docx(..)
, Relationship
, Media
, RunStyle(..)
+ , VertAlign(..)
, ParIndentation(..)
, ParagraphStyle(..)
, Row(..)
@@ -196,12 +197,14 @@ data Run = Run RunStyle [RunElem]
data RunElem = TextRun String | LnBrk | Tab
deriving Show
+data VertAlign = BaseLn | SupScrpt | SubScrpt
+ deriving Show
+
data RunStyle = RunStyle { isBold :: Maybe Bool
, isItalic :: Maybe Bool
, isSmallCaps :: Maybe Bool
, isStrike :: Maybe Bool
- , isSuperScript :: Bool
- , isSubScript :: Bool
+ , rVertAlign :: Maybe VertAlign
, rUnderline :: Maybe String
, rStyle :: Maybe String }
deriving Show
@@ -211,8 +214,7 @@ defaultRunStyle = RunStyle { isBold = Nothing
, isItalic = Nothing
, isSmallCaps = Nothing
, isStrike = Nothing
- , isSuperScript = False
- , isSubScript = False
+ , rVertAlign = Nothing
, rUnderline = Nothing
, rStyle = Nothing
}
@@ -677,14 +679,13 @@ elemToRunStyle ns element
, isItalic = checkOnOff ns rPr (elemName ns "w" "i")
, isSmallCaps = checkOnOff ns rPr (elemName ns "w" "smallCaps")
, isStrike = checkOnOff ns rPr (elemName ns "w" "strike")
- , isSuperScript =
- (Just "superscript" ==
- (findChild (elemName ns "w" "vertAlign") rPr >>=
- findAttr (elemName ns "w" "val")))
- , isSubScript =
- (Just "subscript" ==
- (findChild (elemName ns "w" "vertAlign") rPr >>=
- findAttr (elemName ns "w" "val")))
+ , rVertAlign =
+ findChild (elemName ns "w" "vertAlign") rPr >>=
+ findAttr (elemName ns "w" "val") >>=
+ \v -> Just $ case v of
+ "superscript" -> SupScrpt
+ "subscript" -> SubScrpt
+ _ -> BaseLn
, rUnderline =
findChild (elemName ns "w" "u") rPr >>=
findAttr (elemName ns "w" "val")
diff --git a/src/Text/Pandoc/Readers/HTML.hs b/src/Text/Pandoc/Readers/HTML.hs
index cee7ea300..bd60a74fa 100644
--- a/src/Text/Pandoc/Readers/HTML.hs
+++ b/src/Text/Pandoc/Readers/HTML.hs
@@ -570,7 +570,12 @@ pSpan = try $ do
guardEnabled Ext_native_spans
TagOpen _ attr <- lookAhead $ pSatisfy $ tagOpen (=="span") (const True)
contents <- pInTags "span" inline
- return $ B.spanWith (mkAttr attr) contents
+ let attr' = mkAttr attr
+ return $ case attr' of
+ ("",[],[("style",s)])
+ | filter (`notElem` " \t;") s == "font-variant:small-caps" ->
+ B.smallcaps contents
+ _ -> B.spanWith (mkAttr attr) contents
pRawHtmlInline :: TagParser Inlines
pRawHtmlInline = do
diff --git a/src/Text/Pandoc/Writers/Docx.hs b/src/Text/Pandoc/Writers/Docx.hs
index 010a6e3ff..fbf38e6f1 100644
--- a/src/Text/Pandoc/Writers/Docx.hs
+++ b/src/Text/Pandoc/Writers/Docx.hs
@@ -114,7 +114,13 @@ type WS a = StateT WriterState IO a
mknode :: Node t => String -> [(String,String)] -> t -> Element
mknode s attrs =
- add_attrs (map (\(k,v) -> Attr (unqual k) v) attrs) . node (unqual s)
+ add_attrs (map (\(k,v) -> Attr (nodename k) v) attrs) . node (nodename s)
+
+nodename :: String -> QName
+nodename s = QName{ qName = name, qURI = Nothing, qPrefix = prefix }
+ where (name, prefix) = case break (==':') s of
+ (xs,[]) -> (xs, Nothing)
+ (ys,(_:zs)) -> (zs, Just ys)
toLazy :: B.ByteString -> BL.ByteString
toLazy = BL.fromChunks . (:[])
@@ -297,7 +303,8 @@ writeDocx opts doc@(Pandoc meta _) = do
-- otherwise things break:
[Elem e | e <- allElts
, qName (elName e) == "abstractNum" ] ++
- [Elem e | e <- allElts, qName (elName e) == "num" ] }
+ [Elem e | e <- allElts
+ , qName (elName e) == "num" ] }
let docPropsPath = "docProps/core.xml"
let docProps = mknode "cp:coreProperties"
[("xmlns:cp","http://schemas.openxmlformats.org/package/2006/metadata/core-properties")
@@ -470,7 +477,7 @@ mkLvl marker lvl =
patternFor _ s = s ++ "."
getNumId :: WS Int
-getNumId = ((999 +) . length) `fmap` gets stLists
+getNumId = (((baseListId - 1) +) . length) `fmap` gets stLists
-- | Convert Pandoc document to two lists of
-- OpenXML elements (the main document and footnotes).