module Hsmtlib.Solvers.Cmd.Parser.Syntax where
data SpecConstant = SpecConstantNumeral Integer
| SpecConstantDecimal String
| SpecConstantHexadecimal String
| SpecConstantBinary String
| SpecConstantString String
deriving (Show)
data Sexpr = SexprSpecConstant SpecConstant
| SexprSymbol String
| SexprKeyword String
| SexprSxp [Sexpr]
deriving (Show)
data Identifier = ISymbol String
| I_Symbol String [String] deriving (Show)
data Sort = SortId Identifier | SortIdentifiers Identifier [Sort]
deriving (Show)
data AttrValue = AttrValueConstant SpecConstant
| AttrValueSymbol String
| AttrValueSexpr [Sexpr]
deriving (Show)
data Attribute = Attribute String
| AttributeVal String AttrValue
deriving (Show)
data QualIdentifier = QIdentifier Identifier
| QIdentifierAs Identifier Sort
deriving (Show)
data VarBinding = VB String Term deriving (Show)
data SortedVar = SV String Sort deriving (Show)
data Term = TermSpecConstant SpecConstant
| TermQualIdentifier QualIdentifier
| TermQualIdentifierT QualIdentifier [Term]
| TermLet [VarBinding] Term
| TermForall [SortedVar] Term
| TermExists [SortedVar] Term
| TermAnnot Term [Attribute]
deriving (Show)
data GenResponse = Unsupported | Success | Error String deriving (Show)
data ErrorBehavior = ImmediateExit | ContinuedExecution deriving (Show)
data ReasonUnknown = Memout | Incomplete deriving (Show)
data CheckSatResponse = Sat | Unsat | Unknown deriving (Show)
type GetInfoResponse = [InfoResponse]
data InfoResponse = ResponseErrorBehavior ErrorBehavior
| ResponseName String
| ResponseAuthors String
| ResponseVersion String
| ResponseReasonUnknown ReasonUnknown
| ResponseAttribute Attribute
deriving (Show)
type GetAssertionsResponse = [Term]
type GetProofResponse = Sexpr
type GetUnsatCoreResponse = [String]
data ValuationPair = ValuationPair Term Term deriving (Show)
type GetValueResponse = [ValuationPair]
data TValuationPair = TValuationPair String Bool deriving (Show)
type GetAssignmentResponse = [TValuationPair]
type GetOptionResponse = AttrValue
data CmdResponse = CmdGenResponse GenResponse
| CmdGetInfoResponse GetInfoResponse
| CmdCheckSatResponse CheckSatResponse
| CmdGetAssertionResponse GetAssignmentResponse
| CmdGetProofResponse GetProofResponse
| CmdGetUnsatCoreResoponse GetUnsatCoreResponse
| CmdGetValueResponse GetValueResponse
| CmdGetAssigmnentResponse TValuationPair
| CmdGetOptionResponse GetOptionResponse
deriving (Show)