FpMLv53-0.1: A binding for the Financial Products Markup Language (v5.3)

Safe HaskellSafe-Infered

Data.FpML.V53.Riskdef

Synopsis

Documentation

data BasicAssetValuation Source

A structure that holds a set of measures about an asset.

Constructors

BasicAssetValuation 

Fields

basicAssetVal_ID :: Maybe ID
 
basicAssetVal_definitionRef :: Maybe IDREF

An optional reference to the scenario that this valuation applies to.

basicAssetVal_objectReference :: Maybe AnyAssetReference

A reference to the asset or pricing structure that this values.

basicAssetVal_valuationScenarioReference :: Maybe ValuationScenarioReference

A reference to the valuation scenario used to calculate this valuation. If the Valuation occurs within a ValuationSet, this value is optional and is defaulted from the ValuationSet. If this value occurs in both places, the lower level value (i.e. the one here) overrides that in the higher (i.e. ValuationSet).

basicAssetVal_quote :: [BasicQuotation]

One or more numerical measures relating to the asset, possibly together with sensitivities of that measure to pricing inputs

data DenominatorTerm Source

The type defining a denominator term of the formula. Its value is (sum of weighted partials) ^ power.

Constructors

DenominatorTerm 

Fields

denomTerm_weightedPartial :: Maybe WeightedPartialDerivative

A partial derivative multiplied by a weighting factor.

denomTerm_power :: Maybe PositiveInteger

The power to which this term is raised.

data DerivativeCalculationProcedure Source

A description of how a numerical derivative is computed.

Constructors

DerivativeCalculationProcedure 

Fields

derivCalcProced_method :: Maybe DerivativeCalculationMethod

The method by which a derivative is computed, e.g. analytic, numerical model, perturbation, etc.

derivCalcProced_choice1 :: Maybe (OneOf3 (Maybe Decimal, Maybe Boolean, Maybe PerturbationType) XsdString PricingStructureReference)

Choice between:

  1. Sequence of:
  • The size and direction of the perturbation used to compute the derivative, e.g. 0.0001 = 1 bp.
  • The value is calculated by perturbing by the perturbationAmount and then the negative of the perturbationAmount and then averaging the two values (i.e. the value is half of the difference between perturbing up and perturbing down).
  • The type of perturbation, if any, used to compute the derivative (Absolute vs Relative).
  1. The formula used to compute the derivative (perhaps could be updated to use the Formula type in EQS.).
  2. A reference to the replacement version of the market input, e.g. a bumped yield curve.

data DerivativeFormula Source

A formula for computing a complex derivative from partial derivatives. Its value is the sum of the terms divided by the product of the denominator terms.

Constructors

DerivativeFormula 

Fields

derivFormula_term :: Maybe FormulaTerm

A term of the formula. Its value is the product of the its coefficient and the referenced partial derivatives.

derivFormula_denominatorTerm :: Maybe DenominatorTerm

A denominator term of the formula. Its value is (sum of weighted partials) ^ power.

data FormulaTerm Source

A type defining a term of the formula. Its value is the product of the its coefficient and the referenced partial derivatives.

Constructors

FormulaTerm 

Fields

formulaTerm_coefficient :: Maybe Decimal

The coefficient by which this term is multiplied, typically 1 or -1.

formulaTerm_partialDerivativeReference :: [PricingParameterDerivativeReference]

A reference to the partial derivative.

data GenericDimension Source

A generic (user defined) dimension, e.g. for use in a correlation surface. e.g. a currency, stock, etc. This would take values like USD, GBP, JPY, or IBM, MSFT, etc.

data GenericDimensionAttributes Source

Constructors

GenericDimensionAttributes 

Fields

genericDimensAttrib_name :: NormalizedString

The name of the dimension. E.g.: Currency, Stock, Issuer, etc.

genericDimensAttrib_href :: Maybe IDREF

A reference to an instrument (e.g. currency) that this value represents.

data InstrumentSet Source

A collection of instruments usable for quotation purposes. In future releases, quotable derivative assets may be added after the underlying asset.

Constructors

InstrumentSet 

Fields

instrSet_choice0 :: Maybe (OneOf2 Asset Asset)

Choice between:

  1. Define the underlying asset, either a listed security or other instrument.
  2. Defines the underlying asset when it is a curve instrument.

data Market Source

A collection of pricing inputs.

Constructors

Market 

Fields

market_ID :: Maybe ID
 
market_name :: Maybe XsdString

The name of the market, e.g. the USDLIBOR market. Used for description and understandability.

market_benchmarkQuotes :: Maybe QuotedAssetSet

A collection of benchmark instruments and quotes used as inputs to the pricing models.

market_pricingStructure :: [PricingStructure]
 
market_pricingStructureValuation :: [PricingStructureValuation]
 
market_benchmarkPricingMethod :: [PricingMethod]

The pricing structure used to quote a benchmark instrument.

data PerturbationType Source

The type of perturbation applied to compute a derivative perturbatively.

data PositionId Source

A unique identifier for the position. The id attribute is defined for intradocument referencing.

data PricingInputReplacement Source

The substitution of a pricing input (e.g. curve) for another, used in generating prices and risks for valuation scenarios.

Constructors

PricingInputReplacement 

Fields

pricingInputReplac_originalInputReference :: Maybe PricingStructureReference

A reference to the original value of the pricing input.

pricingInputReplac_replacementInputReference :: Maybe PricingStructureReference

A reference to the substitution to do.

data PricingDataPointCoordinate Source

A set of index values that identify a pricing data point. For example: (strike = 17%, expiration = 6M, term = 1Y.

Constructors

PricingDataPointCoordinate 

Fields

pricingDataPointCoord_ID :: Maybe ID
 
pricingDataPointCoord_choice0 :: Maybe (OneOf4 TimeDimension TimeDimension Decimal GenericDimension)

Choice between:

  1. A time dimension that represents the term of a financial instrument, e.g. of a zero-coupon bond on a curve, or of an underlying caplet or swap for an option.
  2. A time dimension that represents the time to expiration of an option.
  3. A numerical dimension that represents the strike rate or price of an option.
  4. generic

data PricingMethod Source

For an asset (e.g. a reference/benchmark asset), the pricing structure used to price it. Used, for example, to specify that the rateIndex USD-LIBOR-Telerate with term = 6M is priced using the USD-LIBOR-Close curve.

Constructors

PricingMethod 

Fields

pricingMethod_assetReference :: Maybe AnyAssetReference

The asset whose price is required.

pricingMethod_pricingInputReference :: Maybe PricingStructureReference

A reference to the pricing input used to value the asset.

data PricingParameterDerivative Source

A definition of the mathematical derivative with respect to a specific pricing parameter.

Constructors

PricingParameterDerivative 

Fields

pricingParamDeriv_ID :: Maybe ID
 
pricingParamDeriv_description :: Maybe XsdString

A description, if needed, of how the derivative is computed.

pricingParamDeriv_choice1 :: Maybe (OneOf2 AssetOrTermPointOrPricingStructureReference [ValuationReference])

Choice between:

  1. A reference to the pricing input parameter to which the sensitivity is computed. If it is omitted, the derivative definition is generic, and applies to any input point in the valuation set.
  2. Reference(s) to the pricing input dates that are shifted when the sensitivity is computed. Depending on the time advance method used, this list could vary. Used for describing time-advance derivatives (theta, carry, etc.)
pricingParamDeriv_calculationProcedure :: Maybe DerivativeCalculationProcedure

The method by which a derivative is computed, e.g. analytic, numerical model, perturbation, etc., and the corresponding parameters

data PricingParameterShift Source

A definition of a shift with respect to a specific pricing parameter.

Constructors

PricingParameterShift 

Fields

pricingParamShift_ID :: Maybe ID
 
pricingParamShift_parameterReference :: Maybe AssetOrTermPointOrPricingStructureReference
 
pricingParamShift_shift :: Maybe Decimal

The size of the denominator, e.g. 0.0001 = 1 bp.

pricingParamShift_shiftUnits :: Maybe PriceQuoteUnits

The units of the denominator, e.g. currency. If not present, use the units of the PricingInputReference.

data PricingStructureValuation Source

An abstract pricing structure valuation base type. Used as a base for values of pricing structures such as yield curves and volatility matrices. Derived from the Valuation type.

Constructors

PricingStructureValuation 

Fields

pricingStructVal_ID :: Maybe ID
 
pricingStructVal_definitionRef :: Maybe IDREF

An optional reference to the scenario that this valuation applies to.

pricingStructVal_objectReference :: Maybe AnyAssetReference

A reference to the asset or pricing structure that this values.

pricingStructVal_valuationScenarioReference :: Maybe ValuationScenarioReference

A reference to the valuation scenario used to calculate this valuation. If the Valuation occurs within a ValuationSet, this value is optional and is defaulted from the ValuationSet. If this value occurs in both places, the lower level value (i.e. the one here) overrides that in the higher (i.e. ValuationSet).

pricingStructVal_baseDate :: Maybe IdentifiedDate

The base date for which the structure applies, i.e. the curve date. Normally this will align with the valuation date.

pricingStructVal_spotDate :: Maybe IdentifiedDate

The spot settlement date for which the structure applies, normally 0-2 days after the base date. The difference between the baseDate and the spotDate is termed the settlement lag, and is sometimes called days to spot.

pricingStructVal_inputDataDate :: Maybe IdentifiedDate

The date from which the input data used to construct the pricing input was obtained. Often the same as the baseDate, but sometimes the pricing input may be rolled forward, in which input data from one date is used to generate a curve for a later date.

pricingStructVal_endDate :: Maybe IdentifiedDate

The last date for which data is supplied in this pricing input.

pricingStructVal_buildDateTime :: Maybe DateTime

The date and time when the pricing input was generated.

data QuotedAssetSet Source

A collection of quoted assets.

Constructors

QuotedAssetSet 

Fields

quotedAssetSet_instrumentSet :: Maybe InstrumentSet

A collection of instruments used as a basis for quotation.

quotedAssetSet_assetQuote :: [BasicAssetValuation]

A collection of valuations (quotes) for the assets needed in the set. Normally these quotes will be for the underlying assets listed above, but they don't necesarily have to be.

data SensitivityDefinition Source

A set of characteristics describing a sensitivity.

Constructors

SensitivityDefinition 

Fields

sensitDefin_ID :: Maybe ID
 
sensitDefin_name :: Maybe XsdString

The name of the derivative, e.g. first derivative, Hessian, etc. Typically not required, but may be used to explain more complex derivative calculations.

sensitDefin_valuationScenarioReference :: Maybe ValuationScenarioReference

Reference to the valuation scenario to which this sensitivity definition applies. If the SensitivityDefinition occurs within a SensitivitySetDefinition, this is not required and normally not used. In this case, if it is supplied it overrides the valuationScenarioReference in the SensitivitySetDefinition.

sensitDefin_choice2 :: OneOf2 ([PricingParameterDerivative], Maybe DerivativeFormula) (OneOf2 TimeDimension (Maybe (OneOf2 PricingDataPointCoordinate PricingDataPointCoordinateReference)))

Choice between:

  1. Sequence of:
  • A partial derivative of the measure with respect to an input.
  • A formula defining how to compute the derivative from the partial derivatives. If absent, the derivative is just the product of the partial derivatives. Normally only required for more higher-order derivatives, e.g. Hessians.
  1. unknown

data SensitivitySetDefinition Source

A sensitivity report definition, consisting of a collection of sensitivity definitions.

Constructors

SensitivitySetDefinition 

Fields

sensitSetDefin_ID :: Maybe ID
 
sensitSetDefin_name :: Maybe XsdString

The name of the sensitivity set definition, e.g. USDLIBOR curve sensitivities.

sensitSetDefin_sensitivityCharacteristics :: Maybe QuotationCharacteristics

The default characteristics of the quotation, e.g. type, units, etc.

sensitSetDefin_valuationScenarioReference :: Maybe ValuationScenarioReference

Reference to the valuation scenario to which this sensitivity definition applies, e.g. a reference to the EOD valuation scenario. If not supplied, this sensitivity set definition is generic to a variety of valuation scenarios.

sensitSetDefin_pricingInputType :: Maybe PricingInputType

The type of the pricing input to which the sensitivity is shown, e.g. a yield curve or volatility matrix.

sensitSetDefin_pricingInputReference :: Maybe PricingStructureReference

A reference to the pricing input to which the sensitivity is shown, e.g. a reference to a USDLIBOR yield curve.

sensitSetDefin_scale :: Maybe Decimal

The size of the denominator, e.g. 0.0001 = 1 bp. For derivatives with respect to time, the default period is 1 day.

sensitSetDefin_sensitivityDefinition :: [SensitivityDefinition]

A set of sensitivity definitions. Either one per point reported, or one generic definition that applies to all points.

sensitSetDefin_calculationProcedure :: Maybe DerivativeCalculationProcedure

The method by which each derivative is computed, e.g. analytic, numerical model, perturbation, etc., and the corresponding parameters (eg. shift amounts).

data TimeDimension Source

The time dimensions of a term-structure. The user must supply either a tenor or a date or both.

Constructors

TimeDimension 

Fields

timeDimens_choice0 :: Maybe (OneOf1 (Maybe Date, Maybe Period))

Choice between:

  1. Sequence of:
  • The absolute date corresponding to this term point, for example January 3, 2005.
  • The amount of time from the base date of the pricing input to the specified term point, e.g. 6M or 5Y.

data Valuation Source

A valuation of an valuable object - an asset or a pricing input. This is an abstract type, used as a base for values of pricing structures such as yield curves as well as asset values.

Constructors

Valuation 

Fields

valuation_ID :: Maybe ID
 
valuation_definitionRef :: Maybe IDREF

An optional reference to the scenario that this valuation applies to.

valuation_objectReference :: Maybe AnyAssetReference

A reference to the asset or pricing structure that this values.

valuation_scenarioReference :: Maybe ValuationScenarioReference

A reference to the valuation scenario used to calculate this valuation. If the Valuation occurs within a ValuationSet, this value is optional and is defaulted from the ValuationSet. If this value occurs in both places, the lower level value (i.e. the one here) overrides that in the higher (i.e. ValuationSet).

data ValuationReference Source

Reference to a Valuation or any derived structure such as PricingStructureValuation.

Constructors

ValuationReference 

Fields

valRef_href :: IDREF
 

data ValuationScenario Source

A set of rules for generating a valuation.

Constructors

ValuationScenario 

Fields

valScenar_ID :: Maybe ID
 
valScenar_name :: Maybe XsdString

The (optional) name for this valuation scenario, used for understandability. For example EOD Valuations.

valScenar_valuationDate :: Maybe IdentifiedDate

The date for which the assets are valued.

valScenar_marketReference :: Maybe MarketReference

A reference to the market environment used to price the asset.

valScenar_shift :: [PricingParameterShift]

A collection of shifts to be applied to market inputs prior to computation of the derivative.

valScenar_replacement :: [PricingInputReplacement]

A collection of shifts to be applied to market inputs prior to computation of the derivative.

data WeightedPartialDerivative Source

A partial derivative multiplied by a weighting factor.

Constructors

WeightedPartialDerivative 

Fields

weightPartialDeriv_partialDerivativeReference :: Maybe PricingParameterDerivativeReference

A reference to a partial derivative defined in the ComputedDerivative.model, i.e. defined as part of this sensitivity definition.

weightPartialDeriv_weight :: Maybe Decimal

The weight factor to be applied to the partial derivative, e.g. 1 or -1, or some other scaling value.

elementMarket :: XMLParser MarketSource

This is a global element used for creating global types. It holds Market information, e.g. curves, surfaces, quotes, etc.