{-# LANGUAGE NoImplicitPrelude, UnicodeSyntax #-} {-| Module : PreludePlus.Unicode Copyright : 2018 Joshua Booth License : BSD3 (see the file LICENSE) Maintainer : Joshua Booth Various unicode synonyms for basic functions. -} module PreludePlus.Unicode ( -- * Functional (∘) , (↦) , (↤) , (↤∘) , (≫=) , (≫) , (=≪) -- * Boolean , (∨) , (∧) -- * Comparison , (≡) , (≠) , (≤) , (≥) -- * Arithmetic , (÷) , (٪) , (—) -- * Collections , (⌥) , (∈) , (∉) , (⧺) , (∪) , (∩) , (⩀) , (∖) , ø ) where import Control.Applicative (Alternative, (<|>)) import Control.Monad (Monad, (>>=), (>>), (=<<)) import Data.Bool (Bool, (&&), (||), not) import Data.Eq (Eq, (==), (/=)) import Data.Foldable (Foldable, elem, notElem) import Data.Function ((.), ($), flip) import Data.Functor (Functor, fmap) import Data.Monoid (Monoid, mempty) import Data.List ((\\), intersect, null, union) import Data.Ord (Ord, (<=), (>=)) import Data.Semigroup (Semigroup, (<>)) import GHC.Num (Num, (-)) import GHC.Real (Integral, quot, mod) ------------ -- Functions ------------ -- | @(∘) = ('.')@ -- -- U+2218, RING OPERATOR infixr 9 ∘ (∘) ∷ (b → g) → (a → b) → (a → g) (∘) = (.) {-# INLINE (∘) #-} -- | @(↦) = 'flip' 'fmap'@ -- -- U+21A6, RIGHTWARDS ARROW FROM BAR infixl 4 ↦ (↦) ∷ Functor f => f a → (a → b) → f b (↦) = flip fmap {-# INLINE (↦) #-} -- | @(↤) = 'fmap'@ -- -- U+21A4, LEFTWARDS ARROW FROM BAR infixl 4 ↤ (↤) ∷ Functor f => (a → b) → f a → f b (↤) = fmap {-# INLINE (↤) #-} -- | @f ↤∘ g = 'fmap' f ∘ g@ -- -- (U+21A4, LEFTWARDS ARROW FROM BAR) + (U+2218, RING OPERATOR) infixr 7 ↤∘ (↤∘) ∷ Functor f => (a → b) → (c → f a) → c → f b f ↤∘ g = fmap f ∘ g -- | @(≫=) = ('>>=')@ -- -- (U+226B, MUCH GREATER-THAN) + (U+003D, EQUALS SIGN) infixl 1 ≫= (≫=) ∷ Monad m => m a → (a → m b) → m b (≫=) = (>>=) {-# INLINE (≫=) #-} -- | @(≫) = ('>>')@ -- -- U+226B, MUCH GREATER-THAN infixl 1 ≫ (≫) ∷ Monad m => m a → m b → m b (≫) = (>>) {-# INLINE (≫) #-} -- | @(=≪) = ('=<<')@ -- -- (U+003D, EQUALS SIGN) + (U+226A, MUCH LESS-THAN) infixr 1 =≪ (=≪) ∷ Monad m => (a → m b) → m a → m b (=≪) = (=<<) {-# INLINE (=≪) #-} ---------- -- Boolean ---------- -- | @(∨) = ('||')@ -- -- U+2228, LOGICAL OR infixr 2 ∨ (∨) ∷ Bool → Bool → Bool (∨) = (||) {-# INLINE (∨) #-} -- | @(∧) = ('&&')@ -- -- U+2227, LOGICAL AND infixr 3 ∧ (∧) ∷ Bool → Bool → Bool (∧) = (&&) {-# INLINE (∧) #-} ------------- -- Comparison ------------- -- | @(≡) = ('==')@ -- -- U+2261, IDENTICAL TO infix 4 ≡ (≡) ∷ Eq a => a → a → Bool (≡) = (==) {-# INLINE (≡) #-} -- | @(≠) = ('/=')@ -- -- U+2260, NOT EQUAL TO infix 4 ≠ (≠) ∷ Eq a => a → a → Bool (≠) = (/=) {-# INLINE (≠) #-} -- | @(≤) = ('<=')@ -- -- U+2264, LESS-THAN OR EQUAL TO infix 4 ≤ (≤) ∷ Ord a => a → a → Bool (≤) = (<=) {-# INLINE (≤) #-} -- | @(≥) = ('>=')@ -- -- U+2265, GREATER-THAN OR EQUAL TO infix 4 ≥ (≥) ∷ Ord a => a → a → Bool (≥) = (>=) {-# INLINE (≥) #-} ------------- -- Arithmetic ------------- -- | @(÷) = 'quot'@ -- -- U+00F7, DIVISION SIGN infixl 7 ÷ (÷) ∷ Integral a => a → a → a (÷) = quot {-# INLINE (÷) #-} -- | @(٪) = 'mod'@ -- -- U+066A, ARABIC PERCENT SIGN infixl 7 ٪ (٪) ∷ Integral a => a → a → a (٪) = mod {-# INLINE (٪) #-} -- | @(—) = ('-')@ -- -- U+2014, EM DASH -- -- Allows for sections, as in @(—3)@. (—) ∷ Num a => a → a → a (—) = (-) -------------- -- Collections -------------- -- | @(⌥) = ('<|>')@ -- -- U+2325, OPTION KEY (⌥) ∷ Alternative f => f a → f a → f a (⌥) = (<|>) -- | @(∈) = 'elem'@ -- -- U+2208, ELEMENT OF infix 4 ∈ (∈) ∷ (Foldable a, Eq b) => b → a b → Bool (∈) = elem {-# INLINE (∈) #-} -- | @(∉) = 'notElem'@ -- -- U+2209, NOT AN ELEMENT OF infix 4 ∉ (∉) ∷ (Foldable a, Eq b) => b → a b → Bool (∉) = notElem {-# INLINE (∉) #-} -- | @(⧺) = ('<>')@ -- -- U+29FA, DOUBLE PLUS infixr 5 ⧺ (⧺) ∷ Semigroup m => m → m → m (⧺) = (<>) {-# INLINE (⧺) #-} -- | @(∖) = ('\\')@ -- -- U+2216, SET MINUS infixr 5 ∖ (∖) ∷ Eq a => [a] → [a] → [a] (∖) = (\\) -- | @(∪) = 'union'@ -- -- U+22A, UNION infixl 6 ∪ (∪) ∷ Eq a => [a] → [a] → [a] (∪) = union {-# INLINE (∪) #-} -- | @(∩) = 'intersect'@ -- -- U+2229, INTERSECTION infixr 6 ∩ (∩) ∷ Eq a => [a] → [a] → [a] (∩) = intersect -- | @(⩀) a b = 'not' ∘ 'null' $ 'intersect' a b@ -- -- U+2A40, INTERSECTION WITH DOT infixr 6 ⩀ (⩀) ∷ Eq a => [a] → [a] → Bool (⩀) a b = not ∘ null $ intersect a b -- | @ø = 'mempty'@ -- -- U+00F8, LATIN SMALL LETTER O WITH STROKE ø ∷ Monoid a => a ø = mempty