aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--README8
-rw-r--r--src/Text/Pandoc/ImageSize.hs7
-rw-r--r--src/Text/Pandoc/Readers/HTML.hs13
-rw-r--r--src/Text/Pandoc/Readers/Markdown.hs10
-rw-r--r--src/Text/Pandoc/Readers/MediaWiki.hs12
-rw-r--r--src/Text/Pandoc/Writers/LaTeX.hs12
6 files changed, 52 insertions, 10 deletions
diff --git a/README b/README
index 122db23ec..012b75e2a 100644
--- a/README
+++ b/README
@@ -2020,6 +2020,14 @@ Attributes can be attached to verbatim text, just as with
`<$>`{.haskell}
+### Small caps ###
+
+To write small caps, you can use an HTML span tag:
+
+ <span style="font-variant:small-caps;">Small caps</span>
+
+This will work in all output formats that support small caps.
+
Math
----
diff --git a/src/Text/Pandoc/ImageSize.hs b/src/Text/Pandoc/ImageSize.hs
index 9e6b457c0..68b34dcf3 100644
--- a/src/Text/Pandoc/ImageSize.hs
+++ b/src/Text/Pandoc/ImageSize.hs
@@ -76,6 +76,9 @@ imageSize img = do
Eps -> epsSize img
Pdf -> Nothing -- TODO
+defaultSize :: (Integer, Integer)
+defaultSize = (72, 72)
+
sizeInPixels :: ImageSize -> (Integer, Integer)
sizeInPixels s = (pxX s, pxY s)
@@ -260,7 +263,9 @@ exifHeader hdr = do
lookup ExifImageHeight allentries) of
(Just (UnsignedLong w), Just (UnsignedLong h)) ->
return (fromIntegral w, fromIntegral h)
- _ -> fail "Could not determine image width, height"
+ _ -> return defaultSize
+ -- we return a default width and height when
+ -- the exif header doesn't contain these
let resfactor = case lookup ResolutionUnit allentries of
Just (UnsignedShort 1) -> (100 / 254)
_ -> 1
diff --git a/src/Text/Pandoc/Readers/HTML.hs b/src/Text/Pandoc/Readers/HTML.hs
index 204239923..552e8a251 100644
--- a/src/Text/Pandoc/Readers/HTML.hs
+++ b/src/Text/Pandoc/Readers/HTML.hs
@@ -50,6 +50,8 @@ import Data.Char ( isDigit )
import Control.Monad ( liftM, guard, when, mzero )
import Control.Applicative ( (<$>), (<$), (<*) )
import Data.Monoid
+import Text.Printf (printf)
+import Debug.Trace (trace)
isSpace :: Char -> Bool
isSpace ' ' = True
@@ -92,7 +94,10 @@ pHead = pInTags "head" $ pTitle <|> pMetaTag <|> (mempty <$ pAnyTag)
return mempty
block :: TagParser Blocks
-block = choice
+block = do
+ tr <- getOption readerTrace
+ pos <- getPosition
+ res <- choice
[ pPara
, pHeader
, pBlockQuote
@@ -106,6 +111,10 @@ block = choice
, pDiv
, pRawHtmlBlock
]
+ when tr $ trace (printf "line %d: %s" (sourceLine pos)
+ (take 60 $ show $ B.toList res)) (return ())
+ return res
+
pList :: TagParser Blocks
pList = pBulletList <|> pOrderedList <|> pDefinitionList
@@ -462,6 +471,8 @@ pCloses tagtype = try $ do
(TagClose "ul") | tagtype == "li" -> return ()
(TagClose "ol") | tagtype == "li" -> return ()
(TagClose "dl") | tagtype == "li" -> return ()
+ (TagClose "table") | tagtype == "td" -> return ()
+ (TagClose "table") | tagtype == "tr" -> return ()
_ -> mzero
pTagText :: TagParser Inlines
diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs
index a6720beba..6c710c8ff 100644
--- a/src/Text/Pandoc/Readers/Markdown.hs
+++ b/src/Text/Pandoc/Readers/Markdown.hs
@@ -1560,7 +1560,8 @@ endline = try $ do
guardEnabled Ext_blank_before_header <|> notFollowedBy (char '#') -- atx header
guardDisabled Ext_backtick_code_blocks <|>
notFollowedBy (() <$ (lookAhead (char '`') >> codeBlockFenced))
- (guardEnabled Ext_hard_line_breaks >> return (return B.linebreak))
+ (eof >> return mempty)
+ <|> (guardEnabled Ext_hard_line_breaks >> return (return B.linebreak))
<|> (guardEnabled Ext_ignore_line_breaks >> return mempty)
<|> (return $ return B.space)
@@ -1735,7 +1736,12 @@ spanHtml = try $ do
let ident = fromMaybe "" $ lookup "id" attrs
let classes = maybe [] words $ lookup "class" attrs
let keyvals = [(k,v) | (k,v) <- attrs, k /= "id" && k /= "class"]
- return $ B.spanWith (ident, classes, keyvals) <$> contents
+ case lookup "style" keyvals of
+ Just s | null ident && null classes &&
+ map toLower (filter (`notElem` " \t;") s) ==
+ "font-variant:small-caps"
+ -> return $ B.smallcaps <$> contents
+ _ -> return $ B.spanWith (ident, classes, keyvals) <$> contents
divHtml :: MarkdownParser (F Blocks)
divHtml = try $ do
diff --git a/src/Text/Pandoc/Readers/MediaWiki.hs b/src/Text/Pandoc/Readers/MediaWiki.hs
index e4fabc898..f1dcce8f7 100644
--- a/src/Text/Pandoc/Readers/MediaWiki.hs
+++ b/src/Text/Pandoc/Readers/MediaWiki.hs
@@ -55,6 +55,8 @@ import qualified Data.Foldable as F
import qualified Data.Map as M
import Data.Char (isDigit, isSpace)
import Data.Maybe (fromMaybe)
+import Text.Printf (printf)
+import Debug.Trace (trace)
-- | Read mediawiki from an input string and return a Pandoc document.
readMediaWiki :: ReaderOptions -- ^ Reader options
@@ -187,7 +189,10 @@ parseMediaWiki = do
--
block :: MWParser Blocks
-block = mempty <$ skipMany1 blankline
+block = do
+ tr <- getOption readerTrace
+ pos <- getPosition
+ res <- mempty <$ skipMany1 blankline
<|> table
<|> header
<|> hrule
@@ -199,6 +204,10 @@ block = mempty <$ skipMany1 blankline
<|> blockTag
<|> (B.rawBlock "mediawiki" <$> template)
<|> para
+ when tr $
+ trace (printf "line %d: %s" (sourceLine pos)
+ (take 60 $ show $ B.toList res)) (return ())
+ return res
para :: MWParser Blocks
para = do
@@ -308,6 +317,7 @@ template :: MWParser String
template = try $ do
string "{{"
notFollowedBy (char '{')
+ lookAhead $ letter <|> digit <|> char ':'
let chunk = template <|> variable <|> many1 (noneOf "{}") <|> count 1 anyChar
contents <- manyTill chunk (try $ string "}}")
return $ "{{" ++ concat contents ++ "}}"
diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs
index ed735242f..f2f7438c4 100644
--- a/src/Text/Pandoc/Writers/LaTeX.hs
+++ b/src/Text/Pandoc/Writers/LaTeX.hs
@@ -311,12 +311,14 @@ blockToLaTeX (Plain lst) =
inlineListToLaTeX $ dropWhile isLineBreakOrSpace lst
-- title beginning with fig: indicates that the image is a figure
blockToLaTeX (Para [Image txt (src,'f':'i':'g':':':tit)]) = do
- capt <- if null txt
- then return empty
- else (\c -> "\\caption" <> braces c) `fmap` inlineListToLaTeX txt
+ inNote <- gets stInNote
+ capt <- inlineListToLaTeX txt
img <- inlineToLaTeX (Image txt (src,tit))
- return $ "\\begin{figure}[htbp]" $$ "\\centering" $$ img $$
- capt $$ "\\end{figure}"
+ return $ if inNote
+ -- can't have figures in notes
+ then "\\begin{center}" $$ img $+$ capt $$ "\\end{center}"
+ else "\\begin{figure}[htbp]" $$ "\\centering" $$ img $$
+ ("\\caption" <> braces capt) $$ "\\end{figure}"
-- . . . indicates pause in beamer slides
blockToLaTeX (Para [Str ".",Space,Str ".",Space,Str "."]) = do
beamer <- writerBeamer `fmap` gets stOptions