{-# LANGUAGE CPP                #-}
{-# LANGUAGE DeriveDataTypeable #-}
module Distribution.Compat.NonEmptySet (
    NonEmptySet,
    -- * Construction
    singleton,
    -- * Insertion
    insert,
    -- * Deletion
    delete,
    -- * Conversions
    toNonEmpty,
    fromNonEmpty,
    toList,
    toSet,
    -- * Query
    member,
    -- * Map
    map,
) where

import Prelude (Bool (..), Eq, Maybe (..), Ord (..), Read, Show (..), String, error, otherwise, return, showParen, showString, ($), (++), (.))

import Control.DeepSeq    (NFData (..))
import Data.Data          (Data)
import Data.List.NonEmpty (NonEmpty (..))
import Data.Semigroup     (Semigroup (..))
import Data.Typeable      (Typeable)

import qualified Data.Foldable as F
import qualified Data.Set      as Set

import Distribution.Compat.Binary    (Binary (..))
import Distribution.Utils.Structured

#if MIN_VERSION_binary(0,6,0)
import Control.Applicative (empty)
#else
import Control.Monad (fail)
#endif

-- | @since 3.4.0.0
newtype NonEmptySet a = NES (Set.Set a)
  deriving (NonEmptySet a -> NonEmptySet a -> Bool
(NonEmptySet a -> NonEmptySet a -> Bool)
-> (NonEmptySet a -> NonEmptySet a -> Bool) -> Eq (NonEmptySet a)
forall a. Eq a => NonEmptySet a -> NonEmptySet a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NonEmptySet a -> NonEmptySet a -> Bool
$c/= :: forall a. Eq a => NonEmptySet a -> NonEmptySet a -> Bool
== :: NonEmptySet a -> NonEmptySet a -> Bool
$c== :: forall a. Eq a => NonEmptySet a -> NonEmptySet a -> Bool
Eq, Eq (NonEmptySet a)
Eq (NonEmptySet a)
-> (NonEmptySet a -> NonEmptySet a -> Ordering)
-> (NonEmptySet a -> NonEmptySet a -> Bool)
-> (NonEmptySet a -> NonEmptySet a -> Bool)
-> (NonEmptySet a -> NonEmptySet a -> Bool)
-> (NonEmptySet a -> NonEmptySet a -> Bool)
-> (NonEmptySet a -> NonEmptySet a -> NonEmptySet a)
-> (NonEmptySet a -> NonEmptySet a -> NonEmptySet a)
-> Ord (NonEmptySet a)
NonEmptySet a -> NonEmptySet a -> Bool
NonEmptySet a -> NonEmptySet a -> Ordering
NonEmptySet a -> NonEmptySet a -> NonEmptySet a
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall {a}. Ord a => Eq (NonEmptySet a)
forall a. Ord a => NonEmptySet a -> NonEmptySet a -> Bool
forall a. Ord a => NonEmptySet a -> NonEmptySet a -> Ordering
forall a. Ord a => NonEmptySet a -> NonEmptySet a -> NonEmptySet a
min :: NonEmptySet a -> NonEmptySet a -> NonEmptySet a
$cmin :: forall a. Ord a => NonEmptySet a -> NonEmptySet a -> NonEmptySet a
max :: NonEmptySet a -> NonEmptySet a -> NonEmptySet a
$cmax :: forall a. Ord a => NonEmptySet a -> NonEmptySet a -> NonEmptySet a
>= :: NonEmptySet a -> NonEmptySet a -> Bool
$c>= :: forall a. Ord a => NonEmptySet a -> NonEmptySet a -> Bool
> :: NonEmptySet a -> NonEmptySet a -> Bool
$c> :: forall a. Ord a => NonEmptySet a -> NonEmptySet a -> Bool
<= :: NonEmptySet a -> NonEmptySet a -> Bool
$c<= :: forall a. Ord a => NonEmptySet a -> NonEmptySet a -> Bool
< :: NonEmptySet a -> NonEmptySet a -> Bool
$c< :: forall a. Ord a => NonEmptySet a -> NonEmptySet a -> Bool
compare :: NonEmptySet a -> NonEmptySet a -> Ordering
$ccompare :: forall a. Ord a => NonEmptySet a -> NonEmptySet a -> Ordering
Ord, Typeable, Typeable (NonEmptySet a)
Typeable (NonEmptySet a)
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> NonEmptySet a -> c (NonEmptySet a))
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c (NonEmptySet a))
-> (NonEmptySet a -> Constr)
-> (NonEmptySet a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c (NonEmptySet a)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c (NonEmptySet a)))
-> ((forall b. Data b => b -> b) -> NonEmptySet a -> NonEmptySet a)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> NonEmptySet a -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> NonEmptySet a -> r)
-> (forall u. (forall d. Data d => d -> u) -> NonEmptySet a -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> NonEmptySet a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d)
    -> NonEmptySet a -> m (NonEmptySet a))
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> NonEmptySet a -> m (NonEmptySet a))
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> NonEmptySet a -> m (NonEmptySet a))
-> Data (NonEmptySet a)
NonEmptySet a -> DataType
NonEmptySet a -> Constr
(forall b. Data b => b -> b) -> NonEmptySet a -> NonEmptySet a
forall {a}. (Data a, Ord a) => Typeable (NonEmptySet a)
forall a. (Data a, Ord a) => NonEmptySet a -> DataType
forall a. (Data a, Ord a) => NonEmptySet a -> Constr
forall a.
(Data a, Ord a) =>
(forall b. Data b => b -> b) -> NonEmptySet a -> NonEmptySet a
forall a u.
(Data a, Ord a) =>
Int -> (forall d. Data d => d -> u) -> NonEmptySet a -> u
forall a u.
(Data a, Ord a) =>
(forall d. Data d => d -> u) -> NonEmptySet a -> [u]
forall a r r'.
(Data a, Ord a) =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> NonEmptySet a -> r
forall a r r'.
(Data a, Ord a) =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> NonEmptySet a -> r
forall a (m :: * -> *).
(Data a, Ord a, Monad m) =>
(forall d. Data d => d -> m d)
-> NonEmptySet a -> m (NonEmptySet a)
forall a (m :: * -> *).
(Data a, Ord a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> NonEmptySet a -> m (NonEmptySet a)
forall a (c :: * -> *).
(Data a, Ord a) =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (NonEmptySet a)
forall a (c :: * -> *).
(Data a, Ord a) =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NonEmptySet a -> c (NonEmptySet a)
forall a (t :: * -> *) (c :: * -> *).
(Data a, Ord a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (NonEmptySet a))
forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Ord a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (NonEmptySet a))
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> NonEmptySet a -> u
forall u. (forall d. Data d => d -> u) -> NonEmptySet a -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> NonEmptySet a -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> NonEmptySet a -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> NonEmptySet a -> m (NonEmptySet a)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> NonEmptySet a -> m (NonEmptySet a)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (NonEmptySet a)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NonEmptySet a -> c (NonEmptySet a)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (NonEmptySet a))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (NonEmptySet a))
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> NonEmptySet a -> m (NonEmptySet a)
$cgmapMo :: forall a (m :: * -> *).
(Data a, Ord a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> NonEmptySet a -> m (NonEmptySet a)
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> NonEmptySet a -> m (NonEmptySet a)
$cgmapMp :: forall a (m :: * -> *).
(Data a, Ord a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> NonEmptySet a -> m (NonEmptySet a)
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> NonEmptySet a -> m (NonEmptySet a)
$cgmapM :: forall a (m :: * -> *).
(Data a, Ord a, Monad m) =>
(forall d. Data d => d -> m d)
-> NonEmptySet a -> m (NonEmptySet a)
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> NonEmptySet a -> u
$cgmapQi :: forall a u.
(Data a, Ord a) =>
Int -> (forall d. Data d => d -> u) -> NonEmptySet a -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> NonEmptySet a -> [u]
$cgmapQ :: forall a u.
(Data a, Ord a) =>
(forall d. Data d => d -> u) -> NonEmptySet a -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> NonEmptySet a -> r
$cgmapQr :: forall a r r'.
(Data a, Ord a) =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> NonEmptySet a -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> NonEmptySet a -> r
$cgmapQl :: forall a r r'.
(Data a, Ord a) =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> NonEmptySet a -> r
gmapT :: (forall b. Data b => b -> b) -> NonEmptySet a -> NonEmptySet a
$cgmapT :: forall a.
(Data a, Ord a) =>
(forall b. Data b => b -> b) -> NonEmptySet a -> NonEmptySet a
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (NonEmptySet a))
$cdataCast2 :: forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Ord a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (NonEmptySet a))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (NonEmptySet a))
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Ord a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (NonEmptySet a))
dataTypeOf :: NonEmptySet a -> DataType
$cdataTypeOf :: forall a. (Data a, Ord a) => NonEmptySet a -> DataType
toConstr :: NonEmptySet a -> Constr
$ctoConstr :: forall a. (Data a, Ord a) => NonEmptySet a -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (NonEmptySet a)
$cgunfold :: forall a (c :: * -> *).
(Data a, Ord a) =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (NonEmptySet a)
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NonEmptySet a -> c (NonEmptySet a)
$cgfoldl :: forall a (c :: * -> *).
(Data a, Ord a) =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NonEmptySet a -> c (NonEmptySet a)
Data, ReadPrec [NonEmptySet a]
ReadPrec (NonEmptySet a)
Int -> ReadS (NonEmptySet a)
ReadS [NonEmptySet a]
(Int -> ReadS (NonEmptySet a))
-> ReadS [NonEmptySet a]
-> ReadPrec (NonEmptySet a)
-> ReadPrec [NonEmptySet a]
-> Read (NonEmptySet a)
forall a. (Read a, Ord a) => ReadPrec [NonEmptySet a]
forall a. (Read a, Ord a) => ReadPrec (NonEmptySet a)
forall a. (Read a, Ord a) => Int -> ReadS (NonEmptySet a)
forall a. (Read a, Ord a) => ReadS [NonEmptySet a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [NonEmptySet a]
$creadListPrec :: forall a. (Read a, Ord a) => ReadPrec [NonEmptySet a]
readPrec :: ReadPrec (NonEmptySet a)
$creadPrec :: forall a. (Read a, Ord a) => ReadPrec (NonEmptySet a)
readList :: ReadS [NonEmptySet a]
$creadList :: forall a. (Read a, Ord a) => ReadS [NonEmptySet a]
readsPrec :: Int -> ReadS (NonEmptySet a)
$creadsPrec :: forall a. (Read a, Ord a) => Int -> ReadS (NonEmptySet a)
Read)

-------------------------------------------------------------------------------
-- Instances
-------------------------------------------------------------------------------

instance Show a => Show (NonEmptySet a) where
    showsPrec :: Int -> NonEmptySet a -> ShowS
showsPrec Int
d NonEmptySet a
s = Bool -> ShowS -> ShowS
showParen (Int
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
10)
        (ShowS -> ShowS) -> ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$ String -> ShowS
showString String
"fromNonEmpty "
        ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> NonEmpty a -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
11 (NonEmptySet a -> NonEmpty a
forall a. NonEmptySet a -> NonEmpty a
toNonEmpty NonEmptySet a
s)

instance Binary a => Binary (NonEmptySet a) where
    put :: NonEmptySet a -> Put
put (NES Set a
s) = Set a -> Put
forall t. Binary t => t -> Put
put Set a
s
    get :: Get (NonEmptySet a)
get = do
        Set a
xs <- Get (Set a)
forall t. Binary t => Get t
get
        if Set a -> Bool
forall a. Set a -> Bool
Set.null Set a
xs
#if MIN_VERSION_binary(0,6,0)
        then Get (NonEmptySet a)
forall (f :: * -> *) a. Alternative f => f a
empty
#else
        then fail "NonEmptySet: empty"
#endif
        else NonEmptySet a -> Get (NonEmptySet a)
forall (m :: * -> *) a. Monad m => a -> m a
return (Set a -> NonEmptySet a
forall a. Set a -> NonEmptySet a
NES Set a
xs)

instance Structured a => Structured (NonEmptySet a) where
    structure :: Proxy (NonEmptySet a) -> Structure
structure = Proxy (NonEmptySet a) -> Structure
forall {k} (f :: * -> k) a.
(Typeable f, Structured a) =>
Proxy (f a) -> Structure
containerStructure

instance NFData a => NFData (NonEmptySet a) where
    rnf :: NonEmptySet a -> ()
rnf (NES Set a
x) = Set a -> ()
forall a. NFData a => a -> ()
rnf Set a
x

-- | Note: there aren't @Monoid@ instance.
instance Ord a => Semigroup (NonEmptySet a) where
    NES Set a
x <> :: NonEmptySet a -> NonEmptySet a -> NonEmptySet a
<> NES Set a
y = Set a -> NonEmptySet a
forall a. Set a -> NonEmptySet a
NES (Set a -> Set a -> Set a
forall a. Ord a => Set a -> Set a -> Set a
Set.union Set a
x Set a
y)

instance F.Foldable NonEmptySet where
    foldMap :: forall m a. Monoid m => (a -> m) -> NonEmptySet a -> m
foldMap a -> m
f (NES Set a
s) = (a -> m) -> Set a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
F.foldMap a -> m
f Set a
s
    foldr :: forall a b. (a -> b -> b) -> b -> NonEmptySet a -> b
foldr a -> b -> b
f b
z (NES Set a
s) = (a -> b -> b) -> b -> Set a -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
F.foldr a -> b -> b
f b
z Set a
s

#if MIN_VERSION_base(4,8,0)
    toList :: forall a. NonEmptySet a -> [a]
toList         = NonEmptySet a -> [a]
forall a. NonEmptySet a -> [a]
toList
    null :: forall a. NonEmptySet a -> Bool
null NonEmptySet a
_         = Bool
False
    length :: forall a. NonEmptySet a -> Int
length (NES Set a
s) = Set a -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
F.length Set a
s
#endif

-------------------------------------------------------------------------------
-- Constructors
-------------------------------------------------------------------------------

singleton :: a -> NonEmptySet a
singleton :: forall a. a -> NonEmptySet a
singleton = Set a -> NonEmptySet a
forall a. Set a -> NonEmptySet a
NES (Set a -> NonEmptySet a) -> (a -> Set a) -> a -> NonEmptySet a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Set a
forall a. a -> Set a
Set.singleton

-------------------------------------------------------------------------------
-- Insertion
-------------------------------------------------------------------------------

insert :: Ord a => a -> NonEmptySet a -> NonEmptySet a
insert :: forall a. Ord a => a -> NonEmptySet a -> NonEmptySet a
insert a
x (NES Set a
xs) = Set a -> NonEmptySet a
forall a. Set a -> NonEmptySet a
NES (a -> Set a -> Set a
forall a. Ord a => a -> Set a -> Set a
Set.insert a
x Set a
xs)

-------------------------------------------------------------------------------
-- Deletion
-------------------------------------------------------------------------------

delete :: Ord a => a -> NonEmptySet a -> Maybe (NonEmptySet a)
delete :: forall a. Ord a => a -> NonEmptySet a -> Maybe (NonEmptySet a)
delete a
x (NES Set a
xs)
    | Set a -> Bool
forall a. Set a -> Bool
Set.null Set a
res = Maybe (NonEmptySet a)
forall a. Maybe a
Nothing
    | Bool
otherwise    = NonEmptySet a -> Maybe (NonEmptySet a)
forall a. a -> Maybe a
Just (Set a -> NonEmptySet a
forall a. Set a -> NonEmptySet a
NES Set a
xs)
  where
    res :: Set a
res = a -> Set a -> Set a
forall a. Ord a => a -> Set a -> Set a
Set.delete a
x Set a
xs

-------------------------------------------------------------------------------
-- Conversions
-------------------------------------------------------------------------------

fromNonEmpty :: Ord a => NonEmpty a -> NonEmptySet a
fromNonEmpty :: forall a. Ord a => NonEmpty a -> NonEmptySet a
fromNonEmpty (a
x :| [a]
xs) = Set a -> NonEmptySet a
forall a. Set a -> NonEmptySet a
NES ([a] -> Set a
forall a. Ord a => [a] -> Set a
Set.fromList (a
x a -> [a] -> [a]
forall a. a -> [a] -> [a]
: [a]
xs))

toNonEmpty :: NonEmptySet a -> NonEmpty a
toNonEmpty :: forall a. NonEmptySet a -> NonEmpty a
toNonEmpty (NES Set a
s) = case Set a -> [a]
forall a. Set a -> [a]
Set.toList Set a
s of
    []   -> String -> NonEmpty a
forall a. String -> a
panic String
"toNonEmpty"
    a
x:[a]
xs -> a
x a -> [a] -> NonEmpty a
forall a. a -> [a] -> NonEmpty a
:| [a]
xs

toList :: NonEmptySet a -> [a]
toList :: forall a. NonEmptySet a -> [a]
toList (NES Set a
s) = Set a -> [a]
forall a. Set a -> [a]
Set.toList Set a
s

toSet :: NonEmptySet a -> Set.Set a
toSet :: forall a. NonEmptySet a -> Set a
toSet (NES Set a
s) = Set a
s

-------------------------------------------------------------------------------
-- Query
-------------------------------------------------------------------------------

member :: Ord a => a -> NonEmptySet a -> Bool
member :: forall a. Ord a => a -> NonEmptySet a -> Bool
member a
x (NES Set a
xs) = a -> Set a -> Bool
forall a. Ord a => a -> Set a -> Bool
Set.member a
x Set a
xs

-------------------------------------------------------------------------------
-- Map
-------------------------------------------------------------------------------

map
    :: ( Ord b
#if !MIN_VERSION_containers(0,5,2)
       , Ord a
#endif
       )
    => (a -> b) -> NonEmptySet a -> NonEmptySet b
map :: forall b a. Ord b => (a -> b) -> NonEmptySet a -> NonEmptySet b
map a -> b
f (NES Set a
x) = Set b -> NonEmptySet b
forall a. Set a -> NonEmptySet a
NES ((a -> b) -> Set a -> Set b
forall b a. Ord b => (a -> b) -> Set a -> Set b
Set.map a -> b
f Set a
x)

-------------------------------------------------------------------------------
-- Internal
-------------------------------------------------------------------------------

panic :: String -> a
panic :: forall a. String -> a
panic String
msg = String -> a
forall a. HasCallStack => String -> a
error (String -> a) -> String -> a
forall a b. (a -> b) -> a -> b
$ String
"NonEmptySet invariant violated: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
msg