Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Language.Hasmtlib.Type.Solution
Synopsis
- type Solver s m = s -> m (Result, Solution)
- data Result
- type Solution = DMap SSMTSort IntValueMap
- newtype IntValueMap t = IntValueMap (IntMap (Value t))
- data SMTVarSol (t :: SMTSort) = SMTVarSol {}
- solVar :: forall t. Lens' (SMTVarSol t) (SMTVar t)
- solVal :: forall t. Lens' (SMTVarSol t) (Value t)
- class Ord (HaskellType t) => OrdHaskellType t
- type SomeKnownOrdSMTSort f = SomeSMTSort '[KnownSMTSort, OrdHaskellType] f
- fromSomeVarSols :: [SomeKnownOrdSMTSort SMTVarSol] -> Solution
Documentation
type Solver s m = s -> m (Result, Solution) Source #
Function that turns a state into a result and a solution.
newtype IntValueMap t Source #
Constructors
IntValueMap (IntMap (Value t)) |
Instances
Monoid (IntValueMap t) Source # | |
Defined in Language.Hasmtlib.Type.Solution Methods mempty :: IntValueMap t # mappend :: IntValueMap t -> IntValueMap t -> IntValueMap t # mconcat :: [IntValueMap t] -> IntValueMap t # | |
Semigroup (IntValueMap t) Source # | |
Defined in Language.Hasmtlib.Type.Solution Methods (<>) :: IntValueMap t -> IntValueMap t -> IntValueMap t # sconcat :: NonEmpty (IntValueMap t) -> IntValueMap t # stimes :: Integral b => b -> IntValueMap t -> IntValueMap t # | |
Show (IntValueMap t) Source # | |
Defined in Language.Hasmtlib.Type.Solution Methods showsPrec :: Int -> IntValueMap t -> ShowS # show :: IntValueMap t -> String # showList :: [IntValueMap t] -> ShowS # |
class Ord (HaskellType t) => OrdHaskellType t Source #
Alias class for constraint Ord
(HaskellType
t)
Instances
Ord (HaskellType t) => OrdHaskellType t Source # | |
Defined in Language.Hasmtlib.Type.Solution |
type SomeKnownOrdSMTSort f = SomeSMTSort '[KnownSMTSort, OrdHaskellType] f Source #
An existential wrapper that hides some known SMTSort
with an Ord
HaskellType