{-# LANGUAGE CPP               #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE UnicodeSyntax     #-}

{-|
Module     : Data.IntMap.Lazy.Unicode
Copyright  : 2009–2012 Roel van Dijk
License    : BSD3 (see the file LICENSE)
Maintainer : Roel van Dijk <vandijk.roel@gmail.com>
-}

module Data.IntMap.Lazy.Unicode
    ( (∈), (∋), (∉), (∌)
    , (∅)
    , (∪), (∖), (∆), (∩)
    ) where


-------------------------------------------------------------------------------
-- Imports
-------------------------------------------------------------------------------

-- from base:
import Data.Bool     ( Bool )
import Data.Int      ( Int )
import Data.Function ( flip )

-- from containers:
#ifdef CONTAINERS_OLD
#define MODULE Data.IntMap
#else
#define MODULE Data.IntMap.Lazy
#endif
import MODULE ( IntMap
              , member, notMember
              , empty
              , union, difference, intersection
              )
#undef MODULE


-------------------------------------------------------------------------------
-- Fixities
-------------------------------------------------------------------------------

infix  4 
infix  4 
infix  4 
infix  4 
infixl 6 
infixr 6 
infixl 9 
infixl 9 


-------------------------------------------------------------------------------
-- Symbols
-------------------------------------------------------------------------------

{-|
(&#x2208;) = 'member'

U+2208, ELEMENT OF
-}
(∈)  Int  IntMap α  Bool
∈ :: Int -> IntMap α -> Bool
(∈) = Int -> IntMap α -> Bool
forall a. Int -> IntMap a -> Bool
member
{-# INLINE () #-}

{-|
(&#x220B;) = 'flip' (&#x2208;)

U+220B, CONTAINS AS MEMBER
-}
(∋)  IntMap α  Int  Bool
∋ :: IntMap α -> Int -> Bool
(∋) = (Int -> IntMap α -> Bool) -> IntMap α -> Int -> Bool
forall a b c. (a -> b -> c) -> b -> a -> c
flip Int -> IntMap α -> Bool
forall a. Int -> IntMap a -> Bool
(∈)
{-# INLINE () #-}

{-|
(&#x2209;) = 'notMember'

U+2209, NOT AN ELEMENT OF
-}
(∉)  Int  IntMap α  Bool
∉ :: Int -> IntMap α -> Bool
(∉) = Int -> IntMap α -> Bool
forall a. Int -> IntMap a -> Bool
notMember
{-# INLINE () #-}

{-|
(&#x220C;) = 'flip' (&#x2209;)

U+220C, DOES NOT CONTAIN AS MEMBER
-}
(∌)  IntMap α  Int  Bool
∌ :: IntMap α -> Int -> Bool
(∌) = (Int -> IntMap α -> Bool) -> IntMap α -> Int -> Bool
forall a b c. (a -> b -> c) -> b -> a -> c
flip Int -> IntMap α -> Bool
forall a. Int -> IntMap a -> Bool
(∉)
{-# INLINE () #-}

{-|
(&#x2205;) = 'empty'

U+2205, EMPTY SET
-}
(∅)  IntMap α
∅ :: IntMap α
(∅) = IntMap α
forall a. IntMap a
empty
{-# INLINE () #-}

{-|
(&#x222A;) = 'union'

U+222A, UNION
-}
(∪)  IntMap α  IntMap α  IntMap α
∪ :: IntMap α -> IntMap α -> IntMap α
(∪) = IntMap α -> IntMap α -> IntMap α
forall a. IntMap a -> IntMap a -> IntMap a
union
{-# INLINE () #-}

{-|
(&#x2216;) = 'difference'

U+2216, SET MINUS
-}
(∖)  IntMap α  IntMap β  IntMap α
∖ :: IntMap α -> IntMap β -> IntMap α
(∖) = IntMap α -> IntMap β -> IntMap α
forall a b. IntMap a -> IntMap b -> IntMap a
difference
{-# INLINE () #-}

{-|
Symmetric difference

a &#x2206; b = (a &#x2216; b) &#x222A; (b &#x2216; a)

U+2206, INCREMENT
-}
(∆)  IntMap α  IntMap α  IntMap α
IntMap α
a ∆ :: IntMap α -> IntMap α -> IntMap α
 IntMap α
b = (IntMap α
a IntMap α -> IntMap α -> IntMap α
forall a b. IntMap a -> IntMap b -> IntMap a
 IntMap α
b) IntMap α -> IntMap α -> IntMap α
forall a. IntMap a -> IntMap a -> IntMap a
 (IntMap α
b IntMap α -> IntMap α -> IntMap α
forall a b. IntMap a -> IntMap b -> IntMap a
 IntMap α
a)
{-# INLINE () #-}

{-|
(&#x2229;) = 'intersection'

U+2229, INTERSECTION
-}
(∩)  IntMap α  IntMap β  IntMap α
∩ :: IntMap α -> IntMap β -> IntMap α
(∩) = IntMap α -> IntMap β -> IntMap α
forall a b. IntMap a -> IntMap b -> IntMap a
intersection
{-# INLINE () #-}