Use NoImplicitPrelude and explicitly import Prelude.
This seems to be necessary if we are to use our custom Prelude with ghci. Closes #4464.
This commit is contained in:
parent
daf731a001
commit
7e389cb3db
177 changed files with 353 additions and 11 deletions
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-
|
||||
Copyright (C) 2006-2018 John MacFarlane <jgm@berkeley.edu>
|
||||
|
||||
|
@ -29,6 +30,7 @@ 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,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE CPP #-}
|
||||
{-# LANGUAGE DeriveGeneric #-}
|
||||
{-# LANGUAGE ScopedTypeVariables #-}
|
||||
|
@ -42,6 +43,7 @@ module Text.Pandoc.App (
|
|||
, options
|
||||
, applyFilters
|
||||
) where
|
||||
import Prelude
|
||||
import qualified Control.Exception as E
|
||||
import Control.Monad
|
||||
import Control.Monad.Except (catchError, throwError)
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-
|
||||
Copyright (C) 2013-2018 John MacFarlane <jgm@berkeley.edu>
|
||||
|
||||
|
@ -30,6 +31,7 @@ ascii equivalents (used in constructing HTML identifiers).
|
|||
-}
|
||||
module Text.Pandoc.Asciify (toAsciiChar)
|
||||
where
|
||||
import Prelude
|
||||
import Data.Char (isAscii)
|
||||
import qualified Data.Map as M
|
||||
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-
|
||||
Copyright (C) 2017–2018 John MacFarlane <jgm@berkeley.edu>
|
||||
|
||||
|
@ -34,6 +35,7 @@ module Text.Pandoc.BCP47 (
|
|||
, renderLang
|
||||
)
|
||||
where
|
||||
import Prelude
|
||||
import Control.Monad (guard)
|
||||
import Data.Char (isAlphaNum, isAscii, isLetter, isLower, isUpper, toLower,
|
||||
toUpper)
|
||||
|
|
|
@ -1,9 +1,11 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
module Text.Pandoc.CSS ( foldOrElse
|
||||
, pickStyleAttrProps
|
||||
, pickStylesToKVs
|
||||
)
|
||||
where
|
||||
|
||||
import Prelude
|
||||
import Text.Pandoc.Shared (trim)
|
||||
import Text.Parsec
|
||||
import Text.Parsec.String
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-
|
||||
Copyright (C) 2017–2018 John MacFarlane <jgm@berkeley.edu>
|
||||
|
||||
|
@ -34,6 +35,7 @@ module Text.Pandoc.CSV (
|
|||
ParseError
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Control.Monad (void)
|
||||
import Data.Text (Text)
|
||||
import qualified Data.Text as T
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE CPP #-}
|
||||
{-# LANGUAGE PatternGuards #-}
|
||||
{-# LANGUAGE DeriveFunctor #-}
|
||||
|
@ -96,6 +97,7 @@ module Text.Pandoc.Class ( PandocMonad(..)
|
|||
, Translations
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Prelude hiding (readFile)
|
||||
import System.Random (StdGen, next, mkStdGen)
|
||||
import qualified System.Random as IO (newStdGen)
|
||||
|
|
|
@ -1,7 +1,9 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE TemplateHaskell #-}
|
||||
|
||||
module Text.Pandoc.Data (dataFiles) where
|
||||
|
||||
import Prelude
|
||||
import qualified Data.ByteString as B
|
||||
import Data.FileEmbed
|
||||
import System.FilePath (splitDirectories)
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-
|
||||
Copyright (C) 2015 John MacFarlane <jgm@berkeley.edu>
|
||||
|
||||
|
@ -28,6 +29,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
|
|||
Emoji symbol lookup from canonical string identifier.
|
||||
-}
|
||||
module Text.Pandoc.Emoji ( emojis ) where
|
||||
import Prelude
|
||||
import qualified Data.Map as M
|
||||
|
||||
emojis :: M.Map String String
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE DeriveDataTypeable #-}
|
||||
{-# LANGUAGE DeriveGeneric #-}
|
||||
{-
|
||||
|
@ -34,6 +35,7 @@ module Text.Pandoc.Error (
|
|||
PandocError(..),
|
||||
handleError) where
|
||||
|
||||
import Prelude
|
||||
import Control.Exception (Exception)
|
||||
import Data.Typeable (Typeable)
|
||||
import GHC.Generics (Generic)
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE CPP #-}
|
||||
{-# LANGUAGE DeriveDataTypeable #-}
|
||||
{-# LANGUAGE DeriveGeneric #-}
|
||||
|
@ -48,6 +49,7 @@ module Text.Pandoc.Extensions ( Extension(..)
|
|||
, githubMarkdownExtensions
|
||||
, multimarkdownExtensions )
|
||||
where
|
||||
import Prelude
|
||||
import Data.Aeson (FromJSON (..), ToJSON (..), defaultOptions)
|
||||
import Data.Aeson.TH (deriveJSON)
|
||||
import Data.Bits (clearBit, setBit, testBit, (.|.))
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-
|
||||
Copyright (C) 2006-2017 John MacFarlane <jgm@berkeley.edu>
|
||||
|
||||
|
@ -33,6 +34,7 @@ module Text.Pandoc.Filter
|
|||
, applyFilters
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Data.Aeson (defaultOptions)
|
||||
import Data.Aeson.TH (deriveJSON)
|
||||
import Data.Foldable (foldrM)
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-
|
||||
Copyright (C) 2006-2018 John MacFarlane <jgm@berkeley.edu>
|
||||
|
||||
|
@ -29,6 +30,7 @@ Programmatically modifications of pandoc documents via JSON filters.
|
|||
-}
|
||||
module Text.Pandoc.Filter.JSON (apply) where
|
||||
|
||||
import Prelude
|
||||
import Control.Monad (unless, when)
|
||||
import Control.Monad.Trans (MonadIO (liftIO))
|
||||
import Data.Aeson (eitherDecode', encode)
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-
|
||||
Copyright (C) 2006-2018 John MacFarlane <jgm@berkeley.edu>
|
||||
|
||||
|
@ -29,6 +30,7 @@ Apply Lua filters to modify a pandoc documents programmatically.
|
|||
-}
|
||||
module Text.Pandoc.Filter.Lua (apply) where
|
||||
|
||||
import Prelude
|
||||
import Control.Exception (throw)
|
||||
import Text.Pandoc.Class (PandocIO)
|
||||
import Text.Pandoc.Definition (Pandoc)
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-
|
||||
Copyright (C) 2006-2018 John MacFarlane <jgm@berkeley.edu>
|
||||
|
||||
|
@ -31,6 +32,7 @@ module Text.Pandoc.Filter.Path
|
|||
( expandFilterPath
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Text.Pandoc.Class (PandocMonad, fileExists, getUserDataDir)
|
||||
import System.FilePath ((</>), isRelative)
|
||||
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-
|
||||
Copyright (C) 2008-2018 John MacFarlane <jgm@berkeley.edu>
|
||||
|
||||
|
@ -49,6 +50,7 @@ module Text.Pandoc.Highlighting ( highlightingStyles
|
|||
, fromListingsLanguage
|
||||
, toListingsLanguage
|
||||
) where
|
||||
import Prelude
|
||||
import Control.Monad
|
||||
import Data.Char (toLower)
|
||||
import qualified Data.Map as M
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE OverloadedStrings, ScopedTypeVariables, CPP #-}
|
||||
{-# OPTIONS_GHC -fno-warn-type-defaults #-}
|
||||
{-
|
||||
|
@ -49,6 +50,7 @@ module Text.Pandoc.ImageSize ( ImageType(..)
|
|||
, showInPixel
|
||||
, showFl
|
||||
) where
|
||||
import Prelude
|
||||
import Data.ByteString (ByteString, unpack)
|
||||
import qualified Data.ByteString.Char8 as B
|
||||
import qualified Data.ByteString.Lazy as BL
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE DeriveDataTypeable #-}
|
||||
{-# LANGUAGE DeriveGeneric #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
|
@ -39,6 +40,7 @@ module Text.Pandoc.Logging (
|
|||
, messageVerbosity
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Control.Monad (mzero)
|
||||
import Data.Aeson
|
||||
import Data.Aeson.Encode.Pretty (Config (..), defConfig, encodePretty',
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-
|
||||
Copyright © 2017–2018 Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
|
||||
|
||||
|
@ -31,6 +32,7 @@ module Text.Pandoc.Lua
|
|||
, runPandocLua
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Control.Monad ((>=>))
|
||||
import Foreign.Lua (FromLuaStack (peek), Lua, LuaException (..),
|
||||
Status (OK), ToLuaStack (push))
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE FlexibleContexts #-}
|
||||
|
||||
module Text.Pandoc.Lua.Filter ( LuaFilterFunction
|
||||
|
@ -10,6 +11,7 @@ module Text.Pandoc.Lua.Filter ( LuaFilterFunction
|
|||
, blockElementNames
|
||||
, inlineElementNames
|
||||
) where
|
||||
import Prelude
|
||||
import Control.Monad (mplus, unless, when, (>=>))
|
||||
import Control.Monad.Catch (finally)
|
||||
import Text.Pandoc.Definition
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-
|
||||
Copyright © 2017-2018 Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
|
||||
|
||||
|
@ -34,6 +35,7 @@ module Text.Pandoc.Lua.Init
|
|||
, registerScriptPath
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Control.Monad.Trans (MonadIO (..))
|
||||
import Data.Data (Data, dataTypeConstrs, dataTypeOf, showConstr)
|
||||
import Data.IORef (newIORef, readIORef)
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-
|
||||
Copyright © 2017-2018 Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
|
||||
|
||||
|
@ -29,6 +30,7 @@ module Text.Pandoc.Lua.Module.MediaBag
|
|||
( pushModule
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Control.Monad (zipWithM_)
|
||||
import Data.IORef (IORef, modifyIORef', readIORef)
|
||||
import Data.Maybe (fromMaybe)
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-
|
||||
Copyright © 2017-2018 Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
|
||||
|
||||
|
@ -30,6 +31,7 @@ module Text.Pandoc.Lua.Module.Pandoc
|
|||
( pushModule
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Control.Monad (when)
|
||||
import Data.Default (Default (..))
|
||||
import Data.Maybe (fromMaybe)
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-
|
||||
Copyright © 2017-2018 Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
|
||||
|
||||
|
@ -29,6 +30,7 @@ module Text.Pandoc.Lua.Module.Utils
|
|||
( pushModule
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Control.Applicative ((<|>))
|
||||
import Data.Default (def)
|
||||
import Foreign.Lua (FromLuaStack, Lua, LuaInteger, NumResults)
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-
|
||||
Copyright © 2017-2018 Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
|
||||
|
||||
|
@ -32,6 +33,7 @@ module Text.Pandoc.Lua.Packages
|
|||
, installPandocPackageSearcher
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Control.Monad (forM_)
|
||||
import Data.ByteString.Char8 (unpack)
|
||||
import Data.IORef (IORef)
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-
|
||||
Copyright © 2012-2018 John MacFarlane <jgm@berkeley.edu>
|
||||
2017-2018 Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
|
||||
|
@ -33,6 +34,7 @@ StackValue instances for pandoc types.
|
|||
-}
|
||||
module Text.Pandoc.Lua.StackInstances () where
|
||||
|
||||
import Prelude
|
||||
import Control.Applicative ((<|>))
|
||||
import Control.Monad (when)
|
||||
import Control.Monad.Catch (finally)
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-
|
||||
Copyright © 2012-2018 John MacFarlane <jgm@berkeley.edu>
|
||||
2017-2018 Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
|
||||
|
@ -46,6 +47,7 @@ module Text.Pandoc.Lua.Util
|
|||
, dostring'
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Control.Monad (when)
|
||||
import Control.Monad.Catch (finally)
|
||||
import Data.ByteString.Char8 (unpack)
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-
|
||||
Copyright (C) 2011-2018 John MacFarlane <jgm@berkeley.edu>
|
||||
|
||||
|
@ -29,6 +30,7 @@ Mime type lookup for ODT writer.
|
|||
-}
|
||||
module Text.Pandoc.MIME ( MimeType, getMimeType, getMimeTypeDef,
|
||||
extensionFromMimeType )where
|
||||
import Prelude
|
||||
import Data.Char (toLower)
|
||||
import Data.List (isPrefixOf, isSuffixOf)
|
||||
import qualified Data.Map as M
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE CPP #-}
|
||||
{-# LANGUAGE DeriveDataTypeable #-}
|
||||
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
|
||||
|
@ -37,6 +38,7 @@ module Text.Pandoc.MediaBag (
|
|||
insertMedia,
|
||||
mediaDirectory,
|
||||
) where
|
||||
import Prelude
|
||||
import qualified Data.ByteString.Lazy as BL
|
||||
import Data.Data (Data)
|
||||
import qualified Data.Map as M
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE DeriveDataTypeable #-}
|
||||
{-# LANGUAGE DeriveGeneric #-}
|
||||
{-# LANGUAGE TemplateHaskell #-}
|
||||
|
@ -46,6 +47,7 @@ module Text.Pandoc.Options ( module Text.Pandoc.Extensions
|
|||
, def
|
||||
, isEnabled
|
||||
) where
|
||||
import Prelude
|
||||
import Data.Aeson (defaultOptions)
|
||||
import Data.Aeson.TH (deriveJSON)
|
||||
import Data.Data (Data)
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE CPP #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-# LANGUAGE ScopedTypeVariables #-}
|
||||
|
@ -32,6 +33,7 @@ Conversion of LaTeX documents to PDF.
|
|||
-}
|
||||
module Text.Pandoc.PDF ( makePDF ) where
|
||||
|
||||
import Prelude
|
||||
import qualified Codec.Picture as JP
|
||||
import qualified Control.Exception as E
|
||||
import Control.Monad (unless, when)
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE CPP #-}
|
||||
{-# LANGUAGE ExplicitForAll #-}
|
||||
{-# LANGUAGE FlexibleContexts #-}
|
||||
|
@ -195,6 +196,7 @@ module Text.Pandoc.Parsing ( takeWhileP,
|
|||
)
|
||||
where
|
||||
|
||||
import Prelude
|
||||
import Control.Monad.Identity
|
||||
import Control.Monad.Reader
|
||||
import Data.Char (chr, isAlphaNum, isAscii, isAsciiUpper, isHexDigit,
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE CPP #-}
|
||||
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
|
||||
{-
|
||||
|
@ -77,6 +78,7 @@ module Text.Pandoc.Pretty (
|
|||
)
|
||||
|
||||
where
|
||||
import Prelude
|
||||
import Control.Monad
|
||||
import Control.Monad.State.Strict
|
||||
import Data.Char (isSpace)
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-
|
||||
Copyright (C) 2013-2018 John MacFarlane <jgm@berkeley.edu>
|
||||
|
||||
|
@ -29,6 +30,7 @@ ByteString variant of 'readProcessWithExitCode'.
|
|||
-}
|
||||
module Text.Pandoc.Process (pipeProcess)
|
||||
where
|
||||
import Prelude
|
||||
import Control.Concurrent (forkIO, newEmptyMVar, putMVar, takeMVar)
|
||||
import Control.Exception
|
||||
import Control.Monad (unless)
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE FlexibleInstances #-}
|
||||
{-# LANGUAGE GADTs #-}
|
||||
{-# LANGUAGE ScopedTypeVariables #-}
|
||||
|
@ -69,6 +70,7 @@ module Text.Pandoc.Readers
|
|||
, getDefaultExtensions
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Control.Monad.Except (throwError)
|
||||
import Data.Aeson
|
||||
import qualified Data.ByteString.Lazy as BL
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-
|
||||
Copyright (C) 2015-2018 John MacFarlane <jgm@berkeley.edu>
|
||||
|
||||
|
@ -32,6 +33,7 @@ CommonMark is a strongly specified variant of Markdown: http://commonmark.org.
|
|||
module Text.Pandoc.Readers.CommonMark (readCommonMark)
|
||||
where
|
||||
|
||||
import Prelude
|
||||
import CMarkGFM
|
||||
import Control.Monad.State
|
||||
import Data.Char (isAlphaNum, isLetter, isSpace, toLower)
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-
|
||||
Copyright (C) 2017 Sascha Wilde <wilde@sha-bang.de>
|
||||
|
||||
|
@ -35,6 +36,7 @@ Conversion of creole text to 'Pandoc' document.
|
|||
module Text.Pandoc.Readers.Creole ( readCreole
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Control.Monad.Except (guard, liftM2, throwError)
|
||||
import qualified Data.Foldable as F
|
||||
import Data.Maybe (fromMaybe)
|
||||
|
|
|
@ -1,5 +1,7 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE ExplicitForAll #-}
|
||||
module Text.Pandoc.Readers.DocBook ( readDocBook ) where
|
||||
import Prelude
|
||||
import Control.Monad.State.Strict
|
||||
import Data.Char (isSpace, toUpper)
|
||||
import Data.Default
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE CPP #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-# LANGUAGE PatternGuards #-}
|
||||
|
@ -74,6 +75,7 @@ module Text.Pandoc.Readers.Docx
|
|||
( readDocx
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Codec.Archive.Zip
|
||||
import Control.Monad.Reader
|
||||
import Control.Monad.State.Strict
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE FlexibleInstances #-}
|
||||
{-# LANGUAGE PatternGuards #-}
|
||||
{-# LANGUAGE TypeSynonymInstances #-}
|
||||
|
@ -7,6 +8,7 @@ module Text.Pandoc.Readers.Docx.Combine ( smushInlines
|
|||
)
|
||||
where
|
||||
|
||||
import Prelude
|
||||
import Data.List
|
||||
import Data.Sequence (ViewL (..), ViewR (..), viewl, viewr, (><), (|>))
|
||||
import qualified Data.Sequence as Seq (null)
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-
|
||||
Copyright (C) 2014-2018 Jesse Rosenthal <jrosenthal@jhu.edu>
|
||||
|
||||
|
@ -32,6 +33,7 @@ module Text.Pandoc.Readers.Docx.Fields ( FieldInfo(..)
|
|||
, parseFieldInfo
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Text.Parsec
|
||||
import Text.Parsec.String (Parser)
|
||||
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-
|
||||
Copyright (C) 2014-2018 Jesse Rosenthal <jrosenthal@jhu.edu>
|
||||
|
||||
|
@ -33,6 +34,7 @@ module Text.Pandoc.Readers.Docx.Lists ( blocksToBullets
|
|||
, listParagraphDivs
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Data.List
|
||||
import Data.Maybe
|
||||
import Text.Pandoc.Generic (bottomUp)
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE FlexibleInstances #-}
|
||||
{-# LANGUAGE PatternGuards #-}
|
||||
{-# LANGUAGE ViewPatterns #-}
|
||||
|
@ -58,6 +59,7 @@ module Text.Pandoc.Readers.Docx.Parse ( Docx(..)
|
|||
, archiveToDocx
|
||||
, archiveToDocxWithWarnings
|
||||
) where
|
||||
import Prelude
|
||||
import Codec.Archive.Zip
|
||||
import Control.Applicative ((<|>))
|
||||
import Control.Monad.Except
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
module Text.Pandoc.Readers.Docx.StyleMap ( StyleMaps(..)
|
||||
, alterMap
|
||||
, getMap
|
||||
|
@ -7,6 +8,7 @@ module Text.Pandoc.Readers.Docx.StyleMap ( StyleMaps(..)
|
|||
, hasStyleName
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Control.Monad.State.Strict
|
||||
import Data.Char (toLower)
|
||||
import qualified Data.Map as M
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
module Text.Pandoc.Readers.Docx.Util (
|
||||
NameSpaces
|
||||
, elemName
|
||||
|
@ -8,6 +9,7 @@ module Text.Pandoc.Readers.Docx.Util (
|
|||
, findAttrByName
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Data.Maybe (mapMaybe)
|
||||
import Text.XML.Light
|
||||
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE FlexibleContexts #-}
|
||||
|
||||
{-# LANGUAGE TupleSections #-}
|
||||
|
@ -7,6 +8,7 @@ module Text.Pandoc.Readers.EPUB
|
|||
(readEPUB)
|
||||
where
|
||||
|
||||
import Prelude
|
||||
import Codec.Archive.Zip (Archive (..), Entry, findEntryByPath, fromEntry,
|
||||
toArchiveOrFail)
|
||||
import Control.DeepSeq (NFData, deepseq)
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE FlexibleContexts #-}
|
||||
{-# LANGUAGE FlexibleInstances #-}
|
||||
{-# LANGUAGE MultiParamTypeClasses #-}
|
||||
|
@ -42,6 +43,7 @@ module Text.Pandoc.Readers.HTML ( readHtml
|
|||
, isCommentTag
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Control.Applicative ((<|>))
|
||||
import Control.Arrow (first)
|
||||
import Control.Monad (guard, mplus, msum, mzero, unless, void)
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE CPP #-}
|
||||
{- |
|
||||
Module : Text.Pandoc.Readers.Haddock
|
||||
|
@ -14,6 +15,7 @@ module Text.Pandoc.Readers.Haddock
|
|||
( readHaddock
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Control.Monad.Except (throwError)
|
||||
import Data.List (intersperse, stripPrefix)
|
||||
import Data.Maybe (fromMaybe)
|
||||
|
|
|
@ -1,5 +1,7 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE ExplicitForAll, TupleSections #-}
|
||||
module Text.Pandoc.Readers.JATS ( readJATS ) where
|
||||
import Prelude
|
||||
import Control.Monad.State.Strict
|
||||
import Data.Char (isDigit, isSpace, toUpper)
|
||||
import Data.Default
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE FlexibleInstances #-}
|
||||
{-# LANGUAGE MultiParamTypeClasses #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
|
@ -42,6 +43,7 @@ module Text.Pandoc.Readers.LaTeX ( readLaTeX,
|
|||
untokenize
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Control.Applicative (many, optional, (<|>))
|
||||
import Control.Monad
|
||||
import Control.Monad.Except (throwError)
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-
|
||||
Copyright (C) 2017-2018 John MacFarlane <jgm@berkeley.edu>
|
||||
|
||||
|
@ -34,6 +35,7 @@ module Text.Pandoc.Readers.LaTeX.Types ( Tok(..)
|
|||
, SourcePos
|
||||
)
|
||||
where
|
||||
import Prelude
|
||||
import Data.Text (Text)
|
||||
import Text.Parsec.Pos (SourcePos)
|
||||
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE RelaxedPolyRec #-}
|
||||
{-# LANGUAGE ScopedTypeVariables #-}
|
||||
|
||||
|
@ -32,6 +33,7 @@ Conversion of markdown-formatted plain text to 'Pandoc' document.
|
|||
-}
|
||||
module Text.Pandoc.Readers.Markdown ( readMarkdown ) where
|
||||
|
||||
import Prelude
|
||||
import Control.Monad
|
||||
import Control.Monad.Except (throwError)
|
||||
import Data.Char (isAlphaNum, isPunctuation, isSpace, toLower)
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE FlexibleInstances #-}
|
||||
{-# LANGUAGE RelaxedPolyRec #-}
|
||||
{-# LANGUAGE TypeSynonymInstances #-}
|
||||
|
@ -38,6 +39,7 @@ _ parse templates?
|
|||
-}
|
||||
module Text.Pandoc.Readers.MediaWiki ( readMediaWiki ) where
|
||||
|
||||
import Prelude
|
||||
import Control.Monad
|
||||
import Control.Monad.Except (throwError)
|
||||
import Data.Char (isDigit, isSpace)
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE FlexibleContexts #-}
|
||||
{-
|
||||
Copyright (C) 2017-2018 Alexander Krotov <ilabdsf@gmail.com>
|
||||
|
@ -39,6 +40,7 @@ TODO:
|
|||
-}
|
||||
module Text.Pandoc.Readers.Muse (readMuse) where
|
||||
|
||||
import Prelude
|
||||
import Control.Monad
|
||||
import Control.Monad.Except (throwError)
|
||||
import Data.Char (isLetter)
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-
|
||||
Copyright (C) 2011-2018 John MacFarlane <jgm@berkeley.edu>
|
||||
|
||||
|
@ -30,6 +31,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.Options (ReaderOptions)
|
||||
import Text.Pandoc.Shared (safeRead)
|
||||
|
|
|
@ -1,5 +1,7 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE FlexibleContexts #-}
|
||||
module Text.Pandoc.Readers.OPML ( readOPML ) where
|
||||
import Prelude
|
||||
import Control.Monad.State.Strict
|
||||
import Data.Char (toUpper)
|
||||
import Data.Default
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE PatternGuards #-}
|
||||
|
||||
{-
|
||||
|
@ -32,6 +33,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
|
||||
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE FlexibleInstances #-}
|
||||
{-# LANGUAGE TupleSections #-}
|
||||
{-
|
||||
|
@ -37,14 +38,13 @@ faster and easier to implement this way.
|
|||
|
||||
module Text.Pandoc.Readers.Odt.Arrows.State where
|
||||
|
||||
import Prelude
|
||||
import Prelude hiding (foldl, foldr)
|
||||
|
||||
import Control.Arrow
|
||||
import qualified Control.Category as Cat
|
||||
import Control.Monad
|
||||
|
||||
import Data.Foldable
|
||||
|
||||
import Text.Pandoc.Readers.Odt.Arrows.Utils
|
||||
import Text.Pandoc.Readers.Odt.Generic.Fallible
|
||||
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-
|
||||
Copyright (C) 2015 Martin Linnemann <theCodingMarlin@googlemail.com>
|
||||
|
||||
|
@ -39,6 +40,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)
|
||||
|
||||
|
|
|
@ -1,5 +1,3 @@
|
|||
|
||||
|
||||
{-
|
||||
Copyright (C) 2015 Martin Linnemann <theCodingMarlin@googlemail.com>
|
||||
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE Arrows #-}
|
||||
{-# LANGUAGE PatternGuards #-}
|
||||
{-# LANGUAGE RecordWildCards #-}
|
||||
|
@ -39,6 +40,7 @@ module Text.Pandoc.Readers.Odt.ContentReader
|
|||
, read_body
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Control.Applicative hiding (liftA, liftA2, liftA3)
|
||||
import Control.Arrow
|
||||
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
|
||||
|
||||
{-
|
||||
|
@ -38,6 +39,7 @@ compatible instances of "ArrowChoice".
|
|||
|
||||
-- We export everything
|
||||
module Text.Pandoc.Readers.Odt.Generic.Fallible where
|
||||
import Prelude
|
||||
|
||||
-- | Default for now. Will probably become a class at some point.
|
||||
type Failure = ()
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-
|
||||
Copyright (C) 2015 Martin Linnemann <theCodingMarlin@googlemail.com>
|
||||
|
||||
|
@ -31,6 +32,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
|
||||
|
||||
--
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-
|
||||
Copyright (C) 2015 Martin Linnemann <theCodingMarlin@googlemail.com>
|
||||
|
||||
|
@ -30,6 +31,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
|
||||
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
|
||||
|
||||
{-# LANGUAGE TypeOperators #-}
|
||||
|
@ -51,6 +52,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)
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE Arrows #-}
|
||||
{-# LANGUAGE TupleSections #-}
|
||||
{-# LANGUAGE GADTs #-}
|
||||
|
@ -67,6 +68,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
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-
|
||||
Copyright (C) 2015 Martin Linnemann <theCodingMarlin@googlemail.com>
|
||||
|
||||
|
@ -31,6 +32,7 @@ Namespaces used in odt files.
|
|||
module Text.Pandoc.Readers.Odt.Namespaces ( Namespace (..)
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Data.List (isPrefixOf)
|
||||
import qualified Data.Map as M (empty, insert)
|
||||
import Data.Maybe (fromMaybe, listToMaybe)
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE CPP #-}
|
||||
{-# LANGUAGE Arrows #-}
|
||||
{-# LANGUAGE RecordWildCards #-}
|
||||
|
@ -57,6 +58,7 @@ module Text.Pandoc.Readers.Odt.StyleReader
|
|||
, readStylesAt
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Control.Applicative hiding (liftA, liftA2, liftA3)
|
||||
import Control.Arrow
|
||||
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-
|
||||
Copyright (C) 2014-2018 Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
|
||||
|
||||
|
@ -27,6 +28,7 @@ Conversion of org-mode formatted plain text to 'Pandoc' document.
|
|||
-}
|
||||
module Text.Pandoc.Readers.Org ( readOrg ) where
|
||||
|
||||
import Prelude
|
||||
import Text.Pandoc.Readers.Org.Blocks (blockList, meta)
|
||||
import Text.Pandoc.Readers.Org.ParserState (optionsToParserState)
|
||||
import Text.Pandoc.Readers.Org.Parsing (OrgParser, readWithM)
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-
|
||||
Copyright (C) 2014-2018 Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
|
||||
|
||||
|
@ -40,6 +41,7 @@ module Text.Pandoc.Readers.Org.BlockStarts
|
|||
, endOfBlock
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Control.Monad (void)
|
||||
import Text.Pandoc.Readers.Org.Parsing
|
||||
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-
|
||||
Copyright (C) 2014-2018 Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
|
||||
|
||||
|
@ -31,6 +32,7 @@ module Text.Pandoc.Readers.Org.Blocks
|
|||
, meta
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Text.Pandoc.Readers.Org.BlockStarts
|
||||
import Text.Pandoc.Readers.Org.DocumentTree (documentTree, headlineToBlocks)
|
||||
import Text.Pandoc.Readers.Org.Inlines
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-
|
||||
Copyright (C) 2014-2018 Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
|
||||
|
||||
|
@ -32,6 +33,7 @@ module Text.Pandoc.Readers.Org.DocumentTree
|
|||
, headlineToBlocks
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Control.Arrow ((***))
|
||||
import Control.Monad (guard, void)
|
||||
import Data.Char (toLower, toUpper)
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-
|
||||
Copyright (C) 2016-2018 Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
|
||||
|
||||
|
@ -29,6 +30,7 @@ module Text.Pandoc.Readers.Org.ExportSettings
|
|||
( exportSettings
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Text.Pandoc.Readers.Org.ParserState
|
||||
import Text.Pandoc.Readers.Org.Parsing
|
||||
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-
|
||||
Copyright (C) 2014-2018 Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
|
||||
|
@ -33,6 +34,7 @@ module Text.Pandoc.Readers.Org.Inlines
|
|||
, linkTarget
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Text.Pandoc.Readers.Org.BlockStarts (endOfBlock, noteMarker)
|
||||
import Text.Pandoc.Readers.Org.ParserState
|
||||
import Text.Pandoc.Readers.Org.Parsing
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE FlexibleContexts #-}
|
||||
{-# LANGUAGE TupleSections #-}
|
||||
{-
|
||||
|
@ -33,6 +34,7 @@ module Text.Pandoc.Readers.Org.Meta
|
|||
, metaLine
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Text.Pandoc.Readers.Org.BlockStarts
|
||||
import Text.Pandoc.Readers.Org.ExportSettings (exportSettings)
|
||||
import Text.Pandoc.Readers.Org.Inlines
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE FlexibleInstances #-}
|
||||
{-# LANGUAGE MultiParamTypeClasses #-}
|
||||
{-
|
||||
|
@ -54,6 +55,7 @@ module Text.Pandoc.Readers.Org.ParserState
|
|||
, optionsToParserState
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Control.Monad.Reader (ReaderT, asks, local)
|
||||
|
||||
import Data.Default (Default (..))
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-
|
||||
Copyright (C) 2014-2018 Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
|
||||
|
||||
|
@ -112,6 +113,7 @@ module Text.Pandoc.Readers.Org.Parsing
|
|||
, getPosition
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Text.Pandoc.Readers.Org.ParserState
|
||||
|
||||
import Text.Pandoc.Parsing hiding (F, anyLine, blanklines, newline,
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-
|
||||
Copyright (C) 2014-2018 Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
|
||||
|
@ -33,6 +34,7 @@ module Text.Pandoc.Readers.Org.Shared
|
|||
, translateLang
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Data.Char (isAlphaNum)
|
||||
import Data.List (isPrefixOf, isSuffixOf)
|
||||
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE FlexibleContexts #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-# LANGUAGE ScopedTypeVariables #-}
|
||||
|
@ -31,6 +32,7 @@ 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 Prelude
|
||||
import Control.Arrow (second)
|
||||
import Control.Monad (forM_, guard, liftM, mplus, mzero, when)
|
||||
import Control.Monad.Except (throwError)
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE FlexibleContexts #-}
|
||||
{-# LANGUAGE FlexibleInstances #-}
|
||||
{-# LANGUAGE RelaxedPolyRec #-}
|
||||
|
@ -35,6 +36,7 @@ Conversion of twiki text to 'Pandoc' document.
|
|||
module Text.Pandoc.Readers.TWiki ( readTWiki
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Control.Monad
|
||||
import Control.Monad.Except (throwError)
|
||||
import Data.Char (isAlphaNum)
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-
|
||||
Copyright (C) 2010-2012 Paul Rivier <paul*rivier#demotera*com> | tr '*#' '.@'
|
||||
2010-2018 John MacFarlane
|
||||
|
@ -52,6 +53,7 @@ TODO : refactor common patterns across readers :
|
|||
|
||||
|
||||
module Text.Pandoc.Readers.Textile ( readTextile) where
|
||||
import Prelude
|
||||
import Control.Monad (guard, liftM)
|
||||
import Control.Monad.Except (throwError)
|
||||
import Data.Char (digitToInt, isUpper)
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE FlexibleContexts #-}
|
||||
{-# LANGUAGE FlexibleInstances #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
|
@ -19,6 +20,7 @@ Conversion of TikiWiki text to 'Pandoc' document.
|
|||
module Text.Pandoc.Readers.TikiWiki ( readTikiWiki
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Control.Monad
|
||||
import Control.Monad.Except (throwError)
|
||||
import qualified Data.Foldable as F
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-
|
||||
Copyright (C) 2014 Matthew Pickering <matthewtpickering@gmail.com>
|
||||
|
||||
|
@ -31,6 +32,7 @@ module Text.Pandoc.Readers.Txt2Tags ( readTxt2Tags
|
|||
)
|
||||
where
|
||||
|
||||
import Prelude
|
||||
import Control.Monad (guard, void, when)
|
||||
import Control.Monad.Except (catchError, throwError)
|
||||
import Control.Monad.Reader (Reader, asks, runReader)
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE CPP #-}
|
||||
{-
|
||||
Copyright (C) 2017-2018 Yuchen Pei <me@ypei.me>
|
||||
|
@ -64,6 +65,7 @@ Conversion of vimwiki text to 'Pandoc' document.
|
|||
|
||||
module Text.Pandoc.Readers.Vimwiki ( readVimwiki
|
||||
) where
|
||||
import Prelude
|
||||
import Control.Monad (guard)
|
||||
import Control.Monad.Except (throwError)
|
||||
import Data.Default
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-
|
||||
Copyright (C) 2011-2018 John MacFarlane <jgm@berkeley.edu>
|
||||
|
@ -31,6 +32,7 @@ offline, by incorporating linked images, CSS, and scripts into
|
|||
the HTML using data URIs.
|
||||
-}
|
||||
module Text.Pandoc.SelfContained ( makeDataURI, makeSelfContained ) where
|
||||
import Prelude
|
||||
import Codec.Compression.GZip as Gzip
|
||||
import Control.Applicative ((<|>))
|
||||
import Control.Monad.Except (throwError)
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE CPP #-}
|
||||
{-# LANGUAGE DeriveDataTypeable #-}
|
||||
{-# LANGUAGE FlexibleContexts #-}
|
||||
|
@ -100,6 +101,7 @@ module Text.Pandoc.Shared (
|
|||
pandocVersion
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Codec.Archive.Zip
|
||||
import qualified Control.Exception as E
|
||||
import Control.Monad (MonadPlus (..), msum, unless)
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-
|
||||
Copyright (C) 2012-2018 John MacFarlane <jgm@berkeley.edu>
|
||||
|
||||
|
@ -29,6 +30,7 @@ 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
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE FlexibleInstances #-}
|
||||
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
|
@ -38,6 +39,7 @@ module Text.Pandoc.Templates ( module Text.DocTemplates
|
|||
, getDefaultTemplate
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Control.Monad.Except (throwError)
|
||||
import Data.Aeson (ToJSON (..))
|
||||
import qualified Data.Text as T
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE CPP #-}
|
||||
{-# LANGUAGE DeriveGeneric #-}
|
||||
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
|
||||
|
@ -46,6 +47,7 @@ module Text.Pandoc.Translations (
|
|||
, readTranslations
|
||||
)
|
||||
where
|
||||
import Prelude
|
||||
import Data.Aeson.Types (typeMismatch)
|
||||
import qualified Data.HashMap.Strict as HM
|
||||
import qualified Data.Map as M
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-
|
||||
Copyright (C) 2010-2018 John MacFarlane <jgm@berkeley.edu>
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-
|
||||
Copyright (C) 2010-2018 John MacFarlane <jgm@berkeley.edu>
|
||||
|
||||
|
@ -31,6 +32,7 @@ in RFC4122. See http://tools.ietf.org/html/rfc4122
|
|||
|
||||
module Text.Pandoc.UUID ( UUID(..), getRandomUUID, getUUID ) where
|
||||
|
||||
import Prelude
|
||||
import Data.Bits (clearBit, setBit)
|
||||
import Data.Word
|
||||
import System.Random (RandomGen, getStdGen, randoms)
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-
|
||||
Copyright (C) 2006-2018 John MacFarlane <jgm@berkeley.edu>
|
||||
|
||||
|
@ -82,6 +83,7 @@ module Text.Pandoc.Writers
|
|||
, getWriter
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Data.Aeson
|
||||
import qualified Data.ByteString.Lazy as BL
|
||||
import Data.List (intercalate)
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-
|
||||
Copyright (C) 2006-2018 John MacFarlane <jgm@berkeley.edu>
|
||||
|
@ -37,6 +38,7 @@ that it has omitted the construct.
|
|||
AsciiDoc: <http://www.methods.co.nz/asciidoc/>
|
||||
-}
|
||||
module Text.Pandoc.Writers.AsciiDoc (writeAsciiDoc) where
|
||||
import Prelude
|
||||
import Control.Monad.State.Strict
|
||||
import Data.Aeson (Result (..), Value (String), fromJSON, toJSON)
|
||||
import Data.Char (isPunctuation, isSpace)
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-
|
||||
Copyright (C) 2015-2018 John MacFarlane <jgm@berkeley.edu>
|
||||
|
@ -32,6 +33,7 @@ CommonMark: <http://commonmark.org>
|
|||
-}
|
||||
module Text.Pandoc.Writers.CommonMark (writeCommonMark) where
|
||||
|
||||
import Prelude
|
||||
import CMarkGFM
|
||||
import Control.Monad.State.Strict (State, get, modify, runState)
|
||||
import Data.Foldable (foldrM)
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-# LANGUAGE ScopedTypeVariables #-}
|
||||
{-
|
||||
|
@ -30,6 +31,7 @@ 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 Control.Monad.State.Strict
|
||||
import Data.Char (ord, isDigit)
|
||||
import Data.List (intercalate, intersperse)
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE DeriveDataTypeable #-}
|
||||
{-# LANGUAGE FlexibleInstances #-}
|
||||
{- Copyright (C) 2012-2018 John MacFarlane <jgm@berkeley.edu>
|
||||
|
@ -30,6 +31,7 @@ Conversion of 'Pandoc' documents to custom markup using
|
|||
a lua writer.
|
||||
-}
|
||||
module Text.Pandoc.Writers.Custom ( writeCustom ) where
|
||||
import Prelude
|
||||
import Control.Arrow ((***))
|
||||
import Control.Exception
|
||||
import Control.Monad (when)
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-# LANGUAGE PatternGuards #-}
|
||||
{-
|
||||
|
@ -30,6 +31,7 @@ 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 Prelude
|
||||
import Control.Monad.Reader
|
||||
import Data.Char (toLower)
|
||||
import Data.Generics (everywhere, mkT)
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE PatternGuards #-}
|
||||
{-# LANGUAGE RankNTypes #-}
|
||||
{-# LANGUAGE ScopedTypeVariables #-}
|
||||
|
@ -32,6 +33,7 @@ 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 Codec.Archive.Zip
|
||||
import Control.Applicative ((<|>))
|
||||
import Control.Monad.Except (catchError)
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-
|
||||
Copyright (C) 2008-2018 John MacFarlane <jgm@berkeley.edu>
|
||||
|
||||
|
@ -39,6 +40,7 @@ DokuWiki: <https://www.dokuwiki.org/dokuwiki>
|
|||
-}
|
||||
|
||||
module Text.Pandoc.Writers.DokuWiki ( writeDokuWiki ) where
|
||||
import Prelude
|
||||
import Control.Monad (zipWithM)
|
||||
import Control.Monad.Reader (ReaderT, ask, local, runReaderT)
|
||||
import Control.Monad.State.Strict (StateT, evalStateT)
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE CPP #-}
|
||||
{-# LANGUAGE FlexibleContexts #-}
|
||||
{-# LANGUAGE PatternGuards #-}
|
||||
|
@ -32,6 +33,7 @@ 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 Prelude
|
||||
import Codec.Archive.Zip (Entry, addEntryToArchive, eRelativePath, emptyArchive,
|
||||
fromArchive, fromEntry, toEntry)
|
||||
import Control.Monad (mplus, unless, when, zipWithM)
|
||||
|
|
Some files were not shown because too many files have changed in this diff Show more
Loading…
Add table
Reference in a new issue