Revert "Use -XNoImplicitPrelude and 'import Prelude' explicitly."
This reverts commit c423dbb5a3
.
This commit is contained in:
parent
777d717d22
commit
23b693c029
109 changed files with 12 additions and 118 deletions
|
@ -15,7 +15,6 @@ You should have received a copy of the GNU General Public License
|
|||
along with this program; if not, write to the Free Software
|
||||
Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
|
||||
-}
|
||||
import Prelude
|
||||
import Text.Pandoc
|
||||
import Criterion.Main
|
||||
import Criterion.Types (Config(..))
|
||||
|
|
|
@ -303,7 +303,7 @@ Library
|
|||
other-modules: Text.Pandoc.Data
|
||||
if os(windows)
|
||||
Cpp-options: -D_WINDOWS
|
||||
Ghc-Options: -rtsopts -Wall -fno-warn-unused-do-bind -XNoImplicitPrelude
|
||||
Ghc-Options: -rtsopts -Wall -fno-warn-unused-do-bind
|
||||
Ghc-Prof-Options: -fprof-auto-exported -rtsopts
|
||||
Default-Language: Haskell98
|
||||
Other-Extensions: PatternGuards, OverloadedStrings,
|
||||
|
@ -420,7 +420,7 @@ Executable pandoc
|
|||
Build-Depends: network-uri >= 2.6 && < 2.7, network >= 2.6
|
||||
else
|
||||
Build-Depends: network >= 2 && < 2.6
|
||||
Ghc-Options: -rtsopts -with-rtsopts=-K16m -Wall -fno-warn-unused-do-bind -XNoImplicitPrelude
|
||||
Ghc-Options: -rtsopts -with-rtsopts=-K16m -Wall -fno-warn-unused-do-bind
|
||||
Ghc-Prof-Options: -fprof-auto-exported -rtsopts -with-rtsopts=-K16m
|
||||
if os(windows)
|
||||
Cpp-options: -D_WINDOWS
|
||||
|
@ -496,7 +496,7 @@ Test-Suite test-pandoc
|
|||
Tests.Writers.Docx
|
||||
Tests.Writers.RST
|
||||
Prelude
|
||||
Ghc-Options: -rtsopts -Wall -fno-warn-unused-do-bind -threaded -XNoImplicitPrelude
|
||||
Ghc-Options: -rtsopts -Wall -fno-warn-unused-do-bind -threaded
|
||||
Default-Language: Haskell98
|
||||
|
||||
benchmark benchmark-pandoc
|
||||
|
@ -507,6 +507,6 @@ benchmark benchmark-pandoc
|
|||
base >= 4.2 && < 5,
|
||||
syb >= 0.1 && < 0.7,
|
||||
criterion >= 1.0 && < 1.2
|
||||
Ghc-Options: -rtsopts -Wall -fno-warn-unused-do-bind -XNoImplicitPrelude
|
||||
Ghc-Options: -rtsopts -Wall -fno-warn-unused-do-bind
|
||||
Default-Language: Haskell98
|
||||
Other-Modules: Prelude
|
||||
|
|
|
@ -30,7 +30,6 @@ Parses command-line options and calls the appropriate readers and
|
|||
writers.
|
||||
-}
|
||||
module Main where
|
||||
import Prelude
|
||||
import Text.Pandoc
|
||||
import Text.Pandoc.Builder (setMeta)
|
||||
import Text.Pandoc.PDF (makePDF)
|
||||
|
|
|
@ -150,7 +150,6 @@ import Text.Pandoc.Writers.RST
|
|||
import Text.Pandoc.Writers.LaTeX
|
||||
import Text.Pandoc.Writers.ConTeXt
|
||||
import Text.Pandoc.Writers.Texinfo
|
||||
import Prelude
|
||||
import Text.Pandoc.Writers.HTML
|
||||
import Text.Pandoc.Writers.ODT
|
||||
import Text.Pandoc.Writers.Docx
|
||||
|
|
|
@ -30,7 +30,6 @@ ascii equivalents (used in constructing HTML identifiers).
|
|||
-}
|
||||
module Text.Pandoc.Asciify (toAsciiChar)
|
||||
where
|
||||
import Prelude
|
||||
import qualified Data.Map as M
|
||||
import Data.Char (isAscii)
|
||||
|
||||
|
|
|
@ -3,7 +3,6 @@ module Text.Pandoc.CSS ( foldOrElse,
|
|||
)
|
||||
where
|
||||
|
||||
import Prelude
|
||||
import Text.Pandoc.Shared (trim)
|
||||
import Text.Parsec
|
||||
import Text.Parsec.String
|
||||
|
|
|
@ -5,6 +5,7 @@ module Text.Pandoc.Compat.Directory ( getModificationTime )
|
|||
#if MIN_VERSION_directory(1,2,0)
|
||||
import System.Directory
|
||||
|
||||
|
||||
#else
|
||||
import qualified System.Directory as S
|
||||
import Data.Time.Clock (UTCTime)
|
||||
|
|
|
@ -9,7 +9,6 @@ module Text.Pandoc.Compat.Except ( ExceptT
|
|||
, catchError )
|
||||
where
|
||||
|
||||
import Prelude
|
||||
#if MIN_VERSION_mtl(2,2,1)
|
||||
import Control.Monad.Except
|
||||
|
||||
|
|
|
@ -2,7 +2,6 @@
|
|||
module Text.Pandoc.Compat.TagSoupEntity (lookupEntity
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import qualified Text.HTML.TagSoup.Entity as TE
|
||||
|
||||
lookupEntity :: String -> Maybe Char
|
||||
|
|
|
@ -31,7 +31,6 @@ during parsing.
|
|||
-}
|
||||
module Text.Pandoc.Error (PandocError(..), handleError) where
|
||||
|
||||
import Prelude
|
||||
import Text.Parsec.Error
|
||||
import Text.Parsec.Pos hiding (Line)
|
||||
import Text.Pandoc.Compat.Except
|
||||
|
|
|
@ -48,7 +48,6 @@ module Text.Pandoc.Highlighting ( languages
|
|||
, fromListingsLanguage
|
||||
, toListingsLanguage
|
||||
) where
|
||||
import Prelude
|
||||
import Text.Pandoc.Definition
|
||||
import Text.Pandoc.Shared (safeRead)
|
||||
import Text.Highlighting.Kate
|
||||
|
|
|
@ -31,7 +31,6 @@ Functions for determining the size of a PNG, JPEG, or GIF image.
|
|||
-}
|
||||
module Text.Pandoc.ImageSize ( ImageType(..), imageType, imageSize,
|
||||
sizeInPixels, sizeInPoints ) where
|
||||
import Prelude
|
||||
import Data.ByteString (ByteString, unpack)
|
||||
import qualified Data.ByteString.Char8 as B
|
||||
import qualified Data.ByteString.Lazy as BL
|
||||
|
|
|
@ -29,7 +29,6 @@ Mime type lookup for ODT writer.
|
|||
-}
|
||||
module Text.Pandoc.MIME ( MimeType, getMimeType, getMimeTypeDef,
|
||||
extensionFromMimeType )where
|
||||
import Prelude
|
||||
import System.FilePath
|
||||
import Data.Char ( toLower )
|
||||
import Data.List (isPrefixOf, isSuffixOf)
|
||||
|
|
|
@ -36,7 +36,6 @@ module Text.Pandoc.MediaBag (
|
|||
mediaDirectory,
|
||||
extractMediaBag
|
||||
) where
|
||||
import Prelude
|
||||
import System.FilePath
|
||||
import qualified System.FilePath.Posix as Posix
|
||||
import System.Directory (createDirectoryIfMissing)
|
||||
|
|
|
@ -47,7 +47,6 @@ module Text.Pandoc.Options ( Extension(..)
|
|||
, def
|
||||
, isEnabled
|
||||
) where
|
||||
import Prelude
|
||||
import Data.Set (Set)
|
||||
import qualified Data.Set as Set
|
||||
import Data.Default
|
||||
|
|
|
@ -30,7 +30,6 @@ Conversion of LaTeX documents to PDF.
|
|||
-}
|
||||
module Text.Pandoc.PDF ( makePDF ) where
|
||||
|
||||
import Prelude
|
||||
import Data.ByteString.Lazy (ByteString)
|
||||
import qualified Data.ByteString.Lazy as B
|
||||
import qualified Data.ByteString.Lazy.Char8 as BC
|
||||
|
|
|
@ -180,7 +180,6 @@ import Data.Char ( toLower, toUpper, ord, chr, isAscii, isAlphaNum,
|
|||
isHexDigit, isSpace )
|
||||
import Data.List ( intercalate, transpose, isSuffixOf )
|
||||
import Text.Pandoc.Shared
|
||||
import Prelude
|
||||
import qualified Data.Map as M
|
||||
import Text.TeXMath.Readers.TeX.Macros (applyMacros, Macro,
|
||||
parseMacroDefinitions)
|
||||
|
|
|
@ -74,7 +74,6 @@ module Text.Pandoc.Pretty (
|
|||
)
|
||||
|
||||
where
|
||||
import Prelude
|
||||
import Data.Sequence (Seq, fromList, (<|), singleton, mapWithIndex, viewl, ViewL(..))
|
||||
import Data.Foldable (toList)
|
||||
import Data.List (intercalate)
|
||||
|
|
|
@ -29,7 +29,6 @@ ByteString variant of 'readProcessWithExitCode'.
|
|||
-}
|
||||
module Text.Pandoc.Process (pipeProcess)
|
||||
where
|
||||
import Prelude
|
||||
import System.Process
|
||||
import System.Exit (ExitCode (..))
|
||||
import Control.Exception
|
||||
|
|
|
@ -32,7 +32,6 @@ CommonMark is a strongly specified variant of Markdown: http://commonmark.org.
|
|||
module Text.Pandoc.Readers.CommonMark (readCommonMark)
|
||||
where
|
||||
|
||||
import Prelude
|
||||
import CMark
|
||||
import Data.Text (unpack, pack)
|
||||
import Data.List (groupBy)
|
||||
|
|
|
@ -1,5 +1,4 @@
|
|||
module Text.Pandoc.Readers.DocBook ( readDocBook ) where
|
||||
import Prelude
|
||||
import Data.Char (toUpper)
|
||||
import Text.Pandoc.Shared (safeRead)
|
||||
import Text.Pandoc.Options
|
||||
|
|
|
@ -74,7 +74,6 @@ module Text.Pandoc.Readers.Docx
|
|||
( readDocx
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Codec.Archive.Zip
|
||||
import Text.Pandoc.Definition
|
||||
import Text.Pandoc.Options
|
||||
|
|
|
@ -29,7 +29,6 @@ Utilities to convert between font codepoints and unicode characters.
|
|||
-}
|
||||
module Text.Pandoc.Readers.Docx.Fonts (getUnicode, Font(..)) where
|
||||
|
||||
import Prelude
|
||||
|
||||
-- | Enumeration of recognised fonts
|
||||
data Font = Symbol -- ^ <http://en.wikipedia.org/wiki/Symbol_(typeface) Adobe Symbol>
|
||||
|
|
|
@ -33,7 +33,6 @@ module Text.Pandoc.Readers.Docx.Lists ( blocksToBullets
|
|||
, listParagraphDivs
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Text.Pandoc.JSON
|
||||
import Text.Pandoc.Generic (bottomUp)
|
||||
import Text.Pandoc.Shared (trim)
|
||||
|
|
|
@ -50,7 +50,6 @@ module Text.Pandoc.Readers.Docx.Parse ( Docx(..)
|
|||
, Cell(..)
|
||||
, archiveToDocx
|
||||
) where
|
||||
import Prelude
|
||||
import Codec.Archive.Zip
|
||||
import Text.XML.Light
|
||||
import Data.Maybe
|
||||
|
|
|
@ -7,7 +7,6 @@ module Text.Pandoc.Readers.Docx.Reducible ( concatReduce
|
|||
where
|
||||
|
||||
|
||||
import Prelude
|
||||
import Text.Pandoc.Builder
|
||||
import Data.List
|
||||
import Data.Sequence (ViewR(..), ViewL(..), viewl, viewr)
|
||||
|
|
|
@ -5,7 +5,6 @@ module Text.Pandoc.Readers.Docx.StyleMap ( StyleMaps(..)
|
|||
, hasStyleName
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Text.XML.Light
|
||||
import Text.Pandoc.Readers.Docx.Util
|
||||
import Control.Monad.State
|
||||
|
|
|
@ -5,7 +5,6 @@ module Text.Pandoc.Readers.Docx.Util (
|
|||
, elemToNameSpaces
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Text.XML.Light
|
||||
import Data.Maybe (mapMaybe)
|
||||
|
||||
|
|
|
@ -8,7 +8,6 @@ module Text.Pandoc.Readers.EPUB
|
|||
(readEPUB)
|
||||
where
|
||||
|
||||
import Prelude
|
||||
import Text.XML.Light
|
||||
import Text.Pandoc.Definition hiding (Attr)
|
||||
import Text.Pandoc.Walk (walk, query)
|
||||
|
|
|
@ -38,7 +38,6 @@ module Text.Pandoc.Readers.HTML ( readHtml
|
|||
, isCommentTag
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Text.HTML.TagSoup
|
||||
import Text.HTML.TagSoup.Match
|
||||
import Text.Pandoc.Definition
|
||||
|
|
|
@ -14,7 +14,6 @@ module Text.Pandoc.Readers.Haddock
|
|||
( readHaddock
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Text.Pandoc.Builder (Blocks, Inlines)
|
||||
import qualified Text.Pandoc.Builder as B
|
||||
import Text.Pandoc.Shared (trim, splitBy)
|
||||
|
@ -130,7 +129,7 @@ makeExample prompt expression result =
|
|||
<> (mconcat $ intersperse B.linebreak $ map coder result')
|
||||
where
|
||||
-- 1. drop trailing whitespace from the prompt, remember the prefix
|
||||
prefix = takeWhile (`elem` [' ','\t']) prompt
|
||||
prefix = takeWhile (`elem` " \t") prompt
|
||||
|
||||
-- 2. drop, if possible, the exact same sequence of whitespace
|
||||
-- characters from each result line
|
||||
|
|
|
@ -35,7 +35,6 @@ module Text.Pandoc.Readers.LaTeX ( readLaTeX,
|
|||
handleIncludes
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Text.Pandoc.Definition
|
||||
import Text.Pandoc.Walk
|
||||
import Text.Pandoc.Shared
|
||||
|
|
|
@ -32,7 +32,6 @@ Conversion of markdown-formatted plain text to 'Pandoc' document.
|
|||
module Text.Pandoc.Readers.Markdown ( readMarkdown,
|
||||
readMarkdownWithWarnings ) where
|
||||
|
||||
import Prelude
|
||||
import Data.List ( transpose, sortBy, findIndex, intersperse, intercalate )
|
||||
import qualified Data.Map as M
|
||||
import Data.Scientific (coefficient, base10Exponent)
|
||||
|
|
|
@ -36,7 +36,6 @@ _ parse templates?
|
|||
-}
|
||||
module Text.Pandoc.Readers.MediaWiki ( readMediaWiki ) where
|
||||
|
||||
import Prelude
|
||||
import Text.Pandoc.Definition
|
||||
import qualified Text.Pandoc.Builder as B
|
||||
import Text.Pandoc.Builder (Inlines, Blocks, trimInlines)
|
||||
|
|
|
@ -30,7 +30,6 @@ Conversion of a string representation of a pandoc type (@Pandoc@,
|
|||
-}
|
||||
module Text.Pandoc.Readers.Native ( readNative ) where
|
||||
|
||||
import Prelude
|
||||
import Text.Pandoc.Definition
|
||||
import Text.Pandoc.Shared (safeRead)
|
||||
|
||||
|
|
|
@ -1,6 +1,5 @@
|
|||
{-# LANGUAGE FlexibleContexts #-}
|
||||
module Text.Pandoc.Readers.OPML ( readOPML ) where
|
||||
import Prelude
|
||||
import Data.Char (toUpper)
|
||||
import Text.Pandoc.Options
|
||||
import Text.Pandoc.Definition
|
||||
|
|
|
@ -32,7 +32,6 @@ Entry point to the odt reader.
|
|||
|
||||
module Text.Pandoc.Readers.Odt ( readOdt ) where
|
||||
|
||||
import Prelude
|
||||
import Codec.Archive.Zip
|
||||
import qualified Text.XML.Light as XML
|
||||
|
||||
|
|
|
@ -39,7 +39,6 @@ with an equivalent return value.
|
|||
-- We export everything
|
||||
module Text.Pandoc.Readers.Odt.Arrows.Utils where
|
||||
|
||||
import Prelude
|
||||
import Control.Arrow
|
||||
import Control.Monad ( join, MonadPlus(..) )
|
||||
|
||||
|
|
|
@ -39,7 +39,6 @@ module Text.Pandoc.Readers.Odt.ContentReader
|
|||
, read_body
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Control.Arrow
|
||||
import Control.Applicative hiding ( liftA, liftA2, liftA3 )
|
||||
|
||||
|
|
|
@ -39,7 +39,6 @@ compatible instances of "ArrowChoice".
|
|||
-- We export everything
|
||||
module Text.Pandoc.Readers.Odt.Generic.Fallible where
|
||||
|
||||
import Prelude
|
||||
import Control.Applicative
|
||||
import Control.Monad
|
||||
|
||||
|
|
|
@ -31,7 +31,6 @@ typesafe Haskell namespace identifiers and unsafe "real world" namespaces.
|
|||
|
||||
module Text.Pandoc.Readers.Odt.Generic.Namespaces where
|
||||
|
||||
import Prelude
|
||||
import qualified Data.Map as M
|
||||
|
||||
--
|
||||
|
|
|
@ -30,7 +30,6 @@ A map of values to sets of values.
|
|||
|
||||
module Text.Pandoc.Readers.Odt.Generic.SetMap where
|
||||
|
||||
import Prelude
|
||||
import qualified Data.Map as M
|
||||
import qualified Data.Set as S
|
||||
|
||||
|
|
|
@ -53,7 +53,6 @@ module Text.Pandoc.Readers.Odt.Generic.Utils
|
|||
, composition
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Control.Category ( Category, (>>>), (<<<) )
|
||||
import qualified Control.Category as Cat ( id )
|
||||
import Control.Monad ( msum )
|
||||
|
|
|
@ -116,7 +116,6 @@ module Text.Pandoc.Readers.Odt.Generic.XMLConverter
|
|||
, matchContent
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Control.Applicative hiding ( liftA, liftA2 )
|
||||
import Control.Monad ( MonadPlus )
|
||||
import Control.Arrow
|
||||
|
|
|
@ -31,7 +31,6 @@ Namespaces used in odt files.
|
|||
module Text.Pandoc.Readers.Odt.Namespaces ( Namespace (..)
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Data.List ( isPrefixOf )
|
||||
import Data.Maybe ( fromMaybe, listToMaybe )
|
||||
import qualified Data.Map as M ( empty, insert )
|
||||
|
|
|
@ -70,7 +70,6 @@ module Text.Pandoc.Readers.Odt.StyleReader
|
|||
, readStylesAt
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Control.Arrow
|
||||
import Control.Applicative hiding ( liftA, liftA2, liftA3 )
|
||||
|
||||
|
|
|
@ -30,7 +30,6 @@ Conversion of org-mode formatted plain text to 'Pandoc' document.
|
|||
-}
|
||||
module Text.Pandoc.Readers.Org ( readOrg ) where
|
||||
|
||||
import Prelude
|
||||
import qualified Text.Pandoc.Builder as B
|
||||
import Text.Pandoc.Builder ( Inlines, Blocks, HasMeta(..),
|
||||
trimInlines )
|
||||
|
|
|
@ -33,7 +33,6 @@ module Text.Pandoc.Readers.RST (
|
|||
readRST,
|
||||
readRSTWithWarnings
|
||||
) where
|
||||
import Prelude
|
||||
import Text.Pandoc.Definition
|
||||
import Text.Pandoc.Builder (setMeta, fromList)
|
||||
import Text.Pandoc.Shared
|
||||
|
|
|
@ -33,7 +33,6 @@ module Text.Pandoc.Readers.TWiki ( readTWiki
|
|||
, readTWikiWithWarnings
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Text.Pandoc.Definition
|
||||
import qualified Text.Pandoc.Builder as B
|
||||
import Text.Pandoc.Options
|
||||
|
|
|
@ -29,7 +29,6 @@ Conversion of TeX math to a list of 'Pandoc' inline elements.
|
|||
-}
|
||||
module Text.Pandoc.Readers.TeXMath ( texMathToInlines ) where
|
||||
|
||||
import Prelude
|
||||
import Text.Pandoc.Definition
|
||||
import Text.TeXMath
|
||||
|
||||
|
|
|
@ -51,7 +51,6 @@ TODO : refactor common patterns across readers :
|
|||
|
||||
|
||||
module Text.Pandoc.Readers.Textile ( readTextile) where
|
||||
import Prelude
|
||||
import Text.Pandoc.Definition
|
||||
import Text.Pandoc.Builder (Inlines, Blocks, trimInlines)
|
||||
import qualified Text.Pandoc.Builder as B
|
||||
|
|
|
@ -32,7 +32,6 @@ module Text.Pandoc.Readers.Txt2Tags ( readTxt2Tags
|
|||
, readTxt2TagsNoMacros)
|
||||
where
|
||||
|
||||
import Prelude
|
||||
import qualified Text.Pandoc.Builder as B
|
||||
import Text.Pandoc.Builder ( Inlines, Blocks, trimInlines )
|
||||
import Text.Pandoc.Definition
|
||||
|
|
|
@ -31,7 +31,6 @@ offline, by incorporating linked images, CSS, and scripts into
|
|||
the HTML using data URIs.
|
||||
-}
|
||||
module Text.Pandoc.SelfContained ( makeSelfContained ) where
|
||||
import Prelude
|
||||
import Text.HTML.TagSoup
|
||||
import Network.URI (isURI, escapeURIString, URI(..), parseURI)
|
||||
import Data.ByteString.Base64
|
||||
|
|
|
@ -97,7 +97,6 @@ module Text.Pandoc.Shared (
|
|||
pandocVersion
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Text.Pandoc.Definition
|
||||
import Text.Pandoc.Walk
|
||||
import Text.Pandoc.MediaBag (MediaBag, lookupMedia)
|
||||
|
@ -247,7 +246,7 @@ trim = triml . trimr
|
|||
|
||||
-- | Remove leading space (including newlines) from string.
|
||||
triml :: String -> String
|
||||
triml = dropWhile (`elem` [' ','\r','\n','\t'])
|
||||
triml = dropWhile (`elem` " \r\n\t")
|
||||
|
||||
-- | Remove trailing space (including newlines) from string.
|
||||
trimr :: String -> String
|
||||
|
@ -660,7 +659,7 @@ inlineListToIdentifier :: [Inline] -> String
|
|||
inlineListToIdentifier =
|
||||
dropWhile (not . isAlpha) . intercalate "-" . words .
|
||||
map (nbspToSp . toLower) .
|
||||
filter (\c -> isLetter c || isDigit c || c `elem` ['_','-','.',' ']) .
|
||||
filter (\c -> isLetter c || isDigit c || c `elem` "_-. ") .
|
||||
stringify
|
||||
where nbspToSp '\160' = ' '
|
||||
nbspToSp x = x
|
||||
|
@ -914,9 +913,9 @@ fetchItem' media sourceURL s = do
|
|||
-- | Read from a URL and return raw data and maybe mime type.
|
||||
openURL :: String -> IO (Either E.SomeException (BS.ByteString, Maybe MimeType))
|
||||
openURL u
|
||||
| Just u'' <- stripPrefix "data:" u =
|
||||
let mime = takeWhile (/=',') u''
|
||||
contents = B8.pack $ unEscapeString $ drop 1 $ dropWhile (/=',') u''
|
||||
| Just u' <- stripPrefix "data:" u =
|
||||
let mime = takeWhile (/=',') u'
|
||||
contents = B8.pack $ unEscapeString $ drop 1 $ dropWhile (/=',') u'
|
||||
in return $ Right (decodeLenient contents, Just mime)
|
||||
#ifdef HTTP_CLIENT
|
||||
| otherwise = withSocketsDo $ E.try $ do
|
||||
|
|
|
@ -29,7 +29,6 @@ Utility functions for splitting documents into slides for slide
|
|||
show formats (dzslides, revealjs, s5, slidy, slideous, beamer).
|
||||
-}
|
||||
module Text.Pandoc.Slides ( getSlideLevel, prepSlides ) where
|
||||
import Prelude
|
||||
import Text.Pandoc.Definition
|
||||
|
||||
-- | Find level of header that starts slides (defined as the least header
|
||||
|
|
|
@ -93,7 +93,6 @@ module Text.Pandoc.Templates ( renderTemplate
|
|||
, Template
|
||||
, getDefaultTemplate ) where
|
||||
|
||||
import Prelude
|
||||
import Data.Char (isAlphaNum)
|
||||
import Control.Monad (guard, when)
|
||||
import Data.Aeson (ToJSON(..), Value(..))
|
||||
|
|
|
@ -31,7 +31,6 @@ in RFC4122. See http://tools.ietf.org/html/rfc4122
|
|||
|
||||
module Text.Pandoc.UUID ( UUID, getRandomUUID ) where
|
||||
|
||||
import Prelude
|
||||
import Text.Printf ( printf )
|
||||
import System.Random ( randomIO )
|
||||
import Data.Word
|
||||
|
|
|
@ -37,7 +37,6 @@ that it has omitted the construct.
|
|||
AsciiDoc: <http://www.methods.co.nz/asciidoc/>
|
||||
-}
|
||||
module Text.Pandoc.Writers.AsciiDoc (writeAsciiDoc) where
|
||||
import Prelude
|
||||
import Text.Pandoc.Definition
|
||||
import Text.Pandoc.Templates (renderTemplate')
|
||||
import Text.Pandoc.Shared
|
||||
|
|
|
@ -31,7 +31,6 @@ CommonMark: <http://commonmark.org>
|
|||
-}
|
||||
module Text.Pandoc.Writers.CommonMark (writeCommonMark) where
|
||||
|
||||
import Prelude
|
||||
import Text.Pandoc.Writers.HTML (writeHtmlString)
|
||||
import Text.Pandoc.Definition
|
||||
import Text.Pandoc.Shared (isTightList)
|
||||
|
|
|
@ -29,7 +29,6 @@ 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 Prelude
|
||||
import Text.Pandoc.Definition
|
||||
import Text.Pandoc.Shared
|
||||
import Text.Pandoc.Writers.Shared
|
||||
|
|
|
@ -35,7 +35,6 @@ Conversion of 'Pandoc' documents to custom markup using
|
|||
a lua writer.
|
||||
-}
|
||||
module Text.Pandoc.Writers.Custom ( writeCustom ) where
|
||||
import Prelude
|
||||
import Text.Pandoc.Definition
|
||||
import Text.Pandoc.Options
|
||||
import Data.List ( intersperse )
|
||||
|
|
|
@ -29,7 +29,6 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
|
|||
Conversion of 'Pandoc' documents to Docbook XML.
|
||||
-}
|
||||
module Text.Pandoc.Writers.Docbook ( writeDocbook) where
|
||||
import Prelude
|
||||
import Text.Pandoc.Definition
|
||||
import Text.Pandoc.XML
|
||||
import Text.Pandoc.Shared
|
||||
|
|
|
@ -29,7 +29,6 @@ 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 Prelude
|
||||
import Data.List ( intercalate, isPrefixOf, isSuffixOf )
|
||||
import qualified Data.ByteString as B
|
||||
import qualified Data.ByteString.Lazy as BL
|
||||
|
|
|
@ -39,7 +39,6 @@ DokuWiki: <https://www.dokuwiki.org/dokuwiki>
|
|||
-}
|
||||
|
||||
module Text.Pandoc.Writers.DokuWiki ( writeDokuWiki ) where
|
||||
import Prelude
|
||||
import Text.Pandoc.Definition
|
||||
import Text.Pandoc.Options ( WriterOptions(
|
||||
writerTableOfContents
|
||||
|
|
|
@ -29,7 +29,6 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
|
|||
Conversion of 'Pandoc' documents to EPUB.
|
||||
-}
|
||||
module Text.Pandoc.Writers.EPUB ( writeEPUB ) where
|
||||
import Prelude
|
||||
import Data.IORef ( IORef, newIORef, readIORef, modifyIORef )
|
||||
import qualified Data.Map as M
|
||||
import Data.Maybe ( fromMaybe, catMaybes )
|
||||
|
|
|
@ -27,7 +27,6 @@ FictionBook is an XML-based e-book format. For more information see:
|
|||
-}
|
||||
module Text.Pandoc.Writers.FB2 (writeFB2) where
|
||||
|
||||
import Prelude
|
||||
import Control.Monad.State (StateT, evalStateT, get, modify)
|
||||
import Control.Monad.State (liftM, liftM2, liftIO)
|
||||
import Data.ByteString.Base64 (encode)
|
||||
|
|
|
@ -30,7 +30,6 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
|
|||
Conversion of 'Pandoc' documents to HTML.
|
||||
-}
|
||||
module Text.Pandoc.Writers.HTML ( writeHtml , writeHtmlString ) where
|
||||
import Prelude
|
||||
import Text.Pandoc.Definition
|
||||
import Text.Pandoc.Shared
|
||||
import Text.Pandoc.Writers.Shared
|
||||
|
|
|
@ -31,7 +31,6 @@ Conversion of 'Pandoc' documents to haddock markup.
|
|||
Haddock: <http://www.haskell.org/haddock/doc/html/>
|
||||
-}
|
||||
module Text.Pandoc.Writers.Haddock (writeHaddock) where
|
||||
import Prelude
|
||||
import Text.Pandoc.Definition
|
||||
import Text.Pandoc.Templates (renderTemplate')
|
||||
import Text.Pandoc.Shared
|
||||
|
|
|
@ -14,7 +14,6 @@ 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 Prelude
|
||||
import Text.Pandoc.Definition
|
||||
import Text.Pandoc.XML
|
||||
import Text.Pandoc.Writers.Shared
|
||||
|
|
|
@ -30,7 +30,6 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
|
|||
Conversion of 'Pandoc' format into LaTeX.
|
||||
-}
|
||||
module Text.Pandoc.Writers.LaTeX ( writeLaTeX ) where
|
||||
import Prelude
|
||||
import Text.Pandoc.Definition
|
||||
import Text.Pandoc.Walk
|
||||
import Text.Pandoc.Shared
|
||||
|
|
|
@ -29,7 +29,6 @@ Conversion of 'Pandoc' documents to groff man page format.
|
|||
|
||||
-}
|
||||
module Text.Pandoc.Writers.Man ( writeMan) where
|
||||
import Prelude
|
||||
import Text.Pandoc.Definition
|
||||
import Text.Pandoc.Templates
|
||||
import Text.Pandoc.Shared
|
||||
|
|
|
@ -31,7 +31,6 @@ Conversion of 'Pandoc' documents to markdown-formatted plain text.
|
|||
Markdown: <http://daringfireball.net/projects/markdown/>
|
||||
-}
|
||||
module Text.Pandoc.Writers.Markdown (writeMarkdown, writePlain) where
|
||||
import Prelude
|
||||
import Text.Pandoc.Definition
|
||||
import Text.Pandoc.Walk
|
||||
import Text.Pandoc.Templates (renderTemplate')
|
||||
|
|
|
@ -30,7 +30,6 @@ Conversion of 'Pandoc' documents to MediaWiki markup.
|
|||
MediaWiki: <http://www.mediawiki.org/wiki/MediaWiki>
|
||||
-}
|
||||
module Text.Pandoc.Writers.MediaWiki ( writeMediaWiki ) where
|
||||
import Prelude
|
||||
import Text.Pandoc.Definition
|
||||
import Text.Pandoc.Options
|
||||
import Text.Pandoc.Shared
|
||||
|
|
|
@ -34,7 +34,6 @@ metadata.
|
|||
-}
|
||||
module Text.Pandoc.Writers.Native ( writeNative )
|
||||
where
|
||||
import Prelude
|
||||
import Text.Pandoc.Options ( WriterOptions(..) )
|
||||
import Data.List ( intersperse )
|
||||
import Text.Pandoc.Definition
|
||||
|
|
|
@ -29,7 +29,6 @@ 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 Prelude
|
||||
import Data.IORef
|
||||
import Data.List ( isPrefixOf )
|
||||
import Data.Maybe ( fromMaybe )
|
||||
|
|
|
@ -29,7 +29,6 @@ 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 Prelude
|
||||
import Text.Pandoc.Definition
|
||||
import Text.Pandoc.XML
|
||||
import Text.Pandoc.Writers.Shared
|
||||
|
|
|
@ -30,7 +30,6 @@ 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 Prelude
|
||||
import Text.Pandoc.Definition
|
||||
import Text.Pandoc.Options
|
||||
import Text.Pandoc.XML
|
||||
|
|
|
@ -32,7 +32,6 @@ Conversion of 'Pandoc' documents to Emacs Org-Mode.
|
|||
Org-Mode: <http://orgmode.org>
|
||||
-}
|
||||
module Text.Pandoc.Writers.Org ( writeOrg) where
|
||||
import Prelude
|
||||
import Text.Pandoc.Definition
|
||||
import Text.Pandoc.Options
|
||||
import Text.Pandoc.Shared
|
||||
|
|
|
@ -31,7 +31,6 @@ Conversion of 'Pandoc' documents to reStructuredText.
|
|||
reStructuredText: <http://docutils.sourceforge.net/rst.html>
|
||||
-}
|
||||
module Text.Pandoc.Writers.RST ( writeRST ) where
|
||||
import Prelude
|
||||
import Text.Pandoc.Definition
|
||||
import Text.Pandoc.Options
|
||||
import Text.Pandoc.Shared
|
||||
|
|
|
@ -28,7 +28,6 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
|
|||
Conversion of 'Pandoc' documents to RTF (rich text format).
|
||||
-}
|
||||
module Text.Pandoc.Writers.RTF ( writeRTF, writeRTFWithEmbeddedImages ) where
|
||||
import Prelude
|
||||
import Text.Pandoc.Definition
|
||||
import Text.Pandoc.Options
|
||||
import Text.Pandoc.Shared
|
||||
|
|
|
@ -37,7 +37,6 @@ module Text.Pandoc.Writers.Shared (
|
|||
, fixDisplayMath
|
||||
)
|
||||
where
|
||||
import Prelude
|
||||
import Text.Pandoc.Definition
|
||||
import Text.Pandoc.Pretty
|
||||
import Text.Pandoc.XML (escapeStringForXML)
|
||||
|
|
|
@ -29,7 +29,6 @@ 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 Prelude
|
||||
import Text.Pandoc.Definition
|
||||
import Text.Pandoc.Options
|
||||
import Text.Pandoc.Shared
|
||||
|
|
|
@ -30,7 +30,6 @@ 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 Prelude
|
||||
import Text.Pandoc.Definition
|
||||
import Text.Pandoc.Options
|
||||
import Text.Pandoc.Shared
|
||||
|
|
|
@ -36,7 +36,6 @@ module Text.Pandoc.XML ( escapeCharForXML,
|
|||
toEntities,
|
||||
fromEntities ) where
|
||||
|
||||
import Prelude
|
||||
import Text.Pandoc.Pretty
|
||||
import Data.Char (ord, isAscii, isSpace)
|
||||
import Text.Pandoc.Compat.TagSoupEntity (lookupEntity)
|
||||
|
|
|
@ -3,7 +3,6 @@
|
|||
-- provides Arbitrary instance for Pandoc types
|
||||
module Tests.Arbitrary ()
|
||||
where
|
||||
import Prelude
|
||||
import Test.QuickCheck.Gen
|
||||
import Test.QuickCheck.Arbitrary
|
||||
import Control.Monad (liftM, liftM2)
|
||||
|
|
|
@ -9,7 +9,6 @@ module Tests.Helpers ( test
|
|||
)
|
||||
where
|
||||
|
||||
import Prelude
|
||||
import Text.Pandoc.Definition
|
||||
import Text.Pandoc.Builder (Inlines, Blocks, doc, plain)
|
||||
import Test.Framework
|
||||
|
|
|
@ -1,6 +1,5 @@
|
|||
module Tests.Old (tests) where
|
||||
|
||||
import Prelude
|
||||
import Test.Framework (testGroup, Test )
|
||||
import Test.Framework.Providers.HUnit
|
||||
import Test.HUnit ( assertBool )
|
||||
|
|
|
@ -1,6 +1,5 @@
|
|||
module Tests.Readers.Docx (tests) where
|
||||
|
||||
import Prelude
|
||||
import Text.Pandoc.Options
|
||||
import Text.Pandoc.Readers.Native
|
||||
import Text.Pandoc.Definition
|
||||
|
|
|
@ -1,6 +1,5 @@
|
|||
module Tests.Readers.EPUB (tests) where
|
||||
|
||||
import Prelude
|
||||
import Text.Pandoc.Options
|
||||
import Test.Framework
|
||||
import Test.HUnit (assertBool)
|
||||
|
|
|
@ -1,7 +1,6 @@
|
|||
{-# LANGUAGE OverloadedStrings #-}
|
||||
module Tests.Readers.HTML (tests) where
|
||||
|
||||
import Prelude
|
||||
import Text.Pandoc.Definition
|
||||
import Test.Framework
|
||||
import Tests.Helpers
|
||||
|
|
|
@ -1,7 +1,6 @@
|
|||
{-# LANGUAGE OverloadedStrings #-}
|
||||
module Tests.Readers.LaTeX (tests) where
|
||||
|
||||
import Prelude
|
||||
import Text.Pandoc.Definition
|
||||
import Test.Framework
|
||||
import Tests.Helpers
|
||||
|
|
|
@ -1,7 +1,6 @@
|
|||
{-# LANGUAGE OverloadedStrings #-}
|
||||
module Tests.Readers.Markdown (tests) where
|
||||
|
||||
import Prelude
|
||||
import Text.Pandoc.Definition
|
||||
import Test.Framework
|
||||
import Tests.Helpers
|
||||
|
|
|
@ -1,6 +1,5 @@
|
|||
module Tests.Readers.Odt (tests) where
|
||||
|
||||
import Prelude
|
||||
import Control.Monad ( liftM )
|
||||
import Text.Pandoc.Options
|
||||
import Text.Pandoc.Readers.Native
|
||||
|
@ -163,4 +162,4 @@ namesOfTestsComparingToNative = [ "blockquote"
|
|||
-- , "table"
|
||||
, "unicode"
|
||||
, "unorderedList"
|
||||
]
|
||||
]
|
|
@ -1,7 +1,6 @@
|
|||
{-# LANGUAGE OverloadedStrings #-}
|
||||
module Tests.Readers.Org (tests) where
|
||||
|
||||
import Prelude
|
||||
import Text.Pandoc.Definition
|
||||
import Test.Framework
|
||||
import Tests.Helpers
|
||||
|
|
|
@ -1,7 +1,6 @@
|
|||
{-# LANGUAGE OverloadedStrings, ScopedTypeVariables #-}
|
||||
module Tests.Readers.RST (tests) where
|
||||
|
||||
import Prelude
|
||||
import Text.Pandoc.Definition
|
||||
import Test.Framework
|
||||
import Tests.Helpers
|
||||
|
|
|
@ -1,7 +1,6 @@
|
|||
{-# LANGUAGE OverloadedStrings #-}
|
||||
module Tests.Readers.Txt2Tags (tests) where
|
||||
|
||||
import Prelude
|
||||
import Text.Pandoc.Definition
|
||||
import Test.Framework
|
||||
import Tests.Helpers
|
||||
|
|
|
@ -1,6 +1,5 @@
|
|||
module Tests.Shared (tests) where
|
||||
|
||||
import Prelude
|
||||
import Text.Pandoc.Definition
|
||||
import Text.Pandoc.Shared
|
||||
import Test.Framework
|
||||
|
|
|
@ -1,7 +1,6 @@
|
|||
{-# LANGUAGE ScopedTypeVariables, FlexibleContexts #-}
|
||||
module Tests.Walk (tests) where
|
||||
|
||||
import Prelude
|
||||
import Text.Pandoc.Definition
|
||||
import Text.Pandoc.Walk
|
||||
import Test.Framework
|
||||
|
|
|
@ -1,6 +1,5 @@
|
|||
module Tests.Writers.AsciiDoc (tests) where
|
||||
|
||||
import Prelude
|
||||
import Test.Framework
|
||||
import Text.Pandoc.Builder
|
||||
import Text.Pandoc
|
||||
|
|
|
@ -1,7 +1,6 @@
|
|||
{-# LANGUAGE OverloadedStrings #-}
|
||||
module Tests.Writers.ConTeXt (tests) where
|
||||
|
||||
import Prelude
|
||||
import Test.Framework
|
||||
import Text.Pandoc.Builder
|
||||
import Text.Pandoc
|
||||
|
|
Some files were not shown because too many files have changed in this diff Show more
Loading…
Add table
Reference in a new issue