| Copyright | (c) The University of Glasgow 2005 |
|---|---|
| License | BSD-style (see the file libraries/base/LICENSE) |
| Maintainer | libraries@haskell.org |
| Stability | stable |
| Portability | portable |
| Safe Haskell | Trustworthy |
| Language | Haskell2010 |
Data.Eq
Description
Equality
Documentation
The Eq class defines equality (== ) and inequality (/= ).
All the basic datatypes exported by the Prelude are instances of Eq ,
and Eq may be derived for any datatype whose constituents are also
instances of Eq .
The Haskell Report defines no laws for Eq . However, instances are
encouraged to follow these properties:
Instances
Instances details
Instance details
Defined in Data.Typeable.Internal
Methods
(==) :: SomeTypeRep -> SomeTypeRep -> Bool Source #
(/=) :: SomeTypeRep -> SomeTypeRep -> Bool Source #
Instance details
Defined in Foreign.C.Types
Methods
(==) :: CSUSeconds -> CSUSeconds -> Bool Source #
(/=) :: CSUSeconds -> CSUSeconds -> Bool Source #
Instance details
Defined in Foreign.C.Types
Methods
(==) :: CSigAtomic -> CSigAtomic -> Bool Source #
(/=) :: CSigAtomic -> CSigAtomic -> Bool Source #
Instance details
Defined in GHC.Conc.Sync
Methods
(==) :: BlockReason -> BlockReason -> Bool Source #
(/=) :: BlockReason -> BlockReason -> Bool Source #
Instance details
Defined in GHC.Conc.Sync
Methods
(==) :: ThreadStatus -> ThreadStatus -> Bool Source #
(/=) :: ThreadStatus -> ThreadStatus -> Bool Source #
Instance details
Defined in GHC.Event.TimeOut
Methods
(==) :: TimeoutKey -> TimeoutKey -> Bool Source #
(/=) :: TimeoutKey -> TimeoutKey -> Bool Source #
Instance details
Defined in GHC.Exception.Type
Methods
(==) :: ArithException -> ArithException -> Bool Source #
(/=) :: ArithException -> ArithException -> Bool Source #
Instance details
Defined in GHC.Exts
Methods
(==) :: SpecConstrAnnotation -> SpecConstrAnnotation -> Bool Source #
(/=) :: SpecConstrAnnotation -> SpecConstrAnnotation -> Bool Source #
Instance details
Defined in GHC.Fingerprint.Type
Methods
(==) :: Fingerprint -> Fingerprint -> Bool Source #
(/=) :: Fingerprint -> Fingerprint -> Bool Source #
Instance details
Defined in GHC.Generics
Methods
(==) :: Associativity -> Associativity -> Bool Source #
(/=) :: Associativity -> Associativity -> Bool Source #
Instance details
Defined in GHC.Generics
Methods
(==) :: DecidedStrictness -> DecidedStrictness -> Bool Source #
(/=) :: DecidedStrictness -> DecidedStrictness -> Bool Source #
Instance details
Defined in GHC.Generics
Methods
(==) :: SourceStrictness -> SourceStrictness -> Bool Source #
(/=) :: SourceStrictness -> SourceStrictness -> Bool Source #
Instance details
Defined in GHC.Generics
Methods
(==) :: SourceUnpackedness -> SourceUnpackedness -> Bool Source #
(/=) :: SourceUnpackedness -> SourceUnpackedness -> Bool Source #
Instance details
Defined in GHC.IO
Methods
(==) :: MaskingState -> MaskingState -> Bool Source #
(/=) :: MaskingState -> MaskingState -> Bool Source #
Instance details
Defined in GHC.IO.Buffer
Methods
(==) :: BufferState -> BufferState -> Bool Source #
(/=) :: BufferState -> BufferState -> Bool Source #
Instance details
Defined in GHC.IO.Device
Methods
(==) :: IODeviceType -> IODeviceType -> Bool Source #
(/=) :: IODeviceType -> IODeviceType -> Bool Source #
Instance details
Defined in GHC.IO.Encoding.Types
Methods
(==) :: CodingProgress -> CodingProgress -> Bool Source #
(/=) :: CodingProgress -> CodingProgress -> Bool Source #
Instance details
Defined in GHC.IO.Exception
Methods
(==) :: ArrayException -> ArrayException -> Bool Source #
(/=) :: ArrayException -> ArrayException -> Bool Source #
Instance details
Defined in GHC.IO.Exception
Methods
(==) :: AsyncException -> AsyncException -> Bool Source #
(/=) :: AsyncException -> AsyncException -> Bool Source #
Instance details
Defined in GHC.IO.Exception
Methods
(==) :: IOErrorType -> IOErrorType -> Bool Source #
(/=) :: IOErrorType -> IOErrorType -> Bool Source #
Instance details
Defined in GHC.IO.Exception
Methods
(==) :: IOException -> IOException -> Bool Source #
(/=) :: IOException -> IOException -> Bool Source #
Instance details
Defined in GHC.IO.Handle
Methods
(==) :: HandlePosn -> HandlePosn -> Bool Source #
(/=) :: HandlePosn -> HandlePosn -> Bool Source #
Instance details
Defined in GHC.IO.Handle.Types
Methods
(==) :: BufferMode -> BufferMode -> Bool Source #
(/=) :: BufferMode -> BufferMode -> Bool Source #
Instance details
Defined in GHC.IO.Handle.Types
Methods
(==) :: NewlineMode -> NewlineMode -> Bool Source #
(/=) :: NewlineMode -> NewlineMode -> Bool Source #
Instance details
Defined in GHC.RTS.Flags
Methods
(==) :: IoSubSystem -> IoSubSystem -> Bool Source #
(/=) :: IoSubSystem -> IoSubSystem -> Bool Source #
Instance details
Defined in GHC.Stack.CloneStack
Methods
(==) :: StackEntry -> StackEntry -> Bool Source #
(/=) :: StackEntry -> StackEntry -> Bool Source #
Instance details
Defined in GHC.TypeLits
Methods
(==) :: SomeSymbol -> SomeSymbol -> Bool Source #
(/=) :: SomeSymbol -> SomeSymbol -> Bool Source #
Instance details
Defined in GHC.Unicode
Methods
(==) :: GeneralCategory -> GeneralCategory -> Bool Source #
(/=) :: GeneralCategory -> GeneralCategory -> Bool Source #
Note that due to the presence of NaN, Double 's Eq instance does not
satisfy reflexivity.
>>>0/0 == (0/0 :: Double)False
Also note that Double 's Eq instance does not satisfy substitutivity:
>>>0 == (-0 :: Double)True>>>recip 0 == recip (-0 :: Double)False
Note that due to the presence of NaN, Float 's Eq instance does not
satisfy reflexivity.
>>>0/0 == (0/0 :: Float)False
Also note that Float 's Eq instance does not satisfy extensionality:
>>>0 == (-0 :: Float)True>>>recip 0 == recip (-0 :: Float)False
Instance details
Defined in Data.Array.Byte
Methods
(==) :: MutableByteArray s -> MutableByteArray s -> Bool Source #
(/=) :: MutableByteArray s -> MutableByteArray s -> Bool Source #
Instance details
Defined in Data.Semigroup
Methods
(==) :: WrappedMonoid m -> WrappedMonoid m -> Bool Source #
(/=) :: WrappedMonoid m -> WrappedMonoid m -> Bool Source #
Instance details
Defined in GHC.ForeignPtr
Methods
(==) :: ForeignPtr a -> ForeignPtr a -> Bool Source #
(/=) :: ForeignPtr a -> ForeignPtr a -> Bool Source #
Instance details
Defined in GHC.StableName
Methods
(==) :: StableName a -> StableName a -> Bool Source #
(/=) :: StableName a -> StableName a -> Bool Source #
Instance details
Defined in GHC.Generics
Methods
(==) :: Generically1 f a -> Generically1 f a -> Bool Source #
(/=) :: Generically1 f a -> Generically1 f a -> Bool Source #