-----------------------------------------------------------------------------
-- |
-- Module      :  Prelude.Unicode
-- Copyright   :  (c) Péter Diviánszky 2008
-- License     :  BSD3-style (see LICENSE)
-- 
-- Maintainer:    divip@aszt.inf.elte.hu
-- Stability   :  alpha
-- Portability :  unknown
--
-- /If the Haddock documentation is unreadable, look the source./
--
-- This module adds unicode notation for some definitions in Prelude.
--
-- The following notations are built in GHC (enabled with the 'UnicodeSyntax' language extension):
--
-- * '→' ('\x2192') is equivalent to '->'.
--
-- * '←' ('\x2190') is equivalent to '<-'.
--
-- * '∷' ('\x2237') is equivalent to '::'.
--
-- * '⇒' ('\x21d2') is equivalent to '=>'.
--
-- * '∀' ('\x2200') is equivalent to 'forall' (use the 'Rank2Types' language extension).
--
-- The following notations are /not/ built in GHC
-- (see also <http://hackage.haskell.org/trac/haskell-prime/wiki/UnicodeInHaskellSource>):
--
-- * '‥' ('\x2025') is equivalent to '..'.
--
-- * '∃' ('\x2203') is equivalent to 'exists' (with 'ExistentialQuantification').
--
-- Usage examples
--
-- > even ◦ succ  ∷  Integral a ⇒ a → Bool 
--
-- > 25 ∈ [x·x | x←[1..10], x≠2]  ∷  Bool
--
-- > foldl (flip (:)) (∅)  ∷  [a] → [a]
--
-- > (\a → a × a × a)  ∷  a → a :× a :× a
--
-- > (\a b → (¬)(a ∧ b) ⇔ (¬)a ∨ (¬)b)  ∷  Bool → Bool → Bool
--

module Prelude.Unicode
    (
    -- * Data structures
      (:×)
    , (×)
    -- * Boolean functions and operators
    , (¬)
    , ()
    , ()
    , ()
    -- * Comparisons
    , ()
    , ()
    , ()
    , ()
    , ()
    , ()
    , ()
    -- * Numbers
    , π
    , (÷)
    , (·)
    -- * Functions
    , ()
    -- * Lists
    , ()
    , ()
    , ()
    -- * Misc
    , ()
    ) where


infixr 4 :×, ×

-- | Pair.
type a :× b = (a, b)

-- | Pair creation. It is not a constructor so can not be used in patterns.
(×)  a  b  a :× b
(×) = (,)

-- | Boolean "not".
(¬)  Bool  Bool
(¬) = not

infixr 3 

-- | Boolean "and".
()  Bool  Bool  Bool
() = (&&)

infixr 2 

-- | Boolean "or".
()  Bool  Bool  Bool
() = (||)

infix 1 

-- | Boolean equality check.
()  Bool  Bool  Bool
() = (==)

infix 4 , , , , , 

-- | Equal.
()  Eq a  a  a  Bool
() = (==)

-- | Not equal.
()  Eq a  a  a  Bool
() = (/=)

-- | Not equal.
()  Eq a  a  a  Bool
() = (/=)

-- | Less or equal.
()  Ord a  a  a  Bool
() = (<=)

-- | Greater or equal.
()  Ord a  a  a  Bool
() = (>=)

-- | Not less.
()  Ord a  a  a  Bool
() = (>=)

-- | Not greater.
()  Ord a  a  a  Bool
() = (<=)

-- | 3.1415..
π  Floating a  a
π = pi

infixl 7 ÷, ·

-- | Division.
(÷)  Fractional a  a  a  a
(÷) = (/)

-- | Multiplication.
(·)  Num a  a  a  a
(·) = (*)

infixr 9 

-- | Function composition.
()  (b  c)  (a  b)  (a  c)
() = (.)

-- | The empty list.
()  [a]
() = []

infix 4 , 

-- | The list membership predicate.
()  Eq a  a  [a]  Bool
() = elem

-- | The negation of the list membership predicate.
()  Eq a  a  [a]  Bool
a  b = not (a  b)

-- | Undefined value.
()  a
() = undefined