{-# LANGUAGE NoImplicitPrelude, UnicodeSyntax #-} {-| Module : Data.IntMap.Lazy.Unicode Copyright : 2009–2012 Roel van Dijk License : BSD3 (see the file LICENSE) Maintainer : Roel van Dijk -} module Data.IntMap.Strict.Unicode ( (∈), (∋), (∉), (∌) , (∅) , (∪), (∖), (∆), (∩) ) where ------------------------------------------------------------------------------- -- Imports ------------------------------------------------------------------------------- -- from base: import Data.Bool ( Bool ) import Data.Int ( Int ) import Data.Function ( flip ) -- from containers: import Data.IntMap.Strict ( IntMap , member, notMember , empty , union, difference, intersection ) ------------------------------------------------------------------------------- -- Fixities ------------------------------------------------------------------------------- infix 4 ∈ infix 4 ∋ infix 4 ∉ infix 4 ∌ infixl 6 ∪ infixr 6 ∩ infixl 9 ∖ infixl 9 ∆ ------------------------------------------------------------------------------- -- Symbols ------------------------------------------------------------------------------- {-| (∈) = 'member' U+2208, ELEMENT OF -} (∈) ∷ Int → IntMap α → Bool (∈) = member {-# INLINE (∈) #-} {-| (∋) = 'flip' (∈) U+220B, CONTAINS AS MEMBER -} (∋) ∷ IntMap α → Int → Bool (∋) = flip (∈) {-# INLINE (∋) #-} {-| (∉) = 'notMember' U+2209, NOT AN ELEMENT OF -} (∉) ∷ Int → IntMap α → Bool (∉) = notMember {-# INLINE (∉) #-} {-| (∌) = 'flip' (∉) U+220C, DOES NOT CONTAIN AS MEMBER -} (∌) ∷ IntMap α → Int → Bool (∌) = flip (∉) {-# INLINE (∌) #-} {-| (∅) = 'empty' U+2205, EMPTY SET -} (∅) ∷ IntMap α (∅) = empty {-# INLINE (∅) #-} {-| (∪) = 'union' U+222A, UNION -} (∪) ∷ IntMap α → IntMap α → IntMap α (∪) = union {-# INLINE (∪) #-} {-| (∖) = 'difference' U+2216, SET MINUS -} (∖) ∷ IntMap α → IntMap β → IntMap α (∖) = difference {-# INLINE (∖) #-} {-| Symmetric difference a ∆ b = (a ∖ b) ∪ (b ∖ a) U+2206, INCREMENT -} (∆) ∷ IntMap α → IntMap α → IntMap α a ∆ b = (a ∖ b) ∪ (b ∖ a) {-# INLINE (∆) #-} {-| (∩) = 'intersection' U+2229, INTERSECTION -} (∩) ∷ IntMap α → IntMap β → IntMap α (∩) = intersection {-# INLINE (∩) #-}