diff options
author | John MacFarlane <jgm@berkeley.edu> | 2018-03-18 10:46:28 -0700 |
---|---|---|
committer | John MacFarlane <jgm@berkeley.edu> | 2018-03-18 10:46:28 -0700 |
commit | 7e389cb3dbdc11126b9bdb6a7741a65e5a94a43e (patch) | |
tree | 0e3ca00745cc0248d803c31e748889fcd02460fa /src/Text/Pandoc/Readers/Org | |
parent | daf731a001ee75ba3e09c8337278fe167ec347ae (diff) | |
download | pandoc-7e389cb3dbdc11126b9bdb6a7741a65e5a94a43e.tar.gz |
Use NoImplicitPrelude and explicitly import Prelude.
This seems to be necessary if we are to use our custom Prelude
with ghci.
Closes #4464.
Diffstat (limited to 'src/Text/Pandoc/Readers/Org')
-rw-r--r-- | src/Text/Pandoc/Readers/Org/BlockStarts.hs | 2 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Org/Blocks.hs | 2 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Org/DocumentTree.hs | 2 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Org/ExportSettings.hs | 2 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Org/Inlines.hs | 2 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Org/Meta.hs | 2 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Org/ParserState.hs | 2 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Org/Parsing.hs | 2 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Org/Shared.hs | 2 |
9 files changed, 18 insertions, 0 deletions
diff --git a/src/Text/Pandoc/Readers/Org/BlockStarts.hs b/src/Text/Pandoc/Readers/Org/BlockStarts.hs index 424102cb0..5dbce01bd 100644 --- a/src/Text/Pandoc/Readers/Org/BlockStarts.hs +++ b/src/Text/Pandoc/Readers/Org/BlockStarts.hs @@ -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 diff --git a/src/Text/Pandoc/Readers/Org/Blocks.hs b/src/Text/Pandoc/Readers/Org/Blocks.hs index de5cb007a..888cd9307 100644 --- a/src/Text/Pandoc/Readers/Org/Blocks.hs +++ b/src/Text/Pandoc/Readers/Org/Blocks.hs @@ -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 diff --git a/src/Text/Pandoc/Readers/Org/DocumentTree.hs b/src/Text/Pandoc/Readers/Org/DocumentTree.hs index ae244e3b0..c9465581a 100644 --- a/src/Text/Pandoc/Readers/Org/DocumentTree.hs +++ b/src/Text/Pandoc/Readers/Org/DocumentTree.hs @@ -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) diff --git a/src/Text/Pandoc/Readers/Org/ExportSettings.hs b/src/Text/Pandoc/Readers/Org/ExportSettings.hs index 6a70c50b9..d02eb37c5 100644 --- a/src/Text/Pandoc/Readers/Org/ExportSettings.hs +++ b/src/Text/Pandoc/Readers/Org/ExportSettings.hs @@ -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 diff --git a/src/Text/Pandoc/Readers/Org/Inlines.hs b/src/Text/Pandoc/Readers/Org/Inlines.hs index 6173669a5..91d3b7dd3 100644 --- a/src/Text/Pandoc/Readers/Org/Inlines.hs +++ b/src/Text/Pandoc/Readers/Org/Inlines.hs @@ -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 diff --git a/src/Text/Pandoc/Readers/Org/Meta.hs b/src/Text/Pandoc/Readers/Org/Meta.hs index 6ad403fd8..938e393bb 100644 --- a/src/Text/Pandoc/Readers/Org/Meta.hs +++ b/src/Text/Pandoc/Readers/Org/Meta.hs @@ -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 diff --git a/src/Text/Pandoc/Readers/Org/ParserState.hs b/src/Text/Pandoc/Readers/Org/ParserState.hs index 6316766fa..4cb5bb626 100644 --- a/src/Text/Pandoc/Readers/Org/ParserState.hs +++ b/src/Text/Pandoc/Readers/Org/ParserState.hs @@ -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 (..)) diff --git a/src/Text/Pandoc/Readers/Org/Parsing.hs b/src/Text/Pandoc/Readers/Org/Parsing.hs index 36420478b..e014de65e 100644 --- a/src/Text/Pandoc/Readers/Org/Parsing.hs +++ b/src/Text/Pandoc/Readers/Org/Parsing.hs @@ -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, diff --git a/src/Text/Pandoc/Readers/Org/Shared.hs b/src/Text/Pandoc/Readers/Org/Shared.hs index cba72cc07..07dbeca2a 100644 --- a/src/Text/Pandoc/Readers/Org/Shared.hs +++ b/src/Text/Pandoc/Readers/Org/Shared.hs @@ -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) |