Copyright | (c) Galois Inc 2018-2020 |
---|---|
License | BSD3 |
Maintainer | Rob Dockins <rdockins@galois.com> |
Stability | provisional |
Safe Haskell | None |
Language | Haskell2010 |
This module defines a representation of concrete values of base types. These are values in fully-evaluated form that do not depend on any symbolic constants.
Synopsis
- data ConcreteVal tp where
- ConcreteBool :: Bool -> ConcreteVal BaseBoolType
- ConcreteNat :: Natural -> ConcreteVal BaseNatType
- ConcreteInteger :: Integer -> ConcreteVal BaseIntegerType
- ConcreteReal :: Rational -> ConcreteVal BaseRealType
- ConcreteString :: StringLiteral si -> ConcreteVal (BaseStringType si)
- ConcreteComplex :: Complex Rational -> ConcreteVal BaseComplexType
- ConcreteBV :: 1 <= w => NatRepr w -> BV w -> ConcreteVal (BaseBVType w)
- ConcreteStruct :: Assignment ConcreteVal ctx -> ConcreteVal (BaseStructType ctx)
- ConcreteArray :: Assignment BaseTypeRepr (idx ::> i) -> ConcreteVal b -> Map (Assignment ConcreteVal (idx ::> i)) (ConcreteVal b) -> ConcreteVal (BaseArrayType (idx ::> i) b)
- concreteType :: ConcreteVal tp -> BaseTypeRepr tp
- ppConcrete :: ConcreteVal tp -> Doc
- fromConcreteBool :: ConcreteVal BaseBoolType -> Bool
- fromConcreteNat :: ConcreteVal BaseNatType -> Natural
- fromConcreteInteger :: ConcreteVal BaseIntegerType -> Integer
- fromConcreteReal :: ConcreteVal BaseRealType -> Rational
- fromConcreteString :: ConcreteVal (BaseStringType si) -> StringLiteral si
- fromConcreteBV :: ConcreteVal (BaseBVType w) -> BV w
- fromConcreteComplex :: ConcreteVal BaseComplexType -> Complex Rational
Concrete values
data ConcreteVal tp where Source #
A data type for representing the concrete values of base types.
ConcreteBool :: Bool -> ConcreteVal BaseBoolType | |
ConcreteNat :: Natural -> ConcreteVal BaseNatType | |
ConcreteInteger :: Integer -> ConcreteVal BaseIntegerType | |
ConcreteReal :: Rational -> ConcreteVal BaseRealType | |
ConcreteString :: StringLiteral si -> ConcreteVal (BaseStringType si) | |
ConcreteComplex :: Complex Rational -> ConcreteVal BaseComplexType | |
ConcreteBV :: 1 <= w => NatRepr w -> BV w -> ConcreteVal (BaseBVType w) | |
ConcreteStruct :: Assignment ConcreteVal ctx -> ConcreteVal (BaseStructType ctx) | |
ConcreteArray :: Assignment BaseTypeRepr (idx ::> i) -> ConcreteVal b -> Map (Assignment ConcreteVal (idx ::> i)) (ConcreteVal b) -> ConcreteVal (BaseArrayType (idx ::> i) b) |
Instances
concreteType :: ConcreteVal tp -> BaseTypeRepr tp Source #
Compute the type representative for a concrete value.
ppConcrete :: ConcreteVal tp -> Doc Source #
Pretty-print a concrete value
Concrete projections
fromConcreteString :: ConcreteVal (BaseStringType si) -> StringLiteral si Source #
fromConcreteBV :: ConcreteVal (BaseBVType w) -> BV w Source #