Avoid unnecessary use of NoImplicitPrelude pragma (#7089)
This commit is contained in:
parent
f7be8d0964
commit
d202f7eb77
59 changed files with 1 additions and 112 deletions
|
@ -1,4 +1,3 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{- |
|
||||
Module : Main
|
||||
Copyright : Copyright (C) 2006-2021 John MacFarlane
|
||||
|
@ -12,7 +11,6 @@ Parses command-line options and calls the appropriate readers and
|
|||
writers.
|
||||
-}
|
||||
module Main where
|
||||
import Prelude
|
||||
import qualified Control.Exception as E
|
||||
import Text.Pandoc.App (convertWithOpts, defaultOpts, options, parseOptions)
|
||||
import Text.Pandoc.Error (handleError)
|
||||
|
|
|
@ -1,4 +1,3 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-
|
||||
Copyright (C) 2012-2021 John MacFarlane <jgm@berkeley.edu>
|
||||
|
@ -17,7 +16,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 Text.Pandoc.MIME
|
||||
import Control.Monad.Except (throwError, liftIO)
|
||||
|
|
|
@ -1,4 +1,3 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{- |
|
||||
Module : Main
|
||||
|
@ -11,7 +10,6 @@
|
|||
|
||||
Benchmarks to determine resource use of readers and writers.
|
||||
-}
|
||||
import Prelude
|
||||
import Weigh
|
||||
import Text.Pandoc
|
||||
import Data.Text (Text, unpack)
|
||||
|
|
|
@ -400,7 +400,6 @@ common common-options
|
|||
default-language: Haskell2010
|
||||
build-depends: base >= 4.9 && < 5,
|
||||
text >= 1.1.1.0 && < 1.3
|
||||
other-extensions: NoImplicitPrelude
|
||||
ghc-options: -Wall -fno-warn-unused-do-bind
|
||||
-Wincomplete-record-updates
|
||||
-Wnoncanonical-monad-instances
|
||||
|
@ -409,6 +408,7 @@ common common-options
|
|||
hs-source-dirs: prelude
|
||||
other-modules: Prelude
|
||||
build-depends: base-compat >= 0.9
|
||||
other-extensions: NoImplicitPrelude
|
||||
|
||||
if os(windows)
|
||||
cpp-options: -D_WINDOWS
|
||||
|
|
|
@ -1,4 +1,3 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{- |
|
||||
Module : Text.Pandoc.UTF8
|
||||
|
|
|
@ -1,4 +1,3 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE TupleSections #-}
|
||||
{- |
|
||||
Module : Tests.Command
|
||||
|
@ -14,7 +13,6 @@ Run commands, and test results, defined in markdown files.
|
|||
module Tests.Command (runTest, tests)
|
||||
where
|
||||
|
||||
import Prelude
|
||||
import Data.Algorithm.Diff
|
||||
import System.Environment.Executable (getExecutablePath)
|
||||
import qualified Data.ByteString as BS
|
||||
|
|
|
@ -1,5 +1,4 @@
|
|||
{-# LANGUAGE CPP #-}
|
||||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE FlexibleInstances #-}
|
||||
{- |
|
||||
Module : Tests.Helpers
|
||||
|
@ -22,7 +21,6 @@ module Tests.Helpers ( test
|
|||
)
|
||||
where
|
||||
|
||||
import Prelude
|
||||
import Data.Algorithm.Diff
|
||||
import qualified Data.Map as M
|
||||
import Data.Text (Text, unpack)
|
||||
|
|
|
@ -1,4 +1,3 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-# LANGUAGE ScopedTypeVariables #-}
|
||||
{- |
|
||||
|
@ -14,7 +13,6 @@ Unit and integration tests for pandoc's Lua subsystem.
|
|||
-}
|
||||
module Tests.Lua ( runLuaTest, tests ) where
|
||||
|
||||
import Prelude
|
||||
import Control.Monad (when)
|
||||
import System.FilePath ((</>))
|
||||
import Test.Tasty (TestTree, localOption)
|
||||
|
|
|
@ -1,4 +1,3 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE TupleSections #-}
|
||||
{- |
|
||||
Module : Tests.Old
|
||||
|
@ -13,7 +12,6 @@
|
|||
-}
|
||||
module Tests.Old (tests) where
|
||||
|
||||
import Prelude
|
||||
import Data.Algorithm.Diff
|
||||
import System.Exit
|
||||
import System.FilePath ((<.>), (</>))
|
||||
|
|
|
@ -1,4 +1,3 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{- |
|
||||
Module : Tests.Readers.Creole
|
||||
|
@ -14,7 +13,6 @@ Tests for the creole reader.
|
|||
-}
|
||||
module Tests.Readers.Creole (tests) where
|
||||
|
||||
import Prelude
|
||||
import Data.Text (Text)
|
||||
import qualified Data.Text as T
|
||||
import Test.Tasty
|
||||
|
|
|
@ -1,4 +1,3 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{- |
|
||||
Module : Tests.Readers.Docx
|
||||
|
@ -13,7 +12,6 @@ Tests for the word docx reader.
|
|||
-}
|
||||
module Tests.Readers.Docx (tests) where
|
||||
|
||||
import Prelude
|
||||
import Codec.Archive.Zip
|
||||
import qualified Data.ByteString as BS
|
||||
import qualified Data.ByteString.Lazy as B
|
||||
|
|
|
@ -1,4 +1,3 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-# LANGUAGE ScopedTypeVariables #-}
|
||||
{- |
|
||||
|
@ -14,7 +13,6 @@ Tests for DokuWiki reader.
|
|||
-}
|
||||
module Tests.Readers.DokuWiki (tests) where
|
||||
|
||||
import Prelude
|
||||
import Data.Text (Text)
|
||||
import qualified Data.Text as T
|
||||
import Test.Tasty
|
||||
|
|
|
@ -1,4 +1,3 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{- |
|
||||
Module : Tests.Readers.EPUB
|
||||
Copyright : © 2006-2021 John MacFarlane
|
||||
|
@ -12,7 +11,6 @@ Tests for the EPUB mediabag.
|
|||
-}
|
||||
module Tests.Readers.EPUB (tests) where
|
||||
|
||||
import Prelude
|
||||
import qualified Data.ByteString.Lazy as BL
|
||||
import qualified Data.Text as T
|
||||
import Test.Tasty
|
||||
|
|
|
@ -1,4 +1,3 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{- |
|
||||
Module : Tests.Readers.FB2
|
||||
Copyright : © 2018-2020 Alexander Krotov
|
||||
|
@ -12,7 +11,6 @@ Tests for the EPUB mediabag.
|
|||
-}
|
||||
module Tests.Readers.FB2 (tests) where
|
||||
|
||||
import Prelude
|
||||
import Test.Tasty
|
||||
import Tests.Helpers
|
||||
import Test.Tasty.Golden (goldenVsString)
|
||||
|
|
|
@ -1,4 +1,3 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{- |
|
||||
Module : Tests.Readers.HTML
|
||||
|
@ -13,7 +12,6 @@ Tests for the HTML reader.
|
|||
-}
|
||||
module Tests.Readers.HTML (tests) where
|
||||
|
||||
import Prelude
|
||||
import Data.Text (Text)
|
||||
import qualified Data.Text as T
|
||||
import Test.Tasty
|
||||
|
|
|
@ -1,4 +1,3 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{- |
|
||||
Module : Tests.Readers.JATS
|
||||
|
@ -13,7 +12,6 @@ Tests for the JATS reader.
|
|||
-}
|
||||
module Tests.Readers.JATS (tests) where
|
||||
|
||||
import Prelude
|
||||
import Data.Text (Text)
|
||||
import Test.Tasty
|
||||
import Tests.Helpers
|
||||
|
|
|
@ -1,4 +1,3 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-# LANGUAGE ScopedTypeVariables #-}
|
||||
{- |
|
||||
|
|
|
@ -1,4 +1,3 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{- |
|
||||
Module : Tests.Readers.LaTeX
|
||||
|
@ -13,7 +12,6 @@ Tests for the LaTeX reader.
|
|||
-}
|
||||
module Tests.Readers.LaTeX (tests) where
|
||||
|
||||
import Prelude
|
||||
import Data.Text (Text)
|
||||
import qualified Data.Text as T
|
||||
import qualified Text.Pandoc.UTF8 as UTF8
|
||||
|
|
|
@ -13,7 +13,6 @@ Tests for the Man reader.
|
|||
-}
|
||||
module Tests.Readers.Man (tests) where
|
||||
|
||||
import Prelude
|
||||
import Data.Text (Text)
|
||||
import Test.Tasty
|
||||
import Tests.Helpers
|
||||
|
|
|
@ -1,4 +1,3 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{- |
|
||||
Module : Tests.Readers.Markdown
|
||||
|
@ -13,7 +12,6 @@ Tests for the Markdown reader.
|
|||
-}
|
||||
module Tests.Readers.Markdown (tests) where
|
||||
|
||||
import Prelude
|
||||
import Data.Text (Text, unpack)
|
||||
import qualified Data.Text as T
|
||||
import Test.Tasty
|
||||
|
|
|
@ -1,4 +1,3 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{- |
|
||||
Module : Tests.Readers.Muse
|
||||
|
@ -13,7 +12,6 @@ Tests for the Muse reader.
|
|||
-}
|
||||
module Tests.Readers.Muse (tests) where
|
||||
|
||||
import Prelude
|
||||
import Data.List (intersperse)
|
||||
import Data.Monoid (Any (..))
|
||||
import Data.Text (Text)
|
||||
|
|
|
@ -1,4 +1,3 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{- |
|
||||
Module : Tests.Readers.Odt
|
||||
|
@ -14,7 +13,6 @@ Tests for the ODT reader.
|
|||
-}
|
||||
module Tests.Readers.Odt (tests) where
|
||||
|
||||
import Prelude
|
||||
import Control.Monad (liftM)
|
||||
import qualified Data.ByteString as BS
|
||||
import qualified Data.ByteString.Lazy as B
|
||||
|
|
|
@ -1,4 +1,3 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{- |
|
||||
Module : Tests.Readers.Org.Block
|
||||
|
@ -13,7 +12,6 @@ Tests parsing of org blocks.
|
|||
-}
|
||||
module Tests.Readers.Org.Block (tests) where
|
||||
|
||||
import Prelude
|
||||
import Test.Tasty (TestTree, testGroup)
|
||||
import Tests.Helpers ((=?>))
|
||||
import Tests.Readers.Org.Shared ((=:), spcSep)
|
||||
|
|
|
@ -1,4 +1,3 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{- |
|
||||
Module : Tests.Readers.Org.Block.CodeBlock
|
||||
|
@ -13,7 +12,6 @@ Test parsing of org code blocks.
|
|||
-}
|
||||
module Tests.Readers.Org.Block.CodeBlock (tests) where
|
||||
|
||||
import Prelude
|
||||
import Test.Tasty (TestTree)
|
||||
import Tests.Helpers ((=?>))
|
||||
import Tests.Readers.Org.Shared ((=:), spcSep)
|
||||
|
|
|
@ -1,4 +1,3 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{- |
|
||||
Module : Tests.Readers.Org.Block.Figure
|
||||
|
@ -13,7 +12,6 @@ Test parsing of org figures.
|
|||
-}
|
||||
module Tests.Readers.Org.Block.Figure (tests) where
|
||||
|
||||
import Prelude
|
||||
import Test.Tasty (TestTree)
|
||||
import Tests.Helpers ((=?>))
|
||||
import Tests.Readers.Org.Shared ((=:))
|
||||
|
|
|
@ -1,4 +1,3 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{- |
|
||||
Module : Tests.Readers.Org.Block.Header
|
||||
|
@ -13,7 +12,6 @@ Test parsing of org header blocks.
|
|||
-}
|
||||
module Tests.Readers.Org.Block.Header (tests) where
|
||||
|
||||
import Prelude
|
||||
import Test.Tasty (TestTree, testGroup)
|
||||
import Tests.Helpers ((=?>))
|
||||
import Tests.Readers.Org.Shared ((=:), spcSep, tagSpan)
|
||||
|
|
|
@ -1,4 +1,3 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{- |
|
||||
Module : Tests.Readers.Org.Block.Header
|
||||
|
@ -13,7 +12,6 @@ Test parsing of org lists.
|
|||
-}
|
||||
module Tests.Readers.Org.Block.List (tests) where
|
||||
|
||||
import Prelude
|
||||
import Test.Tasty (TestTree)
|
||||
import Tests.Helpers ((=?>))
|
||||
import Tests.Readers.Org.Shared ((=:), spcSep)
|
||||
|
|
|
@ -1,4 +1,3 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{- |
|
||||
Module : Tests.Readers.Org.Block.Table
|
||||
|
@ -13,7 +12,6 @@ Test parsing of org tables.
|
|||
-}
|
||||
module Tests.Readers.Org.Block.Table (tests) where
|
||||
|
||||
import Prelude
|
||||
import Test.Tasty (TestTree)
|
||||
import Tests.Helpers ((=?>))
|
||||
import Tests.Readers.Org.Shared ((=:), spcSep)
|
||||
|
|
|
@ -1,4 +1,3 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{- |
|
||||
Module : Tests.Readers.Org.Directive
|
||||
|
@ -13,7 +12,6 @@ Tests parsing of org directives (like @#+OPTIONS@).
|
|||
-}
|
||||
module Tests.Readers.Org.Directive (tests) where
|
||||
|
||||
import Prelude
|
||||
import Data.Time (UTCTime (UTCTime), secondsToDiffTime)
|
||||
import Data.Time.Calendar (Day (ModifiedJulianDay))
|
||||
import Test.Tasty (TestTree, testGroup)
|
||||
|
|
|
@ -1,4 +1,3 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{- |
|
||||
Module : Tests.Readers.Org.Inline
|
||||
|
@ -13,7 +12,6 @@ Tests parsing of org inlines.
|
|||
-}
|
||||
module Tests.Readers.Org.Inline (tests) where
|
||||
|
||||
import Prelude
|
||||
import Data.List (intersperse)
|
||||
import Test.Tasty (TestTree, testGroup)
|
||||
import Tests.Helpers ((=?>))
|
||||
|
|
|
@ -1,4 +1,3 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{- |
|
||||
Module : Tests.Readers.Org.Inline.Citation
|
||||
|
@ -13,7 +12,6 @@ Test parsing of citations in org input.
|
|||
-}
|
||||
module Tests.Readers.Org.Inline.Citation (tests) where
|
||||
|
||||
import Prelude
|
||||
import Test.Tasty (TestTree, testGroup)
|
||||
import Tests.Helpers ((=?>))
|
||||
import Tests.Readers.Org.Shared ((=:))
|
||||
|
|
|
@ -1,4 +1,3 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{- |
|
||||
Module : Tests.Readers.Org.Inline.Note
|
||||
|
@ -13,7 +12,6 @@ Test parsing of footnotes in org input.
|
|||
-}
|
||||
module Tests.Readers.Org.Inline.Note (tests) where
|
||||
|
||||
import Prelude
|
||||
import Test.Tasty (TestTree)
|
||||
import Tests.Helpers ((=?>))
|
||||
import Tests.Readers.Org.Shared ((=:))
|
||||
|
|
|
@ -1,4 +1,3 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{- |
|
||||
Module : Tests.Readers.Org.Inline.Smart
|
||||
|
@ -13,7 +12,6 @@ Test smart parsing of quotes, apostrophe, etc.
|
|||
-}
|
||||
module Tests.Readers.Org.Inline.Smart (tests) where
|
||||
|
||||
import Prelude
|
||||
import Data.Text (Text)
|
||||
import Test.Tasty (TestTree)
|
||||
import Tests.Helpers ((=?>), purely, test)
|
||||
|
|
|
@ -1,4 +1,3 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{- |
|
||||
Module : Tests.Readers.Org.Meta
|
||||
|
@ -13,7 +12,6 @@ Tests parsing of org meta data (mostly lines starting with @#+@).
|
|||
-}
|
||||
module Tests.Readers.Org.Meta (tests) where
|
||||
|
||||
import Prelude
|
||||
import Test.Tasty (TestTree, testGroup)
|
||||
import Tests.Helpers ((=?>))
|
||||
import Tests.Readers.Org.Shared ((=:), spcSep)
|
||||
|
|
|
@ -1,4 +1,3 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{- |
|
||||
Module : Tests.Readers.Org.Shared
|
||||
|
@ -18,7 +17,6 @@ module Tests.Readers.Org.Shared
|
|||
, tagSpan
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Data.List (intersperse)
|
||||
import Data.Text (Text)
|
||||
import Tests.Helpers (ToString, purely, test)
|
||||
|
|
|
@ -1,4 +1,3 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-# LANGUAGE ScopedTypeVariables #-}
|
||||
{- |
|
||||
|
@ -14,7 +13,6 @@ Tests for the RST reader.
|
|||
-}
|
||||
module Tests.Readers.RST (tests) where
|
||||
|
||||
import Prelude
|
||||
import Data.Text (Text)
|
||||
import qualified Data.Text as T
|
||||
import Test.Tasty
|
||||
|
|
|
@ -1,4 +1,3 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{- |
|
||||
Module : Tests.Readers.Txt2Tags
|
||||
|
@ -14,7 +13,6 @@ Tests for the Txt2Tags reader.
|
|||
-}
|
||||
module Tests.Readers.Txt2Tags (tests) where
|
||||
|
||||
import Prelude
|
||||
import Data.List (intersperse)
|
||||
import Data.Text (Text)
|
||||
import qualified Data.Text as T
|
||||
|
|
|
@ -1,4 +1,3 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{- |
|
||||
Module : Tests.Shared
|
||||
|
@ -13,7 +12,6 @@ Tests for functions used in many parts of the library.
|
|||
-}
|
||||
module Tests.Shared (tests) where
|
||||
|
||||
import Prelude
|
||||
import System.FilePath.Posix (joinPath)
|
||||
import Test.Tasty
|
||||
import Test.Tasty.HUnit (assertBool, testCase, (@?=))
|
||||
|
|
|
@ -1,4 +1,3 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{- |
|
||||
Module : Tests.Writers.AnnotatedTable
|
||||
|
|
|
@ -1,8 +1,6 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
module Tests.Writers.AsciiDoc (tests) where
|
||||
|
||||
import Prelude
|
||||
import Data.Text (unpack)
|
||||
import Test.Tasty
|
||||
import Tests.Helpers
|
||||
|
|
|
@ -1,8 +1,6 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
module Tests.Writers.ConTeXt (tests) where
|
||||
|
||||
import Prelude
|
||||
import Data.Text (unpack, pack)
|
||||
import Test.Tasty
|
||||
import Test.Tasty.QuickCheck
|
||||
|
|
|
@ -1,8 +1,6 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
module Tests.Writers.Docbook (tests) where
|
||||
|
||||
import Prelude
|
||||
import Data.Text (unpack)
|
||||
import Test.Tasty
|
||||
import Tests.Helpers
|
||||
|
|
|
@ -1,7 +1,5 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
module Tests.Writers.Docx (tests) where
|
||||
|
||||
import Prelude
|
||||
import Text.Pandoc
|
||||
import Test.Tasty
|
||||
import Tests.Writers.OOXML
|
||||
|
|
|
@ -1,8 +1,6 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
module Tests.Writers.FB2 (tests) where
|
||||
|
||||
import Prelude
|
||||
import Test.Tasty
|
||||
import Tests.Helpers
|
||||
import Text.Pandoc
|
||||
|
|
|
@ -1,8 +1,6 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
module Tests.Writers.HTML (tests) where
|
||||
|
||||
import Prelude
|
||||
import Data.Text (unpack)
|
||||
import Test.Tasty
|
||||
import Tests.Helpers
|
||||
|
|
|
@ -1,8 +1,6 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
module Tests.Writers.JATS (tests) where
|
||||
|
||||
import Prelude
|
||||
import Data.Text (unpack)
|
||||
import Test.Tasty
|
||||
import Tests.Helpers
|
||||
|
|
|
@ -1,8 +1,6 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
module Tests.Writers.LaTeX (tests) where
|
||||
|
||||
import Prelude
|
||||
import Data.Text (unpack)
|
||||
import Test.Tasty
|
||||
import Tests.Helpers
|
||||
|
|
|
@ -1,9 +1,7 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-# OPTIONS_GHC -fno-warn-name-shadowing #-}
|
||||
module Tests.Writers.Markdown (tests) where
|
||||
|
||||
import Prelude
|
||||
import Data.Text (unpack)
|
||||
import Test.Tasty
|
||||
import Tests.Helpers
|
||||
|
|
|
@ -1,8 +1,6 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
module Tests.Writers.Ms (tests) where
|
||||
|
||||
import Prelude
|
||||
import Test.Tasty
|
||||
import Tests.Helpers
|
||||
import Text.Pandoc
|
||||
|
|
|
@ -1,4 +1,3 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
module Tests.Writers.Muse (tests) where
|
||||
|
||||
|
|
|
@ -1,7 +1,5 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
module Tests.Writers.Native (tests) where
|
||||
|
||||
import Prelude
|
||||
import Data.Text (unpack)
|
||||
import Test.Tasty
|
||||
import Test.Tasty.QuickCheck
|
||||
|
|
|
@ -1,10 +1,8 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE PatternGuards #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
|
||||
module Tests.Writers.OOXML (ooxmlTest) where
|
||||
|
||||
import Prelude
|
||||
import Text.Pandoc
|
||||
import Test.Tasty
|
||||
import Test.Tasty.Golden.Advanced
|
||||
|
|
|
@ -1,8 +1,6 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
module Tests.Writers.Org (tests) where
|
||||
|
||||
import Prelude
|
||||
import Test.Tasty
|
||||
import Tests.Helpers
|
||||
import Text.Pandoc
|
||||
|
|
|
@ -1,8 +1,6 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
module Tests.Writers.Plain (tests) where
|
||||
|
||||
import Prelude
|
||||
import Test.Tasty
|
||||
import Tests.Helpers
|
||||
import Text.Pandoc
|
||||
|
|
|
@ -1,7 +1,5 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
module Tests.Writers.Powerpoint (tests) where
|
||||
|
||||
import Prelude
|
||||
import Tests.Writers.OOXML (ooxmlTest)
|
||||
import Text.Pandoc
|
||||
import Test.Tasty
|
||||
|
|
|
@ -1,8 +1,6 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
module Tests.Writers.RST (tests) where
|
||||
|
||||
import Prelude
|
||||
import Control.Monad.Identity
|
||||
import Test.Tasty
|
||||
import Test.Tasty.HUnit
|
||||
|
|
|
@ -1,8 +1,6 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
module Tests.Writers.TEI (tests) where
|
||||
|
||||
import Prelude
|
||||
import Test.Tasty
|
||||
import Tests.Helpers
|
||||
import Text.Pandoc
|
||||
|
|
|
@ -1,9 +1,7 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# OPTIONS_GHC -Wall #-}
|
||||
|
||||
module Main where
|
||||
|
||||
import Prelude
|
||||
import System.Environment (getArgs)
|
||||
import qualified Control.Exception as E
|
||||
import Text.Pandoc.App (convertWithOpts, defaultOpts, options,
|
||||
|
|
|
@ -1,4 +1,3 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{- |
|
||||
Module : Main
|
||||
|
@ -12,7 +11,6 @@
|
|||
Provides a webservice which allows to try pandoc in the browser.
|
||||
-}
|
||||
module Main where
|
||||
import Prelude
|
||||
import Network.Wai.Handler.CGI
|
||||
import Network.Wai
|
||||
import Control.Applicative ((<$>))
|
||||
|
|
Loading…
Add table
Reference in a new issue