deltaq-1.0.0.0: Framework for ∆Q System Development
CopyrightPredictable Network Solutions Ltd. 2003-2024
LicenseBSD-3-Clause
Safe HaskellSafe-Inferred
LanguageHaskell2010

DeltaQ.Class

Description

Type classes

  • Outcome — outcomes their combinations.
  • DeltaQ — probability distributions of completion times.
Synopsis

Type classes

Outcome

class (Ord (Duration o), Num (Duration o)) => Outcome o where Source #

An Outcome is the result of an activity that takes time, such as a distributed computation, communication, bus ride, … .

Outcomes can be composed in sequence or in parallel.

Minimal complete definition

never, wait, sequentially, firstToFinish, lastToFinish

Associated Types

type Duration o Source #

Numerical type representing times in \( [0,+∞) \).

For example Double or Rational.

Methods

never :: o Source #

The outcome that never finishes.

wait :: Duration o -> o Source #

The outcome that succeeds after waiting for a fixed amount of time.

sequentially :: o -> o -> o Source #

Sequential composition:

First run the outcome on the left, then run the outcome on the right.

(.>>.) :: o -> o -> o infixl 1 Source #

Infix operator synonym for sequentially.

firstToFinish :: o -> o -> o Source #

Parallel composition, first to finish:

Run two outcomes in parallel, finish as soon as any one of them finishes.

(.\/.) :: o -> o -> o infixr 2 Source #

Infix operator synonym for firstToFinish.

lastToFinish :: o -> o -> o Source #

Parallel composiiton, last to finish:

Run two outcomes in parallel, finish after all of them have finished.

(./\.) :: o -> o -> o infixr 3 Source #

Infix operator synonym for lastToFinish.

Instances

Instances details
Outcome DQ Source # 
Instance details

Defined in DeltaQ.PiecewisePolynomial

Associated Types

type Duration DQ Source #

DeltaQ

data Eventually a Source #

Eventually represents a value that either eventually occurs or is eventually abandoned.

Similar to the Maybe type, but with a different Ord instance: Occurs x < Abandoned for all x.

Constructors

Occurs a 
Abandoned 

Instances

Instances details
Applicative Eventually Source #
Abandoned <*> _ = Abandoned
_ <*> Abandoned = Abandoned
Instance details

Defined in DeltaQ.Class

Methods

pure :: a -> Eventually a #

(<*>) :: Eventually (a -> b) -> Eventually a -> Eventually b #

liftA2 :: (a -> b -> c) -> Eventually a -> Eventually b -> Eventually c #

(*>) :: Eventually a -> Eventually b -> Eventually b #

(<*) :: Eventually a -> Eventually b -> Eventually a #

Functor Eventually Source # 
Instance details

Defined in DeltaQ.Class

Methods

fmap :: (a -> b) -> Eventually a -> Eventually b #

(<$) :: a -> Eventually b -> Eventually a #

Show a => Show (Eventually a) Source # 
Instance details

Defined in DeltaQ.Class

Eq a => Eq (Eventually a) Source # 
Instance details

Defined in DeltaQ.Class

Methods

(==) :: Eventually a -> Eventually a -> Bool #

(/=) :: Eventually a -> Eventually a -> Bool #

Ord a => Ord (Eventually a) Source #

For all x, we have Occurs x < Abandoned.

Instance details

Defined in DeltaQ.Class

eventually :: b -> (a -> b) -> Eventually a -> b Source #

Helper function to eliminate Eventually.

See also: maybe.

eventuallyFromMaybe :: Maybe a -> Eventually a Source #

Helper function that converts Maybe to Eventually.

maybeFromEventually :: Eventually a -> Maybe a Source #

Helper function that converts Eventually to Maybe.

class (Ord (Probability o), Enum (Probability o), Num (Probability o), Fractional (Probability o), Outcome o) => DeltaQ o where Source #

DeltaQ — quality attenuation.

DeltaQ is a probability distribution of time.

Specifically, DeltaQ is the probability distribution of finish times for an outcome.

Minimal complete definition

choice, uniform, failure, successWithin, quantile, earliest, deadline

Associated Types

type Probability o Source #

Numerical type representing probabilities in \( [0,1] \).

For example Double or Rational.

Methods

choice :: Probability o -> o -> o -> o Source #

Left-biased random choice.

choice p chooses the left argument with probablity p and the right argument with probability (1-p).

choices :: [(Probability o, o)] -> o Source #

Random choice between multiple alternatives

choices [(w_1, o_1), (w_2, o_2), …] chooses randomly between multiple outcomes. The probability p_i for choosing the outcome o_i is determined by the weights as p_i = w_i / (w_1 + w_2 + …).

uniform :: Duration o -> Duration o -> o Source #

Uniform probability distribution on a time interval.

failure :: o -> Probability o Source #

Probability of not finishing.

successWithin :: o -> Duration o -> Probability o Source #

Probability of finishing within the given time t.

"Within" is inclusive, i.e. this returns the probability that the finishing time is <= t.

quantile :: o -> Probability o -> Eventually (Duration o) Source #

Given a probability p, return the smallest time t such that the probability of completing within that time is at least p.

Return Abandoned if the given probability exceeds the probability of finishing.

earliest :: o -> Eventually (Duration o) Source #

The earliest finish time with non-zero probability.

Return Abandoned if the outcome is never.

deadline :: o -> Eventually (Duration o) Source #

The last finish time which still has non-zero probability to occur.

Return Abandoned if arbitrarily late times are possible.

Properties

All instances of the above type classes are expected to satisfy the following properties.

For instances that use approximate arithmetic such as floating point arithmetic or fixed precision arithmetic, equality may be up to numerical accuracy.

Outcome

never

never .>>. y = never
never ./\. y = never
never .\/. y = y

x .>>. never = never
x ./\. never = never
x .\/. never = x

wait

wait t .>>. wait s  =  wait (t+s)
wait t ./\. wait s  =  wait (max t s)
wait t .\/. wait s  =  wait (min t s)

(.>>.)

(x .>>. y) .>>. z  =  x .>>. (y .>>. z)

(./\.)

(x ./\. y) ./\. z  =  x ./\. (y ./\. z)

x ./\. y  =  y ./\. x

(.\/.)

(x .\/. y) .\/. z  =  x .\/. (y .\/. z)

x .\/. y  =  y .\/. x

DeltaQ

choice

choice 1 x y = x
choice 0 x y = y

choice p x y .>>. z  =  choice p (x .>>. z) (y .>>. z)
choice p x y ./\. z  =  choice p (x ./\. z) (y ./\. z)
choice p x y .\/. z  =  choice p (x .\/. z) (y .\/. z)

choices

choices [] = never
choices ((w,o) : wos) = choice p o (choices wos)
  where  p = w / (w + sum (map fst wos))

uniform

wait t .>>. uniform r s  =  uniform (t+r) (t+s)
uniform r s .>>. wait t  =  uniform (r+t) (s+t)

failure

failure never      = 1
failure (wait t)   = 0
failure (x .>>. y) = 1 - (1 - failure x) * (1 - failure y)
failure (x ./\. y) = 1 - (1 - failure x) * (1 - failure y)
failure (x .\/. y) = failure x * failure y

failure (choice p x y) = p * failure x + (1-p) * failure y
failure (uniform r s)  = 0

successWithin

successWithin never    t = 0
successWithin (wait s) t = if t < s then 0 else 1

successWithin (x ./\. y) t =
  successWithin t x * successWithin t y
successWithin (x .\/. y) t =
  1 - (1 - successWithin t x) * (1 - successWithin t y)

successWithin (choice p x y) t =
  p * successWithin t x + (1-p) * successWithin t y
successWithin (uniform r s) t
  | t < r           = 0
  | r <= t && t < s = (t-r) / (s-r)
  | s <= t          = 1

quantile

p <= q  implies  quantile o p <= quantile o q

quantile x        0 = Occurs 0
quantile never    p = Abandoned       if p > 0
quantile (wait t) p = Occurs t        if p > 0

quantile (uniform r s) p  =  r + p*(s-t)  if p > 0, r <= s

earliest

earliest never      = Abandoned
earliest (wait t)   = Occurs t
earliest (x .>>. y) = (+) <$> earliest x <*> earliest y
earliest (x ./\. y) = max (earliest x) (earliest y)
earliest (x .\/. y) = min (earliest x) (earliest y)

earliest (choice p x y) = min (earliest x) (earliest y)  if p ≠ 0, p ≠ 1
earliest (uniform r s)  = Occurs r   if r <= s

deadline

deadline never      =  Abandoned
deadline (wait t)   =  Occurs t
deadline (x .>>. y) =  (+) <$> deadline x <*> deadline y
deadline (x ./\. y) =  max (deadline x) (deadline y)

deadline (x .\/. y) =  min (deadline x) (deadline y)
  if failure x = 0, failure y = 0

deadline (choice p x y) = max (deadline x) (deadline y)
  if p ≠ 0, p ≠ 1, failure x = 0, failure y = 0


deadline (uniform r s)  = Occurs s   if r <= s