ersatz-0.4.13: 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.Orderable

Description

 
Synopsis

Documentation

class Equatable t => Orderable 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 less-than within the SAT problem.

default (<?) :: (Generic t, GOrderable (Rep t)) => t -> t -> Bit Source #

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

Compare for less-than or equal-to within the SAT problem.

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

Compare for greater-than or equal-to within the SAT problem.

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

Compare for greater-than within the SAT problem.

Instances

Instances details
Orderable Void Source # 
Instance details

Defined in Ersatz.Orderable

Methods

(<?) :: Void -> Void -> Bit Source #

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

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

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

Orderable Int16 Source # 
Instance details

Defined in Ersatz.Orderable

Orderable Int32 Source # 
Instance details

Defined in Ersatz.Orderable

Orderable Int64 Source # 
Instance details

Defined in Ersatz.Orderable

Orderable Int8 Source # 
Instance details

Defined in Ersatz.Orderable

Methods

(<?) :: Int8 -> Int8 -> Bit Source #

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

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

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

Orderable Word16 Source # 
Instance details

Defined in Ersatz.Orderable

Orderable Word32 Source # 
Instance details

Defined in Ersatz.Orderable

Orderable Word64 Source # 
Instance details

Defined in Ersatz.Orderable

Orderable Word8 Source # 
Instance details

Defined in Ersatz.Orderable

Orderable Bit Source # 
Instance details

Defined in Ersatz.Orderable

Methods

(<?) :: Bit -> Bit -> Bit Source #

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

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

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

Orderable BitChar Source # 
Instance details

Defined in Ersatz.BitChar

Orderable Bit1 Source # 
Instance details

Defined in Ersatz.Bits

Methods

(<?) :: Bit1 -> Bit1 -> Bit Source #

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

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

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

Orderable Bit2 Source # 
Instance details

Defined in Ersatz.Bits

Methods

(<?) :: Bit2 -> Bit2 -> Bit Source #

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

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

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

Orderable Bit3 Source # 
Instance details

Defined in Ersatz.Bits

Methods

(<?) :: Bit3 -> Bit3 -> Bit Source #

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

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

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

Orderable Bit4 Source # 
Instance details

Defined in Ersatz.Bits

Methods

(<?) :: Bit4 -> Bit4 -> Bit Source #

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

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

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

Orderable Bit5 Source # 
Instance details

Defined in Ersatz.Bits

Methods

(<?) :: Bit5 -> Bit5 -> Bit Source #

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

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

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

Orderable Bit6 Source # 
Instance details

Defined in Ersatz.Bits

Methods

(<?) :: Bit6 -> Bit6 -> Bit Source #

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

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

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

Orderable Bit7 Source # 
Instance details

Defined in Ersatz.Bits

Methods

(<?) :: Bit7 -> Bit7 -> Bit Source #

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

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

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

Orderable Bit8 Source # 
Instance details

Defined in Ersatz.Bits

Methods

(<?) :: Bit8 -> Bit8 -> Bit Source #

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

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

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

Orderable Bits Source # 
Instance details

Defined in Ersatz.Bits

Methods

(<?) :: Bits -> Bits -> Bit Source #

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

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

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

Orderable Ordering Source # 
Instance details

Defined in Ersatz.Orderable

Orderable Integer Source # 
Instance details

Defined in Ersatz.Orderable

Orderable Natural Source # 
Instance details

Defined in Ersatz.Orderable

Orderable () Source # 
Instance details

Defined in Ersatz.Orderable

Methods

(<?) :: () -> () -> Bit Source #

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

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

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

Orderable Bool Source # 
Instance details

Defined in Ersatz.Orderable

Methods

(<?) :: Bool -> Bool -> Bit Source #

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

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

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

Orderable Char Source # 
Instance details

Defined in Ersatz.Orderable

Methods

(<?) :: Char -> Char -> Bit Source #

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

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

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

Orderable Double Source # 
Instance details

Defined in Ersatz.Orderable

Orderable Float Source # 
Instance details

Defined in Ersatz.Orderable

Orderable Int Source # 
Instance details

Defined in Ersatz.Orderable

Methods

(<?) :: Int -> Int -> Bit Source #

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

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

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

Orderable Word Source # 
Instance details

Defined in Ersatz.Orderable

Methods

(<?) :: Word -> Word -> Bit Source #

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

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

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

Orderable v => Orderable (IntMap v) Source #

Compare by lexicographic order on sorted key-value pairs

Instance details

Defined in Ersatz.Orderable

Methods

(<?) :: IntMap v -> IntMap v -> Bit Source #

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

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

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

Orderable v => Orderable (Seq v) Source #

Compare by lexicographic order on elements

Instance details

Defined in Ersatz.Orderable

Methods

(<?) :: Seq v -> Seq v -> Bit Source #

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

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

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

Orderable a => Orderable (Tree a) Source #

Compare by lexicographic order on: root node, list of children

Instance details

Defined in Ersatz.Orderable

Methods

(<?) :: Tree a -> Tree a -> Bit Source #

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

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

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

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

Defined in Ersatz.Orderable

Methods

(<?) :: Maybe a -> Maybe a -> Bit Source #

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

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

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

Orderable a => Orderable [a] Source #

Lexicographic order

Instance details

Defined in Ersatz.Orderable

Methods

(<?) :: [a] -> [a] -> Bit Source #

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

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

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

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

Defined in Ersatz.Orderable

Methods

(<?) :: Either a b -> Either a b -> Bit Source #

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

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

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

(Ord k, Orderable v) => Orderable (Map k v) Source #

Compare by lexicographic order on sorted key-value pairs

Instance details

Defined in Ersatz.Orderable

Methods

(<?) :: Map k v -> Map k v -> Bit Source #

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

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

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

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

Defined in Ersatz.Orderable

Methods

(<?) :: (a, b) -> (a, b) -> Bit Source #

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

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

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

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

Defined in Ersatz.Orderable

Methods

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

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

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

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

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

Defined in Ersatz.Orderable

Methods

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

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

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

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

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

Defined in Ersatz.Orderable

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 #

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

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

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

Defined in Ersatz.Orderable

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 #

(>=?) :: (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 #

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

Defined in Ersatz.Orderable

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 #

(>=?) :: (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 => GOrderable f where Source #

Methods

(<?#) :: f a -> f a -> Bit Source #

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

Instances

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

Defined in Ersatz.Orderable

Methods

(<?#) :: U1 a -> U1 a -> Bit Source #

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

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

Defined in Ersatz.Orderable

Methods

(<?#) :: V1 a -> V1 a -> Bit Source #

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

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

Defined in Ersatz.Orderable

Methods

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

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

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

Defined in Ersatz.Orderable

Methods

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

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

Orderable a => GOrderable (K1 i a :: Type -> Type) Source # 
Instance details

Defined in Ersatz.Orderable

Methods

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

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

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

Defined in Ersatz.Orderable

Methods

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

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