Script 'mail_helper' called by obssrc
Hello community,
here is the log from the commit of package ghc-ordered-containers for openSUSE:Factory checked in at 2024-06-03 17:45:05
++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
Comparing /work/SRC/openSUSE:Factory/ghc-ordered-containers (Old)
and /work/SRC/openSUSE:Factory/.ghc-ordered-containers.new.24587 (New)
++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
Package is "ghc-ordered-containers"
Mon Jun 3 17:45:05 2024 rev:2 rq:1178298 version:0.2.4
Changes:
--------
--- /work/SRC/openSUSE:Factory/ghc-ordered-containers/ghc-ordered-containers.changes 2023-06-22 23:25:25.721648067 +0200
+++ /work/SRC/openSUSE:Factory/.ghc-ordered-containers.new.24587/ghc-ordered-containers.changes 2024-06-03 17:45:52.236324679 +0200
@@ -1,0 +2,14 @@
+Sun May 19 21:31:49 UTC 2024 - Peter Simons <psimons(a)suse.com>
+
+- Update ordered-containers to version 0.2.4.
+ ## 0.2.4 -- 2024-05-18
+
+ * Misc. housekeeping -- version bumps, documentation fixes, etc. (thank you Ryan Scott and Andrew Kent!)
+ * Add `IsList` and `Hashable` instances (thank you Alexis King!)
+ * the strict variant of `alter`
+
+ ## 0.2.3 -- 2022-11-01
+
+ * `alter` (thank you Raoul Hidalgo Charman!)
+
+-------------------------------------------------------------------
Old:
----
ordered-containers-0.2.3.tar.gz
New:
----
ordered-containers-0.2.4.tar.gz
++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
Other differences:
------------------
++++++ ghc-ordered-containers.spec ++++++
--- /var/tmp/diff_new_pack.YpJsBI/_old 2024-06-03 17:45:52.716341835 +0200
+++ /var/tmp/diff_new_pack.YpJsBI/_new 2024-06-03 17:45:52.716341835 +0200
@@ -1,7 +1,7 @@
#
# spec file for package ghc-ordered-containers
#
-# Copyright (c) 2022 SUSE LLC
+# Copyright (c) 2024 SUSE LLC
#
# All modifications and additions to the file contributed by third parties
# remain the property of their copyright owners, unless otherwise agreed
@@ -19,7 +19,7 @@
%global pkg_name ordered-containers
%global pkgver %{pkg_name}-%{version}
Name: ghc-%{pkg_name}
-Version: 0.2.3
+Version: 0.2.4
Release: 0
Summary: Set- and Map-like types that remember the order elements were inserted
License: BSD-3-Clause
@@ -30,6 +30,8 @@
BuildRequires: ghc-base-prof
BuildRequires: ghc-containers-devel
BuildRequires: ghc-containers-prof
+BuildRequires: ghc-hashable-devel
+BuildRequires: ghc-hashable-prof
BuildRequires: ghc-rpm-macros
ExcludeArch: %{ix86}
++++++ ordered-containers-0.2.3.tar.gz -> ordered-containers-0.2.4.tar.gz ++++++
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/ordered-containers-0.2.3/ChangeLog.md new/ordered-containers-0.2.4/ChangeLog.md
--- old/ordered-containers-0.2.3/ChangeLog.md 2001-09-09 03:46:40.000000000 +0200
+++ new/ordered-containers-0.2.4/ChangeLog.md 2001-09-09 03:46:40.000000000 +0200
@@ -1,5 +1,15 @@
# Revision history for ordered-containers
+## 0.2.4 -- 2024-05-18
+
+* Misc. housekeeping -- version bumps, documentation fixes, etc. (thank you Ryan Scott and Andrew Kent!)
+* Add `IsList` and `Hashable` instances (thank you Alexis King!)
+* the strict variant of `alter`
+
+## 0.2.3 -- 2022-11-01
+
+* `alter` (thank you Raoul Hidalgo Charman!)
+
## 0.2.2 -- 2019-07-05
* Add `toMap` and `toSet`, which support efficient conversions from
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/ordered-containers-0.2.3/Data/Map/Ordered/Internal.hs new/ordered-containers-0.2.4/Data/Map/Ordered/Internal.hs
--- old/ordered-containers-0.2.3/Data/Map/Ordered/Internal.hs 2001-09-09 03:46:40.000000000 +0200
+++ new/ordered-containers-0.2.4/Data/Map/Ordered/Internal.hs 2001-09-09 03:46:40.000000000 +0200
@@ -2,7 +2,7 @@
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE FlexibleInstances #-}
-{-# LANGUAGE TupleSections #-}
+{-# LANGUAGE TypeFamilies #-}
module Data.Map.Ordered.Internal where
@@ -10,6 +10,7 @@
import Data.Data
import Data.Foldable (Foldable, foldl', foldMap)
import Data.Function (on)
+import Data.Hashable (Hashable(..))
import Data.Map (Map)
import Data.Map.Util
import Data.Monoid (Monoid(..))
@@ -22,19 +23,27 @@
#endif
import Prelude hiding (filter, lookup, null)
import qualified Data.Map as M
+import qualified GHC.Exts as Exts
data OMap k v = OMap !(Map k (Tag, v)) !(Map Tag (k, v))
- deriving (Functor, Typeable)
+ deriving
+ ( Functor -- ^ @since 0.2
+ , Typeable -- ^ @since 0.2
+ )
-- | Values are produced in insertion order, not key order.
instance Foldable (OMap k) where foldMap f (OMap _ kvs) = foldMap (f . snd) kvs
instance ( Eq k, Eq v) => Eq (OMap k v) where (==) = (==) `on` assocs
instance ( Ord k, Ord v) => Ord (OMap k v) where compare = compare `on` assocs
instance ( Show k, Show v) => Show (OMap k v) where showsPrec = showsPrecList assocs
+-- | Value-lazy
instance (Ord k, Read k, Read v) => Read (OMap k v) where readsPrec = readsPrecList fromList
+-- | @since 0.2.4
+instance (Hashable k, Hashable v) => Hashable (OMap k v) where hashWithSalt s = hashWithSalt s . assocs
-- This instance preserves data abstraction at the cost of inefficiency.
-- We provide limited reflection services for the sake of data abstraction.
+-- | @since 0.2
instance (Data k, Data a, Ord k) => Data (OMap k a) where
gfoldl f z m = z fromList `f` assocs m
toConstr _ = fromListConstr
@@ -51,9 +60,24 @@
oMapDataType :: DataType
oMapDataType = mkDataType "Data.Map.Ordered.Map" [fromListConstr]
+-- | @'GHC.Exts.fromList' = 'fromList'@ (the value-lazy variant) and
+-- @'GHC.Exts.toList' = 'assocs'@.
+--
+-- @since 0.2.4
+instance Ord k => Exts.IsList (OMap k v) where
+ type Item (OMap k v) = (k, v)
+ fromList = fromList
+ toList = assocs
+
#if MIN_VERSION_base(4,9,0)
+-- | Uses the value-lazy variant of 'unionWithL'.
+--
+-- @since 0.2
instance (Ord k, Semigroup v) => Semigroup (Bias L (OMap k v)) where
Bias o <> Bias o' = Bias (unionWithL (const (<>)) o o')
+-- | Uses the value-lazy variant of 'unionWithR'.
+--
+-- @since 0.2
instance (Ord k, Semigroup v) => Semigroup (Bias R (OMap k v)) where
Bias o <> Bias o' = Bias (unionWithR (const (<>)) o o')
#endif
@@ -62,7 +86,9 @@
-- indices of the left argument are preferred, and the values are combined with
-- 'mappend'.
--
--- See the asymptotics of 'unionWithL'.
+-- See the asymptotics of 'unionWithL'. Uses the value-lazy variant.
+--
+-- @since 0.2
instance (Ord k, Monoid v) => Monoid (Bias L (OMap k v)) where
mempty = Bias empty
mappend (Bias o) (Bias o') = Bias (unionWithL (const mappend) o o')
@@ -71,7 +97,9 @@
-- indices of the right argument are preferred, and the values are combined
-- with 'mappend'.
--
--- See the asymptotics of 'unionWithR'.
+-- See the asymptotics of 'unionWithR'. Uses the value-lazy variant.
+--
+-- @since 0.2
instance (Ord k, Monoid v) => Monoid (Bias R (OMap k v)) where
mempty = Bias empty
mappend (Bias o) (Bias o') = Bias (unionWithR (const mappend) o o')
@@ -79,9 +107,13 @@
-- | Values are traversed in insertion order, not key order.
--
-- /O(n*log(n))/ where /n/ is the size of the map.
+--
+-- @since 0.2
instance Ord k => Traversable (OMap k) where
traverse f (OMap tvs kvs) = fromKV <$> traverse (\(k,v) -> (,) k <$> f v) kvs
+-- these are here rather than in Data.Map.Ordered to support the IsList,
+-- Semigroup, and Monoid instances
infixr 5 <|, |< -- copy :
infixl 5 >|, |>
infixr 6 <>|, |<> -- copy <>
@@ -89,14 +121,18 @@
(<|) , (|<) :: Ord k => (,) k v -> OMap k v -> OMap k v
(>|) , (|>) :: Ord k => OMap k v -> (,) k v -> OMap k v
--- | When a key occurs in both maps, prefer the value from the first map.
+-- | When a key occurs in both maps, prefer the value from the second map.
--
-- See asymptotics of 'unionWithR'.
+--
+-- @since 0.2
(<>|) :: Ord k => OMap k v -> OMap k v -> OMap k v
-- | When a key occurs in both maps, prefer the value from the first map.
--
-- See asymptotics of 'unionWithL'.
+--
+-- @since 0.2
(|<>) :: Ord k => OMap k v -> OMap k v -> OMap k v
(k, v) <| OMap tvs kvs = OMap (M.insert k (t, v) tvs) (M.insert t (k, v) kvs) where
@@ -121,6 +157,8 @@
-- precedence, and the supplied function is used to combine the values.
--
-- /O(r*log(r))/ where /r/ is the size of the result
+--
+-- @since 0.2
unionWithL :: Ord k => (k -> v -> v -> v) -> OMap k v -> OMap k v -> OMap k v
unionWithL = unionWithInternal (\t t' -> t )
@@ -129,6 +167,8 @@
-- precedence, and the supplied function is used to combine the values.
--
-- /O(r*log(r))/ where /r/ is the size of the result
+--
+-- @since 0.2
unionWithR :: Ord k => (k -> v -> v -> v) -> OMap k v -> OMap k v -> OMap k v
unionWithR = unionWithInternal (\t t' -> t')
@@ -156,9 +196,8 @@
empty :: OMap k v
empty = OMap M.empty M.empty
-singleton :: (k, v) -> OMap k v
-singleton kv@(k, v) = OMap (M.singleton k (0, v)) (M.singleton 0 kv)
-
+-- This is here rather than in Data.Map.Ordered to support the Read and IsList
+-- instances.
-- | If a key appears multiple times, the first occurrence is used for ordering
-- and the last occurrence is used for its value. The library author welcomes
-- comments on whether this default is sane.
@@ -195,6 +234,8 @@
-- mathematical notation for set intersection.)
--
-- See asymptotics of 'intersectionWith'.
+--
+-- @since 0.2
(/\|) :: Ord k => OMap k v -> OMap k v' -> OMap k v
o /\| o' = intersectionWith (\k v' v -> v) o' o
@@ -202,6 +243,8 @@
-- mathematical notation for set intersection.)
--
-- See asymptotics of 'intersectionWith'.
+--
+-- @since 0.2
(|/\) :: Ord k => OMap k v -> OMap k v' -> OMap k v
o |/\ o' = intersectionWith (\k v v' -> v) o o'
@@ -210,6 +253,8 @@
--
-- /O(m*log(n\/(m+1)) + r*log(r))/ where /m/ is the size of the smaller map, /n/
-- is the size of the larger map, and /r/ is the size of the result.
+--
+-- @since 0.2
intersectionWith ::
Ord k =>
(k -> v -> v' -> v'') ->
@@ -246,14 +291,7 @@
-- | Convert an 'OMap' to a 'Map'.
--
-- /O(n)/, where /n/ is the size of the 'OMap'.
+--
+-- @since 0.2.2
toMap :: OMap k v -> Map k v
toMap (OMap tvs _) = fmap snd tvs
-
--- | Alter the value at k, or absence of. Can be used to insert delete or update
--- with the same semantics as 'Map's alter
-alter :: Ord k => (Maybe v -> Maybe v) -> k -> OMap k v -> OMap k v
-alter f k om@(OMap tvs kvs) =
- case fst <$> M.lookup k tvs of
- Just t -> OMap (M.alter (fmap (t,) . f . fmap snd) k tvs)
- (M.alter (fmap (k,) . f . fmap snd) t kvs)
- Nothing -> maybe om ((om |>) . (k, )) $ f Nothing
\ No newline at end of file
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/ordered-containers-0.2.3/Data/Map/Ordered/Strict.hs new/ordered-containers-0.2.4/Data/Map/Ordered/Strict.hs
--- old/ordered-containers-0.2.3/Data/Map/Ordered/Strict.hs 2001-09-09 03:46:40.000000000 +0200
+++ new/ordered-containers-0.2.4/Data/Map/Ordered/Strict.hs 2001-09-09 03:46:40.000000000 +0200
@@ -1,7 +1,4 @@
-{-# LANGUAGE CPP #-}
-{-# LANGUAGE DeriveDataTypeable #-}
-{-# LANGUAGE DeriveFunctor #-}
-{-# LANGUAGE FlexibleInstances #-}
+{-# LANGUAGE TupleSections #-}
-- | An 'OMap' behaves much like a 'M.Map', with mostly the same asymptotics, but
-- also remembers the order that keys were inserted. All operations whose
@@ -69,6 +66,8 @@
-- precedence, and the supplied function is used to combine the values.
--
-- /O(r*log(r))/ where /r/ is the size of the result
+--
+-- @since 0.2
unionWithL :: Ord k => (k -> v -> v -> v) -> OMap k v -> OMap k v -> OMap k v
unionWithL = unionWithInternal (\t t' -> t )
@@ -77,6 +76,8 @@
-- precedence, and the supplied function is used to combine the values.
--
-- /O(r*log(r))/ where /r/ is the size of the result
+--
+-- @since 0.2
unionWithR :: Ord k => (k -> v -> v -> v) -> OMap k v -> OMap k v -> OMap k v
unionWithR = unionWithInternal (\t t' -> t')
@@ -106,9 +107,21 @@
--
-- /O(m*log(n\/(m+1)) + r*log(r))/ where /m/ is the size of the smaller map, /n/
-- is the size of the larger map, and /r/ is the size of the result.
+--
+-- @since 0.2
intersectionWith ::
Ord k =>
(k -> v -> v' -> v'') ->
OMap k v -> OMap k v' -> OMap k v''
intersectionWith f (OMap tvs kvs) (OMap tvs' kvs') = fromTV
$ M.intersectionWithKey (\k (t,v) (t',v') -> (t, f k v v')) tvs tvs'
+
+-- | Alter the value (or its absence) associated with a key.
+--
+-- @since 0.2.4
+alter :: Ord k => (Maybe v -> Maybe v) -> k -> OMap k v -> OMap k v
+alter f k om@(OMap tvs kvs) = case M.lookup k tvs of
+ Just (t, _) -> OMap
+ (M.alter (fmap (t,) . f . fmap snd) k tvs)
+ (M.alter (fmap (k,) . f . fmap snd) t kvs)
+ Nothing -> maybe om ((om |>) . (k, )) $ f Nothing
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/ordered-containers-0.2.3/Data/Map/Ordered.hs new/ordered-containers-0.2.4/Data/Map/Ordered.hs
--- old/ordered-containers-0.2.3/Data/Map/Ordered.hs 2001-09-09 03:46:40.000000000 +0200
+++ new/ordered-containers-0.2.4/Data/Map/Ordered.hs 2001-09-09 03:46:40.000000000 +0200
@@ -2,6 +2,7 @@
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE FlexibleInstances #-}
+{-# LANGUAGE TupleSections #-}
-- | An 'OMap' behaves much like a 'M.Map', with mostly the same asymptotics, but
-- also remembers the order that keys were inserted. All operations whose
@@ -37,7 +38,20 @@
, toMap
) where
-import qualified Data.Map as M ()
+import qualified Data.Map as M
import Data.Map.Ordered.Internal
import Data.Map.Util
import Prelude hiding (filter, lookup, null)
+
+singleton :: (k, v) -> OMap k v
+singleton kv@(k, v) = OMap (M.singleton k (0, v)) (M.singleton 0 kv)
+
+-- | Alter the value (or its absence) associated with a key.
+--
+-- @since 0.2.3
+alter :: Ord k => (Maybe v -> Maybe v) -> k -> OMap k v -> OMap k v
+alter f k om@(OMap tvs kvs) = case M.lookup k tvs of
+ Just (t, _) -> OMap
+ (M.alter (fmap (t,) . f . fmap snd) k tvs)
+ (M.alter (fmap (k,) . f . fmap snd) t kvs)
+ Nothing -> maybe om ((om |>) . (k, )) $ f Nothing
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/ordered-containers-0.2.3/Data/Map/Util.hs new/ordered-containers-0.2.4/Data/Map/Util.hs
--- old/ordered-containers-0.2.3/Data/Map/Util.hs 2001-09-09 03:46:40.000000000 +0200
+++ new/ordered-containers-0.2.4/Data/Map/Util.hs 2001-09-09 03:46:40.000000000 +0200
@@ -45,11 +45,14 @@
(xs, t) <- reads s
return (fromList xs, t)
--- | A newtype to hand a 'Monoid' instance on. The phantom first parameter
+-- | A newtype to hang a 'Monoid' instance on. The phantom first parameter
-- tells whether 'mappend' will prefer the indices of its first or second
-- argument if there are shared elements in both.
+--
+-- @since 0.2
newtype Bias (dir :: IndexPreference) a = Bias { unbiased :: a }
deriving (Data, Eq, Foldable, Functor, Ord, Read, Show, Traversable, Typeable)
+-- | @since 0.2
data IndexPreference = L | R
deriving Typeable
type L = 'L
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/ordered-containers-0.2.3/Data/Set/Ordered.hs new/ordered-containers-0.2.4/Data/Set/Ordered.hs
--- old/ordered-containers-0.2.3/Data/Set/Ordered.hs 2001-09-09 03:46:40.000000000 +0200
+++ new/ordered-containers-0.2.4/Data/Set/Ordered.hs 2001-09-09 03:46:40.000000000 +0200
@@ -1,6 +1,7 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE FlexibleInstances #-}
+{-# LANGUAGE TypeFamilies #-}
-- | An 'OSet' behaves much like a 'Set', with mostly the same asymptotics, but
-- also remembers the order that values were inserted. All operations whose
@@ -36,6 +37,7 @@
import Data.Data
import Data.Foldable (Foldable, foldl', foldMap, foldr, toList)
import Data.Function (on)
+import Data.Hashable (Hashable(..))
import Data.Map (Map)
import Data.Map.Util
import Data.Monoid (Monoid(..))
@@ -45,9 +47,10 @@
import Data.Set (Set) -- so the haddocks link to the right place
import Prelude hiding (filter, foldr, lookup, null)
import qualified Data.Map as M
+import qualified GHC.Exts as Exts
data OSet a = OSet !(Map a Tag) !(Map Tag a)
- deriving Typeable
+ deriving Typeable -- ^ @since 0.2
-- | Values appear in insertion order, not ascending order.
instance Foldable OSet where foldMap f (OSet _ vs) = foldMap f vs
@@ -55,9 +58,12 @@
instance Ord a => Ord (OSet a) where compare = compare `on` toList
instance Show a => Show (OSet a) where showsPrec = showsPrecList toList
instance (Ord a, Read a) => Read (OSet a) where readsPrec = readsPrecList fromList
+-- | @since 0.2.4
+instance Hashable a => Hashable (OSet a) where hashWithSalt s = hashWithSalt s . toList
-- This instance preserves data abstraction at the cost of inefficiency.
-- We provide limited reflection services for the sake of data abstraction.
+-- | @since 0.2
instance (Data a, Ord a) => Data (OSet a) where
gfoldl f z set = z fromList `f` toList set
toConstr _ = fromListConstr
@@ -74,8 +80,18 @@
oSetDataType :: DataType
oSetDataType = mkDataType "Data.Set.Ordered.Set" [fromListConstr]
+-- | @'GHC.Exts.fromList' = 'fromList'@ and @'GHC.Exts.toList' = 'toList'@.
+--
+-- @since 0.2.4
+instance Ord a => Exts.IsList (OSet a) where
+ type Item (OSet a) = a
+ fromList = fromList
+ toList = toList
+
#if MIN_VERSION_base(4,9,0)
+-- | @since 0.2
instance Ord a => Semigroup (Bias L (OSet a)) where Bias o <> Bias o' = Bias (o |<> o')
+-- | @since 0.2
instance Ord a => Semigroup (Bias R (OSet a)) where Bias o <> Bias o' = Bias (o <>| o')
#endif
@@ -83,6 +99,8 @@
-- indices of the left argument are preferred.
--
-- See the asymptotics of ('|<>').
+--
+-- @since 0.2
instance Ord a => Monoid (Bias L (OSet a)) where
mempty = Bias empty
mappend (Bias o) (Bias o') = Bias (o |<> o')
@@ -91,6 +109,8 @@
-- indices of the right argument are preferred.
--
-- See the asymptotics of ('<>|').
+--
+-- @since 0.2
instance Ord a => Monoid (Bias R (OSet a)) where
mempty = Bias empty
mappend (Bias o) (Bias o') = Bias (o <>| o')
@@ -162,16 +182,20 @@
--
-- /O(m*log(n\/(m+1)) + r*log(r))/, where /m/ is the size of the smaller set,
-- /n/ the size of the larger set, and /r/ the size of the result.
+--
+-- @since 0.2
(|/\) :: Ord a => OSet a -> OSet a -> OSet a
OSet ts vs |/\ OSet ts' vs' = OSet ts'' vs'' where
ts'' = M.intersection ts ts'
- vs'' = M.fromList [(t, v) | (v, t) <- M.toList ts]
+ vs'' = M.fromList [(t, v) | (v, t) <- M.toList ts'']
-- | @flip ('|/\')@
--
-- See asymptotics of '|/\'.
+--
+-- @since 0.2
(/\|) :: Ord a => OSet a -> OSet a -> OSet a
-(/\|) = flip (/\|)
+(/\|) = flip (|/\)
empty :: OSet a
empty = OSet M.empty M.empty
@@ -222,5 +246,7 @@
-- | Convert an 'OSet' to a 'Set'.
--
-- /O(n)/, where /n/ is the size of the 'OSet'.
+--
+-- @since 0.2.2
toSet :: OSet a -> Set a
toSet (OSet ts _) = M.keysSet ts
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/ordered-containers-0.2.3/ordered-containers.cabal new/ordered-containers-0.2.4/ordered-containers.cabal
--- old/ordered-containers-0.2.3/ordered-containers.cabal 2001-09-09 03:46:40.000000000 +0200
+++ new/ordered-containers-0.2.4/ordered-containers.cabal 2001-09-09 03:46:40.000000000 +0200
@@ -1,5 +1,5 @@
name: ordered-containers
-version: 0.2.3
+version: 0.2.4
synopsis: Set- and Map-like types that remember the order elements were inserted
license: BSD3
license-file: LICENSE
@@ -17,6 +17,6 @@
library
exposed-modules: Data.Map.Ordered, Data.Map.Ordered.Strict, Data.Set.Ordered
other-modules: Data.Map.Ordered.Internal, Data.Map.Util
- build-depends: base >=4.7 && <5, containers >=0.1 && <0.7
+ build-depends: base >=4.7 && <5, containers >=0.1 && <0.8, hashable >=1.2 && <2.0
default-language: Haskell98
ghc-options: -fno-warn-tabs