ersatz-0.5: A monad for expressing SAT or QSAT problems using observable sharing.
Copyright© Edward Kmett 2010-2014 Johan Kiviniemi 2013
LicenseBSD3
MaintainerEdward Kmett <ekmett@gmail.com>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Ersatz.Equatable

Description

 
Synopsis

Documentation

class Equatable t where Source #

Instances for this class for arbitrary types can be automatically derived from Generic.

Minimal complete definition

Nothing

Methods

(===) :: t -> t -> Bit infix 4 Source #

Compare for equality within the SAT problem.

default (===) :: (Generic t, GEquatable (Rep t)) => t -> t -> Bit Source #

(/==) :: t -> t -> Bit infix 4 Source #

Compare for inequality within the SAT problem.

Instances

Instances details
Equatable Void Source # 
Instance details

Defined in Ersatz.Equatable

Methods

(===) :: Void -> Void -> Bit Source #

(/==) :: Void -> Void -> Bit Source #

Equatable Int16 Source # 
Instance details

Defined in Ersatz.Equatable

Methods

(===) :: Int16 -> Int16 -> Bit Source #

(/==) :: Int16 -> Int16 -> Bit Source #

Equatable Int32 Source # 
Instance details

Defined in Ersatz.Equatable

Methods

(===) :: Int32 -> Int32 -> Bit Source #

(/==) :: Int32 -> Int32 -> Bit Source #

Equatable Int64 Source # 
Instance details

Defined in Ersatz.Equatable

Methods

(===) :: Int64 -> Int64 -> Bit Source #

(/==) :: Int64 -> Int64 -> Bit Source #

Equatable Int8 Source # 
Instance details

Defined in Ersatz.Equatable

Methods

(===) :: Int8 -> Int8 -> Bit Source #

(/==) :: Int8 -> Int8 -> Bit Source #

Equatable Word16 Source # 
Instance details

Defined in Ersatz.Equatable

Equatable Word32 Source # 
Instance details

Defined in Ersatz.Equatable

Equatable Word64 Source # 
Instance details

Defined in Ersatz.Equatable

Equatable Word8 Source # 
Instance details

Defined in Ersatz.Equatable

Methods

(===) :: Word8 -> Word8 -> Bit Source #

(/==) :: Word8 -> Word8 -> Bit Source #

Equatable Bit Source # 
Instance details

Defined in Ersatz.Equatable

Methods

(===) :: Bit -> Bit -> Bit Source #

(/==) :: Bit -> Bit -> Bit Source #

Equatable BitChar Source # 
Instance details

Defined in Ersatz.BitChar

Equatable Bit1 Source # 
Instance details

Defined in Ersatz.Bits

Methods

(===) :: Bit1 -> Bit1 -> Bit Source #

(/==) :: Bit1 -> Bit1 -> Bit Source #

Equatable Bit2 Source # 
Instance details

Defined in Ersatz.Bits

Methods

(===) :: Bit2 -> Bit2 -> Bit Source #

(/==) :: Bit2 -> Bit2 -> Bit Source #

Equatable Bit3 Source # 
Instance details

Defined in Ersatz.Bits

Methods

(===) :: Bit3 -> Bit3 -> Bit Source #

(/==) :: Bit3 -> Bit3 -> Bit Source #

Equatable Bit4 Source # 
Instance details

Defined in Ersatz.Bits

Methods

(===) :: Bit4 -> Bit4 -> Bit Source #

(/==) :: Bit4 -> Bit4 -> Bit Source #

Equatable Bit5 Source # 
Instance details

Defined in Ersatz.Bits

Methods

(===) :: Bit5 -> Bit5 -> Bit Source #

(/==) :: Bit5 -> Bit5 -> Bit Source #

Equatable Bit6 Source # 
Instance details

Defined in Ersatz.Bits

Methods

(===) :: Bit6 -> Bit6 -> Bit Source #

(/==) :: Bit6 -> Bit6 -> Bit Source #

Equatable Bit7 Source # 
Instance details

Defined in Ersatz.Bits

Methods

(===) :: Bit7 -> Bit7 -> Bit Source #

(/==) :: Bit7 -> Bit7 -> Bit Source #

Equatable Bit8 Source # 
Instance details

Defined in Ersatz.Bits

Methods

(===) :: Bit8 -> Bit8 -> Bit Source #

(/==) :: Bit8 -> Bit8 -> Bit Source #

Equatable Bits Source # 
Instance details

Defined in Ersatz.Bits

Methods

(===) :: Bits -> Bits -> Bit Source #

(/==) :: Bits -> Bits -> Bit Source #

Equatable Ordering Source # 
Instance details

Defined in Ersatz.Equatable

Equatable Integer Source # 
Instance details

Defined in Ersatz.Equatable

Equatable Natural Source # 
Instance details

Defined in Ersatz.Equatable

Equatable () Source # 
Instance details

Defined in Ersatz.Equatable

Methods

(===) :: () -> () -> Bit Source #

(/==) :: () -> () -> Bit Source #

Equatable Bool Source # 
Instance details

Defined in Ersatz.Equatable

Methods

(===) :: Bool -> Bool -> Bit Source #

(/==) :: Bool -> Bool -> Bit Source #

Equatable Char Source # 
Instance details

Defined in Ersatz.Equatable

Methods

(===) :: Char -> Char -> Bit Source #

(/==) :: Char -> Char -> Bit Source #

Equatable Double Source # 
Instance details

Defined in Ersatz.Equatable

Equatable Float Source # 
Instance details

Defined in Ersatz.Equatable

Methods

(===) :: Float -> Float -> Bit Source #

(/==) :: Float -> Float -> Bit Source #

Equatable Int Source # 
Instance details

Defined in Ersatz.Equatable

Methods

(===) :: Int -> Int -> Bit Source #

(/==) :: Int -> Int -> Bit Source #

Equatable Word Source # 
Instance details

Defined in Ersatz.Equatable

Methods

(===) :: Word -> Word -> Bit Source #

(/==) :: Word -> Word -> Bit Source #

Equatable v => Equatable (IntMap v) Source # 
Instance details

Defined in Ersatz.Equatable

Methods

(===) :: IntMap v -> IntMap v -> Bit Source #

(/==) :: IntMap v -> IntMap v -> Bit Source #

Equatable v => Equatable (Seq v) Source # 
Instance details

Defined in Ersatz.Equatable

Methods

(===) :: Seq v -> Seq v -> Bit Source #

(/==) :: Seq v -> Seq v -> Bit Source #

Equatable a => Equatable (Tree a) Source # 
Instance details

Defined in Ersatz.Equatable

Methods

(===) :: Tree a -> Tree a -> Bit Source #

(/==) :: Tree a -> Tree a -> Bit Source #

Equatable a => Equatable (NonEmpty a) Source # 
Instance details

Defined in Ersatz.Equatable

Methods

(===) :: NonEmpty a -> NonEmpty a -> Bit Source #

(/==) :: NonEmpty a -> NonEmpty a -> Bit Source #

Equatable a => Equatable (Maybe a) Source # 
Instance details

Defined in Ersatz.Equatable

Methods

(===) :: Maybe a -> Maybe a -> Bit Source #

(/==) :: Maybe a -> Maybe a -> Bit Source #

Equatable a => Equatable [a] Source # 
Instance details

Defined in Ersatz.Equatable

Methods

(===) :: [a] -> [a] -> Bit Source #

(/==) :: [a] -> [a] -> Bit Source #

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

Defined in Ersatz.Equatable

Methods

(===) :: Either a b -> Either a b -> Bit Source #

(/==) :: Either a b -> Either a b -> Bit Source #

(Eq k, Equatable v) => Equatable (Map k v) Source # 
Instance details

Defined in Ersatz.Equatable

Methods

(===) :: Map k v -> Map k v -> Bit Source #

(/==) :: Map k v -> Map k v -> Bit Source #

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

Defined in Ersatz.Equatable

Methods

(===) :: (a, b) -> (a, b) -> Bit Source #

(/==) :: (a, b) -> (a, b) -> Bit Source #

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

Defined in Ersatz.Equatable

Methods

(===) :: (a, b, c) -> (a, b, c) -> Bit Source #

(/==) :: (a, b, c) -> (a, b, c) -> Bit Source #

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

Defined in Ersatz.Equatable

Methods

(===) :: (a, b, c, d) -> (a, b, c, d) -> Bit Source #

(/==) :: (a, b, c, d) -> (a, b, c, d) -> Bit Source #

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

Defined in Ersatz.Equatable

Methods

(===) :: (a, b, c, d, e) -> (a, b, c, d, e) -> Bit Source #

(/==) :: (a, b, c, d, e) -> (a, b, c, d, e) -> Bit Source #

(Equatable a, Equatable b, Equatable c, Equatable d, Equatable e, Equatable f) => Equatable (a, b, c, d, e, f) Source # 
Instance details

Defined in Ersatz.Equatable

Methods

(===) :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> Bit Source #

(/==) :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> Bit Source #

(Equatable a, Equatable b, Equatable c, Equatable d, Equatable e, Equatable f, Equatable g) => Equatable (a, b, c, d, e, f, g) Source # 
Instance details

Defined in Ersatz.Equatable

Methods

(===) :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> Bit Source #

(/==) :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> Bit Source #

class GEquatable f where Source #

Methods

(===#) :: f a -> f a -> Bit Source #

Instances

Instances details
GEquatable (U1 :: Type -> Type) Source # 
Instance details

Defined in Ersatz.Equatable

Methods

(===#) :: U1 a -> U1 a -> Bit Source #

GEquatable (V1 :: Type -> Type) Source # 
Instance details

Defined in Ersatz.Equatable

Methods

(===#) :: V1 a -> V1 a -> Bit Source #

(GEquatable f, GEquatable g) => GEquatable (f :*: g) Source # 
Instance details

Defined in Ersatz.Equatable

Methods

(===#) :: (f :*: g) a -> (f :*: g) a -> Bit Source #

(GEquatable f, GEquatable g) => GEquatable (f :+: g) Source # 
Instance details

Defined in Ersatz.Equatable

Methods

(===#) :: (f :+: g) a -> (f :+: g) a -> Bit Source #

Equatable a => GEquatable (K1 i a :: Type -> Type) Source # 
Instance details

Defined in Ersatz.Equatable

Methods

(===#) :: K1 i a a0 -> K1 i a a0 -> Bit Source #

GEquatable f => GEquatable (M1 i c f) Source # 
Instance details

Defined in Ersatz.Equatable

Methods

(===#) :: M1 i c f a -> M1 i c f a -> Bit Source #