hasmtlib-2.8.1: A monad for interfacing with external SMT solvers
Safe HaskellSafe-Inferred
LanguageGHC2021

Language.Hasmtlib.Boolean

Description

This module provides a more generic version of bool-like algebras than what the Prelude does for Bool.

The class Boolean therefore overloads most of the Preludes operators like (&&).

However, as Bool also features an instance of Boolean, you can simply hide the Prelude ones - not having to import either qualified.

Example

Expand
import Prelude hiding (not, any, all, (&&), (||), and, or)
import Language.Hasmtlib

problem :: MonadSMT s m => StateT s m (Expr BoolSort, Expr BoolSort)
problem = do
  x <- var @BoolSort
  y <- var
  let b = False || True
  assert $ x && y <==> and [x, y, true] && encode b ==> x && y
  return (x,y)
Synopsis

Class

class Boolean b where Source #

Minimal complete definition

bool, (&&), (||), not, xor

Methods

bool :: Bool -> b Source #

Lift a Bool.

true :: b Source #

The true constant. true = bool True

false :: b Source #

The false constant. false = bool False

(&&) :: b -> b -> b infixr 3 Source #

Logical conjunction.

(||) :: b -> b -> b infixr 2 Source #

Logical disjunction (inclusive or).

(==>) :: b -> b -> b infixr 0 Source #

Logical implication.

(<==) :: b -> b -> b infixl 0 Source #

Logical implication with arrow reversed.

forall x y. (x ==> y) === (y <== x)

(<==>) :: b -> b -> b infixr 4 Source #

Logical equivalence.

not :: b -> b Source #

Logical negation.

xor :: b -> b -> b infix 4 Source #

Exclusive-or.

Instances

Instances details
Boolean Bit Source # 
Instance details

Defined in Language.Hasmtlib.Boolean

Boolean Bool Source # 
Instance details

Defined in Language.Hasmtlib.Boolean

Boolean (Expr 'BoolSort) Source # 
Instance details

Defined in Language.Hasmtlib.Type.Expr

(KnownBvEnc enc, KnownNat n) => Boolean (Expr ('BvSort enc n)) Source # 
Instance details

Defined in Language.Hasmtlib.Type.Expr

Methods

bool :: Bool -> Expr ('BvSort enc n) Source #

true :: Expr ('BvSort enc n) Source #

false :: Expr ('BvSort enc n) Source #

(&&) :: Expr ('BvSort enc n) -> Expr ('BvSort enc n) -> Expr ('BvSort enc n) Source #

(||) :: Expr ('BvSort enc n) -> Expr ('BvSort enc n) -> Expr ('BvSort enc n) Source #

(==>) :: Expr ('BvSort enc n) -> Expr ('BvSort enc n) -> Expr ('BvSort enc n) Source #

(<==) :: Expr ('BvSort enc n) -> Expr ('BvSort enc n) -> Expr ('BvSort enc n) Source #

(<==>) :: Expr ('BvSort enc n) -> Expr ('BvSort enc n) -> Expr ('BvSort enc n) Source #

not :: Expr ('BvSort enc n) -> Expr ('BvSort enc n) Source #

xor :: Expr ('BvSort enc n) -> Expr ('BvSort enc n) -> Expr ('BvSort enc n) Source #

Boolean (Value 'BoolSort) Source # 
Instance details

Defined in Language.Hasmtlib.Type.Value

KnownNat n => Boolean (Bitvec enc n) Source # 
Instance details

Defined in Language.Hasmtlib.Type.Bitvec

Methods

bool :: Bool -> Bitvec enc n Source #

true :: Bitvec enc n Source #

false :: Bitvec enc n Source #

(&&) :: Bitvec enc n -> Bitvec enc n -> Bitvec enc n Source #

(||) :: Bitvec enc n -> Bitvec enc n -> Bitvec enc n Source #

(==>) :: Bitvec enc n -> Bitvec enc n -> Bitvec enc n Source #

(<==) :: Bitvec enc n -> Bitvec enc n -> Bitvec enc n Source #

(<==>) :: Bitvec enc n -> Bitvec enc n -> Bitvec enc n Source #

not :: Bitvec enc n -> Bitvec enc n Source #

xor :: Bitvec enc n -> Bitvec enc n -> Bitvec enc n Source #

KnownNat n => Boolean (Vector n Bit) Source #

Defined bitwise

Instance details

Defined in Language.Hasmtlib.Boolean

Operators

and :: (Foldable t, Boolean b) => t b -> b Source #

The logical conjunction of several values.

or :: (Foldable t, Boolean b) => t b -> b Source #

The logical disjunction of several values.

nand :: (Foldable t, Boolean b) => t b -> b Source #

The negated logical conjunction of several values.

nand = not . and

nor :: (Foldable t, Boolean b) => t b -> b Source #

The negated logical disjunction of several values.

nor = not . or

all :: (Foldable t, Boolean b) => (a -> b) -> t a -> b Source #

The logical conjunction of the mapping of a function over several values.

any :: (Foldable t, Boolean b) => (a -> b) -> t a -> b Source #

The logical disjunction of the mapping of a function over several values.