{-# LANGUAGE NoImplicitPrelude, UnicodeSyntax #-}
module Data.IntSet.Unicode
( (∈), (∋), (∉), (∌)
, (∅)
, (∪), (∖), (∆), (∩)
, (⊆), (⊇), (⊈), (⊉)
, (⊂), (⊃), (⊄), (⊅)
) where
import Data.Bool ( Bool, not )
import Data.Function ( flip )
import Data.Int ( Int )
import Data.Eq.Unicode ( (≢) )
import Data.Bool.Unicode ( (∧) )
import Data.IntSet ( IntSet
, member, notMember
, empty
, union, difference, intersection
, isSubsetOf, isProperSubsetOf
)
infix 4 ∈
infix 4 ∋
infix 4 ∉
infix 4 ∌
infix 4 ⊆
infix 4 ⊇
infix 4 ⊈
infix 4 ⊉
infix 4 ⊂
infix 4 ⊃
infix 4 ⊄
infix 4 ⊅
infixl 6 ∪
infixr 6 ∩
infixl 9 ∖
infixl 9 ∆
(∈) ∷ Int → IntSet → Bool
∈ :: Int -> IntSet -> Bool
(∈) = Int -> IntSet -> Bool
member
{-# INLINE (∈) #-}
(∋) ∷ IntSet → Int → Bool
∋ :: IntSet -> Int -> Bool
(∋) = (Int -> IntSet -> Bool) -> IntSet -> Int -> Bool
forall a b c. (a -> b -> c) -> b -> a -> c
flip Int -> IntSet -> Bool
(∈)
{-# INLINE (∋) #-}
(∉) ∷ Int → IntSet → Bool
∉ :: Int -> IntSet -> Bool
(∉) = Int -> IntSet -> Bool
notMember
{-# INLINE (∉) #-}
(∌) ∷ IntSet → Int → Bool
∌ :: IntSet -> Int -> Bool
(∌) = (Int -> IntSet -> Bool) -> IntSet -> Int -> Bool
forall a b c. (a -> b -> c) -> b -> a -> c
flip Int -> IntSet -> Bool
(∉)
{-# INLINE (∌) #-}
(∅) ∷ IntSet
∅ :: IntSet
(∅) = IntSet
empty
{-# INLINE (∅) #-}
(∪) ∷ IntSet → IntSet → IntSet
∪ :: IntSet -> IntSet -> IntSet
(∪) = IntSet -> IntSet -> IntSet
union
{-# INLINE (∪) #-}
(∖) ∷ IntSet → IntSet → IntSet
∖ :: IntSet -> IntSet -> IntSet
(∖) = IntSet -> IntSet -> IntSet
difference
{-# INLINE (∖) #-}
(∆) ∷ IntSet → IntSet → IntSet
IntSet
a ∆ :: IntSet -> IntSet -> IntSet
∆ IntSet
b = (IntSet
a IntSet -> IntSet -> IntSet
∖ IntSet
b) IntSet -> IntSet -> IntSet
∪ (IntSet
b IntSet -> IntSet -> IntSet
∖ IntSet
a)
{-# INLINE (∆) #-}
(∩) ∷ IntSet → IntSet → IntSet
∩ :: IntSet -> IntSet -> IntSet
(∩) = IntSet -> IntSet -> IntSet
intersection
{-# INLINE (∩) #-}
(⊆) ∷ IntSet → IntSet → Bool
⊆ :: IntSet -> IntSet -> Bool
(⊆) = IntSet -> IntSet -> Bool
isSubsetOf
{-# INLINE (⊆) #-}
(⊇) ∷ IntSet → IntSet → Bool
⊇ :: IntSet -> IntSet -> Bool
(⊇) = (IntSet -> IntSet -> Bool) -> IntSet -> IntSet -> Bool
forall a b c. (a -> b -> c) -> b -> a -> c
flip IntSet -> IntSet -> Bool
(⊆)
{-# INLINE (⊇) #-}
(⊈) ∷ IntSet → IntSet → Bool
IntSet
a ⊈ :: IntSet -> IntSet -> Bool
⊈ IntSet
b = (IntSet
a IntSet -> IntSet -> Bool
forall α. Eq α => α -> α -> Bool
≢ IntSet
b) Bool -> Bool -> Bool
∧ (IntSet
a IntSet -> IntSet -> Bool
⊄ IntSet
b)
{-# INLINE (⊈) #-}
(⊉) ∷ IntSet → IntSet → Bool
IntSet
a ⊉ :: IntSet -> IntSet -> Bool
⊉ IntSet
b = (IntSet
a IntSet -> IntSet -> Bool
forall α. Eq α => α -> α -> Bool
≢ IntSet
b) Bool -> Bool -> Bool
∧ (IntSet
a IntSet -> IntSet -> Bool
⊅ IntSet
b)
{-# INLINE (⊉) #-}
(⊂) ∷ IntSet → IntSet → Bool
⊂ :: IntSet -> IntSet -> Bool
(⊂) = IntSet -> IntSet -> Bool
isProperSubsetOf
{-# INLINE (⊂) #-}
(⊃) ∷ IntSet → IntSet → Bool
⊃ :: IntSet -> IntSet -> Bool
(⊃) = (IntSet -> IntSet -> Bool) -> IntSet -> IntSet -> Bool
forall a b c. (a -> b -> c) -> b -> a -> c
flip IntSet -> IntSet -> Bool
(⊂)
{-# INLINE (⊃) #-}
(⊄) ∷ IntSet → IntSet → Bool
IntSet
a ⊄ :: IntSet -> IntSet -> Bool
⊄ IntSet
b = Bool -> Bool
not (IntSet
a IntSet -> IntSet -> Bool
⊂ IntSet
b)
{-# INLINE (⊄) #-}
(⊅) ∷ IntSet → IntSet → Bool
IntSet
a ⊅ :: IntSet -> IntSet -> Bool
⊅ IntSet
b = Bool -> Bool
not (IntSet
a IntSet -> IntSet -> Bool
⊃ IntSet
b)
{-# INLINE (⊅) #-}