aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorJohn MacFarlane <[email protected]>2025-07-23 14:20:01 -0700
committerJohn MacFarlane <[email protected]>2025-07-23 14:20:01 -0700
commit1778cc29a66ae0b951a986b10459ee3436c7820e (patch)
tree1f5b2d702e0fd4c441ed63120ced76540ad80952
parentfb28952bec116fcf1b3d8e7848373004b66a4fe7 (diff)
Ensure that all modules have explicit export lists.
-rw-r--r--src/Text/Pandoc/Readers/ODT/Arrows/State.hs16
-rw-r--r--src/Text/Pandoc/Readers/ODT/Arrows/Utils.hs35
-rw-r--r--src/Text/Pandoc/Readers/ODT/Base.hs6
-rw-r--r--src/Text/Pandoc/Readers/ODT/Generic/Fallible.hs16
-rw-r--r--src/Text/Pandoc/Readers/ODT/Generic/Namespaces.hs6
-rw-r--r--src/Text/Pandoc/Readers/ODT/Generic/SetMap.hs8
-rw-r--r--test/test-pandoc.hs6
7 files changed, 83 insertions, 10 deletions
diff --git a/src/Text/Pandoc/Readers/ODT/Arrows/State.hs b/src/Text/Pandoc/Readers/ODT/Arrows/State.hs
index 742f6e9ee..5307c1063 100644
--- a/src/Text/Pandoc/Readers/ODT/Arrows/State.hs
+++ b/src/Text/Pandoc/Readers/ODT/Arrows/State.hs
@@ -17,7 +17,21 @@ Most of these might be implemented without access to innards, but it's much
faster and easier to implement this way.
-}
-module Text.Pandoc.Readers.ODT.Arrows.State where
+module Text.Pandoc.Readers.ODT.Arrows.State
+ ( ArrowState(..)
+ , withState
+ , modifyState
+ , ignoringState
+ , fromState
+ , extractFromState
+ , tryModifyState
+ , withSubStateF
+ , withSubStateF'
+ , foldS
+ , iterateS
+ , iterateSL
+ , iterateS'
+ ) where
import Control.Arrow
import qualified Control.Category as Cat
diff --git a/src/Text/Pandoc/Readers/ODT/Arrows/Utils.hs b/src/Text/Pandoc/Readers/ODT/Arrows/Utils.hs
index 339bff1cb..f39230616 100644
--- a/src/Text/Pandoc/Readers/ODT/Arrows/Utils.hs
+++ b/src/Text/Pandoc/Readers/ODT/Arrows/Utils.hs
@@ -19,7 +19,40 @@ with an equivalent return value.
-}
-- We export everything
-module Text.Pandoc.Readers.ODT.Arrows.Utils where
+module Text.Pandoc.Readers.ODT.Arrows.Utils
+ ( and2
+ , and3
+ , and4
+ , and5
+ , and6
+ , liftA2
+ , liftA3
+ , liftA4
+ , liftA5
+ , liftA6
+ , liftA
+ , duplicate
+ , (>>%)
+ , keepingTheValue
+ , (^|||)
+ , (|||^)
+ , (^|||^)
+ , (^&&&)
+ , (&&&^)
+ , choiceToMaybe
+ , maybeToChoice
+ , returnV
+ , FallibleArrow
+ , liftAsSuccess
+ , (>>?)
+ , (>>?^)
+ , (>>?^?)
+ , (^>>?)
+ , (>>?!)
+ , (>>?%)
+ , (>>?%?)
+ , ifFailedDo
+ ) where
import Prelude hiding (Applicative(..))
import Control.Arrow
diff --git a/src/Text/Pandoc/Readers/ODT/Base.hs b/src/Text/Pandoc/Readers/ODT/Base.hs
index 4a99f5ad6..bf0fbe86e 100644
--- a/src/Text/Pandoc/Readers/ODT/Base.hs
+++ b/src/Text/Pandoc/Readers/ODT/Base.hs
@@ -10,7 +10,11 @@
Core types of the odt reader.
-}
-module Text.Pandoc.Readers.ODT.Base where
+module Text.Pandoc.Readers.ODT.Base
+ ( ODTConverterState
+ , XMLReader
+ , XMLReaderSafe
+ ) where
import Text.Pandoc.Readers.ODT.Generic.XMLConverter
import Text.Pandoc.Readers.ODT.Namespaces
diff --git a/src/Text/Pandoc/Readers/ODT/Generic/Fallible.hs b/src/Text/Pandoc/Readers/ODT/Generic/Fallible.hs
index c6f45ced1..122e8f195 100644
--- a/src/Text/Pandoc/Readers/ODT/Generic/Fallible.hs
+++ b/src/Text/Pandoc/Readers/ODT/Generic/Fallible.hs
@@ -17,7 +17,21 @@ compatible instances of "ArrowChoice".
-}
-- We export everything
-module Text.Pandoc.Readers.ODT.Generic.Fallible where
+module Text.Pandoc.Readers.ODT.Generic.Fallible
+ ( Failure
+ , Fallible
+ , maybeToEither
+ , eitherToMaybe
+ , recover
+ , failWith
+ , failEmpty
+ , succeedWith
+ , collapseEither
+ , chooseMax
+ , chooseMaxWith
+ , ChoiceVector(..)
+ , SuccessList(..)
+ ) where
-- | Default for now. Will probably become a class at some point.
type Failure = ()
diff --git a/src/Text/Pandoc/Readers/ODT/Generic/Namespaces.hs b/src/Text/Pandoc/Readers/ODT/Generic/Namespaces.hs
index d7310d2e5..7d0136f29 100644
--- a/src/Text/Pandoc/Readers/ODT/Generic/Namespaces.hs
+++ b/src/Text/Pandoc/Readers/ODT/Generic/Namespaces.hs
@@ -11,7 +11,11 @@ A class containing a set of namespace identifiers. Used to convert between
typesafe Haskell namespace identifiers and unsafe "real world" namespaces.
-}
-module Text.Pandoc.Readers.ODT.Generic.Namespaces where
+module Text.Pandoc.Readers.ODT.Generic.Namespaces
+ ( NameSpaceIRI
+ , NameSpaceIRIs
+ , NameSpaceID(..)
+ ) where
import qualified Data.Map as M
import Data.Text (Text)
diff --git a/src/Text/Pandoc/Readers/ODT/Generic/SetMap.hs b/src/Text/Pandoc/Readers/ODT/Generic/SetMap.hs
index be586803b..50461890b 100644
--- a/src/Text/Pandoc/Readers/ODT/Generic/SetMap.hs
+++ b/src/Text/Pandoc/Readers/ODT/Generic/SetMap.hs
@@ -10,7 +10,13 @@
A map of values to sets of values.
-}
-module Text.Pandoc.Readers.ODT.Generic.SetMap where
+module Text.Pandoc.Readers.ODT.Generic.SetMap
+ ( SetMap
+ , empty
+ , fromList
+ , insert
+ , union3
+ ) where
import qualified Data.Map as M
import qualified Data.Set as S
diff --git a/test/test-pandoc.hs b/test/test-pandoc.hs
index d310b932f..2f53c16be 100644
--- a/test/test-pandoc.hs
+++ b/test/test-pandoc.hs
@@ -1,6 +1,4 @@
-{-# OPTIONS_GHC -Wall #-}
-
-module Main where
+module Main (main) where
import System.Environment (getArgs, getExecutablePath)
import qualified Control.Exception as E
@@ -122,4 +120,4 @@ main = do
_ -> inDirectory "test" $ do
fp <- getExecutablePath
-- putStrLn $ "Using pandoc executable at " ++ fp
- defaultMain $ tests fp
+ defaultMain $ tests fp \ No newline at end of file