summaryrefslogtreecommitdiff
path: root/src/Text/Pandoc
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc')
-rw-r--r--src/Text/Pandoc/App.hs219
-rw-r--r--src/Text/Pandoc/Asciify.hs2
-rw-r--r--src/Text/Pandoc/CSS.hs4
-rw-r--r--src/Text/Pandoc/Error.hs9
-rw-r--r--src/Text/Pandoc/Extensions.hs5
-rw-r--r--src/Text/Pandoc/Highlighting.hs10
-rw-r--r--src/Text/Pandoc/Logging.hs54
-rw-r--r--src/Text/Pandoc/MIME.hs6
-rw-r--r--src/Text/Pandoc/MediaBag.hs25
-rw-r--r--src/Text/Pandoc/Options.hs85
-rw-r--r--src/Text/Pandoc/PDF.hs42
-rw-r--r--src/Text/Pandoc/Pretty.hs66
-rw-r--r--src/Text/Pandoc/Process.hs8
-rw-r--r--src/Text/Pandoc/Readers/CommonMark.hs12
-rw-r--r--src/Text/Pandoc/Readers/Docx.hs84
-rw-r--r--src/Text/Pandoc/Readers/Docx/Combine.hs31
-rw-r--r--src/Text/Pandoc/Readers/Docx/Lists.hs30
-rw-r--r--src/Text/Pandoc/Readers/Docx/Parse.hs82
-rw-r--r--src/Text/Pandoc/Readers/Docx/StyleMap.hs12
-rw-r--r--src/Text/Pandoc/Readers/Docx/Util.hs4
-rw-r--r--src/Text/Pandoc/Readers/EPUB.hs60
-rw-r--r--src/Text/Pandoc/Readers/Haddock.hs18
-rw-r--r--src/Text/Pandoc/Readers/LaTeX.hs58
-rw-r--r--src/Text/Pandoc/Readers/Markdown.hs98
-rw-r--r--src/Text/Pandoc/Readers/MediaWiki.hs56
-rw-r--r--src/Text/Pandoc/Readers/Native.hs4
-rw-r--r--src/Text/Pandoc/Readers/OPML.hs15
-rw-r--r--src/Text/Pandoc/Readers/Org.hs18
-rw-r--r--src/Text/Pandoc/Readers/Org/BlockStarts.hs2
-rw-r--r--src/Text/Pandoc/Readers/Org/Blocks.hs50
-rw-r--r--src/Text/Pandoc/Readers/Org/ExportSettings.hs10
-rw-r--r--src/Text/Pandoc/Readers/Org/Inlines.hs48
-rw-r--r--src/Text/Pandoc/Readers/Org/Meta.hs30
-rw-r--r--src/Text/Pandoc/Readers/Org/ParserState.hs48
-rw-r--r--src/Text/Pandoc/Readers/Org/Parsing.hs10
-rw-r--r--src/Text/Pandoc/Readers/Org/Shared.hs8
-rw-r--r--src/Text/Pandoc/Readers/RST.hs52
-rw-r--r--src/Text/Pandoc/Readers/TWiki.hs27
-rw-r--r--src/Text/Pandoc/Readers/Textile.hs32
-rw-r--r--src/Text/Pandoc/Readers/Txt2Tags.hs32
-rw-r--r--src/Text/Pandoc/SelfContained.hs32
-rw-r--r--src/Text/Pandoc/Slides.hs4
-rw-r--r--src/Text/Pandoc/Templates.hs17
-rw-r--r--src/Text/Pandoc/UTF8.hs18
-rw-r--r--src/Text/Pandoc/UUID.hs6
-rw-r--r--src/Text/Pandoc/Writers/AsciiDoc.hs46
-rw-r--r--src/Text/Pandoc/Writers/CommonMark.hs16
-rw-r--r--src/Text/Pandoc/Writers/ConTeXt.hs54
-rw-r--r--src/Text/Pandoc/Writers/Custom.hs47
-rw-r--r--src/Text/Pandoc/Writers/Docbook.hs47
-rw-r--r--src/Text/Pandoc/Writers/Docx.hs145
-rw-r--r--src/Text/Pandoc/Writers/DokuWiki.hs57
-rw-r--r--src/Text/Pandoc/Writers/EPUB.hs188
-rw-r--r--src/Text/Pandoc/Writers/FB2.hs86
-rw-r--r--src/Text/Pandoc/Writers/HTML.hs103
-rw-r--r--src/Text/Pandoc/Writers/Haddock.hs26
-rw-r--r--src/Text/Pandoc/Writers/ICML.hs48
-rw-r--r--src/Text/Pandoc/Writers/LaTeX.hs124
-rw-r--r--src/Text/Pandoc/Writers/Man.hs32
-rw-r--r--src/Text/Pandoc/Writers/Markdown.hs117
-rw-r--r--src/Text/Pandoc/Writers/Math.hs2
-rw-r--r--src/Text/Pandoc/Writers/MediaWiki.hs52
-rw-r--r--src/Text/Pandoc/Writers/Native.hs6
-rw-r--r--src/Text/Pandoc/Writers/ODT.hs40
-rw-r--r--src/Text/Pandoc/Writers/OPML.hs20
-rw-r--r--src/Text/Pandoc/Writers/OpenDocument.hs46
-rw-r--r--src/Text/Pandoc/Writers/Org.hs34
-rw-r--r--src/Text/Pandoc/Writers/RST.hs58
-rw-r--r--src/Text/Pandoc/Writers/RTF.hs36
-rw-r--r--src/Text/Pandoc/Writers/Shared.hs27
-rw-r--r--src/Text/Pandoc/Writers/TEI.hs23
-rw-r--r--src/Text/Pandoc/Writers/Texinfo.hs30
-rw-r--r--src/Text/Pandoc/Writers/Textile.hs36
-rw-r--r--src/Text/Pandoc/Writers/ZimWiki.hs44
-rw-r--r--src/Text/Pandoc/XML.hs18
75 files changed, 1593 insertions, 1558 deletions
diff --git a/src/Text/Pandoc/App.hs b/src/Text/Pandoc/App.hs
index a8a046ccf..d1047c3cf 100644
--- a/src/Text/Pandoc/App.hs
+++ b/src/Text/Pandoc/App.hs
@@ -1,4 +1,6 @@
-{-# LANGUAGE CPP, TupleSections, ScopedTypeVariables #-}
+{-# LANGUAGE CPP #-}
+{-# LANGUAGE ScopedTypeVariables #-}
+{-# LANGUAGE TupleSections #-}
{-
Copyright (C) 2006-2016 John MacFarlane <jgm@berkeley.edu>
@@ -35,51 +37,50 @@ module Text.Pandoc.App (
, parseOptions
, options
) where
-import Text.Pandoc
-import Text.Pandoc.Builder (setMeta)
-import Text.Pandoc.PDF (makePDF)
-import Text.Pandoc.Walk (walk)
-import Text.Pandoc.Shared ( tabFilter, readDataFileUTF8,
- headerShift, err, openURL, safeRead,
- readDataFile )
-import Text.Pandoc.MediaBag ( mediaDirectory, extractMediaBag, MediaBag )
-import Text.Pandoc.XML ( toEntities )
-import Text.Pandoc.Highlighting (highlightingStyles)
-import Text.Pandoc.SelfContained ( makeSelfContained )
-import Text.Pandoc.Process (pipeProcess)
-import Skylighting ( Style, defaultSyntaxMap, Syntax(..) )
-import Text.Printf
-import System.Environment ( getEnvironment, getProgName, getArgs )
import Control.Applicative ((<|>))
-import System.Exit ( ExitCode (..), exitSuccess )
-import System.FilePath
-import Data.Char ( toLower, toUpper )
-import Data.List ( intercalate, isPrefixOf, isSuffixOf, sort )
-import System.Directory ( getAppUserDataDirectory, findExecutable,
- doesFileExist, Permissions(..), getPermissions )
-import System.IO ( stdout, stderr )
-import System.IO.Error ( isDoesNotExistError )
import qualified Control.Exception as E
-import Control.Exception.Extensible ( throwIO )
-import qualified Text.Pandoc.UTF8 as UTF8
+import Control.Exception.Extensible (throwIO)
import Control.Monad
import Control.Monad.Trans
-import Data.Maybe (fromMaybe, isNothing, isJust)
-import Data.Foldable (foldrM)
-import Network.URI (parseURI, isURI, URI(..))
-import qualified Data.ByteString.Lazy as B
+import Data.Aeson (eitherDecode', encode)
import qualified Data.ByteString as BS
+import qualified Data.ByteString.Lazy as B
+import Data.Char (toLower, toUpper)
+import Data.Foldable (foldrM)
+import Data.List (intercalate, isPrefixOf, isSuffixOf, sort)
import qualified Data.Map as M
-import Data.Aeson (eitherDecode', encode)
+import Data.Maybe (fromMaybe, isJust, isNothing)
+import qualified Data.Text as T
import Data.Yaml (decode)
import qualified Data.Yaml as Yaml
-import qualified Data.Text as T
-import System.Console.GetOpt
-import Text.Pandoc.Class (withMediaBag, PandocIO, getLog)
+import Network.URI (URI (..), isURI, parseURI)
import Paths_pandoc (getDataDir)
+import Skylighting (Style, Syntax (..), defaultSyntaxMap)
+import System.Console.GetOpt
+import System.Directory (Permissions (..), doesFileExist, findExecutable,
+ getAppUserDataDirectory, getPermissions)
+import System.Environment (getArgs, getEnvironment, getProgName)
+import System.Exit (ExitCode (..), exitSuccess)
+import System.FilePath
+import System.IO (stderr, stdout)
+import System.IO.Error (isDoesNotExistError)
+import Text.Pandoc
+import Text.Pandoc.Builder (setMeta)
+import Text.Pandoc.Class (PandocIO, getLog, withMediaBag)
+import Text.Pandoc.Highlighting (highlightingStyles)
+import Text.Pandoc.MediaBag (MediaBag, extractMediaBag, mediaDirectory)
+import Text.Pandoc.PDF (makePDF)
+import Text.Pandoc.Process (pipeProcess)
+import Text.Pandoc.SelfContained (makeSelfContained)
+import Text.Pandoc.Shared (err, headerShift, openURL, readDataFile,
+ readDataFileUTF8, safeRead, tabFilter)
+import qualified Text.Pandoc.UTF8 as UTF8
+import Text.Pandoc.Walk (walk)
+import Text.Pandoc.XML (toEntities)
+import Text.Printf
#ifndef _WINDOWS
-import System.Posix.Terminal (queryTerminal)
import System.Posix.IO (stdOutput)
+import System.Posix.Terminal (queryTerminal)
#endif
parseOptions :: [OptDescr (Opt -> IO Opt)] -> Opt -> IO Opt
@@ -119,7 +120,7 @@ convertWithOpts opts = do
let csscdn = "https://cdnjs.cloudflare.com/ajax/libs/KaTeX/0.6.0/katex.min.css"
let mathMethod =
case (optKaTeXJS opts, optKaTeXStylesheet opts) of
- (Nothing, _) -> optHTMLMathMethod opts
+ (Nothing, _) -> optHTMLMathMethod opts
(Just js, ss) -> KaTeX js (fromMaybe csscdn ss)
@@ -151,8 +152,8 @@ convertWithOpts opts = do
Just x -> map toLower x
let writerName = case optWriter opts of
- Nothing -> defaultWriterName outputFile
- Just x -> map toLower x
+ Nothing -> defaultWriterName outputFile
+ Just x -> map toLower x
let format = takeWhile (`notElem` ['+','-'])
$ takeFileName writerName -- in case path to lua script
@@ -196,13 +197,13 @@ convertWithOpts opts = do
Nothing -> do
deftemp <- getDefaultTemplate datadir format
case deftemp of
- Left e -> throwIO e
- Right t -> return (Just t)
+ Left e -> throwIO e
+ Right t -> return (Just t)
Just tp -> do
-- strip off extensions
let tp' = case takeExtension tp of
- "" -> tp <.> format
- _ -> tp
+ "" -> tp <.> format
+ _ -> tp
Just <$> E.catch (UTF8.readFile tp')
(\e -> if isDoesNotExistError e
then E.catch
@@ -221,7 +222,7 @@ convertWithOpts opts = do
-- note: this reverses the list constructed in option parsing,
-- which in turn was reversed from the command-line order,
-- so we end up with the correct order in the variable list:
- let withList _ [] vars = return vars
+ let withList _ [] vars = return vars
withList f (x:xs) vars = f x vars >>= withList f xs
variables <-
@@ -352,7 +353,7 @@ convertWithOpts opts = do
rs <- getLog
return (x, rs)
case optLogFile opts of
- Nothing -> return ()
+ Nothing -> return ()
Just logfile -> B.writeFile logfile (encodeLogMessages reports)
let isWarning msg = messageVerbosity msg == WARNING
when (optFailIfWarnings opts && any isWarning reports) $
@@ -394,7 +395,7 @@ convertWithOpts opts = do
let pdfprog = case () of
_ | conTeXtOutput -> "context"
_ | html5Output -> "wkhtmltopdf"
- _ -> optLaTeXEngine opts
+ _ -> optLaTeXEngine opts
-- check for pdf creating program
mbPdfProg <- liftIO $ findExecutable pdfprog
when (isNothing mbPdfProg) $
@@ -437,7 +438,7 @@ externalFilter f args' d = liftIO $ do
else return True
let (f', args'') = if exists
then case map toLower (takeExtension f) of
- _ | isExecutable -> ("." </> f, args')
+ _ | isExecutable -> ("." </> f, args')
".py" -> ("python", f:args')
".hs" -> ("runhaskell", f:args')
".pl" -> ("perl", f:args')
@@ -465,66 +466,66 @@ externalFilter f args' d = liftIO $ do
-- | Data structure for command line options.
data Opt = Opt
- { optTabStop :: Int -- ^ Number of spaces per tab
- , optPreserveTabs :: Bool -- ^ Preserve tabs instead of converting to spaces
- , optStandalone :: Bool -- ^ Include header, footer
- , optReader :: Maybe String -- ^ Reader format
- , optWriter :: Maybe String -- ^ Writer format
- , optTableOfContents :: Bool -- ^ Include table of contents
- , optBaseHeaderLevel :: Int -- ^ Base header level
- , optTemplate :: Maybe FilePath -- ^ Custom template
- , optVariables :: [(String,String)] -- ^ Template variables to set
- , optMetadata :: [(String, String)] -- ^ Metadata fields to set
- , optOutputFile :: FilePath -- ^ Name of output file
- , optInputFiles :: [FilePath] -- ^ Names of input files
- , optNumberSections :: Bool -- ^ Number sections in LaTeX
- , optNumberOffset :: [Int] -- ^ Starting number for sections
- , optSectionDivs :: Bool -- ^ Put sections in div tags in HTML
- , optIncremental :: Bool -- ^ Use incremental lists in Slidy/Slideous/S5
- , optSelfContained :: Bool -- ^ Make HTML accessible offline
- , optHtmlQTags :: Bool -- ^ Use <q> tags in HTML
- , optHighlightStyle :: Maybe String -- ^ Style to use for highlighted code
- , optTopLevelDivision :: TopLevelDivision -- ^ Type of the top-level divisions
- , optHTMLMathMethod :: HTMLMathMethod -- ^ Method to print HTML math
- , optReferenceDoc :: Maybe FilePath -- ^ Path of reference doc
- , optEpubMetadata :: Maybe FilePath -- ^ EPUB metadata
- , optEpubFonts :: [FilePath] -- ^ EPUB fonts to embed
- , optEpubChapterLevel :: Int -- ^ Header level at which to split chapters
- , optEpubCoverImage :: Maybe FilePath -- ^ Cover image for epub
- , optTOCDepth :: Int -- ^ Number of levels to include in TOC
- , optDumpArgs :: Bool -- ^ Output command-line arguments
- , optIgnoreArgs :: Bool -- ^ Ignore command-line arguments
- , optVerbosity :: Verbosity -- ^ Verbosity of diagnostic output
- , optLogFile :: Maybe FilePath -- ^ File to write JSON log output
- , optFailIfWarnings :: Bool -- ^ Fail on warnings
- , optReferenceLinks :: Bool -- ^ Use reference links in writing markdown, rst
- , optReferenceLocation :: ReferenceLocation -- ^ location for footnotes and link references in markdown output
- , optDpi :: Int -- ^ Dpi
- , optWrapText :: WrapOption -- ^ Options for wrapping text
- , optColumns :: Int -- ^ Line length in characters
- , optFilters :: [FilePath] -- ^ Filters to apply
- , optEmailObfuscation :: ObfuscationMethod
- , optIdentifierPrefix :: String
- , optIndentedCodeClasses :: [String] -- ^ Default classes for indented code blocks
- , optDataDir :: Maybe FilePath
- , optCiteMethod :: CiteMethod -- ^ Method to output cites
- , optListings :: Bool -- ^ Use listings package for code blocks
- , optLaTeXEngine :: String -- ^ Program to use for latex -> pdf
- , optLaTeXEngineArgs :: [String] -- ^ Flags to pass to the latex-engine
- , optSlideLevel :: Maybe Int -- ^ Header level that creates slides
- , optSetextHeaders :: Bool -- ^ Use atx headers for markdown level 1-2
- , optAscii :: Bool -- ^ Use ascii characters only in html
+ { optTabStop :: Int -- ^ Number of spaces per tab
+ , optPreserveTabs :: Bool -- ^ Preserve tabs instead of converting to spaces
+ , optStandalone :: Bool -- ^ Include header, footer
+ , optReader :: Maybe String -- ^ Reader format
+ , optWriter :: Maybe String -- ^ Writer format
+ , optTableOfContents :: Bool -- ^ Include table of contents
+ , optBaseHeaderLevel :: Int -- ^ Base header level
+ , optTemplate :: Maybe FilePath -- ^ Custom template
+ , optVariables :: [(String,String)] -- ^ Template variables to set
+ , optMetadata :: [(String, String)] -- ^ Metadata fields to set
+ , optOutputFile :: FilePath -- ^ Name of output file
+ , optInputFiles :: [FilePath] -- ^ Names of input files
+ , optNumberSections :: Bool -- ^ Number sections in LaTeX
+ , optNumberOffset :: [Int] -- ^ Starting number for sections
+ , optSectionDivs :: Bool -- ^ Put sections in div tags in HTML
+ , optIncremental :: Bool -- ^ Use incremental lists in Slidy/Slideous/S5
+ , optSelfContained :: Bool -- ^ Make HTML accessible offline
+ , optHtmlQTags :: Bool -- ^ Use <q> tags in HTML
+ , optHighlightStyle :: Maybe String -- ^ Style to use for highlighted code
+ , optTopLevelDivision :: TopLevelDivision -- ^ Type of the top-level divisions
+ , optHTMLMathMethod :: HTMLMathMethod -- ^ Method to print HTML math
+ , optReferenceDoc :: Maybe FilePath -- ^ Path of reference doc
+ , optEpubMetadata :: Maybe FilePath -- ^ EPUB metadata
+ , optEpubFonts :: [FilePath] -- ^ EPUB fonts to embed
+ , optEpubChapterLevel :: Int -- ^ Header level at which to split chapters
+ , optEpubCoverImage :: Maybe FilePath -- ^ Cover image for epub
+ , optTOCDepth :: Int -- ^ Number of levels to include in TOC
+ , optDumpArgs :: Bool -- ^ Output command-line arguments
+ , optIgnoreArgs :: Bool -- ^ Ignore command-line arguments
+ , optVerbosity :: Verbosity -- ^ Verbosity of diagnostic output
+ , optLogFile :: Maybe FilePath -- ^ File to write JSON log output
+ , optFailIfWarnings :: Bool -- ^ Fail on warnings
+ , optReferenceLinks :: Bool -- ^ Use reference links in writing markdown, rst
+ , optReferenceLocation :: ReferenceLocation -- ^ location for footnotes and link references in markdown output
+ , optDpi :: Int -- ^ Dpi
+ , optWrapText :: WrapOption -- ^ Options for wrapping text
+ , optColumns :: Int -- ^ Line length in characters
+ , optFilters :: [FilePath] -- ^ Filters to apply
+ , optEmailObfuscation :: ObfuscationMethod
+ , optIdentifierPrefix :: String
+ , optIndentedCodeClasses :: [String] -- ^ Default classes for indented code blocks
+ , optDataDir :: Maybe FilePath
+ , optCiteMethod :: CiteMethod -- ^ Method to output cites
+ , optListings :: Bool -- ^ Use listings package for code blocks
+ , optLaTeXEngine :: String -- ^ Program to use for latex -> pdf
+ , optLaTeXEngineArgs :: [String] -- ^ Flags to pass to the latex-engine
+ , optSlideLevel :: Maybe Int -- ^ Header level that creates slides
+ , optSetextHeaders :: Bool -- ^ Use atx headers for markdown level 1-2
+ , optAscii :: Bool -- ^ Use ascii characters only in html
, optDefaultImageExtension :: String -- ^ Default image extension
- , optExtractMedia :: Maybe FilePath -- ^ Path to extract embedded media
- , optTrackChanges :: TrackChanges -- ^ Accept or reject MS Word track-changes.
- , optFileScope :: Bool -- ^ Parse input files before combining
- , optKaTeXStylesheet :: Maybe String -- ^ Path to stylesheet for KaTeX
- , optKaTeXJS :: Maybe String -- ^ Path to js file for KaTeX
- , optTitlePrefix :: Maybe String -- ^ Prefix for title
- , optCss :: [FilePath] -- ^ CSS files to link to
- , optIncludeBeforeBody :: [FilePath] -- ^ Files to include before
- , optIncludeAfterBody :: [FilePath] -- ^ Files to include after body
- , optIncludeInHeader :: [FilePath] -- ^ Files to include in header
+ , optExtractMedia :: Maybe FilePath -- ^ Path to extract embedded media
+ , optTrackChanges :: TrackChanges -- ^ Accept or reject MS Word track-changes.
+ , optFileScope :: Bool -- ^ Parse input files before combining
+ , optKaTeXStylesheet :: Maybe String -- ^ Path to stylesheet for KaTeX
+ , optKaTeXJS :: Maybe String -- ^ Path to js file for KaTeX
+ , optTitlePrefix :: Maybe String -- ^ Prefix for title
+ , optCss :: [FilePath] -- ^ CSS files to link to
+ , optIncludeBeforeBody :: [FilePath] -- ^ Files to include before
+ , optIncludeAfterBody :: [FilePath] -- ^ Files to include after body
+ , optIncludeInHeader :: [FilePath] -- ^ Files to include in header
}
-- | Defaults for command-line options.
@@ -675,7 +676,7 @@ defaultWriterName x =
".icml" -> "icml"
".tei.xml" -> "tei"
".tei" -> "tei"
- ['.',y] | y `elem` ['1'..'9'] -> "man"
+ ['.',y] | y `elem` ['1'..'9'] -> "man"
_ -> "html"
-- Transformations of a Pandoc document post-parsing:
@@ -1210,8 +1211,8 @@ options =
(OptArg
(\arg opt -> do
let url' = case arg of
- Just u -> u ++ "?"
- Nothing -> "/cgi-bin/mimetex.cgi?"
+ Just u -> u ++ "?"
+ Nothing -> "/cgi-bin/mimetex.cgi?"
return opt { optHTMLMathMethod = WebTeX url' })
"URL")
"" -- "Use mimetex for HTML math"
@@ -1423,7 +1424,7 @@ handleUnrecognizedOption x =
uppercaseFirstLetter :: String -> String
uppercaseFirstLetter (c:cs) = toUpper c : cs
-uppercaseFirstLetter [] = []
+uppercaseFirstLetter [] = []
readers'names :: [String]
readers'names = sort (map fst (readers :: [(String, Reader PandocIO)]))
diff --git a/src/Text/Pandoc/Asciify.hs b/src/Text/Pandoc/Asciify.hs
index 8eb1ba663..411a112b2 100644
--- a/src/Text/Pandoc/Asciify.hs
+++ b/src/Text/Pandoc/Asciify.hs
@@ -30,8 +30,8 @@ ascii equivalents (used in constructing HTML identifiers).
-}
module Text.Pandoc.Asciify (toAsciiChar)
where
-import qualified Data.Map as M
import Data.Char (isAscii)
+import qualified Data.Map as M
toAsciiChar :: Char -> Maybe Char
toAsciiChar c | isAscii c = Just c
diff --git a/src/Text/Pandoc/CSS.hs b/src/Text/Pandoc/CSS.hs
index f479ed9d0..3e2fd6309 100644
--- a/src/Text/Pandoc/CSS.hs
+++ b/src/Text/Pandoc/CSS.hs
@@ -25,14 +25,14 @@ foldOrElse v xs = foldr (orElse v) v xs
eitherToMaybe :: Either a b -> Maybe b
eitherToMaybe (Right x) = Just x
-eitherToMaybe _ = Nothing
+eitherToMaybe _ = Nothing
-- | takes a list of keys/properties and a CSS string and
-- returns the corresponding key-value-pairs.
pickStylesToKVs :: [String] -> String -> [(String, String)]
pickStylesToKVs props styleAttr =
case parse styleAttrParser "" styleAttr of
- Left _ -> []
+ Left _ -> []
Right styles -> filter (\s -> fst s `elem` props) styles
-- | takes a list of key/property synonyms and a CSS string and maybe
diff --git a/src/Text/Pandoc/Error.hs b/src/Text/Pandoc/Error.hs
index 159f4340c..4b38348ac 100644
--- a/src/Text/Pandoc/Error.hs
+++ b/src/Text/Pandoc/Error.hs
@@ -1,4 +1,5 @@
-{-# LANGUAGE DeriveDataTypeable, DeriveGeneric #-}
+{-# LANGUAGE DeriveDataTypeable #-}
+{-# LANGUAGE DeriveGeneric #-}
{-
Copyright (C) 2006-2016 John MacFarlane <jgm@berkeley.edu>
@@ -33,12 +34,12 @@ module Text.Pandoc.Error (
PandocError(..),
handleError) where
-import Text.Parsec.Error
-import Text.Parsec.Pos hiding (Line)
+import Control.Exception (Exception)
import Data.Generics (Typeable)
import GHC.Generics (Generic)
-import Control.Exception (Exception)
import Text.Pandoc.Shared (err)
+import Text.Parsec.Error
+import Text.Parsec.Pos hiding (Line)
type Input = String
diff --git a/src/Text/Pandoc/Extensions.hs b/src/Text/Pandoc/Extensions.hs
index d5e59e8e1..f6db6dc0f 100644
--- a/src/Text/Pandoc/Extensions.hs
+++ b/src/Text/Pandoc/Extensions.hs
@@ -1,4 +1,5 @@
-{-# LANGUAGE DeriveDataTypeable, DeriveGeneric #-}
+{-# LANGUAGE DeriveDataTypeable #-}
+{-# LANGUAGE DeriveGeneric #-}
{-
Copyright (C) 2012-2016 John MacFarlane <jgm@berkeley.edu>
@@ -42,7 +43,7 @@ module Text.Pandoc.Extensions ( Extension(..)
, githubMarkdownExtensions
, multimarkdownExtensions )
where
-import Data.Bits (testBit, setBit, clearBit)
+import Data.Bits (clearBit, setBit, testBit)
import Data.Data (Data)
import Data.Typeable (Typeable)
import GHC.Generics (Generic)
diff --git a/src/Text/Pandoc/Highlighting.hs b/src/Text/Pandoc/Highlighting.hs
index df060915c..80e6581b7 100644
--- a/src/Text/Pandoc/Highlighting.hs
+++ b/src/Text/Pandoc/Highlighting.hs
@@ -49,14 +49,14 @@ module Text.Pandoc.Highlighting ( highlightingStyles
, fromListingsLanguage
, toListingsLanguage
) where
-import Text.Pandoc.Definition
-import Text.Pandoc.Shared (safeRead)
-import Skylighting
-import Data.Maybe (fromMaybe)
+import Control.Monad
import Data.Char (toLower)
import qualified Data.Map as M
-import Control.Monad
+import Data.Maybe (fromMaybe)
import qualified Data.Text as T
+import Skylighting
+import Text.Pandoc.Definition
+import Text.Pandoc.Shared (safeRead)
highlightingStyles :: [(String, Style)]
highlightingStyles =
diff --git a/src/Text/Pandoc/Logging.hs b/src/Text/Pandoc/Logging.hs
index 32695f03d..e7d81d292 100644
--- a/src/Text/Pandoc/Logging.hs
+++ b/src/Text/Pandoc/Logging.hs
@@ -1,4 +1,6 @@
-{-# LANGUAGE DeriveDataTypeable, DeriveGeneric, OverloadedStrings #-}
+{-# LANGUAGE DeriveDataTypeable #-}
+{-# LANGUAGE DeriveGeneric #-}
+{-# LANGUAGE OverloadedStrings #-}
{-
Copyright (C) 2016-17 John MacFarlane <jgm@berkeley.edu>
@@ -37,16 +39,16 @@ module Text.Pandoc.Logging (
, messageVerbosity
) where
-import Text.Parsec.Pos
+import Data.Aeson
+import Data.Aeson.Encode.Pretty (Config (..), defConfig, encodePretty',
+ keyOrder)
+import qualified Data.ByteString.Lazy as BL
import Data.Data (Data)
import Data.Generics (Typeable)
-import GHC.Generics (Generic)
import qualified Data.Text as Text
-import Data.Aeson
+import GHC.Generics (Generic)
import Text.Pandoc.Definition
-import Data.Aeson.Encode.Pretty (encodePretty', keyOrder,
- defConfig, Config(..))
-import qualified Data.ByteString.Lazy as BL
+import Text.Parsec.Pos
-- | Verbosity level.
data Verbosity = ERROR | WARNING | INFO | DEBUG
@@ -240,23 +242,23 @@ showLogMessage msg =
messageVerbosity:: LogMessage -> Verbosity
messageVerbosity msg =
case msg of
- SkippedContent{} -> INFO
- CouldNotParseYamlMetadata{} -> WARNING
- DuplicateLinkReference{} -> WARNING
- DuplicateNoteReference{} -> WARNING
- ReferenceNotFound{} -> WARNING
- CircularReference{} -> WARNING
- CouldNotLoadIncludeFile{} -> WARNING
- ParsingUnescaped{} -> INFO
- ParsingTrace{} -> DEBUG
- InlineNotRendered{} -> INFO
- BlockNotRendered{} -> INFO
- DocxParserWarning{} -> WARNING
- CouldNotFetchResource{} -> WARNING
+ SkippedContent{} -> INFO
+ CouldNotParseYamlMetadata{} -> WARNING
+ DuplicateLinkReference{} -> WARNING
+ DuplicateNoteReference{} -> WARNING
+ ReferenceNotFound{} -> WARNING
+ CircularReference{} -> WARNING
+ CouldNotLoadIncludeFile{} -> WARNING
+ ParsingUnescaped{} -> INFO
+ ParsingTrace{} -> DEBUG
+ InlineNotRendered{} -> INFO
+ BlockNotRendered{} -> INFO
+ DocxParserWarning{} -> WARNING
+ CouldNotFetchResource{} -> WARNING
CouldNotDetermineImageSize{} -> WARNING
- CouldNotConvertImage{} -> WARNING
- CouldNotDetermineMimeType{} -> WARNING
- CouldNotConvertTeXMath{} -> WARNING
- CouldNotParseCSS{} -> WARNING
- Fetching{} -> INFO
- NoTitleElement{} -> WARNING
+ CouldNotConvertImage{} -> WARNING
+ CouldNotDetermineMimeType{} -> WARNING
+ CouldNotConvertTeXMath{} -> WARNING
+ CouldNotParseCSS{} -> WARNING
+ Fetching{} -> INFO
+ NoTitleElement{} -> WARNING
diff --git a/src/Text/Pandoc/MIME.hs b/src/Text/Pandoc/MIME.hs
index 6fe3d6b20..2e4a97b71 100644
--- a/src/Text/Pandoc/MIME.hs
+++ b/src/Text/Pandoc/MIME.hs
@@ -29,11 +29,11 @@ Mime type lookup for ODT writer.
-}
module Text.Pandoc.MIME ( MimeType, getMimeType, getMimeTypeDef,
extensionFromMimeType )where
-import System.FilePath
-import Data.Char ( toLower )
+import Data.Char (toLower)
import Data.List (isPrefixOf, isSuffixOf)
-import Data.Maybe (fromMaybe)
import qualified Data.Map as M
+import Data.Maybe (fromMaybe)
+import System.FilePath
type MimeType = String
diff --git a/src/Text/Pandoc/MediaBag.hs b/src/Text/Pandoc/MediaBag.hs
index fe99be5fe..b865f97c2 100644
--- a/src/Text/Pandoc/MediaBag.hs
+++ b/src/Text/Pandoc/MediaBag.hs
@@ -1,4 +1,5 @@
-{-# LANGUAGE GeneralizedNewtypeDeriving, DeriveDataTypeable #-}
+{-# LANGUAGE DeriveDataTypeable #-}
+{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-
Copyright (C) 2014 John MacFarlane <jgm@berkeley.edu>
@@ -36,19 +37,19 @@ module Text.Pandoc.MediaBag (
mediaDirectory,
extractMediaBag
) where
+import Control.Monad (when)
+import Control.Monad.Trans (MonadIO (..))
+import qualified Data.ByteString.Lazy as BL
+import Data.Data (Data)
+import qualified Data.Map as M
+import Data.Maybe (fromMaybe)
+import Data.Typeable (Typeable)
+import System.Directory (createDirectoryIfMissing)
import System.FilePath
import qualified System.FilePath.Posix as Posix
-import System.Directory (createDirectoryIfMissing)
-import qualified Data.Map as M
-import qualified Data.ByteString.Lazy as BL
-import Control.Monad (when)
-import Control.Monad.Trans (MonadIO(..))
+import System.IO (stderr)
import Text.Pandoc.MIME (MimeType, getMimeTypeDef)
import qualified Text.Pandoc.UTF8 as UTF8
-import Data.Maybe (fromMaybe)
-import System.IO (stderr)
-import Data.Data (Data)
-import Data.Typeable (Typeable)
-- | A container for a collection of binary resources, with names and
-- mime types. Note that a 'MediaBag' is a Monoid, so 'mempty'
@@ -71,8 +72,8 @@ insertMedia fp mbMime contents (MediaBag mediamap) =
MediaBag (M.insert (splitDirectories fp) (mime, contents) mediamap)
where mime = fromMaybe fallback mbMime
fallback = case takeExtension fp of
- ".gz" -> getMimeTypeDef $ dropExtension fp
- _ -> getMimeTypeDef fp
+ ".gz" -> getMimeTypeDef $ dropExtension fp
+ _ -> getMimeTypeDef fp
-- | Lookup a media item in a 'MediaBag', returning mime type and contents.
lookupMedia :: FilePath
diff --git a/src/Text/Pandoc/Options.hs b/src/Text/Pandoc/Options.hs
index 41688af89..6db53c3dc 100644
--- a/src/Text/Pandoc/Options.hs
+++ b/src/Text/Pandoc/Options.hs
@@ -1,4 +1,5 @@
-{-# LANGUAGE DeriveDataTypeable, DeriveGeneric #-}
+{-# LANGUAGE DeriveDataTypeable #-}
+{-# LANGUAGE DeriveGeneric #-}
{-
Copyright (C) 2012-2016 John MacFarlane <jgm@berkeley.edu>
@@ -44,23 +45,23 @@ module Text.Pandoc.Options ( module Text.Pandoc.Extensions
, def
, isEnabled
) where
-import Text.Pandoc.Extensions
-import Data.Default
-import Text.Pandoc.Highlighting (Style, pygments)
import Data.Data (Data)
+import Data.Default
import Data.Typeable (Typeable)
import GHC.Generics (Generic)
+import Text.Pandoc.Extensions
+import Text.Pandoc.Highlighting (Style, pygments)
data ReaderOptions = ReaderOptions{
- readerExtensions :: Extensions -- ^ Syntax extensions
- , readerStandalone :: Bool -- ^ Standalone document with header
- , readerColumns :: Int -- ^ Number of columns in terminal
- , readerTabStop :: Int -- ^ Tab stop
- , readerApplyMacros :: Bool -- ^ Apply macros to TeX math
- , readerIndentedCodeClasses :: [String] -- ^ Default classes for
+ readerExtensions :: Extensions -- ^ Syntax extensions
+ , readerStandalone :: Bool -- ^ Standalone document with header
+ , readerColumns :: Int -- ^ Number of columns in terminal
+ , readerTabStop :: Int -- ^ Tab stop
+ , readerApplyMacros :: Bool -- ^ Apply macros to TeX math
+ , readerIndentedCodeClasses :: [String] -- ^ Default classes for
-- indented code blocks
, readerDefaultImageExtension :: String -- ^ Default extension for images
- , readerTrackChanges :: TrackChanges
+ , readerTrackChanges :: TrackChanges
} deriving (Show, Read, Data, Typeable, Generic)
instance Default ReaderOptions
@@ -139,39 +140,39 @@ data ReferenceLocation = EndOfBlock -- ^ End of block
-- | Options for writers
data WriterOptions = WriterOptions
- { writerTemplate :: Maybe String -- ^ Template to use
- , writerVariables :: [(String, String)] -- ^ Variables to set in template
- , writerTabStop :: Int -- ^ Tabstop for conversion btw spaces and tabs
- , writerTableOfContents :: Bool -- ^ Include table of contents
- , writerIncremental :: Bool -- ^ True if lists should be incremental
- , writerHTMLMathMethod :: HTMLMathMethod -- ^ How to print math in HTML
- , writerNumberSections :: Bool -- ^ Number sections in LaTeX
- , writerNumberOffset :: [Int] -- ^ Starting number for section, subsection, ...
- , writerSectionDivs :: Bool -- ^ Put sections in div tags in HTML
- , writerExtensions :: Extensions -- ^ Markdown extensions that can be used
- , writerReferenceLinks :: Bool -- ^ Use reference links in writing markdown, rst
- , writerDpi :: Int -- ^ Dpi for pixel to/from inch/cm conversions
- , writerWrapText :: WrapOption -- ^ Option for wrapping text
- , writerColumns :: Int -- ^ Characters in a line (for text wrapping)
- , writerEmailObfuscation :: ObfuscationMethod -- ^ How to obfuscate emails
- , writerIdentifierPrefix :: String -- ^ Prefix for section & note ids in HTML
+ { writerTemplate :: Maybe String -- ^ Template to use
+ , writerVariables :: [(String, String)] -- ^ Variables to set in template
+ , writerTabStop :: Int -- ^ Tabstop for conversion btw spaces and tabs
+ , writerTableOfContents :: Bool -- ^ Include table of contents
+ , writerIncremental :: Bool -- ^ True if lists should be incremental
+ , writerHTMLMathMethod :: HTMLMathMethod -- ^ How to print math in HTML
+ , writerNumberSections :: Bool -- ^ Number sections in LaTeX
+ , writerNumberOffset :: [Int] -- ^ Starting number for section, subsection, ...
+ , writerSectionDivs :: Bool -- ^ Put sections in div tags in HTML
+ , writerExtensions :: Extensions -- ^ Markdown extensions that can be used
+ , writerReferenceLinks :: Bool -- ^ Use reference links in writing markdown, rst
+ , writerDpi :: Int -- ^ Dpi for pixel to/from inch/cm conversions
+ , writerWrapText :: WrapOption -- ^ Option for wrapping text
+ , writerColumns :: Int -- ^ Characters in a line (for text wrapping)
+ , writerEmailObfuscation :: ObfuscationMethod -- ^ How to obfuscate emails
+ , writerIdentifierPrefix :: String -- ^ Prefix for section & note ids in HTML
-- and for footnote marks in markdown
- , writerSourceURL :: Maybe String -- ^ Absolute URL + directory of 1st source file
- , writerUserDataDir :: Maybe FilePath -- ^ Path of user data directory
- , writerCiteMethod :: CiteMethod -- ^ How to print cites
- , writerHtmlQTags :: Bool -- ^ Use @<q>@ tags for quotes in HTML
- , writerSlideLevel :: Maybe Int -- ^ Force header level of slides
- , writerTopLevelDivision :: TopLevelDivision -- ^ Type of top-level divisions
- , writerListings :: Bool -- ^ Use listings package for code
- , writerHighlightStyle :: Maybe Style -- ^ Style to use for highlighting
+ , writerSourceURL :: Maybe String -- ^ Absolute URL + directory of 1st source file
+ , writerUserDataDir :: Maybe FilePath -- ^ Path of user data directory
+ , writerCiteMethod :: CiteMethod -- ^ How to print cites
+ , writerHtmlQTags :: Bool -- ^ Use @<q>@ tags for quotes in HTML
+ , writerSlideLevel :: Maybe Int -- ^ Force header level of slides
+ , writerTopLevelDivision :: TopLevelDivision -- ^ Type of top-level divisions
+ , writerListings :: Bool -- ^ Use listings package for code
+ , writerHighlightStyle :: Maybe Style -- ^ Style to use for highlighting
-- (Nothing = no highlighting)
- , writerSetextHeaders :: Bool -- ^ Use setext headers for levels 1-2 in markdown
- , writerEpubMetadata :: Maybe String -- ^ Metadata to include in EPUB
- , writerEpubFonts :: [FilePath] -- ^ Paths to fonts to embed
- , writerEpubChapterLevel :: Int -- ^ Header level for chapters (separate files)
- , writerTOCDepth :: Int -- ^ Number of levels to include in TOC
- , writerReferenceDoc :: Maybe FilePath -- ^ Path to reference document if specified
- , writerLaTeXArgs :: [String] -- ^ Flags to pass to latex-engine
+ , writerSetextHeaders :: Bool -- ^ Use setext headers for levels 1-2 in markdown
+ , writerEpubMetadata :: Maybe String -- ^ Metadata to include in EPUB
+ , writerEpubFonts :: [FilePath] -- ^ Paths to fonts to embed
+ , writerEpubChapterLevel :: Int -- ^ Header level for chapters (separate files)
+ , writerTOCDepth :: Int -- ^ Number of levels to include in TOC
+ , writerReferenceDoc :: Maybe FilePath -- ^ Path to reference document if specified
+ , writerLaTeXArgs :: [String] -- ^ Flags to pass to latex-engine
, writerReferenceLocation :: ReferenceLocation -- ^ Location of footnotes and references for writing markdown
} deriving (Show, Data, Typeable, Generic)
diff --git a/src/Text/Pandoc/PDF.hs b/src/Text/Pandoc/PDF.hs
index ff206daaa..43110abf1 100644
--- a/src/Text/Pandoc/PDF.hs
+++ b/src/Text/Pandoc/PDF.hs
@@ -1,4 +1,6 @@
-{-# LANGUAGE OverloadedStrings, CPP, ScopedTypeVariables #-}
+{-# LANGUAGE CPP #-}
+{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE ScopedTypeVariables #-}
{-
Copyright (C) 2012-2016 John MacFarlane <jgm@berkeley.edu>
@@ -30,39 +32,39 @@ Conversion of LaTeX documents to PDF.
-}
module Text.Pandoc.PDF ( makePDF ) where
+import qualified Codec.Picture as JP
+import qualified Control.Exception as E
+import Control.Monad (unless, when, (<=<))
+import Control.Monad.Trans (MonadIO (..))
+import qualified Data.ByteString as BS
import Data.ByteString.Lazy (ByteString)
import qualified Data.ByteString.Lazy as B
+import qualified Data.ByteString.Lazy as BL
import qualified Data.ByteString.Lazy.Char8 as BC
-import qualified Data.ByteString as BS
+import Data.Digest.Pure.SHA (sha1, showDigest)
+import Data.List (isInfixOf)
+import Data.Maybe (fromMaybe)
import Data.Monoid ((<>))
+import System.Directory
+import System.Environment
import System.Exit (ExitCode (..))
import System.FilePath
import System.IO (stdout)
-import System.IO.Temp (withTempFile, withTempDirectory)
-import System.Directory
-import Data.Digest.Pure.SHA (showDigest, sha1)
-import System.Environment
-import Control.Monad (unless, when, (<=<))
-import qualified Control.Exception as E
-import Data.List (isInfixOf)
-import Data.Maybe (fromMaybe)
-import qualified Text.Pandoc.UTF8 as UTF8
+import System.IO.Temp (withTempDirectory, withTempFile)
import Text.Pandoc.Definition
import Text.Pandoc.MediaBag
-import Text.Pandoc.Walk (walkM)
-import Text.Pandoc.Shared (withTempDir, inDirectory, stringify)
-import Text.Pandoc.Writers.Shared (getField, metaToJSON)
-import Text.Pandoc.Options (WriterOptions(..), HTMLMathMethod(..))
import Text.Pandoc.MIME (extensionFromMimeType, getMimeType)
+import Text.Pandoc.Options (HTMLMathMethod (..), WriterOptions (..))
import Text.Pandoc.Process (pipeProcess)
-import Control.Monad.Trans (MonadIO(..))
-import qualified Data.ByteString.Lazy as BL
-import qualified Codec.Picture as JP
+import Text.Pandoc.Shared (inDirectory, stringify, withTempDir)
+import qualified Text.Pandoc.UTF8 as UTF8
+import Text.Pandoc.Walk (walkM)
+import Text.Pandoc.Writers.Shared (getField, metaToJSON)
#ifdef _WINDOWS
import Data.List (intercalate)
#endif
-import Text.Pandoc.Class (PandocIO, runIOorExplode, fetchItem, report,
- setVerbosity, setMediaBag, runIO)
+import Text.Pandoc.Class (PandocIO, fetchItem, report, runIO, runIOorExplode,
+ setMediaBag, setVerbosity)
import Text.Pandoc.Logging
#ifdef _WINDOWS
diff --git a/src/Text/Pandoc/Pretty.hs b/src/Text/Pandoc/Pretty.hs
index 2cf728b9c..32e60843c 100644
--- a/src/Text/Pandoc/Pretty.hs
+++ b/src/Text/Pandoc/Pretty.hs
@@ -1,4 +1,5 @@
-{-# LANGUAGE GeneralizedNewtypeDeriving, CPP #-}
+{-# LANGUAGE CPP #-}
+{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-
Copyright (C) 2010-2016 John MacFarlane <jgm@berkeley.edu>
@@ -76,22 +77,23 @@ module Text.Pandoc.Pretty (
)
where
-import Data.Sequence (Seq, fromList, (<|), singleton, mapWithIndex, viewl, ViewL(..))
-import qualified Data.Sequence as Seq
-import Data.Foldable (toList)
-import Data.List (intersperse)
-import Data.String
import Control.Monad.State
import Data.Char (isSpace)
+import Data.Foldable (toList)
+import Data.List (intersperse)
import Data.Monoid ((<>))
+import Data.Sequence (Seq, ViewL (..), fromList, mapWithIndex, singleton, viewl,
+ (<|))
+import qualified Data.Sequence as Seq
+import Data.String
data RenderState a = RenderState{
- output :: [a] -- ^ In reverse order
- , prefix :: String
- , usePrefix :: Bool
- , lineLength :: Maybe Int -- ^ 'Nothing' means no wrapping
- , column :: Int
- , newlines :: Int -- ^ Number of preceding newlines
+ output :: [a] -- ^ In reverse order
+ , prefix :: String
+ , usePrefix :: Bool
+ , lineLength :: Maybe Int -- ^ 'Nothing' means no wrapping
+ , column :: Int
+ , newlines :: Int -- ^ Number of preceding newlines
}
type DocState a = State (RenderState a) ()
@@ -184,21 +186,21 @@ nestle :: Doc -> Doc
nestle (Doc d) = Doc $ go d
where go x = case viewl x of
(BlankLines _ :< rest) -> go rest
- (NewLine :< rest) -> go rest
- _ -> x
+ (NewLine :< rest) -> go rest
+ _ -> x
-- | Chomps trailing blank space off of a 'Doc'.
chomp :: Doc -> Doc
chomp d = Doc (fromList dl')
where dl = toList (unDoc d)
dl' = reverse $ go $ reverse dl
- go [] = []
- go (BreakingSpace : xs) = go xs
+ go [] = []
+ go (BreakingSpace : xs) = go xs
go (CarriageReturn : xs) = go xs
- go (NewLine : xs) = go xs
- go (BlankLines _ : xs) = go xs
- go (Prefixed s d' : xs) = Prefixed s (chomp d') : xs
- go xs = xs
+ go (NewLine : xs) = go xs
+ go (BlankLines _ : xs) = go xs
+ go (Prefixed s d' : xs) = Prefixed s (chomp d') : xs
+ go xs = xs
outp :: (IsString a) => Int -> String -> DocState a
outp off s | off < 0 = do -- offset < 0 means newline characters
@@ -306,10 +308,10 @@ renderList (BreakingSpace : NewLine : xs) = renderList (NewLine:xs)
renderList (BreakingSpace : BlankLines n : xs) = renderList (BlankLines n:xs)
renderList (BreakingSpace : BreakingSpace : xs) = renderList (BreakingSpace:xs)
renderList (BreakingSpace : xs) = do
- let isText (Text _ _) = True
- isText (Block _ _) = True
- isText (AfterBreak _) = True
- isText _ = False
+ let isText (Text _ _) = True
+ isText (Block _ _) = True
+ isText (AfterBreak _) = True
+ isText _ = False
let isBreakingSpace BreakingSpace = True
isBreakingSpace _ = False
let xs' = dropWhile isBreakingSpace xs
@@ -342,7 +344,7 @@ renderList (Block _width lns : xs) = do
let oldPref = prefix st
case column st - realLength oldPref of
n | n > 0 -> modify $ \s -> s{ prefix = oldPref ++ replicate n ' ' }
- _ -> return ()
+ _ -> return ()
renderList $ intersperse CarriageReturn (map (Text 0) lns)
modify $ \s -> s{ prefix = oldPref }
renderList xs
@@ -362,10 +364,10 @@ mergeBlocks addSpace (IsBlock w1 lns1) (IsBlock w2 lns2) =
sp xs = if addSpace then (' ' : xs) else xs
offsetOf :: D -> Int
-offsetOf (Text o _) = o
-offsetOf (Block w _) = w
-offsetOf BreakingSpace = 1
-offsetOf _ = 0
+offsetOf (Text o _) = o
+offsetOf (Block w _) = w
+offsetOf BreakingSpace = 1
+offsetOf _ = 0
-- | A literal string.
text :: String -> Doc
@@ -430,7 +432,7 @@ beforeNonBlank d = Doc $ singleton (BeforeNonBlank d)
nowrap :: Doc -> Doc
nowrap doc = Doc $ mapWithIndex replaceSpace $ unDoc doc
where replaceSpace _ BreakingSpace = Text 1 " "
- replaceSpace _ x = x
+ replaceSpace _ x = x
-- | Content to print only if it comes at the beginning of a line,
-- to be used e.g. for escaping line-initial `.` in groff man.
@@ -440,8 +442,8 @@ afterBreak s = Doc $ singleton (AfterBreak s)
-- | Returns the width of a 'Doc'.
offset :: Doc -> Int
offset d = case map realLength . lines . render Nothing $ d of
- [] -> 0
- os -> maximum os
+ [] -> 0
+ os -> maximum os
-- | Returns the minimal width of a 'Doc' when reflowed at breakable spaces.
minOffset :: Doc -> Int
diff --git a/src/Text/Pandoc/Process.hs b/src/Text/Pandoc/Process.hs
index 294a38a1b..1014f37dd 100644
--- a/src/Text/Pandoc/Process.hs
+++ b/src/Text/Pandoc/Process.hs
@@ -29,13 +29,13 @@ ByteString variant of 'readProcessWithExitCode'.
-}
module Text.Pandoc.Process (pipeProcess)
where
-import System.Process
-import System.Exit (ExitCode (..))
+import Control.Concurrent (forkIO, newEmptyMVar, putMVar, takeMVar)
import Control.Exception
-import System.IO (hClose, hFlush)
-import Control.Concurrent (putMVar, takeMVar, newEmptyMVar, forkIO)
import Control.Monad (unless)
import qualified Data.ByteString.Lazy as BL
+import System.Exit (ExitCode (..))
+import System.IO (hClose, hFlush)
+import System.Process
{- |
Version of 'System.Process.readProcessWithExitCode' that uses lazy bytestrings
diff --git a/src/Text/Pandoc/Readers/CommonMark.hs b/src/Text/Pandoc/Readers/CommonMark.hs
index b0bcbd580..e98ee066e 100644
--- a/src/Text/Pandoc/Readers/CommonMark.hs
+++ b/src/Text/Pandoc/Readers/CommonMark.hs
@@ -33,11 +33,11 @@ module Text.Pandoc.Readers.CommonMark (readCommonMark)
where
import CMark
-import Data.Text (unpack, pack)
import Data.List (groupBy)
+import Data.Text (pack, unpack)
+import Text.Pandoc.Class (PandocMonad)
import Text.Pandoc.Definition
import Text.Pandoc.Options
-import Text.Pandoc.Class (PandocMonad)
-- | Parse a CommonMark formatted string into a 'Pandoc' structure.
readCommonMark :: PandocMonad m => ReaderOptions -> String -> m Pandoc
@@ -86,8 +86,8 @@ addBlock (Node _ (LIST listAttrs) nodes) =
paraToPlain (Para xs) = Plain (xs)
paraToPlain x = x
delim = case listDelim listAttrs of
- PERIOD_DELIM -> Period
- PAREN_DELIM -> OneParen
+ PERIOD_DELIM -> Period
+ PAREN_DELIM -> OneParen
addBlock (Node _ ITEM _) = id -- handled in LIST
addBlock _ = id
@@ -105,8 +105,8 @@ addInline (Node _ (TEXT t) _) = (map toinl clumps ++)
samekind ' ' _ = False
samekind _ ' ' = False
samekind _ _ = True
- toinl (' ':_) = Space
- toinl xs = Str xs
+ toinl (' ':_) = Space
+ toinl xs = Str xs
addInline (Node _ LINEBREAK _) = (LineBreak :)
addInline (Node _ SOFTBREAK _) = (SoftBreak :)
addInline (Node _ (HTML_INLINE t) _) =
diff --git a/src/Text/Pandoc/Readers/Docx.hs b/src/Text/Pandoc/Readers/Docx.hs
index 8936a0403..108055b42 100644
--- a/src/Text/Pandoc/Readers/Docx.hs
+++ b/src/Text/Pandoc/Readers/Docx.hs
@@ -1,4 +1,6 @@
-{-# LANGUAGE PatternGuards, OverloadedStrings, CPP #-}
+{-# LANGUAGE CPP #-}
+{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE PatternGuards #-}
{-
Copyright (C) 2014-2016 Jesse Rosenthal <jrosenthal@jhu.edu>
@@ -74,32 +76,32 @@ module Text.Pandoc.Readers.Docx
) where
import Codec.Archive.Zip
-import Text.Pandoc.Definition
-import Text.Pandoc.Options
+import Control.Monad.Reader
+import Control.Monad.State
+import qualified Data.ByteString.Lazy as B
+import Data.Default (Default)
+import Data.List (delete, intersect)
+import qualified Data.Map as M
+import Data.Sequence (ViewL (..), viewl)
+import qualified Data.Sequence as Seq (null)
+import qualified Data.Set as Set
import Text.Pandoc.Builder
-import Text.Pandoc.Walk
-import Text.Pandoc.Readers.Docx.Parse
-import Text.Pandoc.Readers.Docx.Lists
+-- import Text.Pandoc.Definition
+import Text.Pandoc.MediaBag (MediaBag)
+import Text.Pandoc.Options
import Text.Pandoc.Readers.Docx.Combine
+import Text.Pandoc.Readers.Docx.Lists
+import Text.Pandoc.Readers.Docx.Parse
import Text.Pandoc.Shared
-import Text.Pandoc.MediaBag (MediaBag)
-import Data.List (delete, intersect)
+import Text.Pandoc.Walk
import Text.TeXMath (writeTeX)
-import Data.Default (Default)
-import qualified Data.ByteString.Lazy as B
-import qualified Data.Map as M
-import qualified Data.Set as Set
-import Control.Monad.Reader
-import Control.Monad.State
-import Data.Sequence (ViewL(..), viewl)
-import qualified Data.Sequence as Seq (null)
#if !(MIN_VERSION_base(4,8,0))
import Data.Traversable (traverse)
#endif
-import Text.Pandoc.Error
import Control.Monad.Except (throwError)
import Text.Pandoc.Class (PandocMonad)
import qualified Text.Pandoc.Class as P
+import Text.Pandoc.Error
import Text.Pandoc.Logging
readDocx :: PandocMonad m
@@ -123,9 +125,9 @@ readDocxWithWarnings :: PandocMonad m
readDocxWithWarnings = readDocx
data DState = DState { docxAnchorMap :: M.Map String String
- , docxMediaBag :: MediaBag
- , docxDropCap :: Inlines
- , docxWarnings :: [String]
+ , docxMediaBag :: MediaBag
+ , docxDropCap :: Inlines
+ , docxWarnings :: [String]
}
instance Default DState where
@@ -135,7 +137,7 @@ instance Default DState where
, docxWarnings = []
}
-data DEnv = DEnv { docxOptions :: ReaderOptions
+data DEnv = DEnv { docxOptions :: ReaderOptions
, docxInHeaderBlock :: Bool }
instance Default DEnv where
@@ -173,7 +175,7 @@ isEmptyPar (Paragraph _ parParts) =
all isEmptyParPart parParts
where
isEmptyParPart (PlainRun (Run _ runElems)) = all isEmptyElem runElems
- isEmptyParPart _ = False
+ isEmptyParPart _ = False
isEmptyElem (TextRun s) = trim s == ""
isEmptyElem _ = True
isEmptyPar _ = False
@@ -207,7 +209,7 @@ fixAuthors :: MetaValue -> MetaValue
fixAuthors (MetaBlocks blks) =
MetaList $ map g $ filter f blks
where f (Para _) = True
- f _ = False
+ f _ = False
g (Para ils) = MetaInlines ils
g _ = MetaInlines []
fixAuthors mv = mv
@@ -219,28 +221,28 @@ codeDivs :: [String]
codeDivs = ["SourceCode"]
runElemToInlines :: RunElem -> Inlines
-runElemToInlines (TextRun s) = text s
-runElemToInlines (LnBrk) = linebreak
-runElemToInlines (Tab) = space
-runElemToInlines (SoftHyphen) = text "\xad"
+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 (LnBrk) = ['\n']
-runElemToString (Tab) = ['\t']
-runElemToString (SoftHyphen) = ['\xad']
+runElemToString (TextRun s) = s
+runElemToString (LnBrk) = ['\n']
+runElemToString (Tab) = ['\t']
+runElemToString (SoftHyphen) = ['\xad']
runElemToString (NoBreakHyphen) = ['\x2011']
runToString :: Run -> String
runToString (Run _ runElems) = concatMap runElemToString runElems
-runToString _ = ""
+runToString _ = ""
parPartToString :: ParPart -> String
-parPartToString (PlainRun run) = runToString run
+parPartToString (PlainRun run) = runToString run
parPartToString (InternalHyperLink _ runs) = concatMap runToString runs
parPartToString (ExternalHyperLink _ runs) = concatMap runToString runs
-parPartToString _ = ""
+parPartToString _ = ""
blacklistedCharStyles :: [String]
blacklistedCharStyles = ["Hyperlink"]
@@ -332,9 +334,9 @@ blocksToInlinesWarn :: PandocMonad m => String -> Blocks -> DocxContext m Inline
blocksToInlinesWarn cmtId blks = do
let blkList = toList blks
notParaOrPlain :: Block -> Bool
- notParaOrPlain (Para _) = False
+ notParaOrPlain (Para _) = False
notParaOrPlain (Plain _) = False
- notParaOrPlain _ = True
+ notParaOrPlain _ = True
when (not $ null $ filter notParaOrPlain blkList) $
lift $ P.report $ DocxParserWarning $
"Docx comment " ++ cmtId ++ " will not retain formatting"
@@ -508,14 +510,14 @@ parStyleToTransform pPr
let pPr' = pPr { indentation = Nothing }
in
case (left - hang) > 0 of
- True -> blockQuote . (parStyleToTransform pPr')
+ True -> blockQuote . (parStyleToTransform pPr')
False -> parStyleToTransform pPr'
| null (pStyle pPr),
Just left <- indentation pPr >>= leftParIndent =
let pPr' = pPr { indentation = Nothing }
in
case left > 0 of
- True -> blockQuote . (parStyleToTransform pPr')
+ True -> blockQuote . (parStyleToTransform pPr')
False -> parStyleToTransform pPr'
parStyleToTransform _ = id
@@ -542,7 +544,7 @@ bodyPartToBlocks (Paragraph pPr parparts)
else do modify $ \s -> s { docxDropCap = mempty }
return $ case isNull ils' of
True -> mempty
- _ -> parStyleToTransform pPr $ para ils'
+ _ -> parStyleToTransform pPr $ para ils'
bodyPartToBlocks (ListItem pPr numId lvl (Just levelInfo) parparts) = do
let
kvs = case levelInfo of
@@ -573,12 +575,12 @@ bodyPartToBlocks (Tbl cap _ look (r:rs)) = do
| otherwise -> (Just r, rs)
False -> (Nothing, r:rs)
- cells <- mapM rowToBlocksList rows
+ cells <- mapM rowToBlocksList rows
let width = case cells of
r':_ -> length r'
-- shouldn't happen
- [] -> 0
+ [] -> 0
hdrCells <- case hdr of
Just r' -> rowToBlocksList r'
diff --git a/src/Text/Pandoc/Readers/Docx/Combine.hs b/src/Text/Pandoc/Readers/Docx/Combine.hs
index 39e0df825..f516d63d4 100644
--- a/src/Text/Pandoc/Readers/Docx/Combine.hs
+++ b/src/Text/Pandoc/Readers/Docx/Combine.hs
@@ -1,15 +1,16 @@
-{-# LANGUAGE TypeSynonymInstances, FlexibleInstances,
- PatternGuards #-}
+{-# LANGUAGE FlexibleInstances #-}
+{-# LANGUAGE PatternGuards #-}
+{-# LANGUAGE TypeSynonymInstances #-}
module Text.Pandoc.Readers.Docx.Combine ( smushInlines
, smushBlocks
)
where
-import Text.Pandoc.Builder
import Data.List
-import Data.Sequence (ViewR(..), ViewL(..), viewl, viewr, (><), (|>))
+import Data.Sequence (ViewL (..), ViewR (..), viewl, viewr, (><), (|>))
import qualified Data.Sequence as Seq (null)
+import Text.Pandoc.Builder
data Modifier a = Modifier (a -> a)
| AttrModifier (Attr -> a -> a) Attr
@@ -56,15 +57,15 @@ unstackInlines ms = case ilModifier ms of
ilModifier :: Inlines -> Modifier Inlines
ilModifier ils = case viewl (unMany ils) of
(x :< xs) | Seq.null xs -> case x of
- (Emph _) -> Modifier emph
- (Strong _) -> Modifier strong
- (SmallCaps _) -> Modifier smallcaps
- (Strikeout _) -> Modifier strikeout
- (Superscript _) -> Modifier superscript
- (Subscript _) -> Modifier subscript
+ (Emph _) -> Modifier emph
+ (Strong _) -> Modifier strong
+ (SmallCaps _) -> Modifier smallcaps
+ (Strikeout _) -> Modifier strikeout
+ (Superscript _) -> Modifier superscript
+ (Subscript _) -> Modifier subscript
(Link attr _ tgt) -> Modifier $ linkWith attr (fst tgt) (snd tgt)
- (Span attr _) -> AttrModifier spanWith attr
- _ -> NullModifier
+ (Span attr _) -> AttrModifier spanWith attr
+ _ -> NullModifier
_ -> NullModifier
ilInnards :: Inlines -> Inlines
@@ -78,18 +79,18 @@ ilInnards ils = case viewl (unMany ils) of
(Subscript lst) -> fromList lst
(Link _ lst _) -> fromList lst
(Span _ lst) -> fromList lst
- _ -> ils
+ _ -> ils
_ -> ils
inlinesL :: Inlines -> (Inlines, Inlines)
inlinesL ils = case viewl $ unMany ils of
(s :< sq) -> (singleton s, Many sq)
- _ -> (mempty, ils)
+ _ -> (mempty, ils)
inlinesR :: Inlines -> (Inlines, Inlines)
inlinesR ils = case viewr $ unMany ils of
(sq :> s) -> (Many sq, singleton s)
- _ -> (ils, mempty)
+ _ -> (ils, mempty)
combineInlines :: Inlines -> Inlines -> Inlines
combineInlines x y =
diff --git a/src/Text/Pandoc/Readers/Docx/Lists.hs b/src/Text/Pandoc/Readers/Docx/Lists.hs
index 395a53907..94b4d919a 100644
--- a/src/Text/Pandoc/Readers/Docx/Lists.hs
+++ b/src/Text/Pandoc/Readers/Docx/Lists.hs
@@ -33,38 +33,38 @@ module Text.Pandoc.Readers.Docx.Lists ( blocksToBullets
, listParagraphDivs
) where
-import Text.Pandoc.JSON
-import Text.Pandoc.Generic (bottomUp)
-import Text.Pandoc.Shared (trim)
import Control.Monad
import Data.List
import Data.Maybe
+import Text.Pandoc.Generic (bottomUp)
+import Text.Pandoc.JSON
+import Text.Pandoc.Shared (trim)
isListItem :: Block -> Bool
isListItem (Div (_, classes, _) _) | "list-item" `elem` classes = True
-isListItem _ = False
+isListItem _ = False
getLevel :: Block -> Maybe Integer
getLevel (Div (_, _, kvs) _) = liftM read $ lookup "level" kvs
-getLevel _ = Nothing
+getLevel _ = Nothing
getLevelN :: Block -> Integer
getLevelN b = case getLevel b of
- Just n -> n
+ Just n -> n
Nothing -> -1
getNumId :: Block -> Maybe Integer
getNumId (Div (_, _, kvs) _) = liftM read $ lookup "num-id" kvs
-getNumId _ = Nothing
+getNumId _ = Nothing
getNumIdN :: Block -> Integer
getNumIdN b = case getNumId b of
- Just n -> n
+ Just n -> n
Nothing -> -1
getText :: Block -> Maybe String
getText (Div (_, _, kvs) _) = lookup "text" kvs
-getText _ = Nothing
+getText _ = Nothing
data ListType = Itemized | Enumerated ListAttributes
@@ -162,7 +162,7 @@ flatToBullets elems = flatToBullets' (-1) elems
singleItemHeaderToHeader :: Block -> Block
singleItemHeaderToHeader (OrderedList _ [[h@(Header _ _ _)]]) = h
-singleItemHeaderToHeader blk = blk
+singleItemHeaderToHeader blk = blk
blocksToBullets :: [Block] -> [Block]
@@ -173,8 +173,8 @@ blocksToBullets blks =
plainParaInlines :: Block -> [Inline]
plainParaInlines (Plain ils) = ils
-plainParaInlines (Para ils) = ils
-plainParaInlines _ = []
+plainParaInlines (Para ils) = ils
+plainParaInlines _ = []
blocksToDefinitions' :: [([Inline], [[Block]])] -> [Block] -> [Block] -> [Block]
blocksToDefinitions' [] acc [] = reverse acc
@@ -194,7 +194,7 @@ blocksToDefinitions' defAcc acc
| (not . null) defAcc && "Definition" `elem` classes2 =
let remainingAttr2 = (ident2, delete "Definition" classes2, kvs2)
defItems2 = case remainingAttr2 == ("", [], []) of
- True -> blks2
+ True -> blks2
False -> [Div remainingAttr2 blks2]
((defTerm, defItems):defs) = defAcc
defAcc' = case null defItems of
@@ -211,12 +211,12 @@ removeListDivs' :: Block -> [Block]
removeListDivs' (Div (ident, classes, kvs) blks)
| "list-item" `elem` classes =
case delete "list-item" classes of
- [] -> blks
+ [] -> blks
classes' -> [Div (ident, classes', kvs) $ blks]
removeListDivs' (Div (ident, classes, kvs) blks)
| not $ null $ listParagraphDivs `intersect` classes =
case classes \\ listParagraphDivs of
- [] -> blks
+ [] -> blks
classes' -> [Div (ident, classes', kvs) blks]
removeListDivs' blk = [blk]
diff --git a/src/Text/Pandoc/Readers/Docx/Parse.hs b/src/Text/Pandoc/Readers/Docx/Parse.hs
index 221a1d10a..0f23555f4 100644
--- a/src/Text/Pandoc/Readers/Docx/Parse.hs
+++ b/src/Text/Pandoc/Readers/Docx/Parse.hs
@@ -1,4 +1,6 @@
-{-# LANGUAGE PatternGuards, ViewPatterns, FlexibleInstances #-}
+{-# LANGUAGE FlexibleInstances #-}
+{-# LANGUAGE PatternGuards #-}
+{-# LANGUAGE ViewPatterns #-}
{-
Copyright (C) 2014-2016 Jesse Rosenthal <jrosenthal@jhu.edu>
@@ -53,24 +55,24 @@ module Text.Pandoc.Readers.Docx.Parse ( Docx(..)
, archiveToDocxWithWarnings
) where
import Codec.Archive.Zip
-import Text.XML.Light
-import Data.Maybe
-import Data.List
-import System.FilePath
-import Data.Bits ((.|.))
-import qualified Data.ByteString.Lazy as B
-import qualified Text.Pandoc.UTF8 as UTF8
+import Control.Applicative ((<|>))
+import Control.Monad.Except
import Control.Monad.Reader
import Control.Monad.State
-import Control.Applicative ((<|>))
+import Data.Bits ((.|.))
+import qualified Data.ByteString.Lazy as B
+import Data.Char (chr, isDigit, ord, readLitChar)
+import Data.List
import qualified Data.Map as M
-import Control.Monad.Except
-import Text.Pandoc.Shared (safeRead, filteredFilesFromArchive)
-import Text.TeXMath.Readers.OMML (readOMML)
-import Text.TeXMath.Unicode.Fonts (getUnicode, stringToFont, Font(..))
-import Text.TeXMath (Exp)
+import Data.Maybe
+import System.FilePath
import Text.Pandoc.Readers.Docx.Util
-import Data.Char (readLitChar, ord, chr, isDigit)
+import Text.Pandoc.Shared (filteredFilesFromArchive, safeRead)
+import qualified Text.Pandoc.UTF8 as UTF8
+import Text.TeXMath (Exp)
+import Text.TeXMath.Readers.OMML (readOMML)
+import Text.TeXMath.Unicode.Fonts (Font (..), getUnicode, stringToFont)
+import Text.XML.Light
data ReaderEnv = ReaderEnv { envNotes :: Notes
, envComments :: Comments
@@ -97,7 +99,7 @@ runD dx re rs = runState (runReaderT (runExceptT dx) re) rs
maybeToD :: Maybe a -> D a
maybeToD (Just a) = return a
-maybeToD Nothing = throwError DocxError
+maybeToD Nothing = throwError DocxError
eitherToD :: Either a b -> D b
eitherToD (Right b) = return b
@@ -160,12 +162,12 @@ data Notes = Notes NameSpaces
data Comments = Comments NameSpaces (M.Map String Element)
deriving Show
-data ParIndentation = ParIndentation { leftParIndent :: Maybe Integer
- , rightParIndent :: Maybe Integer
+data ParIndentation = ParIndentation { leftParIndent :: Maybe Integer
+ , rightParIndent :: Maybe Integer
, hangingParIndent :: Maybe Integer}
deriving Show
-data ParagraphStyle = ParagraphStyle { pStyle :: [String]
+data ParagraphStyle = ParagraphStyle { pStyle :: [String]
, indentation :: Maybe ParIndentation
, dropCap :: Bool
, pHeading :: Maybe (String, Int)
@@ -234,19 +236,19 @@ data RunElem = TextRun String | LnBrk | Tab | SoftHyphen | NoBreakHyphen
data VertAlign = BaseLn | SupScrpt | SubScrpt
deriving Show
-data RunStyle = RunStyle { isBold :: Maybe Bool
- , isItalic :: Maybe Bool
+data RunStyle = RunStyle { isBold :: Maybe Bool
+ , isItalic :: Maybe Bool
, isSmallCaps :: Maybe Bool
- , isStrike :: Maybe Bool
- , rVertAlign :: Maybe VertAlign
- , rUnderline :: Maybe String
- , rStyle :: Maybe CharStyle}
+ , isStrike :: Maybe Bool
+ , rVertAlign :: Maybe VertAlign
+ , rUnderline :: Maybe String
+ , rStyle :: Maybe CharStyle}
deriving Show
-data ParStyleData = ParStyleData { headingLev :: Maybe (String, Int)
+data ParStyleData = ParStyleData { headingLev :: Maybe (String, Int)
, isBlockQuote :: Maybe Bool
- , numInfo :: Maybe (String, String)
- , psStyle :: Maybe ParStyle}
+ , numInfo :: Maybe (String, String)
+ , psStyle :: Maybe ParStyle}
deriving Show
defaultRunStyle :: RunStyle
@@ -381,10 +383,10 @@ archiveToNotes zf =
enElem = findEntryByPath "word/endnotes.xml" zf
>>= (parseXMLDoc . UTF8.toStringLazy . fromEntry)
fn_namespaces = case fnElem of
- Just e -> elemToNameSpaces e
+ Just e -> elemToNameSpaces e
Nothing -> []
en_namespaces = case enElem of
- Just e -> elemToNameSpaces e
+ Just e -> elemToNameSpaces e
Nothing -> []
ns = unionBy (\x y -> fst x == fst y) fn_namespaces en_namespaces
fn = fnElem >>= (elemToNotes ns "footnote")
@@ -397,19 +399,19 @@ archiveToComments zf =
let cmtsElem = findEntryByPath "word/comments.xml" zf
>>= (parseXMLDoc . UTF8.toStringLazy . fromEntry)
cmts_namespaces = case cmtsElem of
- Just e -> elemToNameSpaces e
+ Just e -> elemToNameSpaces e
Nothing -> []
cmts = (elemToComments cmts_namespaces) <$> cmtsElem
in
case cmts of
- Just c -> Comments cmts_namespaces c
+ Just c -> Comments cmts_namespaces c
Nothing -> Comments cmts_namespaces M.empty
filePathToRelType :: FilePath -> Maybe DocumentLocation
-filePathToRelType "word/_rels/document.xml.rels" = Just InDocument
+filePathToRelType "word/_rels/document.xml.rels" = Just InDocument
filePathToRelType "word/_rels/footnotes.xml.rels" = Just InFootnote
-filePathToRelType "word/_rels/endnotes.xml.rels" = Just InEndnote
-filePathToRelType _ = Nothing
+filePathToRelType "word/_rels/endnotes.xml.rels" = Just InEndnote
+filePathToRelType _ = Nothing
relElemToRelationship :: DocumentLocation -> Element -> Maybe Relationship
relElemToRelationship relType element | qName (elName element) == "Relationship" =
@@ -616,12 +618,12 @@ elemToBodyPart ns element
>>= findAttrByName ns "w" "val"
caption = (fromMaybe "" caption')
grid' = case findChildByName ns "w" "tblGrid" element of
- Just g -> elemToTblGrid ns g
+ Just g -> elemToTblGrid ns g
Nothing -> return []
tblLook' = case findChildByName ns "w" "tblPr" element >>=
findChildByName ns "w" "tblLook"
of
- Just l -> elemToTblLook ns l
+ Just l -> elemToTblLook ns l
Nothing -> return defaultTblLook
grid <- grid'
@@ -741,7 +743,7 @@ elemToParPart ns element
(Comments _ commentMap) <- asks envComments
case M.lookup cmtId commentMap of
Just cmtElem -> elemToCommentStart ns cmtElem
- Nothing -> throwError WrongElem
+ Nothing -> throwError WrongElem
elemToParPart ns element
| isElem ns "w" "commentRangeEnd" element
, Just cmtId <- findAttrByName ns "w" "id" element =
@@ -771,7 +773,7 @@ elemToExtent :: Element -> Extent
elemToExtent drawingElem =
case (getDim "cx", getDim "cy") of
(Just w, Just h) -> Just (w, h)
- _ -> Nothing
+ _ -> Nothing
where
wp_ns = "http://schemas.openxmlformats.org/drawingml/2006/wordprocessingDrawing"
getDim at = findElement (QName "extent" (Just wp_ns) (Just "wp")) drawingElem
@@ -1023,7 +1025,7 @@ getSymChar ns element
getCodepoint = findAttrByName ns "w" "char" element
getFont = stringToFont =<< findAttrByName ns "w" "font" element
lowerFromPrivate ('F':xs) = '0':xs
- lowerFromPrivate xs = xs
+ lowerFromPrivate xs = xs
getSymChar _ _ = TextRun ""
elemToRunElems :: NameSpaces -> Element -> D [RunElem]
diff --git a/src/Text/Pandoc/Readers/Docx/StyleMap.hs b/src/Text/Pandoc/Readers/Docx/StyleMap.hs
index 00906cf07..38f976fd8 100644
--- a/src/Text/Pandoc/Readers/Docx/StyleMap.hs
+++ b/src/Text/Pandoc/Readers/Docx/StyleMap.hs
@@ -7,11 +7,11 @@ module Text.Pandoc.Readers.Docx.StyleMap ( StyleMaps(..)
, hasStyleName
) where
-import Text.XML.Light
-import Text.Pandoc.Readers.Docx.Util
-import Control.Monad.State
-import Data.Char (toLower)
-import qualified Data.Map as M
+import Control.Monad.State
+import Data.Char (toLower)
+import qualified Data.Map as M
+import Text.Pandoc.Readers.Docx.Util
+import Text.XML.Light
newtype ParaStyleMap = ParaStyleMap ( M.Map String String )
newtype CharStyleMap = CharStyleMap ( M.Map String String )
@@ -30,7 +30,7 @@ instance StyleMap CharStyleMap where
insert :: (StyleMap a) => Maybe String -> Maybe String -> a -> a
insert (Just k) (Just v) m = alterMap (M.insert k v) m
-insert _ _ m = m
+insert _ _ m = m
getStyleId :: (StyleMap a) => String -> a -> String
getStyleId s = M.findWithDefault (filter (/=' ') s) (map toLower s) . getMap
diff --git a/src/Text/Pandoc/Readers/Docx/Util.hs b/src/Text/Pandoc/Readers/Docx/Util.hs
index 6646e5b7f..8415dbf68 100644
--- a/src/Text/Pandoc/Readers/Docx/Util.hs
+++ b/src/Text/Pandoc/Readers/Docx/Util.hs
@@ -8,8 +8,8 @@ module Text.Pandoc.Readers.Docx.Util (
, findAttrByName
) where
-import Text.XML.Light
import Data.Maybe (mapMaybe)
+import Text.XML.Light
type NameSpaces = [(String, String)]
@@ -18,7 +18,7 @@ elemToNameSpaces = mapMaybe attrToNSPair . elAttribs
attrToNSPair :: Attr -> Maybe (String, String)
attrToNSPair (Attr (QName s _ (Just "xmlns")) val) = Just (s, val)
-attrToNSPair _ = Nothing
+attrToNSPair _ = Nothing
elemName :: NameSpaces -> String -> String -> QName
elemName ns prefix name =
diff --git a/src/Text/Pandoc/Readers/EPUB.hs b/src/Text/Pandoc/Readers/EPUB.hs
index 69edb9761..db58e9654 100644
--- a/src/Text/Pandoc/Readers/EPUB.hs
+++ b/src/Text/Pandoc/Readers/EPUB.hs
@@ -1,39 +1,37 @@
-{-# LANGUAGE
- ViewPatterns
- , StandaloneDeriving
- , TupleSections
- , FlexibleContexts #-}
+{-# LANGUAGE FlexibleContexts #-}
+{-# LANGUAGE StandaloneDeriving #-}
+{-# LANGUAGE TupleSections #-}
+{-# LANGUAGE ViewPatterns #-}
module Text.Pandoc.Readers.EPUB
(readEPUB)
where
-import Text.XML.Light
-import Text.Pandoc.Definition hiding (Attr)
-import Text.Pandoc.Readers.HTML (readHtml)
-import Text.Pandoc.Walk (walk, query)
-import Text.Pandoc.Options ( ReaderOptions(..))
-import Text.Pandoc.Extensions (enableExtension, Extension(Ext_raw_html))
-import Text.Pandoc.Shared (escapeURI, collapseFilePath, addMetaField)
-import Network.URI (unEscapeString)
+import Codec.Archive.Zip (Archive (..), Entry, findEntryByPath, fromEntry,
+ toArchiveOrFail)
+import Control.DeepSeq (NFData, deepseq)
+import Control.Monad (guard, liftM)
import Control.Monad.Except (throwError)
-import Text.Pandoc.MIME (MimeType)
-import qualified Text.Pandoc.Builder as B
-import Codec.Archive.Zip ( Archive (..), toArchiveOrFail, fromEntry
- , findEntryByPath, Entry)
import qualified Data.ByteString.Lazy as BL (ByteString)
-import System.FilePath ( takeFileName, (</>), dropFileName, normalise
- , dropFileName
- , splitFileName )
-import qualified Text.Pandoc.UTF8 as UTF8 (toStringLazy)
-import Control.Monad (guard, liftM)
-import Data.List (isPrefixOf, isInfixOf)
-import Data.Maybe (mapMaybe, fromMaybe)
-import qualified Data.Map as M (Map, lookup, fromList, elems)
+import Data.List (isInfixOf, isPrefixOf)
+import qualified Data.Map as M (Map, elems, fromList, lookup)
+import Data.Maybe (fromMaybe, mapMaybe)
import Data.Monoid ((<>))
-import Control.DeepSeq (deepseq, NFData)
-import Text.Pandoc.Error
+import Network.URI (unEscapeString)
+import System.FilePath (dropFileName, dropFileName, normalise, splitFileName,
+ takeFileName, (</>))
+import qualified Text.Pandoc.Builder as B
import Text.Pandoc.Class (PandocMonad, insertMedia)
+import Text.Pandoc.Definition hiding (Attr)
+import Text.Pandoc.Error
+import Text.Pandoc.Extensions (Extension (Ext_raw_html), enableExtension)
+import Text.Pandoc.MIME (MimeType)
+import Text.Pandoc.Options (ReaderOptions (..))
+import Text.Pandoc.Readers.HTML (readHtml)
+import Text.Pandoc.Shared (addMetaField, collapseFilePath, escapeURI)
+import qualified Text.Pandoc.UTF8 as UTF8 (toStringLazy)
+import Text.Pandoc.Walk (query, walk)
+import Text.XML.Light
type Items = M.Map String (FilePath, MimeType)
@@ -99,7 +97,7 @@ fetchImages mimes root arc (query iq -> links) =
iq :: Inline -> [FilePath]
iq (Image _ _ (url, _)) = [url]
-iq _ = []
+iq _ = []
-- Remove relative paths
renameImages :: FilePath -> Inline -> Inline
@@ -159,7 +157,7 @@ parseMetaItem e@(stripNamespace . elName -> field) meta =
renameMeta :: String -> String
renameMeta "creator" = "author"
-renameMeta s = s
+renameMeta s = s
getManifest :: PandocMonad m => Archive -> m (String, Element)
getManifest archive = do
@@ -216,7 +214,7 @@ fixAttrs :: FilePath -> B.Attr -> B.Attr
fixAttrs s (ident, cs, kvs) = (addHash s ident, filter (not . null) cs, removeEPUBAttrs kvs)
addHash :: String -> String -> String
-addHash _ "" = ""
+addHash _ "" = ""
addHash s ident = takeFileName s ++ "#" ++ ident
removeEPUBAttrs :: [(String, String)] -> [(String, String)]
@@ -244,7 +242,7 @@ stripNamespace (QName v _ _) = v
attrToNSPair :: Attr -> Maybe (String, String)
attrToNSPair (Attr (QName "xmlns" _ _) val) = Just ("xmlns", val)
-attrToNSPair _ = Nothing
+attrToNSPair _ = Nothing
attrToPair :: Attr -> (String, String)
attrToPair (Attr (QName name _ _) val) = (name, val)
diff --git a/src/Text/Pandoc/Readers/Haddock.hs b/src/Text/Pandoc/Readers/Haddock.hs
index 310a04574..28caa528e 100644
--- a/src/Text/Pandoc/Readers/Haddock.hs
+++ b/src/Text/Pandoc/Readers/Haddock.hs
@@ -14,19 +14,19 @@ module Text.Pandoc.Readers.Haddock
( readHaddock
) where
-import Text.Pandoc.Builder (Blocks, Inlines)
-import qualified Text.Pandoc.Builder as B
-import Data.Monoid ((<>))
-import Text.Pandoc.Shared (trim, splitBy)
+import Control.Monad.Except (throwError)
import Data.List (intersperse, stripPrefix)
import Data.Maybe (fromMaybe)
-import Text.Pandoc.Definition
-import Text.Pandoc.Options
+import Data.Monoid ((<>))
import Documentation.Haddock.Parser
import Documentation.Haddock.Types
-import Text.Pandoc.Error
-import Control.Monad.Except (throwError)
+import Text.Pandoc.Builder (Blocks, Inlines)
+import qualified Text.Pandoc.Builder as B
import Text.Pandoc.Class (PandocMonad)
+import Text.Pandoc.Definition
+import Text.Pandoc.Error
+import Text.Pandoc.Options
+import Text.Pandoc.Shared (splitBy, trim)
-- | Parse Haddock markup and return a 'Pandoc' document.
@@ -96,7 +96,7 @@ docHToBlocks d' =
isPlain (Plain _) = True
isPlain _ = False
extractContents (Plain xs) = xs
- extractContents _ = []
+ extractContents _ = []
docHToInlines :: Bool -> DocH String Identifier -> Inlines
docHToInlines isCode d' =
diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs
index e7683fd1c..0f17d3db4 100644
--- a/src/Text/Pandoc/Readers/LaTeX.hs
+++ b/src/Text/Pandoc/Readers/LaTeX.hs
@@ -1,4 +1,5 @@
-{-# LANGUAGE ScopedTypeVariables, OverloadedStrings #-}
+{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE ScopedTypeVariables #-}
{-
Copyright (C) 2006-2015 John MacFarlane <jgm@berkeley.edu>
@@ -34,26 +35,25 @@ module Text.Pandoc.Readers.LaTeX ( readLaTeX,
inlineCommand,
) where
-import Text.Pandoc.Definition
-import Text.Pandoc.Walk
-import Text.Pandoc.Shared
-import Text.Pandoc.Options
-import Text.Pandoc.Logging
-import Text.Pandoc.Parsing hiding ((<|>), many, optional, space,
- mathDisplay, mathInline)
-import Data.Char ( chr, ord, isLetter, isAlphaNum )
+import Control.Applicative (many, optional, (<|>))
import Control.Monad
-import Text.Pandoc.Builder
-import Control.Applicative ((<|>), many, optional)
-import Data.Maybe (fromMaybe, maybeToList)
-import System.FilePath (replaceExtension, takeExtension, addExtension)
+import Control.Monad.Except (throwError)
+import Data.Char (chr, isAlphaNum, isLetter, ord)
import Data.List (intercalate)
import qualified Data.Map as M
+import Data.Maybe (fromMaybe, maybeToList)
+import System.FilePath (addExtension, replaceExtension, takeExtension)
+import Text.Pandoc.Builder
+import Text.Pandoc.Class (PandocMonad, PandocPure, lookupEnv, readFileFromDirs,
+ report, setResourcePath)
import Text.Pandoc.Highlighting (fromListingsLanguage, languagesByExtension)
import Text.Pandoc.ImageSize (numUnit, showFl)
-import Control.Monad.Except (throwError)
-import Text.Pandoc.Class (PandocMonad, PandocPure, lookupEnv, report,
- readFileFromDirs, setResourcePath)
+import Text.Pandoc.Logging
+import Text.Pandoc.Options
+import Text.Pandoc.Parsing hiding (many, mathDisplay, mathInline, optional,
+ space, (<|>))
+import Text.Pandoc.Shared
+import Text.Pandoc.Walk
-- | Parse LaTeX from string and return 'Pandoc' document.
readLaTeX :: PandocMonad m
@@ -64,7 +64,7 @@ readLaTeX opts ltx = do
parsed <- readWithM parseLaTeX def{ stateOptions = opts } ltx
case parsed of
Right result -> return result
- Left e -> throwError e
+ Left e -> throwError e
parseLaTeX :: PandocMonad m => LP m Pandoc
parseLaTeX = do
@@ -90,9 +90,9 @@ controlSeq :: PandocMonad m => String -> LP m String
controlSeq name = try $ do
char '\\'
case name of
- "" -> mzero
+ "" -> mzero
[c] | not (isLetter c) -> string [c]
- cs -> string cs <* notFollowedBy letter <* optional sp
+ cs -> string cs <* notFollowedBy letter <* optional sp
return name
dimenarg :: PandocMonad m => LP m String
@@ -176,11 +176,11 @@ mathChars =
where escapedChar = try $ do char '\\'
c <- anyChar
return ['\\',c]
- isOrdChar '$' = False
- isOrdChar '{' = False
- isOrdChar '}' = False
+ isOrdChar '$' = False
+ isOrdChar '{' = False
+ isOrdChar '}' = False
isOrdChar '\\' = False
- isOrdChar _ = True
+ isOrdChar _ = True
quoted' :: PandocMonad m => (Inlines -> Inlines) -> LP m String -> LP m () -> LP m Inlines
quoted' f starter ender = do
@@ -192,9 +192,9 @@ quoted' f starter ender = do
(ender >> return (f (mconcat ils))) <|>
(<> mconcat ils) <$>
lit (case startchs of
- "``" -> "“"
- "`" -> "‘"
- _ -> startchs)
+ "``" -> "“"
+ "`" -> "‘"
+ _ -> startchs)
else lit startchs
doubleQuote :: PandocMonad m => LP m Inlines
@@ -1155,7 +1155,7 @@ closing = do
st <- getState
let extractInlines (MetaBlocks [Plain ys]) = ys
extractInlines (MetaBlocks [Para ys ]) = ys
- extractInlines _ = []
+ extractInlines _ = []
let sigs = case lookupMeta "author" (stateMeta st) of
Just (MetaList xs) ->
para $ trimInlines $ fromList $
@@ -1263,8 +1263,8 @@ preamble = mempty <$> manyTill preambleBlock beginDoc
-- citations
addPrefix :: [Inline] -> [Citation] -> [Citation]
-addPrefix p (k:ks) = k {citationPrefix = p ++ citationPrefix k} : ks
-addPrefix _ _ = []
+addPrefix p (k:ks) = k {citationPrefix = p ++ citationPrefix k} : ks
+addPrefix _ _ = []
addSuffix :: [Inline] -> [Citation] -> [Citation]
addSuffix s ks@(_:_) =
diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs
index 6c7f8362f..6fb1cc40c 100644
--- a/src/Text/Pandoc/Readers/Markdown.hs
+++ b/src/Text/Pandoc/Readers/Markdown.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE RelaxedPolyRec #-} -- needed for inlinesBetween on GHC < 7
+{-# LANGUAGE RelaxedPolyRec #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-
@@ -32,40 +32,40 @@ Conversion of markdown-formatted plain text to 'Pandoc' document.
-}
module Text.Pandoc.Readers.Markdown ( readMarkdown ) where
-import Data.List ( transpose, sortBy, findIndex, intercalate )
+import Control.Monad
+import Control.Monad.Except (catchError, throwError)
+import Control.Monad.Trans (lift)
+import Data.Char (isAlphaNum, isPunctuation, isSpace, toLower)
+import qualified Data.HashMap.Strict as H
+import Data.List (findIndex, intercalate, sortBy, transpose)
import qualified Data.Map as M
-import Data.Scientific (coefficient, base10Exponent)
-import Data.Ord ( comparing )
-import Data.Char ( isSpace, isAlphaNum, toLower, isPunctuation )
import Data.Maybe
-import Text.Pandoc.Definition
-import Text.Pandoc.Emoji (emojis)
-import Text.Pandoc.Generic (bottomUp)
-import qualified Data.Text as T
+import Data.Monoid ((<>))
+import Data.Ord (comparing)
+import Data.Scientific (base10Exponent, coefficient)
import Data.Text (Text)
+import qualified Data.Text as T
+import qualified Data.Vector as V
+import Data.Yaml (ParseException (..), YamlException (..), YamlMark (..))
import qualified Data.Yaml as Yaml
-import Data.Yaml (ParseException(..), YamlException(..), YamlMark(..))
-import qualified Data.HashMap.Strict as H
+import System.FilePath (addExtension, takeExtension)
+import Text.HTML.TagSoup
+import Text.Pandoc.Builder (Blocks, Inlines, trimInlines)
import qualified Text.Pandoc.Builder as B
-import qualified Text.Pandoc.UTF8 as UTF8
-import qualified Data.Vector as V
-import Text.Pandoc.Builder (Inlines, Blocks, trimInlines)
-import Text.Pandoc.Options
+import Text.Pandoc.Class (PandocMonad, report)
+import Text.Pandoc.Definition
+import Text.Pandoc.Emoji (emojis)
+import Text.Pandoc.Generic (bottomUp)
import Text.Pandoc.Logging
-import Text.Pandoc.Shared
+import Text.Pandoc.Options
+import Text.Pandoc.Parsing hiding (tableWith)
import Text.Pandoc.Pretty (charWidth)
+import Text.Pandoc.Readers.HTML (htmlInBalanced, htmlTag, isBlockTag,
+ isCommentTag, isInlineTag, isTextTag)
+import Text.Pandoc.Readers.LaTeX (rawLaTeXBlock, rawLaTeXInline)
+import Text.Pandoc.Shared
+import qualified Text.Pandoc.UTF8 as UTF8
import Text.Pandoc.XML (fromEntities)
-import Text.Pandoc.Parsing hiding (tableWith)
-import Text.Pandoc.Readers.LaTeX ( rawLaTeXInline, rawLaTeXBlock )
-import Text.Pandoc.Readers.HTML ( htmlTag, htmlInBalanced, isInlineTag, isBlockTag,
- isTextTag, isCommentTag )
-import Control.Monad
-import System.FilePath (takeExtension, addExtension)
-import Text.HTML.TagSoup
-import Data.Monoid ((<>))
-import Control.Monad.Trans (lift)
-import Control.Monad.Except (throwError, catchError)
-import Text.Pandoc.Class (PandocMonad, report)
type MarkdownParser m = ParserT [Char] ParserState m
@@ -78,7 +78,7 @@ readMarkdown opts s = do
parsed <- (readWithM parseMarkdown) def{ stateOptions = opts } (s ++ "\n\n")
case parsed of
Right result -> return result
- Left e -> throwError e
+ Left e -> throwError e
trimInlinesF :: F Inlines -> F Inlines
trimInlinesF = liftM trimInlines
@@ -235,11 +235,11 @@ pandocTitleBlock = try $ do
$ nullMeta
updateState $ \st -> st{ stateMeta' = stateMeta' st <> meta' }
-
+
-- Adapted from solution at
-- http://stackoverflow.com/a/29448764/1901888
foldrWithKeyM :: Monad m => (k -> b -> a -> m a) -> a -> H.HashMap k b -> m a
-foldrWithKeyM f acc = H.foldrWithKey f' (return acc)
+foldrWithKeyM f acc = H.foldrWithKey f' (return acc)
where
f' k b ma = ma >>= \a -> f k b a
@@ -688,9 +688,9 @@ codeBlockFenced = try $ do
-- correctly handle github language identifiers
toLanguageId :: String -> String
toLanguageId = map toLower . go
- where go "c++" = "cpp"
+ where go "c++" = "cpp"
go "objective-c" = "objectivec"
- go x = x
+ go x = x
codeBlockIndented :: PandocMonad m => MarkdownParser m (F Blocks)
codeBlockIndented = do
@@ -1167,13 +1167,13 @@ alignType strLst len =
let nonempties = filter (not . null) $ map trimr strLst
(leftSpace, rightSpace) =
case sortBy (comparing length) nonempties of
- (x:_) -> (head x `elem` " \t", length x < len)
- [] -> (False, False)
+ (x:_) -> (head x `elem` " \t", length x < len)
+ [] -> (False, False)
in case (leftSpace, rightSpace) of
- (True, False) -> AlignRight
- (False, True) -> AlignLeft
- (True, True) -> AlignCenter
- (False, False) -> AlignDefault
+ (True, False) -> AlignRight
+ (False, True) -> AlignLeft
+ (True, True) -> AlignCenter
+ (False, False) -> AlignDefault
-- Parse a table footer - dashed lines followed by blank line.
tableFooter :: PandocMonad m => MarkdownParser m String
@@ -1352,7 +1352,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.
@@ -1475,8 +1475,8 @@ table = try $ do
(gridTable False <|> gridTable True)) <?> "table"
optional blanklines
caption <- case frontCaption of
- Nothing -> option (return mempty) tableCaption
- Just c -> return c
+ Nothing -> option (return mempty) tableCaption
+ Just c -> return c
-- renormalize widths if greater than 100%:
let totalWidth = sum widths
let widths' = if totalWidth < 1
@@ -1555,8 +1555,8 @@ exampleRef = try $ do
return $ do
st <- askF
return $ case M.lookup lab (stateExamples st) of
- Just n -> B.str (show n)
- Nothing -> B.str ('@':lab)
+ Just n -> B.str (show n)
+ Nothing -> B.str ('@':lab)
symbol :: PandocMonad m => MarkdownParser m (F Inlines)
symbol = do
@@ -1600,10 +1600,10 @@ enclosure c = do
(return (B.str cs) <>) <$> whitespace
<|> do
case length cs of
- 3 -> three c
- 2 -> two c mempty
- 1 -> one c mempty
- _ -> return (return $ B.str cs)
+ 3 -> three c
+ 2 -> two c mempty
+ 1 -> one c mempty
+ _ -> return (return $ B.str cs)
ender :: PandocMonad m => Char -> Int -> MarkdownParser m ()
ender c n = try $ do
@@ -1839,9 +1839,9 @@ referenceLink constructor (lab, raw) = do
dropBrackets :: String -> String
dropBrackets = reverse . dropRB . reverse . dropLB
where dropRB (']':xs) = xs
- dropRB xs = xs
+ dropRB xs = xs
dropLB ('[':xs) = xs
- dropLB xs = xs
+ dropLB xs = xs
bareURL :: PandocMonad m => MarkdownParser m (F Inlines)
bareURL = try $ do
diff --git a/src/Text/Pandoc/Readers/MediaWiki.hs b/src/Text/Pandoc/Readers/MediaWiki.hs
index 1bd7fc77b..fa20ade07 100644
--- a/src/Text/Pandoc/Readers/MediaWiki.hs
+++ b/src/Text/Pandoc/Readers/MediaWiki.hs
@@ -1,4 +1,6 @@
-{-# LANGUAGE RelaxedPolyRec, FlexibleInstances, TypeSynonymInstances #-}
+{-# LANGUAGE FlexibleInstances #-}
+{-# LANGUAGE RelaxedPolyRec #-}
+{-# LANGUAGE TypeSynonymInstances #-}
-- RelaxedPolyRec needed for inlinesBetween on GHC < 7
{-
Copyright (C) 2012-2015 John MacFarlane <jgm@berkeley.edu>
@@ -36,28 +38,28 @@ _ parse templates?
-}
module Text.Pandoc.Readers.MediaWiki ( readMediaWiki ) where
-import Text.Pandoc.Definition
-import qualified Text.Pandoc.Builder as B
-import Text.Pandoc.Builder (Inlines, Blocks, trimInlines)
-import Data.Monoid ((<>))
-import Text.Pandoc.Options
-import Text.Pandoc.Logging
-import Text.Pandoc.Readers.HTML ( htmlTag, isBlockTag, isCommentTag )
-import Text.Pandoc.XML ( fromEntities )
-import Text.Pandoc.Parsing hiding ( nested )
-import Text.Pandoc.Walk ( walk )
-import Text.Pandoc.Shared ( stripTrailingNewlines, safeRead, stringify, trim )
import Control.Monad
-import Data.List (intersperse, intercalate, isPrefixOf )
-import Text.HTML.TagSoup
-import Data.Sequence (viewl, ViewL(..), (<|))
+import Control.Monad.Except (throwError)
+import Data.Char (isDigit, isSpace)
import qualified Data.Foldable as F
+import Data.List (intercalate, intersperse, isPrefixOf)
import qualified Data.Map as M
-import qualified Data.Set as Set
-import Data.Char (isDigit, isSpace)
import Data.Maybe (fromMaybe)
-import Control.Monad.Except (throwError)
+import Data.Monoid ((<>))
+import Data.Sequence (ViewL (..), viewl, (<|))
+import qualified Data.Set as Set
+import Text.HTML.TagSoup
+import Text.Pandoc.Builder (Blocks, Inlines, trimInlines)
+import qualified Text.Pandoc.Builder as B
import Text.Pandoc.Class (PandocMonad, report)
+import Text.Pandoc.Definition
+import Text.Pandoc.Logging
+import Text.Pandoc.Options
+import Text.Pandoc.Parsing hiding (nested)
+import Text.Pandoc.Readers.HTML (htmlTag, isBlockTag, isCommentTag)
+import Text.Pandoc.Shared (safeRead, stringify, stripTrailingNewlines, trim)
+import Text.Pandoc.Walk (walk)
+import Text.Pandoc.XML (fromEntities)
-- | Read mediawiki from an input string and return a Pandoc document.
readMediaWiki :: PandocMonad m
@@ -75,7 +77,7 @@ readMediaWiki opts s = do
(s ++ "\n")
case parsed of
Right result -> return result
- Left e -> throwError e
+ Left e -> throwError e
data MWState = MWState { mwOptions :: ReaderOptions
, mwMaxNestingLevel :: Int
@@ -134,7 +136,7 @@ isBlockTag' tag = isBlockTag tag
isInlineTag' :: Tag String -> Bool
isInlineTag' (TagComment _) = True
-isInlineTag' t = not (isBlockTag' t)
+isInlineTag' t = not (isBlockTag' t)
eitherBlockOrInline :: [String]
eitherBlockOrInline = ["applet", "button", "del", "iframe", "ins",
@@ -311,7 +313,7 @@ parseWidth :: String -> Maybe Double
parseWidth s =
case reverse s of
('%':ds) | all isDigit ds -> safeRead ('0':'.':reverse ds)
- _ -> Nothing
+ _ -> Nothing
template :: PandocMonad m => MWParser m String
template = try $ do
@@ -468,10 +470,10 @@ listItem c = try $ do
many1 $ listItem' c)
(unlines (first : rest))
case c of
- '*' -> return $ B.bulletList contents
- '#' -> return $ B.orderedList contents
- ':' -> return $ B.definitionList [(mempty, contents)]
- _ -> mzero
+ '*' -> return $ B.bulletList contents
+ '#' -> return $ B.orderedList contents
+ ':' -> return $ B.definitionList [(mempty, contents)]
+ _ -> mzero
-- The point of this is to handle stuff like
-- * {{cite book
@@ -619,9 +621,9 @@ imageOption = try $ char '|' *> opt
<|> try (oneOfStrings ["link=","alt=","page=","class="] <* many (noneOf "|]"))
collapseUnderscores :: String -> String
-collapseUnderscores [] = []
+collapseUnderscores [] = []
collapseUnderscores ('_':'_':xs) = collapseUnderscores ('_':xs)
-collapseUnderscores (x:xs) = x : collapseUnderscores xs
+collapseUnderscores (x:xs) = x : collapseUnderscores xs
addUnderscores :: String -> String
addUnderscores = collapseUnderscores . intercalate "_" . words
diff --git a/src/Text/Pandoc/Readers/Native.hs b/src/Text/Pandoc/Readers/Native.hs
index 1953c0c83..2e307fa4f 100644
--- a/src/Text/Pandoc/Readers/Native.hs
+++ b/src/Text/Pandoc/Readers/Native.hs
@@ -31,12 +31,12 @@ Conversion of a string representation of a pandoc type (@Pandoc@,
module Text.Pandoc.Readers.Native ( readNative ) where
import Text.Pandoc.Definition
-import Text.Pandoc.Shared (safeRead)
import Text.Pandoc.Options (ReaderOptions)
+import Text.Pandoc.Shared (safeRead)
import Control.Monad.Except (throwError)
-import Text.Pandoc.Error
import Text.Pandoc.Class
+import Text.Pandoc.Error
-- | Read native formatted text and return a Pandoc document.
-- The input may be a full pandoc document, a block list, a block,
diff --git a/src/Text/Pandoc/Readers/OPML.hs b/src/Text/Pandoc/Readers/OPML.hs
index cec64895c..cf1c8f479 100644
--- a/src/Text/Pandoc/Readers/OPML.hs
+++ b/src/Text/Pandoc/Readers/OPML.hs
@@ -1,17 +1,16 @@
{-# LANGUAGE FlexibleContexts #-}
module Text.Pandoc.Readers.OPML ( readOPML ) where
+import Control.Monad.State
import Data.Char (toUpper)
-import Text.Pandoc.Options
-import Text.Pandoc.Definition
+import Data.Default
+import Data.Generics
+import Text.HTML.TagSoup.Entity (lookupEntity)
import Text.Pandoc.Builder
+import Text.Pandoc.Class (PandocMonad)
+import Text.Pandoc.Options
import Text.Pandoc.Readers.HTML (readHtml)
import Text.Pandoc.Readers.Markdown (readMarkdown)
import Text.XML.Light
-import Text.HTML.TagSoup.Entity (lookupEntity)
-import Data.Generics
-import Control.Monad.State
-import Data.Default
-import Text.Pandoc.Class (PandocMonad)
type OPML m = StateT OPMLState m
@@ -70,7 +69,7 @@ asHtml :: PandocMonad m => String -> OPML m Inlines
asHtml s =
(\(Pandoc _ bs) -> case bs of
[Plain ils] -> fromList ils
- _ -> mempty) <$> (lift $ readHtml def s)
+ _ -> mempty) <$> (lift $ readHtml def s)
asMarkdown :: PandocMonad m => String -> OPML m Blocks
asMarkdown s = (\(Pandoc _ bs) -> fromList bs) <$> (lift $ readMarkdown def s)
diff --git a/src/Text/Pandoc/Readers/Org.hs b/src/Text/Pandoc/Readers/Org.hs
index c8dbbf45a..cc3ed6003 100644
--- a/src/Text/Pandoc/Readers/Org.hs
+++ b/src/Text/Pandoc/Readers/Org.hs
@@ -27,17 +27,17 @@ Conversion of org-mode formatted plain text to 'Pandoc' document.
-}
module Text.Pandoc.Readers.Org ( readOrg ) where
-import Text.Pandoc.Readers.Org.Blocks ( blockList, meta )
-import Text.Pandoc.Readers.Org.Parsing ( OrgParser, readWithM )
-import Text.Pandoc.Readers.Org.ParserState ( optionsToParserState )
+import Text.Pandoc.Readers.Org.Blocks (blockList, meta)
+import Text.Pandoc.Readers.Org.ParserState (optionsToParserState)
+import Text.Pandoc.Readers.Org.Parsing (OrgParser, readWithM)
-import Text.Pandoc.Class (PandocMonad)
-import Text.Pandoc.Definition
-import Text.Pandoc.Error
-import Text.Pandoc.Options
+import Text.Pandoc.Class (PandocMonad)
+import Text.Pandoc.Definition
+import Text.Pandoc.Error
+import Text.Pandoc.Options
-import Control.Monad.Except ( throwError )
-import Control.Monad.Reader ( runReaderT )
+import Control.Monad.Except (throwError)
+import Control.Monad.Reader (runReaderT)
-- | Parse org-mode string and return a Pandoc document.
diff --git a/src/Text/Pandoc/Readers/Org/BlockStarts.hs b/src/Text/Pandoc/Readers/Org/BlockStarts.hs
index 5588c4552..cc2e82d5b 100644
--- a/src/Text/Pandoc/Readers/Org/BlockStarts.hs
+++ b/src/Text/Pandoc/Readers/Org/BlockStarts.hs
@@ -40,7 +40,7 @@ module Text.Pandoc.Readers.Org.BlockStarts
, endOfBlock
) where
-import Control.Monad ( void )
+import Control.Monad (void)
import Text.Pandoc.Readers.Org.Parsing
-- | Horizontal Line (five -- dashes or more)
diff --git a/src/Text/Pandoc/Readers/Org/Blocks.hs b/src/Text/Pandoc/Readers/Org/Blocks.hs
index 78ac8d0d1..a5311e8f4 100644
--- a/src/Text/Pandoc/Readers/Org/Blocks.hs
+++ b/src/Text/Pandoc/Readers/Org/Blocks.hs
@@ -1,6 +1,6 @@
{-# LANGUAGE FlexibleContexts #-}
-{-# LANGUAGE RecordWildCards #-}
-{-# LANGUAGE ViewPatterns #-}
+{-# LANGUAGE RecordWildCards #-}
+{-# LANGUAGE ViewPatterns #-}
{-
Copyright (C) 2014-2017 Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
@@ -33,28 +33,28 @@ module Text.Pandoc.Readers.Org.Blocks
, meta
) where
-import Text.Pandoc.Readers.Org.BlockStarts
-import Text.Pandoc.Readers.Org.Inlines
-import Text.Pandoc.Readers.Org.Meta ( metaExport, metaKey, metaLine )
-import Text.Pandoc.Readers.Org.ParserState
-import Text.Pandoc.Readers.Org.Parsing
-import Text.Pandoc.Readers.Org.Shared
- ( cleanLinkString, isImageFilename, rundocBlockClass
- , toRundocAttrib, translateLang )
+import Text.Pandoc.Readers.Org.BlockStarts
+import Text.Pandoc.Readers.Org.Inlines
+import Text.Pandoc.Readers.Org.Meta (metaExport, metaKey, metaLine)
+import Text.Pandoc.Readers.Org.ParserState
+import Text.Pandoc.Readers.Org.Parsing
+import Text.Pandoc.Readers.Org.Shared (cleanLinkString, isImageFilename,
+ rundocBlockClass, toRundocAttrib,
+ translateLang)
+import Text.Pandoc.Builder (Blocks, Inlines)
import qualified Text.Pandoc.Builder as B
-import Text.Pandoc.Builder ( Inlines, Blocks )
-import Text.Pandoc.Class (PandocMonad)
-import Text.Pandoc.Definition
-import Text.Pandoc.Options
-import Text.Pandoc.Shared ( compactify, compactifyDL, safeRead )
-
-import Control.Monad ( foldM, guard, mzero, void )
-import Data.Char ( isSpace, toLower, toUpper)
-import Data.Default ( Default )
-import Data.List ( foldl', isPrefixOf )
-import Data.Maybe ( fromMaybe, isNothing )
-import Data.Monoid ((<>))
+import Text.Pandoc.Class (PandocMonad)
+import Text.Pandoc.Definition
+import Text.Pandoc.Options
+import Text.Pandoc.Shared (compactify, compactifyDL, safeRead)
+
+import Control.Monad (foldM, guard, mzero, void)
+import Data.Char (isSpace, toLower, toUpper)
+import Data.Default (Default)
+import Data.List (foldl', isPrefixOf)
+import Data.Maybe (fromMaybe, isNothing)
+import Data.Monoid ((<>))
--
-- Org headers
@@ -581,7 +581,7 @@ genericDrawer = try $ do
_ | name == "PROPERTIES" -> return mempty
Left names | name `elem` names -> return mempty
Right names | name `notElem` names -> return mempty
- _ -> drawerDiv name <$> parseLines content
+ _ -> drawerDiv name <$> parseLines content
where
parseLines :: PandocMonad m => [String] -> OrgParser m (F Blocks)
parseLines = parseFromString blocks . (++ "\n") . unlines
@@ -715,8 +715,8 @@ data OrgTableRow = OrgContentRow (F [Blocks])
-- should be generated using a builder function.
data OrgTable = OrgTable
{ orgTableColumnProperties :: [ColumnProperty]
- , orgTableHeader :: [Blocks]
- , orgTableRows :: [[Blocks]]
+ , orgTableHeader :: [Blocks]
+ , orgTableRows :: [[Blocks]]
}
table :: PandocMonad m => OrgParser m (F Blocks)
diff --git a/src/Text/Pandoc/Readers/Org/ExportSettings.hs b/src/Text/Pandoc/Readers/Org/ExportSettings.hs
index 391877c03..1d6fdd7e1 100644
--- a/src/Text/Pandoc/Readers/Org/ExportSettings.hs
+++ b/src/Text/Pandoc/Readers/Org/ExportSettings.hs
@@ -29,12 +29,12 @@ module Text.Pandoc.Readers.Org.ExportSettings
( exportSettings
) where
-import Text.Pandoc.Readers.Org.ParserState
-import Text.Pandoc.Readers.Org.Parsing
+import Text.Pandoc.Readers.Org.ParserState
+import Text.Pandoc.Readers.Org.Parsing
-import Control.Monad ( mzero, void )
-import Data.Char ( toLower )
-import Data.Maybe ( listToMaybe )
+import Control.Monad (mzero, void)
+import Data.Char (toLower)
+import Data.Maybe (listToMaybe)
-- | Read and handle space separated org-mode export settings.
exportSettings :: Monad m => OrgParser m ()
diff --git a/src/Text/Pandoc/Readers/Org/Inlines.hs b/src/Text/Pandoc/Readers/Org/Inlines.hs
index f3671641a..4e61bc695 100644
--- a/src/Text/Pandoc/Readers/Org/Inlines.hs
+++ b/src/Text/Pandoc/Readers/Org/Inlines.hs
@@ -33,31 +33,31 @@ module Text.Pandoc.Readers.Org.Inlines
, linkTarget
) where
-import Text.Pandoc.Readers.Org.BlockStarts ( endOfBlock, noteMarker )
-import Text.Pandoc.Readers.Org.ParserState
-import Text.Pandoc.Readers.Org.Parsing
-import Text.Pandoc.Readers.Org.Shared
- ( cleanLinkString, isImageFilename, rundocBlockClass
- , toRundocAttrib, translateLang )
-
+import Text.Pandoc.Readers.Org.BlockStarts (endOfBlock, noteMarker)
+import Text.Pandoc.Readers.Org.ParserState
+import Text.Pandoc.Readers.Org.Parsing
+import Text.Pandoc.Readers.Org.Shared (cleanLinkString, isImageFilename,
+ rundocBlockClass, toRundocAttrib,
+ translateLang)
+
+import Text.Pandoc.Builder (Inlines)
import qualified Text.Pandoc.Builder as B
-import Text.Pandoc.Builder ( Inlines )
-import Text.Pandoc.Definition
-import Text.Pandoc.Options
-import Text.Pandoc.Readers.LaTeX ( inlineCommand, rawLaTeXInline )
-import Text.TeXMath ( readTeX, writePandoc, DisplayType(..) )
+import Text.Pandoc.Class (PandocMonad)
+import Text.Pandoc.Definition
+import Text.Pandoc.Options
+import Text.Pandoc.Readers.LaTeX (inlineCommand, rawLaTeXInline)
+import Text.TeXMath (DisplayType (..), readTeX, writePandoc)
import qualified Text.TeXMath.Readers.MathML.EntityMap as MathMLEntityMap
-import Text.Pandoc.Class (PandocMonad)
-
-import Prelude hiding (sequence)
-import Control.Monad ( guard, mplus, mzero, when, void )
-import Control.Monad.Trans ( lift )
-import Data.Char ( isAlphaNum, isSpace )
-import Data.List ( intersperse )
-import Data.Maybe ( fromMaybe )
+
+import Control.Monad (guard, mplus, mzero, void, when)
+import Control.Monad.Trans (lift)
+import Data.Char (isAlphaNum, isSpace)
+import Data.List (intersperse)
import qualified Data.Map as M
-import Data.Monoid ( (<>) )
-import Data.Traversable (sequence)
+import Data.Maybe (fromMaybe)
+import Data.Monoid ((<>))
+import Data.Traversable (sequence)
+import Prelude hiding (sequence)
--
-- Functions acting on the parser state
@@ -258,10 +258,10 @@ berkeleyCite = try $ do
appendSuffix suf c = c { citationSuffix = citationSuffix c <> B.toList suf }
data BerkeleyCitationList = BerkeleyCitationList
- { berkeleyCiteParens :: Bool
+ { berkeleyCiteParens :: Bool
, berkeleyCiteCommonPrefix :: Maybe Inlines
, berkeleyCiteCommonSuffix :: Maybe Inlines
- , berkeleyCiteCitations :: [Citation]
+ , berkeleyCiteCitations :: [Citation]
}
berkeleyCitationList :: PandocMonad m => OrgParser m (F BerkeleyCitationList)
berkeleyCitationList = try $ do
diff --git a/src/Text/Pandoc/Readers/Org/Meta.hs b/src/Text/Pandoc/Readers/Org/Meta.hs
index 2f4e21248..c22f441d4 100644
--- a/src/Text/Pandoc/Readers/Org/Meta.hs
+++ b/src/Text/Pandoc/Readers/Org/Meta.hs
@@ -1,5 +1,5 @@
{-# LANGUAGE FlexibleContexts #-}
-{-# LANGUAGE TupleSections #-}
+{-# LANGUAGE TupleSections #-}
{-
Copyright (C) 2014-2017 Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
@@ -33,23 +33,23 @@ module Text.Pandoc.Readers.Org.Meta
, metaLine
) where
-import Text.Pandoc.Readers.Org.BlockStarts
-import Text.Pandoc.Readers.Org.ExportSettings ( exportSettings )
-import Text.Pandoc.Readers.Org.Inlines
-import Text.Pandoc.Readers.Org.ParserState
-import Text.Pandoc.Readers.Org.Parsing
+import Text.Pandoc.Readers.Org.BlockStarts
+import Text.Pandoc.Readers.Org.ExportSettings (exportSettings)
+import Text.Pandoc.Readers.Org.Inlines
+import Text.Pandoc.Readers.Org.ParserState
+import Text.Pandoc.Readers.Org.Parsing
+import Text.Pandoc.Builder (Blocks, Inlines)
import qualified Text.Pandoc.Builder as B
-import Text.Pandoc.Builder ( Blocks, Inlines )
-import Text.Pandoc.Class ( PandocMonad )
-import Text.Pandoc.Definition
+import Text.Pandoc.Class (PandocMonad)
+import Text.Pandoc.Definition
-import Control.Monad ( mzero, void )
-import Data.Char ( toLower )
-import Data.List ( intersperse )
+import Control.Monad (mzero, void)
+import Data.Char (toLower)
+import Data.List (intersperse)
import qualified Data.Map as M
-import Data.Monoid ( (<>) )
-import Network.HTTP ( urlEncode )
+import Data.Monoid ((<>))
+import Network.HTTP (urlEncode)
-- | Returns the current meta, respecting export options.
metaExport :: Monad m => OrgParser m (F Meta)
@@ -151,7 +151,7 @@ optionLine = try $ do
"todo" -> todoSequence >>= updateState . registerTodoSequence
"seq_todo" -> todoSequence >>= updateState . registerTodoSequence
"typ_todo" -> todoSequence >>= updateState . registerTodoSequence
- _ -> mzero
+ _ -> mzero
addLinkFormat :: Monad m => String
-> (String -> String)
diff --git a/src/Text/Pandoc/Readers/Org/ParserState.hs b/src/Text/Pandoc/Readers/Org/ParserState.hs
index 181dd1d5c..0bbe27991 100644
--- a/src/Text/Pandoc/Readers/Org/ParserState.hs
+++ b/src/Text/Pandoc/Readers/Org/ParserState.hs
@@ -1,6 +1,6 @@
-{-# LANGUAGE FlexibleInstances #-}
+{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
-{-# LANGUAGE MultiParamTypeClasses #-}
+{-# LANGUAGE MultiParamTypeClasses #-}
{-
Copyright (C) 2014-2016 Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
@@ -50,24 +50,20 @@ module Text.Pandoc.Readers.Org.ParserState
, optionsToParserState
) where
-import Control.Monad (liftM, liftM2)
-import Control.Monad.Reader (Reader, runReader, ReaderT, ask, asks, local)
+import Control.Monad (liftM, liftM2)
+import Control.Monad.Reader (Reader, ReaderT, ask, asks, local, runReader)
-import Data.Default (Default(..))
+import Data.Default (Default (..))
import qualified Data.Map as M
import qualified Data.Set as Set
-import Text.Pandoc.Builder ( Inlines, Blocks, trimInlines )
-import Text.Pandoc.Definition ( Meta(..), nullMeta )
-import Text.Pandoc.Options ( ReaderOptions(..) )
-import Text.Pandoc.Parsing ( HasHeaderMap(..)
- , HasIdentifierList(..)
- , HasLastStrPosition(..)
- , HasQuoteContext(..)
- , HasReaderOptions(..)
- , ParserContext(..)
- , QuoteContext(..)
- , SourcePos )
+import Text.Pandoc.Builder (Blocks, Inlines, trimInlines)
+import Text.Pandoc.Definition (Meta (..), nullMeta)
+import Text.Pandoc.Options (ReaderOptions (..))
+import Text.Pandoc.Parsing (HasHeaderMap (..), HasIdentifierList (..),
+ HasLastStrPosition (..), HasQuoteContext (..),
+ HasReaderOptions (..), ParserContext (..),
+ QuoteContext (..), SourcePos)
-- | An inline note / footnote containing the note key and its (inline) value.
type OrgNoteRecord = (String, F Blocks)
@@ -191,20 +187,20 @@ data ArchivedTreesOption =
-- | Export settings <http://orgmode.org/manual/Export-settings.html>
-- These settings can be changed via OPTIONS statements.
data ExportSettings = ExportSettings
- { exportArchivedTrees :: ArchivedTreesOption -- ^ How to treat archived trees
- , exportDrawers :: Either [String] [String]
+ { exportArchivedTrees :: ArchivedTreesOption -- ^ How to treat archived trees
+ , exportDrawers :: Either [String] [String]
-- ^ Specify drawer names which should be exported. @Left@ names are
-- explicitly excluded from the resulting output while @Right@ means that
-- only the listed drawer names should be included.
- , exportEmphasizedText :: Bool -- ^ Parse emphasized text
- , exportHeadlineLevels :: Int
+ , exportEmphasizedText :: Bool -- ^ Parse emphasized text
+ , exportHeadlineLevels :: Int
-- ^ Maximum depth of headlines, deeper headlines are convert to list
- , exportSmartQuotes :: Bool -- ^ Parse quotes smartly
- , exportSpecialStrings :: Bool -- ^ Parse ellipses and dashes smartly
- , exportSubSuperscripts :: Bool -- ^ TeX-like syntax for sub- and superscripts
- , exportWithAuthor :: Bool -- ^ Include author in final meta-data
- , exportWithCreator :: Bool -- ^ Include creator in final meta-data
- , exportWithEmail :: Bool -- ^ Include email in final meta-data
+ , exportSmartQuotes :: Bool -- ^ Parse quotes smartly
+ , exportSpecialStrings :: Bool -- ^ Parse ellipses and dashes smartly
+ , exportSubSuperscripts :: Bool -- ^ TeX-like syntax for sub- and superscripts
+ , exportWithAuthor :: Bool -- ^ Include author in final meta-data
+ , exportWithCreator :: Bool -- ^ Include creator in final meta-data
+ , exportWithEmail :: Bool -- ^ Include email in final meta-data
, exportWithTodoKeywords :: Bool -- ^ Keep TODO keywords in headers
}
diff --git a/src/Text/Pandoc/Readers/Org/Parsing.hs b/src/Text/Pandoc/Readers/Org/Parsing.hs
index 1eb8a3b00..03c9b1981 100644
--- a/src/Text/Pandoc/Readers/Org/Parsing.hs
+++ b/src/Text/Pandoc/Readers/Org/Parsing.hs
@@ -108,14 +108,14 @@ module Text.Pandoc.Readers.Org.Parsing
, getPosition
) where
-import Text.Pandoc.Readers.Org.ParserState
+import Text.Pandoc.Readers.Org.ParserState
+import Text.Pandoc.Parsing hiding (anyLine, blanklines, newline,
+ parseFromString)
import qualified Text.Pandoc.Parsing as P
-import Text.Pandoc.Parsing hiding ( anyLine, blanklines, newline
- , parseFromString )
-import Control.Monad ( guard )
-import Control.Monad.Reader ( ReaderT )
+import Control.Monad (guard)
+import Control.Monad.Reader (ReaderT)
-- | The parser used to read org files.
type OrgParser m = ParserT [Char] OrgParserState (ReaderT OrgParserLocal m)
diff --git a/src/Text/Pandoc/Readers/Org/Shared.hs b/src/Text/Pandoc/Readers/Org/Shared.hs
index 8c87cfa25..a5b285f30 100644
--- a/src/Text/Pandoc/Readers/Org/Shared.hs
+++ b/src/Text/Pandoc/Readers/Org/Shared.hs
@@ -34,9 +34,9 @@ module Text.Pandoc.Readers.Org.Shared
, translateLang
) where
-import Control.Arrow ( first )
-import Data.Char ( isAlphaNum )
-import Data.List ( isPrefixOf, isSuffixOf )
+import Control.Arrow (first)
+import Data.Char (isAlphaNum)
+import Data.List (isPrefixOf, isSuffixOf)
-- | Check whether the given string looks like the path to of URL of an image.
@@ -59,7 +59,7 @@ cleanLinkString s =
'.':'.':'/':_ -> Just s -- relative path
-- Relative path or URL (file schema)
'f':'i':'l':'e':':':s' -> Just $ if ("//" `isPrefixOf` s') then s else s'
- _ | isUrl s -> Just s -- URL
+ _ | isUrl s -> Just s -- URL
_ -> Nothing
where
isUrl :: String -> Bool
diff --git a/src/Text/Pandoc/Readers/RST.hs b/src/Text/Pandoc/Readers/RST.hs
index 0f6785033..0adc190c3 100644
--- a/src/Text/Pandoc/Readers/RST.hs
+++ b/src/Text/Pandoc/Readers/RST.hs
@@ -1,6 +1,6 @@
+{-# LANGUAGE FlexibleContexts #-}
+{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
-{-# LANGUAGE OverloadedStrings #-}
-{-# LANGUAGE FlexibleContexts #-}
{-
Copyright (C) 2006-2015 John MacFarlane <jgm@berkeley.edu>
@@ -31,27 +31,27 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
Conversion from reStructuredText to 'Pandoc' document.
-}
module Text.Pandoc.Readers.RST ( readRST ) where
-import Text.Pandoc.Definition
-import Text.Pandoc.Builder (setMeta, fromList)
-import Text.Pandoc.Shared
-import Text.Pandoc.Parsing
-import Text.Pandoc.Options
-import Text.Pandoc.Logging
-import Text.Pandoc.Error
-import Text.Pandoc.ImageSize (lengthToDim, scaleDimension)
-import Control.Monad ( when, liftM, guard, mzero )
-import Data.List ( findIndex, intercalate, isInfixOf,
- transpose, sort, deleteFirstsBy, isSuffixOf , nub, union)
-import Data.Maybe (fromMaybe, isJust)
+import Control.Monad (guard, liftM, mzero, when)
+import Control.Monad.Except (throwError)
+import Data.Char (isHexDigit, isSpace, toLower, toUpper)
+import Data.List (deleteFirstsBy, findIndex, intercalate, isInfixOf, isSuffixOf,
+ nub, sort, transpose, union)
import qualified Data.Map as M
-import Text.Printf ( printf )
-import Text.Pandoc.Builder (Inlines, Blocks, trimInlines)
-import qualified Text.Pandoc.Builder as B
-import Data.Sequence (viewr, ViewR(..))
-import Data.Char (toLower, isHexDigit, isSpace, toUpper)
+import Data.Maybe (fromMaybe, isJust)
import Data.Monoid ((<>))
-import Control.Monad.Except (throwError)
+import Data.Sequence (ViewR (..), viewr)
+import Text.Pandoc.Builder (fromList, setMeta)
+import Text.Pandoc.Builder (Blocks, Inlines, trimInlines)
+import qualified Text.Pandoc.Builder as B
import Text.Pandoc.Class (PandocMonad, readFileFromDirs)
+import Text.Pandoc.Definition
+import Text.Pandoc.Error
+import Text.Pandoc.ImageSize (lengthToDim, scaleDimension)
+import Text.Pandoc.Logging
+import Text.Pandoc.Options
+import Text.Pandoc.Parsing
+import Text.Pandoc.Shared
+import Text.Printf (printf)
-- TODO:
-- [ ] .. parsed-literal
@@ -667,7 +667,7 @@ directive' = do
_ ->
case safeRead v of
Just (s :: Double) -> s
- Nothing -> 1.0
+ Nothing -> 1.0
Nothing -> 1.0
widthAttr = maybe [] (\x -> [("width",
show $ scaleDimension scale x)])
@@ -744,7 +744,7 @@ directive' = do
-- directive content or the first immediately following element
children <- case body of
"" -> block
- _ -> parseFromString parseBlocks body'
+ _ -> parseFromString parseBlocks body'
return $ B.divWith attrs children
other -> do
pos <- getPosition
@@ -775,7 +775,7 @@ addNewRole roleString fields = do
let getBaseRole (r, f, a) roles =
case M.lookup r roles of
Just (r', f', a') -> getBaseRole (r', f', a') roles
- Nothing -> (r, f, a)
+ Nothing -> (r, f, a)
(baseRole, baseFmt, baseAttr) =
getBaseRole (parentRole, Nothing, nullAttr) customRoles
fmt = if parentRole == "raw" then lookup "format" fields else baseFmt
@@ -1003,7 +1003,7 @@ anonymousKey = try $ do
stripTicks :: String -> String
stripTicks = reverse . stripTick . reverse . stripTick
where stripTick ('`':xs) = xs
- stripTick xs = xs
+ stripTick xs = xs
regularKey :: PandocMonad m => RSTParser m ()
regularKey = try $ do
@@ -1320,7 +1320,7 @@ explicitLink = try $ do
-- `link <google_>` is a reference link to _google!
((src',tit),attr) <- case reverse src of
'_':xs -> lookupKey [] (toKey (reverse xs))
- _ -> return ((src, ""), nullAttr)
+ _ -> return ((src, ""), nullAttr)
return $ B.linkWith attr (escapeURI src') tit label''
citationName :: PandocMonad m => RSTParser m Inlines
@@ -1342,7 +1342,7 @@ referenceLink = try $ do
do char '_'
let anonKeys = sort $ filter isAnonKey $ M.keys keyTable
case anonKeys of
- [] -> mzero
+ [] -> mzero
(k:_) -> return k
((src,tit), attr) <- lookupKey [] key
-- if anonymous link, remove key so it won't be used again
diff --git a/src/Text/Pandoc/Readers/TWiki.hs b/src/Text/Pandoc/Readers/TWiki.hs
index 3b89f2ee9..397179dd1 100644
--- a/src/Text/Pandoc/Readers/TWiki.hs
+++ b/src/Text/Pandoc/Readers/TWiki.hs
@@ -1,4 +1,7 @@
-{-# LANGUAGE RelaxedPolyRec, FlexibleInstances, TypeSynonymInstances, FlexibleContexts #-}
+{-# LANGUAGE FlexibleContexts #-}
+{-# LANGUAGE FlexibleInstances #-}
+{-# LANGUAGE RelaxedPolyRec #-}
+{-# LANGUAGE TypeSynonymInstances #-}
-- RelaxedPolyRec needed for inlinesBetween on GHC < 7
{-
Copyright (C) 2014 Alexander Sulfrian <alexander.sulfrian@fu-berlin.de>
@@ -32,20 +35,20 @@ Conversion of twiki text to 'Pandoc' document.
module Text.Pandoc.Readers.TWiki ( readTWiki
) where
-import Text.Pandoc.Definition
+import Control.Monad
+import Control.Monad.Except (throwError)
+import Data.Char (isAlphaNum)
+import qualified Data.Foldable as F
+import Data.Maybe (fromMaybe)
+import Text.HTML.TagSoup
import qualified Text.Pandoc.Builder as B
-import Text.Pandoc.Options
+import Text.Pandoc.Class (PandocMonad, report)
+import Text.Pandoc.Definition
import Text.Pandoc.Logging
+import Text.Pandoc.Options
import Text.Pandoc.Parsing hiding (enclosed, macro, nested)
import Text.Pandoc.Readers.HTML (htmlTag, isCommentTag)
-import Control.Monad
import Text.Pandoc.XML (fromEntities)
-import Data.Maybe (fromMaybe)
-import Text.HTML.TagSoup
-import Data.Char (isAlphaNum)
-import qualified Data.Foldable as F
-import Control.Monad.Except (throwError)
-import Text.Pandoc.Class (PandocMonad, report)
-- | Read twiki from an input string and return a Pandoc document.
readTWiki :: PandocMonad m
@@ -391,8 +394,8 @@ attributes = char '{' *> spnl *> many (attribute <* spnl) <* char '}' >>=
return . foldr (either mkContent mkKvs) ([], [])
where
spnl = skipMany (spaceChar <|> newline)
- mkContent c ([], kvs) = (c, kvs)
- mkContent c (rest, kvs) = (c ++ " " ++ rest, kvs)
+ mkContent c ([], kvs) = (c, kvs)
+ mkContent c (rest, kvs) = (c ++ " " ++ rest, kvs)
mkKvs kv (cont, rest) = (cont, (kv : rest))
attribute :: PandocMonad m => TWParser m (Either String (String, String))
diff --git a/src/Text/Pandoc/Readers/Textile.hs b/src/Text/Pandoc/Readers/Textile.hs
index 6594b9ab8..047aa061c 100644
--- a/src/Text/Pandoc/Readers/Textile.hs
+++ b/src/Text/Pandoc/Readers/Textile.hs
@@ -51,24 +51,24 @@ TODO : refactor common patterns across readers :
module Text.Pandoc.Readers.Textile ( readTextile) where
+import Control.Monad (guard, liftM)
+import Control.Monad.Except (throwError)
+import Data.Char (digitToInt, isUpper)
+import Data.List (intercalate, intersperse, transpose)
+import Data.Monoid ((<>))
+import Text.HTML.TagSoup (Tag (..), fromAttrib)
+import Text.HTML.TagSoup.Match
+import Text.Pandoc.Builder (Blocks, Inlines, trimInlines)
+import qualified Text.Pandoc.Builder as B
+import Text.Pandoc.Class (PandocMonad, report)
import Text.Pandoc.CSS
import Text.Pandoc.Definition
-import Text.Pandoc.Builder (Inlines, Blocks, trimInlines)
-import qualified Text.Pandoc.Builder as B
+import Text.Pandoc.Logging
import Text.Pandoc.Options
import Text.Pandoc.Parsing
-import Text.Pandoc.Logging
-import Text.Pandoc.Readers.HTML ( htmlTag, isBlockTag, isInlineTag )
+import Text.Pandoc.Readers.HTML (htmlTag, isBlockTag, isInlineTag)
+import Text.Pandoc.Readers.LaTeX (rawLaTeXBlock, rawLaTeXInline)
import Text.Pandoc.Shared (trim)
-import Text.Pandoc.Readers.LaTeX ( rawLaTeXInline, rawLaTeXBlock )
-import Text.HTML.TagSoup (fromAttrib, Tag(..))
-import Text.HTML.TagSoup.Match
-import Data.List ( intercalate, transpose, intersperse )
-import Data.Char ( digitToInt, isUpper )
-import Control.Monad ( guard, liftM )
-import Data.Monoid ((<>))
-import Text.Pandoc.Class (PandocMonad, report)
-import Control.Monad.Except (throwError)
-- | Parse a Textile text and return a Pandoc document.
readTextile :: PandocMonad m
@@ -79,7 +79,7 @@ readTextile opts s = do
parsed <- readWithM parseTextile def{ stateOptions = opts } (s ++ "\n\n")
case parsed of
Right result -> return result
- Left e -> throwError e
+ Left e -> throwError e
-- | Generate a Pandoc ADT from a textile document
@@ -505,8 +505,8 @@ note = try $ do
ref <- (char '[' *> many1 digit <* char ']')
notes <- stateNotes <$> getState
case lookup ref notes of
- Nothing -> fail "note not found"
- Just raw -> B.note <$> parseFromString parseBlocks raw
+ Nothing -> fail "note not found"
+ Just raw -> B.note <$> parseFromString parseBlocks raw
-- | Special chars
markupChars :: [Char]
diff --git a/src/Text/Pandoc/Readers/Txt2Tags.hs b/src/Text/Pandoc/Readers/Txt2Tags.hs
index 9e2b6963d..33f785109 100644
--- a/src/Text/Pandoc/Readers/Txt2Tags.hs
+++ b/src/Text/Pandoc/Readers/Txt2Tags.hs
@@ -32,35 +32,35 @@ module Text.Pandoc.Readers.Txt2Tags ( readTxt2Tags
)
where
-import qualified Text.Pandoc.Builder as B
-import Text.Pandoc.Builder ( Inlines, Blocks, trimInlines )
+import Data.Char (toLower)
+import Data.List (intercalate, intersperse, transpose)
+import Data.Maybe (fromMaybe)
import Data.Monoid ((<>))
+import Text.Pandoc.Builder (Blocks, Inlines, trimInlines)
+import qualified Text.Pandoc.Builder as B
import Text.Pandoc.Definition
import Text.Pandoc.Options
-import Text.Pandoc.Shared (escapeURI,compactify, compactifyDL)
-import Text.Pandoc.Parsing hiding (space, spaces, uri, macro)
-import Data.Char (toLower)
-import Data.List (transpose, intersperse, intercalate)
-import Data.Maybe (fromMaybe)
+import Text.Pandoc.Parsing hiding (macro, space, spaces, uri)
+import Text.Pandoc.Shared (compactify, compactifyDL, escapeURI)
--import Network.URI (isURI) -- Not sure whether to use this function
-import Control.Monad (void, guard, when)
+import Control.Monad (guard, void, when)
+import Control.Monad.Reader (Reader, asks, runReader)
import Data.Default
-import Control.Monad.Reader (Reader, runReader, asks)
+import Control.Monad.Except (catchError, throwError)
import Data.Time.Format (formatTime)
-import Text.Pandoc.Compat.Time (defaultTimeLocale)
-import Control.Monad.Except (throwError, catchError)
import Text.Pandoc.Class (PandocMonad)
import qualified Text.Pandoc.Class as P
+import Text.Pandoc.Compat.Time (defaultTimeLocale)
type T2T = ParserT String ParserState (Reader T2TMeta)
-- | An object for the T2T macros meta information
-- the contents of each field is simply substituted verbatim into the file
data T2TMeta = T2TMeta {
- date :: String -- ^ Current date
- , mtime :: String -- ^ Last modification time of infile
- , infile :: FilePath -- ^ Input file
+ date :: String -- ^ Current date
+ , mtime :: String -- ^ Last modification time of infile
+ , infile :: FilePath -- ^ Input file
, outfile :: FilePath -- ^ Output file
} deriving Show
@@ -76,7 +76,7 @@ getT2TMeta = do
Nothing -> []
mbOutp <- P.getOutputFile
let outp = case mbOutp of
- Just x -> x
+ Just x -> x
Nothing -> ""
curDate <- formatTime defaultTimeLocale "%F" <$> P.getZonedTime
let getModTime = fmap (formatTime defaultTimeLocale "%T") .
@@ -98,7 +98,7 @@ readTxt2Tags opts s = do
let parsed = flip runReader meta $ readWithM parseT2T (def {stateOptions = opts}) (s ++ "\n\n")
case parsed of
Right result -> return $ result
- Left e -> throwError e
+ Left e -> throwError e
-- | Read Txt2Tags (ignoring all macros) from an input string returning
-- a Pandoc document
diff --git a/src/Text/Pandoc/SelfContained.hs b/src/Text/Pandoc/SelfContained.hs
index 378b2fe98..524378146 100644
--- a/src/Text/Pandoc/SelfContained.hs
+++ b/src/Text/Pandoc/SelfContained.hs
@@ -31,28 +31,28 @@ offline, by incorporating linked images, CSS, and scripts into
the HTML using data URIs.
-}
module Text.Pandoc.SelfContained ( makeSelfContained ) where
-import Text.HTML.TagSoup
-import Network.URI (isURI, escapeURIString, URI(..), parseURI)
-import Data.ByteString.Base64
-import qualified Data.ByteString.Char8 as B
-import Data.ByteString (ByteString)
-import System.FilePath (takeExtension, takeDirectory, (</>))
-import Data.Char (toLower, isAscii, isAlphaNum)
import Codec.Compression.GZip as Gzip
-import qualified Data.ByteString.Lazy as L
-import Text.Pandoc.Shared (renderTags', trim)
-import Text.Pandoc.MIME (MimeType)
-import Text.Pandoc.UTF8 (toString)
-import Text.Pandoc.Options (WriterOptions(..))
-import Data.List (isPrefixOf)
import Control.Applicative ((<|>))
-import Text.Parsec (runParserT, ParsecT)
-import qualified Text.Parsec as P
import Control.Monad.Except (throwError)
import Control.Monad.Trans (lift)
-import Text.Pandoc.Class (fetchItem, PandocMonad(..), report)
+import Data.ByteString (ByteString)
+import Data.ByteString.Base64
+import qualified Data.ByteString.Char8 as B
+import qualified Data.ByteString.Lazy as L
+import Data.Char (isAlphaNum, isAscii, toLower)
+import Data.List (isPrefixOf)
+import Network.URI (URI (..), escapeURIString, isURI, parseURI)
+import System.FilePath (takeDirectory, takeExtension, (</>))
+import Text.HTML.TagSoup
+import Text.Pandoc.Class (PandocMonad (..), fetchItem, report)
import Text.Pandoc.Error
import Text.Pandoc.Logging
+import Text.Pandoc.MIME (MimeType)
+import Text.Pandoc.Options (WriterOptions (..))
+import Text.Pandoc.Shared (renderTags', trim)
+import Text.Pandoc.UTF8 (toString)
+import Text.Parsec (ParsecT, runParserT)
+import qualified Text.Parsec as P
isOk :: Char -> Bool
isOk c = isAscii c && isAlphaNum c
diff --git a/src/Text/Pandoc/Slides.hs b/src/Text/Pandoc/Slides.hs
index e19dba3e2..b53e0eb6d 100644
--- a/src/Text/Pandoc/Slides.hs
+++ b/src/Text/Pandoc/Slides.hs
@@ -40,9 +40,9 @@ getSlideLevel = go 6
| otherwise = go least (x:xs)
go least (_ : xs) = go least xs
go least [] = least
- nonHOrHR (Header{}) = False
+ 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 705ac54c9..4ae2e80d7 100644
--- a/src/Text/Pandoc/Templates.hs
+++ b/src/Text/Pandoc/Templates.hs
@@ -1,5 +1,7 @@
-{-# LANGUAGE TypeSynonymInstances, FlexibleInstances,
- OverloadedStrings, GeneralizedNewtypeDeriving #-}
+{-# LANGUAGE FlexibleInstances #-}
+{-# LANGUAGE GeneralizedNewtypeDeriving #-}
+{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE TypeSynonymInstances #-}
{-
Copyright (C) 2009-2016 John MacFarlane <jgm@berkeley.edu>
@@ -39,13 +41,12 @@ module Text.Pandoc.Templates ( renderTemplate
, Template
, getDefaultTemplate ) where
-import Text.DocTemplates (Template, TemplateTarget, compileTemplate,
- renderTemplate, applyTemplate,
- varListToJSON)
-import Data.Aeson (ToJSON(..))
+import qualified Control.Exception.Extensible as E (IOException, try)
+import Data.Aeson (ToJSON (..))
import qualified Data.Text as T
-import System.FilePath ((</>), (<.>))
-import qualified Control.Exception.Extensible as E (try, IOException)
+import System.FilePath ((<.>), (</>))
+import Text.DocTemplates (Template, TemplateTarget, applyTemplate,
+ compileTemplate, renderTemplate, varListToJSON)
import Text.Pandoc.Shared (readDataFileUTF8)
-- | Get default template for the specified writer.
diff --git a/src/Text/Pandoc/UTF8.hs b/src/Text/Pandoc/UTF8.hs
index 62a662029..d88a44948 100644
--- a/src/Text/Pandoc/UTF8.hs
+++ b/src/Text/Pandoc/UTF8.hs
@@ -45,16 +45,16 @@ module Text.Pandoc.UTF8 ( readFile
where
-import System.IO hiding (readFile, writeFile, getContents,
- putStr, putStrLn, hPutStr, hPutStrLn, hGetContents)
-import Prelude hiding (readFile, writeFile, getContents, putStr, putStrLn)
-import qualified System.IO as IO
import qualified Data.ByteString.Char8 as B
import qualified Data.ByteString.Lazy as BL
-import qualified Data.Text.Encoding as T
import qualified Data.Text as T
+import qualified Data.Text.Encoding as T
import qualified Data.Text.Lazy as TL
import qualified Data.Text.Lazy.Encoding as TL
+import Prelude hiding (getContents, putStr, putStrLn, readFile, writeFile)
+import System.IO hiding (getContents, hGetContents, hPutStr, hPutStrLn, putStr,
+ putStrLn, readFile, writeFile)
+import qualified System.IO as IO
readFile :: FilePath -> IO String
readFile f = do
@@ -90,13 +90,13 @@ hGetContents = fmap toString . B.hGetContents
-- no-break space, so if the string begins with this we strip it off.
dropBOM :: String -> String
dropBOM ('\xFEFF':xs) = xs
-dropBOM xs = xs
+dropBOM xs = xs
filterCRs :: String -> String
filterCRs ('\r':'\n':xs) = '\n': filterCRs xs
-filterCRs ('\r':xs) = '\n' : filterCRs xs
-filterCRs (x:xs) = x : filterCRs xs
-filterCRs [] = []
+filterCRs ('\r':xs) = '\n' : filterCRs xs
+filterCRs (x:xs) = x : filterCRs xs
+filterCRs [] = []
-- | Convert UTF8-encoded ByteString to String, also
-- removing '\r' characters.
diff --git a/src/Text/Pandoc/UUID.hs b/src/Text/Pandoc/UUID.hs
index 8de102742..9446c4692 100644
--- a/src/Text/Pandoc/UUID.hs
+++ b/src/Text/Pandoc/UUID.hs
@@ -31,10 +31,10 @@ in RFC4122. See http://tools.ietf.org/html/rfc4122
module Text.Pandoc.UUID ( UUID(..), getRandomUUID, getUUID ) where
-import Text.Printf ( printf )
-import System.Random ( RandomGen, randoms, getStdGen )
+import Data.Bits (clearBit, setBit)
import Data.Word
-import Data.Bits ( setBit, clearBit )
+import System.Random (RandomGen, getStdGen, randoms)
+import Text.Printf (printf)
data UUID = UUID Word8 Word8 Word8 Word8 Word8 Word8 Word8 Word8
Word8 Word8 Word8 Word8 Word8 Word8 Word8 Word8
diff --git a/src/Text/Pandoc/Writers/AsciiDoc.hs b/src/Text/Pandoc/Writers/AsciiDoc.hs
index 594a12222..20fa7c209 100644
--- a/src/Text/Pandoc/Writers/AsciiDoc.hs
+++ b/src/Text/Pandoc/Writers/AsciiDoc.hs
@@ -37,25 +37,25 @@ that it has omitted the construct.
AsciiDoc: <http://www.methods.co.nz/asciidoc/>
-}
module Text.Pandoc.Writers.AsciiDoc (writeAsciiDoc) where
-import Text.Pandoc.Definition
-import Text.Pandoc.Templates (renderTemplate')
-import Text.Pandoc.Shared
-import Text.Pandoc.Writers.Shared
-import Text.Pandoc.Options
-import Text.Pandoc.Parsing hiding (blankline, space)
-import Data.Maybe (fromMaybe)
-import Data.List ( stripPrefix, intersperse, intercalate )
-import Text.Pandoc.Pretty
-import Text.Pandoc.ImageSize
import Control.Monad.State
+import Data.Aeson (Result (..), Value (String), fromJSON, toJSON)
+import Data.Char (isPunctuation, isSpace)
+import Data.List (intercalate, intersperse, stripPrefix)
import qualified Data.Map as M
-import Data.Aeson (Value(String), fromJSON, toJSON, Result(..))
+import Data.Maybe (fromMaybe)
import qualified Data.Text as T
-import Data.Char (isSpace, isPunctuation)
import Text.Pandoc.Class (PandocMonad, report)
+import Text.Pandoc.Definition
+import Text.Pandoc.ImageSize
import Text.Pandoc.Logging
+import Text.Pandoc.Options
+import Text.Pandoc.Parsing hiding (blankline, space)
+import Text.Pandoc.Pretty
+import Text.Pandoc.Shared
+import Text.Pandoc.Templates (renderTemplate')
+import Text.Pandoc.Writers.Shared
-data WriterState = WriterState { defListMarker :: String
+data WriterState = WriterState { defListMarker :: String
, orderedListLevel :: Int
, bulletListLevel :: Int
, intraword :: Bool
@@ -122,8 +122,8 @@ olMarker = do (start, style', delim) <- anyOrderedListMarker
beginsWithOrderedListMarker :: String -> Bool
beginsWithOrderedListMarker str =
case runParser olMarker defaultParserState "para start" (take 10 str) of
- Left _ -> False
- Right _ -> True
+ Left _ -> False
+ Right _ -> True
-- | Convert Pandoc block element to asciidoc.
blockToAsciiDoc :: PandocMonad m
@@ -169,11 +169,11 @@ blockToAsciiDoc opts (Header level (ident,_,_) inlines) = do
then
identifier $$ contents $$
(case level of
- 1 -> text $ replicate len '-'
- 2 -> text $ replicate len '~'
- 3 -> text $ replicate len '^'
- 4 -> text $ replicate len '+'
- _ -> empty) <> blankline
+ 1 -> text $ replicate len '-'
+ 2 -> text $ replicate len '~'
+ 3 -> text $ replicate len '^'
+ 4 -> text $ replicate len '+'
+ _ -> empty) <> blankline
else
identifier $$ text (replicate level '=') <> space <> contents <> blankline)
blockToAsciiDoc _ (CodeBlock (_,classes,_) str) = return $ (flush $
@@ -428,9 +428,9 @@ inlineToAsciiDoc _ LineBreak = return $ " +" <> cr
inlineToAsciiDoc _ Space = return space
inlineToAsciiDoc opts SoftBreak =
case writerWrapText opts of
- WrapAuto -> return space
+ WrapAuto -> return space
WrapPreserve -> return cr
- WrapNone -> return space
+ WrapNone -> return space
inlineToAsciiDoc opts (Cite _ lst) = inlineListToAsciiDoc opts lst
inlineToAsciiDoc opts (Link _ txt (src, _tit)) = do
-- relative: link:downloads/foo.zip[download foo.zip]
@@ -444,7 +444,7 @@ inlineToAsciiDoc opts (Link _ txt (src, _tit)) = do
let srcSuffix = fromMaybe src (stripPrefix "mailto:" src)
let useAuto = case txt of
[Str s] | escapeURI s == srcSuffix -> True
- _ -> False
+ _ -> False
return $ if useAuto
then text srcSuffix
else prefix <> text src <> "[" <> linktext <> "]"
diff --git a/src/Text/Pandoc/Writers/CommonMark.hs b/src/Text/Pandoc/Writers/CommonMark.hs
index b83f6785d..2c844d3a0 100644
--- a/src/Text/Pandoc/Writers/CommonMark.hs
+++ b/src/Text/Pandoc/Writers/CommonMark.hs
@@ -31,18 +31,18 @@ CommonMark: <http://commonmark.org>
-}
module Text.Pandoc.Writers.CommonMark (writeCommonMark) where
-import Text.Pandoc.Writers.HTML (writeHtml5String)
+import CMark
+import Control.Monad.State (State, get, modify, runState)
+import Data.Foldable (foldrM)
+import qualified Data.Text as T
+import Text.Pandoc.Class (PandocMonad)
import Text.Pandoc.Definition
+import Text.Pandoc.Options
import Text.Pandoc.Shared (isTightList, linesToPara)
import Text.Pandoc.Templates (renderTemplate')
-import Text.Pandoc.Writers.Shared
-import Text.Pandoc.Options
-import CMark
-import qualified Data.Text as T
-import Control.Monad.State (runState, State, modify, get)
import Text.Pandoc.Walk (walkM)
-import Text.Pandoc.Class (PandocMonad)
-import Data.Foldable (foldrM)
+import Text.Pandoc.Writers.HTML (writeHtml5String)
+import Text.Pandoc.Writers.Shared
-- | Convert Pandoc to CommonMark.
writeCommonMark :: PandocMonad m => WriterOptions -> Pandoc -> m String
diff --git a/src/Text/Pandoc/Writers/ConTeXt.hs b/src/Text/Pandoc/Writers/ConTeXt.hs
index ea178db92..353901fa5 100644
--- a/src/Text/Pandoc/Writers/ConTeXt.hs
+++ b/src/Text/Pandoc/Writers/ConTeXt.hs
@@ -29,21 +29,21 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
Conversion of 'Pandoc' format into ConTeXt.
-}
module Text.Pandoc.Writers.ConTeXt ( writeConTeXt ) where
+import Control.Monad.State
+import Data.Char (ord)
+import Data.List (intercalate, intersperse)
+import Data.Maybe (catMaybes)
+import Network.URI (isURI, unEscapeString)
+import Text.Pandoc.Class (PandocMonad)
import Text.Pandoc.Definition
-import Text.Pandoc.Shared
-import Text.Pandoc.Writers.Shared
+import Text.Pandoc.ImageSize
import Text.Pandoc.Options
-import Text.Pandoc.Walk (query)
-import Text.Printf ( printf )
-import Data.List ( intercalate, intersperse )
-import Data.Char ( ord )
-import Data.Maybe ( catMaybes )
-import Control.Monad.State
import Text.Pandoc.Pretty
-import Text.Pandoc.ImageSize
-import Text.Pandoc.Templates ( renderTemplate' )
-import Network.URI ( isURI, unEscapeString )
-import Text.Pandoc.Class (PandocMonad)
+import Text.Pandoc.Shared
+import Text.Pandoc.Templates (renderTemplate')
+import Text.Pandoc.Walk (query)
+import Text.Pandoc.Writers.Shared
+import Text.Printf (printf)
data WriterState =
WriterState { stNextRef :: Int -- number of next URL reference
@@ -113,22 +113,22 @@ escapeCharForConTeXt :: WriterOptions -> Char -> String
escapeCharForConTeXt opts ch =
let ligatures = isEnabled Ext_smart opts in
case ch of
- '{' -> "\\{"
- '}' -> "\\}"
- '\\' -> "\\letterbackslash{}"
- '$' -> "\\$"
- '|' -> "\\letterbar{}"
- '%' -> "\\letterpercent{}"
- '~' -> "\\lettertilde{}"
- '#' -> "\\#"
- '[' -> "{[}"
- ']' -> "{]}"
- '\160' -> "~"
+ '{' -> "\\{"
+ '}' -> "\\}"
+ '\\' -> "\\letterbackslash{}"
+ '$' -> "\\$"
+ '|' -> "\\letterbar{}"
+ '%' -> "\\letterpercent{}"
+ '~' -> "\\lettertilde{}"
+ '#' -> "\\#"
+ '[' -> "{[}"
+ ']' -> "{]}"
+ '\160' -> "~"
'\x2014' | ligatures -> "---"
'\x2013' | ligatures -> "--"
'\x2019' | ligatures -> "'"
'\x2026' -> "\\ldots{}"
- x -> [x]
+ x -> [x]
-- | Escape string for ConTeXt
stringToConTeXt :: WriterOptions -> String -> String
@@ -293,9 +293,9 @@ inlineListToConTeXt lst = liftM hcat $ mapM inlineToConTeXt $ addStruts lst
addStruts xs
addStruts (x:xs) = x : addStruts xs
addStruts [] = []
- isSpacey Space = True
+ isSpacey Space = True
isSpacey (Str ('\160':_)) = True
- isSpacey _ = False
+ isSpacey _ = False
-- | Convert inline element to ConTeXt
inlineToConTeXt :: Inline -- ^ Inline to convert
@@ -398,7 +398,7 @@ inlineToConTeXt (Image attr@(_,cls,_) _ (src, _)) = do
inlineToConTeXt (Note contents) = do
contents' <- blockListToConTeXt contents
let codeBlock x@(CodeBlock _ _) = [x]
- codeBlock _ = []
+ codeBlock _ = []
let codeBlocks = query codeBlock contents
return $ if null codeBlocks
then text "\\footnote{" <> nest 2 contents' <> char '}'
diff --git a/src/Text/Pandoc/Writers/Custom.hs b/src/Text/Pandoc/Writers/Custom.hs
index cf641dcd6..d7374b68b 100644
--- a/src/Text/Pandoc/Writers/Custom.hs
+++ b/src/Text/Pandoc/Writers/Custom.hs
@@ -1,6 +1,9 @@
{-# OPTIONS_GHC -fno-warn-orphans #-}
-{-# LANGUAGE FlexibleInstances, OverloadedStrings,
- ScopedTypeVariables, DeriveDataTypeable, CPP #-}
+{-# LANGUAGE CPP #-}
+{-# LANGUAGE DeriveDataTypeable #-}
+{-# LANGUAGE FlexibleInstances #-}
+{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE ScopedTypeVariables #-}
#if MIN_VERSION_base(4,8,0)
#else
{-# LANGUAGE OverlappingInstances #-}
@@ -35,20 +38,20 @@ Conversion of 'Pandoc' documents to custom markup using
a lua writer.
-}
module Text.Pandoc.Writers.Custom ( writeCustom ) where
-import Text.Pandoc.Definition
-import Text.Pandoc.Options
-import Data.List ( intersperse )
-import Data.Char ( toLower )
+import Control.Exception
+import Control.Monad (when)
+import Data.Char (toLower)
+import Data.List (intersperse)
+import qualified Data.Map as M
import Data.Typeable
+import GHC.IO.Encoding (getForeignEncoding, setForeignEncoding, utf8)
import Scripting.Lua (LuaState, StackValue, callfunc)
-import Text.Pandoc.Writers.Shared
import qualified Scripting.Lua as Lua
-import qualified Text.Pandoc.UTF8 as UTF8
-import Control.Monad (when)
-import Control.Exception
-import qualified Data.Map as M
+import Text.Pandoc.Definition
+import Text.Pandoc.Options
import Text.Pandoc.Templates
-import GHC.IO.Encoding (getForeignEncoding,setForeignEncoding, utf8)
+import qualified Text.Pandoc.UTF8 as UTF8
+import Text.Pandoc.Writers.Shared
attrToMap :: Attr -> M.Map String String
attrToMap (id',classes,keyvals) = M.fromList
@@ -142,19 +145,19 @@ instance StackValue [Block] where
valuetype _ = Lua.TSTRING
instance StackValue MetaValue where
- push l (MetaMap m) = Lua.push l m
- push l (MetaList xs) = Lua.push l xs
- push l (MetaBool x) = Lua.push l x
- push l (MetaString s) = Lua.push l s
+ push l (MetaMap m) = Lua.push l m
+ push l (MetaList xs) = Lua.push l xs
+ push l (MetaBool x) = Lua.push l x
+ push l (MetaString s) = Lua.push l s
push l (MetaInlines ils) = Lua.push l ils
- push l (MetaBlocks bs) = Lua.push l bs
+ push l (MetaBlocks bs) = Lua.push l bs
peek _ _ = undefined
- valuetype (MetaMap _) = Lua.TTABLE
- valuetype (MetaList _) = Lua.TTABLE
- valuetype (MetaBool _) = Lua.TBOOLEAN
- valuetype (MetaString _) = Lua.TSTRING
+ valuetype (MetaMap _) = Lua.TTABLE
+ valuetype (MetaList _) = Lua.TTABLE
+ valuetype (MetaBool _) = Lua.TBOOLEAN
+ valuetype (MetaString _) = Lua.TSTRING
valuetype (MetaInlines _) = Lua.TSTRING
- valuetype (MetaBlocks _) = Lua.TSTRING
+ valuetype (MetaBlocks _) = Lua.TSTRING
instance StackValue Citation where
push lua cit = do
diff --git a/src/Text/Pandoc/Writers/Docbook.hs b/src/Text/Pandoc/Writers/Docbook.hs
index 597851f65..dce2cbd3e 100644
--- a/src/Text/Pandoc/Writers/Docbook.hs
+++ b/src/Text/Pandoc/Writers/Docbook.hs
@@ -1,4 +1,5 @@
-{-# LANGUAGE OverloadedStrings, PatternGuards #-}
+{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE PatternGuards #-}
{-
Copyright (C) 2006-2015 John MacFarlane <jgm@berkeley.edu>
@@ -29,27 +30,27 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
Conversion of 'Pandoc' documents to Docbook XML.
-}
module Text.Pandoc.Writers.Docbook ( writeDocbook4, writeDocbook5 ) where
+import Control.Monad.Reader
+import Data.Char (toLower)
+import Data.Generics (everywhere, mkT)
+import Data.List (intercalate, isPrefixOf, isSuffixOf, stripPrefix)
+import Data.Monoid (Any (..))
+import qualified Text.Pandoc.Builder as B
+import Text.Pandoc.Class (PandocMonad, report)
import Text.Pandoc.Definition
-import Text.Pandoc.XML
-import Text.Pandoc.Shared
-import Text.Pandoc.Walk
-import Text.Pandoc.Writers.Shared
+import Text.Pandoc.Highlighting (languages, languagesByExtension)
+import Text.Pandoc.ImageSize
+import Text.Pandoc.Logging
import Text.Pandoc.Options
+import Text.Pandoc.Pretty
+import Text.Pandoc.Shared
import Text.Pandoc.Templates (renderTemplate')
+import Text.Pandoc.Walk
import Text.Pandoc.Writers.Math
-import Data.List ( stripPrefix, isPrefixOf, intercalate, isSuffixOf )
-import Data.Char ( toLower )
-import Data.Monoid ( Any(..) )
-import Text.Pandoc.Highlighting ( languages, languagesByExtension )
-import Text.Pandoc.Pretty
-import Text.Pandoc.ImageSize
-import qualified Text.Pandoc.Builder as B
+import Text.Pandoc.Writers.Shared
+import Text.Pandoc.XML
import Text.TeXMath
import qualified Text.XML.Light as Xml
-import Data.Generics (everywhere, mkT)
-import Text.Pandoc.Class (PandocMonad, report)
-import Text.Pandoc.Logging
-import Control.Monad.Reader
data DocBookVersion = DocBook4 | DocBook5
deriving (Eq, Show)
@@ -122,8 +123,8 @@ writeDocbook opts (Pandoc meta blocks) = do
_ -> False)
$ metadata
return $ case writerTemplate opts of
- Nothing -> main
- Just tpl -> renderTemplate' tpl context
+ Nothing -> main
+ Just tpl -> renderTemplate' tpl context
-- | Convert an Element to Docbook.
elementToDocbook :: PandocMonad m => WriterOptions -> Int -> Element -> DB m Doc
@@ -311,16 +312,16 @@ hasLineBreaks = getAny . query isLineBreak . walk removeNote
where
removeNote :: Inline -> Inline
removeNote (Note _) = Str ""
- removeNote x = x
+ removeNote x = x
isLineBreak :: Inline -> Any
isLineBreak LineBreak = Any True
- isLineBreak _ = Any False
+ isLineBreak _ = Any False
alignmentToString :: Alignment -> [Char]
alignmentToString alignment = case alignment of
- AlignLeft -> "left"
- AlignRight -> "right"
- AlignCenter -> "center"
+ AlignLeft -> "left"
+ AlignRight -> "right"
+ AlignCenter -> "center"
AlignDefault -> "left"
tableRowToDocbook :: PandocMonad m
diff --git a/src/Text/Pandoc/Writers/Docx.hs b/src/Text/Pandoc/Writers/Docx.hs
index 26b1cfdf6..c182d42a3 100644
--- a/src/Text/Pandoc/Writers/Docx.hs
+++ b/src/Text/Pandoc/Writers/Docx.hs
@@ -1,5 +1,8 @@
-{-# LANGUAGE ScopedTypeVariables, PatternGuards, ViewPatterns, DeriveFunctor,
- ScopedTypeVariables, RankNTypes #-}
+{-# LANGUAGE DeriveFunctor #-}
+{-# LANGUAGE PatternGuards #-}
+{-# LANGUAGE RankNTypes #-}
+{-# LANGUAGE ScopedTypeVariables #-}
+{-# LANGUAGE ViewPatterns #-}
{-
Copyright (C) 2012-2015 John MacFarlane <jgm@berkeley.edu>
@@ -30,45 +33,45 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
Conversion of 'Pandoc' documents to docx.
-}
module Text.Pandoc.Writers.Docx ( writeDocx ) where
-import Data.List ( intercalate, isPrefixOf, isSuffixOf )
+import Codec.Archive.Zip
+import Control.Applicative ((<|>))
+import Control.Monad.Except (catchError)
+import Control.Monad.Reader
+import Control.Monad.State
import qualified Data.ByteString as B
import qualified Data.ByteString.Lazy as BL
import qualified Data.ByteString.Lazy.Char8 as BL8
+import Data.Char (isSpace, ord, toLower)
+import Data.List (intercalate, isPrefixOf, isSuffixOf)
import qualified Data.Map as M
+import Data.Maybe (fromMaybe, isNothing, mapMaybe, maybeToList)
+import Data.Monoid ((<>))
import qualified Data.Set as Set
-import qualified Text.Pandoc.UTF8 as UTF8
-import Codec.Archive.Zip
+import qualified Data.Text as T
import Data.Time.Clock.POSIX
+import Skylighting
+import System.Random (randomR)
+import Text.Pandoc.Class (PandocMonad, report)
+import qualified Text.Pandoc.Class as P
import Text.Pandoc.Compat.Time
import Text.Pandoc.Definition
+import Text.Pandoc.Error
import Text.Pandoc.Generic
+import Text.Pandoc.Highlighting (highlight)
import Text.Pandoc.ImageSize
-import Text.Pandoc.Shared hiding (Element)
-import Text.Pandoc.Writers.Shared (fixDisplayMath)
+import Text.Pandoc.Logging
+import Text.Pandoc.MIME (MimeType, extensionFromMimeType, getMimeType,
+ getMimeTypeDef)
import Text.Pandoc.Options
-import Text.Pandoc.Writers.Math
-import Text.Pandoc.Highlighting ( highlight )
-import Text.Pandoc.Walk
-import Text.XML.Light as XML
-import Text.TeXMath
import Text.Pandoc.Readers.Docx.StyleMap
-import Control.Monad.Reader
-import Control.Monad.State
-import Skylighting
-import Control.Monad.Except (catchError)
-import System.Random (randomR)
+import Text.Pandoc.Shared hiding (Element)
+import qualified Text.Pandoc.UTF8 as UTF8
+import Text.Pandoc.Walk
+import Text.Pandoc.Writers.Math
+import Text.Pandoc.Writers.Shared (fixDisplayMath)
import Text.Printf (printf)
-import Data.Monoid ((<>))
-import qualified Data.Text as T
-import Text.Pandoc.MIME (MimeType, getMimeType, getMimeTypeDef,
- extensionFromMimeType)
-import Control.Applicative ((<|>))
-import Data.Maybe (fromMaybe, mapMaybe, maybeToList, isNothing)
-import Data.Char (ord, isSpace, toLower)
-import Text.Pandoc.Class (PandocMonad, report)
-import qualified Text.Pandoc.Class as P
-import Text.Pandoc.Logging
-import Text.Pandoc.Error
+import Text.TeXMath
+import Text.XML.Light as XML
data ListMarker = NoMarker
| BulletMarker
@@ -81,28 +84,28 @@ listMarkerToId BulletMarker = "991"
listMarkerToId (NumberMarker sty delim n) =
'9' : '9' : styNum : delimNum : show n
where styNum = case sty of
- DefaultStyle -> '2'
- Example -> '3'
- Decimal -> '4'
- LowerRoman -> '5'
- UpperRoman -> '6'
- LowerAlpha -> '7'
- UpperAlpha -> '8'
+ DefaultStyle -> '2'
+ Example -> '3'
+ Decimal -> '4'
+ LowerRoman -> '5'
+ UpperRoman -> '6'
+ LowerAlpha -> '7'
+ UpperAlpha -> '8'
delimNum = case delim of
- DefaultDelim -> '0'
- Period -> '1'
- OneParen -> '2'
- TwoParens -> '3'
+ DefaultDelim -> '0'
+ Period -> '1'
+ OneParen -> '2'
+ TwoParens -> '3'
data WriterEnv = WriterEnv{ envTextProperties :: [Element]
, envParaProperties :: [Element]
- , envRTL :: Bool
- , envListLevel :: Int
- , envListNumId :: Int
- , envInDel :: Bool
- , envChangesAuthor :: String
- , envChangesDate :: String
- , envPrintWidth :: Integer
+ , envRTL :: Bool
+ , envListLevel :: Int
+ , envListNumId :: Int
+ , envInDel :: Bool
+ , envChangesAuthor :: String
+ , envChangesDate :: String
+ , envPrintWidth :: Integer
}
defaultWriterEnv :: WriterEnv
@@ -209,11 +212,11 @@ isValidChar (ord -> c)
| otherwise = False
metaValueToInlines :: MetaValue -> [Inline]
-metaValueToInlines (MetaString s) = [Str s]
+metaValueToInlines (MetaString s) = [Str s]
metaValueToInlines (MetaInlines ils) = ils
-metaValueToInlines (MetaBlocks bs) = query return bs
-metaValueToInlines (MetaBool b) = [Str $ show b]
-metaValueToInlines _ = []
+metaValueToInlines (MetaBlocks bs) = query return bs
+metaValueToInlines (MetaBool b) = [Str $ show b]
+metaValueToInlines _ = []
@@ -452,8 +455,8 @@ writeDocx opts doc@(Pandoc meta _) = do
let newstyles = map newParaPropToOpenXml newDynamicParaProps ++
map newTextPropToOpenXml newDynamicTextProps ++
(case writerHighlightStyle opts of
- Nothing -> []
- Just sty -> (styleToOpenXml styleMaps sty))
+ Nothing -> []
+ Just sty -> (styleToOpenXml styleMaps sty))
let styledoc' = styledoc{ elContent = elContent styledoc ++
map Elem newstyles }
let styleEntry = toEntry stylepath epochtime $ renderXml styledoc'
@@ -675,21 +678,21 @@ mkLvl marker lvl =
bulletFor 4 = "\x2022"
bulletFor 5 = "\x2013"
bulletFor _ = "\x2022"
- styleFor UpperAlpha _ = "upperLetter"
- styleFor LowerAlpha _ = "lowerLetter"
- styleFor UpperRoman _ = "upperRoman"
- styleFor LowerRoman _ = "lowerRoman"
- styleFor Decimal _ = "decimal"
+ styleFor UpperAlpha _ = "upperLetter"
+ styleFor LowerAlpha _ = "lowerLetter"
+ styleFor UpperRoman _ = "upperRoman"
+ styleFor LowerRoman _ = "lowerRoman"
+ styleFor Decimal _ = "decimal"
styleFor DefaultStyle 1 = "decimal"
styleFor DefaultStyle 2 = "lowerLetter"
styleFor DefaultStyle 3 = "lowerRoman"
styleFor DefaultStyle 4 = "decimal"
styleFor DefaultStyle 5 = "lowerLetter"
styleFor DefaultStyle 6 = "lowerRoman"
- styleFor _ _ = "decimal"
- patternFor OneParen s = s ++ ")"
+ styleFor _ _ = "decimal"
+ patternFor OneParen s = s ++ ")"
patternFor TwoParens s = "(" ++ s ++ ")"
- patternFor _ s = s ++ "."
+ patternFor _ s = s ++ "."
getNumId :: (PandocMonad m) => WS m Int
getNumId = (((baseListId - 1) +) . length) `fmap` gets stLists
@@ -733,14 +736,14 @@ writeOpenXML opts (Pandoc meta blocks) = do
let auths = docAuthors meta
let dat = docDate meta
let abstract' = case lookupMeta "abstract" meta of
- Just (MetaBlocks bs) -> bs
+ Just (MetaBlocks bs) -> bs
Just (MetaInlines ils) -> [Plain ils]
- _ -> []
+ _ -> []
let subtitle' = case lookupMeta "subtitle" meta of
Just (MetaBlocks [Plain xs]) -> xs
Just (MetaBlocks [Para xs]) -> xs
Just (MetaInlines xs) -> xs
- _ -> []
+ _ -> []
title <- withParaPropM (pStyleM "Title") $ blocksToOpenXML opts [Para tit | not (null tit)]
subtitle <- withParaPropM (pStyleM "Subtitle") $ blocksToOpenXML opts [Para subtitle' | not (null subtitle')]
authors <- withParaProp (pCustomStyle "Author") $ blocksToOpenXML opts $
@@ -750,8 +753,8 @@ writeOpenXML opts (Pandoc meta blocks) = do
then return []
else withParaProp (pCustomStyle "Abstract") $ blocksToOpenXML opts abstract'
let convertSpace (Str x : Space : Str y : xs) = Str (x ++ " " ++ y) : xs
- convertSpace (Str x : Str y : xs) = Str (x ++ y) : xs
- convertSpace xs = xs
+ convertSpace (Str x : Str y : xs) = Str (x ++ y) : xs
+ convertSpace xs = xs
let blocks' = bottomUp convertSpace blocks
doc' <- (setFirstPara >> blocksToOpenXML opts blocks')
notes' <- reverse `fmap` gets stFootnotes
@@ -981,9 +984,9 @@ listItemToOpenXML opts numid (first:rest) = do
alignmentToString :: Alignment -> [Char]
alignmentToString alignment = case alignment of
- AlignLeft -> "left"
- AlignRight -> "right"
- AlignCenter -> "center"
+ AlignLeft -> "left"
+ AlignRight -> "right"
+ AlignCenter -> "center"
AlignDefault -> "left"
-- | Convert a list of inline elements to OpenXML.
@@ -1063,7 +1066,7 @@ inlineToOpenXML' opts (Span (ident,classes,kvs) ils) = do
let dirmod = case lookup "dir" kvs of
Just "rtl" -> local (\env -> env { envRTL = True })
Just "ltr" -> local (\env -> env { envRTL = False })
- _ -> id
+ _ -> id
let off x = withTextProp (mknode x [("w:val","0")] ())
let pmod = (if "csl-no-emph" `elem` classes then off "w:i" else id) .
(if "csl-no-strong" `elem` classes then off "w:b" else id) .
@@ -1154,8 +1157,8 @@ inlineToOpenXML' opts (Code attrs str) = do
, mknode "w:t" [("xml:space","preserve")] (T.unpack tok) ]
withTextProp (rCustomStyle "VerbatimChar")
$ case writerHighlightStyle opts >> highlight formatOpenXML attrs str of
- Just h -> return h
- Nothing -> unhighlighted
+ Just h -> return h
+ Nothing -> unhighlighted
inlineToOpenXML' opts (Note bs) = do
notes <- gets stFootnotes
notenum <- (lift . lift) getUniqueId
diff --git a/src/Text/Pandoc/Writers/DokuWiki.hs b/src/Text/Pandoc/Writers/DokuWiki.hs
index 9fd6c699c..215d0b2fb 100644
--- a/src/Text/Pandoc/Writers/DokuWiki.hs
+++ b/src/Text/Pandoc/Writers/DokuWiki.hs
@@ -39,31 +39,28 @@ DokuWiki: <https://www.dokuwiki.org/dokuwiki>
-}
module Text.Pandoc.Writers.DokuWiki ( writeDokuWiki ) where
+import Control.Monad (zipWithM)
+import Control.Monad.Reader (ReaderT, ask, local, runReaderT)
+import Control.Monad.State (State, evalState, gets, modify)
+import Data.Default (Default (..))
+import Data.List (intercalate, intersect, isPrefixOf, transpose)
+import Network.URI (isURI)
+import Text.Pandoc.Class (PandocMonad)
import Text.Pandoc.Definition
-import Text.Pandoc.Options ( WriterOptions(
- writerTableOfContents
- , writerTemplate
- , writerWrapText), WrapOption(..) )
-import Text.Pandoc.Shared ( escapeURI, linesToPara, removeFormatting
- , camelCaseToHyphenated, trimr, substitute )
-import Text.Pandoc.Writers.Shared ( defField, metaToJSON )
import Text.Pandoc.ImageSize
-import Text.Pandoc.Templates ( renderTemplate' )
-import Data.List ( intersect, intercalate, isPrefixOf, transpose )
-import Data.Default (Default(..))
-import Network.URI ( isURI )
-import Control.Monad ( zipWithM )
-import Control.Monad.State ( modify, State, gets, evalState )
-import Control.Monad.Reader ( ReaderT, runReaderT, ask, local )
-import Text.Pandoc.Class (PandocMonad)
+import Text.Pandoc.Options (WrapOption (..), WriterOptions (writerTableOfContents, writerTemplate, writerWrapText))
+import Text.Pandoc.Shared (camelCaseToHyphenated, escapeURI, linesToPara,
+ removeFormatting, substitute, trimr)
+import Text.Pandoc.Templates (renderTemplate')
+import Text.Pandoc.Writers.Shared (defField, metaToJSON)
data WriterState = WriterState {
stNotes :: Bool -- True if there are notes
}
data WriterEnvironment = WriterEnvironment {
- stIndent :: String -- Indent after the marker at the beginning of list items
- , stUseTags :: Bool -- True if we should use HTML tags because we're in a complex list
+ stIndent :: String -- Indent after the marker at the beginning of list items
+ , stUseTags :: Bool -- True if we should use HTML tags because we're in a complex list
, stBackSlashLB :: Bool -- True if we should produce formatted strings with newlines (as in a table cell)
}
@@ -178,7 +175,7 @@ blockToDokuWiki _ (CodeBlock (_,classes,_) str) = do
"visualfoxpro", "winbatch", "xml", "xpp", "z80"]
return $ "<code" ++
(case at of
- [] -> ">\n"
+ [] -> ">\n"
(x:_) -> " " ++ x ++ ">\n") ++ str ++ "\n</code>"
blockToDokuWiki opts (BlockQuote blocks) = do
@@ -338,18 +335,18 @@ isSimpleListItem :: [Block] -> Bool
isSimpleListItem [] = True
isSimpleListItem [x] =
case x of
- Plain _ -> True
- Para _ -> True
- BulletList _ -> isSimpleList x
- OrderedList _ _ -> isSimpleList x
- DefinitionList _ -> isSimpleList x
- _ -> False
+ Plain _ -> True
+ Para _ -> True
+ BulletList _ -> isSimpleList x
+ OrderedList _ _ -> isSimpleList x
+ DefinitionList _ -> isSimpleList x
+ _ -> False
isSimpleListItem [x, y] | isPlainOrPara x =
case y of
- BulletList _ -> isSimpleList y
- OrderedList _ _ -> isSimpleList y
- DefinitionList _ -> isSimpleList y
- _ -> False
+ BulletList _ -> isSimpleList y
+ OrderedList _ _ -> isSimpleList y
+ DefinitionList _ -> isSimpleList y
+ _ -> False
isSimpleListItem _ = False
isPlainOrPara :: Block -> Bool
@@ -369,7 +366,7 @@ backSlashLineBreaks cs = reverse $ g $ reverse $ concatMap f cs
where f '\n' = "\\\\ "
f c = [c]
g (' ' : '\\':'\\': xs) = xs
- g s = s
+ g s = s
-- Auxiliary functions for tables:
@@ -515,7 +512,7 @@ imageDims opts attr = go (toPx $ dimension Width attr) (toPx $ dimension Height
where
toPx = fmap (showInPixel opts) . checkPct
checkPct (Just (Percent _)) = Nothing
- checkPct maybeDim = maybeDim
+ checkPct maybeDim = maybeDim
go (Just w) Nothing = "?" ++ w
go (Just w) (Just h) = "?" ++ w ++ "x" ++ h
go Nothing (Just h) = "?0x" ++ h
diff --git a/src/Text/Pandoc/Writers/EPUB.hs b/src/Text/Pandoc/Writers/EPUB.hs
index 17fa0bf3e..5b64564ce 100644
--- a/src/Text/Pandoc/Writers/EPUB.hs
+++ b/src/Text/Pandoc/Writers/EPUB.hs
@@ -1,4 +1,7 @@
-{-# LANGUAGE PatternGuards, CPP, ScopedTypeVariables, ViewPatterns, FlexibleContexts #-}
+{-# LANGUAGE CPP #-}
+{-# LANGUAGE FlexibleContexts #-}
+{-# LANGUAGE PatternGuards #-}
+{-# LANGUAGE ScopedTypeVariables #-}
{-
Copyright (C) 2010-2015 John MacFarlane <jgm@berkeley.edu>
@@ -29,45 +32,44 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
Conversion of 'Pandoc' documents to EPUB.
-}
module Text.Pandoc.Writers.EPUB ( writeEPUB2, writeEPUB3 ) where
-import Text.Pandoc.Logging
-import qualified Data.Map as M
-import qualified Data.Set as Set
-import Data.Maybe ( fromMaybe, catMaybes )
-import Data.List ( isPrefixOf, isInfixOf, intercalate )
-import Text.Printf (printf)
-import System.FilePath ( takeExtension, takeFileName )
-import Network.HTTP ( urlEncode )
+import Codec.Archive.Zip (Entry, addEntryToArchive, eRelativePath, emptyArchive,
+ fromArchive, fromEntry, toEntry)
+import Control.Monad (mplus, when, zipWithM)
+import Control.Monad.Except (catchError, throwError)
+import Control.Monad.State (State, StateT, evalState, evalStateT, get, gets,
+ lift, modify, put)
import qualified Data.ByteString.Lazy as B
import qualified Data.ByteString.Lazy.Char8 as B8
-import qualified Text.Pandoc.UTF8 as UTF8
-import Codec.Archive.Zip ( emptyArchive, addEntryToArchive, eRelativePath, fromEntry , Entry, toEntry, fromArchive)
-import Text.Pandoc.Compat.Time
-import Text.Pandoc.Shared ( renderTags', safeRead, uniqueIdent, trim
- , normalizeDate, stringify
- , hierarchicalize )
-import qualified Text.Pandoc.Shared as S (Element(..))
+import Data.Char (isAlphaNum, isDigit, toLower)
+import Data.List (intercalate, isInfixOf, isPrefixOf)
+import qualified Data.Map as M
+import Data.Maybe (catMaybes, fromMaybe)
+import qualified Data.Set as Set
+import Network.HTTP (urlEncode)
+import System.FilePath (takeExtension, takeFileName)
+import Text.HTML.TagSoup (Tag (TagOpen), fromAttrib, parseTags)
import Text.Pandoc.Builder (fromList, setMeta)
-import Text.Pandoc.Options ( WriterOptions(..)
- , WrapOption(..)
- , HTMLMathMethod(..)
- , EPUBVersion(..)
- , ObfuscationMethod(NoObfuscation) )
-import Text.Pandoc.Definition
-import Text.Pandoc.Walk (walk, walkM, query)
-import Text.Pandoc.UUID (getUUID)
-import Control.Monad.State (modify, get, gets, State, StateT, put, evalState, evalStateT, lift)
-import Control.Monad (mplus, when, zipWithM)
-import Text.XML.Light ( unode, Element(..), unqual, Attr(..), add_attrs
- , strContent, lookupAttr, Node(..), QName(..), parseXML
- , onlyElems, node, ppElement)
-import Text.Pandoc.Writers.HTML ( writeHtmlStringForEPUB )
-import Data.Char ( toLower, isDigit, isAlphaNum )
-import Text.Pandoc.MIME (MimeType, getMimeType, extensionFromMimeType)
-import Text.HTML.TagSoup (Tag(TagOpen), fromAttrib, parseTags)
-import Control.Monad.Except (throwError, catchError)
-import Text.Pandoc.Error
import Text.Pandoc.Class (PandocMonad, report)
import qualified Text.Pandoc.Class as P
+import Text.Pandoc.Compat.Time
+import Text.Pandoc.Definition
+import Text.Pandoc.Error
+import Text.Pandoc.Logging
+import Text.Pandoc.MIME (MimeType, extensionFromMimeType, getMimeType)
+import Text.Pandoc.Options (EPUBVersion (..), HTMLMathMethod (..),
+ ObfuscationMethod (NoObfuscation), WrapOption (..),
+ WriterOptions (..))
+import Text.Pandoc.Shared (hierarchicalize, normalizeDate, renderTags',
+ safeRead, stringify, trim, uniqueIdent)
+import qualified Text.Pandoc.Shared as S (Element (..))
+import qualified Text.Pandoc.UTF8 as UTF8
+import Text.Pandoc.UUID (getUUID)
+import Text.Pandoc.Walk (query, walk, walkM)
+import Text.Pandoc.Writers.HTML (writeHtmlStringForEPUB)
+import Text.Printf (printf)
+import Text.XML.Light (Attr (..), Element (..), Node (..), QName (..),
+ add_attrs, lookupAttr, node, onlyElems, parseXML,
+ ppElement, strContent, unode, unqual)
-- A Chapter includes a list of blocks and maybe a section
-- number offset. Note, some chapters are unnumbered. The section
@@ -82,46 +84,46 @@ data EPUBState = EPUBState {
type E m = StateT EPUBState m
data EPUBMetadata = EPUBMetadata{
- epubIdentifier :: [Identifier]
- , epubTitle :: [Title]
- , epubDate :: [Date]
- , epubLanguage :: String
- , epubCreator :: [Creator]
- , epubContributor :: [Creator]
- , epubSubject :: [String]
- , epubDescription :: Maybe String
- , epubType :: Maybe String
- , epubFormat :: Maybe String
- , epubPublisher :: Maybe String
- , epubSource :: Maybe String
- , epubRelation :: Maybe String
- , epubCoverage :: Maybe String
- , epubRights :: Maybe String
- , epubCoverImage :: Maybe String
- , epubStylesheets :: [FilePath]
- , epubPageDirection :: Maybe ProgressionDirection
+ epubIdentifier :: [Identifier]
+ , epubTitle :: [Title]
+ , epubDate :: [Date]
+ , epubLanguage :: String
+ , epubCreator :: [Creator]
+ , epubContributor :: [Creator]
+ , epubSubject :: [String]
+ , epubDescription :: Maybe String
+ , epubType :: Maybe String
+ , epubFormat :: Maybe String
+ , epubPublisher :: Maybe String
+ , epubSource :: Maybe String
+ , epubRelation :: Maybe String
+ , epubCoverage :: Maybe String
+ , epubRights :: Maybe String
+ , epubCoverImage :: Maybe String
+ , epubStylesheets :: [FilePath]
+ , epubPageDirection :: Maybe ProgressionDirection
} deriving Show
data Date = Date{
- dateText :: String
- , dateEvent :: Maybe String
+ dateText :: String
+ , dateEvent :: Maybe String
} deriving Show
data Creator = Creator{
- creatorText :: String
- , creatorRole :: Maybe String
- , creatorFileAs :: Maybe String
+ creatorText :: String
+ , creatorRole :: Maybe String
+ , creatorFileAs :: Maybe String
} deriving Show
data Identifier = Identifier{
- identifierText :: String
- , identifierScheme :: Maybe String
+ identifierText :: String
+ , identifierScheme :: Maybe String
} deriving Show
data Title = Title{
- titleText :: String
- , titleFileAs :: Maybe String
- , titleType :: Maybe String
+ titleText :: String
+ , titleFileAs :: Maybe String
+ , titleType :: Maybe String
} deriving Show
data ProgressionDirection = LTR | RTL deriving Show
@@ -229,16 +231,16 @@ addMetadataFromXML e@(Element (QName name _ (Just "dc")) attrs _ _) md
addMetadataFromXML _ md = md
metaValueToString :: MetaValue -> String
-metaValueToString (MetaString s) = s
+metaValueToString (MetaString s) = s
metaValueToString (MetaInlines ils) = stringify ils
-metaValueToString (MetaBlocks bs) = stringify bs
-metaValueToString (MetaBool True) = "true"
-metaValueToString (MetaBool False) = "false"
-metaValueToString _ = ""
+metaValueToString (MetaBlocks bs) = stringify bs
+metaValueToString (MetaBool True) = "true"
+metaValueToString (MetaBool False) = "false"
+metaValueToString _ = ""
metaValueToPaths:: MetaValue -> [FilePath]
metaValueToPaths (MetaList xs) = map metaValueToString xs
-metaValueToPaths x = [metaValueToString x]
+metaValueToPaths x = [metaValueToString x]
getList :: String -> Meta -> (MetaValue -> a) -> [a]
getList s meta handleMetaValue =
@@ -286,8 +288,8 @@ simpleList :: String -> Meta -> [String]
simpleList s meta =
case lookupMeta s meta of
Just (MetaList xs) -> map metaValueToString xs
- Just x -> [metaValueToString x]
- Nothing -> []
+ Just x -> [metaValueToString x]
+ Nothing -> []
metadataFromMeta :: WriterOptions -> Meta -> EPUBMetadata
metadataFromMeta opts meta = EPUBMetadata{
@@ -538,8 +540,8 @@ pandocToEPUB version opts doc@(Pandoc meta _) = do
("href", eRelativePath ent),
("media-type", "application/xhtml+xml")]
++ case props ent of
- [] -> []
- xs -> [("properties", unwords xs)])
+ [] -> []
+ xs -> [("properties", unwords xs)])
$ ()
let chapterRefNode ent = unode "itemref" !
[("idref", toId $ eRelativePath ent)] $ ()
@@ -554,7 +556,7 @@ pandocToEPUB version opts doc@(Pandoc meta _) = do
("media-type", fromMaybe "" $ getMimeType $ eRelativePath ent)] $ ()
let plainTitle = case docTitle' meta of
[] -> case epubTitle metadata of
- [] -> "UNTITLED"
+ [] -> "UNTITLED"
(x:_) -> titleText x
x -> stringify x
@@ -635,7 +637,7 @@ pandocToEPUB version opts doc@(Pandoc meta _) = do
Just x -> return x
Nothing -> throwError $ PandocSomeError $ ident ++ " not found in reftable"
let isSec (S.Sec lev _ _ _ _) = lev <= tocLevel
- isSec _ = False
+ isSec _ = False
let subsecs = filter isSec children
subs <- mapM (navPointNode formatter) subsecs
return $ formatter n tit src subs
@@ -830,22 +832,22 @@ metadataElement version md currentTime =
(("id",id') :
maybe [] (\x -> [("opf:event",x)]) (dateEvent date)) $
dateText date]
- schemeToOnix "ISBN-10" = "02"
- schemeToOnix "GTIN-13" = "03"
- schemeToOnix "UPC" = "04"
- schemeToOnix "ISMN-10" = "05"
- schemeToOnix "DOI" = "06"
- schemeToOnix "LCCN" = "13"
- schemeToOnix "GTIN-14" = "14"
- schemeToOnix "ISBN-13" = "15"
+ schemeToOnix "ISBN-10" = "02"
+ schemeToOnix "GTIN-13" = "03"
+ schemeToOnix "UPC" = "04"
+ schemeToOnix "ISMN-10" = "05"
+ schemeToOnix "DOI" = "06"
+ schemeToOnix "LCCN" = "13"
+ schemeToOnix "GTIN-14" = "14"
+ schemeToOnix "ISBN-13" = "15"
schemeToOnix "Legal deposit number" = "17"
- schemeToOnix "URN" = "22"
- schemeToOnix "OCLC" = "23"
- schemeToOnix "ISMN-13" = "25"
- schemeToOnix "ISBN-A" = "26"
- schemeToOnix "JP" = "27"
- schemeToOnix "OLCC" = "28"
- schemeToOnix _ = "01"
+ schemeToOnix "URN" = "22"
+ schemeToOnix "OCLC" = "23"
+ schemeToOnix "ISMN-13" = "25"
+ schemeToOnix "ISBN-A" = "26"
+ schemeToOnix "JP" = "27"
+ schemeToOnix "OLCC" = "28"
+ schemeToOnix _ = "01"
showDateTimeISO8601 :: UTCTime -> String
showDateTimeISO8601 = formatTime defaultTimeLocale "%FT%TZ"
@@ -936,8 +938,8 @@ ppTopElement = ("<?xml version=\"1.0\" encoding=\"UTF-8\"?>\n" ++) . unEntity .
let (ds,ys) = break (==';') xs
rest = drop 1 ys
in case safeRead ('\'':'\\':ds ++ "'") of
- Just x -> x : unEntity rest
- Nothing -> '&':'#':unEntity xs
+ Just x -> x : unEntity rest
+ Nothing -> '&':'#':unEntity xs
unEntity (x:xs) = x : unEntity xs
mediaTypeOf :: FilePath -> Maybe MimeType
@@ -945,7 +947,7 @@ mediaTypeOf x =
let mediaPrefixes = ["image", "video", "audio"] in
case getMimeType x of
Just y | any (`isPrefixOf` y) mediaPrefixes -> Just y
- _ -> Nothing
+ _ -> Nothing
-- Returns filename for chapter number.
showChapter :: Int -> String
diff --git a/src/Text/Pandoc/Writers/FB2.hs b/src/Text/Pandoc/Writers/FB2.hs
index 967fe6a4c..238bd397b 100644
--- a/src/Text/Pandoc/Writers/FB2.hs
+++ b/src/Text/Pandoc/Writers/FB2.hs
@@ -27,37 +27,37 @@ FictionBook is an XML-based e-book format. For more information see:
-}
module Text.Pandoc.Writers.FB2 (writeFB2) where
-import Control.Monad.State (StateT, evalStateT, get, modify, lift)
+import Control.Monad.Except (catchError, throwError)
+import Control.Monad.State (StateT, evalStateT, get, lift, modify)
import Control.Monad.State (liftM)
import Data.ByteString.Base64 (encode)
-import Data.Char (toLower, isSpace, isAscii, isControl)
-import Data.List (intersperse, intercalate, isPrefixOf, stripPrefix)
+import qualified Data.ByteString.Char8 as B8
+import Data.Char (isAscii, isControl, isSpace, toLower)
import Data.Either (lefts, rights)
+import Data.List (intercalate, intersperse, isPrefixOf, stripPrefix)
import Network.HTTP (urlEncode)
import Network.URI (isURI)
import Text.XML.Light
import qualified Text.XML.Light as X
import qualified Text.XML.Light.Cursor as XC
-import qualified Data.ByteString.Char8 as B8
-import Control.Monad.Except (throwError, catchError)
-import Text.Pandoc.Logging
-import Text.Pandoc.Definition
-import Text.Pandoc.Options (WriterOptions(..), HTMLMathMethod(..), def)
-import Text.Pandoc.Shared (orderedListMarkers, isHeaderBlock, capitalize,
- linesToPara)
-import Text.Pandoc.Error
import Text.Pandoc.Class (PandocMonad, report)
import qualified Text.Pandoc.Class as P
+import Text.Pandoc.Definition
+import Text.Pandoc.Error
+import Text.Pandoc.Logging
+import Text.Pandoc.Options (HTMLMathMethod (..), WriterOptions (..), def)
+import Text.Pandoc.Shared (capitalize, isHeaderBlock, linesToPara,
+ orderedListMarkers)
-- | Data to be written at the end of the document:
-- (foot)notes, URLs, references, images.
data FbRenderState = FbRenderState
- { footnotes :: [ (Int, String, [Content]) ] -- ^ #, ID, text
- , imagesToFetch :: [ (String, String) ] -- ^ filename, URL or path
- , parentListMarker :: String -- ^ list marker of the parent ordered list
+ { footnotes :: [ (Int, String, [Content]) ] -- ^ #, ID, text
+ , imagesToFetch :: [ (String, String) ] -- ^ filename, URL or path
+ , parentListMarker :: String -- ^ list marker of the parent ordered list
, parentBulletLevel :: Int -- ^ nesting level of the unordered list
- , writerOptions :: WriterOptions
+ , writerOptions :: WriterOptions
} deriving (Show)
-- | FictionBook building monad.
@@ -188,7 +188,7 @@ split cond xs = let (b,a) = break cond xs
isLineBreak :: Inline -> Bool
isLineBreak LineBreak = True
-isLineBreak _ = False
+isLineBreak _ = False
-- | Divide the stream of block elements into sections: [(title, blocks)].
splitSections :: Int -> [Block] -> [([Inline], [Block])]
@@ -206,7 +206,7 @@ splitSections level blocks = reverse $ revSplit (reverse blocks)
_ -> ([], before)
in (header, reverse lastsec) : revSplit prevblocks
sameLevel (Header n _ _) = n == level
- sameLevel _ = False
+ sameLevel _ = False
-- | Make another FictionBook body with footnotes.
renderFootnotes :: PandocMonad m => FBM m [Content]
@@ -353,9 +353,9 @@ blockToXml (DefinitionList defs) =
blocks ++ [Plain [LineBreak]]
else
blocks
- needsBreak (Para _) = False
+ needsBreak (Para _) = False
needsBreak (Plain ins) = LineBreak `notElem` ins
- needsBreak _ = True
+ needsBreak _ = True
blockToXml (Header _ _ _) = -- should never happen, see renderSections
throwError $ PandocShouldNeverHappenError "unexpected header in section text"
blockToXml HorizontalRule = return
@@ -378,9 +378,9 @@ blockToXml (Table caption aligns _ headers rows) = do
return $ el tag ([align_attr align], cblocks)
--
align_attr a = Attr (QName "align" Nothing Nothing) (align_str a)
- align_str AlignLeft = "left"
- align_str AlignCenter = "center"
- align_str AlignRight = "right"
+ align_str AlignLeft = "left"
+ align_str AlignCenter = "center"
+ align_str AlignRight = "right"
align_str AlignDefault = "left"
blockToXml Null = return []
@@ -488,7 +488,7 @@ insertImage immode (Image _ alt (url,ttl)) = do
modify (\s -> s { imagesToFetch = (fname, url) : images })
let ttlattr = case (immode, null ttl) of
(NormalImage, False) -> [ uattr "title" ttl ]
- _ -> []
+ _ -> []
return . list $
el "image" $
[ attr ("l","href") ('#':fname)
@@ -512,11 +512,11 @@ replaceImagesWithAlt missingHrefs body =
else c
in case XC.nextDF c' of
(Just cnext) -> replaceAll cnext
- Nothing -> c' -- end of document
+ Nothing -> c' -- end of document
--
isImage :: Content -> Bool
isImage (Elem e) = (elName e) == (uname "image")
- isImage _ = False
+ isImage _ = False
--
isMissing (Elem img@(Element _ _ _ _)) =
let imgAttrs = elAttribs img
@@ -555,25 +555,25 @@ list = (:[])
-- | Convert an 'Inline' to plaintext.
plain :: Inline -> String
-plain (Str s) = s
-plain (Emph ss) = concat (map plain ss)
-plain (Span _ ss) = concat (map plain ss)
-plain (Strong ss) = concat (map plain ss)
-plain (Strikeout ss) = concat (map plain ss)
-plain (Superscript ss) = concat (map plain ss)
-plain (Subscript ss) = concat (map plain ss)
-plain (SmallCaps ss) = concat (map plain ss)
-plain (Quoted _ ss) = concat (map plain ss)
-plain (Cite _ ss) = concat (map plain ss) -- FIXME
-plain (Code _ s) = s
-plain Space = " "
-plain SoftBreak = " "
-plain LineBreak = "\n"
-plain (Math _ s) = s
-plain (RawInline _ _) = ""
+plain (Str s) = s
+plain (Emph ss) = concat (map plain ss)
+plain (Span _ ss) = concat (map plain ss)
+plain (Strong ss) = concat (map plain ss)
+plain (Strikeout ss) = concat (map plain ss)
+plain (Superscript ss) = concat (map plain ss)
+plain (Subscript ss) = concat (map plain ss)
+plain (SmallCaps ss) = concat (map plain ss)
+plain (Quoted _ ss) = concat (map plain ss)
+plain (Cite _ ss) = concat (map plain ss) -- FIXME
+plain (Code _ s) = s
+plain Space = " "
+plain SoftBreak = " "
+plain LineBreak = "\n"
+plain (Math _ s) = s
+plain (RawInline _ _) = ""
plain (Link _ text (url,_)) = concat (map plain text ++ [" <", url, ">"])
-plain (Image _ alt _) = concat (map plain alt)
-plain (Note _) = "" -- FIXME
+plain (Image _ alt _) = concat (map plain alt)
+plain (Note _) = "" -- FIXME
-- | Create an XML element.
el :: (Node t)
diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs
index 332536492..6a5c4e43a 100644
--- a/src/Text/Pandoc/Writers/HTML.hs
+++ b/src/Text/Pandoc/Writers/HTML.hs
@@ -1,4 +1,7 @@
-{-# LANGUAGE OverloadedStrings, CPP, ViewPatterns, ScopedTypeVariables #-}
+{-# LANGUAGE CPP #-}
+{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE ScopedTypeVariables #-}
+{-# LANGUAGE ViewPatterns #-}
{-
Copyright (C) 2006-2015 John MacFarlane <jgm@berkeley.edu>
@@ -40,61 +43,61 @@ module Text.Pandoc.Writers.HTML (
writeDZSlides,
writeRevealJs
) where
-import Text.Pandoc.Definition
-import Text.Pandoc.Walk
+import Control.Monad.State
+import Data.Char (ord, toLower)
+import Data.List (intersperse, isPrefixOf)
+import Data.Maybe (catMaybes, fromMaybe, isJust)
import Data.Monoid ((<>))
-import Text.Pandoc.Shared
-import Text.Pandoc.Writers.Shared
-import Text.Pandoc.Options
+import Data.String (fromString)
+import Network.HTTP (urlEncode)
+import Network.URI (URI (..), parseURIReference, unEscapeString)
+import Numeric (showHex)
+import Text.Blaze.Html hiding (contents)
+import Text.Pandoc.Definition
+import Text.Pandoc.Highlighting (formatHtmlBlock, formatHtmlInline, highlight,
+ styleToCss)
import Text.Pandoc.ImageSize
+import Text.Pandoc.Options
+import Text.Pandoc.Shared
+import Text.Pandoc.Slides
import Text.Pandoc.Templates
+import Text.Pandoc.Walk
import Text.Pandoc.Writers.Math
-import Text.Pandoc.Slides
-import Text.Pandoc.Highlighting ( highlight, styleToCss,
- formatHtmlInline, formatHtmlBlock )
-import Text.Pandoc.XML (fromEntities, escapeStringForXML)
-import Network.URI ( parseURIReference, URI(..), unEscapeString )
-import Network.HTTP ( urlEncode )
-import Numeric ( showHex )
-import Data.Char ( ord, toLower )
-import Data.List ( isPrefixOf, intersperse )
-import Data.String ( fromString )
-import Data.Maybe ( catMaybes, fromMaybe, isJust )
-import Control.Monad.State
-import Text.Blaze.Html hiding(contents)
+import Text.Pandoc.Writers.Shared
+import Text.Pandoc.XML (escapeStringForXML, fromEntities)
#if MIN_VERSION_blaze_markup(0,6,3)
#else
-import Text.Blaze.Internal(preEscapedString)
+import Text.Blaze.Internal (preEscapedString)
#endif
#if MIN_VERSION_blaze_html(0,5,1)
import qualified Text.Blaze.XHtml5 as H5
#else
import qualified Text.Blaze.Html5 as H5
#endif
+import Control.Monad.Except (throwError)
+import Data.Aeson (Value)
+import System.FilePath (takeExtension)
+import Text.Blaze.Html.Renderer.String (renderHtml)
import qualified Text.Blaze.XHtml1.Transitional as H
import qualified Text.Blaze.XHtml1.Transitional.Attributes as A
-import Text.Blaze.Html.Renderer.String (renderHtml)
-import Text.TeXMath
-import Text.XML.Light.Output
-import Text.XML.Light (unode, elChildren, unqual)
-import qualified Text.XML.Light as XML
-import System.FilePath (takeExtension)
-import Data.Aeson (Value)
-import Control.Monad.Except (throwError)
-import Text.Pandoc.Error
import Text.Pandoc.Class (PandocMonad, report)
+import Text.Pandoc.Error
import Text.Pandoc.Logging
+import Text.TeXMath
+import Text.XML.Light (elChildren, unode, unqual)
+import qualified Text.XML.Light as XML
+import Text.XML.Light.Output
data WriterState = WriterState
- { stNotes :: [Html] -- ^ List of notes
- , stMath :: Bool -- ^ Math is used in document
- , stQuotes :: Bool -- ^ <q> tag is used
- , stHighlighting :: Bool -- ^ Syntax highlighting is used
- , stSecNum :: [Int] -- ^ Number of current section
- , stElement :: Bool -- ^ Processing an Element
- , stHtml5 :: Bool -- ^ Use HTML5
- , stEPUBVersion :: Maybe EPUBVersion -- ^ EPUB version if for epub
- , stSlideVariant :: HTMLSlideVariant
+ { stNotes :: [Html] -- ^ List of notes
+ , stMath :: Bool -- ^ Math is used in document
+ , stQuotes :: Bool -- ^ <q> tag is used
+ , stHighlighting :: Bool -- ^ Syntax highlighting is used
+ , stSecNum :: [Int] -- ^ Number of current section
+ , stElement :: Bool -- ^ Processing an Element
+ , stHtml5 :: Bool -- ^ Use HTML5
+ , stEPUBVersion :: Maybe EPUBVersion -- ^ EPUB version if for epub
+ , stSlideVariant :: HTMLSlideVariant
}
defaultWriterState :: WriterState
@@ -290,8 +293,8 @@ pandocToHtml opts (Pandoc meta blocks) = do
prefixedId :: WriterOptions -> String -> Attribute
prefixedId opts s =
case s of
- "" -> mempty
- _ -> A.id $ toValue $ writerIdentifierPrefix opts ++ s
+ "" -> mempty
+ _ -> A.id $ toValue $ writerIdentifierPrefix opts ++ s
toList :: PandocMonad m
=> (Html -> Html)
@@ -387,8 +390,8 @@ elementToHtml slideLevel opts (Sec level num (id',classes,keyvals) title' elemen
let isPause (Blk x) = x == Para [Str ".",Space,Str ".",Space,Str "."]
isPause _ = False
let fragmentClass = case slideVariant of
- RevealJsSlides -> "fragment"
- _ -> "incremental"
+ RevealJsSlides -> "fragment"
+ _ -> "incremental"
let inDiv xs = Blk (RawBlock (Format "html") ("<div class=\""
++ fragmentClass ++ "\">")) :
(xs ++ [Blk (RawBlock (Format "html") "</div>")])
@@ -515,7 +518,7 @@ imgAttrsToHtml opts attr =
kvs' = filter isNotDim kvs
isNotDim ("width", _) = False
isNotDim ("height", _) = False
- isNotDim _ = True
+ isNotDim _ = True
dimensionsToAttrList :: WriterOptions -> Attr -> [(String, String)]
dimensionsToAttrList opts attr = (go Width) ++ (go Height)
@@ -581,7 +584,7 @@ blockToHtml opts (Para lst)
return $ H.p contents
where
isEmptyRaw [RawInline f _] = f /= (Format "html")
- isEmptyRaw _ = False
+ isEmptyRaw _ = False
blockToHtml opts (LineBlock lns) =
if writerWrapText opts == WrapNone
then blockToHtml opts $ linesToPara lns
@@ -767,9 +770,9 @@ tableRowToHtml :: PandocMonad m
tableRowToHtml opts aligns rownum cols' = do
let mkcell = if rownum == 0 then H.th else H.td
let rowclass = case rownum of
- 0 -> "header"
+ 0 -> "header"
x | x `rem` 2 == 1 -> "odd"
- _ -> "even"
+ _ -> "even"
cols'' <- sequence $ zipWith
(\alignment item -> tableItemToHtml opts mkcell alignment item)
aligns cols'
@@ -821,9 +824,9 @@ annotateMML :: XML.Element -> String -> XML.Element
annotateMML e tex = math (unode "semantics" [cs, unode "annotation" (annotAttrs, tex)])
where
cs = case elChildren e of
- [] -> unode "mrow" ()
+ [] -> unode "mrow" ()
[x] -> x
- xs -> unode "mrow" xs
+ xs -> unode "mrow" xs
math childs = XML.Element q as [XML.Elem childs] l
where
(XML.Element q as _ l) = e
@@ -908,7 +911,7 @@ inlineToHtml opts inline = do
JsMath _ -> do
let m = preEscapedString str
return $ case t of
- InlineMath -> H.span ! A.class_ mathClass $ m
+ InlineMath -> H.span ! A.class_ mathClass $ m
DisplayMath -> H.div ! A.class_ mathClass $ m
WebTeX url -> do
let imtag = if html5 then H5.img else H.img
@@ -939,7 +942,7 @@ inlineToHtml opts inline = do
DisplayMath -> "\\[" ++ str ++ "\\]"
KaTeX _ _ -> return $ H.span ! A.class_ mathClass $
toHtml (case t of
- InlineMath -> str
+ InlineMath -> str
DisplayMath -> "\\displaystyle " ++ str)
PlainMath -> do
x <- lift (texMathToInlines t str) >>= inlineListToHtml opts
diff --git a/src/Text/Pandoc/Writers/Haddock.hs b/src/Text/Pandoc/Writers/Haddock.hs
index 945e4a0f1..7f7d89a43 100644
--- a/src/Text/Pandoc/Writers/Haddock.hs
+++ b/src/Text/Pandoc/Writers/Haddock.hs
@@ -1,4 +1,6 @@
-{-# LANGUAGE OverloadedStrings, TupleSections, ScopedTypeVariables #-}
+{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE ScopedTypeVariables #-}
+{-# LANGUAGE TupleSections #-}
{-
Copyright (C) 2014 John MacFarlane <jgm@berkeley.edu>
@@ -31,19 +33,19 @@ Conversion of 'Pandoc' documents to haddock markup.
Haddock: <http://www.haskell.org/haddock/doc/html/>
-}
module Text.Pandoc.Writers.Haddock (writeHaddock) where
-import Text.Pandoc.Definition
-import Text.Pandoc.Templates (renderTemplate')
-import Text.Pandoc.Shared
-import Text.Pandoc.Writers.Shared
-import Text.Pandoc.Options
-import Data.List ( intersperse, transpose )
-import Text.Pandoc.Pretty
import Control.Monad.State
-import Text.Pandoc.Writers.Math (texMathToInlines)
-import Network.URI (isURI)
import Data.Default
+import Data.List (intersperse, transpose)
+import Network.URI (isURI)
import Text.Pandoc.Class (PandocMonad, report)
+import Text.Pandoc.Definition
import Text.Pandoc.Logging
+import Text.Pandoc.Options
+import Text.Pandoc.Pretty
+import Text.Pandoc.Shared
+import Text.Pandoc.Templates (renderTemplate')
+import Text.Pandoc.Writers.Math (texMathToInlines)
+import Text.Pandoc.Writers.Shared
type Notes = [[Block]]
data WriterState = WriterState { stNotes :: Notes }
@@ -269,7 +271,7 @@ orderedListItemToHaddock opts marker items = do
contents <- blockListToHaddock opts items
let sps = case length marker - writerTabStop opts of
n | n > 0 -> text $ replicate n ' '
- _ -> text " "
+ _ -> text " "
let start = text marker <> sps
return $ hang (writerTabStop opts) start $ contents <> cr
@@ -356,7 +358,7 @@ inlineToHaddock _ (Link _ txt (src, _)) = do
let useAuto = isURI src &&
case txt of
[Str s] | escapeURI s == src -> True
- _ -> False
+ _ -> False
return $ nowrap $ "<" <> text src <>
(if useAuto then empty else space <> linktext) <> ">"
inlineToHaddock opts (Image attr alternate (source, tit)) = do
diff --git a/src/Text/Pandoc/Writers/ICML.hs b/src/Text/Pandoc/Writers/ICML.hs
index 59f9db26a..cd3cac5a7 100644
--- a/src/Text/Pandoc/Writers/ICML.hs
+++ b/src/Text/Pandoc/Writers/ICML.hs
@@ -1,4 +1,6 @@
-{-# LANGUAGE OverloadedStrings, FlexibleContexts, ScopedTypeVariables #-}
+{-# LANGUAGE FlexibleContexts #-}
+{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE ScopedTypeVariables #-}
{- |
Module : Text.Pandoc.Writers.ICML
@@ -14,25 +16,25 @@ InCopy is the companion word-processor to Adobe InDesign and ICML documents can
into InDesign with File -> Place.
-}
module Text.Pandoc.Writers.ICML (writeICML) where
-import Text.Pandoc.Definition
-import Text.Pandoc.Error (PandocError(..))
-import Text.Pandoc.XML
-import Text.Pandoc.Writers.Math (texMathToInlines)
-import Text.Pandoc.Writers.Shared
-import Text.Pandoc.Shared (linesToPara, splitBy)
-import Text.Pandoc.Options
-import Text.Pandoc.Templates (renderTemplate')
-import Text.Pandoc.Pretty
-import Text.Pandoc.ImageSize
-import Data.List (isPrefixOf, isInfixOf, stripPrefix, intersperse)
-import Data.Text as Text (breakOnAll, pack)
-import Control.Monad.State
import Control.Monad.Except (catchError)
-import Network.URI (isURI)
+import Control.Monad.State
+import Data.List (intersperse, isInfixOf, isPrefixOf, stripPrefix)
import qualified Data.Set as Set
+import Data.Text as Text (breakOnAll, pack)
+import Network.URI (isURI)
import Text.Pandoc.Class (PandocMonad, report)
-import Text.Pandoc.Logging
import qualified Text.Pandoc.Class as P
+import Text.Pandoc.Definition
+import Text.Pandoc.Error (PandocError (..))
+import Text.Pandoc.ImageSize
+import Text.Pandoc.Logging
+import Text.Pandoc.Options
+import Text.Pandoc.Pretty
+import Text.Pandoc.Shared (linesToPara, splitBy)
+import Text.Pandoc.Templates (renderTemplate')
+import Text.Pandoc.Writers.Math (texMathToInlines)
+import Text.Pandoc.Writers.Shared
+import Text.Pandoc.XML
type Style = [String]
type Hyperlink = [(Int, String)]
@@ -384,11 +386,11 @@ listItemToICML :: PandocMonad m => WriterOptions -> Style -> Bool-> Maybe ListAt
listItemToICML opts style isFirst attribs item =
let makeNumbStart (Just (beginsWith, numbStl, _)) =
let doN DefaultStyle = []
- doN LowerRoman = [lowerRomanName]
- doN UpperRoman = [upperRomanName]
- doN LowerAlpha = [lowerAlphaName]
- doN UpperAlpha = [upperAlphaName]
- doN _ = []
+ doN LowerRoman = [lowerRomanName]
+ doN UpperRoman = [upperRomanName]
+ doN LowerAlpha = [lowerAlphaName]
+ doN UpperAlpha = [upperAlphaName]
+ doN _ = []
bw = if beginsWith > 1
then [beginsWithName ++ show beginsWith]
else []
@@ -483,9 +485,9 @@ mergeSpaces (x:xs) = x : (mergeSpaces xs)
mergeSpaces [] = []
isSp :: Inline -> Bool
-isSp Space = True
+isSp Space = True
isSp SoftBreak = True
-isSp _ = False
+isSp _ = False
-- | Intersperse line breaks
intersperseBrs :: [Doc] -> Doc
diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs
index 11cd0479d..578c7017f 100644
--- a/src/Text/Pandoc/Writers/LaTeX.hs
+++ b/src/Text/Pandoc/Writers/LaTeX.hs
@@ -1,5 +1,6 @@
-{-# LANGUAGE OverloadedStrings, ScopedTypeVariables,
- PatternGuards #-}
+{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE PatternGuards #-}
+{-# LANGUAGE ScopedTypeVariables #-}
{-
Copyright (C) 2006-2015 John MacFarlane <jgm@berkeley.edu>
@@ -33,32 +34,31 @@ module Text.Pandoc.Writers.LaTeX (
writeLaTeX
, writeBeamer
) where
-import Text.Pandoc.Definition
-import Text.Pandoc.Walk
-import Text.Pandoc.Shared
-import Text.Pandoc.Writers.Shared
-import Text.Pandoc.Options
-import Text.Pandoc.Templates
-import Text.Pandoc.Logging
-import Text.Printf ( printf )
-import Network.URI ( isURI, unEscapeString )
-import Data.Aeson (object, (.=), FromJSON)
-import Data.List ( (\\), isInfixOf, stripPrefix, intercalate, intersperse,
- nub, nubBy, foldl' )
-import Data.Char ( toLower, isPunctuation, isAscii, isLetter, isDigit,
- ord, isAlphaNum )
-import Data.Maybe ( fromMaybe, isJust, catMaybes )
-import qualified Data.Text as T
import Control.Applicative ((<|>))
import Control.Monad.State
-import qualified Text.Parsec as P
-import Text.Pandoc.Pretty
+import Data.Aeson (FromJSON, object, (.=))
+import Data.Char (isAlphaNum, isAscii, isDigit, isLetter, isPunctuation, ord,
+ toLower)
+import Data.List (foldl', intercalate, intersperse, isInfixOf, nub, nubBy,
+ stripPrefix, (\\))
+import Data.Maybe (catMaybes, fromMaybe, isJust)
+import qualified Data.Text as T
+import Network.URI (isURI, unEscapeString)
+import Text.Pandoc.Class (PandocMonad, report)
+import Text.Pandoc.Definition
+import Text.Pandoc.Highlighting (formatLaTeXBlock, formatLaTeXInline, highlight,
+ styleToLaTeX, toListingsLanguage)
import Text.Pandoc.ImageSize
+import Text.Pandoc.Logging
+import Text.Pandoc.Options
+import Text.Pandoc.Pretty
+import Text.Pandoc.Shared
import Text.Pandoc.Slides
-import Text.Pandoc.Highlighting (highlight, styleToLaTeX,
- formatLaTeXInline, formatLaTeXBlock,
- toListingsLanguage)
-import Text.Pandoc.Class (PandocMonad, report)
+import Text.Pandoc.Templates
+import Text.Pandoc.Walk
+import Text.Pandoc.Writers.Shared
+import qualified Text.Parsec as P
+import Text.Printf (printf)
data WriterState =
WriterState { stInNote :: Bool -- true if we're in a note
@@ -131,11 +131,11 @@ 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]
- isInternalLink _ = []
+ let isInternalLink (Link _ _ ('#':xs,_)) = [xs]
+ isInternalLink _ = []
modify $ \s -> s{ stInternalLinks = query isInternalLink blocks' }
let template = maybe "" id $ writerTemplate options
-- set stBook depending on documentclass
@@ -408,8 +408,8 @@ isListBlock _ = False
isLineBreakOrSpace :: Inline -> Bool
isLineBreakOrSpace LineBreak = True
isLineBreakOrSpace SoftBreak = True
-isLineBreakOrSpace Space = True
-isLineBreakOrSpace _ = False
+isLineBreakOrSpace Space = True
+isLineBreakOrSpace _ = False
-- | Convert Pandoc block element to LaTeX.
blockToLaTeX :: PandocMonad m
@@ -584,10 +584,10 @@ blockToLaTeX (OrderedList (start, numstyle, numdelim) lst) = do
Example -> "\\arabic" <> braces x
DefaultStyle -> "\\arabic" <> braces x
let todelim x = case numdelim of
- OneParen -> x <> ")"
- TwoParens -> parens x
- Period -> x <> "."
- _ -> x <> "."
+ OneParen -> x <> ")"
+ TwoParens -> parens x
+ Period -> x <> "."
+ _ -> x <> "."
let enum = text $ "enum" ++ map toLower (toRomanNumeral oldlevel)
let stylecommand = if numstyle == DefaultStyle && numdelim == DefaultDelim
then empty
@@ -710,7 +710,7 @@ fixLineBreaks' ils = case splitBy (== LineBreak) ils of
-- math breaks in simple tables.
displayMathToInline :: Inline -> Inline
displayMathToInline (Math DisplayMath x) = Math InlineMath x
-displayMathToInline x = x
+displayMathToInline x = x
tableCellToLaTeX :: PandocMonad m => Bool -> (Double, Alignment, [Block])
-> LW m Doc
@@ -783,10 +783,10 @@ sectionHeader :: PandocMonad m
sectionHeader unnumbered ident level lst = do
txt <- inlineListToLaTeX lst
plain <- stringToLaTeX TextString $ concatMap stringify lst
- let removeInvalidInline (Note _) = []
+ let removeInvalidInline (Note _) = []
removeInvalidInline (Span (id', _, _) _) | not (null id') = []
- removeInvalidInline (Image _ _ _) = []
- removeInvalidInline x = [x]
+ removeInvalidInline (Image _ _ _) = []
+ removeInvalidInline x = [x]
let lstNoNotes = foldr (mappend . (\x -> walkM removeInvalidInline x)) mempty lst
txtNoNotes <- inlineListToLaTeX lstNoNotes
-- footnotes in sections don't work (except for starred variants)
@@ -889,7 +889,7 @@ inlineListToLaTeX lst =
isQuoted :: Inline -> Bool
isQuoted (Quoted _ _) = True
-isQuoted _ = False
+isQuoted _ = False
-- | Convert inline element to LaTeX
inlineToLaTeX :: PandocMonad m
@@ -1092,8 +1092,8 @@ citationsToNatbib (one:[])
}
= one
c = case m of
- AuthorInText -> "citet"
- SuppressAuthor -> "citeyearpar"
+ AuthorInText -> "citet"
+ SuppressAuthor -> "citeyearpar"
NormalCitation -> "citep"
citationsToNatbib cits
@@ -1140,7 +1140,7 @@ citeArguments p s k = do
let s' = case s of
(Str (x:[]) : r) | isPunctuation x -> dropWhile (== Space) r
(Str (x:xs) : r) | isPunctuation x -> Str xs : r
- _ -> s
+ _ -> s
pdoc <- inlineListToLaTeX p
sdoc <- inlineListToLaTeX s'
let optargs = case (isEmpty pdoc, isEmpty sdoc) of
@@ -1181,7 +1181,7 @@ citationsToBiblatex _ = return empty
-- Determine listings language from list of class attributes.
getListingsLanguage :: [String] -> Maybe String
-getListingsLanguage [] = Nothing
+getListingsLanguage [] = Nothing
getListingsLanguage (x:xs) = toListingsLanguage x <|> getListingsLanguage xs
mbBraced :: String -> String
@@ -1253,27 +1253,27 @@ toPolyglossia x = (commonFromBcp47 x, "")
-- List of supported languages (slightly outdated):
-- http://tug.ctan.org/language/hyph-utf8/doc/generic/hyph-utf8/hyphenation.pdf
toBabel :: [String] -> String
-toBabel ("de":"1901":_) = "german"
-toBabel ("de":"AT":"1901":_) = "austrian"
-toBabel ("de":"AT":_) = "naustrian"
-toBabel ("de":"CH":"1901":_) = "swissgerman"
-toBabel ("de":"CH":_) = "nswissgerman"
-toBabel ("de":_) = "ngerman"
-toBabel ("dsb":_) = "lowersorbian"
-toBabel ("el":"polyton":_) = "polutonikogreek"
-toBabel ("en":"AU":_) = "australian"
-toBabel ("en":"CA":_) = "canadian"
-toBabel ("en":"GB":_) = "british"
-toBabel ("en":"NZ":_) = "newzealand"
-toBabel ("en":"UK":_) = "british"
-toBabel ("en":"US":_) = "american"
-toBabel ("fr":"CA":_) = "canadien"
-toBabel ("fra":"aca":_) = "acadian"
-toBabel ("grc":_) = "polutonikogreek"
-toBabel ("hsb":_) = "uppersorbian"
+toBabel ("de":"1901":_) = "german"
+toBabel ("de":"AT":"1901":_) = "austrian"
+toBabel ("de":"AT":_) = "naustrian"
+toBabel ("de":"CH":"1901":_) = "swissgerman"
+toBabel ("de":"CH":_) = "nswissgerman"
+toBabel ("de":_) = "ngerman"
+toBabel ("dsb":_) = "lowersorbian"
+toBabel ("el":"polyton":_) = "polutonikogreek"
+toBabel ("en":"AU":_) = "australian"
+toBabel ("en":"CA":_) = "canadian"
+toBabel ("en":"GB":_) = "british"
+toBabel ("en":"NZ":_) = "newzealand"
+toBabel ("en":"UK":_) = "british"
+toBabel ("en":"US":_) = "american"
+toBabel ("fr":"CA":_) = "canadien"
+toBabel ("fra":"aca":_) = "acadian"
+toBabel ("grc":_) = "polutonikogreek"
+toBabel ("hsb":_) = "uppersorbian"
toBabel ("la":"x":"classic":_) = "classiclatin"
-toBabel ("sl":_) = "slovene"
-toBabel x = commonFromBcp47 x
+toBabel ("sl":_) = "slovene"
+toBabel x = commonFromBcp47 x
-- Takes a list of the constituents of a BCP 47 language code
-- and converts it to a string shared by Babel and Polyglossia.
diff --git a/src/Text/Pandoc/Writers/Man.hs b/src/Text/Pandoc/Writers/Man.hs
index 9b46796af..6d7a4f84b 100644
--- a/src/Text/Pandoc/Writers/Man.hs
+++ b/src/Text/Pandoc/Writers/Man.hs
@@ -29,25 +29,25 @@ Conversion of 'Pandoc' documents to groff man page format.
-}
module Text.Pandoc.Writers.Man ( writeMan) where
-import Text.Pandoc.Definition
-import Text.Pandoc.Templates
-import Text.Pandoc.Shared
-import Text.Pandoc.Writers.Shared
-import Text.Pandoc.Options
-import Text.Pandoc.Writers.Math
-import Text.Printf ( printf )
-import Data.List ( stripPrefix, intersperse, intercalate )
+import Control.Monad.Except (throwError)
+import Control.Monad.State
+import Data.List (intercalate, intersperse, stripPrefix)
import Data.Maybe (fromMaybe)
-import Text.Pandoc.Pretty
import Text.Pandoc.Builder (deleteMeta)
-import Control.Monad.State
-import Text.Pandoc.Error
-import Control.Monad.Except (throwError)
import Text.Pandoc.Class (PandocMonad, report)
+import Text.Pandoc.Definition
+import Text.Pandoc.Error
import Text.Pandoc.Logging
+import Text.Pandoc.Options
+import Text.Pandoc.Pretty
+import Text.Pandoc.Shared
+import Text.Pandoc.Templates
+import Text.Pandoc.Writers.Math
+import Text.Pandoc.Writers.Shared
+import Text.Printf (printf)
type Notes = [[Block]]
-data WriterState = WriterState { stNotes :: Notes
+data WriterState = WriterState { stNotes :: Notes
, stHasTables :: Bool }
-- | Convert Pandoc to Man.
@@ -131,7 +131,7 @@ escapeCode = concat . intersperse "\n" . map escapeLine . lines where
escapeLine codeline =
case escapeStringUsing (manEscapes ++ backslashEscapes "\t ") codeline of
a@('.':_) -> "\\&" ++ a
- b -> b
+ b -> b
-- We split inline lists into sentences, and print one sentence per
-- line. groff/troff treats the line-ending period differently.
@@ -143,8 +143,8 @@ breakSentence [] = ([],[])
breakSentence xs =
let isSentenceEndInline (Str ys@(_:_)) | last ys == '.' = True
isSentenceEndInline (Str ys@(_:_)) | last ys == '?' = True
- isSentenceEndInline (LineBreak) = True
- isSentenceEndInline _ = False
+ isSentenceEndInline (LineBreak) = True
+ isSentenceEndInline _ = False
(as, bs) = break isSentenceEndInline xs
in case bs of
[] -> (as, [])
diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs
index e3b400780..e5b3b5001 100644
--- a/src/Text/Pandoc/Writers/Markdown.hs
+++ b/src/Text/Pandoc/Writers/Markdown.hs
@@ -1,4 +1,7 @@
-{-# LANGUAGE OverloadedStrings, TupleSections, ScopedTypeVariables, MultiWayIf #-}
+{-# LANGUAGE MultiWayIf #-}
+{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE ScopedTypeVariables #-}
+{-# LANGUAGE TupleSections #-}
{-
Copyright (C) 2006-2015 John MacFarlane <jgm@berkeley.edu>
@@ -31,36 +34,36 @@ Conversion of 'Pandoc' documents to markdown-formatted plain text.
Markdown: <http://daringfireball.net/projects/markdown/>
-}
module Text.Pandoc.Writers.Markdown (writeMarkdown, writePlain) where
-import Text.Pandoc.Definition
-import Text.Pandoc.Walk
-import Text.Pandoc.Templates (renderTemplate')
-import Text.Pandoc.Shared
-import Text.Pandoc.Writers.Shared
-import Text.Pandoc.Options
-import Text.Pandoc.Parsing hiding (blankline, blanklines, char, space)
-import Data.Maybe (fromMaybe)
-import Data.Monoid (Any(..))
-import Data.List ( group, stripPrefix, find, intersperse, transpose, sortBy )
-import Data.Char ( isSpace, isPunctuation, ord, chr )
-import Data.Ord ( comparing )
-import Text.Pandoc.Pretty
+import Control.Monad.Except (throwError)
import Control.Monad.Reader
import Control.Monad.State
-import Control.Monad.Except (throwError)
-import Text.Pandoc.Writers.HTML (writeHtml5String)
-import Text.Pandoc.Writers.Math (texMathToInlines)
-import Text.HTML.TagSoup (parseTags, isTagText, Tag(..))
-import Network.URI (isURI)
+import Data.Char (chr, isPunctuation, isSpace, ord)
import Data.Default
-import Data.Yaml (Value(Object,String,Array,Bool,Number))
import qualified Data.HashMap.Strict as H
-import qualified Data.Vector as V
-import qualified Data.Text as T
+import Data.List (find, group, intersperse, sortBy, stripPrefix, transpose)
+import Data.Maybe (fromMaybe)
+import Data.Monoid (Any (..))
+import Data.Ord (comparing)
import qualified Data.Set as Set
-import Network.HTTP ( urlEncode )
-import Text.Pandoc.Error
+import qualified Data.Text as T
+import qualified Data.Vector as V
+import Data.Yaml (Value (Array, Bool, Number, Object, String))
+import Network.HTTP (urlEncode)
+import Network.URI (isURI)
+import Text.HTML.TagSoup (Tag (..), isTagText, parseTags)
import Text.Pandoc.Class (PandocMonad, report)
+import Text.Pandoc.Definition
+import Text.Pandoc.Error
import Text.Pandoc.Logging
+import Text.Pandoc.Options
+import Text.Pandoc.Parsing hiding (blankline, blanklines, char, space)
+import Text.Pandoc.Pretty
+import Text.Pandoc.Shared
+import Text.Pandoc.Templates (renderTemplate')
+import Text.Pandoc.Walk
+import Text.Pandoc.Writers.HTML (writeHtml5String)
+import Text.Pandoc.Writers.Math (texMathToInlines)
+import Text.Pandoc.Writers.Shared
type Notes = [[Block]]
type Ref = ([Inline], Target, Attr)
@@ -71,11 +74,11 @@ type MD m = ReaderT WriterEnv (StateT WriterState m)
evalMD :: PandocMonad m => MD m a -> WriterEnv -> WriterState -> m a
evalMD md env st = evalStateT (runReaderT md env) st
-data WriterEnv = WriterEnv { envInList :: Bool
- , envPlain :: Bool
+data WriterEnv = WriterEnv { envInList :: Bool
+ , envPlain :: Bool
, envRefShortcutable :: Bool
, envBlockLevel :: Int
- , envEscapeSpaces :: Bool
+ , envEscapeSpaces :: Bool
}
instance Default WriterEnv
@@ -86,9 +89,9 @@ instance Default WriterEnv
, envEscapeSpaces = False
}
-data WriterState = WriterState { stNotes :: Notes
- , stRefs :: Refs
- , stIds :: Set.Set String
+data WriterState = WriterState { stNotes :: Notes
+ , stRefs :: Refs
+ , stIds :: Set.Set String
, stNoteNum :: Int
}
@@ -206,7 +209,7 @@ pandocToMarkdown opts (Pandoc meta blocks) = do
let blocks' = if isEnabled Ext_citations opts
then case reverse blocks of
(Div (_,["references"],_) _):xs -> reverse xs
- _ -> blocks
+ _ -> blocks
else blocks
body <- blockListToMarkdown opts blocks'
notesAndRefs' <- notesAndRefs opts
@@ -260,7 +263,7 @@ noteToMarkdown opts num blocks = do
let markerSize = 4 + offset num'
let spacer = case writerTabStop opts - markerSize of
n | n > 0 -> text $ replicate n ' '
- _ -> text " "
+ _ -> text " "
return $ if isEnabled Ext_footnotes opts
then hang (writerTabStop opts) (marker <> spacer) contents
else marker <> spacer <> contents
@@ -282,11 +285,11 @@ escapeString opts (c:cs) =
'-' | isEnabled Ext_smart opts ->
case cs of
'-':_ -> '\\':'-':escapeString opts cs
- _ -> '-':escapeString opts cs
+ _ -> '-':escapeString opts cs
'.' | isEnabled Ext_smart opts ->
case cs of
'.':'.':rest -> '\\':'.':'.':'.':escapeString opts rest
- _ -> '.':escapeString opts cs
+ _ -> '.':escapeString opts cs
_ -> c : escapeString opts cs
-- | Construct table of contents from list of header blocks.
@@ -342,8 +345,8 @@ olMarker = do (start, style', delim) <- anyOrderedListMarker
beginsWithOrderedListMarker :: String -> Bool
beginsWithOrderedListMarker str =
case runParser olMarker defaultParserState "para start" (take 10 str) of
- Left _ -> False
- Right _ -> True
+ Left _ -> False
+ Right _ -> True
notesAndRefs :: PandocMonad m => WriterOptions -> MD m Doc
notesAndRefs opts = do
@@ -727,7 +730,7 @@ itemEndsWithTightList bs =
case bs of
[Plain _, BulletList xs] -> isTightList xs
[Plain _, OrderedList _ xs] -> isTightList xs
- _ -> False
+ _ -> False
-- | Convert bullet list item (list of blocks) to markdown.
bulletListItemToMarkdown :: PandocMonad m => WriterOptions -> [Block] -> MD m Doc
@@ -751,7 +754,7 @@ orderedListItemToMarkdown opts marker bs = do
contents <- blockListToMarkdown opts bs
let sps = case length marker - writerTabStop opts of
n | n > 0 -> text $ replicate n ' '
- _ -> text " "
+ _ -> text " "
let start = text marker <> sps
-- remove trailing blank line if item ends with a tight list
let contents' = if itemEndsWithTightList bs
@@ -774,7 +777,7 @@ definitionListItemToMarkdown opts (label, defs) = do
let leader = if isPlain then " " else ": "
let sps = case writerTabStop opts - 3 of
n | n > 0 -> text $ replicate n ' '
- _ -> text " "
+ _ -> text " "
if isEnabled Ext_compact_definition_lists opts
then do
let contents = vcat $ map (\d -> hang tabStop (leader <> sps)
@@ -785,7 +788,7 @@ definitionListItemToMarkdown opts (label, defs) = do
$ vcat d <> cr) defs'
let isTight = case defs of
((Plain _ : _): _) -> True
- _ -> False
+ _ -> False
return $ blankline <> nowrap labelText <>
(if isTight then cr else blankline) <> contents <> blankline
else do
@@ -849,20 +852,20 @@ inlineListToMarkdown opts lst = do
go (i:is) = case i of
(Link _ _ _) -> case is of
-- If a link is followed by another link or '[' we don't shortcut
- (Link _ _ _):_ -> unshortcutable
- Space:(Link _ _ _):_ -> unshortcutable
- Space:(Str('[':_)):_ -> unshortcutable
- Space:(RawInline _ ('[':_)):_ -> unshortcutable
- Space:(Cite _ _):_ -> unshortcutable
- SoftBreak:(Link _ _ _):_ -> unshortcutable
- SoftBreak:(Str('[':_)):_ -> unshortcutable
+ (Link _ _ _):_ -> unshortcutable
+ Space:(Link _ _ _):_ -> unshortcutable
+ Space:(Str('[':_)):_ -> unshortcutable
+ Space:(RawInline _ ('[':_)):_ -> unshortcutable
+ Space:(Cite _ _):_ -> unshortcutable
+ SoftBreak:(Link _ _ _):_ -> unshortcutable
+ SoftBreak:(Str('[':_)):_ -> unshortcutable
SoftBreak:(RawInline _ ('[':_)):_ -> unshortcutable
- SoftBreak:(Cite _ _):_ -> unshortcutable
- (Cite _ _):_ -> unshortcutable
- Str ('[':_):_ -> unshortcutable
- (RawInline _ ('[':_)):_ -> unshortcutable
- (RawInline _ (' ':'[':_)):_ -> unshortcutable
- _ -> shortcutable
+ SoftBreak:(Cite _ _):_ -> unshortcutable
+ (Cite _ _):_ -> unshortcutable
+ Str ('[':_):_ -> unshortcutable
+ (RawInline _ ('[':_)):_ -> unshortcutable
+ (RawInline _ (' ':'[':_)):_ -> unshortcutable
+ _ -> shortcutable
_ -> shortcutable
where shortcutable = liftM2 (<>) (inlineToMarkdown opts i) (go is)
unshortcutable = do
@@ -872,9 +875,9 @@ inlineListToMarkdown opts lst = do
fmap (iMark <>) (go is)
isSp :: Inline -> Bool
-isSp Space = True
+isSp Space = True
isSp SoftBreak = True
-isSp _ = False
+isSp _ = False
avoidBadWrapsInList :: [Inline] -> [Inline]
avoidBadWrapsInList [] = []
@@ -1109,7 +1112,7 @@ inlineToMarkdown opts lnk@(Link attr txt (src, tit))
let useAuto = isURI src &&
case txt of
[Str s] | escapeURI s == srcSuffix -> True
- _ -> False
+ _ -> False
let useRefLinks = writerReferenceLinks opts && not useAuto
shortcutable <- asks envRefShortcutable
let useShortcutRefLinks = shortcutable &&
@@ -1160,5 +1163,5 @@ makeMathPlainer :: [Inline] -> [Inline]
makeMathPlainer = walk go
where
go (Emph xs) = Span nullAttr xs
- go x = x
+ go x = x
diff --git a/src/Text/Pandoc/Writers/Math.hs b/src/Text/Pandoc/Writers/Math.hs
index b7419ddf9..104d3c20b 100644
--- a/src/Text/Pandoc/Writers/Math.hs
+++ b/src/Text/Pandoc/Writers/Math.hs
@@ -7,7 +7,7 @@ where
import Text.Pandoc.Class
import Text.Pandoc.Definition
import Text.Pandoc.Logging
-import Text.TeXMath (Exp, writePandoc, DisplayType(..), readTeX)
+import Text.TeXMath (DisplayType (..), Exp, readTeX, writePandoc)
-- | Converts a raw TeX math formula to a list of 'Pandoc' inlines.
-- Defaults to raw formula between @$@ or @$$@ characters if entire formula
diff --git a/src/Text/Pandoc/Writers/MediaWiki.hs b/src/Text/Pandoc/Writers/MediaWiki.hs
index 22f56d4a8..cb36df5f5 100644
--- a/src/Text/Pandoc/Writers/MediaWiki.hs
+++ b/src/Text/Pandoc/Writers/MediaWiki.hs
@@ -30,30 +30,30 @@ Conversion of 'Pandoc' documents to MediaWiki markup.
MediaWiki: <http://www.mediawiki.org/wiki/MediaWiki>
-}
module Text.Pandoc.Writers.MediaWiki ( writeMediaWiki ) where
+import Control.Monad.Reader
+import Control.Monad.State
+import Data.List (intercalate)
+import qualified Data.Set as Set
+import Network.URI (isURI)
+import Text.Pandoc.Class (PandocMonad)
import Text.Pandoc.Definition
+import Text.Pandoc.ImageSize
import Text.Pandoc.Options
-import Text.Pandoc.Shared
-import Text.Pandoc.Writers.Shared
import Text.Pandoc.Pretty (render)
-import Text.Pandoc.ImageSize
+import Text.Pandoc.Shared
import Text.Pandoc.Templates (renderTemplate')
-import Text.Pandoc.XML ( escapeStringForXML )
-import Data.List ( intercalate )
-import qualified Data.Set as Set
-import Network.URI ( isURI )
-import Control.Monad.Reader
-import Control.Monad.State
-import Text.Pandoc.Class (PandocMonad)
+import Text.Pandoc.Writers.Shared
+import Text.Pandoc.XML (escapeStringForXML)
data WriterState = WriterState {
- stNotes :: Bool -- True if there are notes
- , stOptions :: WriterOptions -- writer options
+ stNotes :: Bool -- True if there are notes
+ , stOptions :: WriterOptions -- writer options
}
data WriterReader = WriterReader {
- options :: WriterOptions -- Writer options
- , listLevel :: String -- String at beginning of list items, e.g. "**"
- , useTags :: Bool -- True if we should use HTML tags because we're in a complex list
+ options :: WriterOptions -- Writer options
+ , listLevel :: String -- String at beginning of list items, e.g. "**"
+ , useTags :: Bool -- True if we should use HTML tags because we're in a complex list
}
type MediaWikiWriter = ReaderT WriterReader (State WriterState)
@@ -253,18 +253,18 @@ isSimpleListItem :: [Block] -> Bool
isSimpleListItem [] = True
isSimpleListItem [x] =
case x of
- Plain _ -> True
- Para _ -> True
- BulletList _ -> isSimpleList x
- OrderedList _ _ -> isSimpleList x
- DefinitionList _ -> isSimpleList x
- _ -> False
+ Plain _ -> True
+ Para _ -> True
+ BulletList _ -> isSimpleList x
+ OrderedList _ _ -> isSimpleList x
+ DefinitionList _ -> isSimpleList x
+ _ -> False
isSimpleListItem [x, y] | isPlainOrPara x =
case y of
- BulletList _ -> isSimpleList y
- OrderedList _ _ -> isSimpleList y
- DefinitionList _ -> isSimpleList y
- _ -> False
+ BulletList _ -> isSimpleList y
+ OrderedList _ _ -> isSimpleList y
+ DefinitionList _ -> isSimpleList y
+ _ -> False
isSimpleListItem _ = False
isPlainOrPara :: Block -> Bool
@@ -322,7 +322,7 @@ imageToMediaWiki attr = do
let (_, cls, _) = attr
toPx = fmap (showInPixel opts) . checkPct
checkPct (Just (Percent _)) = Nothing
- checkPct maybeDim = maybeDim
+ checkPct maybeDim = maybeDim
go (Just w) Nothing = '|':w ++ "px"
go (Just w) (Just h) = '|':w ++ "x" ++ h ++ "px"
go Nothing (Just h) = "|x" ++ h ++ "px"
diff --git a/src/Text/Pandoc/Writers/Native.hs b/src/Text/Pandoc/Writers/Native.hs
index 2421fd94d..b031a0231 100644
--- a/src/Text/Pandoc/Writers/Native.hs
+++ b/src/Text/Pandoc/Writers/Native.hs
@@ -30,11 +30,11 @@ Conversion of a 'Pandoc' document to a string representation.
-}
module Text.Pandoc.Writers.Native ( writeNative )
where
-import Text.Pandoc.Options ( WriterOptions(..), WrapOption(..) )
-import Data.List ( intersperse )
+import Data.List (intersperse)
+import Text.Pandoc.Class (PandocMonad)
import Text.Pandoc.Definition
+import Text.Pandoc.Options (WrapOption (..), WriterOptions (..))
import Text.Pandoc.Pretty
-import Text.Pandoc.Class (PandocMonad)
prettyList :: [Doc] -> Doc
prettyList ds =
diff --git a/src/Text/Pandoc/Writers/ODT.hs b/src/Text/Pandoc/Writers/ODT.hs
index b37739435..395ef0a96 100644
--- a/src/Text/Pandoc/Writers/ODT.hs
+++ b/src/Text/Pandoc/Writers/ODT.hs
@@ -29,30 +29,30 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
Conversion of 'Pandoc' documents to ODT.
-}
module Text.Pandoc.Writers.ODT ( writeODT ) where
-import Data.List ( isPrefixOf )
-import Data.Maybe ( fromMaybe )
-import Text.XML.Light.Output
-import Text.TeXMath
-import qualified Data.ByteString.Lazy as B
-import Text.Pandoc.UTF8 ( fromStringLazy )
import Codec.Archive.Zip
-import Text.Pandoc.Options ( WriterOptions(..), WrapOption(..) )
-import Text.Pandoc.Shared ( stringify )
-import Text.Pandoc.ImageSize
-import Text.Pandoc.MIME ( getMimeType, extensionFromMimeType )
-import Text.Pandoc.Definition
-import Text.Pandoc.Walk
-import Text.Pandoc.Writers.Shared ( fixDisplayMath )
-import Text.Pandoc.Writers.OpenDocument ( writeOpenDocument )
-import Control.Monad.State
import Control.Monad.Except (catchError)
-import Text.Pandoc.Error (PandocError(..))
-import Text.Pandoc.XML
-import Text.Pandoc.Pretty
-import System.FilePath ( takeExtension, takeDirectory, (<.>))
-import Text.Pandoc.Class ( PandocMonad, report )
+import Control.Monad.State
+import qualified Data.ByteString.Lazy as B
+import Data.List (isPrefixOf)
+import Data.Maybe (fromMaybe)
+import System.FilePath (takeDirectory, takeExtension, (<.>))
+import Text.Pandoc.Class (PandocMonad, report)
import qualified Text.Pandoc.Class as P
+import Text.Pandoc.Definition
+import Text.Pandoc.Error (PandocError (..))
+import Text.Pandoc.ImageSize
import Text.Pandoc.Logging
+import Text.Pandoc.MIME (extensionFromMimeType, getMimeType)
+import Text.Pandoc.Options (WrapOption (..), WriterOptions (..))
+import Text.Pandoc.Pretty
+import Text.Pandoc.Shared (stringify)
+import Text.Pandoc.UTF8 (fromStringLazy)
+import Text.Pandoc.Walk
+import Text.Pandoc.Writers.OpenDocument (writeOpenDocument)
+import Text.Pandoc.Writers.Shared (fixDisplayMath)
+import Text.Pandoc.XML
+import Text.TeXMath
+import Text.XML.Light.Output
data ODTState = ODTState { stEntries :: [Entry]
}
diff --git a/src/Text/Pandoc/Writers/OPML.hs b/src/Text/Pandoc/Writers/OPML.hs
index bc0cfc300..98510c40f 100644
--- a/src/Text/Pandoc/Writers/OPML.hs
+++ b/src/Text/Pandoc/Writers/OPML.hs
@@ -29,20 +29,20 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
Conversion of 'Pandoc' documents to OPML XML.
-}
module Text.Pandoc.Writers.OPML ( writeOPML) where
+import Control.Monad.Except (throwError)
+import qualified Text.Pandoc.Builder as B
+import Text.Pandoc.Class (PandocMonad)
+import Text.Pandoc.Compat.Time
import Text.Pandoc.Definition
-import Text.Pandoc.XML
-import Text.Pandoc.Writers.Shared
-import Text.Pandoc.Shared
+import Text.Pandoc.Error
import Text.Pandoc.Options
+import Text.Pandoc.Pretty
+import Text.Pandoc.Shared
import Text.Pandoc.Templates (renderTemplate')
import Text.Pandoc.Writers.HTML (writeHtml5String)
import Text.Pandoc.Writers.Markdown (writeMarkdown)
-import Text.Pandoc.Pretty
-import Text.Pandoc.Compat.Time
-import qualified Text.Pandoc.Builder as B
-import Text.Pandoc.Error
-import Control.Monad.Except (throwError)
-import Text.Pandoc.Class (PandocMonad)
+import Text.Pandoc.Writers.Shared
+import Text.Pandoc.XML
-- | Convert Pandoc document to string in OPML format.
writeOPML :: PandocMonad m => WriterOptions -> Pandoc -> m String
@@ -86,7 +86,7 @@ elementToOPML _ (Blk _) = return empty
elementToOPML opts (Sec _ _num _ title elements) = do
let isBlk :: Element -> Bool
isBlk (Blk _) = True
- isBlk _ = False
+ isBlk _ = False
fromBlk :: PandocMonad m => Element -> m Block
fromBlk (Blk x) = return x
diff --git a/src/Text/Pandoc/Writers/OpenDocument.hs b/src/Text/Pandoc/Writers/OpenDocument.hs
index 865faf37c..961bb981a 100644
--- a/src/Text/Pandoc/Writers/OpenDocument.hs
+++ b/src/Text/Pandoc/Writers/OpenDocument.hs
@@ -1,4 +1,6 @@
-{-# LANGUAGE PatternGuards, OverloadedStrings, FlexibleContexts #-}
+{-# LANGUAGE FlexibleContexts #-}
+{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE PatternGuards #-}
{-
Copyright (C) 2008-2015 Andrea Rossato <andrea.rossato@ing.unitn.it>
and John MacFarlane.
@@ -30,29 +32,29 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
Conversion of 'Pandoc' documents to OpenDocument XML.
-}
module Text.Pandoc.Writers.OpenDocument ( writeOpenDocument ) where
+import Control.Arrow ((***), (>>>))
+import Control.Monad.State hiding (when)
+import Data.Char (chr)
+import Data.List (sortBy)
+import qualified Data.Map as Map
+import Data.Ord (comparing)
+import qualified Data.Set as Set
+import Text.Pandoc.Class (PandocMonad, report)
import Text.Pandoc.Definition
+import Text.Pandoc.Logging
import Text.Pandoc.Options
-import Text.Pandoc.XML
+import Text.Pandoc.Pretty
import Text.Pandoc.Shared (linesToPara)
import Text.Pandoc.Templates (renderTemplate')
import Text.Pandoc.Writers.Math
-import Text.Pandoc.Pretty
-import Text.Printf ( printf )
-import Control.Arrow ( (***), (>>>) )
-import Control.Monad.State hiding ( when )
-import Data.Char (chr)
-import qualified Data.Set as Set
-import qualified Data.Map as Map
import Text.Pandoc.Writers.Shared
-import Data.List (sortBy)
-import Data.Ord (comparing)
-import Text.Pandoc.Class (PandocMonad, report)
-import Text.Pandoc.Logging
+import Text.Pandoc.XML
+import Text.Printf (printf)
-- | Auxiliary function to convert Plain block to Para.
plainToPara :: Block -> Block
plainToPara (Plain x) = Para x
-plainToPara x = x
+plainToPara x = x
--
-- OpenDocument writer
@@ -426,10 +428,10 @@ toChunks o (x : xs)
where (ys, zs) = span isChunkable xs
isChunkable :: Inline -> Bool
-isChunkable (Str _) = True
-isChunkable Space = True
+isChunkable (Str _) = True
+isChunkable Space = True
isChunkable SoftBreak = True
-isChunkable _ = False
+isChunkable _ = False
-- | Convert an inline element to OpenDocument.
inlineToOpenDocument :: PandocMonad m => WriterOptions -> Inline -> OD m Doc
@@ -514,11 +516,11 @@ orderedListLevelStyle (s,n, d) (l,ls) =
,("style:num-suffix", ")")]
_ -> [("style:num-suffix", ".")]
format = case n of
- UpperAlpha -> "A"
- LowerAlpha -> "a"
- UpperRoman -> "I"
- LowerRoman -> "i"
- _ -> "1"
+ UpperAlpha -> "A"
+ LowerAlpha -> "a"
+ UpperRoman -> "I"
+ LowerRoman -> "i"
+ _ -> "1"
listStyle = inTags True "text:list-level-style-number"
([ ("text:level" , show $ 1 + length ls )
, ("text:style-name" , "Numbering_20_Symbols")
diff --git a/src/Text/Pandoc/Writers/Org.hs b/src/Text/Pandoc/Writers/Org.hs
index 848b273c3..50eeec09a 100644
--- a/src/Text/Pandoc/Writers/Org.hs
+++ b/src/Text/Pandoc/Writers/Org.hs
@@ -33,21 +33,21 @@ Conversion of 'Pandoc' documents to Emacs Org-Mode.
Org-Mode: <http://orgmode.org>
-}
module Text.Pandoc.Writers.Org ( writeOrg) where
+import Control.Monad.State
+import Data.Char (isAlphaNum, toLower)
+import Data.List (intersect, intersperse, isPrefixOf, partition, transpose)
+import Text.Pandoc.Class (PandocMonad)
import Text.Pandoc.Definition
import Text.Pandoc.Options
-import Text.Pandoc.Shared
-import Text.Pandoc.Writers.Shared
import Text.Pandoc.Pretty
+import Text.Pandoc.Shared
import Text.Pandoc.Templates (renderTemplate')
-import Data.Char ( isAlphaNum, toLower )
-import Data.List ( isPrefixOf, intersect, intersperse, partition, transpose )
-import Control.Monad.State
-import Text.Pandoc.Class (PandocMonad)
+import Text.Pandoc.Writers.Shared
data WriterState =
- WriterState { stNotes :: [[Block]]
- , stHasMath :: Bool
- , stOptions :: WriterOptions
+ WriterState { stNotes :: [[Block]]
+ , stHasMath :: Bool
+ , stOptions :: WriterOptions
}
-- | Convert Pandoc to Org.
@@ -352,9 +352,9 @@ inlineToOrg Space = return space
inlineToOrg SoftBreak = do
wrapText <- gets (writerWrapText . stOptions)
case wrapText of
- WrapPreserve -> return cr
- WrapAuto -> return space
- WrapNone -> return space
+ WrapPreserve -> return cr
+ WrapAuto -> return space
+ WrapNone -> return space
inlineToOrg (Link _ txt (src, _)) = do
case txt of
[Str x] | escapeURI x == src -> -- autolink
@@ -373,11 +373,11 @@ inlineToOrg (Note contents) = do
orgPath :: String -> String
orgPath src =
case src of
- [] -> mempty -- wiki link
- ('#':_) -> src -- internal link
- _ | isUrl src -> src
- _ | isFilePath src -> src
- _ -> "file:" <> src
+ [] -> mempty -- wiki link
+ ('#':_) -> src -- internal link
+ _ | isUrl src -> src
+ _ | isFilePath src -> src
+ _ -> "file:" <> src
where
isFilePath :: String -> Bool
isFilePath cs = any (`isPrefixOf` cs) ["/", "./", "../", "file:"]
diff --git a/src/Text/Pandoc/Writers/RST.hs b/src/Text/Pandoc/Writers/RST.hs
index 745ab7ce9..f1de2ab0e 100644
--- a/src/Text/Pandoc/Writers/RST.hs
+++ b/src/Text/Pandoc/Writers/RST.hs
@@ -31,20 +31,20 @@ Conversion of 'Pandoc' documents to reStructuredText.
reStructuredText: <http://docutils.sourceforge.net/rst.html>
-}
module Text.Pandoc.Writers.RST ( writeRST ) where
+import Control.Monad.State
+import Data.Char (isSpace, toLower)
+import Data.List (intersperse, isPrefixOf, stripPrefix, transpose)
+import Data.Maybe (fromMaybe)
+import Network.URI (isURI)
+import Text.Pandoc.Builder (deleteMeta)
+import Text.Pandoc.Class (PandocMonad)
import Text.Pandoc.Definition
+import Text.Pandoc.ImageSize
import Text.Pandoc.Options
+import Text.Pandoc.Pretty
import Text.Pandoc.Shared
-import Text.Pandoc.Writers.Shared
-import Text.Pandoc.ImageSize
import Text.Pandoc.Templates (renderTemplate')
-import Text.Pandoc.Builder (deleteMeta)
-import Data.Maybe (fromMaybe)
-import Data.List ( isPrefixOf, stripPrefix, intersperse, transpose )
-import Network.URI (isURI)
-import Text.Pandoc.Pretty
-import Control.Monad.State
-import Data.Char (isSpace, toLower)
-import Text.Pandoc.Class (PandocMonad)
+import Text.Pandoc.Writers.Shared
type Refs = [([Inline], Target)]
@@ -76,7 +76,7 @@ pandocToRST (Pandoc meta blocks) = do
else Nothing
let subtit = case lookupMeta "subtitle" meta of
Just (MetaBlocks [Plain xs]) -> xs
- _ -> []
+ _ -> []
title <- titleToRST (docTitle meta) subtit
metadata <- metaToJSON opts
(fmap (render colwidth) . blockListToRST)
@@ -108,7 +108,7 @@ pandocToRST (Pandoc meta blocks) = do
Header lev a i:normalizeHeadings (lev+1) cont ++ normalizeHeadings lev bs'
where (cont,bs') = break (headerLtEq l) bs
headerLtEq level (Header l' _ _) = l' <= level
- headerLtEq _ _ = False
+ headerLtEq _ _ = False
normalizeHeadings lev (b:bs) = b:normalizeHeadings lev bs
normalizeHeadings _ [] = []
@@ -171,11 +171,11 @@ escapeString opts (c:cs) =
'-' | isEnabled Ext_smart opts ->
case cs of
'-':_ -> '\\':'-':escapeString opts cs
- _ -> '-':escapeString opts cs
+ _ -> '-':escapeString opts cs
'.' | isEnabled Ext_smart opts ->
case cs of
'.':'.':rest -> '\\':'.':'.':'.':escapeString opts rest
- _ -> '.':escapeString opts cs
+ _ -> '.':escapeString opts cs
_ -> c : escapeString opts cs
titleToRST :: [Inline] -> [Inline] -> State WriterState Doc
@@ -412,19 +412,19 @@ inlineListToRST lst =
okBeforeComplex (Str (c:_)) = isSpace c || c `elem` ("-:/'\"<([{–—" :: String)
okBeforeComplex _ = False
isComplex :: Inline -> Bool
- isComplex (Emph _) = True
- isComplex (Strong _) = True
- isComplex (SmallCaps _) = True
- isComplex (Strikeout _) = True
+ isComplex (Emph _) = True
+ isComplex (Strong _) = True
+ isComplex (SmallCaps _) = True
+ isComplex (Strikeout _) = True
isComplex (Superscript _) = True
- isComplex (Subscript _) = True
- isComplex (Link _ _ _) = True
- isComplex (Image _ _ _) = True
- isComplex (Code _ _) = True
- isComplex (Math _ _) = True
- isComplex (Cite _ (x:_)) = isComplex x
- isComplex (Span _ (x:_)) = isComplex x
- isComplex _ = False
+ isComplex (Subscript _) = True
+ isComplex (Link _ _ _) = True
+ isComplex (Image _ _ _) = True
+ isComplex (Code _ _) = True
+ isComplex (Math _ _) = True
+ isComplex (Cite _ (x:_)) = isComplex x
+ isComplex (Span _ (x:_)) = isComplex x
+ isComplex _ = False
-- | Convert Pandoc inline element to RST.
inlineToRST :: Inline -> State WriterState Doc
@@ -485,9 +485,9 @@ inlineToRST Space = return space
inlineToRST SoftBreak = do
wrapText <- gets $ writerWrapText . stOptions
case wrapText of
- WrapPreserve -> return cr
- WrapAuto -> return space
- WrapNone -> return space
+ WrapPreserve -> return cr
+ WrapAuto -> return space
+ WrapNone -> return space
-- autolink
inlineToRST (Link _ [Str str] (src, _))
| isURI src &&
diff --git a/src/Text/Pandoc/Writers/RTF.hs b/src/Text/Pandoc/Writers/RTF.hs
index 56d72afcb..67f0fc2e0 100644
--- a/src/Text/Pandoc/Writers/RTF.hs
+++ b/src/Text/Pandoc/Writers/RTF.hs
@@ -30,24 +30,24 @@ Conversion of 'Pandoc' documents to RTF (rich text format).
-}
module Text.Pandoc.Writers.RTF ( writeRTF
) where
+import Control.Monad.Except (catchError, throwError)
+import qualified Data.ByteString as B
+import Data.Char (chr, isDigit, ord)
+import Data.List (intercalate, isSuffixOf)
+import qualified Data.Map as M
+import Text.Pandoc.Class (PandocMonad, report)
+import qualified Text.Pandoc.Class as P
import Text.Pandoc.Definition
+import Text.Pandoc.Error
+import Text.Pandoc.ImageSize
+import Text.Pandoc.Logging
import Text.Pandoc.Options
import Text.Pandoc.Shared
-import Text.Pandoc.Writers.Shared
-import Text.Pandoc.Writers.Math
import Text.Pandoc.Templates (renderTemplate')
import Text.Pandoc.Walk
-import Text.Pandoc.Logging
-import Data.List ( isSuffixOf, intercalate )
-import Data.Char ( ord, chr, isDigit )
-import qualified Data.ByteString as B
-import qualified Data.Map as M
-import Text.Printf ( printf )
-import Text.Pandoc.ImageSize
-import Control.Monad.Except (throwError, catchError)
-import Text.Pandoc.Error
-import Text.Pandoc.Class (PandocMonad, report)
-import qualified Text.Pandoc.Class as P
+import Text.Pandoc.Writers.Math
+import Text.Pandoc.Writers.Shared
+import Text.Printf (printf)
-- | Convert Image inlines into a raw RTF embedded image, read from a file,
-- or a MediaBag, or the internet.
@@ -106,7 +106,7 @@ writeRTF options doc = do
Pandoc meta@(Meta metamap) blocks <- walkM (rtfEmbedImage options) doc
let spacer = not $ all null $ docTitle meta : docDate meta : docAuthors meta
let toPlain (MetaBlocks [Para ils]) = MetaInlines ils
- toPlain x = x
+ toPlain x = x
-- adjust title, author, date so we don't get para inside para
let meta' = Meta $ M.adjust toPlain "title"
. M.adjust toPlain "author"
@@ -118,7 +118,7 @@ writeRTF options doc = do
meta'
body <- blocksToRTF 0 AlignDefault blocks
let isTOCHeader (Header lev _ _) = lev <= writerTOCDepth options
- isTOCHeader _ = False
+ isTOCHeader _ = False
toc <- tableOfContents $ filter isTOCHeader blocks
let context = defField "body" body
$ defField "spacer" spacer
@@ -193,9 +193,9 @@ rtfParSpaced :: Int -- ^ space after (in twips)
-> String
rtfParSpaced spaceAfter indent firstLineIndent alignment content =
let alignString = case alignment of
- AlignLeft -> "\\ql "
- AlignRight -> "\\qr "
- AlignCenter -> "\\qc "
+ AlignLeft -> "\\ql "
+ AlignRight -> "\\qr "
+ AlignCenter -> "\\qc "
AlignDefault -> "\\ql "
in "{\\pard " ++ alignString ++
"\\f0 \\sa" ++ (show spaceAfter) ++ " \\li" ++ (show indent) ++
diff --git a/src/Text/Pandoc/Writers/Shared.hs b/src/Text/Pandoc/Writers/Shared.hs
index 3ff7d47b2..34bfa0b64 100644
--- a/src/Text/Pandoc/Writers/Shared.hs
+++ b/src/Text/Pandoc/Writers/Shared.hs
@@ -41,19 +41,20 @@ module Text.Pandoc.Writers.Shared (
, unsmartify
)
where
-import Text.Pandoc.Definition
-import Text.Pandoc.Pretty
-import Text.Pandoc.Options
-import Text.Pandoc.XML (escapeStringForXML)
import Control.Monad (liftM)
+import Data.Aeson (FromJSON (..), Result (..), ToJSON (..), Value (Object),
+ encode, fromJSON)
import qualified Data.HashMap.Strict as H
+import Data.List (groupBy)
import qualified Data.Map as M
+import Data.Maybe (isJust)
import qualified Data.Text as T
-import Data.Aeson (FromJSON(..), fromJSON, ToJSON (..), Value(Object), Result(..), encode)
-import Text.Pandoc.UTF8 (toStringLazy)
import qualified Data.Traversable as Traversable
-import Data.List ( groupBy )
-import Data.Maybe ( isJust )
+import Text.Pandoc.Definition
+import Text.Pandoc.Options
+import Text.Pandoc.Pretty
+import Text.Pandoc.UTF8 (toStringLazy)
+import Text.Pandoc.XML (escapeStringForXML)
-- | Create JSON value for template from a 'Meta' and an association list
-- of variables, specified at the command line or in the writer.
@@ -94,7 +95,7 @@ addVariablesToJSON opts metadata =
(writerVariables opts)
`combineMetadata` metadata
where combineMetadata (Object o1) (Object o2) = Object $ H.union o1 o2
- combineMetadata x _ = x
+ combineMetadata x _ = x
metaValueToJSON :: Monad m
=> ([Block] -> m String)
@@ -134,8 +135,8 @@ setField field val (Object hashmap) =
Object $ H.insertWith combine (T.pack field) (toJSON val) hashmap
where combine newval oldval =
case fromJSON oldval of
- Success xs -> toJSON $ xs ++ [newval]
- _ -> toJSON [oldval, newval]
+ Success xs -> toJSON $ xs ++ [newval]
+ _ -> toJSON [oldval, newval]
setField _ _ x = x
resetField :: ToJSON a
@@ -183,9 +184,9 @@ isDisplayMath _ = False
stripLeadingTrailingSpace :: [Inline] -> [Inline]
stripLeadingTrailingSpace = go . reverse . go . reverse
- where go (Space:xs) = xs
+ where go (Space:xs) = xs
go (SoftBreak:xs) = xs
- go xs = xs
+ go xs = xs
-- Put display math in its own block (for ODT/DOCX).
fixDisplayMath :: Block -> Block
diff --git a/src/Text/Pandoc/Writers/TEI.hs b/src/Text/Pandoc/Writers/TEI.hs
index a54d42c53..0ef283ad3 100644
--- a/src/Text/Pandoc/Writers/TEI.hs
+++ b/src/Text/Pandoc/Writers/TEI.hs
@@ -1,4 +1,5 @@
-{-# LANGUAGE OverloadedStrings, PatternGuards #-}
+{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE PatternGuards #-}
{-
Copyright (C) 2006-2015 John MacFarlane <jgm@berkeley.edu>
@@ -29,19 +30,19 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
Conversion of 'Pandoc' documents to Docbook XML.
-}
module Text.Pandoc.Writers.TEI (writeTEI) where
+import Data.Char (toLower)
+import Data.List (isPrefixOf, stripPrefix)
+import qualified Text.Pandoc.Builder as B
+import Text.Pandoc.Class (PandocMonad)
import Text.Pandoc.Definition
-import Text.Pandoc.XML
-import Text.Pandoc.Shared
-import Text.Pandoc.Writers.Shared
+import Text.Pandoc.Highlighting (languages, languagesByExtension)
+import Text.Pandoc.ImageSize
import Text.Pandoc.Options
-import Text.Pandoc.Templates (renderTemplate')
-import Data.List ( stripPrefix, isPrefixOf )
-import Data.Char ( toLower )
-import Text.Pandoc.Highlighting ( languages, languagesByExtension )
import Text.Pandoc.Pretty
-import Text.Pandoc.ImageSize
-import qualified Text.Pandoc.Builder as B
-import Text.Pandoc.Class ( PandocMonad )
+import Text.Pandoc.Shared
+import Text.Pandoc.Templates (renderTemplate')
+import Text.Pandoc.Writers.Shared
+import Text.Pandoc.XML
-- | Convert list of authors to a docbook <author> section
authorToTEI :: WriterOptions -> [Inline] -> B.Inlines
diff --git a/src/Text/Pandoc/Writers/Texinfo.hs b/src/Text/Pandoc/Writers/Texinfo.hs
index fe6024351..da4f43ee5 100644
--- a/src/Text/Pandoc/Writers/Texinfo.hs
+++ b/src/Text/Pandoc/Writers/Texinfo.hs
@@ -29,25 +29,25 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
Conversion of 'Pandoc' format into Texinfo.
-}
module Text.Pandoc.Writers.Texinfo ( writeTexinfo ) where
-import Text.Pandoc.Definition
-import Text.Pandoc.Options
-import Text.Pandoc.Shared
-import Text.Pandoc.Writers.Shared
-import Text.Pandoc.Templates (renderTemplate')
-import Text.Printf ( printf )
-import Data.List ( transpose, maximumBy )
-import Data.Ord ( comparing )
-import Data.Char ( chr, ord )
+import Control.Monad.Except (throwError)
import Control.Monad.State
-import Text.Pandoc.Pretty
-import Text.Pandoc.ImageSize
-import Network.URI ( isURI, unEscapeString )
-import System.FilePath
+import Data.Char (chr, ord)
+import Data.List (maximumBy, transpose)
+import Data.Ord (comparing)
import qualified Data.Set as Set
-import Control.Monad.Except (throwError)
-import Text.Pandoc.Error
+import Network.URI (isURI, unEscapeString)
+import System.FilePath
import Text.Pandoc.Class (PandocMonad, report)
+import Text.Pandoc.Definition
+import Text.Pandoc.Error
+import Text.Pandoc.ImageSize
import Text.Pandoc.Logging
+import Text.Pandoc.Options
+import Text.Pandoc.Pretty
+import Text.Pandoc.Shared
+import Text.Pandoc.Templates (renderTemplate')
+import Text.Pandoc.Writers.Shared
+import Text.Printf (printf)
data WriterState =
WriterState { stStrikeout :: Bool -- document contains strikeout
diff --git a/src/Text/Pandoc/Writers/Textile.hs b/src/Text/Pandoc/Writers/Textile.hs
index 6ec9e0b2f..625e8031b 100644
--- a/src/Text/Pandoc/Writers/Textile.hs
+++ b/src/Text/Pandoc/Writers/Textile.hs
@@ -30,18 +30,18 @@ Conversion of 'Pandoc' documents to Textile markup.
Textile: <http://thresholdstate.com/articles/4312/the-textile-reference-manual>
-}
module Text.Pandoc.Writers.Textile ( writeTextile ) where
+import Control.Monad.State
+import Data.Char (isSpace)
+import Data.List (intercalate)
+import Text.Pandoc.Class (PandocMonad)
import Text.Pandoc.Definition
+import Text.Pandoc.ImageSize
import Text.Pandoc.Options
-import Text.Pandoc.Shared
import Text.Pandoc.Pretty (render)
-import Text.Pandoc.ImageSize
-import Text.Pandoc.Writers.Shared
+import Text.Pandoc.Shared
import Text.Pandoc.Templates (renderTemplate')
-import Text.Pandoc.XML ( escapeStringForXML )
-import Data.List ( intercalate )
-import Control.Monad.State
-import Data.Char ( isSpace )
-import Text.Pandoc.Class ( PandocMonad )
+import Text.Pandoc.Writers.Shared
+import Text.Pandoc.XML (escapeStringForXML)
data WriterState = WriterState {
stNotes :: [String] -- Footnotes
@@ -302,16 +302,16 @@ isSimpleListItem :: [Block] -> Bool
isSimpleListItem [] = True
isSimpleListItem [x] =
case x of
- Plain _ -> True
- Para _ -> True
- BulletList _ -> isSimpleList x
- OrderedList _ _ -> isSimpleList x
- _ -> False
+ Plain _ -> True
+ Para _ -> True
+ BulletList _ -> isSimpleList x
+ OrderedList _ _ -> isSimpleList x
+ _ -> False
isSimpleListItem [x, y] | isPlainOrPara x =
case y of
- BulletList _ -> isSimpleList y
- OrderedList _ _ -> isSimpleList y
- _ -> False
+ BulletList _ -> isSimpleList y
+ OrderedList _ _ -> isSimpleList y
+ _ -> False
isSimpleListItem _ = False
isPlainOrPara :: Block -> Bool
@@ -334,9 +334,9 @@ tableRowToTextile :: WriterOptions
tableRowToTextile opts alignStrings rownum cols' = do
let celltype = if rownum == 0 then "th" else "td"
let rowclass = case rownum of
- 0 -> "header"
+ 0 -> "header"
x | x `rem` 2 == 1 -> "odd"
- _ -> "even"
+ _ -> "even"
cols'' <- sequence $ zipWith
(\alignment item -> tableItemToTextile opts celltype alignment item)
alignStrings cols'
diff --git a/src/Text/Pandoc/Writers/ZimWiki.hs b/src/Text/Pandoc/Writers/ZimWiki.hs
index a7d30fec6..19f476a17 100644
--- a/src/Text/Pandoc/Writers/ZimWiki.hs
+++ b/src/Text/Pandoc/Writers/ZimWiki.hs
@@ -31,27 +31,27 @@ http://zim-wiki.org/manual/Help/Wiki_Syntax.html
-}
module Text.Pandoc.Writers.ZimWiki ( writeZimWiki ) where
+import Control.Monad (zipWithM)
+import Control.Monad.State (State, evalState, gets, modify)
+import Data.Default (Default (..))
+import Data.List (intercalate, isInfixOf, isPrefixOf, transpose)
+import qualified Data.Map as Map
+import Data.Text (breakOnAll, pack)
+import Network.URI (isURI)
+import Text.Pandoc.Class (PandocMonad)
import Text.Pandoc.Definition
-import Text.Pandoc.Options ( WriterOptions(writerTableOfContents, writerTemplate, writerWrapText), WrapOption(..) )
-import Text.Pandoc.Shared ( escapeURI, linesToPara, removeFormatting, trimr
- , substitute )
-import Text.Pandoc.Writers.Shared ( defField, metaToJSON )
import Text.Pandoc.ImageSize
-import Text.Pandoc.Templates ( renderTemplate' )
-import Data.List ( intercalate, isPrefixOf, transpose, isInfixOf )
-import Data.Text ( breakOnAll, pack )
-import Data.Default (Default(..))
-import Network.URI ( isURI )
-import Control.Monad ( zipWithM )
-import Control.Monad.State ( modify, State, gets, evalState )
-import Text.Pandoc.Class ( PandocMonad )
-import qualified Data.Map as Map
+import Text.Pandoc.Options (WrapOption (..), WriterOptions (writerTableOfContents, writerTemplate, writerWrapText))
+import Text.Pandoc.Shared (escapeURI, linesToPara, removeFormatting, substitute,
+ trimr)
+import Text.Pandoc.Templates (renderTemplate')
+import Text.Pandoc.Writers.Shared (defField, metaToJSON)
data WriterState = WriterState {
- stItemNum :: Int,
- stIndent :: String, -- Indent after the marker at the beginning of list items
- stInTable :: Bool, -- Inside a table
- stInLink :: Bool -- Inside a link description
+ stItemNum :: Int,
+ stIndent :: String, -- Indent after the marker at the beginning of list items
+ stInTable :: Bool, -- Inside a table
+ stInLink :: Bool -- Inside a link description
}
instance Default WriterState where
@@ -139,7 +139,7 @@ blockToZimWiki _ (CodeBlock (_,classes,_) str) = do
(x:_) -> "{{{code: lang=\"" ++
(case Map.lookup x langmap of
Nothing -> x
- Just y -> y) ++ "\" linenumbers=\"True\"\n" ++ str ++ "\n}}}\n" -- for zim's code plugin, go verbatim on the lang spec
+ Just y -> y) ++ "\" linenumbers=\"True\"\n" ++ str ++ "\n}}}\n" -- for zim's code plugin, go verbatim on the lang spec
blockToZimWiki opts (BlockQuote blocks) = do
contents <- blockListToZimWiki opts blocks
@@ -319,7 +319,7 @@ inlineToZimWiki _ (Str str) = do
inTable <- gets stInTable
inLink <- gets stInLink
if inTable
- then return $ substitute "|" "\\|" . escapeString $ str
+ then return $ substitute "|" "\\|" . escapeString $ str
else
if inLink
then return $ str
@@ -371,10 +371,10 @@ inlineToZimWiki opts (Image attr alt (source, tit)) = do
alt' <- inlineListToZimWiki opts alt
inTable <- gets stInTable
let txt = case (tit, alt, inTable) of
- ("",[], _) -> ""
+ ("",[], _) -> ""
("", _, False ) -> "|" ++ alt'
(_ , _, False ) -> "|" ++ tit
- (_ , _, True ) -> ""
+ (_ , _, True ) -> ""
-- Relative links fail isURI and receive a colon
prefix = if isURI source then "" else ":"
return $ "{{" ++ prefix ++ source ++ imageDims opts attr ++ txt ++ "}}"
@@ -389,7 +389,7 @@ imageDims opts attr = go (toPx $ dimension Width attr) (toPx $ dimension Height
where
toPx = fmap (showInPixel opts) . checkPct
checkPct (Just (Percent _)) = Nothing
- checkPct maybeDim = maybeDim
+ checkPct maybeDim = maybeDim
go (Just w) Nothing = "?" ++ w
go (Just w) (Just h) = "?" ++ w ++ "x" ++ h
go Nothing (Just h) = "?0x" ++ h
diff --git a/src/Text/Pandoc/XML.hs b/src/Text/Pandoc/XML.hs
index e105aee91..d7fdc4278 100644
--- a/src/Text/Pandoc/XML.hs
+++ b/src/Text/Pandoc/XML.hs
@@ -36,18 +36,18 @@ module Text.Pandoc.XML ( escapeCharForXML,
toEntities,
fromEntities ) where
-import Text.Pandoc.Pretty
-import Data.Char (ord, isAscii, isSpace)
+import Data.Char (isAscii, isSpace, ord)
import Text.HTML.TagSoup.Entity (lookupEntity)
+import Text.Pandoc.Pretty
-- | Escape one character as needed for XML.
escapeCharForXML :: Char -> String
escapeCharForXML x = case x of
- '&' -> "&amp;"
- '<' -> "&lt;"
- '>' -> "&gt;"
- '"' -> "&quot;"
- c -> [c]
+ '&' -> "&amp;"
+ '<' -> "&lt;"
+ '>' -> "&gt;"
+ '"' -> "&quot;"
+ c -> [c]
-- | Escape string as needed for XML. Entity references are not preserved.
escapeStringForXML :: String -> String
@@ -108,8 +108,8 @@ fromEntities ('&':xs) =
(zs, ys) -> (zs,ys)
ent' = case ent of
'#':'X':ys -> '#':'x':ys -- workaround tagsoup bug
- '#':_ -> ent
- _ -> ent ++ ";"
+ '#':_ -> ent
+ _ -> ent ++ ";"
fromEntities (x:xs) = x : fromEntities xs
fromEntities [] = []