Copyright | (c) Erich Gut |
---|---|
License | BSD3 |
Maintainer | zerich.gut@gmail.com |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Statements on properties which can be validated via validateStoch
. They serve to
implement automatic testing (see OAlg.Control.Validate).
Examples Deterministic
Validation of the valid and invalid statement
>>>
getOmega >>= validateStoch SValid 10
Valid
>>>
getOmega >>= validateStoch SInvalid 5
Invalid
As no stochastic was used to evaluate the two examples, the result is Valid
and Invalid
respectively!
Examples Stochastic
Validation of a Forall
and Exist
statement
>>>
getOmega >>= validateStoch (Forall (xIntB 0 10) (\i -> (0 <= i && i <= 10):?>Params["i":=show i]-- )) 100
ProbablyValid
>>>
getOmega >>= validateStoch (Exist (xIntB 0 10) (\i -> (11 <= i):?>Params["i":=show i])) 100
ProbablyInvalid
The valuation of these two examples uses the given Omega
and Wide
of 100
to pick randomly
100
samples of the given random variable
and applies these samples to the given
test function. The result is xIntB
0 10ProbablyValid
and ProbablyInvalid
respectively!
Synopsis
- data Statement where
- SInvalid :: Statement
- SValid :: Statement
- (:?>) :: Bool -> Message -> Statement
- Catch :: Exception e => Statement -> (e -> Statement) -> Statement
- Not :: Statement -> Statement
- (:&&) :: Statement -> Statement -> Statement
- And :: [Statement] -> Statement
- (:||) :: Statement -> Statement -> Statement
- Or :: [Statement] -> Statement
- (:=>) :: Statement -> Statement -> Statement
- Impl :: [Statement] -> Statement -> Statement
- (:<=>:) :: Label -> Statement -> Statement
- (:<=>) :: Statement -> Statement -> Statement
- Eqvl :: [Statement] -> Statement
- Forall :: X x -> (x -> Statement) -> Statement
- Exist :: X x -> (x -> Statement) -> Statement
- (.==.) :: Eq a => a -> a -> Statement
- (./=.) :: Eq a => a -> a -> Statement
- (|~>) :: Statement -> Statement -> Statement
- someException :: Statement -> SomeException -> Statement
- data Label
- data Message
- type Variable = String
- data Parameter where
- validateStoch :: Statement -> Wide -> Omega -> IO Valid
- type Wide = Int
- value :: Statement -> Wide -> Omega -> IO V
- data V
- valDeterministic :: V -> Bool
- valT :: V -> T
- type T = HNFValue Valid
- data Valid
- showV :: Indent -> V -> String
- indent0 :: String -> Indent
- showVStatement :: Wide -> Statement -> IO ()
- validateDet :: Statement -> Bool
- tests :: V -> [(Int, SPath)]
- type SPath = [String]
- cntTests :: V -> Int
- rdcTrue :: V -> Maybe V
- cntTestsRdcTrue :: V -> Int
- rdcFalse :: V -> Maybe V
- cntTestsRdcFalse :: V -> Int
- rdcDndPrms :: V -> Maybe V
- cntTestsRdcDndPrms :: V -> Int
- rdcFailed :: V -> Maybe V
- cntTestsRdcFailed :: V -> Int
- xValue :: Statement -> X (Wide, Omega) -> X (IO V)
- xWO :: Wide -> Wide -> X (Wide, Omega)
- xValid :: X Valid
- data ValidateingException = NonDeterministic
Statement
statement on properties..
SInvalid :: Statement | the invalid statement. |
SValid :: Statement | the valid statement. |
(:?>) :: Bool -> Message -> Statement infix 4 | checking a boolean. |
Catch :: Exception e => Statement -> (e -> Statement) -> Statement | catching an exception. |
Not :: Statement -> Statement | not |
(:&&) :: Statement -> Statement -> Statement infixr 3 | and |
And :: [Statement] -> Statement | and |
(:||) :: Statement -> Statement -> Statement infixr 2 | or |
Or :: [Statement] -> Statement | or |
(:=>) :: Statement -> Statement -> Statement infixr 1 | implication |
Impl :: [Statement] -> Statement -> Statement | implication |
(:<=>:) :: Label -> Statement -> Statement infixr 0 | efinitional equivalence |
(:<=>) :: Statement -> Statement -> Statement infixr 1 | equivalence |
Eqvl :: [Statement] -> Statement | equivalence |
Forall :: X x -> (x -> Statement) -> Statement | the for all constructor |
Exist :: X x -> (x -> Statement) -> Statement | the exist constructor. |
Instances
HNFData Statement Source # | |
Defined in OAlg.Data.Statement.Definition | |
Boolean Statement Source # | |
Defined in OAlg.Data.Statement.Definition not :: Statement -> Statement Source # (||) :: Statement -> Statement -> Statement Source # or :: [Statement] -> Statement Source # (&&) :: Statement -> Statement -> Statement Source # and :: [Statement] -> Statement Source # (~>) :: Statement -> Statement -> Statement Source # |
(|~>) :: Statement -> Statement -> Statement infixr 1 Source #
implication without resulting in denied premises for a false
premises. This
is useful for switch cases.
someException :: Statement -> SomeException -> Statement Source #
convenient catcher for SomeException
.
a labels.
a message.
showing the involved parameters of a statement.
Validating
Stochastic
validateStoch :: Statement -> Wide -> Omega -> IO Valid Source #
validates the statement according to a given Wide
and Omega
. For
deterministic statements better use validateDet
and for non deterministic
or to get more information validate
.
value :: Statement -> Wide -> Omega -> IO V Source #
evaluates the value of a statement according a given Wide
and Omega
.
Note
- The only reason to valuate a statement in the
IO
monad is to be able to catch exceptions. Other interactions with the real world during the valuation are not performed. - During the evaluation process the given wide and omega will not be changed and as such all same random variables will produce exactly the same samples. This restricts the stochastic, but it is necessary for the sound behavior of the validation of statements.
valDeterministic :: V -> Bool Source #
determines whether the value is deterministic, i.e. dose not contain a VForall
or VExist
constructor.
weak form of classical boolean values arising from stochastically performed valuation
of Statement
s.
Definition Let a
, b
be in Valid
, then we define:
Note min
and max
are implemented lazy as Valid
is bounded. This
is important that ~>
behaves as desired, i.e. for a
and ~>
ba =
then
Invalid
b
has not to be evaluated, because the maximum is already reached..
Instances
Bounded Valid Source # | |
Enum Valid Source # | |
Defined in OAlg.Data.Statement.Definition | |
Show Valid Source # | |
NFData Valid Source # | |
Defined in OAlg.Data.Statement.Definition | |
Eq Valid Source # | |
Ord Valid Source # | |
Boolean Valid Source # | |
Validable Valid Source # | |
Projectible Bool Valid Source # | |
Deterministic
validateDet :: Statement -> Bool Source #
validation for deterministic statements.
Definition A statement s is called deterministic if and only if it dose not depend on the stochastic nor on the state of the machine.
Examples
>>>
validateDet SValid
True
>>>
validateDet (Forall xBool (\_ -> SValid))
*** Exception: NonDeterministic
>>>
validateDet (SValid || Exist xInt (\i -> (i==0):?>MInvalid))
True
Reducing Values
tests :: V -> [(Int, SPath)] Source #
the list of all relevant tests - i.e 'VDedEqvl l _
where l =
- together with the number of tests.Label
_
cntTestsRdcTrue :: V -> Int Source #
cntTestsRdcFalse :: V -> Int Source #
rdcDndPrms :: V -> Maybe V Source #
reduces ture values - having implications with no conclusions, i.e. denied premises - to its relevant part.
cntTestsRdcDndPrms :: V -> Int Source #
number of tests
for values containing denied premises. Note Before counting
the tests they will be first reduced to there relevant part (see rdcDndPrms
).
cntTestsRdcFailed :: V -> Int Source #
X
xWO :: Wide -> Wide -> X (Wide, Omega) Source #
xWO l h
is the random variable over wide and omgea, where the wide is bounded between l
and
h
.
Exception
data ValidateingException Source #
validating exceptions which are sub exceptions from SomeOAlgException
.
Instances
Exception ValidateingException Source # | |
Show ValidateingException Source # | |
Defined in OAlg.Data.Statement.Definition showsPrec :: Int -> ValidateingException -> ShowS # show :: ValidateingException -> String # showList :: [ValidateingException] -> ShowS # | |
Eq ValidateingException Source # | |
Defined in OAlg.Data.Statement.Definition (==) :: ValidateingException -> ValidateingException -> Bool # (/=) :: ValidateingException -> ValidateingException -> Bool # |