{-# LANGUAGE GADTs #-}
module What4.Expr.AppTheory
( AppTheory(..)
, quantTheory
, appTheory
, typeTheory
) where
import What4.BaseTypes
import What4.Expr.Builder
import qualified What4.SemiRing as SR
import qualified What4.Expr.WeightedSum as WSum
data AppTheory
= BoolTheory
| LinearArithTheory
| NonlinearArithTheory
| ComputableArithTheory
| BitvectorTheory
| QuantifierTheory
| StringTheory
| FloatingPointTheory
| ArrayTheory
| StructTheory
| FnTheory
deriving (Eq, Ord)
quantTheory :: NonceApp t (Expr t) tp -> AppTheory
quantTheory a0 =
case a0 of
Annotation tpr _ _ -> typeTheory tpr
Forall{} -> QuantifierTheory
Exists{} -> QuantifierTheory
ArrayFromFn{} -> FnTheory
MapOverArrays{} -> ArrayTheory
ArrayTrueOnEntries{} -> ArrayTheory
FnApp{} -> FnTheory
typeTheory :: BaseTypeRepr tp -> AppTheory
typeTheory tp = case tp of
BaseBoolRepr -> BoolTheory
BaseBVRepr _ -> BitvectorTheory
BaseNatRepr -> LinearArithTheory
BaseIntegerRepr -> LinearArithTheory
BaseRealRepr -> LinearArithTheory
BaseFloatRepr _ -> FloatingPointTheory
BaseStringRepr{} -> StringTheory
BaseComplexRepr -> LinearArithTheory
BaseStructRepr _ -> StructTheory
BaseArrayRepr _ _ -> ArrayTheory
appTheory :: App (Expr t) tp -> AppTheory
appTheory a0 =
case a0 of
BaseIte tp _ _ _ _ -> typeTheory tp
BaseEq tp _ _ -> typeTheory tp
NotPred{} -> BoolTheory
ConjPred{} -> BoolTheory
RealIsInteger{} -> LinearArithTheory
BVTestBit{} -> BitvectorTheory
BVSlt{} -> BitvectorTheory
BVUlt{} -> BitvectorTheory
BVOrBits{} -> BitvectorTheory
SemiRingProd pd ->
case WSum.prodRepr pd of
SR.SemiRingBVRepr _ _ -> BitvectorTheory
SR.SemiRingNatRepr -> NonlinearArithTheory
SR.SemiRingIntegerRepr -> NonlinearArithTheory
SR.SemiRingRealRepr -> NonlinearArithTheory
SemiRingSum sm ->
case WSum.sumRepr sm of
SR.SemiRingBVRepr _ _ -> BitvectorTheory
SR.SemiRingNatRepr -> LinearArithTheory
SR.SemiRingIntegerRepr -> LinearArithTheory
SR.SemiRingRealRepr -> LinearArithTheory
SemiRingLe{} -> LinearArithTheory
NatDiv _ SemiRingLiteral{} -> LinearArithTheory
NatDiv{} -> NonlinearArithTheory
NatMod _ SemiRingLiteral{} -> LinearArithTheory
NatMod{} -> NonlinearArithTheory
IntMod _ SemiRingLiteral{} -> LinearArithTheory
IntMod{} -> NonlinearArithTheory
IntDiv _ SemiRingLiteral{} -> LinearArithTheory
IntDiv{} -> NonlinearArithTheory
IntAbs{} -> LinearArithTheory
IntDivisible{} -> LinearArithTheory
RealDiv{} -> NonlinearArithTheory
RealSqrt{} -> NonlinearArithTheory
Pi -> ComputableArithTheory
RealSin{} -> ComputableArithTheory
RealCos{} -> ComputableArithTheory
RealATan2{} -> ComputableArithTheory
RealSinh{} -> ComputableArithTheory
RealCosh{} -> ComputableArithTheory
RealExp{} -> ComputableArithTheory
RealLog{} -> ComputableArithTheory
BVUnaryTerm{} -> BoolTheory
BVConcat{} -> BitvectorTheory
BVSelect{} -> BitvectorTheory
BVUdiv{} -> BitvectorTheory
BVUrem{} -> BitvectorTheory
BVSdiv{} -> BitvectorTheory
BVSrem{} -> BitvectorTheory
BVShl{} -> BitvectorTheory
BVLshr{} -> BitvectorTheory
BVRol{} -> BitvectorTheory
BVRor{} -> BitvectorTheory
BVAshr{} -> BitvectorTheory
BVZext{} -> BitvectorTheory
BVSext{} -> BitvectorTheory
BVPopcount{} -> BitvectorTheory
BVCountLeadingZeros{} -> BitvectorTheory
BVCountTrailingZeros{} -> BitvectorTheory
BVFill{} -> BitvectorTheory
FloatPZero{} -> FloatingPointTheory
FloatNZero{} -> FloatingPointTheory
FloatNaN{} -> FloatingPointTheory
FloatPInf{} -> FloatingPointTheory
FloatNInf{} -> FloatingPointTheory
FloatNeg{} -> FloatingPointTheory
FloatAbs{} -> FloatingPointTheory
FloatSqrt{} -> FloatingPointTheory
FloatAdd{} -> FloatingPointTheory
FloatSub{} -> FloatingPointTheory
FloatMul{} -> FloatingPointTheory
FloatDiv{} -> FloatingPointTheory
FloatRem{} -> FloatingPointTheory
FloatMin{} -> FloatingPointTheory
FloatMax{} -> FloatingPointTheory
FloatFMA{} -> FloatingPointTheory
FloatFpEq{} -> FloatingPointTheory
FloatFpNe{} -> FloatingPointTheory
FloatLe{} -> FloatingPointTheory
FloatLt{} -> FloatingPointTheory
FloatIsNaN{} -> FloatingPointTheory
FloatIsInf{} -> FloatingPointTheory
FloatIsZero{} -> FloatingPointTheory
FloatIsPos{} -> FloatingPointTheory
FloatIsNeg{} -> FloatingPointTheory
FloatIsSubnorm{} -> FloatingPointTheory
FloatIsNorm{} -> FloatingPointTheory
FloatCast{} -> FloatingPointTheory
FloatRound{} -> FloatingPointTheory
FloatFromBinary{} -> FloatingPointTheory
FloatToBinary{} -> FloatingPointTheory
BVToFloat{} -> FloatingPointTheory
SBVToFloat{} -> FloatingPointTheory
RealToFloat{} -> FloatingPointTheory
FloatToBV{} -> FloatingPointTheory
FloatToSBV{} -> FloatingPointTheory
FloatToReal{} -> FloatingPointTheory
NatToInteger{} -> LinearArithTheory
IntegerToReal{} -> LinearArithTheory
BVToNat{} -> LinearArithTheory
BVToInteger{} -> LinearArithTheory
SBVToInteger{} -> LinearArithTheory
RoundReal{} -> LinearArithTheory
RoundEvenReal{} -> LinearArithTheory
FloorReal{} -> LinearArithTheory
CeilReal{} -> LinearArithTheory
RealToInteger{} -> LinearArithTheory
IntegerToNat{} -> LinearArithTheory
IntegerToBV{} -> BitvectorTheory
ArrayMap{} -> ArrayTheory
ConstantArray{} -> ArrayTheory
SelectArray{} -> ArrayTheory
UpdateArray{} -> ArrayTheory
StringAppend{} -> StringTheory
StringLength{} -> StringTheory
StringContains{} -> StringTheory
StringIndexOf{} -> StringTheory
StringIsPrefixOf{} -> StringTheory
StringIsSuffixOf{} -> StringTheory
StringSubstring{} -> StringTheory
Cplx{} -> LinearArithTheory
RealPart{} -> LinearArithTheory
ImagPart{} -> LinearArithTheory
StructCtor{} -> StructTheory
StructField{} -> StructTheory