{-# LANGUAGE NoImplicitPrelude, UnicodeSyntax #-}

{-|
Module     : PreludePlus.Unicode
Copyright  : 2018 Joshua Booth
License    : BSD3 (see the file LICENSE)
Maintainer : Joshua Booth <joshua.n.booth@gmail.com>

Various unicode synonyms for basic functions.
-}

module PreludePlus.Unicode
    ( -- * Functional
      ()
    , ()
    , ()
    , (↤∘)
    , (≫=)
    , ()
    , (=≪)
    -- * Boolean
    , ()
    , ()
    -- * Comparison
    , ()
    , ()
    , ()
    , ()
    -- * Arithmetic
    , (÷)
    , (٪)
    , ()
    -- * Collections
    , ()
    , ()
    , ()
    , ()
    , ()
    , ()
    , ø
    ) where

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
------------

-- | '.'
infixr 9 
()  (b  g)  (a  b)  (a  g)
() = (.)
{-# INLINE () #-}

-- | 'flip' . 'fmap'
infixl 6 
()  Functor f  f a  (a  b)  f b
() = flip fmap
{-# INLINE () #-}

-- | 'fmap'
infixl 6 
()  Functor f  (a  b)  f a  f b
() = fmap
{-# INLINE () #-}

-- | 'fmap' '.'
infixr 7 ↤∘
(↤∘)  Functor f  (a  b)  (c  f a)  c  f b
f ↤∘ g = fmap f  g

-- | '>>='
infixl 1 ≫=
(≫=)  Monad m  m a  (a  m b)  m b
(≫=) = (>>=)
{-# INLINE (≫=) #-}

-- | '>>'
infixl 1 
()  Monad m  m a  m b  m b
() = (>>)
{-# INLINE () #-}

-- | '=<<'
infixr 1 =≪
(=≪)  Monad m  (a  m b)  m a  m b
(=≪) = (=<<)
{-# INLINE (=≪) #-}

----------
-- Boolean
----------

-- | '&&'
infixr 2 
()  Bool  Bool  Bool
() = (||)
{-# INLINE () #-}

-- | '||'
infixr 3 
()  Bool  Bool  Bool
() = (&&)
{-# INLINE () #-}

-------------
-- Comparison
-------------

-- | '=='
infix  4 
()  Eq a  a  a  Bool
() = (==)
{-# INLINE () #-}

-- | '≠'
infix  4 
()  Eq a  a  a  Bool
() = (/=)
{-# INLINE () #-}

-- | '<='
infix  4 
()  Ord a  a  a  Bool
() = (<=)
{-# INLINE () #-}

-- | '>='
infix  4 
()  Ord a  a  a  Bool
() = (>=)
{-# INLINE () #-}

-------------
-- Arithmetic
-------------

-- | 'quot'
infixl 7 ÷
(÷)  Integral a  a  a  a
(÷) = quot
{-# INLINE (÷) #-}

-- | 'mod'
infixl 7 ٪
(٪)  Integral a  a  a  a
(٪) = mod
{-# INLINE (٪) #-}

-- | '-' allowing for sections
()  Num a  a  a  a
() = (-)

--------------
-- Collections
--------------

-- | 'elem'
infix  4 
()  (Foldable a, Eq b)  b  a b  Bool
() = elem
{-# INLINE () #-}

-- | 'notElem'
infix 4 
()  (Foldable a, Eq b)  b  a b  Bool
() = notElem
{-# INLINE () #-}

-- | '<>'
infixr 5 
()  Semigroup m  m  m  m
() = (<>)
{-# INLINE () #-}

-- | 'union'
infixl 6 
()  Eq a  [a]  [a]  [a]
() = union
{-# INLINE () #-}

-- | 'intersect'
infixr 6 
()  Eq a  [a]  [a]  [a]
() = intersect

-- | 'not' '.' 'null' '.' 'intersect'
infixr 6 
()  Eq a  [a]  [a]  Bool
() a b = not  null $ intersect a b

-- | 'mempty'
ø  Monoid a  a
ø = mempty