{-# LANGUAGE UnicodeSyntax #-} module Data.IntSet.Unicode ( (∈), (∉) , (∅) , (∪), (∩) , (⊆), (⊇), (⊈), (⊉) , (⊂), (⊃), (⊄), (⊅) ) where import Prelude.Unicode ( (≢), (∧) ) import Data.IntSet ( IntSet , member, notMember , empty , union, intersection , isSubsetOf, isProperSubsetOf ) {- | (∈) = 'member' U+2208, ELEMENT OF -} (∈) ∷ Int -> IntSet → Bool (∈) = member {- | (∉) = 'notMember' U+2209, NOT AN ELEMENT OF -} (∉) ∷ Int -> IntSet → Bool (∉) = notMember {- | (∅) = 'empty' U+2205, EMPTY SET -} (∅) ∷ IntSet (∅) = empty {- | (∪) = 'union' U+222A, UNION -} (∪) ∷ IntSet → IntSet → IntSet (∪) = union {- | (∩) = 'intersection' U+2229, INTERSECTION -} (∩) ∷ IntSet → IntSet → IntSet (∩) = intersection {- | (⊆) = 'isSubsetOf' U+2286, SUBSET OF OR EQUAL TO -} (⊆) ∷ IntSet → IntSet → Bool (⊆) = isSubsetOf {- | (⊇) = 'flip' (⊆) U+2287, SUPERSET OF OR EQUAL TO -} (⊇) ∷ IntSet → IntSet → Bool (⊇) = flip (⊆) {- | x ⊈ y = (x ≢ y) ∧ (x ⊄ y) U+2288, NEITHER A SUBSET OF NOR EQUAL TO -} (⊈) ∷ IntSet → IntSet → Bool x ⊈ y = (x ≢ y) ∧ (x ⊄ y) {- | x ⊉ y = (x ≢ y) ∧ (x ⊅ y) U+2289, NEITHER A SUPERSET OF NOR EQUAL TO -} (⊉) ∷ IntSet → IntSet → Bool x ⊉ y = (x ≢ y) ∧ (x ⊅ y) {- | (⊂) = 'isProperSubsetOf' U+2282, SUBSET OF -} (⊂) ∷ IntSet → IntSet → Bool (⊂) = isProperSubsetOf {- | (⊃) = 'flip' (⊂) U+2283, SUPERSET OF -} (⊃) ∷ IntSet → IntSet → Bool (⊃) = flip (⊂) {- | x ⊄ y = 'not' (x ⊂ y) U+2284, NOT A SUBSET OF -} (⊄) ∷ IntSet → IntSet → Bool x ⊄ y = not (x ⊂ y) {- | x ⊅ y = 'not' (x ⊃ y) U+2285, NOT A SUPERSET OF -} (⊅) ∷ IntSet → IntSet → Bool x ⊅ y = not (x ⊃ y)