aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Readers
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2015-11-08 16:56:59 -0800
committerJohn MacFarlane <jgm@berkeley.edu>2015-11-08 16:56:59 -0800
commitc423dbb5a34c2d1195020e0f0ca3aae883d0749b (patch)
treea118d6561e1886fe019f51599c5c1258606eadd4 /src/Text/Pandoc/Readers
parentda056191182777c4e4e951d3aae49c6428677fc7 (diff)
downloadpandoc-c423dbb5a34c2d1195020e0f0ca3aae883d0749b.tar.gz
Use -XNoImplicitPrelude and 'import Prelude' explicitly.
This is needed for ghci to work with pandoc, given that we now use a custom prelude. Closes #2503.
Diffstat (limited to 'src/Text/Pandoc/Readers')
-rw-r--r--src/Text/Pandoc/Readers/CommonMark.hs1
-rw-r--r--src/Text/Pandoc/Readers/DocBook.hs1
-rw-r--r--src/Text/Pandoc/Readers/Docx.hs1
-rw-r--r--src/Text/Pandoc/Readers/Docx/Fonts.hs1
-rw-r--r--src/Text/Pandoc/Readers/Docx/Lists.hs1
-rw-r--r--src/Text/Pandoc/Readers/Docx/Parse.hs1
-rw-r--r--src/Text/Pandoc/Readers/Docx/Reducible.hs1
-rw-r--r--src/Text/Pandoc/Readers/Docx/StyleMap.hs1
-rw-r--r--src/Text/Pandoc/Readers/Docx/Util.hs1
-rw-r--r--src/Text/Pandoc/Readers/EPUB.hs1
-rw-r--r--src/Text/Pandoc/Readers/HTML.hs1
-rw-r--r--src/Text/Pandoc/Readers/Haddock.hs3
-rw-r--r--src/Text/Pandoc/Readers/LaTeX.hs1
-rw-r--r--src/Text/Pandoc/Readers/Markdown.hs1
-rw-r--r--src/Text/Pandoc/Readers/MediaWiki.hs1
-rw-r--r--src/Text/Pandoc/Readers/Native.hs1
-rw-r--r--src/Text/Pandoc/Readers/OPML.hs1
-rw-r--r--src/Text/Pandoc/Readers/Odt.hs1
-rw-r--r--src/Text/Pandoc/Readers/Odt/Arrows/Utils.hs1
-rw-r--r--src/Text/Pandoc/Readers/Odt/ContentReader.hs1
-rw-r--r--src/Text/Pandoc/Readers/Odt/Generic/Fallible.hs1
-rw-r--r--src/Text/Pandoc/Readers/Odt/Generic/Namespaces.hs1
-rw-r--r--src/Text/Pandoc/Readers/Odt/Generic/SetMap.hs1
-rw-r--r--src/Text/Pandoc/Readers/Odt/Generic/Utils.hs1
-rw-r--r--src/Text/Pandoc/Readers/Odt/Generic/XMLConverter.hs1
-rw-r--r--src/Text/Pandoc/Readers/Odt/Namespaces.hs1
-rw-r--r--src/Text/Pandoc/Readers/Odt/StyleReader.hs1
-rw-r--r--src/Text/Pandoc/Readers/Org.hs1
-rw-r--r--src/Text/Pandoc/Readers/RST.hs1
-rw-r--r--src/Text/Pandoc/Readers/TWiki.hs1
-rw-r--r--src/Text/Pandoc/Readers/TeXMath.hs1
-rw-r--r--src/Text/Pandoc/Readers/Textile.hs1
-rw-r--r--src/Text/Pandoc/Readers/Txt2Tags.hs1
33 files changed, 34 insertions, 1 deletions
diff --git a/src/Text/Pandoc/Readers/CommonMark.hs b/src/Text/Pandoc/Readers/CommonMark.hs
index 51a35c8ad..e6f8026ab 100644
--- a/src/Text/Pandoc/Readers/CommonMark.hs
+++ b/src/Text/Pandoc/Readers/CommonMark.hs
@@ -32,6 +32,7 @@ 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)
diff --git a/src/Text/Pandoc/Readers/DocBook.hs b/src/Text/Pandoc/Readers/DocBook.hs
index f679ddb57..0845f5e03 100644
--- a/src/Text/Pandoc/Readers/DocBook.hs
+++ b/src/Text/Pandoc/Readers/DocBook.hs
@@ -1,4 +1,5 @@
module Text.Pandoc.Readers.DocBook ( readDocBook ) where
+import Prelude
import Data.Char (toUpper)
import Text.Pandoc.Shared (safeRead)
import Text.Pandoc.Options
diff --git a/src/Text/Pandoc/Readers/Docx.hs b/src/Text/Pandoc/Readers/Docx.hs
index ab49bf002..35b2ba3fd 100644
--- a/src/Text/Pandoc/Readers/Docx.hs
+++ b/src/Text/Pandoc/Readers/Docx.hs
@@ -74,6 +74,7 @@ module Text.Pandoc.Readers.Docx
( readDocx
) where
+import Prelude
import Codec.Archive.Zip
import Text.Pandoc.Definition
import Text.Pandoc.Options
diff --git a/src/Text/Pandoc/Readers/Docx/Fonts.hs b/src/Text/Pandoc/Readers/Docx/Fonts.hs
index b44c71412..967ca296c 100644
--- a/src/Text/Pandoc/Readers/Docx/Fonts.hs
+++ b/src/Text/Pandoc/Readers/Docx/Fonts.hs
@@ -29,6 +29,7 @@ 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>
diff --git a/src/Text/Pandoc/Readers/Docx/Lists.hs b/src/Text/Pandoc/Readers/Docx/Lists.hs
index c265ad074..0c9297139 100644
--- a/src/Text/Pandoc/Readers/Docx/Lists.hs
+++ b/src/Text/Pandoc/Readers/Docx/Lists.hs
@@ -33,6 +33,7 @@ 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)
diff --git a/src/Text/Pandoc/Readers/Docx/Parse.hs b/src/Text/Pandoc/Readers/Docx/Parse.hs
index 432965d49..91eab1339 100644
--- a/src/Text/Pandoc/Readers/Docx/Parse.hs
+++ b/src/Text/Pandoc/Readers/Docx/Parse.hs
@@ -50,6 +50,7 @@ module Text.Pandoc.Readers.Docx.Parse ( Docx(..)
, Cell(..)
, archiveToDocx
) where
+import Prelude
import Codec.Archive.Zip
import Text.XML.Light
import Data.Maybe
diff --git a/src/Text/Pandoc/Readers/Docx/Reducible.hs b/src/Text/Pandoc/Readers/Docx/Reducible.hs
index c93b40119..a850141f6 100644
--- a/src/Text/Pandoc/Readers/Docx/Reducible.hs
+++ b/src/Text/Pandoc/Readers/Docx/Reducible.hs
@@ -7,6 +7,7 @@ module Text.Pandoc.Readers.Docx.Reducible ( concatReduce
where
+import Prelude
import Text.Pandoc.Builder
import Data.List
import Data.Sequence (ViewR(..), ViewL(..), viewl, viewr)
diff --git a/src/Text/Pandoc/Readers/Docx/StyleMap.hs b/src/Text/Pandoc/Readers/Docx/StyleMap.hs
index 2901ea2a3..231653106 100644
--- a/src/Text/Pandoc/Readers/Docx/StyleMap.hs
+++ b/src/Text/Pandoc/Readers/Docx/StyleMap.hs
@@ -5,6 +5,7 @@ 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
diff --git a/src/Text/Pandoc/Readers/Docx/Util.hs b/src/Text/Pandoc/Readers/Docx/Util.hs
index 891f107b0..2790c0d1a 100644
--- a/src/Text/Pandoc/Readers/Docx/Util.hs
+++ b/src/Text/Pandoc/Readers/Docx/Util.hs
@@ -5,6 +5,7 @@ module Text.Pandoc.Readers.Docx.Util (
, elemToNameSpaces
) where
+import Prelude
import Text.XML.Light
import Data.Maybe (mapMaybe)
diff --git a/src/Text/Pandoc/Readers/EPUB.hs b/src/Text/Pandoc/Readers/EPUB.hs
index 2da5e9e18..9938bb70b 100644
--- a/src/Text/Pandoc/Readers/EPUB.hs
+++ b/src/Text/Pandoc/Readers/EPUB.hs
@@ -8,6 +8,7 @@ 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)
diff --git a/src/Text/Pandoc/Readers/HTML.hs b/src/Text/Pandoc/Readers/HTML.hs
index a97285ae2..570efc2be 100644
--- a/src/Text/Pandoc/Readers/HTML.hs
+++ b/src/Text/Pandoc/Readers/HTML.hs
@@ -38,6 +38,7 @@ module Text.Pandoc.Readers.HTML ( readHtml
, isCommentTag
) where
+import Prelude
import Text.HTML.TagSoup
import Text.HTML.TagSoup.Match
import Text.Pandoc.Definition
diff --git a/src/Text/Pandoc/Readers/Haddock.hs b/src/Text/Pandoc/Readers/Haddock.hs
index 2b74f5f62..578a89d21 100644
--- a/src/Text/Pandoc/Readers/Haddock.hs
+++ b/src/Text/Pandoc/Readers/Haddock.hs
@@ -14,6 +14,7 @@ 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)
@@ -129,7 +130,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
diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs
index 359661c3e..dd73feea8 100644
--- a/src/Text/Pandoc/Readers/LaTeX.hs
+++ b/src/Text/Pandoc/Readers/LaTeX.hs
@@ -35,6 +35,7 @@ module Text.Pandoc.Readers.LaTeX ( readLaTeX,
handleIncludes
) where
+import Prelude
import Text.Pandoc.Definition
import Text.Pandoc.Walk
import Text.Pandoc.Shared
diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs
index 58878feb5..d3b71c499 100644
--- a/src/Text/Pandoc/Readers/Markdown.hs
+++ b/src/Text/Pandoc/Readers/Markdown.hs
@@ -32,6 +32,7 @@ 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)
diff --git a/src/Text/Pandoc/Readers/MediaWiki.hs b/src/Text/Pandoc/Readers/MediaWiki.hs
index 4f5f9c293..b21fb58c0 100644
--- a/src/Text/Pandoc/Readers/MediaWiki.hs
+++ b/src/Text/Pandoc/Readers/MediaWiki.hs
@@ -36,6 +36,7 @@ _ 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)
diff --git a/src/Text/Pandoc/Readers/Native.hs b/src/Text/Pandoc/Readers/Native.hs
index 4ec164e19..73ac0d4b2 100644
--- a/src/Text/Pandoc/Readers/Native.hs
+++ b/src/Text/Pandoc/Readers/Native.hs
@@ -30,6 +30,7 @@ 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)
diff --git a/src/Text/Pandoc/Readers/OPML.hs b/src/Text/Pandoc/Readers/OPML.hs
index b2e5f2e67..e7633e414 100644
--- a/src/Text/Pandoc/Readers/OPML.hs
+++ b/src/Text/Pandoc/Readers/OPML.hs
@@ -1,5 +1,6 @@
{-# LANGUAGE FlexibleContexts #-}
module Text.Pandoc.Readers.OPML ( readOPML ) where
+import Prelude
import Data.Char (toUpper)
import Text.Pandoc.Options
import Text.Pandoc.Definition
diff --git a/src/Text/Pandoc/Readers/Odt.hs b/src/Text/Pandoc/Readers/Odt.hs
index a925c1d84..cc15c9e20 100644
--- a/src/Text/Pandoc/Readers/Odt.hs
+++ b/src/Text/Pandoc/Readers/Odt.hs
@@ -32,6 +32,7 @@ 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
diff --git a/src/Text/Pandoc/Readers/Odt/Arrows/Utils.hs b/src/Text/Pandoc/Readers/Odt/Arrows/Utils.hs
index fdc02d8d2..e7d2bcb92 100644
--- a/src/Text/Pandoc/Readers/Odt/Arrows/Utils.hs
+++ b/src/Text/Pandoc/Readers/Odt/Arrows/Utils.hs
@@ -39,6 +39,7 @@ 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(..) )
diff --git a/src/Text/Pandoc/Readers/Odt/ContentReader.hs b/src/Text/Pandoc/Readers/Odt/ContentReader.hs
index 1f1c57646..06dd83668 100644
--- a/src/Text/Pandoc/Readers/Odt/ContentReader.hs
+++ b/src/Text/Pandoc/Readers/Odt/ContentReader.hs
@@ -39,6 +39,7 @@ module Text.Pandoc.Readers.Odt.ContentReader
, read_body
) where
+import Prelude
import Control.Arrow
import Control.Applicative hiding ( liftA, liftA2, liftA3 )
diff --git a/src/Text/Pandoc/Readers/Odt/Generic/Fallible.hs b/src/Text/Pandoc/Readers/Odt/Generic/Fallible.hs
index 343ec14ee..7213bc8f1 100644
--- a/src/Text/Pandoc/Readers/Odt/Generic/Fallible.hs
+++ b/src/Text/Pandoc/Readers/Odt/Generic/Fallible.hs
@@ -39,6 +39,7 @@ compatible instances of "ArrowChoice".
-- We export everything
module Text.Pandoc.Readers.Odt.Generic.Fallible where
+import Prelude
import Control.Applicative
import Control.Monad
diff --git a/src/Text/Pandoc/Readers/Odt/Generic/Namespaces.hs b/src/Text/Pandoc/Readers/Odt/Generic/Namespaces.hs
index 82ae3e20e..0a6095e98 100644
--- a/src/Text/Pandoc/Readers/Odt/Generic/Namespaces.hs
+++ b/src/Text/Pandoc/Readers/Odt/Generic/Namespaces.hs
@@ -31,6 +31,7 @@ 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
--
diff --git a/src/Text/Pandoc/Readers/Odt/Generic/SetMap.hs b/src/Text/Pandoc/Readers/Odt/Generic/SetMap.hs
index afd7d616c..b7a555219 100644
--- a/src/Text/Pandoc/Readers/Odt/Generic/SetMap.hs
+++ b/src/Text/Pandoc/Readers/Odt/Generic/SetMap.hs
@@ -30,6 +30,7 @@ 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
diff --git a/src/Text/Pandoc/Readers/Odt/Generic/Utils.hs b/src/Text/Pandoc/Readers/Odt/Generic/Utils.hs
index 6c10ed61d..a09b4cc1d 100644
--- a/src/Text/Pandoc/Readers/Odt/Generic/Utils.hs
+++ b/src/Text/Pandoc/Readers/Odt/Generic/Utils.hs
@@ -53,6 +53,7 @@ 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 )
diff --git a/src/Text/Pandoc/Readers/Odt/Generic/XMLConverter.hs b/src/Text/Pandoc/Readers/Odt/Generic/XMLConverter.hs
index 8c03d1a09..7d72ee125 100644
--- a/src/Text/Pandoc/Readers/Odt/Generic/XMLConverter.hs
+++ b/src/Text/Pandoc/Readers/Odt/Generic/XMLConverter.hs
@@ -116,6 +116,7 @@ module Text.Pandoc.Readers.Odt.Generic.XMLConverter
, matchContent
) where
+import Prelude
import Control.Applicative hiding ( liftA, liftA2 )
import Control.Monad ( MonadPlus )
import Control.Arrow
diff --git a/src/Text/Pandoc/Readers/Odt/Namespaces.hs b/src/Text/Pandoc/Readers/Odt/Namespaces.hs
index deb009998..f00093368 100644
--- a/src/Text/Pandoc/Readers/Odt/Namespaces.hs
+++ b/src/Text/Pandoc/Readers/Odt/Namespaces.hs
@@ -31,6 +31,7 @@ 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 )
diff --git a/src/Text/Pandoc/Readers/Odt/StyleReader.hs b/src/Text/Pandoc/Readers/Odt/StyleReader.hs
index 96cfed0b3..4140bf2c7 100644
--- a/src/Text/Pandoc/Readers/Odt/StyleReader.hs
+++ b/src/Text/Pandoc/Readers/Odt/StyleReader.hs
@@ -70,6 +70,7 @@ module Text.Pandoc.Readers.Odt.StyleReader
, readStylesAt
) where
+import Prelude
import Control.Arrow
import Control.Applicative hiding ( liftA, liftA2, liftA3 )
diff --git a/src/Text/Pandoc/Readers/Org.hs b/src/Text/Pandoc/Readers/Org.hs
index 2585ace21..d27acea2a 100644
--- a/src/Text/Pandoc/Readers/Org.hs
+++ b/src/Text/Pandoc/Readers/Org.hs
@@ -30,6 +30,7 @@ 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 )
diff --git a/src/Text/Pandoc/Readers/RST.hs b/src/Text/Pandoc/Readers/RST.hs
index 4fb30e6c4..82fa67407 100644
--- a/src/Text/Pandoc/Readers/RST.hs
+++ b/src/Text/Pandoc/Readers/RST.hs
@@ -33,6 +33,7 @@ module Text.Pandoc.Readers.RST (
readRST,
readRSTWithWarnings
) where
+import Prelude
import Text.Pandoc.Definition
import Text.Pandoc.Builder (setMeta, fromList)
import Text.Pandoc.Shared
diff --git a/src/Text/Pandoc/Readers/TWiki.hs b/src/Text/Pandoc/Readers/TWiki.hs
index fc2bdc069..558e9691a 100644
--- a/src/Text/Pandoc/Readers/TWiki.hs
+++ b/src/Text/Pandoc/Readers/TWiki.hs
@@ -33,6 +33,7 @@ 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
diff --git a/src/Text/Pandoc/Readers/TeXMath.hs b/src/Text/Pandoc/Readers/TeXMath.hs
index e5778b123..ad0eacb2b 100644
--- a/src/Text/Pandoc/Readers/TeXMath.hs
+++ b/src/Text/Pandoc/Readers/TeXMath.hs
@@ -29,6 +29,7 @@ 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
diff --git a/src/Text/Pandoc/Readers/Textile.hs b/src/Text/Pandoc/Readers/Textile.hs
index 43aaa3f9a..a99831a56 100644
--- a/src/Text/Pandoc/Readers/Textile.hs
+++ b/src/Text/Pandoc/Readers/Textile.hs
@@ -51,6 +51,7 @@ 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
diff --git a/src/Text/Pandoc/Readers/Txt2Tags.hs b/src/Text/Pandoc/Readers/Txt2Tags.hs
index 1c868f5f0..3a3172734 100644
--- a/src/Text/Pandoc/Readers/Txt2Tags.hs
+++ b/src/Text/Pandoc/Readers/Txt2Tags.hs
@@ -32,6 +32,7 @@ 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