summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2017-10-29 14:29:32 -0700
committerJohn MacFarlane <jgm@berkeley.edu>2017-10-29 14:29:32 -0700
commit52ee19a825fad5255e15fccfdf6de8d4203b5fec (patch)
tree38f34828cf0ec0adbcec1f5e4b04543207d98879
parentf270dd9b18de69e87198216f13943b2ceefea8f8 (diff)
Source code reformatting.
-rw-r--r--src/Text/Pandoc/Class.hs1
-rw-r--r--src/Text/Pandoc/Logging.hs2
-rw-r--r--src/Text/Pandoc/Parsing.hs129
-rw-r--r--src/Text/Pandoc/Readers/DocBook.hs48
-rw-r--r--src/Text/Pandoc/Readers/Docx.hs4
-rw-r--r--src/Text/Pandoc/Readers/Docx/Lists.hs2
-rw-r--r--src/Text/Pandoc/Readers/EPUB.hs6
-rw-r--r--src/Text/Pandoc/Readers/HTML.hs124
-rw-r--r--src/Text/Pandoc/Readers/Muse.hs18
-rw-r--r--src/Text/Pandoc/Readers/Odt/ContentReader.hs1
-rw-r--r--src/Text/Pandoc/Readers/RST.hs11
-rw-r--r--src/Text/Pandoc/Readers/Vimwiki.hs10
-rw-r--r--src/Text/Pandoc/Shared.hs2
-rw-r--r--src/Text/Pandoc/Slides.hs2
-rw-r--r--src/Text/Pandoc/Templates.hs6
-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
25 files changed, 202 insertions, 204 deletions
diff --git a/src/Text/Pandoc/Class.hs b/src/Text/Pandoc/Class.hs
index 7c518e84b..2b8b1c090 100644
--- a/src/Text/Pandoc/Class.hs
+++ b/src/Text/Pandoc/Class.hs
@@ -2,6 +2,7 @@
{-# LANGUAGE PatternGuards #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE TypeSynonymInstances #-}
+{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE FlexibleContexts #-}
diff --git a/src/Text/Pandoc/Logging.hs b/src/Text/Pandoc/Logging.hs
index a156f017c..4723c1119 100644
--- a/src/Text/Pandoc/Logging.hs
+++ b/src/Text/Pandoc/Logging.hs
@@ -45,8 +45,8 @@ import Data.Aeson.Encode.Pretty (Config (..), defConfig, encodePretty',
keyOrder)
import qualified Data.ByteString.Lazy as BL
import Data.Data (Data, toConstr)
-import Data.Typeable (Typeable)
import qualified Data.Text as Text
+import Data.Typeable (Typeable)
import GHC.Generics (Generic)
import Text.Pandoc.Definition
import Text.Parsec.Pos
diff --git a/src/Text/Pandoc/Parsing.hs b/src/Text/Pandoc/Parsing.hs
index 73498788d..a02034de4 100644
--- a/src/Text/Pandoc/Parsing.hs
+++ b/src/Text/Pandoc/Parsing.hs
@@ -1,11 +1,10 @@
-{-# LANGUAGE
- FlexibleContexts
-, GeneralizedNewtypeDeriving
-, TypeSynonymInstances
-, MultiParamTypeClasses
-, FlexibleInstances
-, IncoherentInstances #-}
-
+{-# LANGUAGE ExplicitForAll #-}
+{-# LANGUAGE FlexibleContexts #-}
+{-# LANGUAGE FlexibleInstances #-}
+{-# LANGUAGE GeneralizedNewtypeDeriving #-}
+{-# LANGUAGE IncoherentInstances #-}
+{-# LANGUAGE MultiParamTypeClasses #-}
+{-# LANGUAGE TypeSynonymInstances #-}
{-
Copyright (C) 2006-2017 John MacFarlane <jgm@berkeley.edu>
@@ -187,34 +186,34 @@ module Text.Pandoc.Parsing ( takeWhileP,
)
where
+import Control.Monad.Identity
+import Control.Monad.Reader
+import Data.Char (chr, isAlphaNum, isAscii, isHexDigit, isPunctuation, isSpace,
+ ord, toLower, toUpper)
+import Data.Default
+import Data.List (intercalate, isSuffixOf, transpose)
+import qualified Data.Map as M
+import Data.Maybe (catMaybes)
+import Data.Monoid ((<>))
+import qualified Data.Set as Set
import Data.Text (Text)
+import Text.HTML.TagSoup.Entity (lookupEntity)
+import Text.Pandoc.Asciify (toAsciiChar)
+import Text.Pandoc.Builder (Blocks, HasMeta (..), Inlines, trimInlines)
+import qualified Text.Pandoc.Builder as B
+import Text.Pandoc.Class (PandocMonad, readFileFromDirs, report)
import Text.Pandoc.Definition
+import Text.Pandoc.Logging
import Text.Pandoc.Options
-import Text.Pandoc.Builder (Blocks, Inlines, HasMeta(..), trimInlines)
-import qualified Text.Pandoc.Builder as B
-import Text.Pandoc.XML (fromEntities)
+import Text.Pandoc.Readers.LaTeX.Types (Macro)
+import Text.Pandoc.Shared
import qualified Text.Pandoc.UTF8 as UTF8 (putStrLn)
+import Text.Pandoc.XML (fromEntities)
import Text.Parsec hiding (token)
-import Text.Parsec.Pos (newPos, initialPos, updatePosString)
-import Data.Char ( toLower, toUpper, ord, chr, isAscii, isAlphaNum,
- isHexDigit, isSpace, isPunctuation )
-import Data.List ( intercalate, transpose, isSuffixOf )
-import Text.Pandoc.Shared
-import qualified Data.Map as M
-import Text.Pandoc.Readers.LaTeX.Types (Macro)
-import Text.HTML.TagSoup.Entity ( lookupEntity )
-import Text.Pandoc.Asciify (toAsciiChar)
-import Data.Monoid ((<>))
-import Text.Pandoc.Class (PandocMonad, readFileFromDirs, report)
-import Text.Pandoc.Logging
-import Data.Default
-import qualified Data.Set as Set
-import Control.Monad.Reader
-import Control.Monad.Identity
-import Data.Maybe (catMaybes)
+import Text.Parsec.Pos (initialPos, newPos, updatePosString)
-import Text.Pandoc.Error
import Control.Monad.Except
+import Text.Pandoc.Error
type Parser t s = Parsec t s
@@ -670,9 +669,9 @@ withRaw parser = do
let (l2,c2) = (sourceLine pos2, sourceColumn pos2)
let inplines = take ((l2 - l1) + 1) $ lines inp
let raw = case inplines of
- [] -> ""
- [l] -> take (c2 - c1) l
- ls -> unlines (init ls) ++ take (c2 - 1) (last ls)
+ [] -> ""
+ [l] -> take (c2 - c1) l
+ ls -> unlines (init ls) ++ take (c2 - 1) (last ls)
return (result, raw)
-- | Parses backslash, then applies character parser.
@@ -688,11 +687,11 @@ characterReference = try $ do
ent <- many1Till nonspaceChar (char ';')
let ent' = case ent of
'#':'X':xs -> '#':'x':xs -- workaround tagsoup bug
- '#':_ -> ent
- _ -> ent ++ ";"
+ '#':_ -> ent
+ _ -> ent ++ ";"
case lookupEntity ent' of
- Just (c : _) -> return c
- _ -> fail "entity not found"
+ Just (c : _) -> return c
+ _ -> fail "entity not found"
-- | Parses an uppercase roman numeral and returns (UpperRoman, number).
upperRoman :: Stream s m Char => ParserT s st m (ListNumberStyle, Int)
@@ -1006,7 +1005,7 @@ removeOneLeadingSpace xs =
if all startsWithSpace xs
then map (drop 1) xs
else xs
- where startsWithSpace "" = True
+ where startsWithSpace "" = True
startsWithSpace (y:_) = y == ' '
-- | Parse footer for a grid table.
@@ -1042,36 +1041,36 @@ testStringWith parser str = UTF8.putStrLn $ show $
-- | Parsing options.
data ParserState = ParserState
- { stateOptions :: ReaderOptions, -- ^ User options
- stateParserContext :: ParserContext, -- ^ Inside list?
- stateQuoteContext :: QuoteContext, -- ^ Inside quoted environment?
- stateAllowLinks :: Bool, -- ^ Allow parsing of links
- stateMaxNestingLevel :: Int, -- ^ Max # of nested Strong/Emph
- stateLastStrPos :: Maybe SourcePos, -- ^ Position after last str parsed
- stateKeys :: KeyTable, -- ^ List of reference keys
- stateHeaderKeys :: KeyTable, -- ^ List of implicit header ref keys
- stateSubstitutions :: SubstTable, -- ^ List of substitution references
- stateNotes :: NoteTable, -- ^ List of notes (raw bodies)
- stateNotes' :: NoteTable', -- ^ List of notes (parsed bodies)
- stateNoteRefs :: Set.Set String, -- ^ List of note references used
- stateMeta :: Meta, -- ^ Document metadata
- stateMeta' :: F Meta, -- ^ Document metadata
- stateCitations :: M.Map String String, -- ^ RST-style citations
- stateHeaderTable :: [HeaderType], -- ^ Ordered list of header types used
- stateHeaders :: M.Map Inlines String, -- ^ List of headers and ids (used for implicit ref links)
- stateIdentifiers :: Set.Set String, -- ^ Header identifiers used
- stateNextExample :: Int, -- ^ Number of next example
- stateExamples :: M.Map String Int, -- ^ Map from example labels to numbers
- stateMacros :: M.Map Text Macro, -- ^ Table of macros defined so far
- stateRstDefaultRole :: String, -- ^ Current rST default interpreted text role
- stateRstCustomRoles :: M.Map String (String, Maybe String, Attr), -- ^ Current rST custom text roles
+ { stateOptions :: ReaderOptions, -- ^ User options
+ stateParserContext :: ParserContext, -- ^ Inside list?
+ stateQuoteContext :: QuoteContext, -- ^ Inside quoted environment?
+ stateAllowLinks :: Bool, -- ^ Allow parsing of links
+ stateMaxNestingLevel :: Int, -- ^ Max # of nested Strong/Emph
+ stateLastStrPos :: Maybe SourcePos, -- ^ Position after last str parsed
+ stateKeys :: KeyTable, -- ^ List of reference keys
+ stateHeaderKeys :: KeyTable, -- ^ List of implicit header ref keys
+ stateSubstitutions :: SubstTable, -- ^ List of substitution references
+ stateNotes :: NoteTable, -- ^ List of notes (raw bodies)
+ stateNotes' :: NoteTable', -- ^ List of notes (parsed bodies)
+ stateNoteRefs :: Set.Set String, -- ^ List of note references used
+ stateMeta :: Meta, -- ^ Document metadata
+ stateMeta' :: F Meta, -- ^ Document metadata
+ stateCitations :: M.Map String String, -- ^ RST-style citations
+ stateHeaderTable :: [HeaderType], -- ^ Ordered list of header types used
+ stateHeaders :: M.Map Inlines String, -- ^ List of headers and ids (used for implicit ref links)
+ stateIdentifiers :: Set.Set String, -- ^ Header identifiers used
+ stateNextExample :: Int, -- ^ Number of next example
+ stateExamples :: M.Map String Int, -- ^ Map from example labels to numbers
+ stateMacros :: M.Map Text Macro, -- ^ Table of macros defined so far
+ stateRstDefaultRole :: String, -- ^ Current rST default interpreted text role
+ stateRstCustomRoles :: M.Map String (String, Maybe String, Attr), -- ^ Current rST custom text roles
-- Triple represents: 1) Base role, 2) Optional format (only for :raw:
-- roles), 3) Additional classes (rest of Attr is unused)).
- stateCaption :: Maybe Inlines, -- ^ Caption in current environment
- stateInHtmlBlock :: Maybe String, -- ^ Tag type of HTML block being parsed
- stateFencedDivLevel :: Int, -- ^ Depth of fenced div
- stateContainers :: [String], -- ^ parent include files
- stateLogMessages :: [LogMessage], -- ^ log messages
+ stateCaption :: Maybe Inlines, -- ^ Caption in current environment
+ stateInHtmlBlock :: Maybe String, -- ^ Tag type of HTML block being parsed
+ stateFencedDivLevel :: Int, -- ^ Depth of fenced div
+ stateContainers :: [String], -- ^ parent include files
+ stateLogMessages :: [LogMessage], -- ^ log messages
stateMarkdownAttribute :: Bool -- ^ True if in markdown=1 context
}
diff --git a/src/Text/Pandoc/Readers/DocBook.hs b/src/Text/Pandoc/Readers/DocBook.hs
index 0f3f6f6e3..728f77a05 100644
--- a/src/Text/Pandoc/Readers/DocBook.hs
+++ b/src/Text/Pandoc/Readers/DocBook.hs
@@ -1,22 +1,22 @@
+{-# LANGUAGE ExplicitForAll #-}
module Text.Pandoc.Readers.DocBook ( readDocBook ) where
-import Data.Char (toUpper, isSpace)
-import Text.Pandoc.Shared (safeRead, crFilter)
-import Text.Pandoc.Options
-import Text.Pandoc.Definition
-import Text.Pandoc.Builder
-import Text.XML.Light
-import Text.HTML.TagSoup.Entity (lookupEntity)
+import Control.Monad.State.Strict
+import Data.Char (isSpace, toUpper)
+import Data.Default
import Data.Either (rights)
+import Data.Foldable (asum)
import Data.Generics
-import Control.Monad.State.Strict
import Data.List (intersperse)
import Data.Maybe (fromMaybe)
-import Text.TeXMath (readMathML, writeTeX)
-import Data.Default
-import Data.Foldable (asum)
-import Text.Pandoc.Class (PandocMonad)
import Data.Text (Text)
import qualified Data.Text as T
+import Text.HTML.TagSoup.Entity (lookupEntity)
+import Text.Pandoc.Builder
+import Text.Pandoc.Class (PandocMonad)
+import Text.Pandoc.Options
+import Text.Pandoc.Shared (crFilter, safeRead)
+import Text.TeXMath (readMathML, writeTeX)
+import Text.XML.Light
{-
@@ -538,12 +538,12 @@ handleInstructions ('<':'?':'a':'s':'c':'i':'i':'d':'o':'c':'-':'b':'r':'?':'>':
handleInstructions xs = case break (=='<') xs of
(ys, []) -> ys
([], '<':zs) -> '<' : handleInstructions zs
- (ys, zs) -> ys ++ handleInstructions zs
+ (ys, zs) -> ys ++ handleInstructions zs
getFigure :: PandocMonad m => Element -> DB m Blocks
getFigure e = do
tit <- case filterChild (named "title") e of
- Just t -> getInlines t
+ Just t -> getInlines t
Nothing -> return mempty
modify $ \st -> st{ dbFigureTitle = tit }
res <- getBlocks e
@@ -797,8 +797,8 @@ parseBlock (Elem e) =
return $ p <> b <> x
codeBlockWithLang = do
let classes' = case attrValue "language" e of
- "" -> []
- x -> [x]
+ "" -> []
+ x -> [x]
return $ codeBlockWith (attrValue "id" e, classes', [])
$ trimNl $ strContentRecursive e
parseBlockquote = do
@@ -871,11 +871,11 @@ parseBlock (Elem e) =
|| x == '.') w
Nothing -> 0 :: Double
let numrows = case bodyrows of
- [] -> 0
- xs -> maximum $ map length xs
+ [] -> 0
+ xs -> maximum $ map length xs
let aligns = case colspecs of
- [] -> replicate numrows AlignDefault
- cs -> map toAlignment cs
+ [] -> replicate numrows AlignDefault
+ cs -> map toAlignment cs
let widths = case colspecs of
[] -> replicate numrows 0
cs -> let ws = map toWidth cs
@@ -895,7 +895,7 @@ parseBlock (Elem e) =
headerText <- case filterChild (named "title") e `mplus`
(filterChild (named "info") e >>=
filterChild (named "title")) of
- Just t -> getInlines t
+ Just t -> getInlines t
Nothing -> return mempty
modify $ \st -> st{ dbSectionLevel = n }
b <- getBlocks e
@@ -989,10 +989,10 @@ parseInline (Elem e) =
return $ linkWith attr href "" ils'
"foreignphrase" -> emph <$> innerInlines
"emphasis" -> case attrValue "role" e of
- "bold" -> strong <$> innerInlines
- "strong" -> strong <$> innerInlines
+ "bold" -> strong <$> innerInlines
+ "strong" -> strong <$> innerInlines
"strikethrough" -> strikeout <$> innerInlines
- _ -> emph <$> innerInlines
+ _ -> emph <$> innerInlines
"footnote" -> (note . mconcat) <$>
mapM parseBlock (elContent e)
"title" -> return mempty
diff --git a/src/Text/Pandoc/Readers/Docx.hs b/src/Text/Pandoc/Readers/Docx.hs
index 1874a011a..295b79195 100644
--- a/src/Text/Pandoc/Readers/Docx.hs
+++ b/src/Text/Pandoc/Readers/Docx.hs
@@ -214,14 +214,14 @@ codeDivs :: [String]
codeDivs = ["SourceCode"]
runElemToInlines :: RunElem -> Inlines
-runElemToInlines (TextRun s) = text s
+runElemToInlines (TextRun s) = text s
runElemToInlines LnBrk = linebreak
runElemToInlines Tab = space
runElemToInlines SoftHyphen = text "\xad"
runElemToInlines NoBreakHyphen = text "\x2011"
runElemToString :: RunElem -> String
-runElemToString (TextRun s) = s
+runElemToString (TextRun s) = s
runElemToString LnBrk = ['\n']
runElemToString Tab = ['\t']
runElemToString SoftHyphen = ['\xad']
diff --git a/src/Text/Pandoc/Readers/Docx/Lists.hs b/src/Text/Pandoc/Readers/Docx/Lists.hs
index 53840c609..70eccd7d6 100644
--- a/src/Text/Pandoc/Readers/Docx/Lists.hs
+++ b/src/Text/Pandoc/Readers/Docx/Lists.hs
@@ -157,7 +157,7 @@ flatToBullets elems = flatToBullets' (-1) elems
singleItemHeaderToHeader :: Block -> Block
singleItemHeaderToHeader (OrderedList _ [[h@Header{}]]) = h
-singleItemHeaderToHeader blk = blk
+singleItemHeaderToHeader blk = blk
blocksToBullets :: [Block] -> [Block]
diff --git a/src/Text/Pandoc/Readers/EPUB.hs b/src/Text/Pandoc/Readers/EPUB.hs
index c1eb6ca59..3b13bbe13 100644
--- a/src/Text/Pandoc/Readers/EPUB.hs
+++ b/src/Text/Pandoc/Readers/EPUB.hs
@@ -1,7 +1,7 @@
-{-# LANGUAGE FlexibleContexts #-}
+{-# LANGUAGE FlexibleContexts #-}
-{-# LANGUAGE TupleSections #-}
-{-# LANGUAGE ViewPatterns #-}
+{-# LANGUAGE TupleSections #-}
+{-# LANGUAGE ViewPatterns #-}
module Text.Pandoc.Readers.EPUB
(readEPUB)
diff --git a/src/Text/Pandoc/Readers/HTML.hs b/src/Text/Pandoc/Readers/HTML.hs
index 277405b09..8d37deb26 100644
--- a/src/Text/Pandoc/Readers/HTML.hs
+++ b/src/Text/Pandoc/Readers/HTML.hs
@@ -1,5 +1,8 @@
-{-# LANGUAGE FlexibleContexts, FlexibleInstances, MultiParamTypeClasses,
-ViewPatterns, OverloadedStrings #-}
+{-# LANGUAGE FlexibleContexts #-}
+{-# LANGUAGE FlexibleInstances #-}
+{-# LANGUAGE MultiParamTypeClasses #-}
+{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE ViewPatterns #-}
{-
Copyright (C) 2006-2017 John MacFarlane <jgm@berkeley.edu>
@@ -39,43 +42,42 @@ module Text.Pandoc.Readers.HTML ( readHtml
, isCommentTag
) where
+import Control.Applicative ((<|>))
+import Control.Arrow ((***))
+import Control.Monad (guard, mplus, msum, mzero, unless, void)
+import Control.Monad.Except (throwError)
+import Control.Monad.Reader (ReaderT, ask, asks, lift, local, runReaderT)
+import Data.Char (isAlphaNum, isDigit, isLetter)
+import Data.Default (Default (..), def)
+import Data.Foldable (for_)
+import Data.List (intercalate, isPrefixOf)
+import Data.List.Split (wordsBy)
+import qualified Data.Map as M
+import Data.Maybe (fromMaybe, isJust, isNothing)
+import Data.Monoid (First (..))
+import Data.Monoid ((<>))
+import qualified Data.Set as Set
+import Data.Text (Text)
+import qualified Data.Text as T
+import Network.URI (URI, nonStrictRelativeTo, parseURIReference)
import Text.HTML.TagSoup
import Text.HTML.TagSoup.Match
-import Text.Pandoc.Definition
+import Text.Pandoc.Builder (Blocks, HasMeta (..), Inlines, trimInlines)
import qualified Text.Pandoc.Builder as B
-import Text.Pandoc.Builder (Blocks, Inlines, trimInlines, HasMeta(..))
-import Text.Pandoc.Shared ( extractSpaces, addMetaField
- , escapeURI, safeRead, crFilter, underlineSpan )
-import Text.Pandoc.Options (
- ReaderOptions(readerExtensions,readerStripComments), extensionEnabled,
- Extension (Ext_epub_html_exts,
- Ext_raw_html, Ext_native_divs, Ext_native_spans))
+import Text.Pandoc.Class (PandocMonad (..))
+import Text.Pandoc.CSS (foldOrElse, pickStyleAttrProps)
+import Text.Pandoc.Definition
+import Text.Pandoc.Error
import Text.Pandoc.Logging
+import Text.Pandoc.Options (Extension (Ext_epub_html_exts, Ext_native_divs, Ext_native_spans, Ext_raw_html),
+ ReaderOptions (readerExtensions, readerStripComments),
+ extensionEnabled)
import Text.Pandoc.Parsing hiding ((<|>))
+import Text.Pandoc.Shared (addMetaField, crFilter, escapeURI, extractSpaces,
+ safeRead, underlineSpan)
import Text.Pandoc.Walk
-import qualified Data.Map as M
-import Data.Foldable ( for_ )
-import Data.Maybe ( fromMaybe, isJust, isNothing )
-import Data.List.Split ( wordsBy )
-import Data.List ( intercalate, isPrefixOf )
-import Data.Char ( isDigit, isLetter, isAlphaNum )
-import Control.Monad ( guard, mzero, void, unless, mplus, msum )
-import Control.Arrow ((***))
-import Control.Applicative ( (<|>) )
-import Data.Monoid (First (..))
-import Data.Text (Text)
-import qualified Data.Text as T
-import Text.TeXMath (readMathML, writeTeX)
-import Data.Default (Default (..), def)
-import Control.Monad.Reader (ask, asks, local, ReaderT, runReaderT, lift)
-import Network.URI (URI, parseURIReference, nonStrictRelativeTo)
-import Text.Pandoc.CSS (foldOrElse, pickStyleAttrProps)
-import Data.Monoid ((<>))
import Text.Parsec.Error
-import qualified Data.Set as Set
-import Text.Pandoc.Error
-import Text.Pandoc.Class (PandocMonad(..))
-import Control.Monad.Except (throwError)
+import Text.TeXMath (readMathML, writeTeX)
-- | Convert HTML-formatted string to 'Pandoc' document.
readHtml :: PandocMonad m
@@ -123,8 +125,8 @@ data HTMLState =
}
data HTMLLocal = HTMLLocal { quoteContext :: QuoteContext
- , inChapter :: Bool -- ^ Set if in chapter section
- , inPlain :: Bool -- ^ Set if in pPlain
+ , inChapter :: Bool -- ^ Set if in chapter section
+ , inPlain :: Bool -- ^ Set if in pPlain
}
setInChapter :: PandocMonad m => HTMLParser m s a -> HTMLParser m s a
@@ -354,16 +356,16 @@ fixPlains :: Bool -> Blocks -> Blocks
fixPlains inList bs = if any isParaish bs'
then B.fromList $ map plainToPara bs'
else bs
- where isParaish (Para _) = True
- isParaish (CodeBlock _ _) = True
- isParaish (Header _ _ _) = True
- isParaish (BlockQuote _) = True
- isParaish (BulletList _) = not inList
- isParaish (OrderedList _ _) = not inList
+ where isParaish (Para _) = True
+ isParaish (CodeBlock _ _) = True
+ isParaish (Header _ _ _) = True
+ isParaish (BlockQuote _) = True
+ isParaish (BulletList _) = not inList
+ isParaish (OrderedList _ _) = not inList
isParaish (DefinitionList _) = not inList
- isParaish _ = False
+ isParaish _ = False
plainToPara (Plain xs) = Para xs
- plainToPara x = x
+ plainToPara x = x
bs' = B.toList bs
pRawTag :: PandocMonad m => TagParser m Text
@@ -377,10 +379,10 @@ pRawTag = do
pDiv :: PandocMonad m => TagParser m Blocks
pDiv = try $ do
guardEnabled Ext_native_divs
- let isDivLike "div" = True
+ let isDivLike "div" = True
isDivLike "section" = True
- isDivLike "main" = True
- isDivLike _ = False
+ isDivLike "main" = True
+ isDivLike _ = False
TagOpen tag attr' <- lookAhead $ pSatisfy $ tagOpen isDivLike (const True)
let attr = toStringAttr attr'
contents <- pInTags tag block
@@ -545,9 +547,9 @@ pCell celltype = try $ do
skipMany pBlank
tag <- lookAhead $
pSatisfy (\t -> t ~== TagOpen celltype [] && noColOrRowSpans t)
- let extractAlign' [] = ""
+ let extractAlign' [] = ""
extractAlign' ("text-align":x:_) = x
- extractAlign' (_:xs) = extractAlign' xs
+ extractAlign' (_:xs) = extractAlign' xs
let extractAlign = extractAlign' . wordsBy (`elem` [' ','\t',';',':'])
let align = case maybeFromAttrib "align" tag `mplus`
(extractAlign <$> maybeFromAttrib "style" tag) of
@@ -603,18 +605,18 @@ pCodeBlock = try $ do
let rawText = concatMap tagToString contents
-- drop leading newline if any
let result' = case rawText of
- '\n':xs -> xs
- _ -> rawText
+ '\n':xs -> xs
+ _ -> rawText
-- drop trailing newline if any
let result = case reverse result' of
- '\n':_ -> init result'
- _ -> result'
+ '\n':_ -> init result'
+ _ -> result'
return $ B.codeBlockWith (mkAttr attr) result
tagToString :: Tag Text -> String
-tagToString (TagText s) = T.unpack s
+tagToString (TagText s) = T.unpack s
tagToString (TagOpen "br" _) = "\n"
-tagToString _ = ""
+tagToString _ = ""
inline :: PandocMonad m => TagParser m Inlines
inline = choice
@@ -893,16 +895,16 @@ pStr = do
return $ B.str result
isSpecial :: Char -> Bool
-isSpecial '"' = True
-isSpecial '\'' = True
-isSpecial '.' = True
-isSpecial '-' = True
-isSpecial '$' = True
+isSpecial '"' = True
+isSpecial '\'' = True
+isSpecial '.' = True
+isSpecial '-' = True
+isSpecial '$' = True
isSpecial '\8216' = True
isSpecial '\8217' = True
isSpecial '\8220' = True
isSpecial '\8221' = True
-isSpecial _ = False
+isSpecial _ = False
pSymbol :: PandocMonad m => InlinesParser m Inlines
pSymbol = satisfy isSpecial >>= return . B.str . (:[])
@@ -1123,7 +1125,7 @@ htmlInBalanced' tagname ts = fromMaybe [] $ go 0 ts
hasTagWarning :: [Tag a] -> Bool
hasTagWarning (TagWarning _:_) = True
-hasTagWarning _ = False
+hasTagWarning _ = False
-- | Matches a tag meeting a certain condition.
htmlTag :: (HasReaderOptions st, Monad m)
@@ -1148,7 +1150,7 @@ htmlTag f = try $ do
-- in XML elemnet names
let isNameChar c = isAlphaNum c || c == ':' || c == '-' || c == '_'
let isName s = case s of
- [] -> False
+ [] -> False
(c:cs) -> isLetter c && all isNameChar cs
let endAngle = try $ do char '>'
diff --git a/src/Text/Pandoc/Readers/Muse.hs b/src/Text/Pandoc/Readers/Muse.hs
index 3bb4b64e6..6f4244ac3 100644
--- a/src/Text/Pandoc/Readers/Muse.hs
+++ b/src/Text/Pandoc/Readers/Muse.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE FlexibleContexts #-}
+{-# LANGUAGE FlexibleContexts #-}
{-
Copyright (C) 2017 Alexander Krotov <ilabdsf@gmail.com>
@@ -42,23 +42,23 @@ module Text.Pandoc.Readers.Muse (readMuse) where
import Control.Monad
import Control.Monad.Except (throwError)
-import qualified Data.Map as M
import Data.Char (isLetter)
-import Data.Text (Text, unpack)
import Data.List (stripPrefix)
+import qualified Data.Map as M
import Data.Maybe (fromMaybe)
+import Data.Text (Text, unpack)
+import System.FilePath (takeExtension)
import Text.HTML.TagSoup
import Text.Pandoc.Builder (Blocks, Inlines)
import qualified Text.Pandoc.Builder as B
-import Text.Pandoc.Class (PandocMonad(..))
+import Text.Pandoc.Class (PandocMonad (..))
import Text.Pandoc.Definition
import Text.Pandoc.Logging
import Text.Pandoc.Options
-import Text.Pandoc.Shared (crFilter)
import Text.Pandoc.Parsing hiding (nested)
import Text.Pandoc.Readers.HTML (htmlTag)
+import Text.Pandoc.Shared (crFilter)
import Text.Pandoc.XML (fromEntities)
-import System.FilePath (takeExtension)
-- | Read Muse from an input string and return a Pandoc document.
readMuse :: PandocMonad m
@@ -233,7 +233,7 @@ exampleTag = do
return $ return $ B.codeBlockWith attr $ chop contents
where lchop s = case s of
'\n':ss -> ss
- _ -> s
+ _ -> s
rchop = reverse . lchop . reverse
-- Trim up to one newline from the beginning and the end,
-- in case opening and/or closing tags are on separate lines.
@@ -315,7 +315,7 @@ noteBlock = try $ do
content <- mconcat <$> blocksTillNote
oldnotes <- stateNotes' <$> getState
case M.lookup ref oldnotes of
- Just _ -> logMessage $ DuplicateNoteReference ref pos
+ Just _ -> logMessage $ DuplicateNoteReference ref pos
Nothing -> return ()
updateState $ \s -> s{ stateNotes' = M.insert ref (pos, content) oldnotes }
return mempty
@@ -445,7 +445,7 @@ definitionList = do
data MuseTable = MuseTable
{ museTableCaption :: Inlines
, museTableHeaders :: [[Blocks]]
- , museTableRows :: [[Blocks]]
+ , museTableRows :: [[Blocks]]
, museTableFooters :: [[Blocks]]
}
diff --git a/src/Text/Pandoc/Readers/Odt/ContentReader.hs b/src/Text/Pandoc/Readers/Odt/ContentReader.hs
index 69eececc8..44bd89278 100644
--- a/src/Text/Pandoc/Readers/Odt/ContentReader.hs
+++ b/src/Text/Pandoc/Readers/Odt/ContentReader.hs
@@ -49,7 +49,6 @@ import Data.Maybe
import qualified Text.XML.Light as XML
-import Text.Pandoc.Definition
import Text.Pandoc.Builder
import Text.Pandoc.MediaBag (MediaBag, insertMedia)
import Text.Pandoc.Shared
diff --git a/src/Text/Pandoc/Readers/RST.hs b/src/Text/Pandoc/Readers/RST.hs
index 070a05df1..de488adfe 100644
--- a/src/Text/Pandoc/Readers/RST.hs
+++ b/src/Text/Pandoc/Readers/RST.hs
@@ -36,16 +36,15 @@ import Control.Monad (forM_, guard, liftM, mplus, mzero, when)
import Control.Monad.Except (throwError)
import Control.Monad.Identity (Identity (..))
import Data.Char (isHexDigit, isSpace, toLower, toUpper)
-import Data.List (deleteFirstsBy, intercalate, isInfixOf,
- elemIndex, isSuffixOf, nub, sort, transpose, union)
+import Data.List (deleteFirstsBy, elemIndex, intercalate, isInfixOf, isSuffixOf,
+ nub, sort, transpose, union)
import qualified Data.Map as M
import Data.Maybe (fromMaybe, isJust)
import Data.Monoid ((<>))
import Data.Sequence (ViewR (..), viewr)
import Data.Text (Text)
import qualified Data.Text as T
-import Text.Pandoc.Builder
- (fromList, setMeta, Blocks, Inlines, trimInlines)
+import Text.Pandoc.Builder (Blocks, Inlines, fromList, setMeta, trimInlines)
import qualified Text.Pandoc.Builder as B
import Text.Pandoc.Class (PandocMonad, fetchItem, readFileFromDirs)
import Text.Pandoc.CSV (CSVOptions (..), defaultCSVOptions, parseCSV)
@@ -315,7 +314,7 @@ doubleHeader = do
let headerTable = stateHeaderTable state
let (headerTable',level) = case elemIndex (DoubleHeader c) headerTable of
Just ind -> (headerTable, ind + 1)
- Nothing -> (headerTable ++ [DoubleHeader c], length headerTable + 1)
+ Nothing -> (headerTable ++ [DoubleHeader c], length headerTable + 1)
setState (state { stateHeaderTable = headerTable' })
attr <- registerHeader nullAttr txt
return $ B.headerWith attr level txt
@@ -344,7 +343,7 @@ singleHeader = do
let headerTable = stateHeaderTable state
let (headerTable',level) = case elemIndex (SingleHeader c) headerTable of
Just ind -> (headerTable, ind + 1)
- Nothing -> (headerTable ++ [SingleHeader c], length headerTable + 1)
+ Nothing -> (headerTable ++ [SingleHeader c], length headerTable + 1)
setState (state { stateHeaderTable = headerTable' })
attr <- registerHeader nullAttr txt
return $ B.headerWith attr level txt
diff --git a/src/Text/Pandoc/Readers/Vimwiki.hs b/src/Text/Pandoc/Readers/Vimwiki.hs
index 49da5a6c6..fecbb2fb4 100644
--- a/src/Text/Pandoc/Readers/Vimwiki.hs
+++ b/src/Text/Pandoc/Readers/Vimwiki.hs
@@ -91,12 +91,10 @@ import Text.Pandoc.Parsing (F, ParserState, ParserT, blanklines, emailAddress,
registerHeader, runF, spaceChar, stateMeta',
stateOptions, uri)
import Text.Pandoc.Shared (crFilter, splitBy, stringify, stripFirstAndLast)
-import Text.Parsec.Char
- (alphaNum, anyChar, char, newline, noneOf, spaces, string, oneOf,
- space)
-import Text.Parsec.Combinator
- (choice, count, eof, many1, manyTill, notFollowedBy, option,
- skipMany1, between, lookAhead)
+import Text.Parsec.Char (alphaNum, anyChar, char, newline, noneOf, oneOf, space,
+ spaces, string)
+import Text.Parsec.Combinator (between, choice, count, eof, lookAhead, many1,
+ manyTill, notFollowedBy, option, skipMany1)
import Text.Parsec.Prim (getState, many, try, updateState, (<|>))
readVimwiki :: PandocMonad m => ReaderOptions -> Text -> m Pandoc
diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs
index 9d4877c24..60c8e1a0c 100644
--- a/src/Text/Pandoc/Shared.hs
+++ b/src/Text/Pandoc/Shared.hs
@@ -520,7 +520,7 @@ uniqueIdent title' usedIdents
-- | True if block is a Header block.
isHeaderBlock :: Block -> Bool
isHeaderBlock (Header{}) = True
-isHeaderBlock _ = False
+isHeaderBlock _ = False
-- | Shift header levels up or down.
headerShift :: Int -> Pandoc -> Pandoc
diff --git a/src/Text/Pandoc/Slides.hs b/src/Text/Pandoc/Slides.hs
index d83735029..27e7d3d76 100644
--- a/src/Text/Pandoc/Slides.hs
+++ b/src/Text/Pandoc/Slides.hs
@@ -42,7 +42,7 @@ getSlideLevel = go 6
go least [] = least
nonHOrHR Header{} = False
nonHOrHR HorizontalRule = False
- nonHOrHR _ = True
+ nonHOrHR _ = True
-- | Prepare a block list to be passed to hierarchicalize.
prepSlides :: Int -> [Block] -> [Block]
diff --git a/src/Text/Pandoc/Templates.hs b/src/Text/Pandoc/Templates.hs
index 89d524d96..1ba8d5a05 100644
--- a/src/Text/Pandoc/Templates.hs
+++ b/src/Text/Pandoc/Templates.hs
@@ -1,7 +1,7 @@
-{-# LANGUAGE FlexibleInstances #-}
+{-# LANGUAGE FlexibleInstances #-}
-{-# LANGUAGE OverloadedStrings #-}
-{-# LANGUAGE TypeSynonymInstances #-}
+{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE TypeSynonymInstances #-}
{-
Copyright (C) 2009-2017 John MacFarlane <jgm@berkeley.edu>
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