linear-base-0.1.0: Standard library for linear types.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Ord.Linear.Internal.Eq

Description

This module provides a linear Eq class for testing equality between values, along with standard instances.

Synopsis

Documentation

class Eq a where Source #

Testing equality on values.

The laws are that (==) and (/=) are compatible and (==) is an equivalence relation. So, for all x, y, z,

  • x == x always
  • x == y implies y == x
  • x == y and y == z implies x == z
  • (x == y)not (x /= y)

Minimal complete definition

(==) | (/=)

Methods

(==) :: a %1 -> a %1 -> Bool infix 4 Source #

(/=) :: a %1 -> a %1 -> Bool infix 4 Source #

Instances

Instances details
Eq Bool Source # 
Instance details

Defined in Data.Ord.Linear.Internal.Eq

Methods

(==) :: Bool %1 -> Bool %1 -> Bool Source #

(/=) :: Bool %1 -> Bool %1 -> Bool Source #

Eq Char Source # 
Instance details

Defined in Data.Ord.Linear.Internal.Eq

Methods

(==) :: Char %1 -> Char %1 -> Bool Source #

(/=) :: Char %1 -> Char %1 -> Bool Source #

Eq Double Source # 
Instance details

Defined in Data.Ord.Linear.Internal.Eq

Methods

(==) :: Double %1 -> Double %1 -> Bool Source #

(/=) :: Double %1 -> Double %1 -> Bool Source #

Eq Int Source # 
Instance details

Defined in Data.Ord.Linear.Internal.Eq

Methods

(==) :: Int %1 -> Int %1 -> Bool Source #

(/=) :: Int %1 -> Int %1 -> Bool Source #

Eq Ordering Source # 
Instance details

Defined in Data.Ord.Linear.Internal.Eq

Methods

(==) :: Ordering %1 -> Ordering %1 -> Bool Source #

(/=) :: Ordering %1 -> Ordering %1 -> Bool Source #

Eq () Source # 
Instance details

Defined in Data.Ord.Linear.Internal.Eq

Methods

(==) :: () %1 -> () %1 -> Bool Source #

(/=) :: () %1 -> () %1 -> Bool Source #

(Consumable a, Eq a) => Eq [a] Source # 
Instance details

Defined in Data.Ord.Linear.Internal.Eq

Methods

(==) :: [a] %1 -> [a] %1 -> Bool Source #

(/=) :: [a] %1 -> [a] %1 -> Bool Source #

(Consumable a, Eq a) => Eq (Maybe a) Source # 
Instance details

Defined in Data.Ord.Linear.Internal.Eq

Methods

(==) :: Maybe a %1 -> Maybe a %1 -> Bool Source #

(/=) :: Maybe a %1 -> Maybe a %1 -> Bool Source #

Eq a => Eq (Ur a) Source # 
Instance details

Defined in Data.Ord.Linear.Internal.Eq

Methods

(==) :: Ur a %1 -> Ur a %1 -> Bool Source #

(/=) :: Ur a %1 -> Ur a %1 -> Bool Source #

(Consumable a, Consumable b, Eq a, Eq b) => Eq (Either a b) Source # 
Instance details

Defined in Data.Ord.Linear.Internal.Eq

Methods

(==) :: Either a b %1 -> Either a b %1 -> Bool Source #

(/=) :: Either a b %1 -> Either a b %1 -> Bool Source #

(Eq a, Eq b) => Eq (a, b) Source # 
Instance details

Defined in Data.Ord.Linear.Internal.Eq

Methods

(==) :: (a, b) %1 -> (a, b) %1 -> Bool Source #

(/=) :: (a, b) %1 -> (a, b) %1 -> Bool Source #

(Eq a, Eq b, Eq c) => Eq (a, b, c) Source # 
Instance details

Defined in Data.Ord.Linear.Internal.Eq

Methods

(==) :: (a, b, c) %1 -> (a, b, c) %1 -> Bool Source #

(/=) :: (a, b, c) %1 -> (a, b, c) %1 -> Bool Source #

(Eq a, Eq b, Eq c, Eq d) => Eq (a, b, c, d) Source # 
Instance details

Defined in Data.Ord.Linear.Internal.Eq

Methods

(==) :: (a, b, c, d) %1 -> (a, b, c, d) %1 -> Bool Source #

(/=) :: (a, b, c, d) %1 -> (a, b, c, d) %1 -> Bool Source #