Docx Reader: Added recognition of sym element in paragraphs
This commit is contained in:
parent
c2a0d47c7b
commit
2deaa7096f
1 changed files with 19 additions and 0 deletions
|
@ -62,7 +62,9 @@ import Control.Monad.Reader
|
|||
import qualified Data.Map as M
|
||||
import Text.Pandoc.Compat.Except
|
||||
import Text.Pandoc.Readers.Docx.OMath (readOMML)
|
||||
import Text.Pandoc.Readers.Docx.Fonts (getUnicode, Font(..))
|
||||
import Text.TeXMath (Exp)
|
||||
import Data.Char (readLitChar)
|
||||
|
||||
data ReaderEnv = ReaderEnv { envNotes :: Notes
|
||||
, envNumbering :: Numbering
|
||||
|
@ -673,8 +675,25 @@ elemToRunElem ns element
|
|||
return $ TextRun $ strContent element
|
||||
| isElem ns "w" "br" element = return LnBrk
|
||||
| isElem ns "w" "tab" element = return Tab
|
||||
| isElem ns "w" "sym" element = return (getSymChar ns element)
|
||||
| otherwise = throwError WrongElem
|
||||
|
||||
-- The char attribute is a hex string
|
||||
getSymChar :: NameSpaces -> Element -> RunElem
|
||||
getSymChar ns element
|
||||
| Just s <- getCodepoint
|
||||
, Just font <- getFont =
|
||||
let [(char, _)] = readLitChar ("\\x" ++ s) in
|
||||
TextRun . maybe "" (:[]) $ getUnicode font char
|
||||
where
|
||||
getCodepoint = findAttr (elemName ns "w" "char") element
|
||||
getFont = stringToFont =<< findAttr (elemName ns "w" "font") element
|
||||
getSymChar _ _ = TextRun ""
|
||||
|
||||
stringToFont :: String -> Maybe Font
|
||||
stringToFont "Symbol" = Just Symbol
|
||||
stringToFont _ = Nothing
|
||||
|
||||
elemToRunElems :: NameSpaces -> Element -> D [RunElem]
|
||||
elemToRunElems ns element
|
||||
| isElem ns "w" "r" element
|
||||
|
|
Loading…
Reference in a new issue