{-# LANGUAGE NoImplicitPrelude, UnicodeSyntax #-} module Data.Bool.Unicode ( (∧), (∨), (¬), (⊻), (⊼), (⊽) ) where ------------------------------------------------------------------------------- -- Imports ------------------------------------------------------------------------------- -- from base: import Data.Bool ( Bool, (&&), (||), not ) ------------------------------------------------------------------------------- -- Fixities ------------------------------------------------------------------------------- infixr 2 ∨ infixr 3 ⊽ infixr 3 ⊼ infixr 3 ⊻ infixr 3 ∧ ------------------------------------------------------------------------------- -- Symbols ------------------------------------------------------------------------------- {-| (¬) = 'not' U+00AC, NOT SIGN -} (¬) ∷ Bool → Bool (¬) = not {-# INLINE (¬) #-} {-| (∧) = ('&&') U+2227, LOGICAL AND -} (∧) ∷ Bool → Bool → Bool (∧) = (&&) {-# INLINE (∧) #-} {-| (∨) = ('||') U+2228, LOGICAL OR -} (∨) ∷ Bool → Bool → Bool (∨) = (||) {-# INLINE (∨) #-} {-| a ⊻ b = (a ∨ b) ∧ not (a ∧ b) U+22BB, XOR -} (⊻) ∷ Bool → Bool → Bool a ⊻ b = (a || b) && not (a && b) {-# INLINE (⊻) #-} {-| a ⊼ b = not (a ∧ b) U+22bc, NAND -} (⊼) ∷ Bool → Bool → Bool a ⊼ b = not (a && b) {-# INLINE (⊼) #-} {-| a ⊽ b = not (a ∨ b) U+22bd, NOR -} (⊽) ∷ Bool → Bool → Bool a ⊽ b = not (a || b) {-# INLINE (⊽) #-}