diff options
| m--------- | data/templates | 12 | ||||
| -rw-r--r-- | pandoc.hs | 15 | ||||
| -rw-r--r-- | src/Text/Pandoc/Readers/Docx.hs | 8 | ||||
| -rw-r--r-- | src/Text/Pandoc/Readers/Docx/Parse.hs | 25 | ||||
| -rw-r--r-- | src/Text/Pandoc/Readers/HTML.hs | 7 | ||||
| -rw-r--r-- | src/Text/Pandoc/Writers/Docx.hs | 13 | ||||
| -rw-r--r-- | tests/html-reader.html | 1 | ||||
| -rw-r--r-- | tests/html-reader.native | 1 |
8 files changed, 49 insertions, 33 deletions
diff --git a/data/templates b/data/templates -Subproject 950b54c55c5e6577a09715d9654abafac445ab5 +Subproject ecb769cb7b4354234135c030dcb03a064f03947 @@ -44,7 +44,7 @@ import Text.Pandoc.SelfContained ( makeSelfContained ) import Text.Pandoc.Process (pipeProcess) import Text.Highlighting.Kate ( languages, Style, tango, pygments, espresso, zenburn, kate, haddock, monochrome ) -import System.Environment ( getArgs, getProgName, getEnvironment ) +import System.Environment ( getArgs, getProgName ) import System.Exit ( exitWith, ExitCode (..) ) import System.FilePath import System.Console.GetOpt @@ -113,12 +113,15 @@ isTextFormat s = takeWhile (`notElem` "+-") s `notElem` binaries externalFilter :: FilePath -> [String] -> Pandoc -> IO Pandoc externalFilter f args' d = do - mbPath <- lookup "PATH" <$> getEnvironment - mbexe <- if '/' `elem` f || mbPath == Nothing - -- don't check PATH if filter name has a path, or - -- if the PATH is not set + mbexe <- if '/' `elem` f + -- don't check PATH if filter name has a path then return Nothing - else findExecutable f + -- we catch isDoesNotExistError because this will + -- be triggered if PATH not set: + else E.catch (findExecutable f) + (\e -> if isDoesNotExistError e + then return Nothing + else throwIO e) (f', args'') <- case mbexe of Just x -> return (x, args') Nothing -> do 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). diff --git a/tests/html-reader.html b/tests/html-reader.html index d059d7b4b..14ad3ed54 100644 --- a/tests/html-reader.html +++ b/tests/html-reader.html @@ -309,6 +309,7 @@ These should not be escaped: \$ \\ \> \[ \{ <p><strong><em>This is strong and em.</em></strong></p> <p>So is <strong><em>this</em></strong> word.</p> <p>This is code: <code>></code>, <code>$</code>, <code>\</code>, <code>\$</code>, <code><html></code>.</p> +<p>This is <span style="font-variant: small-caps;">small caps</span>.</p> <hr /> <h1>Smart quotes, ellipses, dashes</h1> <p>"Hello," said the spider. "'Shelob' is my name."</p> diff --git a/tests/html-reader.native b/tests/html-reader.native index c6ed36910..aef6e40fc 100644 --- a/tests/html-reader.native +++ b/tests/html-reader.native @@ -193,6 +193,7 @@ Pandoc (Meta {unMeta = fromList [("generator",MetaInlines [Str "pandoc"]),("titl ,Para [Strong [Emph [Str "This",Space,Str "is",Space,Str "strong",Space,Str "and",Space,Str "em."]]] ,Para [Str "So",Space,Str "is",Space,Strong [Emph [Str "this"]],Space,Str "word."] ,Para [Str "This",Space,Str "is",Space,Str "code:",Space,Code ("",[],[]) ">",Str ",",Space,Code ("",[],[]) "$",Str ",",Space,Code ("",[],[]) "\\",Str ",",Space,Code ("",[],[]) "\\$",Str ",",Space,Code ("",[],[]) "<html>",Str "."] +,Para [Str "This",Space,Str "is",Space,SmallCaps [Str "small",Space,Str "caps"],Str "."] ,HorizontalRule ,Header 1 ("",[],[]) [Str "Smart",Space,Str "quotes,",Space,Str "ellipses,",Space,Str "dashes"] ,Para [Str "\"Hello,\"",Space,Str "said",Space,Str "the",Space,Str "spider.",Space,Str "\"'Shelob'",Space,Str "is",Space,Str "my",Space,Str "name.\""] |
