aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Writers
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Writers')
-rw-r--r--src/Text/Pandoc/Writers/Docbook.hs6
-rw-r--r--src/Text/Pandoc/Writers/EPUB.hs2
-rw-r--r--src/Text/Pandoc/Writers/HTML.hs4
-rw-r--r--src/Text/Pandoc/Writers/JATS.hs6
-rw-r--r--src/Text/Pandoc/Writers/LaTeX.hs4
-rw-r--r--src/Text/Pandoc/Writers/Man.hs2
-rw-r--r--src/Text/Pandoc/Writers/Ms.hs6
-rw-r--r--src/Text/Pandoc/Writers/RST.hs6
-rw-r--r--src/Text/Pandoc/Writers/Texinfo.hs2
-rw-r--r--src/Text/Pandoc/Writers/ZimWiki.hs2
10 files changed, 20 insertions, 20 deletions
diff --git a/src/Text/Pandoc/Writers/Docbook.hs b/src/Text/Pandoc/Writers/Docbook.hs
index 24df7e2b4..74a1249a4 100644
--- a/src/Text/Pandoc/Writers/Docbook.hs
+++ b/src/Text/Pandoc/Writers/Docbook.hs
@@ -76,9 +76,9 @@ authorToDocbook opts name' = do
let namewords = words name
lengthname = length namewords
(firstname, lastname) = case lengthname of
- 0 -> ("","")
- 1 -> ("", name)
- n -> (unwords (take (n-1) namewords), last namewords)
+ 0 -> ("","")
+ 1 -> ("", name)
+ n -> (unwords (take (n-1) namewords), last namewords)
in inTagsSimple "firstname" (text $ escapeStringForXML firstname) $$
inTagsSimple "surname" (text $ escapeStringForXML lastname)
diff --git a/src/Text/Pandoc/Writers/EPUB.hs b/src/Text/Pandoc/Writers/EPUB.hs
index 6bfd78d3c..94eea3a45 100644
--- a/src/Text/Pandoc/Writers/EPUB.hs
+++ b/src/Text/Pandoc/Writers/EPUB.hs
@@ -43,7 +43,7 @@ import qualified Data.ByteString.Lazy.Char8 as B8
import Data.Char (isAlphaNum, isAscii, isDigit, toLower)
import Data.List (intercalate, isInfixOf, isPrefixOf)
import qualified Data.Map as M
-import Data.Maybe (fromMaybe, mapMaybe, isNothing)
+import Data.Maybe (fromMaybe, isNothing, mapMaybe)
import qualified Data.Set as Set
import qualified Data.Text as TS
import qualified Data.Text.Lazy as TL
diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs
index ddbd9e972..ffcde3ce7 100644
--- a/src/Text/Pandoc/Writers/HTML.hs
+++ b/src/Text/Pandoc/Writers/HTML.hs
@@ -421,7 +421,7 @@ elementToHtml slideLevel opts (Sec level num (id',classes,keyvals) title' elemen
return res
let isSec (Sec{}) = True
- isSec (Blk _) = False
+ isSec (Blk _) = False
let isPause (Blk x) = x == Para [Str ".",Space,Str ".",Space,Str "."]
isPause _ = False
let fragmentClass = case slideVariant of
@@ -1174,7 +1174,7 @@ isMathEnvironment s = "\\begin{" `isPrefixOf` s &&
allowsMathEnvironments :: HTMLMathMethod -> Bool
allowsMathEnvironments (MathJax _) = True
-allowsMathEnvironments MathML = True
+allowsMathEnvironments MathML = True
allowsMathEnvironments (WebTeX _) = True
allowsMathEnvironments _ = False
diff --git a/src/Text/Pandoc/Writers/JATS.hs b/src/Text/Pandoc/Writers/JATS.hs
index a62286fa3..2aac777c6 100644
--- a/src/Text/Pandoc/Writers/JATS.hs
+++ b/src/Text/Pandoc/Writers/JATS.hs
@@ -76,9 +76,9 @@ authorToJATS opts name' = do
let namewords = words name
lengthname = length namewords
(firstname, lastname) = case lengthname of
- 0 -> ("","")
- 1 -> ("", name)
- n -> (unwords (take (n-1) namewords), last namewords)
+ 0 -> ("","")
+ 1 -> ("", name)
+ n -> (unwords (take (n-1) namewords), last namewords)
in inTagsSimple "firstname" (text $ escapeStringForXML firstname) $$
inTagsSimple "surname" (text $ escapeStringForXML lastname)
diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs
index e667984ef..ab1e90b3b 100644
--- a/src/Text/Pandoc/Writers/LaTeX.hs
+++ b/src/Text/Pandoc/Writers/LaTeX.hs
@@ -135,7 +135,7 @@ pandocToLaTeX options (Pandoc meta blocks) = do
let blocks' = if method == Biblatex || method == Natbib
then case reverse blocks of
Div (_,["references"],_) _:xs -> reverse xs
- _ -> blocks
+ _ -> blocks
else blocks
-- see if there are internal links
let isInternalLink (Link _ _ ('#':xs,_)) = [xs]
@@ -848,7 +848,7 @@ sectionHeader unnumbered ident level lst = do
plain <- stringToLaTeX TextString $ concatMap stringify lst
let removeInvalidInline (Note _) = []
removeInvalidInline (Span (id', _, _) _) | not (null id') = []
- removeInvalidInline (Image{}) = []
+ removeInvalidInline (Image{}) = []
removeInvalidInline x = [x]
let lstNoNotes = foldr (mappend . (\x -> walkM removeInvalidInline x)) mempty lst
txtNoNotes <- inlineListToLaTeX lstNoNotes
diff --git a/src/Text/Pandoc/Writers/Man.hs b/src/Text/Pandoc/Writers/Man.hs
index cd7a98d43..ad3de41eb 100644
--- a/src/Text/Pandoc/Writers/Man.hs
+++ b/src/Text/Pandoc/Writers/Man.hs
@@ -156,7 +156,7 @@ breakSentence [] = ([],[])
breakSentence xs =
let isSentenceEndInline (Str ys@(_:_)) | last ys == '.' = True
isSentenceEndInline (Str ys@(_:_)) | last ys == '?' = True
- isSentenceEndInline LineBreak = True
+ isSentenceEndInline LineBreak = True
isSentenceEndInline _ = False
(as, bs) = break isSentenceEndInline xs
in case bs of
diff --git a/src/Text/Pandoc/Writers/Ms.hs b/src/Text/Pandoc/Writers/Ms.hs
index 9e3036753..223d1bcc1 100644
--- a/src/Text/Pandoc/Writers/Ms.hs
+++ b/src/Text/Pandoc/Writers/Ms.hs
@@ -191,7 +191,7 @@ breakSentence [] = ([],[])
breakSentence xs =
let isSentenceEndInline (Str ys@(_:_)) | last ys == '.' = True
isSentenceEndInline (Str ys@(_:_)) | last ys == '?' = True
- isSentenceEndInline LineBreak = True
+ isSentenceEndInline LineBreak = True
isSentenceEndInline _ = False
(as, bs) = break isSentenceEndInline xs
in case bs of
@@ -408,8 +408,8 @@ definitionListItemToMs opts (label, defs) = do
else liftM vcat $ forM defs $ \blocks -> do
let (first, rest) = case blocks of
(Para x:y) -> (Plain x,y)
- (x:y) -> (x,y)
- [] -> (Plain [], [])
+ (x:y) -> (x,y)
+ [] -> (Plain [], [])
-- should not happen
rest' <- liftM vcat $
mapM (\item -> blockToMs opts item) rest
diff --git a/src/Text/Pandoc/Writers/RST.hs b/src/Text/Pandoc/Writers/RST.hs
index 6c6010880..aab8a3bf0 100644
--- a/src/Text/Pandoc/Writers/RST.hs
+++ b/src/Text/Pandoc/Writers/RST.hs
@@ -344,7 +344,7 @@ definitionListItemToRST (label, defs) = do
linesToLineBlock :: PandocMonad m => [[Inline]] -> RST m Doc
linesToLineBlock inlineLines = do
lns <- mapM inlineListToRST inlineLines
- return $
+ return $
vcat (map (hang 2 (text "| ")) lns) <> blankline
-- | Convert list of Pandoc block elements to RST.
@@ -437,8 +437,8 @@ inlineListToRST lst =
isComplex (Strikeout _) = True
isComplex (Superscript _) = True
isComplex (Subscript _) = True
- isComplex (Link{}) = True
- isComplex (Image{}) = True
+ isComplex (Link{}) = True
+ isComplex (Image{}) = True
isComplex (Code _ _) = True
isComplex (Math _ _) = True
isComplex (Cite _ (x:_)) = isComplex x
diff --git a/src/Text/Pandoc/Writers/Texinfo.hs b/src/Text/Pandoc/Writers/Texinfo.hs
index 2d0c7a86d..15dd2e3d9 100644
--- a/src/Text/Pandoc/Writers/Texinfo.hs
+++ b/src/Text/Pandoc/Writers/Texinfo.hs
@@ -340,7 +340,7 @@ blockListToTexinfo (x:xs) = do
xs' <- blockListToTexinfo xs
case xs of
(CodeBlock _ _:_) -> return $ x' $$ xs'
- _ -> return $ x' $+$ xs'
+ _ -> return $ x' $+$ xs'
_ -> do
xs' <- blockListToTexinfo xs
return $ x' $$ xs'
diff --git a/src/Text/Pandoc/Writers/ZimWiki.hs b/src/Text/Pandoc/Writers/ZimWiki.hs
index 60029c0d4..29849aa51 100644
--- a/src/Text/Pandoc/Writers/ZimWiki.hs
+++ b/src/Text/Pandoc/Writers/ZimWiki.hs
@@ -36,8 +36,8 @@ import Control.Monad (zipWithM)
import Control.Monad.State.Strict (StateT, evalStateT, gets, modify)
import Data.Default (Default (..))
import Data.List (intercalate, isInfixOf, isPrefixOf, transpose)
-import Data.Maybe (fromMaybe)
import qualified Data.Map as Map
+import Data.Maybe (fromMaybe)
import Data.Text (Text, breakOnAll, pack)
import Text.Pandoc.Class (PandocMonad, report)
import Text.Pandoc.Definition