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

Safe HaskellSafe-Infered

Data.FpML.V53.IRD

Synopsis

Documentation

data BondReference Source

A type including a reference to a bond to support the representation of an asset swap or Condition Precedent Bond.

Constructors

BondReference 

Fields

bondRef_bond :: Maybe Bond

Identifies the underlying asset when it is a series or a class of bonds.

bondRef_conditionPrecedentBond :: Maybe Boolean

To indicate whether the Condition Precedent Bond is applicable. The swap contract is only valid if the bond is issued and if there is any dispute over the terms of fixed stream then the bond terms would be used.

bondRef_discrepancyClause :: Maybe Boolean

To indicate whether the Discrepancy Clause is applicable.

data BulletPayment Source

A product to represent a single cashflow.

Constructors

BulletPayment 

Fields

bulletPayment_ID :: Maybe ID
 
bulletPayment_primaryAssetClass :: Maybe AssetClass

A classification of the most important risk class of the trade. FpML defines a simple asset class categorization using a coding scheme.

bulletPayment_secondaryAssetClass :: [AssetClass]

A classification of additional risk classes of the trade, if any. FpML defines a simple asset class categorization using a coding scheme.

bulletPayment_productType :: [ProductType]

A classification of the type of product. FpML defines a simple product categorization using a coding scheme.

bulletPayment_productId :: [ProductId]

A product reference identifier. The product ID is an identifier that describes the key economic characteristics of the trade type, with the exception of concepts such as size (notional, quantity, number of units) and price (fixed rate, strike, etc.) that are negotiated for each transaction. It can be used to hold identifiers such as the UPI (universal product identifier) required by certain regulatory reporting rules. It can also be used to hold identifiers of benchmark products or product temnplates used by certain trading systems or facilities. FpML does not define the domain values associated with this element. Note that the domain values for this element are not strictly an enumerated list.

bulletPayment_payment :: Maybe Payment

A known payment between two parties.

data Calculation Source

A type definining the parameters used in the calculation of fixed or floating calculation period amounts.

Constructors

Calculation 

Fields

calculation_choice0 :: OneOf2 Notional FxLinkedNotionalSchedule

Choice between:

  1. The notional amount or notional amount schedule.
  2. A notional amount schedule where each notional that applied to a calculation period is calculated with reference to a notional amount or notional amount schedule in a different currency by means of a spot currency exchange rate which is normally observed at the beginning of each period.
calculation_choice1 :: OneOf2 (Schedule, Maybe FutureValueAmount) Rate

Choice between:

  1. Sequence of:
  • The fixed rate or fixed rate schedule expressed as explicit fixed rates and dates. In the case of a schedule, the step dates may be subject to adjustment in accordance with any adjustments specified in calculationPeriodDatesAdjustments.
  • The future value notional is normally only required for BRL CDI Swaps. The value is calculated as follows: Future Value Notional = Notional Amount * (1 + Fixed Rate) ^ (Fixed Rate Day Count Fraction). The currency should always match that expressed in the notional schedule. The value date should match the adjusted termination date.
  1. The base element for the floating rate calculation definitions.
calculation_dayCountFraction :: DayCountFraction

The day count fraction.

calculation_discounting :: Maybe Discounting

The parameters specifying any discounting conventions that may apply. This element must only be included if discounting applies.

calculation_compoundingMethod :: Maybe CompoundingMethodEnum

If more that one calculation period contributes to a single payment amount this element specifies whether compounding is applicable, and if so, what compounding method is to be used. This element must only be included when more that one calculation period contributes to a single payment amount.

data CalculationPeriod Source

A type defining the parameters used in the calculation of a fixed or floating rate calculation period amount. This type forms part of cashflows representation of a swap stream.

Constructors

CalculationPeriod 

Fields

calcPeriod_ID :: Maybe ID
 
calcPeriod_unadjustedStartDate :: Maybe Date
 
calcPeriod_unadjustedEndDate :: Maybe Date
 
calcPeriod_adjustedStartDate :: Maybe Date

The calculation period start date, adjusted according to any relevant business day convention.

calcPeriod_adjustedEndDate :: Maybe Date

The calculation period end date, adjusted according to any relevant business day convention.

calculationPeriod_numberOfDays :: Maybe PositiveInteger

The number of days from the adjusted effective / start date to the adjusted termination / end date calculated in accordance with the applicable day count fraction.

calcPeriod_choice5 :: Maybe (OneOf2 Decimal FxLinkedNotionalAmount)

Choice between:

  1. The amount that a cashflow will accrue interest on.
  2. The amount that a cashflow will accrue interest on. This is the calculated amount of the fx linked - ie the other currency notional amount multiplied by the appropriate fx spot rate.
calcPeriod_choice6 :: Maybe (OneOf2 FloatingRateDefinition Decimal)

Choice between:

  1. The floating rate reset information for the calculation period.
  2. The calculation period fixed rate. A per annum rate, expressed as a decimal. A fixed rate of 5% would be represented as 0.05.
calcPeriod_dayCountYearFraction :: Maybe Decimal

The year fraction value of the calculation period, result of applying the ISDA rules for day count fraction defined in the ISDA Annex.

calcPeriod_forecastAmount :: Maybe Money

The amount representing the forecast of the accrued value of the calculation period. An intermediate value used to generate the forecastPaymentAmount in the PaymentCalculationPeriod.

calcPeriod_forecastRate :: Maybe Decimal

A value representing the forecast rate used to calculate the forecast future value of the accrual period. This is a calculated rate determined based on averaging the rates in the rateObservation elements, and incorporates all of the rate treatment and averaging rules. A value of 1% should be represented as 0.01

data CalculationPeriodAmount Source

A type defining the parameters used in the calculation of fixed or floating rate calculation period amounts or for specifying a known calculation period amount or known amount schedule.

Constructors

CalculationPeriodAmount 

Fields

calcPeriodAmount_choice0 :: OneOf2 Calculation AmountSchedule

Choice between:

  1. The parameters used in the calculation of fixed or floaring rate calculation period amounts.
  2. The known calculation period amount or a known amount schedule expressed as explicit known amounts and dates. In the case of a schedule, the step dates may be subject to adjustment in accordance with any adjustments specified in calculationPeriodDatesAdjustments.

data CalculationPeriodDates Source

A type defining the parameters used to generate the calculation period dates schedule, including the specification of any initial or final stub calculation periods. A calculation perod schedule consists of an optional initial stub calculation period, one or more regular calculation periods and an optional final stub calculation period. In the absence of any initial or final stub calculation periods, the regular part of the calculation period schedule is assumed to be between the effective date and the termination date. No implicit stubs are allowed, i.e. stubs must be explicitly specified using an appropriate combination of firstPeriodStateDate, firstRegularPeriodStartDate and lastRegularPeriodEndDate.

Constructors

CalculationPeriodDates 

Fields

calcPeriodDates_ID :: Maybe ID
 
calcPeriodDates_choice0 :: OneOf2 AdjustableDate AdjustedRelativeDateOffset

Choice between:

  1. The first day of the term of the trade. This day may be subject to adjustment in accordance with a business day convention.
  2. Defines the effective date.
calcPeriodDates_choice1 :: OneOf2 AdjustableDate RelativeDateOffset

Choice between:

  1. The last day of the term of the trade. This day may be subject to adjustment in accordance with a business day convention.
  2. The term/maturity of the swap, express as a tenor (typically in years).
calculationPeriodDates_adjustments :: Maybe BusinessDayAdjustments

The business day convention to apply to each calculation period end date if it would otherwise fall on a day that is not a business day in the specified financial business centers.

calcPeriodDates_firstPeriodStartDate :: Maybe AdjustableDate

The start date of the calculation period if the date falls before the effective date. It must only be specified if it is not equal to the effective date. This date may be subject to adjustment in accordance with a business day convention.

calcPeriodDates_firstRegularPeriodStartDate :: Maybe Date

The start date of the regular part of the calculation period schedule. It must only be specified if there is an initial stub calculation period. This day may be subject to adjustment in accordance with any adjustments specified in calculationPeriodDatesAdjustments.

calcPeriodDates_firstCompoundingPeriodEndDate :: Maybe Date

The end date of the initial compounding period when compounding is applicable. It must only be specified when the compoundingMethod element is present and not equal to a value of None. This date may be subject to adjustment in accordance with any adjustments specified in calculationPeriodDatesAdjustments.

calcPeriodDates_lastRegularPeriodEndDate :: Maybe Date

The end date of the regular part of the calculation period schedule. It must only be specified if there is a final stub calculation period. This day may be subject to adjustment in accordance with any adjustments specified in calculationPeriodDatesAdjustments.

calcPeriodDates_stubPeriodType :: Maybe StubPeriodTypeEnum

Method to allocate any irregular period remaining after regular periods have been allocated between the effective and termination date.

calcPeriodDates_calculationPeriodFrequency :: Maybe CalculationPeriodFrequency

The frequency at which calculation period end dates occur with the regular part of the calculation period schedule and their roll date convention.

data CancelableProvision Source

A type defining the right of a party to cancel a swap transaction on the specified exercise dates. The provision is for walkaway cancellation (i.e. the fair value of the swap is not paid). A fee payable on exercise can be specified.

Constructors

CancelableProvision 

Fields

cancelProvis_buyerPartyReference :: Maybe PartyReference

A reference to the party that buys this instrument, ie. pays for this instrument and receives the rights defined by it. See 2000 ISDA definitions Article 11.1 (b). In the case of FRAs this the fixed rate payer.

cancelProvis_buyerAccountReference :: Maybe AccountReference

A reference to the account that buys this instrument.

cancelProvis_sellerPartyReference :: Maybe PartyReference

A reference to the party that sells (writes) this instrument, i.e. that grants the rights defined by this instrument and in return receives a payment for it. See 2000 ISDA definitions Article 11.1 (a). In the case of FRAs this is the floating rate payer.

cancelProvis_sellerAccountReference :: Maybe AccountReference

A reference to the account that sells this instrument.

cancelProvis_exercise :: Maybe Exercise

An placeholder for the actual option exercise definitions.

cancelProvis_exerciseNotice :: Maybe ExerciseNotice

Definition of the party to whom notice of exercise should be given.

cancelProvis_followUpConfirmation :: Maybe Boolean

A flag to indicate whether follow-up confirmation of exercise (written or electronic) is required following telephonic notice by the buyer to the seller or seller's agent.

cancelableProvision_adjustedDates :: Maybe CancelableProvisionAdjustedDates

The adjusted dates associated with a cancelable provision. These dates have been adjusted for any applicable business day convention.

cancelProvis_finalCalculationPeriodDateAdjustment :: [FinalCalculationPeriodDateAdjustment]

Business date convention adjustment to final payment period per leg (swapStream) upon exercise event. The adjustments can be made in-line with leg level BDC's or they can be specified seperately.

cancelProvis_initialFee :: Maybe SimplePayment

An initial fee for the cancelable option.

data CancelableProvisionAdjustedDates Source

A type to define the adjusted dates for a cancelable provision on a swap transaction.

Constructors

CancelableProvisionAdjustedDates 

Fields

cancelProvisAdjustDates_cancellationEvent :: [CancellationEvent]

The adjusted dates for an individual cancellation date.

data CancellationEvent Source

The adjusted dates for a specific cancellation date, including the adjusted exercise date and adjusted termination date.

Constructors

CancellationEvent 

Fields

cancelEvent_ID :: Maybe ID
 
cancelEvent_adjustedExerciseDate :: Maybe Date

The date on which option exercise takes place. This date should already be adjusted for any applicable business day convention.

cancelEvent_adjustedEarlyTerminationDate :: Maybe Date

The early termination date that is applicable if an early termination provision is exercised. This date should already be adjusted for any applicable business day convention.

data CapFloor Source

A type defining an interest rate cap, floor, or cap/floor strategy (e.g. collar) product.

Constructors

CapFloor 

Fields

capFloor_ID :: Maybe ID
 
capFloor_primaryAssetClass :: Maybe AssetClass

A classification of the most important risk class of the trade. FpML defines a simple asset class categorization using a coding scheme.

capFloor_secondaryAssetClass :: [AssetClass]

A classification of additional risk classes of the trade, if any. FpML defines a simple asset class categorization using a coding scheme.

capFloor_productType :: [ProductType]

A classification of the type of product. FpML defines a simple product categorization using a coding scheme.

capFloor_productId :: [ProductId]

A product reference identifier. The product ID is an identifier that describes the key economic characteristics of the trade type, with the exception of concepts such as size (notional, quantity, number of units) and price (fixed rate, strike, etc.) that are negotiated for each transaction. It can be used to hold identifiers such as the UPI (universal product identifier) required by certain regulatory reporting rules. It can also be used to hold identifiers of benchmark products or product temnplates used by certain trading systems or facilities. FpML does not define the domain values associated with this element. Note that the domain values for this element are not strictly an enumerated list.

capFloor_stream :: Maybe InterestRateStream
 
capFloor_premium :: [Payment]

The option premium amount payable by buyer to seller on the specified payment date.

capFloor_additionalPayment :: [Payment]

Additional payments between the principal parties.

capFloor_earlyTerminationProvision :: Maybe EarlyTerminationProvision

Parameters specifying provisions relating to the optional and mandatory early terminarion of a CapFloor transaction.

data Cashflows Source

A type defining the cashflow representation of a swap trade.

Constructors

Cashflows 

Fields

cashflows_matchParameters :: Maybe Boolean

A true/false flag to indicate whether the cashflows match the parametric definition of the stream, i.e. whether the cashflows could be regenerated from the parameters without loss of information.

cashflows_principalExchange :: [PrincipalExchange]

The initial, intermediate and final principal exchange amounts. Typically required on cross currency interest rate swaps where actual exchanges of principal occur. A list of principal exchange elements may be ordered in the document by ascending adjusted principal exchange date. An FpML document containing an unordered principal exchange list is still regarded as a conformant document.

cashflows_paymentCalculationPeriod :: [PaymentCalculationPeriod]

The adjusted payment date and associated calculation period parameters required to calculate the actual or projected payment amount. A list of payment calculation period elements may be ordered in the document by ascending adjusted payment date. An FpML document containing an unordered list of payment calculation periods is still regarded as a conformant document.

data CashPriceMethod Source

A type defining the parameters necessary for each of the ISDA cash price methods for cash settlement.

Constructors

CashPriceMethod 

Fields

cashPriceMethod_cashSettlementReferenceBanks :: Maybe CashSettlementReferenceBanks

A container for a set of reference institutions. These reference institutions may be called upon to provide rate quotations as part of the method to determine the applicable cash settlement amount. If institutions are not specified, it is assumed that reference institutions will be agreed between the parties on the exercise date, or in the case of swap transaction to which mandatory early termination is applicable, the cash settlement valuation date.

cashPriceMethod_cashSettlementCurrency :: Maybe Currency

The currency in which the cash settlement amount will be calculated and settled.

cashPriceMethod_quotationRateType :: Maybe QuotationRateTypeEnum

Which rate quote is to be observed, either Bid, Mid, Offer or Exercising Party Pays. The meaning of Exercising Party Pays is defined in the 2000 ISDA Definitions, Section 17.2. Certain Definitions Relating to Cash Settlement, paragraph (j)

data CashSettlement Source

A type to define the cash settlement terms for a product where cash settlement is applicable.

Constructors

CashSettlement 

Fields

cashSettl_ID :: Maybe ID
 
cashSettlement_valuationTime :: Maybe BusinessCenterTime

The time of the cash settlement valuation date when the cash settlement amount will be determined according to the cash settlement method if the parties have not otherwise been able to agree the cash settlement amount.

cashSettlement_valuationDate :: Maybe RelativeDateOffset

The date on which the cash settlement amount will be determined according to the cash settlement method if the parties have not otherwise been able to agree the cash settlement amount.

cashSettlement_paymentDate :: Maybe CashSettlementPaymentDate

The date on which the cash settlement amount will be paid, subject to adjustment in accordance with any applicable business day convention. This component would not be present for a mandatory early termination provision where the cash settlement payment date is the mandatory early termination date.

cashSettl_choice3 :: Maybe (OneOf7 CashPriceMethod CashPriceMethod YieldCurveMethod YieldCurveMethod YieldCurveMethod CrossCurrencyMethod YieldCurveMethod)

Choice between:

  1. An ISDA defined cash settlement method used for the determination of the applicable cash settlement amount. The method is defined in the 2006 ISDA Definitions, Section 18.3. Cash Settlement Methods, paragraph (a).
  2. An ISDA defined cash settlement method used for the determination of the applicable cash settlement amount. The method is defined in the 2006 ISDA Definitions, Section 18.3. Cash Settlement Methods, paragraph (b).
  3. An ISDA defined cash settlement method used for the determination of the applicable cash settlement amount. The method is defined in the 2006 ISDA Definitions, Section 18.3. Cash Settlement Methods, paragraph (c).
  4. An ISDA defined cash settlement method used for the determination of the applicable cash settlement amount. The method is defined in the 2006 ISDA Definitions, Section 18.3. Cash Settlement Methods, paragraph (d).
  5. An ISDA defined cash settlement method used for the determination of the applicable cash settlement amount. The method is defined in the 2006 ISDA Definitions, Section 18.3. Cash Settlement Methods, paragraph (e).
  6. An ISDA defined cash settlement method used for the determination of the applicable cash settlement amount. The method is defined in the 2006 ISDA Definitions, Section 18.3. Cash Settlement Methods, paragraph (f) (published in Supplement number 23).
  7. An ISDA defined cash settlement method used for the determination of the applicable cash settlement amount. The method is defined in the 2006 ISDA Definitions, Section 18.3. Cash Settlement Methods, paragraph (g) (published in Supplement number 28).

data CashSettlementPaymentDate Source

A type defining the cash settlement payment date(s) as either a set of explicit dates, together with applicable adjustments, or as a date relative to some other (anchor) date, or as any date in a range of contiguous business days.

Constructors

CashSettlementPaymentDate 

Fields

cashSettlPaymentDate_ID :: Maybe ID
 
cashSettlPaymentDate_choice0 :: Maybe (OneOf3 AdjustableDates RelativeDateOffset BusinessDateRange)

Choice between:

  1. A series of dates that shall be subject to adjustment if they would otherwise fall on a day that is not a business day in the specified business centers, together with the convention for adjusting the date.
  2. A date specified as some offset to another date (the anchor date).
  3. A range of contiguous business days.

data CrossCurrencyMethod Source

Constructors

CrossCurrencyMethod 

Fields

crossCurrenMethod_cashSettlementReferenceBanks :: Maybe CashSettlementReferenceBanks

A container for a set of reference institutions. These reference institutions may be called upon to provide rate quotations as part of the method to determine the applicable cash settlement amount. If institutions are not specified, it is assumed that reference institutions will be agreed between the parties on the exercise date, or in the case of swap transaction to which mandatory early termination is applicable, the cash settlement valuation date.

crossCurrenMethod_cashSettlementCurrency :: [Currency]

The currency, or currencies, in which the cash settlement amount(s) will be calculated and settled. While the order in which the currencies are stated is unimportant, the cash settlement currency or currencies must correspond to one or both of the constituent currencies of the swap transaction.

crossCurrenMethod_quotationRateType :: Maybe QuotationRateTypeEnum

Which rate quote is to be observed, either Bid, Mid, Offer or Exercising Party Pays. The meaning of Exercising Party Pays is defined in the 2000 ISDA Definitions, Section 17.2. Certain Definitions Relating to Cash Settlement, paragraph (j)

data DateRelativeToCalculationPeriodDates Source

A type to provide the ability to point to multiple payment nodes in the document through the unbounded paymentDatesReference.

Constructors

DateRelativeToCalculationPeriodDates 

Fields

drtcpd_calculationPeriodDatesReference :: [CalculationPeriodDatesReference]

A set of href pointers to calculation period dates defined somewhere else in the document.

data DateRelativeToPaymentDates Source

A type to provide the ability to point to multiple payment nodes in the document through the unbounded paymentDatesReference.

Constructors

DateRelativeToPaymentDates 

Fields

dateRelatToPaymentDates_paymentDatesReference :: [PaymentDatesReference]

A set of href pointers to payment dates defined somewhere else in the document.

data Discounting Source

A type defining discounting information. The 2000 ISDA definitions, section 8.4. discounting (related to the calculation of a discounted fixed amount or floating amount) apply. This type must only be included if discounting applies.

Constructors

Discounting 

Fields

discounting_type :: Maybe DiscountingTypeEnum

The discounting method that is applicable.

discounting_discountRate :: Maybe Decimal

A discount rate, expressed as a decimal, to be used in the calculation of a discounted amount. A discount amount of 5% would be represented as 0.05.

discounting_discountRateDayCountFraction :: Maybe DayCountFraction

A discount day count fraction to be used in the calculation of a discounted amount.

data EarlyTerminationEvent Source

A type to define the adjusted dates associated with an early termination provision.

Constructors

EarlyTerminationEvent 

Fields

earlyTerminEvent_ID :: Maybe ID
 
earlyTerminEvent_adjustedExerciseDate :: Maybe Date

The date on which option exercise takes place. This date should already be adjusted for any applicable business day convention.

earlyTerminEvent_adjustedEarlyTerminationDate :: Maybe Date

The early termination date that is applicable if an early termination provision is exercised. This date should already be adjusted for any applicable business day convention.

earlyTerminEvent_adjustedCashSettlementValuationDate :: Maybe Date

The date by which the cash settlement amount must be agreed. This date should already be adjusted for any applicable business day convention.

earlyTerminEvent_adjustedCashSettlementPaymentDate :: Maybe Date

The date on which the cash settlement amount is paid. This date should already be adjusted for any applicable business dat convention.

earlyTerminEvent_adjustedExerciseFeePaymentDate :: Maybe Date

The date on which the exercise fee amount is paid. This date should already be adjusted for any applicable business day convention.

data EarlyTerminationProvision Source

A type defining an early termination provision for a swap. This early termination is at fair value, i.e. on termination the fair value of the product must be settled between the parties.

data ExerciseEvent Source

A type defining the adjusted dates associated with a particular exercise event.

Constructors

ExerciseEvent 

Fields

exercEvent_ID :: Maybe ID
 
exercEvent_adjustedExerciseDate :: Maybe Date

The date on which option exercise takes place. This date should already be adjusted for any applicable business day convention.

exercEvent_adjustedRelevantSwapEffectiveDate :: Maybe Date

The effective date of the underlying swap associated with a given exercise date. This date should already be adjusted for any applicable business day convention.

exercEvent_adjustedCashSettlementValuationDate :: Maybe Date

The date by which the cash settlement amount must be agreed. This date should already be adjusted for any applicable business day convention.

exercEvent_adjustedCashSettlementPaymentDate :: Maybe Date

The date on which the cash settlement amount is paid. This date should already be adjusted for any applicable business dat convention.

exercEvent_adjustedExerciseFeePaymentDate :: Maybe Date

The date on which the exercise fee amount is paid. This date should already be adjusted for any applicable business day convention.

data ExercisePeriod Source

This defines the time interval to the start of the exercise period, i.e. the earliest exercise date, and the frequency of subsequent exercise dates (if any).

Constructors

ExercisePeriod 

Fields

exercPeriod_ID :: Maybe ID
 
exercPeriod_earliestExerciseDateTenor :: Maybe Period

The time interval to the first (and possibly only) exercise date in the exercise period.

exercPeriod_exerciseFrequency :: Maybe Period

The frequency of subsequent exercise dates in the exercise period following the earliest exercise date. An interval of 1 day should be used to indicate an American style exercise period.

data ExtendibleProvision Source

A type defining an option to extend an existing swap transaction on the specified exercise dates for a term ending on the specified new termination date.

Constructors

ExtendibleProvision 

Fields

extendProvis_buyerPartyReference :: Maybe PartyReference

A reference to the party that buys this instrument, ie. pays for this instrument and receives the rights defined by it. See 2000 ISDA definitions Article 11.1 (b). In the case of FRAs this the fixed rate payer.

extendProvis_buyerAccountReference :: Maybe AccountReference

A reference to the account that buys this instrument.

extendProvis_sellerPartyReference :: Maybe PartyReference

A reference to the party that sells (writes) this instrument, i.e. that grants the rights defined by this instrument and in return receives a payment for it. See 2000 ISDA definitions Article 11.1 (a). In the case of FRAs this is the floating rate payer.

extendProvis_sellerAccountReference :: Maybe AccountReference

A reference to the account that sells this instrument.

extendProvis_exercise :: Maybe Exercise

An placeholder for the actual option exercise definitions.

extendProvis_exerciseNotice :: Maybe ExerciseNotice

Definition of the party to whom notice of exercise should be given.

extendProvis_followUpConfirmation :: Maybe Boolean

A flag to indicate whether follow-up confirmation of exercise (written or electronic) is required following telephonic notice by the buyer to the seller or seller's agent.

extendibleProvision_adjustedDates :: Maybe ExtendibleProvisionAdjustedDates

The adjusted dates associated with an extendible provision. These dates have been adjusted for any applicable business day convention.

data ExtendibleProvisionAdjustedDates Source

A type defining the adjusted dates associated with a provision to extend a swap.

Constructors

ExtendibleProvisionAdjustedDates 

Fields

extendProvisAdjustDates_extensionEvent :: [ExtensionEvent]

The adjusted dates associated with a single extendible exercise date.

data ExtensionEvent Source

A type to define the adjusted dates associated with an individual extension event.

Constructors

ExtensionEvent 

Fields

extensEvent_ID :: Maybe ID
 
extensEvent_adjustedExerciseDate :: Maybe Date

The date on which option exercise takes place. This date should already be adjusted for any applicable business day convention.

extensEvent_adjustedExtendedTerminationDate :: Maybe Date

The termination date if an extendible provision is exercised. This date should already be adjusted for any applicable business day convention.

data FinalCalculationPeriodDateAdjustment Source

A type to define business date convention adjustment to final payment period per leg.

Constructors

FinalCalculationPeriodDateAdjustment 

Fields

fcpda_relevantUnderlyingDateReference :: Maybe RelevantUnderlyingDateReference

Reference to the unadjusted cancellation effective dates.

fcpda_swapStreamReference :: InterestRateStreamReference

Reference to the leg, where date adjustments may apply.

fcpda_businessDayConvention :: Maybe BusinessDayConventionEnum

Override business date convention. This takes precedence over leg level information.

data FallbackReferencePrice Source

The method, prioritzed by the order it is listed in this element, to get a replacement rate for the disrupted settlement rate option.

Constructors

FallbackReferencePrice 

Fields

fallbRefPrice_valuationPostponement :: Maybe ValuationPostponement

Specifies how long to wait to get a quote from a settlement rate option upon a price source disruption

fallbRefPrice_fallbackSettlementRateOption :: [SettlementRateOption]

This settlement rate option will be used in its place.

fallbRefPrice_fallbackSurveyValuationPostponenment :: Maybe Empty

Request rate quotes from the market.

fallbRefPrice_calculationAgentDetermination :: Maybe CalculationAgent

The calculation agent will decide the rate.

data FloatingRateDefinition Source

A type defining parameters associated with a floating rate reset. This type forms part of the cashflows representation of a stream.

Constructors

FloatingRateDefinition 

Fields

floatRateDefin_calculatedRate :: Maybe Decimal

The final calculated rate for a calculation period after any required averaging of rates A calculated rate of 5% would be represented as 0.05.

floatRateDefin_rateObservation :: [RateObservation]

The details of a particular rate observation, including the fixing date and observed rate. A list of rate observation elements may be ordered in the document by ascending adjusted fixing date. An FpML document containing an unordered list of rate observations is still regarded as a conformant document.

floatRateDefin_floatingRateMultiplier :: Maybe Decimal

A rate multiplier to apply to the floating rate. The multiplier can be a positive or negative decimal. This element should only be included if the multiplier is not equal to 1 (one).

floatRateDefin_spread :: Maybe Decimal

The ISDA Spread, if any, which applies for the calculation period. The spread is a per annum rate, expressed as a decimal. For purposes of determining a calculation period amount, if positive the spread will be added to the floating rate and if negative the spread will be subtracted from the floating rate. A positive 10 basis point (0.1%) spread would be represented as 0.001.

floatRateDefin_capRate :: [Strike]

The cap rate, if any, which applies to the floating rate for the calculation period. The cap rate (strike) is only required where the floating rate on a swap stream is capped at a certain strike level. The cap rate is assumed to be exclusive of any spread and is a per annum rate, expressed as a decimal. A cap rate of 5% would be represented as 0.05.

floatRateDefin_floorRate :: [Strike]

The floor rate, if any, which applies to the floating rate for the calculation period. The floor rate (strike) is only required where the floating rate on a swap stream is floored at a certain strike level. The floor rate is assumed to be exclusive of any spread and is a per annum rate, expressed as a decimal. The floor rate of 5% would be represented as 0.05.

data Fra Source

A type defining a Forward Rate Agreement (FRA) product.

Constructors

Fra 

Fields

fra_ID :: Maybe ID
 
fra_primaryAssetClass :: Maybe AssetClass

A classification of the most important risk class of the trade. FpML defines a simple asset class categorization using a coding scheme.

fra_secondaryAssetClass :: [AssetClass]

A classification of additional risk classes of the trade, if any. FpML defines a simple asset class categorization using a coding scheme.

fra_productType :: [ProductType]

A classification of the type of product. FpML defines a simple product categorization using a coding scheme.

fra_productId :: [ProductId]

A product reference identifier. The product ID is an identifier that describes the key economic characteristics of the trade type, with the exception of concepts such as size (notional, quantity, number of units) and price (fixed rate, strike, etc.) that are negotiated for each transaction. It can be used to hold identifiers such as the UPI (universal product identifier) required by certain regulatory reporting rules. It can also be used to hold identifiers of benchmark products or product temnplates used by certain trading systems or facilities. FpML does not define the domain values associated with this element. Note that the domain values for this element are not strictly an enumerated list.

fra_buyerPartyReference :: Maybe PartyReference

A reference to the party that buys this instrument, ie. pays for this instrument and receives the rights defined by it. See 2000 ISDA definitions Article 11.1 (b). In the case of FRAs this the fixed rate payer.

fra_buyerAccountReference :: Maybe AccountReference

A reference to the account that buys this instrument.

fra_sellerPartyReference :: Maybe PartyReference

A reference to the party that sells (writes) this instrument, i.e. that grants the rights defined by this instrument and in return receives a payment for it. See 2000 ISDA definitions Article 11.1 (a). In the case of FRAs this is the floating rate payer.

fra_sellerAccountReference :: Maybe AccountReference

A reference to the account that sells this instrument.

fra_adjustedEffectiveDate :: RequiredIdentifierDate

The start date of the calculation period. This date should already be adjusted for any applicable business day convention. This is also the date when the observed rate is applied, the reset date.

fra_adjustedTerminationDate :: Date

The end date of the calculation period. This date should already be adjusted for any applicable business day convention.

fra_paymentDate :: Maybe AdjustableDate

The payment date. This date is subject to adjustment in accordance with any applicable business day convention.

fra_fixingDateOffset :: Maybe RelativeDateOffset

Specifies the fixing date relative to the reset date in terms of a business days offset and an associated set of financial business centers. Normally these offset calculation rules will be those specified in the ISDA definition for the relevant floating rate index (ISDA's Floating Rate Option). However, non-standard offset calculation rules may apply for a trade if mutually agreed by the principal parties to the transaction. The href attribute on the dateRelativeTo element should reference the id attribute on the adjustedEffectiveDate element.

fra_dayCountFraction :: DayCountFraction

The day count fraction.

fra_calculationPeriodNumberOfDays :: Maybe PositiveInteger

The number of days from the adjusted effective date to the adjusted termination date calculated in accordance with the applicable day count fraction.

fra_notional :: Money

The notional amount.

fra_fixedRate :: Decimal

The calculation period fixed rate. A per annum rate, expressed as a decimal. A fixed rate of 5% would be represented as 0.05.

fra_floatingRateIndex :: FloatingRateIndex
 
fra_indexTenor :: [Period]

The ISDA Designated Maturity, i.e. the tenor of the floating rate.

fra_discounting :: Maybe FraDiscountingEnum

Specifies whether discounting applies and, if so, what type.

data FxFixingDate Source

A type that is extending the Offset structure for providing the ability to specify an FX fixing date as an offset to dates specified somewhere else in the document.

Constructors

FxFixingDate 

Fields

fxFixingDate_ID :: Maybe ID
 
fxFixingDate_periodMultiplier :: Integer

A time period multiplier, e.g. 1, 2 or 3 etc. A negative value can be used when specifying an offset relative to another date, e.g. -2 days.

fxFixingDate_period :: PeriodEnum

A time period, e.g. a day, week, month or year of the stream. If the periodMultiplier value is 0 (zero) then period must contain the value D (day).

fxFixingDate_dayType :: Maybe DayTypeEnum

In the case of an offset specified as a number of days, this element defines whether consideration is given as to whether a day is a good business day or not. If a day type of business days is specified then non-business days are ignored when calculating the offset. The financial business centers to use for determination of business days are implied by the context in which this element is used. This element must only be included when the offset is specified as a number of days. If the offset is zero days then the dayType element should not be included.

fxFixingDate_businessDayConvention :: Maybe BusinessDayConventionEnum

The convention for adjusting a date if it would otherwise fall on a day that is not a business day.

fxFixingDate_choice4 :: Maybe (OneOf2 BusinessCentersReference BusinessCenters)

Choice between:

  1. A pointer style reference to a set of financial business centers defined elsewhere in the document. This set of business centers is used to determine whether a particular day is a business day or not.
  2. businessCenters
fxFixingDate_choice5 :: Maybe (OneOf2 DateRelativeToPaymentDates DateRelativeToCalculationPeriodDates)

Choice between:

  1. The payment date references on which settlements in non-deliverable currency are due and will then have to be converted according to the terms specified through the other parts of the nonDeliverableSettlement structure.
  2. The calculation period references on which settlements in non-deliverable currency are due and will then have to be converted according to the terms specified through the other parts of the nonDeliverableSettlement structure. Implemented for Brazilian-CDI swaps where it will refer to the termination date of the appropriate leg.

data FxLinkedNotionalAmount Source

A type to describe the cashflow representation for fx linked notionals.

Constructors

FxLinkedNotionalAmount 

Fields

fxLinkedNotionAmount_resetDate :: Maybe Date
 
fxLinkedNotionAmount_adjustedFxSpotFixingDate :: Maybe Date

The date on which the fx spot rate is observed. This date should already be adjusted for any applicable business day convention.

fxLinkedNotionAmount_observedFxSpotRate :: Maybe Decimal

The actual observed fx spot rate.

fxLinkedNotionAmount_notionalAmount :: Maybe Decimal

The calculation period notional amount.

data FxLinkedNotionalSchedule Source

A type to describe a notional schedule where each notional that applies to a calculation period is calculated with reference to a notional amount or notional amount schedule in a different currency by means of a spot currency exchange rate which is normally observed at the beginning of each period.

Constructors

FxLinkedNotionalSchedule 

Fields

fxLinkedNotionSched_constantNotionalScheduleReference :: Maybe NotionalReference

A pointer style reference to the associated constant notional schedule defined elsewhere in the document which contains the currency amounts which will be converted into the varying notional currency amounts using the spot currency exchange rate.

fxLinkedNotionSched_initialValue :: Maybe Decimal

The initial currency amount for the varying notional.

fxLinkedNotionSched_varyingNotionalCurrency :: Maybe Currency

The currency of the varying notional amount, i.e. the notional amount being determined periodically based on observation of a spot currency exchange rate.

fxLinkedNotionSched_varyingNotionalFixingDates :: Maybe RelativeDateOffset

The dates on which spot currency exchange rates are observed for purposes of determining the varying notional currency amount that will apply to a calculation period.

fxLinkedNotionSched_fxSpotRateSource :: Maybe FxSpotRateSource

The information source and time at which the spot currency exchange rate will be observed.

fxLinkedNotionSched_varyingNotionalInterimExchangePaymentDates :: Maybe RelativeDateOffset

The dates on which interim exchanges of notional are paid. Interim exchanges will arise as a result of changes in the spot currency exchange amount or changes in the constant notional schedule (e.g. amortization).

data InflationRateCalculation Source

A type defining the components specifiying an Inflation Rate Calculation

Constructors

InflationRateCalculation 

Fields

inflatRateCalc_ID :: Maybe ID
 
inflatRateCalc_floatingRateIndex :: FloatingRateIndex
 
inflatRateCalc_indexTenor :: Maybe Period

The ISDA Designated Maturity, i.e. the tenor of the floating rate.

inflatRateCalc_floatingRateMultiplierSchedule :: Maybe Schedule

A rate multiplier or multiplier schedule to apply to the floating rate. A multiplier schedule is expressed as explicit multipliers and dates. In the case of a schedule, the step dates may be subject to adjustment in accordance with any adjustments specified in the calculationPeriodDatesAdjustments. The multiplier can be a positive or negative decimal. This element should only be included if the multiplier is not equal to 1 (one) for the term of the stream.

inflatRateCalc_spreadSchedule :: [SpreadSchedule]

The ISDA Spread or a Spread schedule expressed as explicit spreads and dates. In the case of a schedule, the step dates may be subject to adjustment in accordance with any adjustments specified in calculationPeriodDatesAdjustments. The spread is a per annum rate, expressed as a decimal. For purposes of determining a calculation period amount, if positive the spread will be added to the floating rate and if negative the spread will be subtracted from the floating rate. A positive 10 basis point (0.1%) spread would be represented as 0.001.

inflatRateCalc_rateTreatment :: Maybe RateTreatmentEnum

The specification of any rate conversion which needs to be applied to the observed rate before being used in any calculations. The two common conversions are for securities quoted on a bank discount basis which will need to be converted to either a Money Market Yield or Bond Equivalent Yield. See the Annex to the 2000 ISDA Definitions, Section 7.3. Certain General Definitions Relating to Floating Rate Options, paragraphs (g) and (h) for definitions of these terms.

inflatRateCalc_capRateSchedule :: [StrikeSchedule]

The cap rate or cap rate schedule, if any, which applies to the floating rate. The cap rate (strike) is only required where the floating rate on a swap stream is capped at a certain level. A cap rate schedule is expressed as explicit cap rates and dates and the step dates may be subject to adjustment in accordance with any adjustments specified in calculationPeriodDatesAdjustments. The cap rate is assumed to be exclusive of any spread and is a per annum rate, expressed as a decimal. A cap rate of 5% would be represented as 0.05.

inflatRateCalc_floorRateSchedule :: [StrikeSchedule]

The floor rate or floor rate schedule, if any, which applies to the floating rate. The floor rate (strike) is only required where the floating rate on a swap stream is floored at a certain strike level. A floor rate schedule is expressed as explicit floor rates and dates and the step dates may be subject to adjustment in accordance with any adjustments specified in calculationPeriodDatesAdjustments. The floor rate is assumed to be exclusive of any spread and is a per annum rate, expressed as a decimal. A floor rate of 5% would be represented as 0.05.

inflatRateCalc_initialRate :: Maybe Decimal

The initial floating rate reset agreed between the principal parties involved in the trade. This is assumed to be the first required reset rate for the first regular calculation period. It should only be included when the rate is not equal to the rate published on the source implied by the floating rate index. An initial rate of 5% would be represented as 0.05.

inflatRateCalc_finalRateRounding :: Maybe Rounding

The rounding convention to apply to the final rate used in determination of a calculation period amount.

inflatRateCalc_averagingMethod :: Maybe AveragingMethodEnum

If averaging is applicable, this component specifies whether a weighted or unweighted average method of calculation is to be used. The component must only be included when averaging applies.

inflatRateCalc_negativeInterestRateTreatment :: Maybe NegativeInterestRateTreatmentEnum

The specification of any provisions for calculating payment obligations when a floating rate is negative (either due to a quoted negative floating rate or by operation of a spread that is subtracted from the floating rate).

inflatRateCalc_inflationLag :: Maybe Offset

an offsetting period from the payment date which determines the reference period for which the inflation index is onserved.

inflatRateCalc_indexSource :: Maybe RateSourcePage

The reference source such as Reuters or Bloomberg.

inflatRateCalc_mainPublication :: Maybe MainPublication

The current main publication source such as relevant web site or a government body.

inflatRateCalc_interpolationMethod :: Maybe InterpolationMethod

The method used when calculating the Inflation Index Level from multiple points - the most common is Linear.

inflatRateCalc_initialIndexLevel :: Maybe Decimal

initial known index level for the first calculation period.

inflatRateCalc_fallbackBondApplicable :: Maybe Boolean

The applicability of a fallback bond as defined in the 2006 ISDA Inflation Derivatives Definitions, sections 1.3 and 1.8. Omission of this element imples a value of true.

data InterestRateStream Source

A type defining the components specifiying an interest rate stream, including both a parametric and cashflow representation for the stream of payments.

Constructors

InterestRateStream 

Fields

interRateStream_ID :: Maybe ID
 
interRateStream_payerPartyReference :: Maybe PartyReference

A reference to the party responsible for making the payments defined by this structure.

interRateStream_payerAccountReference :: Maybe AccountReference

A reference to the account responsible for making the payments defined by this structure.

interRateStream_receiverPartyReference :: Maybe PartyReference

A reference to the party that receives the payments corresponding to this structure.

interRateStream_receiverAccountReference :: Maybe AccountReference

A reference to the account that receives the payments corresponding to this structure.

interRateStream_calculationPeriodDates :: CalculationPeriodDates

The calculation periods dates schedule.

interRateStream_paymentDates :: PaymentDates

The payment dates schedule.

interRateStream_resetDates :: Maybe ResetDates

The reset dates schedule. The reset dates schedule only applies for a floating rate stream.

interRateStream_calculationPeriodAmount :: CalculationPeriodAmount

The calculation period amount parameters.

interRateStream_stubCalculationPeriodAmount :: Maybe StubCalculationPeriodAmount

The stub calculation period amount parameters. This element must only be included if there is an initial or final stub calculation period. Even then, it must only be included if either the stub references a different floating rate tenor to the regular calculation periods, or if the stub is calculated as a linear interpolation of two different floating rate tenors, or if a specific stub rate or stub amount has been negotiated.

interRateStream_principalExchanges :: Maybe PrincipalExchanges

The true/false flags indicating whether initial, intermediate or final exchanges of principal should occur.

interRateStream_cashflows :: Maybe Cashflows

The cashflows representation of the swap stream.

interRateStream_settlementProvision :: Maybe SettlementProvision

A provision that allows the specification of settlement terms, occuring when the settlement currency is different to the notional currency of the trade.

interRateStream_formula :: Maybe Formula

An interest rate derivative formula.

data MandatoryEarlyTermination Source

A type to define an early termination provision for which exercise is mandatory.

Constructors

MandatoryEarlyTermination 

Fields

mandatEarlyTermin_ID :: Maybe ID
 
mandatoryEarlyTermination_date :: Maybe AdjustableDate

The early termination date associated with a mandatory early termination of a swap.

mandatEarlyTermin_calculationAgent :: Maybe CalculationAgent

The ISDA Calculation Agent responsible for performing duties associated with an optional early termination.

mandatEarlyTermin_cashSettlement :: Maybe CashSettlement

If specified, this means that cash settlement is applicable to the transaction and defines the parameters associated with the cash settlement prodcedure. If not specified, then physical settlement is applicable.

mandatoryEarlyTermination_adjustedDates :: Maybe MandatoryEarlyTerminationAdjustedDates

The adjusted dates associated with a mandatory early termination provision. These dates have been adjusted for any applicable business day convention.

data MandatoryEarlyTerminationAdjustedDates Source

A type defining the adjusted dates associated with a mandatory early termination provision.

Constructors

MandatoryEarlyTerminationAdjustedDates 

Fields

metad_adjustedEarlyTerminationDate :: Maybe Date

The early termination date that is applicable if an early termination provision is exercised. This date should already be adjusted for any applicable business day convention.

metad_adjustedCashSettlementValuationDate :: Maybe Date

The date by which the cash settlement amount must be agreed. This date should already be adjusted for any applicable business day convention.

metad_adjustedCashSettlementPaymentDate :: Maybe Date

The date on which the cash settlement amount is paid. This date should already be adjusted for any applicable business dat convention.

data NonDeliverableSettlement Source

A type defining the parameters used when the reference currency of the swapStream is non-deliverable.

Constructors

NonDeliverableSettlement 

Fields

nonDelivSettl_referenceCurrency :: Maybe Currency

The currency in which the swap stream is denominated.

nonDelivSettl_choice1 :: Maybe (OneOf2 FxFixingDate AdjustableDates)

Choice between:

  1. The date, when expressed as a relative date, on which the currency rate will be determined for the purpose of specifying the amount in deliverable currency.
  2. The date, when expressed as a schedule of date(s), on which the currency rate will be determined for the purpose of specifying the amount in deliverable currency.
nonDelivSettl_settlementRateOption :: Maybe SettlementRateOption

The rate source for the conversion to the settlement currency. This source is specified through a scheme that reflects the terms of the Annex A to the 1998 FX and Currency Option Definitions.

nonDelivSettl_priceSourceDisruption :: Maybe PriceSourceDisruption

A type defining the parameters to get a new quote when a settlement rate option is disrupted.

data Notional Source

An type defining the notional amount or notional amount schedule associated with a swap stream. The notional schedule will be captured explicitly, specifying the dates that the notional changes and the outstanding notional amount that applies from that date. A parametric representation of the rules defining the notional step schedule can optionally be included.

Constructors

Notional 

Fields

notional_ID :: Maybe ID
 
notional_stepSchedule :: NonNegativeAmountSchedule

The notional amount or notional amount schedule expressed as explicit outstanding notional amounts and dates. In the case of a schedule, the step dates may be subject to adjustment in accordance with any adjustments specified in calculationPeriodDatesAdjustments.

notional_stepParameters :: Maybe NotionalStepRule

A parametric representation of the notional step schedule, i.e. parameters used to generate the notional schedule.

data NotionalStepRule Source

A type defining a parametric representation of the notional step schedule, i.e. parameters used to generate the notional balance on each step date. The step change in notional can be expressed in terms of either a fixed amount or as a percentage of either the initial notional or previous notional amount. This parametric representation is intended to cover the more common amortizing/accreting.

Constructors

NotionalStepRule 

Fields

notionStepRule_calculationPeriodDatesReference :: Maybe CalculationPeriodDatesReference

A pointer style reference to the associated calculation period dates component defined elsewhere in the document.

notionStepRule_stepFrequency :: Maybe Period

The frequency at which the step changes occur. This frequency must be a multiple of the stream calculation period frequency.

notionStepRule_firstNotionalStepDate :: Maybe Date

Effective date of the first change in notional (i.e. a calculation period start date).

notionStepRule_lastNotionalStepDate :: Maybe Date

Effective date of the last change in notional (i.e. a calculation period start date).

notionStepRule_choice4 :: Maybe (OneOf2 Decimal (Maybe Decimal, Maybe StepRelativeToEnum))

Choice between:

  1. The explicit amount that the notional changes on each step date. This can be a positive or negative amount.
  2. Sequence of:
  • The percentage amount by which the notional changes on each step date. The percentage is either a percentage applied to the initial notional amount or the previous outstanding notional, depending on the value of the element stepRelativeTo. The percentage can be either positive or negative. A percentage of 5% would be represented as 0.05.
  • Specifies whether the notionalStepRate should be applied to the initial notional or the previous notional in order to calculate the notional step change amount.

data OptionalEarlyTermination Source

A type defining an early termination provision where either or both parties have the right to exercise.

Constructors

OptionalEarlyTermination 

Fields

optionEarlyTermin_singlePartyOption :: Maybe SinglePartyOption

If optional early termination is not available to both parties then this component specifies the buyer and seller of the option.

optionEarlyTermin_exercise :: Maybe Exercise

An placeholder for the actual option exercise definitions.

optionEarlyTermin_exerciseNotice :: [ExerciseNotice]

Definition of the party to whom notice of exercise should be given.

optionEarlyTermin_followUpConfirmation :: Maybe Boolean

A flag to indicate whether follow-up confirmation of exercise (written or electronic) is required following telephonic notice by the buyer to the seller or seller's agent.

optionEarlyTermin_calculationAgent :: Maybe CalculationAgent

The ISDA Calculation Agent responsible for performing duties associated with an optional early termination.

optionEarlyTermin_cashSettlement :: Maybe CashSettlement

If specified, this means that cash settlement is applicable to the transaction and defines the parameters associated with the cash settlement prodcedure. If not specified, then physical settlement is applicable.

optionalEarlyTermination_adjustedDates :: Maybe OptionalEarlyTerminationAdjustedDates

An early termination provision to terminate the trade at fair value where one or both parties have the right to decide on termination.

data OptionalEarlyTerminationAdjustedDates Source

A type defining the adjusted dates associated with an optional early termination provision.

Constructors

OptionalEarlyTerminationAdjustedDates 

Fields

oetad_earlyTerminationEvent :: [EarlyTerminationEvent]

The adjusted dates associated with an individual earley termination date.

data PaymentCalculationPeriod Source

A type defining the adjusted payment date and associated calculation period parameters required to calculate the actual or projected payment amount. This type forms part of the cashflow representation of a swap stream.

Constructors

PaymentCalculationPeriod 

Fields

paymentCalcPeriod_ID :: Maybe ID
 
paymentCalcPeriod_href :: Maybe IDREF

Attribute that can be used to reference the yield curve used to estimate the discount factor.

paymentCalcPeriod_unadjustedPaymentDate :: Maybe Date
 
paymentCalcPeriod_adjustedPaymentDate :: Maybe Date

The adjusted payment date. This date should already be adjusted for any applicable business day convention. This component is not intended for use in trade confirmation but may be specified to allow the fee structure to also serve as a cashflow type component (all dates the Cashflows type are adjusted payment dates).

paymentCalcPeriod_choice2 :: Maybe (OneOf2 [CalculationPeriod] Decimal)

Choice between:

  1. The parameters used in the calculation of a fixed or floating rate calculation period amount. A list of calculation period elements may be ordered in the document by ascending start date. An FpML document which contains an unordered list of calcularion periods is still regarded as a conformant document.
  2. A known fixed payment amount.
paymentCalcPeriod_discountFactor :: Maybe Decimal

A decimal value representing the discount factor used to calculate the present value of cash flow.

paymentCalcPeriod_forecastPaymentAmount :: Maybe Money

A monetary amount representing the forecast of the future value of the payment.

paymentCalcPeriod_presentValueAmount :: Maybe Money

A monetary amount representing the present value of the forecast payment.

data PaymentDates Source

A type defining parameters used to generate the payment dates schedule, including the specification of early or delayed payments. Payment dates are determined relative to the calculation period dates or the reset dates.

Constructors

PaymentDates 

Fields

paymentDates_ID :: Maybe ID
 
paymentDates_choice0 :: Maybe (OneOf3 CalculationPeriodDatesReference ResetDatesReference ValuationDatesReference)

Choice between:

  1. A pointer style reference to the associated calculation period dates component defined elsewhere in the document.
  2. A pointer style reference to the associated reset dates component defined elsewhere in the document.
  3. A pointer style reference to the associated valuation dates component defined elsewhere in the document. Implemented for Brazilian-CDI Swaps where it will refer to the settlemementProvisionnonDeliverableSettlementfxFixingDate structure.
paymentDates_paymentFrequency :: Frequency

The frequency at which regular payment dates occur. If the payment frequency is equal to the frequency defined in the calculation period dates component then one calculation period contributes to each payment amount. If the payment frequency is less frequent than the frequency defined in the calculation period dates component then more than one calculation period will contribute to the payment amount. A payment frequency more frequent than the calculation period frequency or one that is not a multiple of the calculation period frequency is invalid. If the payment frequency is of value T (term), the period is defined by the swapswapStreamcalculationPerioDateseffectiveDate and the swapswapStreamcalculationPerioDatesterminationDate.

paymentDates_firstPaymentDate :: Maybe Date

The first unadjusted payment date. This day may be subject to adjustment in accordance with any business day convention specified in paymentDatesAdjustments. This element must only be included if there is an initial stub. This date will normally correspond to an unadjusted calculation period start or end date. This is true even if early or delayed payment is specified to be applicable since the actual first payment date will be the specified number of days before or after the applicable adjusted calculation period start or end date with the resulting payment date then being adjusted in accordance with any business day convention specified in paymentDatesAdjustments.

paymentDates_lastRegularPaymentDate :: Maybe Date

The last regular unadjusted payment date. This day may be subject to adjustment in accordance with any business day convention specified in paymentDatesAdjustments. This element must only be included if there is a final stub. All calculation periods after this date contribute to the final payment. The final payment is made relative to the final set of calculation periods or the final reset date as the case may be. This date will normally correspond to an unadjusted calculation period start or end date. This is true even if early or delayed payment is specified to be applicable since the actual last regular payment date will be the specified number of days before or after the applicable adjusted calculation period start or end date with the resulting payment date then being adjusted in accordance with any business day convention specified in paymentDatesAdjustments.

paymentDates_payRelativeTo :: Maybe PayRelativeToEnum

Specifies whether the payments occur relative to each adjusted calculation period start date, adjusted calculation period end date or each reset date. The reset date is applicable in the case of certain euro (former French Franc) floating rate indices. Calculation period start date means relative to the start of the first calculation period contributing to a given payment. Similarly, calculation period end date means the end of the last calculation period contributing to a given payment.The valuation date is applicable for Brazilian-CDI swaps.

paymentDates_paymentDaysOffset :: Maybe Offset

If early payment or delayed payment is required, specifies the number of days offset that the payment occurs relative to what would otherwise be the unadjusted payment date. The offset can be specified in terms of either calendar or business days. Even in the case of a calendar days offset, the resulting payment date, adjusted for the specified calendar days offset, will still be adjusted in accordance with the specified payment dates adjustments. This element should only be included if early or delayed payment is applicable, i.e. if the periodMultiplier element value is not equal to zero. An early payment would be indicated by a negative periodMultiplier element value and a delayed payment (or payment lag) would be indicated by a positive periodMultiplier element value.

paymentDates_adjustments :: Maybe BusinessDayAdjustments

The business day convention to apply to each payment date if it would otherwise fall on a day that is not a business day in the specified financial business centers.

data PriceSourceDisruption Source

A type defining the parameters used to get a price quote to replace the settlement rate option that is disrupted.

Constructors

PriceSourceDisruption 

Fields

priceSourceDisrup_fallbackReferencePrice :: Maybe FallbackReferencePrice

The method, prioritzed by the order it is listed in this element, to get a replacement rate for the disrupted settlement rate option.

data PrincipalExchange Source

A type defining a principal exchange amount and adjusted exchange date. The type forms part of the cashflow representation of a swap stream.

Constructors

PrincipalExchange 

Fields

princExch_ID :: Maybe ID
 
princExch_unadjustedPrincipalExchangeDate :: Maybe Date
 
princExch_adjustedPrincipalExchangeDate :: Maybe Date

The principal exchange date. This date should already be adjusted for any applicable business day convention.

principalExchange_amount :: Maybe Decimal

The principal exchange amount. This amount should be positive if the stream payer is paying the exchange amount and signed negative if they are receiving it.

princExch_discountFactor :: Maybe Decimal

The value representing the discount factor used to calculate the present value of the principal exchange amount.

princExch_presentValuePrincipalExchangeAmount :: Maybe Money

The amount representing the present value of the principal exchange.

data ResetDates Source

A type defining the parameters used to generate the reset dates schedule and associated fixing dates. The reset dates are determined relative to the calculation periods schedules dates.

Constructors

ResetDates 

Fields

resetDates_ID :: Maybe ID
 
resetDates_calculationPeriodDatesReference :: Maybe CalculationPeriodDatesReference

A pointer style reference to the associated calculation period dates component defined elsewhere in the document.

resetDates_resetRelativeTo :: Maybe ResetRelativeToEnum

Specifies whether the reset dates are determined with respect to each adjusted calculation period start date or adjusted calculation period end date. If the reset frequency is specified as daily this element must not be included.

resetDates_initialFixingDate :: Maybe RelativeDateOffset
 
resetDates_fixingDates :: Maybe RelativeDateOffset

Specifies the fixing date relative to the reset date in terms of a business days offset and an associated set of financial business centers. Normally these offset calculation rules will be those specified in the ISDA definition for the relevant floating rate index (ISDA's Floating Rate Option). However, non-standard offset calculation rules may apply for a trade if mutually agreed by the principal parties to the transaction. The href attribute on the dateRelativeTo element should reference the id attribute on the resetDates element.

resetDates_rateCutOffDaysOffset :: Maybe Offset

Specifies the number of business days before the period end date when the rate cut-off date is assumed to apply. The financial business centers associated with determining the rate cut-off date are those specified in the reset dates adjustments. The rate cut-off number of days must be a negative integer (a value of zero would imply no rate cut off applies in which case the rateCutOffDaysOffset element should not be included). The relevant rate for each reset date in the period from, and including, a rate cut-off date to, but excluding, the next applicable period end date (or, in the case of the last calculation period, the termination date) will (solely for purposes of calculating the floating amount payable on the next applicable payment date) be deemed to be the relevant rate in effect on that rate cut-off date. For example, if rate cut-off days for a daily averaging deal is -2 business days, then the refix rate applied on (period end date - 2 days) will also be applied as the reset on (period end date - 1 day), i.e. the actual number of reset dates remains the same but from the rate cut-off date until the period end date, the same refix rate is applied. Note that in the case of several calculation periods contributing to a single payment, the rate cut-off is assumed only to apply to the final calculation period contributing to that payment. The day type associated with the offset must imply a business days offset.

resetDates_resetFrequency :: ResetFrequency

The frequency at which reset dates occur. In the case of a weekly reset frequency, also specifies the day of the week that the reset occurs. If the reset frequency is greater than the calculation period frequency then this implies that more than one reset date is established for each calculation period and some form of rate averaging is applicable.

resetDates_adjustments :: Maybe BusinessDayAdjustments

The business day convention to apply to each reset date if it would otherwise fall on a day that is not a business day in the specified financial business centers.

data SettlementProvision Source

A type defining the specification of settlement terms, occuring when the settlement currency is different to the notional currency of the trade.

Constructors

SettlementProvision 

Fields

settlProvis_settlementCurrency :: Maybe Currency

The currency that stream settles in (to support swaps that settle in a currency different from the notional currency).

settlProvis_nonDeliverableSettlement :: Maybe NonDeliverableSettlement

The specification of the non-deliverable settlement provision.

data SettlementRateOption Source

A type defining the settlement rate options through a scheme reflecting the terms of the Annex A to the 1998 FX and Currency Option Definitions.

data SinglePartyOption Source

A type describing the buyer and seller of an option.

Constructors

SinglePartyOption 

Fields

singlePartyOption_buyerPartyReference :: Maybe PartyReference

A reference to the party that buys this instrument, ie. pays for this instrument and receives the rights defined by it. See 2000 ISDA definitions Article 11.1 (b). In the case of FRAs this the fixed rate payer.

singlePartyOption_buyerAccountReference :: Maybe AccountReference

A reference to the account that buys this instrument.

singlePartyOption_sellerPartyReference :: Maybe PartyReference

A reference to the party that sells (writes) this instrument, i.e. that grants the rights defined by this instrument and in return receives a payment for it. See 2000 ISDA definitions Article 11.1 (a). In the case of FRAs this is the floating rate payer.

singlePartyOption_sellerAccountReference :: Maybe AccountReference

A reference to the account that sells this instrument.

data StubCalculationPeriodAmount Source

A type defining how the initial or final stub calculation period amounts is calculated. For example, the rate to be applied to the initial or final stub calculation period may be the linear interpolation of two different tenors for the floating rate index specified in the calculation period amount component, e.g. A two month stub period may used the linear interpolation of a one month and three month floating rate. The different rate tenors would be specified in this component. Note that a maximum of two rate tenors can be specified. If a stub period uses a single index tenor and this is the same as that specified in the calculation period amount component then the initial stub or final stub component, as the case may be, must not be included.

Constructors

StubCalculationPeriodAmount 

Fields

stubCalcPeriodAmount_calculationPeriodDatesReference :: Maybe CalculationPeriodDatesReference

A pointer style reference to the associated calculation period dates component defined elsewhere in the document.

stubCalcPeriodAmount_initialStub :: Maybe StubValue

Specifies how the initial stub amount is calculated. A single floating rate tenor different to that used for the regular part of the calculation periods schedule may be specified, or two floating tenors may be specified. If two floating rate tenors are specified then Linear Interpolation (in accordance with the 2000 ISDA Definitions, Section 8.3. Interpolation) is assumed to apply. Alternatively, an actual known stub rate or stub amount may be specified.

stubCalcPeriodAmount_finalStub :: Maybe StubValue

Specifies how the final stub amount is calculated. A single floating rate tenor different to that used for the regular part of the calculation periods schedule may be specified, or two floating tenors may be specified. If two floating rate tenors are specified then Linear Interpolation (in accordance with the 2000 ISDA Definitions, Section 8.3. Interpolation) is assumed to apply. Alternatively, an actual known stub rate or stub amount may be specified.

data Swap Source

A type defining swap streams and additional payments between the principal parties involved in the swap.

Constructors

Swap 

Fields

swap_ID :: Maybe ID
 
swap_primaryAssetClass :: Maybe AssetClass

A classification of the most important risk class of the trade. FpML defines a simple asset class categorization using a coding scheme.

swap_secondaryAssetClass :: [AssetClass]

A classification of additional risk classes of the trade, if any. FpML defines a simple asset class categorization using a coding scheme.

swap_productType :: [ProductType]

A classification of the type of product. FpML defines a simple product categorization using a coding scheme.

swap_productId :: [ProductId]

A product reference identifier. The product ID is an identifier that describes the key economic characteristics of the trade type, with the exception of concepts such as size (notional, quantity, number of units) and price (fixed rate, strike, etc.) that are negotiated for each transaction. It can be used to hold identifiers such as the UPI (universal product identifier) required by certain regulatory reporting rules. It can also be used to hold identifiers of benchmark products or product temnplates used by certain trading systems or facilities. FpML does not define the domain values associated with this element. Note that the domain values for this element are not strictly an enumerated list.

swap_stream :: [InterestRateStream]

The swap streams.

swap_earlyTerminationProvision :: Maybe EarlyTerminationProvision

Parameters specifying provisions relating to the optional and mandatory early terminarion of a swap transaction.

swap_cancelableProvision :: Maybe CancelableProvision

A provision that allows the specification of an embedded option within a swap giving the buyer of the option the right to terminate the swap, in whole or in part, on the early termination date.

swap_extendibleProvision :: Maybe ExtendibleProvision

A provision that allows the specification of an embedded option with a swap giving the buyer of the option the right to extend the swap, in whole or in part, to the extended termination date.

swap_additionalPayment :: [Payment]

Additional payments between the principal parties.

swap_additionalTerms :: Maybe SwapAdditionalTerms

Contains any additional terms to the swap contract.

data SwapAdditionalTerms Source

Additional terms to a swap contract.

Constructors

SwapAdditionalTerms 

Fields

swapAddTerms_bondReference :: Maybe BondReference

Reference to a bond underlyer to represent an asset swap or Condition Precedent Bond.

data Swaption Source

A type to define an option on a swap.

Constructors

Swaption 

Fields

swaption_ID :: Maybe ID
 
swaption_primaryAssetClass :: Maybe AssetClass

A classification of the most important risk class of the trade. FpML defines a simple asset class categorization using a coding scheme.

swaption_secondaryAssetClass :: [AssetClass]

A classification of additional risk classes of the trade, if any. FpML defines a simple asset class categorization using a coding scheme.

swaption_productType :: [ProductType]

A classification of the type of product. FpML defines a simple product categorization using a coding scheme.

swaption_productId :: [ProductId]

A product reference identifier. The product ID is an identifier that describes the key economic characteristics of the trade type, with the exception of concepts such as size (notional, quantity, number of units) and price (fixed rate, strike, etc.) that are negotiated for each transaction. It can be used to hold identifiers such as the UPI (universal product identifier) required by certain regulatory reporting rules. It can also be used to hold identifiers of benchmark products or product temnplates used by certain trading systems or facilities. FpML does not define the domain values associated with this element. Note that the domain values for this element are not strictly an enumerated list.

swaption_buyerPartyReference :: Maybe PartyReference

A reference to the party that buys this instrument, ie. pays for this instrument and receives the rights defined by it. See 2000 ISDA definitions Article 11.1 (b). In the case of FRAs this the fixed rate payer.

swaption_buyerAccountReference :: Maybe AccountReference

A reference to the account that buys this instrument.

swaption_sellerPartyReference :: Maybe PartyReference

A reference to the party that sells (writes) this instrument, i.e. that grants the rights defined by this instrument and in return receives a payment for it. See 2000 ISDA definitions Article 11.1 (a). In the case of FRAs this is the floating rate payer.

swaption_sellerAccountReference :: Maybe AccountReference

A reference to the account that sells this instrument.

swaption_premium :: [Payment]

The option premium amount payable by buyer to seller on the specified payment date.

swaption_optionType :: Maybe OptionTypeEnum

The type of option transaction. From a usage standpoint, putcall is the default option type, while payerreceiver indicator is used for options index credit default swaps, consistently with the industry practice. Straddle is used for the case of straddle strategy, that combine a call and a put with the same strike. This element is needed for transparency reporting because the counterparties are not available. TODO: can this be represented instead using the UPI?

swaption_exercise :: Exercise

An placeholder for the actual option exercise definitions.

swaption_exerciseProcedure :: Maybe ExerciseProcedure

A set of parameters defining procedures associated with the exercise.

swaption_calculationAgent :: Maybe CalculationAgent

The ISDA Calculation Agent responsible for performing duties associated with an optional early termination.

swaption_choice13 :: Maybe (OneOf2 CashSettlement SwaptionPhysicalSettlement)

In the absence of both cashSettlement and (explicit) physicalSettlement terms, physical settlement is inferred.

Choice between:

  1. If specified, this means that cash settlement is applicable to the transaction and defines the parameters associated with the cash settlement procedure. If not specified, then physical settlement is applicable.
  2. If specified, this defines physical settlement terms which apply to the transaction.
swaption_straddle :: Boolean

Whether the option is a swaption or a swaption straddle.

swaption_adjustedDates :: Maybe SwaptionAdjustedDates

The adjusted dates associated with swaption exercise. These dates have been adjusted for any applicable business day convention.

swaption_swap :: Swap
 

data SwaptionAdjustedDates Source

A type describing the adjusted dates associated with swaption exercise and settlement.

Constructors

SwaptionAdjustedDates 

Fields

swaptAdjustDates_exerciseEvent :: [ExerciseEvent]

The adjusted dates associated with an individual swaption exercise date.

data SwaptionPhysicalSettlement Source

Constructors

SwaptionPhysicalSettlement 

Fields

swaptPhysicSettl_clearedPhysicalSettlement :: Maybe Boolean

Specifies whether the swap resulting from physical settlement of the swaption transaction will clear through a clearing house. The meaning of Cleared Physical Settlement is defined in the 2006 ISDA Definitions, Section 15.2 (published in Supplement number 28).

data ValuationPostponement Source

Specifies how long to wait to get a quote from a settlement rate option upon a price source disruption.

Constructors

ValuationPostponement 

Fields

valPostp_maximumDaysOfPostponement :: Maybe PositiveInteger

The maximum number of days to wait for a quote from the disrupted settlement rate option before proceding to the next method.

data YieldCurveMethod Source

A type defining the parameters required for each of the ISDA defined yield curve methods for cash settlement.

Constructors

YieldCurveMethod 

Fields

yieldCurveMethod_settlementRateSource :: Maybe SettlementRateSource

The method for obtaining a settlement rate. This may be from some information source (e.g. Reuters) or from a set of reference banks.

yieldCurveMethod_quotationRateType :: Maybe QuotationRateTypeEnum

Which rate quote is to be observed, either Bid, Mid, Offer or Exercising Party Pays. The meaning of Exercising Party Pays is defined in the 2000 ISDA Definitions, Section 17.2. Certain Definitions Relating to Cash Settlement, paragraph (j)

elementBulletPayment :: XMLParser BulletPaymentSource

A product to represent a single known payment.

elementCapFloor :: XMLParser CapFloorSource

A cap, floor or cap floor structures product definition.

elementFra :: XMLParser FraSource

A forward rate agreement product definition.

elementInflationRateCalculation :: XMLParser InflationRateCalculationSource

An inflation rate calculation definition.

elementRateCalculation :: XMLParser RateSource

The base element for the floating rate calculation definitions.

elementSwap :: XMLParser SwapSource

A swap product definition.

elementSwaption :: XMLParser SwaptionSource

A swaption product definition.