diff --git a/Data/IntMap/Lazy.hs b/Data/IntMap/Lazy.hs
index 455308e52e9e4e502f8747517df51b3e69f92f72..fed65387444b20b91cf9badd385ab3913d0aee84 100644
--- a/Data/IntMap/Lazy.hs
+++ b/Data/IntMap/Lazy.hs
@@ -50,154 +50,154 @@
 -----------------------------------------------------------------------------
 
 module Data.IntMap.Lazy (
-            -- * Strictness properties
-            -- $strictness
+    -- * Strictness properties
+    -- $strictness
 
-            -- * Map type
+    -- * Map type
 #if !defined(TESTING)
-              IntMap, Key          -- instance Eq,Show
+    IntMap, Key          -- instance Eq,Show
 #else
-              IntMap(..), Key          -- instance Eq,Show
+    IntMap(..), Key          -- instance Eq,Show
 #endif
 
-            -- * Operators
-            , (!), (\\)
-
-            -- * Query
-            , IM.null
-            , size
-            , member
-            , notMember
-            , IM.lookup
-            , findWithDefault
-            , lookupLT
-            , lookupGT
-            , lookupLE
-            , lookupGE
-
-            -- * Construction
-            , empty
-            , singleton
-
-            -- ** Insertion
-            , insert
-            , insertWith
-            , insertWithKey
-            , insertLookupWithKey
-
-            -- ** Delete\/Update
-            , delete
-            , adjust
-            , adjustWithKey
-            , update
-            , updateWithKey
-            , updateLookupWithKey
-            , alter
-
-            -- * Combine
-
-            -- ** Union
-            , union
-            , unionWith
-            , unionWithKey
-            , unions
-            , unionsWith
-
-            -- ** Difference
-            , difference
-            , differenceWith
-            , differenceWithKey
-
-            -- ** Intersection
-            , intersection
-            , intersectionWith
-            , intersectionWithKey
-
-            -- ** Universal combining function
-            , mergeWithKey
-
-            -- * Traversal
-            -- ** Map
-            , IM.map
-            , mapWithKey
-            , traverseWithKey
-            , mapAccum
-            , mapAccumWithKey
-            , mapAccumRWithKey
-            , mapKeys
-            , mapKeysWith
-            , mapKeysMonotonic
-
-            -- * Folds
-            , IM.foldr
-            , IM.foldl
-            , foldrWithKey
-            , foldlWithKey
-            -- ** Strict folds
-            , foldr'
-            , foldl'
-            , foldrWithKey'
-            , foldlWithKey'
-
-            -- * Conversion
-            , elems
-            , keys
-            , assocs
-            , keysSet
-            , fromSet
-
-            -- ** Lists
-            , toList
-            , fromList
-            , fromListWith
-            , fromListWithKey
-
-            -- ** Ordered lists
-            , toAscList
-            , toDescList
-            , fromAscList
-            , fromAscListWith
-            , fromAscListWithKey
-            , fromDistinctAscList
-
-            -- * Filter
-            , IM.filter
-            , filterWithKey
-            , partition
-            , partitionWithKey
-
-            , mapMaybe
-            , mapMaybeWithKey
-            , mapEither
-            , mapEitherWithKey
-
-            , split
-            , splitLookup
-
-            -- * Submap
-            , isSubmapOf, isSubmapOfBy
-            , isProperSubmapOf, isProperSubmapOfBy
-
-            -- * Min\/Max
-            , findMin
-            , findMax
-            , deleteMin
-            , deleteMax
-            , deleteFindMin
-            , deleteFindMax
-            , updateMin
-            , updateMax
-            , updateMinWithKey
-            , updateMaxWithKey
-            , minView
-            , maxView
-            , minViewWithKey
-            , maxViewWithKey
-
-            -- * Debugging
-            , showTree
-            , showTreeWith
-            ) where
+    -- * Operators
+    , (!), (\\)
+
+    -- * Query
+    , IM.null
+    , size
+    , member
+    , notMember
+    , IM.lookup
+    , findWithDefault
+    , lookupLT
+    , lookupGT
+    , lookupLE
+    , lookupGE
+
+    -- * Construction
+    , empty
+    , singleton
+
+    -- ** Insertion
+    , insert
+    , insertWith
+    , insertWithKey
+    , insertLookupWithKey
+
+    -- ** Delete\/Update
+    , delete
+    , adjust
+    , adjustWithKey
+    , update
+    , updateWithKey
+    , updateLookupWithKey
+    , alter
+
+    -- * Combine
+
+    -- ** Union
+    , union
+    , unionWith
+    , unionWithKey
+    , unions
+    , unionsWith
+
+    -- ** Difference
+    , difference
+    , differenceWith
+    , differenceWithKey
+
+    -- ** Intersection
+    , intersection
+    , intersectionWith
+    , intersectionWithKey
+
+    -- ** Universal combining function
+    , mergeWithKey
+
+    -- * Traversal
+    -- ** Map
+    , IM.map
+    , mapWithKey
+    , traverseWithKey
+    , mapAccum
+    , mapAccumWithKey
+    , mapAccumRWithKey
+    , mapKeys
+    , mapKeysWith
+    , mapKeysMonotonic
+
+    -- * Folds
+    , IM.foldr
+    , IM.foldl
+    , foldrWithKey
+    , foldlWithKey
+    -- ** Strict folds
+    , foldr'
+    , foldl'
+    , foldrWithKey'
+    , foldlWithKey'
+
+    -- * Conversion
+    , elems
+    , keys
+    , assocs
+    , keysSet
+    , fromSet
+
+    -- ** Lists
+    , toList
+    , fromList
+    , fromListWith
+    , fromListWithKey
+
+    -- ** Ordered lists
+    , toAscList
+    , toDescList
+    , fromAscList
+    , fromAscListWith
+    , fromAscListWithKey
+    , fromDistinctAscList
+
+    -- * Filter
+    , IM.filter
+    , filterWithKey
+    , partition
+    , partitionWithKey
+
+    , mapMaybe
+    , mapMaybeWithKey
+    , mapEither
+    , mapEitherWithKey
+
+    , split
+    , splitLookup
+
+    -- * Submap
+    , isSubmapOf, isSubmapOfBy
+    , isProperSubmapOf, isProperSubmapOfBy
+
+    -- * Min\/Max
+    , findMin
+    , findMax
+    , deleteMin
+    , deleteMax
+    , deleteFindMin
+    , deleteFindMax
+    , updateMin
+    , updateMax
+    , updateMinWithKey
+    , updateMaxWithKey
+    , minView
+    , maxView
+    , minViewWithKey
+    , maxViewWithKey
+
+    -- * Debugging
+    , showTree
+    , showTreeWith
+    ) where
 
 import Data.IntMap.Base as IM
 
diff --git a/Data/IntMap/Strict.hs b/Data/IntMap/Strict.hs
index 1b79154cccdc9577ac7027b5d9506964ccd10be8..e6b370810169e9b7e9a625037f7b025e68eed13d 100644
--- a/Data/IntMap/Strict.hs
+++ b/Data/IntMap/Strict.hs
@@ -56,154 +56,154 @@
 -- See the notes at the beginning of Data.IntMap.Base.
 
 module Data.IntMap.Strict (
-            -- * Strictness properties
-            -- $strictness
+    -- * Strictness properties
+    -- $strictness
 
-            -- * Map type
+    -- * Map type
 #if !defined(TESTING)
-              IntMap, Key          -- instance Eq,Show
+    IntMap, Key          -- instance Eq,Show
 #else
-              IntMap(..), Key          -- instance Eq,Show
+    IntMap(..), Key          -- instance Eq,Show
 #endif
 
-            -- * Operators
-            , (!), (\\)
-
-            -- * Query
-            , null
-            , size
-            , member
-            , notMember
-            , lookup
-            , findWithDefault
-            , lookupLT
-            , lookupGT
-            , lookupLE
-            , lookupGE
-
-            -- * Construction
-            , empty
-            , singleton
-
-            -- ** Insertion
-            , insert
-            , insertWith
-            , insertWithKey
-            , insertLookupWithKey
-
-            -- ** Delete\/Update
-            , delete
-            , adjust
-            , adjustWithKey
-            , update
-            , updateWithKey
-            , updateLookupWithKey
-            , alter
-
-            -- * Combine
-
-            -- ** Union
-            , union
-            , unionWith
-            , unionWithKey
-            , unions
-            , unionsWith
-
-            -- ** Difference
-            , difference
-            , differenceWith
-            , differenceWithKey
-
-            -- ** Intersection
-            , intersection
-            , intersectionWith
-            , intersectionWithKey
-
-            -- ** Universal combining function
-            , mergeWithKey
-
-            -- * Traversal
-            -- ** Map
-            , map
-            , mapWithKey
-            , traverseWithKey
-            , mapAccum
-            , mapAccumWithKey
-            , mapAccumRWithKey
-            , mapKeys
-            , mapKeysWith
-            , mapKeysMonotonic
-
-            -- * Folds
-            , foldr
-            , foldl
-            , foldrWithKey
-            , foldlWithKey
-            -- ** Strict folds
-            , foldr'
-            , foldl'
-            , foldrWithKey'
-            , foldlWithKey'
-
-            -- * Conversion
-            , elems
-            , keys
-            , assocs
-            , keysSet
-            , fromSet
-
-            -- ** Lists
-            , toList
-            , fromList
-            , fromListWith
-            , fromListWithKey
-
-            -- ** Ordered lists
-            , toAscList
-            , toDescList
-            , fromAscList
-            , fromAscListWith
-            , fromAscListWithKey
-            , fromDistinctAscList
-
-            -- * Filter
-            , filter
-            , filterWithKey
-            , partition
-            , partitionWithKey
-
-            , mapMaybe
-            , mapMaybeWithKey
-            , mapEither
-            , mapEitherWithKey
-
-            , split
-            , splitLookup
-
-            -- * Submap
-            , isSubmapOf, isSubmapOfBy
-            , isProperSubmapOf, isProperSubmapOfBy
-
-            -- * Min\/Max
-            , findMin
-            , findMax
-            , deleteMin
-            , deleteMax
-            , deleteFindMin
-            , deleteFindMax
-            , updateMin
-            , updateMax
-            , updateMinWithKey
-            , updateMaxWithKey
-            , minView
-            , maxView
-            , minViewWithKey
-            , maxViewWithKey
-
-            -- * Debugging
-            , showTree
-            , showTreeWith
-            ) where
+    -- * Operators
+    , (!), (\\)
+
+    -- * Query
+    , null
+    , size
+    , member
+    , notMember
+    , lookup
+    , findWithDefault
+    , lookupLT
+    , lookupGT
+    , lookupLE
+    , lookupGE
+
+    -- * Construction
+    , empty
+    , singleton
+
+    -- ** Insertion
+    , insert
+    , insertWith
+    , insertWithKey
+    , insertLookupWithKey
+
+    -- ** Delete\/Update
+    , delete
+    , adjust
+    , adjustWithKey
+    , update
+    , updateWithKey
+    , updateLookupWithKey
+    , alter
+
+    -- * Combine
+
+    -- ** Union
+    , union
+    , unionWith
+    , unionWithKey
+    , unions
+    , unionsWith
+
+    -- ** Difference
+    , difference
+    , differenceWith
+    , differenceWithKey
+
+    -- ** Intersection
+    , intersection
+    , intersectionWith
+    , intersectionWithKey
+
+    -- ** Universal combining function
+    , mergeWithKey
+
+    -- * Traversal
+    -- ** Map
+    , map
+    , mapWithKey
+    , traverseWithKey
+    , mapAccum
+    , mapAccumWithKey
+    , mapAccumRWithKey
+    , mapKeys
+    , mapKeysWith
+    , mapKeysMonotonic
+
+    -- * Folds
+    , foldr
+    , foldl
+    , foldrWithKey
+    , foldlWithKey
+    -- ** Strict folds
+    , foldr'
+    , foldl'
+    , foldrWithKey'
+    , foldlWithKey'
+
+    -- * Conversion
+    , elems
+    , keys
+    , assocs
+    , keysSet
+    , fromSet
+
+    -- ** Lists
+    , toList
+    , fromList
+    , fromListWith
+    , fromListWithKey
+
+    -- ** Ordered lists
+    , toAscList
+    , toDescList
+    , fromAscList
+    , fromAscListWith
+    , fromAscListWithKey
+    , fromDistinctAscList
+
+    -- * Filter
+    , filter
+    , filterWithKey
+    , partition
+    , partitionWithKey
+
+    , mapMaybe
+    , mapMaybeWithKey
+    , mapEither
+    , mapEitherWithKey
+
+    , split
+    , splitLookup
+
+    -- * Submap
+    , isSubmapOf, isSubmapOfBy
+    , isProperSubmapOf, isProperSubmapOfBy
+
+    -- * Min\/Max
+    , findMin
+    , findMax
+    , deleteMin
+    , deleteMax
+    , deleteFindMin
+    , deleteFindMax
+    , updateMin
+    , updateMax
+    , updateMinWithKey
+    , updateMaxWithKey
+    , minView
+    , maxView
+    , minViewWithKey
+    , maxViewWithKey
+
+    -- * Debugging
+    , showTree
+    , showTreeWith
+    ) where
 
 import Prelude hiding (lookup,map,filter,foldr,foldl,null)
 
diff --git a/Data/Map/Base.hs b/Data/Map/Base.hs
index ca581d69b3c03a253bcf5a7c04af369858f199a4..3e240e87d88dc55280999c2a030af787d4f30e50 100644
--- a/Data/Map/Base.hs
+++ b/Data/Map/Base.hs
@@ -93,184 +93,185 @@
 -- improves the benchmark by up to 10% on x86.
 
 module Data.Map.Base (
-            -- * Map type
-              Map(..)          -- instance Eq,Show,Read
-
-            -- * Operators
-            , (!), (\\)
-
-            -- * Query
-            , null
-            , size
-            , member
-            , notMember
-            , lookup
-            , findWithDefault
-            , lookupLT
-            , lookupGT
-            , lookupLE
-            , lookupGE
-
-            -- * Construction
-            , empty
-            , singleton
-
-            -- ** Insertion
-            , insert
-            , insertWith
-            , insertWithKey
-            , insertLookupWithKey
-
-            -- ** Delete\/Update
-            , delete
-            , adjust
-            , adjustWithKey
-            , update
-            , updateWithKey
-            , updateLookupWithKey
-            , alter
-
-            -- * Combine
-
-            -- ** Union
-            , union
-            , unionWith
-            , unionWithKey
-            , unions
-            , unionsWith
-
-            -- ** Difference
-            , difference
-            , differenceWith
-            , differenceWithKey
-
-            -- ** Intersection
-            , intersection
-            , intersectionWith
-            , intersectionWithKey
-
-            -- ** Universal combining function
-            , mergeWithKey
-
-            -- * Traversal
-            -- ** Map
-            , map
-            , mapWithKey
-            , traverseWithKey
-            , mapAccum
-            , mapAccumWithKey
-            , mapAccumRWithKey
-            , mapKeys
-            , mapKeysWith
-            , mapKeysMonotonic
-
-            -- * Folds
-            , foldr
-            , foldl
-            , foldrWithKey
-            , foldlWithKey
-            -- ** Strict folds
-            , foldr'
-            , foldl'
-            , foldrWithKey'
-            , foldlWithKey'
-
-            -- * Conversion
-            , elems
-            , keys
-            , assocs
-            , keysSet
-            , fromSet
-
-            -- ** Lists
-            , toList
-            , fromList
-            , fromListWith
-            , fromListWithKey
-
-            -- ** Ordered lists
-            , toAscList
-            , toDescList
-            , fromAscList
-            , fromAscListWith
-            , fromAscListWithKey
-            , fromDistinctAscList
-
-            -- * Filter
-            , filter
-            , filterWithKey
-            , partition
-            , partitionWithKey
-
-            , mapMaybe
-            , mapMaybeWithKey
-            , mapEither
-            , mapEitherWithKey
-
-            , split
-            , splitLookup
-
-            -- * Submap
-            , isSubmapOf, isSubmapOfBy
-            , isProperSubmapOf, isProperSubmapOfBy
-
-            -- * Indexed
-            , lookupIndex
-            , findIndex
-            , elemAt
-            , updateAt
-            , deleteAt
-
-            -- * Min\/Max
-            , findMin
-            , findMax
-            , deleteMin
-            , deleteMax
-            , deleteFindMin
-            , deleteFindMax
-            , updateMin
-            , updateMax
-            , updateMinWithKey
-            , updateMaxWithKey
-            , minView
-            , maxView
-            , minViewWithKey
-            , maxViewWithKey
-
-            -- * Debugging
-            , showTree
-            , showTreeWith
-            , valid
-
-            -- Used by the strict version
-            , bin
-            , balance
-            , balanced
-            , balanceL
-            , balanceR
-            , delta
-            , join
-            , insertMax
-            , merge
-            , glue
-            , trim
-            , trimLookupLo
-            , foldlStrict
-            , MaybeS(..)
-            , filterGt
-            , filterLt
-            ) where
-
-import Prelude hiding (lookup,map,filter,foldr,foldl,null)
-import qualified Data.Set.Base as Set
-import Data.StrictPair
+    -- * Map type
+      Map(..)          -- instance Eq,Show,Read
+
+    -- * Operators
+    , (!), (\\)
+
+    -- * Query
+    , null
+    , size
+    , member
+    , notMember
+    , lookup
+    , findWithDefault
+    , lookupLT
+    , lookupGT
+    , lookupLE
+    , lookupGE
+
+    -- * Construction
+    , empty
+    , singleton
+
+    -- ** Insertion
+    , insert
+    , insertWith
+    , insertWithKey
+    , insertLookupWithKey
+
+    -- ** Delete\/Update
+    , delete
+    , adjust
+    , adjustWithKey
+    , update
+    , updateWithKey
+    , updateLookupWithKey
+    , alter
+
+    -- * Combine
+
+    -- ** Union
+    , union
+    , unionWith
+    , unionWithKey
+    , unions
+    , unionsWith
+
+    -- ** Difference
+    , difference
+    , differenceWith
+    , differenceWithKey
+
+    -- ** Intersection
+    , intersection
+    , intersectionWith
+    , intersectionWithKey
+
+    -- ** Universal combining function
+    , mergeWithKey
+
+    -- * Traversal
+    -- ** Map
+    , map
+    , mapWithKey
+    , traverseWithKey
+    , mapAccum
+    , mapAccumWithKey
+    , mapAccumRWithKey
+    , mapKeys
+    , mapKeysWith
+    , mapKeysMonotonic
+
+    -- * Folds
+    , foldr
+    , foldl
+    , foldrWithKey
+    , foldlWithKey
+    -- ** Strict folds
+    , foldr'
+    , foldl'
+    , foldrWithKey'
+    , foldlWithKey'
+
+    -- * Conversion
+    , elems
+    , keys
+    , assocs
+    , keysSet
+    , fromSet
+
+    -- ** Lists
+    , toList
+    , fromList
+    , fromListWith
+    , fromListWithKey
+
+    -- ** Ordered lists
+    , toAscList
+    , toDescList
+    , fromAscList
+    , fromAscListWith
+    , fromAscListWithKey
+    , fromDistinctAscList
+
+    -- * Filter
+    , filter
+    , filterWithKey
+    , partition
+    , partitionWithKey
+
+    , mapMaybe
+    , mapMaybeWithKey
+    , mapEither
+    , mapEitherWithKey
+
+    , split
+    , splitLookup
+
+    -- * Submap
+    , isSubmapOf, isSubmapOfBy
+    , isProperSubmapOf, isProperSubmapOfBy
+
+    -- * Indexed
+    , lookupIndex
+    , findIndex
+    , elemAt
+    , updateAt
+    , deleteAt
+
+    -- * Min\/Max
+    , findMin
+    , findMax
+    , deleteMin
+    , deleteMax
+    , deleteFindMin
+    , deleteFindMax
+    , updateMin
+    , updateMax
+    , updateMinWithKey
+    , updateMaxWithKey
+    , minView
+    , maxView
+    , minViewWithKey
+    , maxViewWithKey
+
+    -- * Debugging
+    , showTree
+    , showTreeWith
+    , valid
+
+    -- Used by the strict version
+    , bin
+    , balance
+    , balanced
+    , balanceL
+    , balanceR
+    , delta
+    , join
+    , insertMax
+    , merge
+    , glue
+    , trim
+    , trimLookupLo
+    , foldlStrict
+    , MaybeS(..)
+    , filterGt
+    , filterLt
+    ) where
+
+import Control.Applicative (Applicative(..), (<$>))
+import Control.DeepSeq (NFData(rnf))
 import Data.Bits (shiftL, shiftR)
+import qualified Data.Foldable as Foldable
 import Data.Monoid (Monoid(..))
-import Control.Applicative (Applicative(..), (<$>))
+import Data.StrictPair
 import Data.Traversable (Traversable(traverse))
-import qualified Data.Foldable as Foldable
 import Data.Typeable
-import Control.DeepSeq (NFData(rnf))
+import Prelude hiding (lookup, map, filter, foldr, foldl, null)
+
+import qualified Data.Set.Base as Set
 
 #if __GLASGOW_HASKELL__
 import GHC.Exts ( build )
diff --git a/Data/Map/Lazy.hs b/Data/Map/Lazy.hs
index df09cd61244166e11ea4e33dafd7f288f0d00eef..e637376c1a4eff51ca9ae85ebde86c092d7c42f1 100644
--- a/Data/Map/Lazy.hs
+++ b/Data/Map/Lazy.hs
@@ -46,171 +46,171 @@
 -----------------------------------------------------------------------------
 
 module Data.Map.Lazy (
-            -- * Strictness properties
-            -- $strictness
+    -- * Strictness properties
+    -- $strictness
 
-            -- * Map type
+    -- * Map type
 #if !defined(TESTING)
-              Map              -- instance Eq,Show,Read
+    Map              -- instance Eq,Show,Read
 #else
-              Map(..)          -- instance Eq,Show,Read
+    Map(..)          -- instance Eq,Show,Read
 #endif
 
-            -- * Operators
-            , (!), (\\)
-
-            -- * Query
-            , M.null
-            , size
-            , member
-            , notMember
-            , M.lookup
-            , findWithDefault
-            , lookupLT
-            , lookupGT
-            , lookupLE
-            , lookupGE
-
-            -- * Construction
-            , empty
-            , singleton
-
-            -- ** Insertion
-            , insert
-            , insertWith
-            , insertWithKey
-            , insertLookupWithKey
-
-            -- ** Delete\/Update
-            , delete
-            , adjust
-            , adjustWithKey
-            , update
-            , updateWithKey
-            , updateLookupWithKey
-            , alter
-
-            -- * Combine
-
-            -- ** Union
-            , union
-            , unionWith
-            , unionWithKey
-            , unions
-            , unionsWith
-
-            -- ** Difference
-            , difference
-            , differenceWith
-            , differenceWithKey
-
-            -- ** Intersection
-            , intersection
-            , intersectionWith
-            , intersectionWithKey
-
-            -- ** Universal combining function
-            , mergeWithKey
-
-            -- * Traversal
-            -- ** Map
-            , M.map
-            , mapWithKey
-            , traverseWithKey
-            , mapAccum
-            , mapAccumWithKey
-            , mapAccumRWithKey
-            , mapKeys
-            , mapKeysWith
-            , mapKeysMonotonic
-
-            -- * Folds
-            , M.foldr
-            , M.foldl
-            , foldrWithKey
-            , foldlWithKey
-            -- ** Strict folds
-            , foldr'
-            , foldl'
-            , foldrWithKey'
-            , foldlWithKey'
-
-            -- * Conversion
-            , elems
-            , keys
-            , assocs
-            , keysSet
-            , fromSet
-
-            -- ** Lists
-            , toList
-            , fromList
-            , fromListWith
-            , fromListWithKey
-
-            -- ** Ordered lists
-            , toAscList
-            , toDescList
-            , fromAscList
-            , fromAscListWith
-            , fromAscListWithKey
-            , fromDistinctAscList
-
-            -- * Filter
-            , M.filter
-            , filterWithKey
-            , partition
-            , partitionWithKey
-
-            , mapMaybe
-            , mapMaybeWithKey
-            , mapEither
-            , mapEitherWithKey
-
-            , split
-            , splitLookup
-
-            -- * Submap
-            , isSubmapOf, isSubmapOfBy
-            , isProperSubmapOf, isProperSubmapOfBy
-
-            -- * Indexed
-            , lookupIndex
-            , findIndex
-            , elemAt
-            , updateAt
-            , deleteAt
-
-            -- * Min\/Max
-            , findMin
-            , findMax
-            , deleteMin
-            , deleteMax
-            , deleteFindMin
-            , deleteFindMax
-            , updateMin
-            , updateMax
-            , updateMinWithKey
-            , updateMaxWithKey
-            , minView
-            , maxView
-            , minViewWithKey
-            , maxViewWithKey
-
-            -- * Debugging
-            , showTree
-            , showTreeWith
-            , valid
+    -- * Operators
+    , (!), (\\)
+
+    -- * Query
+    , M.null
+    , size
+    , member
+    , notMember
+    , M.lookup
+    , findWithDefault
+    , lookupLT
+    , lookupGT
+    , lookupLE
+    , lookupGE
+
+    -- * Construction
+    , empty
+    , singleton
+
+    -- ** Insertion
+    , insert
+    , insertWith
+    , insertWithKey
+    , insertLookupWithKey
+
+    -- ** Delete\/Update
+    , delete
+    , adjust
+    , adjustWithKey
+    , update
+    , updateWithKey
+    , updateLookupWithKey
+    , alter
+
+    -- * Combine
+
+    -- ** Union
+    , union
+    , unionWith
+    , unionWithKey
+    , unions
+    , unionsWith
+
+    -- ** Difference
+    , difference
+    , differenceWith
+    , differenceWithKey
+
+    -- ** Intersection
+    , intersection
+    , intersectionWith
+    , intersectionWithKey
+
+    -- ** Universal combining function
+    , mergeWithKey
+
+    -- * Traversal
+    -- ** Map
+    , M.map
+    , mapWithKey
+    , traverseWithKey
+    , mapAccum
+    , mapAccumWithKey
+    , mapAccumRWithKey
+    , mapKeys
+    , mapKeysWith
+    , mapKeysMonotonic
+
+    -- * Folds
+    , M.foldr
+    , M.foldl
+    , foldrWithKey
+    , foldlWithKey
+    -- ** Strict folds
+    , foldr'
+    , foldl'
+    , foldrWithKey'
+    , foldlWithKey'
+
+    -- * Conversion
+    , elems
+    , keys
+    , assocs
+    , keysSet
+    , fromSet
+
+    -- ** Lists
+    , toList
+    , fromList
+    , fromListWith
+    , fromListWithKey
+
+    -- ** Ordered lists
+    , toAscList
+    , toDescList
+    , fromAscList
+    , fromAscListWith
+    , fromAscListWithKey
+    , fromDistinctAscList
+
+    -- * Filter
+    , M.filter
+    , filterWithKey
+    , partition
+    , partitionWithKey
+
+    , mapMaybe
+    , mapMaybeWithKey
+    , mapEither
+    , mapEitherWithKey
+
+    , split
+    , splitLookup
+
+    -- * Submap
+    , isSubmapOf, isSubmapOfBy
+    , isProperSubmapOf, isProperSubmapOfBy
+
+    -- * Indexed
+    , lookupIndex
+    , findIndex
+    , elemAt
+    , updateAt
+    , deleteAt
+
+    -- * Min\/Max
+    , findMin
+    , findMax
+    , deleteMin
+    , deleteMax
+    , deleteFindMin
+    , deleteFindMax
+    , updateMin
+    , updateMax
+    , updateMinWithKey
+    , updateMaxWithKey
+    , minView
+    , maxView
+    , minViewWithKey
+    , maxViewWithKey
+
+    -- * Debugging
+    , showTree
+    , showTreeWith
+    , valid
 
 #if defined(TESTING)
-            -- * Internals
-            , bin
-            , balanced
-            , join
-            , merge
+    -- * Internals
+    , bin
+    , balanced
+    , join
+    , merge
 #endif
 
-            ) where
+    ) where
 
 import Data.Map.Base as M