netrium-0.6.0: Contract normaliser and simulator

Safe HaskellNone
LanguageHaskell98

Valuation

Contents

Description

Netrium is Copyright Anthony Waite, Dave Hetwett, Shaun Laurens 2009-2015, and files herein are licensed |under the MIT license, the text of which can be found in license.txt

Module for valuation semantics

Synopsis

Value Processes

The basics

newtype PR a Source #

Type for value processes

Constructors

PR 

Fields

Instances

Eq a => Eq (PR a) Source #

To use Equality operations on PR

Methods

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

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

Num a => Num (PR a) Source #

To use Num operations on PR

Methods

(+) :: PR a -> PR a -> PR a #

(-) :: PR a -> PR a -> PR a #

(*) :: PR a -> PR a -> PR a #

negate :: PR a -> PR a #

abs :: PR a -> PR a #

signum :: PR a -> PR a #

fromInteger :: Integer -> PR a #

Ord a => Ord (PR a) Source #

To use Ord operations on PR

Methods

compare :: PR a -> PR a -> Ordering #

(<) :: PR a -> PR a -> Bool #

(<=) :: PR a -> PR a -> Bool #

(>) :: PR a -> PR a -> Bool #

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

max :: PR a -> PR a -> PR a #

min :: PR a -> PR a -> PR a #

Show a => Show (PR a) Source # 

Methods

showsPrec :: Int -> PR a -> ShowS #

show :: PR a -> String #

showList :: [PR a] -> ShowS #

type RV a = [a] Source #

Random variables

Value process helpers

takePr :: Int -> PR a -> PR a Source #

Truncates a (possibly infinite) value process

horizonPr :: PR a -> Int Source #

Determines the number of time steps in a value process. Only terminates for finite value processes

andPr :: PR Bool -> Bool Source #

Returns True if every value in a value process is true, false otherwise. Only terminates for finite value processes.

Value process lifting

liftPr :: (a -> b) -> PR a -> PR b Source #

Lift functions wih a single argument

lift2Pr :: (a -> b -> c) -> PR a -> PR b -> PR c Source #

Lift functions with 2 arguments

lift2PrAll :: (a -> a -> a) -> PR a -> PR a -> PR a Source #

Lift functions for binary operations

lift3Pr :: (a -> b -> c -> d) -> PR a -> PR b -> PR c -> PR d Source #

Lift functions with 3 arguments

zipWithAll :: (a -> a -> a) -> [a] -> [a] -> [a] Source #

A version of zipWith that handles input lists of different lengths

This is used to support lifted binary operations such as (+)

Models

data Model Source #

A model has a start date/time and an exchange rate model

Constructors

Model 

Fields

simpleModel :: Time -> Model Source #

A simple model with a constant exchange rate model

rateModels :: [(Currency, PR Double)] Source #

Each currency has different parameters for the interest rate model. Since the model is not realistic, these parameters are currently entirely arbitrary.

rateModel :: Currency -> PR Double Source #

Function to pick an exchange rate model from the above list

Process primitives

bigK :: a -> PR a Source #

Constant process

konstSlices :: t -> [[t]] Source #

Generate an infinite list

condPr :: PR Bool -> PR a -> PR a -> PR a Source #

Evaluate a condition at date T

disc :: Currency -> (PR Bool, PR Double) -> PR Double Source #

The primitive (disc t k) maps a real-valued random variable at date T, expressed in currency k, to its "fair" equivalent stochastic value process in the same currency k.

A simplifying assumption is that at some point, the boolean-valued process becomes True for an entire RV. This provides a simple termination condition for the discounting process.

absorb :: Currency -> (PR Bool, PR Double) -> PR Double Source #

Given a boolean-valued process o, the primitive absorbk(o,p) transforms the real-valued process p, expressed in currency k, into another real-valued process. For any state, the result is the expected value of receiving p's value if the region o will never be True, and receiving zero in the contrary. In states where o is True, the result is therefore zero

snell :: Currency -> (PR Bool, PR Double) -> PR Double Source #

Not currently implemented. The paper describes the following as a possible algorithm:

  • take the final column of the tree (horizon),
  • discount it back one time step,
  • take the maximum of that column with the corresponding column of the original tree,
  • then repeat that process all the way back to the root.

snellk(o,p) is the smallest process q (under an ordering relation mention briefly at the end of B:4.6) such that:

forall o' . (o => o') => q >= snellk(o',q)

Lattices

Simple calculation

prevSlice :: RV Double -> RV Double Source #

Calculates a previous slice in a lattice by averaging each adjacent pair of values in the specified slice

rates :: Double -> Double -> PR Double Source #

Constructs a lattice containing possible interest rates given a starting rate and an increment per time step. This "unrealistically regular" model matches that shown in B:Fig.8. However, it is so simple that some interest rates go negative after a small number of time steps. A better model is needed for real applications. Don't use this to model your retirement fund!

Probability calculation

probabilityLattice :: [RV Double] Source #

Each node in a value process lattice is associated with a probability.

"...in our very simple setting the number of paths from the root to the node is proportional to the probability that the variable will take that value."

Expected value

expectedValue :: RV Double -> RV Double -> Double Source #

The code for absorb above does not obviously deal with the expected value mentioned in the spec. This is because the expected value of each random variable is implicit in the value process lattice representation: each node in the lattice is associated with a probability, and the expected value at a particular date is simply the sum of the product of the value at each node and its associated probability. The following functions implement this calculation.

Valuation semantics

Valuation semantics for contracts

evalC :: Model -> Currency -> Contract -> PR Double Source #

Evaluate a contract at a given time

Valuation semantics for observables

evalO :: Obs a -> PR a Source #

Evaluate a constant observable

Functions for Graphviz output

latticeImage :: PR Double -> String -> String -> IO ExitCode Source #

This code generates graphs which represent a value process lattice. Currently assumes Double values, constrained by showNode's formatting of the value.

Write out tree as Dot file and run Dot to generate image:

printTree :: PR Double -> IO () Source #

Supports interactive display of generated Dot code.

writeTreeAsDot :: String -> PR Double -> IO () Source #

Write a value process out as a Dot file.

runDot :: String -> String -> IO ExitCode Source #

Run Dot on a file with the specified base name, and generate a graphic file with the specified type.

prToDot :: PR Double -> [String] Source #

Convert a PR Double to a list of dot node relationships.

rvsToDot :: [RV Double] -> [String] Source #

Convert lattice to list of dot node relationships.

assignIds :: [RV a] -> Int -> [RV (Int, a)] Source #

Number each of the nodes in a lattice.

numberList :: [a] -> Int -> [(Int, a)] Source #

showNodes :: [RV (Int, Double)] -> [String] Source #

showNodes returns a list of "primary" Dot representations of numbered RV nodes, with each node's value specified as the node's label. These nodes can then be referenced repeatedly in the generated Dot code without specifying a label.

treeToDot :: [RV (Int, a)] -> [String] Source #

Generate Dot code for relationships between numbered RV nodes.

dotJoin :: RV (Int, a) -> RV (Int, a) -> [String] Source #