{-# LANGUAGE NoImplicitPrelude, UnicodeSyntax #-}

module Data.Foldable.Unicode where

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

-- from base:
import Data.Bool     ( Bool )
import Data.Eq       ( Eq )
import Data.Function ( flip )
import Data.Foldable ( Foldable, elem, notElem )


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

infix  4 
infix  4 
infix  4 
infix  4 


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

{-|
(∈) = 'elem'

U+2208, ELEMENT OF
-}
()  (Foldable t, Eq α)  α  t α  Bool
() = elem
{-# INLINE () #-}

{-|
(∋) = 'flip' (∈)

U+220B, CONTAINS AS MEMBER
-}
()  (Foldable t, Eq α)  t α  α  Bool
() = flip ()
{-# INLINE () #-}

{-|
(∉) = 'notElem'

U+2209, NOT AN ELEMENT OF
-}
()  (Foldable t, Eq α)  α  t α  Bool
() = notElem
{-# INLINE () #-}

{-|
(∌) = 'flip' (∉)

U+220C, DOES NOT CONTAIN AS MEMBER
-}
()  (Foldable t, Eq α)  t α  α  Bool
() = flip ()
{-# INLINE () #-}