unicode-prelude-0.1: Unicode notation for some definitions in Prelude

Portabilityunknown
Stabilityalpha
Maintainerdivip@aszt.inf.elte.hu

Prelude.Unicode

Contents

Description

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  [xx | x[1..10], x2]    Bool
 foldl (flip (:)) ()    [a]  [a]
 (\a  a  a  a)    a  a : a : a
 (\a b  ()(a  b)  ()a  ()b)    Bool  Bool  Bool

Synopsis

Data structures

type a b = (a, b)Source

Pair.

(×) :: a -> b -> a bSource

Pair creation. It is not a constructor so can not be used in patterns.

Boolean functions and operators

(¬) :: Bool -> BoolSource

Boolean not.

(∧) :: Bool -> Bool -> BoolSource

Boolean and.

(∨) :: Bool -> Bool -> BoolSource

Boolean or.

(⇔) :: Bool -> Bool -> BoolSource

Boolean equality check.

Comparisons

(≡) :: Eq a => a -> a -> BoolSource

Equal.

(≠) :: Eq a => a -> a -> BoolSource

Not equal.

(≢) :: Eq a => a -> a -> BoolSource

Not equal.

(≤) :: Ord a => a -> a -> BoolSource

Less or equal.

(≥) :: Ord a => a -> a -> BoolSource

Greater or equal.

(≮) :: Ord a => a -> a -> BoolSource

Not less.

(≯) :: Ord a => a -> a -> BoolSource

Not greater.

Numbers

π :: Floating a => aSource

  1. 1415..

(÷) :: Fractional a => a -> a -> aSource

Division.

· :: Num a => a -> a -> aSource

Multiplication.

Functions

(◦) :: (b -> c) -> (a -> b) -> a -> cSource

Function composition.

Lists

(∅) :: [a]Source

The empty list.

(∈) :: Eq a => a -> [a] -> BoolSource

The list membership predicate.

(∉) :: Eq a => a -> [a] -> BoolSource

The negation of the list membership predicate.

Misc

(⊥) :: aSource

Undefined value.