Skip to content

Commit

Permalink
Rename and expose internal modules (#283)
Browse files Browse the repository at this point in the history
This also removes some "Stability" annotations from internal modules.

Context: #211.
  • Loading branch information
sjakobi authored Jul 20, 2020
1 parent afcbc77 commit 6f1a92f
Show file tree
Hide file tree
Showing 12 changed files with 128 additions and 48 deletions.
24 changes: 18 additions & 6 deletions Data/HashMap/Base.hs → Data/HashMap/Internal.hs
Original file line number Diff line number Diff line change
Expand Up @@ -11,7 +11,19 @@
#endif
{-# OPTIONS_GHC -fno-full-laziness -funbox-strict-fields #-}

module Data.HashMap.Base
-- | = WARNING
--
-- This module is considered __internal__.
--
-- The Package Versioning Policy __does not apply__.
--
-- The contents of this module may change __in any way whatsoever__
-- and __without any warning__ between minor versions of this package.
--
-- Authors importing this module are expected to track development
-- closely.

module Data.HashMap.Internal
(
HashMap(..)
, Leaf(..)
Expand Down Expand Up @@ -140,11 +152,11 @@ import GHC.Exts ((==#), build, reallyUnsafePtrEquality#)
import Prelude hiding (filter, foldl, foldr, lookup, map, null, pred)
import Text.Read hiding (step)

import qualified Data.HashMap.Array as A
import qualified Data.HashMap.Internal.Array as A
import qualified Data.Hashable as H
import Data.Hashable (Hashable)
import Data.HashMap.Unsafe (runST)
import Data.HashMap.List (isPermutationBy, unorderedCompare)
import Data.HashMap.Internal.Unsafe (runST)
import Data.HashMap.Internal.List (isPermutationBy, unorderedCompare)
import Data.Typeable (Typeable)

import GHC.Exts (isTrue#)
Expand Down Expand Up @@ -283,7 +295,7 @@ fromListConstr :: Constr
fromListConstr = mkConstr hashMapDataType "fromList" [] Prefix

hashMapDataType :: DataType
hashMapDataType = mkDataType "Data.HashMap.Base.HashMap" [fromListConstr]
hashMapDataType = mkDataType "Data.HashMap.Internal.HashMap" [fromListConstr]

type Hash = Word
type Bitmap = Word
Expand Down Expand Up @@ -729,7 +741,7 @@ lookupDefault def k t = findWithDefault def k t
#endif
(!) m k = case lookup k m of
Just v -> v
Nothing -> error "Data.HashMap.Base.(!): key not found"
Nothing -> error "Data.HashMap.Internal.(!): key not found"
{-# INLINABLE (!) #-}

infixl 9 !
Expand Down
26 changes: 20 additions & 6 deletions Data/HashMap/Array.hs → Data/HashMap/Internal/Array.hs
Original file line number Diff line number Diff line change
@@ -1,10 +1,24 @@
{-# LANGUAGE BangPatterns, CPP, MagicHash, Rank2Types, UnboxedTuples, ScopedTypeVariables #-}
{-# OPTIONS_GHC -fno-full-laziness -funbox-strict-fields #-}

-- | Zero based arrays.
-- | = WARNING
--
-- This module is considered __internal__.
--
-- The Package Versioning Policy __does not apply__.
--
-- The contents of this module may change __in any way whatsoever__
-- and __without any warning__ between minor versions of this package.
--
-- Authors importing this module are expected to track development
-- closely.
--
-- = Description
--
-- Zero based arrays.
--
-- Note that no bounds checking are performed.
module Data.HashMap.Array
module Data.HashMap.Internal.Array
( Array
, MArray

Expand Down Expand Up @@ -88,7 +102,7 @@ import Data.Monoid (Monoid (..))
import qualified Prelude
#endif

import Data.HashMap.Unsafe (runST)
import Data.HashMap.Internal.Unsafe (runST)
import Control.Monad ((>=>))


Expand Down Expand Up @@ -163,9 +177,9 @@ copyMutableArray# = copySmallMutableArray#
-- This fugly hack is brought by GHC's apparent reluctance to deal
-- with MagicHash and UnboxedTuples when inferring types. Eek!
# define CHECK_BOUNDS(_func_,_len_,_k_) \
if (_k_) < 0 || (_k_) >= (_len_) then error ("Data.HashMap.Array." ++ (_func_) ++ ": bounds error, offset " ++ show (_k_) ++ ", length " ++ show (_len_)) else
if (_k_) < 0 || (_k_) >= (_len_) then error ("Data.HashMap.Internal.Array." ++ (_func_) ++ ": bounds error, offset " ++ show (_k_) ++ ", length " ++ show (_len_)) else
# define CHECK_OP(_func_,_op_,_lhs_,_rhs_) \
if not ((_lhs_) _op_ (_rhs_)) then error ("Data.HashMap.Array." ++ (_func_) ++ ": Check failed: _lhs_ _op_ _rhs_ (" ++ show (_lhs_) ++ " vs. " ++ show (_rhs_) ++ ")") else
if not ((_lhs_) _op_ (_rhs_)) then error ("Data.HashMap.Internal.Array." ++ (_func_) ++ ": Check failed: _lhs_ _op_ _rhs_ (" ++ show (_lhs_) ++ " vs. " ++ show (_rhs_) ++ ")") else
# define CHECK_GT(_func_,_lhs_,_rhs_) CHECK_OP(_func_,>,_lhs_,_rhs_)
# define CHECK_LE(_func_,_lhs_,_rhs_) CHECK_OP(_func_,<=,_lhs_,_rhs_)
# define CHECK_EQ(_func_,_lhs_,_rhs_) CHECK_OP(_func_,==,_lhs_,_rhs_)
Expand Down Expand Up @@ -448,7 +462,7 @@ foldMap f = \ary0 -> case length ary0 of
{-# INLINE foldMap #-}

undefinedElem :: a
undefinedElem = error "Data.HashMap.Array: Undefined element"
undefinedElem = error "Data.HashMap.Internal.Array: Undefined element"
{-# NOINLINE undefinedElem #-}

thaw :: Array e -> Int -> Int -> ST s (MArray s e)
Expand Down
19 changes: 17 additions & 2 deletions Data/HashMap/List.hs → Data/HashMap/Internal/List.hs
Original file line number Diff line number Diff line change
@@ -1,9 +1,24 @@
{-# LANGUAGE ScopedTypeVariables #-}
{-# OPTIONS_GHC -fno-full-laziness -funbox-strict-fields #-}
-- | Extra list functions

-- | = WARNING
--
-- This module is considered __internal__.
--
-- The Package Versioning Policy __does not apply__.
--
-- The contents of this module may change __in any way whatsoever__
-- and __without any warning__ between minor versions of this package.
--
-- Authors importing this module are expected to track development
-- closely.
--
-- = Description
--
-- Extra list functions
--
-- In separate module to aid testing.
module Data.HashMap.List
module Data.HashMap.Internal.List
( isPermutationBy
, deleteBy
, unorderedCompare
Expand Down
29 changes: 21 additions & 8 deletions Data/HashMap/Strict/Base.hs → Data/HashMap/Internal/Strict.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,9 +8,22 @@
-- Copyright : 2010-2012 Johan Tibell
-- License : BSD-style
-- Maintainer : [email protected]
-- Stability : provisional
-- Portability : portable
--
-- = WARNING
--
-- This module is considered __internal__.
--
-- The Package Versioning Policy __does not apply__.
--
-- The contents of this module may change __in any way whatsoever__
-- and __without any warning__ between minor versions of this package.
--
-- Authors importing this module are expected to track development
-- closely.
--
-- = Description
--
-- A map from /hashable/ keys to values. A map cannot contain
-- duplicate keys; each key can map to at most one value. A 'HashMap'
-- makes no guarantees as to the order of its elements.
Expand All @@ -23,7 +36,7 @@
-- Many operations have a average-case complexity of /O(log n)/. The
-- implementation uses a large base (i.e. 16) so in practice these
-- operations are constant time.
module Data.HashMap.Strict.Base
module Data.HashMap.Internal.Strict
(
-- * Strictness properties
-- $strictness
Expand Down Expand Up @@ -107,15 +120,15 @@ import qualified Data.List as L
import Data.Hashable (Hashable)
import Prelude hiding (map, lookup)

import qualified Data.HashMap.Array as A
import qualified Data.HashMap.Base as HM
import Data.HashMap.Base hiding (
import qualified Data.HashMap.Internal.Array as A
import qualified Data.HashMap.Internal as HM
import Data.HashMap.Internal hiding (
alter, alterF, adjust, fromList, fromListWith, fromListWithKey,
insert, insertWith,
differenceWith, intersectionWith, intersectionWithKey, map, mapWithKey,
mapMaybe, mapMaybeWithKey, singleton, update, unionWith, unionWithKey,
traverseWithKey)
import Data.HashMap.Unsafe (runST)
import Data.HashMap.Internal.Unsafe (runST)
#if MIN_VERSION_base(4,8,0)
import Data.Functor.Identity
#endif
Expand Down Expand Up @@ -310,7 +323,7 @@ alterF f = \ !k !m ->
{-# INLINABLE [0] alterF #-}

#if MIN_VERSION_base(4,8,0)
-- See notes in Data.HashMap.Base
-- See notes in Data.HashMap.Internal
test_bottom :: a
test_bottom = error "Data.HashMap.alterF internal error: hit test_bottom"

Expand All @@ -322,7 +335,7 @@ impossibleAdjust = error "Data.HashMap.alterF internal error: impossible adjust"

{-# RULES

-- See detailed notes on alterF rules in Data.HashMap.Base.
-- See detailed notes on alterF rules in Data.HashMap.Internal.

"alterFWeird" forall f. alterF f =
alterFWeird (f Nothing) (f (Just test_bottom)) f
Expand Down
18 changes: 16 additions & 2 deletions Data/HashMap/Unsafe.hs → Data/HashMap/Internal/Unsafe.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,15 +4,29 @@
{-# LANGUAGE MagicHash, Rank2Types, UnboxedTuples #-}
#endif

-- | This module exports a workaround for this bug:
-- | = WARNING
--
-- This module is considered __internal__.
--
-- The Package Versioning Policy __does not apply__.
--
-- The contents of this module may change __in any way whatsoever__
-- and __without any warning__ between minor versions of this package.
--
-- Authors importing this module are expected to track development
-- closely.
--
-- = Description
--
-- This module exports a workaround for this bug:
--
-- http://hackage.haskell.org/trac/ghc/ticket/5916
--
-- Please read the comments in ghc/libraries/base/GHC/ST.lhs to
-- understand what's going on here.
--
-- Code that uses this module should be compiled with -fno-full-laziness
module Data.HashMap.Unsafe
module Data.HashMap.Internal.Unsafe
( runST
) where

Expand Down
4 changes: 2 additions & 2 deletions Data/HashMap/Lazy.hs
Original file line number Diff line number Diff line change
Expand Up @@ -100,8 +100,8 @@ module Data.HashMap.Lazy
, HS.keysSet
) where

import Data.HashMap.Base as HM
import qualified Data.HashSet.Base as HS
import Data.HashMap.Internal as HM
import qualified Data.HashSet.Internal as HS
import Prelude ()

-- $strictness
Expand Down
4 changes: 2 additions & 2 deletions Data/HashMap/Strict.hs
Original file line number Diff line number Diff line change
Expand Up @@ -99,8 +99,8 @@ module Data.HashMap.Strict
, HS.keysSet
) where

import Data.HashMap.Strict.Base as HM
import qualified Data.HashSet.Base as HS
import Data.HashMap.Internal.Strict as HM
import qualified Data.HashSet.Internal as HS
import Prelude ()

-- $strictness
Expand Down
2 changes: 1 addition & 1 deletion Data/HashSet.hs
Original file line number Diff line number Diff line change
Expand Up @@ -137,5 +137,5 @@ module Data.HashSet
, fromMap
) where

import Data.HashSet.Base
import Data.HashSet.Internal
import Prelude ()
25 changes: 19 additions & 6 deletions Data/HashSet/Base.hs → Data/HashSet/Internal.hs
Original file line number Diff line number Diff line change
Expand Up @@ -9,13 +9,26 @@

------------------------------------------------------------------------
-- |
-- Module : Data.HashSet.Base
-- Module : Data.HashSet.Internal
-- Copyright : 2011 Bryan O'Sullivan
-- License : BSD-style
-- Maintainer : [email protected]
-- Stability : provisional
-- Portability : portable
--
-- = WARNING
--
-- This module is considered __internal__.
--
-- The Package Versioning Policy __does not apply__.
--
-- The contents of this module may change __in any way whatsoever__
-- and __without any warning__ between minor versions of this package.
--
-- Authors importing this module are expected to track development
-- closely.
--
-- = Description
--
-- A set of /hashable/ values. A set cannot contain duplicate items.
-- A 'HashSet' makes no guarantees as to the order of its elements.
--
Expand All @@ -28,7 +41,7 @@
-- implementation uses a large base (i.e. 16) so in practice these
-- operations are constant time.

module Data.HashSet.Base
module Data.HashSet.Internal
(
HashSet

Expand Down Expand Up @@ -79,7 +92,7 @@ module Data.HashSet.Base

import Control.DeepSeq (NFData(..))
import Data.Data hiding (Typeable)
import Data.HashMap.Base
import Data.HashMap.Internal
( HashMap, foldMapWithKey, foldlWithKey, foldrWithKey
, equalKeys, equalKeys1)
import Data.Hashable (Hashable(hashWithSalt))
Expand All @@ -91,7 +104,7 @@ import Data.Monoid (Monoid(..))
import GHC.Exts (build)
import Prelude hiding (filter, foldr, foldl, map, null)
import qualified Data.Foldable as Foldable
import qualified Data.HashMap.Base as H
import qualified Data.HashMap.Internal as H
import qualified Data.List as List
import Data.Typeable (Typeable)
import Text.Read
Expand Down Expand Up @@ -257,7 +270,7 @@ fromListConstr :: Constr
fromListConstr = mkConstr hashSetDataType "fromList" [] Prefix

hashSetDataType :: DataType
hashSetDataType = mkDataType "Data.HashSet.Base.HashSet" [fromListConstr]
hashSetDataType = mkDataType "Data.HashSet.Internal.HashSet" [fromListConstr]

-- | /O(1)/ Construct an empty set.
--
Expand Down
4 changes: 2 additions & 2 deletions tests/List.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
module Main (main) where

import Data.HashMap.List
import Data.HashMap.Internal.List
import Data.List (nub, sort, sortBy)
import Data.Ord (comparing)

Expand All @@ -9,7 +9,7 @@ import Test.Framework.Providers.QuickCheck2 (testProperty)
import Test.QuickCheck ((==>), (===), property, Property)

tests :: Test
tests = testGroup "Data.HashMap.List"
tests = testGroup "Data.HashMap.Internal.List"
[ testProperty "isPermutationBy" pIsPermutation
, testProperty "isPermutationBy of different length" pIsPermutationDiffLength
, testProperty "pUnorderedCompare" pUnorderedCompare
Expand Down
15 changes: 7 additions & 8 deletions unordered-containers.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -37,16 +37,15 @@ flag debug

library
exposed-modules:
Data.HashMap.Internal
Data.HashMap.Internal.Array
Data.HashMap.Internal.List
Data.HashMap.Internal.Strict
Data.HashMap.Internal.Unsafe
Data.HashMap.Lazy
Data.HashMap.Strict
Data.HashSet
other-modules:
Data.HashMap.Array
Data.HashMap.Base
Data.HashMap.Strict.Base
Data.HashMap.List
Data.HashMap.Unsafe
Data.HashSet.Base
Data.HashSet.Internal

build-depends:
base >= 4.7 && < 5,
Expand Down Expand Up @@ -130,7 +129,7 @@ test-suite list-tests
hs-source-dirs: tests .
main-is: List.hs
other-modules:
Data.HashMap.List
Data.HashMap.Internal.List
type: exitcode-stdio-1.0

build-depends:
Expand Down
6 changes: 3 additions & 3 deletions utils/Stats.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,9 +3,9 @@
{-# OPTIONS_GHC -funbox-strict-fields #-}
module Stats where

import qualified Data.HashMap.Array as A
import Data.HashMap.Base (HashMap(..))
import qualified Data.HashMap.Base as HM
import qualified Data.HashMap.Internal.Array as A
import Data.HashMap.Internal (HashMap(..))
import qualified Data.HashMap.Internal as HM
import Data.Semigroup

data Histogram = H {
Expand Down

0 comments on commit 6f1a92f

Please sign in to comment.