Safe Haskell | None |
---|---|
Language | Haskell2010 |
Exposes type for reasoning about adversaries. Generally speaking, a
Functionality
may request interfaces from an Adversary
, which need to be
supplied for it to run. The adversary also exposes some power to the
environment to arbitrarily control these interfaces. Functionalities should
be aware that the adversary may respond with anything correctly typed, and
is explicitly permitted to returning Nothing
. WithAdversary'
provides
an interface to repair unacceptable responses before the functionality
itself is called.
Synopsis
- type Adversary s c as bs = Functionality s c (as +|+ MaybeMap bs)
- type family MaybeMap (bs :: [(*, *)]) = (ys :: [(*, *)]) | ys -> bs where ...
- data WithAdversary s (ts :: [(*, *)]) b
- data WithAdversary' s c (as :: [(*, *)]) (bs :: [(*, *)]) = WithAdversary' (HList (Interfaces s (MaybeMap as)) -> HList (Operations s c as)) (HList (Operations s c as) -> Functionality s c bs)
- class NoAdversary s (bs :: [(*, *)]) where
- type family DummyInterfaces s (xs :: [(*, *)]) = (ys :: [*]) | ys -> xs where ...
- class DummyAdversary s (bs :: [(*, *)]) where
- class CreateAdversarial s c as bs adv b where
Documentation
type Adversary s c as bs = Functionality s c (as +|+ MaybeMap bs) Source #
An adversary is a functionality that exposes some interfaces to the
environment, and some interfaces returning Maybe
s to some other party.
type family MaybeMap (bs :: [(*, *)]) = (ys :: [(*, *)]) | ys -> bs where ... Source #
Maps a list of '(in, out)
type tuples to '(in,
.Maybe
out)
data WithAdversary s (ts :: [(*, *)]) b Source #
Allows construction of b
given a list of interfaces ts
from the
adversary. The adversarial interfaces return Maybe
s on all interfaces.
Instances
CreateAdversarial s c as bs (WithAdversary s bs b) b Source # | |
Defined in Yggdrasil.Adversarial createAdversarial :: Adversary s c as bs -> WithAdversary s bs b -> Action s (HList (Interfaces s as), b) Source # |
data WithAdversary' s c (as :: [(*, *)]) (bs :: [(*, *)]) Source #
Allows construction of a Functionality
with state c
and interface bs
whjen given a list of interfaces as
from the adversary. The adversarial
interface is corrected, by passing it through a filter ensuring valid
responses.
WithAdversary' (HList (Interfaces s (MaybeMap as)) -> HList (Operations s c as)) (HList (Operations s c as) -> Functionality s c bs) |
Instances
CreateAdversarial s c as bs (WithAdversary' s c bs cs) (Functionality s c cs) Source # | |
Defined in Yggdrasil.Adversarial createAdversarial :: Adversary s c as bs -> WithAdversary' s c bs cs -> Action s (HList (Interfaces s as), Functionality s c cs) Source # |
class NoAdversary s (bs :: [(*, *)]) where Source #
The empty adversary returns Nothing
.
nullOperations :: HList (Operations s () (MaybeMap bs)) Source #
noAdversary :: Adversary s () '[] bs Source #
Instances
NoAdversary s ([] :: [(*, *)]) Source # | |
Defined in Yggdrasil.Adversarial nullOperations :: HList (Operations s () (MaybeMap [])) Source # noAdversary :: Adversary s () [] [] Source # | |
NoAdversary s xs => NoAdversary s ((,) a b ': xs) Source # | |
Defined in Yggdrasil.Adversarial nullOperations :: HList (Operations s () (MaybeMap ((a, b) ': xs))) Source # noAdversary :: Adversary s () [] ((a, b) ': xs) Source # |
type family DummyInterfaces s (xs :: [(*, *)]) = (ys :: [*]) | ys -> xs where ... Source #
Closely corresponding to Interfaces
, but also receiving a reference to
the original sender.
DummyInterfaces s '[] = '[] | |
DummyInterfaces s ('(a, b) ': xs) = (Ref s -> a -> Action s b) ': DummyInterfaces s xs |
class DummyAdversary s (bs :: [(*, *)]) where Source #
A dummy adversary executes the interfaces the environments hands it.
operations :: HList (DummyInterfaces s (MaybeMap bs)) -> HList (Operations s () (MaybeMap bs)) Source #
dummyAdversary :: HList (DummyInterfaces s (MaybeMap bs)) -> Adversary s () '[] bs Source #
Instances
DummyAdversary s ([] :: [(*, *)]) Source # | |
Defined in Yggdrasil.Adversarial operations :: HList (DummyInterfaces s (MaybeMap [])) -> HList (Operations s () (MaybeMap [])) Source # dummyAdversary :: HList (DummyInterfaces s (MaybeMap [])) -> Adversary s () [] [] Source # | |
DummyAdversary s bs => DummyAdversary s ((,) a b ': bs) Source # | |
Defined in Yggdrasil.Adversarial operations :: HList (DummyInterfaces s (MaybeMap ((a, b) ': bs))) -> HList (Operations s () (MaybeMap ((a, b) ': bs))) Source # dummyAdversary :: HList (DummyInterfaces s (MaybeMap ((a, b) ': bs))) -> Adversary s () [] ((a, b) ': bs) Source # |
class CreateAdversarial s c as bs adv b where Source #
Creates an adversarial functionality given a suitable adversary.
createAdversarial :: (HSplit (Interfaces s (as +|+ MaybeMap bs)) (Interfaces s as) (Interfaces s (MaybeMap bs)), InterfaceMap s c (as +|+ MaybeMap bs)) => Adversary s c as bs -> adv -> Action s (HList (Interfaces s as), b) Source #
Instances
CreateAdversarial s c as bs (WithAdversary s bs b) b Source # | |
Defined in Yggdrasil.Adversarial createAdversarial :: Adversary s c as bs -> WithAdversary s bs b -> Action s (HList (Interfaces s as), b) Source # | |
CreateAdversarial s c as bs (WithAdversary' s c bs cs) (Functionality s c cs) Source # | |
Defined in Yggdrasil.Adversarial createAdversarial :: Adversary s c as bs -> WithAdversary' s c bs cs -> Action s (HList (Interfaces s as), Functionality s c cs) Source # |