{-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies #-} {-# OPTIONS_GHC -fno-warn-duplicate-exports #-} module Data.FpML.V53.IRD ( module Data.FpML.V53.IRD , module Data.FpML.V53.Asset ) where import Text.XML.HaXml.Schema.Schema (SchemaType(..),SimpleType(..),Extension(..),Restricts(..)) import Text.XML.HaXml.Schema.Schema as Schema import Text.XML.HaXml.OneOfN import qualified Text.XML.HaXml.Schema.PrimitiveTypes as Xsd import Data.FpML.V53.Asset -- Some hs-boot imports are required, for fwd-declaring types. -- | A type including a reference to a bond to support the -- representation of an asset swap or Condition Precedent -- Bond. data BondReference = BondReference { bondRef_bond :: Maybe Bond -- ^ Identifies the underlying asset when it is a series or a -- class of bonds. , bondRef_conditionPrecedentBond :: Maybe Xsd.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 Xsd.Boolean -- ^ To indicate whether the Discrepancy Clause is applicable. } deriving (Eq,Show) instance SchemaType BondReference where parseSchemaType s = do (pos,e) <- posnElement [s] commit $ interior e $ return BondReference `apply` optional (elementBond) `apply` optional (parseSchemaType "conditionPrecedentBond") `apply` optional (parseSchemaType "discrepancyClause") schemaTypeToXML s x@BondReference{} = toXMLElement s [] [ maybe [] (elementToXMLBond) $ bondRef_bond x , maybe [] (schemaTypeToXML "conditionPrecedentBond") $ bondRef_conditionPrecedentBond x , maybe [] (schemaTypeToXML "discrepancyClause") $ bondRef_discrepancyClause x ] -- | A product to represent a single cashflow. data BulletPayment = BulletPayment { bulletPayment_ID :: Maybe Xsd.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. } deriving (Eq,Show) instance SchemaType BulletPayment where parseSchemaType s = do (pos,e) <- posnElement [s] a0 <- optional $ getAttribute "id" e pos commit $ interior e $ return (BulletPayment a0) `apply` optional (parseSchemaType "primaryAssetClass") `apply` many (parseSchemaType "secondaryAssetClass") `apply` many (parseSchemaType "productType") `apply` many (parseSchemaType "productId") `apply` optional (parseSchemaType "payment") schemaTypeToXML s x@BulletPayment{} = toXMLElement s [ maybe [] (toXMLAttribute "id") $ bulletPayment_ID x ] [ maybe [] (schemaTypeToXML "primaryAssetClass") $ bulletPayment_primaryAssetClass x , concatMap (schemaTypeToXML "secondaryAssetClass") $ bulletPayment_secondaryAssetClass x , concatMap (schemaTypeToXML "productType") $ bulletPayment_productType x , concatMap (schemaTypeToXML "productId") $ bulletPayment_productId x , maybe [] (schemaTypeToXML "payment") $ bulletPayment_payment x ] instance Extension BulletPayment Product where supertype v = Product_BulletPayment v -- | A type definining the parameters used in the calculation of -- fixed or floating calculation period amounts. data Calculation = Calculation { 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. -- -- (2) 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. } deriving (Eq,Show) instance SchemaType Calculation where parseSchemaType s = do (pos,e) <- posnElement [s] commit $ interior e $ return Calculation `apply` oneOf' [ ("Notional", fmap OneOf2 (parseSchemaType "notionalSchedule")) , ("FxLinkedNotionalSchedule", fmap TwoOf2 (parseSchemaType "fxLinkedNotionalSchedule")) ] `apply` oneOf' [ ("Schedule Maybe FutureValueAmount", fmap OneOf2 (return (,) `apply` parseSchemaType "fixedRateSchedule" `apply` optional (parseSchemaType "futureValueNotional"))) , ("Rate", fmap TwoOf2 (elementRateCalculation)) ] `apply` parseSchemaType "dayCountFraction" `apply` optional (parseSchemaType "discounting") `apply` optional (parseSchemaType "compoundingMethod") schemaTypeToXML s x@Calculation{} = toXMLElement s [] [ foldOneOf2 (schemaTypeToXML "notionalSchedule") (schemaTypeToXML "fxLinkedNotionalSchedule") $ calculation_choice0 x , foldOneOf2 (\ (a,b) -> concat [ schemaTypeToXML "fixedRateSchedule" a , maybe [] (schemaTypeToXML "futureValueNotional") b ]) (elementToXMLRateCalculation) $ calculation_choice1 x , schemaTypeToXML "dayCountFraction" $ calculation_dayCountFraction x , maybe [] (schemaTypeToXML "discounting") $ calculation_discounting x , maybe [] (schemaTypeToXML "compoundingMethod") $ calculation_compoundingMethod x ] -- | 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. data CalculationPeriod = CalculationPeriod { calcPeriod_ID :: Maybe Xsd.ID , calcPeriod_unadjustedStartDate :: Maybe Xsd.Date , calcPeriod_unadjustedEndDate :: Maybe Xsd.Date , calcPeriod_adjustedStartDate :: Maybe Xsd.Date -- ^ The calculation period start date, adjusted according to -- any relevant business day convention. , calcPeriod_adjustedEndDate :: Maybe Xsd.Date -- ^ The calculation period end date, adjusted according to any -- relevant business day convention. , calculationPeriod_numberOfDays :: Maybe Xsd.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 Xsd.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 Xsd.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 Xsd.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 Xsd.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 } deriving (Eq,Show) instance SchemaType CalculationPeriod where parseSchemaType s = do (pos,e) <- posnElement [s] a0 <- optional $ getAttribute "id" e pos commit $ interior e $ return (CalculationPeriod a0) `apply` optional (parseSchemaType "unadjustedStartDate") `apply` optional (parseSchemaType "unadjustedEndDate") `apply` optional (parseSchemaType "adjustedStartDate") `apply` optional (parseSchemaType "adjustedEndDate") `apply` optional (parseSchemaType "calculationPeriodNumberOfDays") `apply` optional (oneOf' [ ("Xsd.Decimal", fmap OneOf2 (parseSchemaType "notionalAmount")) , ("FxLinkedNotionalAmount", fmap TwoOf2 (parseSchemaType "fxLinkedNotionalAmount")) ]) `apply` optional (oneOf' [ ("FloatingRateDefinition", fmap OneOf2 (parseSchemaType "floatingRateDefinition")) , ("Xsd.Decimal", fmap TwoOf2 (parseSchemaType "fixedRate")) ]) `apply` optional (parseSchemaType "dayCountYearFraction") `apply` optional (parseSchemaType "forecastAmount") `apply` optional (parseSchemaType "forecastRate") schemaTypeToXML s x@CalculationPeriod{} = toXMLElement s [ maybe [] (toXMLAttribute "id") $ calcPeriod_ID x ] [ maybe [] (schemaTypeToXML "unadjustedStartDate") $ calcPeriod_unadjustedStartDate x , maybe [] (schemaTypeToXML "unadjustedEndDate") $ calcPeriod_unadjustedEndDate x , maybe [] (schemaTypeToXML "adjustedStartDate") $ calcPeriod_adjustedStartDate x , maybe [] (schemaTypeToXML "adjustedEndDate") $ calcPeriod_adjustedEndDate x , maybe [] (schemaTypeToXML "calculationPeriodNumberOfDays") $ calculationPeriod_numberOfDays x , maybe [] (foldOneOf2 (schemaTypeToXML "notionalAmount") (schemaTypeToXML "fxLinkedNotionalAmount") ) $ calcPeriod_choice5 x , maybe [] (foldOneOf2 (schemaTypeToXML "floatingRateDefinition") (schemaTypeToXML "fixedRate") ) $ calcPeriod_choice6 x , maybe [] (schemaTypeToXML "dayCountYearFraction") $ calcPeriod_dayCountYearFraction x , maybe [] (schemaTypeToXML "forecastAmount") $ calcPeriod_forecastAmount x , maybe [] (schemaTypeToXML "forecastRate") $ calcPeriod_forecastRate x ] -- | 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. data CalculationPeriodAmount = CalculationPeriodAmount { 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. } deriving (Eq,Show) instance SchemaType CalculationPeriodAmount where parseSchemaType s = do (pos,e) <- posnElement [s] commit $ interior e $ return CalculationPeriodAmount `apply` oneOf' [ ("Calculation", fmap OneOf2 (parseSchemaType "calculation")) , ("AmountSchedule", fmap TwoOf2 (parseSchemaType "knownAmountSchedule")) ] schemaTypeToXML s x@CalculationPeriodAmount{} = toXMLElement s [] [ foldOneOf2 (schemaTypeToXML "calculation") (schemaTypeToXML "knownAmountSchedule") $ calcPeriodAmount_choice0 x ] -- | 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. data CalculationPeriodDates = CalculationPeriodDates { calcPeriodDates_ID :: Maybe Xsd.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 Xsd.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 Xsd.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 Xsd.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. } deriving (Eq,Show) instance SchemaType CalculationPeriodDates where parseSchemaType s = do (pos,e) <- posnElement [s] a0 <- optional $ getAttribute "id" e pos commit $ interior e $ return (CalculationPeriodDates a0) `apply` oneOf' [ ("AdjustableDate", fmap OneOf2 (parseSchemaType "effectiveDate")) , ("AdjustedRelativeDateOffset", fmap TwoOf2 (parseSchemaType "relativeEffectiveDate")) ] `apply` oneOf' [ ("AdjustableDate", fmap OneOf2 (parseSchemaType "terminationDate")) , ("RelativeDateOffset", fmap TwoOf2 (parseSchemaType "relativeTerminationDate")) ] `apply` optional (parseSchemaType "calculationPeriodDatesAdjustments") `apply` optional (parseSchemaType "firstPeriodStartDate") `apply` optional (parseSchemaType "firstRegularPeriodStartDate") `apply` optional (parseSchemaType "firstCompoundingPeriodEndDate") `apply` optional (parseSchemaType "lastRegularPeriodEndDate") `apply` optional (parseSchemaType "stubPeriodType") `apply` optional (parseSchemaType "calculationPeriodFrequency") schemaTypeToXML s x@CalculationPeriodDates{} = toXMLElement s [ maybe [] (toXMLAttribute "id") $ calcPeriodDates_ID x ] [ foldOneOf2 (schemaTypeToXML "effectiveDate") (schemaTypeToXML "relativeEffectiveDate") $ calcPeriodDates_choice0 x , foldOneOf2 (schemaTypeToXML "terminationDate") (schemaTypeToXML "relativeTerminationDate") $ calcPeriodDates_choice1 x , maybe [] (schemaTypeToXML "calculationPeriodDatesAdjustments") $ calculationPeriodDates_adjustments x , maybe [] (schemaTypeToXML "firstPeriodStartDate") $ calcPeriodDates_firstPeriodStartDate x , maybe [] (schemaTypeToXML "firstRegularPeriodStartDate") $ calcPeriodDates_firstRegularPeriodStartDate x , maybe [] (schemaTypeToXML "firstCompoundingPeriodEndDate") $ calcPeriodDates_firstCompoundingPeriodEndDate x , maybe [] (schemaTypeToXML "lastRegularPeriodEndDate") $ calcPeriodDates_lastRegularPeriodEndDate x , maybe [] (schemaTypeToXML "stubPeriodType") $ calcPeriodDates_stubPeriodType x , maybe [] (schemaTypeToXML "calculationPeriodFrequency") $ calcPeriodDates_calculationPeriodFrequency x ] -- | Reference to a calculation period dates component. data CalculationPeriodDatesReference = CalculationPeriodDatesReference { calcPeriodDatesRef_href :: Xsd.IDREF } deriving (Eq,Show) instance SchemaType CalculationPeriodDatesReference where parseSchemaType s = do (pos,e) <- posnElement [s] a0 <- getAttribute "href" e pos commit $ interior e $ return (CalculationPeriodDatesReference a0) schemaTypeToXML s x@CalculationPeriodDatesReference{} = toXMLElement s [ toXMLAttribute "href" $ calcPeriodDatesRef_href x ] [] instance Extension CalculationPeriodDatesReference Reference where supertype v = Reference_CalculationPeriodDatesReference v -- | 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. data CancelableProvision = CancelableProvision { 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 Xsd.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. } deriving (Eq,Show) instance SchemaType CancelableProvision where parseSchemaType s = do (pos,e) <- posnElement [s] commit $ interior e $ return CancelableProvision `apply` optional (parseSchemaType "buyerPartyReference") `apply` optional (parseSchemaType "buyerAccountReference") `apply` optional (parseSchemaType "sellerPartyReference") `apply` optional (parseSchemaType "sellerAccountReference") `apply` optional (elementExercise) `apply` optional (parseSchemaType "exerciseNotice") `apply` optional (parseSchemaType "followUpConfirmation") `apply` optional (parseSchemaType "cancelableProvisionAdjustedDates") `apply` many (parseSchemaType "finalCalculationPeriodDateAdjustment") `apply` optional (parseSchemaType "initialFee") schemaTypeToXML s x@CancelableProvision{} = toXMLElement s [] [ maybe [] (schemaTypeToXML "buyerPartyReference") $ cancelProvis_buyerPartyReference x , maybe [] (schemaTypeToXML "buyerAccountReference") $ cancelProvis_buyerAccountReference x , maybe [] (schemaTypeToXML "sellerPartyReference") $ cancelProvis_sellerPartyReference x , maybe [] (schemaTypeToXML "sellerAccountReference") $ cancelProvis_sellerAccountReference x , maybe [] (elementToXMLExercise) $ cancelProvis_exercise x , maybe [] (schemaTypeToXML "exerciseNotice") $ cancelProvis_exerciseNotice x , maybe [] (schemaTypeToXML "followUpConfirmation") $ cancelProvis_followUpConfirmation x , maybe [] (schemaTypeToXML "cancelableProvisionAdjustedDates") $ cancelableProvision_adjustedDates x , concatMap (schemaTypeToXML "finalCalculationPeriodDateAdjustment") $ cancelProvis_finalCalculationPeriodDateAdjustment x , maybe [] (schemaTypeToXML "initialFee") $ cancelProvis_initialFee x ] -- | A type to define the adjusted dates for a cancelable -- provision on a swap transaction. data CancelableProvisionAdjustedDates = CancelableProvisionAdjustedDates { cancelProvisAdjustDates_cancellationEvent :: [CancellationEvent] -- ^ The adjusted dates for an individual cancellation date. } deriving (Eq,Show) instance SchemaType CancelableProvisionAdjustedDates where parseSchemaType s = do (pos,e) <- posnElement [s] commit $ interior e $ return CancelableProvisionAdjustedDates `apply` many (parseSchemaType "cancellationEvent") schemaTypeToXML s x@CancelableProvisionAdjustedDates{} = toXMLElement s [] [ concatMap (schemaTypeToXML "cancellationEvent") $ cancelProvisAdjustDates_cancellationEvent x ] -- | The adjusted dates for a specific cancellation date, -- including the adjusted exercise date and adjusted -- termination date. data CancellationEvent = CancellationEvent { cancelEvent_ID :: Maybe Xsd.ID , cancelEvent_adjustedExerciseDate :: Maybe Xsd.Date -- ^ The date on which option exercise takes place. This date -- should already be adjusted for any applicable business day -- convention. , cancelEvent_adjustedEarlyTerminationDate :: Maybe Xsd.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. } deriving (Eq,Show) instance SchemaType CancellationEvent where parseSchemaType s = do (pos,e) <- posnElement [s] a0 <- optional $ getAttribute "id" e pos commit $ interior e $ return (CancellationEvent a0) `apply` optional (parseSchemaType "adjustedExerciseDate") `apply` optional (parseSchemaType "adjustedEarlyTerminationDate") schemaTypeToXML s x@CancellationEvent{} = toXMLElement s [ maybe [] (toXMLAttribute "id") $ cancelEvent_ID x ] [ maybe [] (schemaTypeToXML "adjustedExerciseDate") $ cancelEvent_adjustedExerciseDate x , maybe [] (schemaTypeToXML "adjustedEarlyTerminationDate") $ cancelEvent_adjustedEarlyTerminationDate x ] -- | A type defining an interest rate cap, floor, or cap/floor -- strategy (e.g. collar) product. data CapFloor = CapFloor { capFloor_ID :: Maybe Xsd.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. } deriving (Eq,Show) instance SchemaType CapFloor where parseSchemaType s = do (pos,e) <- posnElement [s] a0 <- optional $ getAttribute "id" e pos commit $ interior e $ return (CapFloor a0) `apply` optional (parseSchemaType "primaryAssetClass") `apply` many (parseSchemaType "secondaryAssetClass") `apply` many (parseSchemaType "productType") `apply` many (parseSchemaType "productId") `apply` optional (parseSchemaType "capFloorStream") `apply` many (parseSchemaType "premium") `apply` many (parseSchemaType "additionalPayment") `apply` optional (parseSchemaType "earlyTerminationProvision") schemaTypeToXML s x@CapFloor{} = toXMLElement s [ maybe [] (toXMLAttribute "id") $ capFloor_ID x ] [ maybe [] (schemaTypeToXML "primaryAssetClass") $ capFloor_primaryAssetClass x , concatMap (schemaTypeToXML "secondaryAssetClass") $ capFloor_secondaryAssetClass x , concatMap (schemaTypeToXML "productType") $ capFloor_productType x , concatMap (schemaTypeToXML "productId") $ capFloor_productId x , maybe [] (schemaTypeToXML "capFloorStream") $ capFloor_stream x , concatMap (schemaTypeToXML "premium") $ capFloor_premium x , concatMap (schemaTypeToXML "additionalPayment") $ capFloor_additionalPayment x , maybe [] (schemaTypeToXML "earlyTerminationProvision") $ capFloor_earlyTerminationProvision x ] instance Extension CapFloor Product where supertype v = Product_CapFloor v -- | A type defining the cashflow representation of a swap -- trade. data Cashflows = Cashflows { cashflows_matchParameters :: Maybe Xsd.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. } deriving (Eq,Show) instance SchemaType Cashflows where parseSchemaType s = do (pos,e) <- posnElement [s] commit $ interior e $ return Cashflows `apply` optional (parseSchemaType "cashflowsMatchParameters") `apply` many (parseSchemaType "principalExchange") `apply` many (parseSchemaType "paymentCalculationPeriod") schemaTypeToXML s x@Cashflows{} = toXMLElement s [] [ maybe [] (schemaTypeToXML "cashflowsMatchParameters") $ cashflows_matchParameters x , concatMap (schemaTypeToXML "principalExchange") $ cashflows_principalExchange x , concatMap (schemaTypeToXML "paymentCalculationPeriod") $ cashflows_paymentCalculationPeriod x ] -- | A type defining the parameters necessary for each of the -- ISDA cash price methods for cash settlement. data CashPriceMethod = CashPriceMethod { 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) } deriving (Eq,Show) instance SchemaType CashPriceMethod where parseSchemaType s = do (pos,e) <- posnElement [s] commit $ interior e $ return CashPriceMethod `apply` optional (parseSchemaType "cashSettlementReferenceBanks") `apply` optional (parseSchemaType "cashSettlementCurrency") `apply` optional (parseSchemaType "quotationRateType") schemaTypeToXML s x@CashPriceMethod{} = toXMLElement s [] [ maybe [] (schemaTypeToXML "cashSettlementReferenceBanks") $ cashPriceMethod_cashSettlementReferenceBanks x , maybe [] (schemaTypeToXML "cashSettlementCurrency") $ cashPriceMethod_cashSettlementCurrency x , maybe [] (schemaTypeToXML "quotationRateType") $ cashPriceMethod_quotationRateType x ] -- | A type to define the cash settlement terms for a product -- where cash settlement is applicable. data CashSettlement = CashSettlement { cashSettl_ID :: Maybe Xsd.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). } deriving (Eq,Show) instance SchemaType CashSettlement where parseSchemaType s = do (pos,e) <- posnElement [s] a0 <- optional $ getAttribute "id" e pos commit $ interior e $ return (CashSettlement a0) `apply` optional (parseSchemaType "cashSettlementValuationTime") `apply` optional (parseSchemaType "cashSettlementValuationDate") `apply` optional (parseSchemaType "cashSettlementPaymentDate") `apply` optional (oneOf' [ ("CashPriceMethod", fmap OneOf7 (parseSchemaType "cashPriceMethod")) , ("CashPriceMethod", fmap TwoOf7 (parseSchemaType "cashPriceAlternateMethod")) , ("YieldCurveMethod", fmap ThreeOf7 (parseSchemaType "parYieldCurveAdjustedMethod")) , ("YieldCurveMethod", fmap FourOf7 (parseSchemaType "zeroCouponYieldAdjustedMethod")) , ("YieldCurveMethod", fmap FiveOf7 (parseSchemaType "parYieldCurveUnadjustedMethod")) , ("CrossCurrencyMethod", fmap SixOf7 (parseSchemaType "crossCurrencyMethod")) , ("YieldCurveMethod", fmap SevenOf7 (parseSchemaType "collateralizedCashPriceMethod")) ]) schemaTypeToXML s x@CashSettlement{} = toXMLElement s [ maybe [] (toXMLAttribute "id") $ cashSettl_ID x ] [ maybe [] (schemaTypeToXML "cashSettlementValuationTime") $ cashSettlement_valuationTime x , maybe [] (schemaTypeToXML "cashSettlementValuationDate") $ cashSettlement_valuationDate x , maybe [] (schemaTypeToXML "cashSettlementPaymentDate") $ cashSettlement_paymentDate x , maybe [] (foldOneOf7 (schemaTypeToXML "cashPriceMethod") (schemaTypeToXML "cashPriceAlternateMethod") (schemaTypeToXML "parYieldCurveAdjustedMethod") (schemaTypeToXML "zeroCouponYieldAdjustedMethod") (schemaTypeToXML "parYieldCurveUnadjustedMethod") (schemaTypeToXML "crossCurrencyMethod") (schemaTypeToXML "collateralizedCashPriceMethod") ) $ cashSettl_choice3 x ] -- | 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. data CashSettlementPaymentDate = CashSettlementPaymentDate { cashSettlPaymentDate_ID :: Maybe Xsd.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. } deriving (Eq,Show) instance SchemaType CashSettlementPaymentDate where parseSchemaType s = do (pos,e) <- posnElement [s] a0 <- optional $ getAttribute "id" e pos commit $ interior e $ return (CashSettlementPaymentDate a0) `apply` optional (oneOf' [ ("AdjustableDates", fmap OneOf3 (parseSchemaType "adjustableDates")) , ("RelativeDateOffset", fmap TwoOf3 (parseSchemaType "relativeDate")) , ("BusinessDateRange", fmap ThreeOf3 (parseSchemaType "businessDateRange")) ]) schemaTypeToXML s x@CashSettlementPaymentDate{} = toXMLElement s [ maybe [] (toXMLAttribute "id") $ cashSettlPaymentDate_ID x ] [ maybe [] (foldOneOf3 (schemaTypeToXML "adjustableDates") (schemaTypeToXML "relativeDate") (schemaTypeToXML "businessDateRange") ) $ cashSettlPaymentDate_choice0 x ] data CrossCurrencyMethod = CrossCurrencyMethod { 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) } deriving (Eq,Show) instance SchemaType CrossCurrencyMethod where parseSchemaType s = do (pos,e) <- posnElement [s] commit $ interior e $ return CrossCurrencyMethod `apply` optional (parseSchemaType "cashSettlementReferenceBanks") `apply` between (Occurs (Just 0) (Just 2)) (parseSchemaType "cashSettlementCurrency") `apply` optional (parseSchemaType "quotationRateType") schemaTypeToXML s x@CrossCurrencyMethod{} = toXMLElement s [] [ maybe [] (schemaTypeToXML "cashSettlementReferenceBanks") $ crossCurrenMethod_cashSettlementReferenceBanks x , concatMap (schemaTypeToXML "cashSettlementCurrency") $ crossCurrenMethod_cashSettlementCurrency x , maybe [] (schemaTypeToXML "quotationRateType") $ crossCurrenMethod_quotationRateType x ] -- | A type to provide the ability to point to multiple payment -- nodes in the document through the unbounded -- paymentDatesReference. data DateRelativeToCalculationPeriodDates = DateRelativeToCalculationPeriodDates { drtcpd_calculationPeriodDatesReference :: [CalculationPeriodDatesReference] -- ^ A set of href pointers to calculation period dates defined -- somewhere else in the document. } deriving (Eq,Show) instance SchemaType DateRelativeToCalculationPeriodDates where parseSchemaType s = do (pos,e) <- posnElement [s] commit $ interior e $ return DateRelativeToCalculationPeriodDates `apply` many (parseSchemaType "calculationPeriodDatesReference") schemaTypeToXML s x@DateRelativeToCalculationPeriodDates{} = toXMLElement s [] [ concatMap (schemaTypeToXML "calculationPeriodDatesReference") $ drtcpd_calculationPeriodDatesReference x ] -- | A type to provide the ability to point to multiple payment -- nodes in the document through the unbounded -- paymentDatesReference. data DateRelativeToPaymentDates = DateRelativeToPaymentDates { dateRelatToPaymentDates_paymentDatesReference :: [PaymentDatesReference] -- ^ A set of href pointers to payment dates defined somewhere -- else in the document. } deriving (Eq,Show) instance SchemaType DateRelativeToPaymentDates where parseSchemaType s = do (pos,e) <- posnElement [s] commit $ interior e $ return DateRelativeToPaymentDates `apply` many (parseSchemaType "paymentDatesReference") schemaTypeToXML s x@DateRelativeToPaymentDates{} = toXMLElement s [] [ concatMap (schemaTypeToXML "paymentDatesReference") $ dateRelatToPaymentDates_paymentDatesReference x ] -- | 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. data Discounting = Discounting { discounting_type :: Maybe DiscountingTypeEnum -- ^ The discounting method that is applicable. , discounting_discountRate :: Maybe Xsd.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. } deriving (Eq,Show) instance SchemaType Discounting where parseSchemaType s = do (pos,e) <- posnElement [s] commit $ interior e $ return Discounting `apply` optional (parseSchemaType "discountingType") `apply` optional (parseSchemaType "discountRate") `apply` optional (parseSchemaType "discountRateDayCountFraction") schemaTypeToXML s x@Discounting{} = toXMLElement s [] [ maybe [] (schemaTypeToXML "discountingType") $ discounting_type x , maybe [] (schemaTypeToXML "discountRate") $ discounting_discountRate x , maybe [] (schemaTypeToXML "discountRateDayCountFraction") $ discounting_discountRateDayCountFraction x ] -- | A type to define the adjusted dates associated with an -- early termination provision. data EarlyTerminationEvent = EarlyTerminationEvent { earlyTerminEvent_ID :: Maybe Xsd.ID , earlyTerminEvent_adjustedExerciseDate :: Maybe Xsd.Date -- ^ The date on which option exercise takes place. This date -- should already be adjusted for any applicable business day -- convention. , earlyTerminEvent_adjustedEarlyTerminationDate :: Maybe Xsd.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 Xsd.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 Xsd.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 Xsd.Date -- ^ The date on which the exercise fee amount is paid. This -- date should already be adjusted for any applicable business -- day convention. } deriving (Eq,Show) instance SchemaType EarlyTerminationEvent where parseSchemaType s = do (pos,e) <- posnElement [s] a0 <- optional $ getAttribute "id" e pos commit $ interior e $ return (EarlyTerminationEvent a0) `apply` optional (parseSchemaType "adjustedExerciseDate") `apply` optional (parseSchemaType "adjustedEarlyTerminationDate") `apply` optional (parseSchemaType "adjustedCashSettlementValuationDate") `apply` optional (parseSchemaType "adjustedCashSettlementPaymentDate") `apply` optional (parseSchemaType "adjustedExerciseFeePaymentDate") schemaTypeToXML s x@EarlyTerminationEvent{} = toXMLElement s [ maybe [] (toXMLAttribute "id") $ earlyTerminEvent_ID x ] [ maybe [] (schemaTypeToXML "adjustedExerciseDate") $ earlyTerminEvent_adjustedExerciseDate x , maybe [] (schemaTypeToXML "adjustedEarlyTerminationDate") $ earlyTerminEvent_adjustedEarlyTerminationDate x , maybe [] (schemaTypeToXML "adjustedCashSettlementValuationDate") $ earlyTerminEvent_adjustedCashSettlementValuationDate x , maybe [] (schemaTypeToXML "adjustedCashSettlementPaymentDate") $ earlyTerminEvent_adjustedCashSettlementPaymentDate x , maybe [] (schemaTypeToXML "adjustedExerciseFeePaymentDate") $ earlyTerminEvent_adjustedExerciseFeePaymentDate x ] -- | 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 EarlyTerminationProvision = EarlyTerminationProvision { earlyTerminProvis_ID :: Maybe Xsd.ID , earlyTerminProvis_choice0 :: OneOf1 (((Maybe (OneOf1 ((Maybe (Period)),(Maybe (MandatoryEarlyTermination)))))),((Maybe (OneOf1 ((Maybe (ExercisePeriod)),(Maybe (OptionalEarlyTermination))))))) -- ^ Choice between: -- -- (1) Sequence of: -- -- * unknown -- -- * unknown } deriving (Eq,Show) instance SchemaType EarlyTerminationProvision where parseSchemaType s = do (pos,e) <- posnElement [s] a0 <- optional $ getAttribute "id" e pos commit $ interior e $ return (EarlyTerminationProvision a0) `apply` oneOf' [ ("(Maybe (OneOf1 ((Maybe (Period)),(Maybe (MandatoryEarlyTermination))))) (Maybe (OneOf1 ((Maybe (ExercisePeriod)),(Maybe (OptionalEarlyTermination)))))", fmap OneOf1 (return (,) `apply` optional (oneOf' [ ("Maybe Period Maybe MandatoryEarlyTermination", fmap OneOf1 (return (,) `apply` optional (parseSchemaType "mandatoryEarlyTerminationDateTenor") `apply` optional (parseSchemaType "mandatoryEarlyTermination"))) ]) `apply` optional (oneOf' [ ("Maybe ExercisePeriod Maybe OptionalEarlyTermination", fmap OneOf1 (return (,) `apply` optional (parseSchemaType "optionalEarlyTerminationParameters") `apply` optional (parseSchemaType "optionalEarlyTermination"))) ]))) ] schemaTypeToXML s x@EarlyTerminationProvision{} = toXMLElement s [ maybe [] (toXMLAttribute "id") $ earlyTerminProvis_ID x ] [ foldOneOf1 (\ (a,b) -> concat [ maybe [] (foldOneOf1 (\ (a,b) -> concat [ maybe [] (schemaTypeToXML "mandatoryEarlyTerminationDateTenor") a , maybe [] (schemaTypeToXML "mandatoryEarlyTermination") b ]) ) a , maybe [] (foldOneOf1 (\ (a,b) -> concat [ maybe [] (schemaTypeToXML "optionalEarlyTerminationParameters") a , maybe [] (schemaTypeToXML "optionalEarlyTermination") b ]) ) b ]) $ earlyTerminProvis_choice0 x ] -- | A type defining the adjusted dates associated with a -- particular exercise event. data ExerciseEvent = ExerciseEvent { exercEvent_ID :: Maybe Xsd.ID , exercEvent_adjustedExerciseDate :: Maybe Xsd.Date -- ^ The date on which option exercise takes place. This date -- should already be adjusted for any applicable business day -- convention. , exercEvent_adjustedRelevantSwapEffectiveDate :: Maybe Xsd.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 Xsd.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 Xsd.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 Xsd.Date -- ^ The date on which the exercise fee amount is paid. This -- date should already be adjusted for any applicable business -- day convention. } deriving (Eq,Show) instance SchemaType ExerciseEvent where parseSchemaType s = do (pos,e) <- posnElement [s] a0 <- optional $ getAttribute "id" e pos commit $ interior e $ return (ExerciseEvent a0) `apply` optional (parseSchemaType "adjustedExerciseDate") `apply` optional (parseSchemaType "adjustedRelevantSwapEffectiveDate") `apply` optional (parseSchemaType "adjustedCashSettlementValuationDate") `apply` optional (parseSchemaType "adjustedCashSettlementPaymentDate") `apply` optional (parseSchemaType "adjustedExerciseFeePaymentDate") schemaTypeToXML s x@ExerciseEvent{} = toXMLElement s [ maybe [] (toXMLAttribute "id") $ exercEvent_ID x ] [ maybe [] (schemaTypeToXML "adjustedExerciseDate") $ exercEvent_adjustedExerciseDate x , maybe [] (schemaTypeToXML "adjustedRelevantSwapEffectiveDate") $ exercEvent_adjustedRelevantSwapEffectiveDate x , maybe [] (schemaTypeToXML "adjustedCashSettlementValuationDate") $ exercEvent_adjustedCashSettlementValuationDate x , maybe [] (schemaTypeToXML "adjustedCashSettlementPaymentDate") $ exercEvent_adjustedCashSettlementPaymentDate x , maybe [] (schemaTypeToXML "adjustedExerciseFeePaymentDate") $ exercEvent_adjustedExerciseFeePaymentDate x ] -- | 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). data ExercisePeriod = ExercisePeriod { exercPeriod_ID :: Maybe Xsd.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. } deriving (Eq,Show) instance SchemaType ExercisePeriod where parseSchemaType s = do (pos,e) <- posnElement [s] a0 <- optional $ getAttribute "id" e pos commit $ interior e $ return (ExercisePeriod a0) `apply` optional (parseSchemaType "earliestExerciseDateTenor") `apply` optional (parseSchemaType "exerciseFrequency") schemaTypeToXML s x@ExercisePeriod{} = toXMLElement s [ maybe [] (toXMLAttribute "id") $ exercPeriod_ID x ] [ maybe [] (schemaTypeToXML "earliestExerciseDateTenor") $ exercPeriod_earliestExerciseDateTenor x , maybe [] (schemaTypeToXML "exerciseFrequency") $ exercPeriod_exerciseFrequency x ] -- | 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. data ExtendibleProvision = ExtendibleProvision { 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 Xsd.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. } deriving (Eq,Show) instance SchemaType ExtendibleProvision where parseSchemaType s = do (pos,e) <- posnElement [s] commit $ interior e $ return ExtendibleProvision `apply` optional (parseSchemaType "buyerPartyReference") `apply` optional (parseSchemaType "buyerAccountReference") `apply` optional (parseSchemaType "sellerPartyReference") `apply` optional (parseSchemaType "sellerAccountReference") `apply` optional (elementExercise) `apply` optional (parseSchemaType "exerciseNotice") `apply` optional (parseSchemaType "followUpConfirmation") `apply` optional (parseSchemaType "extendibleProvisionAdjustedDates") schemaTypeToXML s x@ExtendibleProvision{} = toXMLElement s [] [ maybe [] (schemaTypeToXML "buyerPartyReference") $ extendProvis_buyerPartyReference x , maybe [] (schemaTypeToXML "buyerAccountReference") $ extendProvis_buyerAccountReference x , maybe [] (schemaTypeToXML "sellerPartyReference") $ extendProvis_sellerPartyReference x , maybe [] (schemaTypeToXML "sellerAccountReference") $ extendProvis_sellerAccountReference x , maybe [] (elementToXMLExercise) $ extendProvis_exercise x , maybe [] (schemaTypeToXML "exerciseNotice") $ extendProvis_exerciseNotice x , maybe [] (schemaTypeToXML "followUpConfirmation") $ extendProvis_followUpConfirmation x , maybe [] (schemaTypeToXML "extendibleProvisionAdjustedDates") $ extendibleProvision_adjustedDates x ] -- | A type defining the adjusted dates associated with a -- provision to extend a swap. data ExtendibleProvisionAdjustedDates = ExtendibleProvisionAdjustedDates { extendProvisAdjustDates_extensionEvent :: [ExtensionEvent] -- ^ The adjusted dates associated with a single extendible -- exercise date. } deriving (Eq,Show) instance SchemaType ExtendibleProvisionAdjustedDates where parseSchemaType s = do (pos,e) <- posnElement [s] commit $ interior e $ return ExtendibleProvisionAdjustedDates `apply` many (parseSchemaType "extensionEvent") schemaTypeToXML s x@ExtendibleProvisionAdjustedDates{} = toXMLElement s [] [ concatMap (schemaTypeToXML "extensionEvent") $ extendProvisAdjustDates_extensionEvent x ] -- | A type to define the adjusted dates associated with an -- individual extension event. data ExtensionEvent = ExtensionEvent { extensEvent_ID :: Maybe Xsd.ID , extensEvent_adjustedExerciseDate :: Maybe Xsd.Date -- ^ The date on which option exercise takes place. This date -- should already be adjusted for any applicable business day -- convention. , extensEvent_adjustedExtendedTerminationDate :: Maybe Xsd.Date -- ^ The termination date if an extendible provision is -- exercised. This date should already be adjusted for any -- applicable business day convention. } deriving (Eq,Show) instance SchemaType ExtensionEvent where parseSchemaType s = do (pos,e) <- posnElement [s] a0 <- optional $ getAttribute "id" e pos commit $ interior e $ return (ExtensionEvent a0) `apply` optional (parseSchemaType "adjustedExerciseDate") `apply` optional (parseSchemaType "adjustedExtendedTerminationDate") schemaTypeToXML s x@ExtensionEvent{} = toXMLElement s [ maybe [] (toXMLAttribute "id") $ extensEvent_ID x ] [ maybe [] (schemaTypeToXML "adjustedExerciseDate") $ extensEvent_adjustedExerciseDate x , maybe [] (schemaTypeToXML "adjustedExtendedTerminationDate") $ extensEvent_adjustedExtendedTerminationDate x ] -- | A type to define business date convention adjustment to -- final payment period per leg. data FinalCalculationPeriodDateAdjustment = FinalCalculationPeriodDateAdjustment { 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. } deriving (Eq,Show) instance SchemaType FinalCalculationPeriodDateAdjustment where parseSchemaType s = do (pos,e) <- posnElement [s] commit $ interior e $ return FinalCalculationPeriodDateAdjustment `apply` optional (parseSchemaType "relevantUnderlyingDateReference") `apply` parseSchemaType "swapStreamReference" `apply` optional (parseSchemaType "businessDayConvention") schemaTypeToXML s x@FinalCalculationPeriodDateAdjustment{} = toXMLElement s [] [ maybe [] (schemaTypeToXML "relevantUnderlyingDateReference") $ fcpda_relevantUnderlyingDateReference x , schemaTypeToXML "swapStreamReference" $ fcpda_swapStreamReference x , maybe [] (schemaTypeToXML "businessDayConvention") $ fcpda_businessDayConvention x ] -- | The method, prioritzed by the order it is listed in this -- element, to get a replacement rate for the disrupted -- settlement rate option. data FallbackReferencePrice = FallbackReferencePrice { 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. } deriving (Eq,Show) instance SchemaType FallbackReferencePrice where parseSchemaType s = do (pos,e) <- posnElement [s] commit $ interior e $ return FallbackReferencePrice `apply` optional (parseSchemaType "valuationPostponement") `apply` many (parseSchemaType "fallbackSettlementRateOption") `apply` optional (parseSchemaType "fallbackSurveyValuationPostponenment") `apply` optional (parseSchemaType "calculationAgentDetermination") schemaTypeToXML s x@FallbackReferencePrice{} = toXMLElement s [] [ maybe [] (schemaTypeToXML "valuationPostponement") $ fallbRefPrice_valuationPostponement x , concatMap (schemaTypeToXML "fallbackSettlementRateOption") $ fallbRefPrice_fallbackSettlementRateOption x , maybe [] (schemaTypeToXML "fallbackSurveyValuationPostponenment") $ fallbRefPrice_fallbackSurveyValuationPostponenment x , maybe [] (schemaTypeToXML "calculationAgentDetermination") $ fallbRefPrice_calculationAgentDetermination x ] -- | A type defining parameters associated with a floating rate -- reset. This type forms part of the cashflows representation -- of a stream. data FloatingRateDefinition = FloatingRateDefinition { floatRateDefin_calculatedRate :: Maybe Xsd.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 Xsd.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 Xsd.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. } deriving (Eq,Show) instance SchemaType FloatingRateDefinition where parseSchemaType s = do (pos,e) <- posnElement [s] commit $ interior e $ return FloatingRateDefinition `apply` optional (parseSchemaType "calculatedRate") `apply` many (parseSchemaType "rateObservation") `apply` optional (parseSchemaType "floatingRateMultiplier") `apply` optional (parseSchemaType "spread") `apply` many (parseSchemaType "capRate") `apply` many (parseSchemaType "floorRate") schemaTypeToXML s x@FloatingRateDefinition{} = toXMLElement s [] [ maybe [] (schemaTypeToXML "calculatedRate") $ floatRateDefin_calculatedRate x , concatMap (schemaTypeToXML "rateObservation") $ floatRateDefin_rateObservation x , maybe [] (schemaTypeToXML "floatingRateMultiplier") $ floatRateDefin_floatingRateMultiplier x , maybe [] (schemaTypeToXML "spread") $ floatRateDefin_spread x , concatMap (schemaTypeToXML "capRate") $ floatRateDefin_capRate x , concatMap (schemaTypeToXML "floorRate") $ floatRateDefin_floorRate x ] -- | A type defining a Forward Rate Agreement (FRA) product. data Fra = Fra { fra_ID :: Maybe Xsd.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 :: Xsd.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 Xsd.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 :: Xsd.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. } deriving (Eq,Show) instance SchemaType Fra where parseSchemaType s = do (pos,e) <- posnElement [s] a0 <- optional $ getAttribute "id" e pos commit $ interior e $ return (Fra a0) `apply` optional (parseSchemaType "primaryAssetClass") `apply` many (parseSchemaType "secondaryAssetClass") `apply` many (parseSchemaType "productType") `apply` many (parseSchemaType "productId") `apply` optional (parseSchemaType "buyerPartyReference") `apply` optional (parseSchemaType "buyerAccountReference") `apply` optional (parseSchemaType "sellerPartyReference") `apply` optional (parseSchemaType "sellerAccountReference") `apply` parseSchemaType "adjustedEffectiveDate" `apply` parseSchemaType "adjustedTerminationDate" `apply` optional (parseSchemaType "paymentDate") `apply` optional (parseSchemaType "fixingDateOffset") `apply` parseSchemaType "dayCountFraction" `apply` optional (parseSchemaType "calculationPeriodNumberOfDays") `apply` parseSchemaType "notional" `apply` parseSchemaType "fixedRate" `apply` parseSchemaType "floatingRateIndex" `apply` many1 (parseSchemaType "indexTenor") `apply` optional (parseSchemaType "fraDiscounting") schemaTypeToXML s x@Fra{} = toXMLElement s [ maybe [] (toXMLAttribute "id") $ fra_ID x ] [ maybe [] (schemaTypeToXML "primaryAssetClass") $ fra_primaryAssetClass x , concatMap (schemaTypeToXML "secondaryAssetClass") $ fra_secondaryAssetClass x , concatMap (schemaTypeToXML "productType") $ fra_productType x , concatMap (schemaTypeToXML "productId") $ fra_productId x , maybe [] (schemaTypeToXML "buyerPartyReference") $ fra_buyerPartyReference x , maybe [] (schemaTypeToXML "buyerAccountReference") $ fra_buyerAccountReference x , maybe [] (schemaTypeToXML "sellerPartyReference") $ fra_sellerPartyReference x , maybe [] (schemaTypeToXML "sellerAccountReference") $ fra_sellerAccountReference x , schemaTypeToXML "adjustedEffectiveDate" $ fra_adjustedEffectiveDate x , schemaTypeToXML "adjustedTerminationDate" $ fra_adjustedTerminationDate x , maybe [] (schemaTypeToXML "paymentDate") $ fra_paymentDate x , maybe [] (schemaTypeToXML "fixingDateOffset") $ fra_fixingDateOffset x , schemaTypeToXML "dayCountFraction" $ fra_dayCountFraction x , maybe [] (schemaTypeToXML "calculationPeriodNumberOfDays") $ fra_calculationPeriodNumberOfDays x , schemaTypeToXML "notional" $ fra_notional x , schemaTypeToXML "fixedRate" $ fra_fixedRate x , schemaTypeToXML "floatingRateIndex" $ fra_floatingRateIndex x , concatMap (schemaTypeToXML "indexTenor") $ fra_indexTenor x , maybe [] (schemaTypeToXML "fraDiscounting") $ fra_discounting x ] instance Extension Fra Product where supertype v = Product_Fra v -- | 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. data FxFixingDate = FxFixingDate { fxFixingDate_ID :: Maybe Xsd.ID , fxFixingDate_periodMultiplier :: Xsd.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. } deriving (Eq,Show) instance SchemaType FxFixingDate where parseSchemaType s = do (pos,e) <- posnElement [s] a0 <- optional $ getAttribute "id" e pos commit $ interior e $ return (FxFixingDate a0) `apply` parseSchemaType "periodMultiplier" `apply` parseSchemaType "period" `apply` optional (parseSchemaType "dayType") `apply` optional (parseSchemaType "businessDayConvention") `apply` optional (oneOf' [ ("BusinessCentersReference", fmap OneOf2 (parseSchemaType "businessCentersReference")) , ("BusinessCenters", fmap TwoOf2 (parseSchemaType "businessCenters")) ]) `apply` optional (oneOf' [ ("DateRelativeToPaymentDates", fmap OneOf2 (parseSchemaType "dateRelativeToPaymentDates")) , ("DateRelativeToCalculationPeriodDates", fmap TwoOf2 (parseSchemaType "dateRelativeToCalculationPeriodDates")) ]) schemaTypeToXML s x@FxFixingDate{} = toXMLElement s [ maybe [] (toXMLAttribute "id") $ fxFixingDate_ID x ] [ schemaTypeToXML "periodMultiplier" $ fxFixingDate_periodMultiplier x , schemaTypeToXML "period" $ fxFixingDate_period x , maybe [] (schemaTypeToXML "dayType") $ fxFixingDate_dayType x , maybe [] (schemaTypeToXML "businessDayConvention") $ fxFixingDate_businessDayConvention x , maybe [] (foldOneOf2 (schemaTypeToXML "businessCentersReference") (schemaTypeToXML "businessCenters") ) $ fxFixingDate_choice4 x , maybe [] (foldOneOf2 (schemaTypeToXML "dateRelativeToPaymentDates") (schemaTypeToXML "dateRelativeToCalculationPeriodDates") ) $ fxFixingDate_choice5 x ] instance Extension FxFixingDate Offset where supertype (FxFixingDate a0 e0 e1 e2 e3 e4 e5) = Offset a0 e0 e1 e2 instance Extension FxFixingDate Period where supertype = (supertype :: Offset -> Period) . (supertype :: FxFixingDate -> Offset) -- | A type to describe the cashflow representation for fx -- linked notionals. data FxLinkedNotionalAmount = FxLinkedNotionalAmount { fxLinkedNotionAmount_resetDate :: Maybe Xsd.Date , fxLinkedNotionAmount_adjustedFxSpotFixingDate :: Maybe Xsd.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 Xsd.Decimal -- ^ The actual observed fx spot rate. , fxLinkedNotionAmount_notionalAmount :: Maybe Xsd.Decimal -- ^ The calculation period notional amount. } deriving (Eq,Show) instance SchemaType FxLinkedNotionalAmount where parseSchemaType s = do (pos,e) <- posnElement [s] commit $ interior e $ return FxLinkedNotionalAmount `apply` optional (parseSchemaType "resetDate") `apply` optional (parseSchemaType "adjustedFxSpotFixingDate") `apply` optional (parseSchemaType "observedFxSpotRate") `apply` optional (parseSchemaType "notionalAmount") schemaTypeToXML s x@FxLinkedNotionalAmount{} = toXMLElement s [] [ maybe [] (schemaTypeToXML "resetDate") $ fxLinkedNotionAmount_resetDate x , maybe [] (schemaTypeToXML "adjustedFxSpotFixingDate") $ fxLinkedNotionAmount_adjustedFxSpotFixingDate x , maybe [] (schemaTypeToXML "observedFxSpotRate") $ fxLinkedNotionAmount_observedFxSpotRate x , maybe [] (schemaTypeToXML "notionalAmount") $ fxLinkedNotionAmount_notionalAmount x ] -- | 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. data FxLinkedNotionalSchedule = FxLinkedNotionalSchedule { 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 Xsd.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). } deriving (Eq,Show) instance SchemaType FxLinkedNotionalSchedule where parseSchemaType s = do (pos,e) <- posnElement [s] commit $ interior e $ return FxLinkedNotionalSchedule `apply` optional (parseSchemaType "constantNotionalScheduleReference") `apply` optional (parseSchemaType "initialValue") `apply` optional (parseSchemaType "varyingNotionalCurrency") `apply` optional (parseSchemaType "varyingNotionalFixingDates") `apply` optional (parseSchemaType "fxSpotRateSource") `apply` optional (parseSchemaType "varyingNotionalInterimExchangePaymentDates") schemaTypeToXML s x@FxLinkedNotionalSchedule{} = toXMLElement s [] [ maybe [] (schemaTypeToXML "constantNotionalScheduleReference") $ fxLinkedNotionSched_constantNotionalScheduleReference x , maybe [] (schemaTypeToXML "initialValue") $ fxLinkedNotionSched_initialValue x , maybe [] (schemaTypeToXML "varyingNotionalCurrency") $ fxLinkedNotionSched_varyingNotionalCurrency x , maybe [] (schemaTypeToXML "varyingNotionalFixingDates") $ fxLinkedNotionSched_varyingNotionalFixingDates x , maybe [] (schemaTypeToXML "fxSpotRateSource") $ fxLinkedNotionSched_fxSpotRateSource x , maybe [] (schemaTypeToXML "varyingNotionalInterimExchangePaymentDates") $ fxLinkedNotionSched_varyingNotionalInterimExchangePaymentDates x ] -- | A type defining the components specifiying an Inflation -- Rate Calculation data InflationRateCalculation = InflationRateCalculation { inflatRateCalc_ID :: Maybe Xsd.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 Xsd.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 Xsd.Decimal -- ^ initial known index level for the first calculation period. , inflatRateCalc_fallbackBondApplicable :: Maybe Xsd.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. } deriving (Eq,Show) instance SchemaType InflationRateCalculation where parseSchemaType s = do (pos,e) <- posnElement [s] a0 <- optional $ getAttribute "id" e pos commit $ interior e $ return (InflationRateCalculation a0) `apply` parseSchemaType "floatingRateIndex" `apply` optional (parseSchemaType "indexTenor") `apply` optional (parseSchemaType "floatingRateMultiplierSchedule") `apply` many (parseSchemaType "spreadSchedule") `apply` optional (parseSchemaType "rateTreatment") `apply` many (parseSchemaType "capRateSchedule") `apply` many (parseSchemaType "floorRateSchedule") `apply` optional (parseSchemaType "initialRate") `apply` optional (parseSchemaType "finalRateRounding") `apply` optional (parseSchemaType "averagingMethod") `apply` optional (parseSchemaType "negativeInterestRateTreatment") `apply` optional (parseSchemaType "inflationLag") `apply` optional (parseSchemaType "indexSource") `apply` optional (parseSchemaType "mainPublication") `apply` optional (parseSchemaType "interpolationMethod") `apply` optional (parseSchemaType "initialIndexLevel") `apply` optional (parseSchemaType "fallbackBondApplicable") schemaTypeToXML s x@InflationRateCalculation{} = toXMLElement s [ maybe [] (toXMLAttribute "id") $ inflatRateCalc_ID x ] [ schemaTypeToXML "floatingRateIndex" $ inflatRateCalc_floatingRateIndex x , maybe [] (schemaTypeToXML "indexTenor") $ inflatRateCalc_indexTenor x , maybe [] (schemaTypeToXML "floatingRateMultiplierSchedule") $ inflatRateCalc_floatingRateMultiplierSchedule x , concatMap (schemaTypeToXML "spreadSchedule") $ inflatRateCalc_spreadSchedule x , maybe [] (schemaTypeToXML "rateTreatment") $ inflatRateCalc_rateTreatment x , concatMap (schemaTypeToXML "capRateSchedule") $ inflatRateCalc_capRateSchedule x , concatMap (schemaTypeToXML "floorRateSchedule") $ inflatRateCalc_floorRateSchedule x , maybe [] (schemaTypeToXML "initialRate") $ inflatRateCalc_initialRate x , maybe [] (schemaTypeToXML "finalRateRounding") $ inflatRateCalc_finalRateRounding x , maybe [] (schemaTypeToXML "averagingMethod") $ inflatRateCalc_averagingMethod x , maybe [] (schemaTypeToXML "negativeInterestRateTreatment") $ inflatRateCalc_negativeInterestRateTreatment x , maybe [] (schemaTypeToXML "inflationLag") $ inflatRateCalc_inflationLag x , maybe [] (schemaTypeToXML "indexSource") $ inflatRateCalc_indexSource x , maybe [] (schemaTypeToXML "mainPublication") $ inflatRateCalc_mainPublication x , maybe [] (schemaTypeToXML "interpolationMethod") $ inflatRateCalc_interpolationMethod x , maybe [] (schemaTypeToXML "initialIndexLevel") $ inflatRateCalc_initialIndexLevel x , maybe [] (schemaTypeToXML "fallbackBondApplicable") $ inflatRateCalc_fallbackBondApplicable x ] instance Extension InflationRateCalculation FloatingRateCalculation where supertype (InflationRateCalculation a0 e0 e1 e2 e3 e4 e5 e6 e7 e8 e9 e10 e11 e12 e13 e14 e15 e16) = FloatingRateCalculation a0 e0 e1 e2 e3 e4 e5 e6 e7 e8 e9 e10 instance Extension InflationRateCalculation FloatingRate where supertype = (supertype :: FloatingRateCalculation -> FloatingRate) . (supertype :: InflationRateCalculation -> FloatingRateCalculation) instance Extension InflationRateCalculation Rate where supertype = (supertype :: FloatingRate -> Rate) . (supertype :: FloatingRateCalculation -> FloatingRate) . (supertype :: InflationRateCalculation -> FloatingRateCalculation) -- | A type defining the components specifiying an interest rate -- stream, including both a parametric and cashflow -- representation for the stream of payments. data InterestRateStream = InterestRateStream { interRateStream_ID :: Maybe Xsd.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. } deriving (Eq,Show) instance SchemaType InterestRateStream where parseSchemaType s = do (pos,e) <- posnElement [s] a0 <- optional $ getAttribute "id" e pos commit $ interior e $ return (InterestRateStream a0) `apply` optional (parseSchemaType "payerPartyReference") `apply` optional (parseSchemaType "payerAccountReference") `apply` optional (parseSchemaType "receiverPartyReference") `apply` optional (parseSchemaType "receiverAccountReference") `apply` parseSchemaType "calculationPeriodDates" `apply` parseSchemaType "paymentDates" `apply` optional (parseSchemaType "resetDates") `apply` parseSchemaType "calculationPeriodAmount" `apply` optional (parseSchemaType "stubCalculationPeriodAmount") `apply` optional (parseSchemaType "principalExchanges") `apply` optional (parseSchemaType "cashflows") `apply` optional (parseSchemaType "settlementProvision") `apply` optional (parseSchemaType "formula") schemaTypeToXML s x@InterestRateStream{} = toXMLElement s [ maybe [] (toXMLAttribute "id") $ interRateStream_ID x ] [ maybe [] (schemaTypeToXML "payerPartyReference") $ interRateStream_payerPartyReference x , maybe [] (schemaTypeToXML "payerAccountReference") $ interRateStream_payerAccountReference x , maybe [] (schemaTypeToXML "receiverPartyReference") $ interRateStream_receiverPartyReference x , maybe [] (schemaTypeToXML "receiverAccountReference") $ interRateStream_receiverAccountReference x , schemaTypeToXML "calculationPeriodDates" $ interRateStream_calculationPeriodDates x , schemaTypeToXML "paymentDates" $ interRateStream_paymentDates x , maybe [] (schemaTypeToXML "resetDates") $ interRateStream_resetDates x , schemaTypeToXML "calculationPeriodAmount" $ interRateStream_calculationPeriodAmount x , maybe [] (schemaTypeToXML "stubCalculationPeriodAmount") $ interRateStream_stubCalculationPeriodAmount x , maybe [] (schemaTypeToXML "principalExchanges") $ interRateStream_principalExchanges x , maybe [] (schemaTypeToXML "cashflows") $ interRateStream_cashflows x , maybe [] (schemaTypeToXML "settlementProvision") $ interRateStream_settlementProvision x , maybe [] (schemaTypeToXML "formula") $ interRateStream_formula x ] instance Extension InterestRateStream Leg where supertype v = Leg_InterestRateStream v -- | Reference to an InterestRateStream component. data InterestRateStreamReference = InterestRateStreamReference { interRateStreamRef_href :: Xsd.IDREF } deriving (Eq,Show) instance SchemaType InterestRateStreamReference where parseSchemaType s = do (pos,e) <- posnElement [s] a0 <- getAttribute "href" e pos commit $ interior e $ return (InterestRateStreamReference a0) schemaTypeToXML s x@InterestRateStreamReference{} = toXMLElement s [ toXMLAttribute "href" $ interRateStreamRef_href x ] [] instance Extension InterestRateStreamReference Reference where supertype v = Reference_InterestRateStreamReference v -- | A type to define an early termination provision for which -- exercise is mandatory. data MandatoryEarlyTermination = MandatoryEarlyTermination { mandatEarlyTermin_ID :: Maybe Xsd.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. } deriving (Eq,Show) instance SchemaType MandatoryEarlyTermination where parseSchemaType s = do (pos,e) <- posnElement [s] a0 <- optional $ getAttribute "id" e pos commit $ interior e $ return (MandatoryEarlyTermination a0) `apply` optional (parseSchemaType "mandatoryEarlyTerminationDate") `apply` optional (parseSchemaType "calculationAgent") `apply` optional (parseSchemaType "cashSettlement") `apply` optional (parseSchemaType "mandatoryEarlyTerminationAdjustedDates") schemaTypeToXML s x@MandatoryEarlyTermination{} = toXMLElement s [ maybe [] (toXMLAttribute "id") $ mandatEarlyTermin_ID x ] [ maybe [] (schemaTypeToXML "mandatoryEarlyTerminationDate") $ mandatoryEarlyTermination_date x , maybe [] (schemaTypeToXML "calculationAgent") $ mandatEarlyTermin_calculationAgent x , maybe [] (schemaTypeToXML "cashSettlement") $ mandatEarlyTermin_cashSettlement x , maybe [] (schemaTypeToXML "mandatoryEarlyTerminationAdjustedDates") $ mandatoryEarlyTermination_adjustedDates x ] -- | A type defining the adjusted dates associated with a -- mandatory early termination provision. data MandatoryEarlyTerminationAdjustedDates = MandatoryEarlyTerminationAdjustedDates { metad_adjustedEarlyTerminationDate :: Maybe Xsd.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 Xsd.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 Xsd.Date -- ^ The date on which the cash settlement amount is paid. This -- date should already be adjusted for any applicable business -- dat convention. } deriving (Eq,Show) instance SchemaType MandatoryEarlyTerminationAdjustedDates where parseSchemaType s = do (pos,e) <- posnElement [s] commit $ interior e $ return MandatoryEarlyTerminationAdjustedDates `apply` optional (parseSchemaType "adjustedEarlyTerminationDate") `apply` optional (parseSchemaType "adjustedCashSettlementValuationDate") `apply` optional (parseSchemaType "adjustedCashSettlementPaymentDate") schemaTypeToXML s x@MandatoryEarlyTerminationAdjustedDates{} = toXMLElement s [] [ maybe [] (schemaTypeToXML "adjustedEarlyTerminationDate") $ metad_adjustedEarlyTerminationDate x , maybe [] (schemaTypeToXML "adjustedCashSettlementValuationDate") $ metad_adjustedCashSettlementValuationDate x , maybe [] (schemaTypeToXML "adjustedCashSettlementPaymentDate") $ metad_adjustedCashSettlementPaymentDate x ] -- | A type defining the parameters used when the reference -- currency of the swapStream is non-deliverable. data NonDeliverableSettlement = NonDeliverableSettlement { 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. } deriving (Eq,Show) instance SchemaType NonDeliverableSettlement where parseSchemaType s = do (pos,e) <- posnElement [s] commit $ interior e $ return NonDeliverableSettlement `apply` optional (parseSchemaType "referenceCurrency") `apply` optional (oneOf' [ ("FxFixingDate", fmap OneOf2 (parseSchemaType "fxFixingDate")) , ("AdjustableDates", fmap TwoOf2 (parseSchemaType "fxFixingSchedule")) ]) `apply` optional (parseSchemaType "settlementRateOption") `apply` optional (parseSchemaType "priceSourceDisruption") schemaTypeToXML s x@NonDeliverableSettlement{} = toXMLElement s [] [ maybe [] (schemaTypeToXML "referenceCurrency") $ nonDelivSettl_referenceCurrency x , maybe [] (foldOneOf2 (schemaTypeToXML "fxFixingDate") (schemaTypeToXML "fxFixingSchedule") ) $ nonDelivSettl_choice1 x , maybe [] (schemaTypeToXML "settlementRateOption") $ nonDelivSettl_settlementRateOption x , maybe [] (schemaTypeToXML "priceSourceDisruption") $ nonDelivSettl_priceSourceDisruption x ] -- | 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. data Notional = Notional { notional_ID :: Maybe Xsd.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. } deriving (Eq,Show) instance SchemaType Notional where parseSchemaType s = do (pos,e) <- posnElement [s] a0 <- optional $ getAttribute "id" e pos commit $ interior e $ return (Notional a0) `apply` parseSchemaType "notionalStepSchedule" `apply` optional (parseSchemaType "notionalStepParameters") schemaTypeToXML s x@Notional{} = toXMLElement s [ maybe [] (toXMLAttribute "id") $ notional_ID x ] [ schemaTypeToXML "notionalStepSchedule" $ notional_stepSchedule x , maybe [] (schemaTypeToXML "notionalStepParameters") $ notional_stepParameters x ] -- | 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. data NotionalStepRule = NotionalStepRule { 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 Xsd.Date -- ^ Effective date of the first change in notional (i.e. a -- calculation period start date). , notionStepRule_lastNotionalStepDate :: Maybe Xsd.Date -- ^ Effective date of the last change in notional (i.e. a -- calculation period start date). , notionStepRule_choice4 :: (Maybe (OneOf2 Xsd.Decimal ((Maybe (Xsd.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. } deriving (Eq,Show) instance SchemaType NotionalStepRule where parseSchemaType s = do (pos,e) <- posnElement [s] commit $ interior e $ return NotionalStepRule `apply` optional (parseSchemaType "calculationPeriodDatesReference") `apply` optional (parseSchemaType "stepFrequency") `apply` optional (parseSchemaType "firstNotionalStepDate") `apply` optional (parseSchemaType "lastNotionalStepDate") `apply` optional (oneOf' [ ("Xsd.Decimal", fmap OneOf2 (parseSchemaType "notionalStepAmount")) , ("Maybe Xsd.Decimal Maybe StepRelativeToEnum", fmap TwoOf2 (return (,) `apply` optional (parseSchemaType "notionalStepRate") `apply` optional (parseSchemaType "stepRelativeTo"))) ]) schemaTypeToXML s x@NotionalStepRule{} = toXMLElement s [] [ maybe [] (schemaTypeToXML "calculationPeriodDatesReference") $ notionStepRule_calculationPeriodDatesReference x , maybe [] (schemaTypeToXML "stepFrequency") $ notionStepRule_stepFrequency x , maybe [] (schemaTypeToXML "firstNotionalStepDate") $ notionStepRule_firstNotionalStepDate x , maybe [] (schemaTypeToXML "lastNotionalStepDate") $ notionStepRule_lastNotionalStepDate x , maybe [] (foldOneOf2 (schemaTypeToXML "notionalStepAmount") (\ (a,b) -> concat [ maybe [] (schemaTypeToXML "notionalStepRate") a , maybe [] (schemaTypeToXML "stepRelativeTo") b ]) ) $ notionStepRule_choice4 x ] -- | A type defining an early termination provision where either -- or both parties have the right to exercise. data OptionalEarlyTermination = OptionalEarlyTermination { 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 Xsd.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. } deriving (Eq,Show) instance SchemaType OptionalEarlyTermination where parseSchemaType s = do (pos,e) <- posnElement [s] commit $ interior e $ return OptionalEarlyTermination `apply` optional (parseSchemaType "singlePartyOption") `apply` optional (elementExercise) `apply` many (parseSchemaType "exerciseNotice") `apply` optional (parseSchemaType "followUpConfirmation") `apply` optional (parseSchemaType "calculationAgent") `apply` optional (parseSchemaType "cashSettlement") `apply` optional (parseSchemaType "optionalEarlyTerminationAdjustedDates") schemaTypeToXML s x@OptionalEarlyTermination{} = toXMLElement s [] [ maybe [] (schemaTypeToXML "singlePartyOption") $ optionEarlyTermin_singlePartyOption x , maybe [] (elementToXMLExercise) $ optionEarlyTermin_exercise x , concatMap (schemaTypeToXML "exerciseNotice") $ optionEarlyTermin_exerciseNotice x , maybe [] (schemaTypeToXML "followUpConfirmation") $ optionEarlyTermin_followUpConfirmation x , maybe [] (schemaTypeToXML "calculationAgent") $ optionEarlyTermin_calculationAgent x , maybe [] (schemaTypeToXML "cashSettlement") $ optionEarlyTermin_cashSettlement x , maybe [] (schemaTypeToXML "optionalEarlyTerminationAdjustedDates") $ optionalEarlyTermination_adjustedDates x ] -- | A type defining the adjusted dates associated with an -- optional early termination provision. data OptionalEarlyTerminationAdjustedDates = OptionalEarlyTerminationAdjustedDates { oetad_earlyTerminationEvent :: [EarlyTerminationEvent] -- ^ The adjusted dates associated with an individual earley -- termination date. } deriving (Eq,Show) instance SchemaType OptionalEarlyTerminationAdjustedDates where parseSchemaType s = do (pos,e) <- posnElement [s] commit $ interior e $ return OptionalEarlyTerminationAdjustedDates `apply` many (parseSchemaType "earlyTerminationEvent") schemaTypeToXML s x@OptionalEarlyTerminationAdjustedDates{} = toXMLElement s [] [ concatMap (schemaTypeToXML "earlyTerminationEvent") $ oetad_earlyTerminationEvent x ] -- | 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. data PaymentCalculationPeriod = PaymentCalculationPeriod { paymentCalcPeriod_ID :: Maybe Xsd.ID , paymentCalcPeriod_href :: Maybe Xsd.IDREF -- ^ Attribute that can be used to reference the yield curve -- used to estimate the discount factor. , paymentCalcPeriod_unadjustedPaymentDate :: Maybe Xsd.Date , paymentCalcPeriod_adjustedPaymentDate :: Maybe Xsd.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] Xsd.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 Xsd.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. } deriving (Eq,Show) instance SchemaType PaymentCalculationPeriod where parseSchemaType s = do (pos,e) <- posnElement [s] a0 <- optional $ getAttribute "id" e pos a1 <- optional $ getAttribute "href" e pos commit $ interior e $ return (PaymentCalculationPeriod a0 a1) `apply` optional (parseSchemaType "unadjustedPaymentDate") `apply` optional (parseSchemaType "adjustedPaymentDate") `apply` optional (oneOf' [ ("[CalculationPeriod]", fmap OneOf2 (many1 (parseSchemaType "calculationPeriod"))) , ("Xsd.Decimal", fmap TwoOf2 (parseSchemaType "fixedPaymentAmount")) ]) `apply` optional (parseSchemaType "discountFactor") `apply` optional (parseSchemaType "forecastPaymentAmount") `apply` optional (parseSchemaType "presentValueAmount") schemaTypeToXML s x@PaymentCalculationPeriod{} = toXMLElement s [ maybe [] (toXMLAttribute "id") $ paymentCalcPeriod_ID x , maybe [] (toXMLAttribute "href") $ paymentCalcPeriod_href x ] [ maybe [] (schemaTypeToXML "unadjustedPaymentDate") $ paymentCalcPeriod_unadjustedPaymentDate x , maybe [] (schemaTypeToXML "adjustedPaymentDate") $ paymentCalcPeriod_adjustedPaymentDate x , maybe [] (foldOneOf2 (concatMap (schemaTypeToXML "calculationPeriod")) (schemaTypeToXML "fixedPaymentAmount") ) $ paymentCalcPeriod_choice2 x , maybe [] (schemaTypeToXML "discountFactor") $ paymentCalcPeriod_discountFactor x , maybe [] (schemaTypeToXML "forecastPaymentAmount") $ paymentCalcPeriod_forecastPaymentAmount x , maybe [] (schemaTypeToXML "presentValueAmount") $ paymentCalcPeriod_presentValueAmount x ] instance Extension PaymentCalculationPeriod PaymentBase where supertype v = PaymentBase_PaymentCalculationPeriod v -- | 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. data PaymentDates = PaymentDates { paymentDates_ID :: Maybe Xsd.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 -- settlemementProvision/nonDeliverableSettlement/fxFixingDate -- 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 -- swap\swapStream\calculationPerioDates\effectiveDate and the -- swap\swapStream\calculationPerioDates\terminationDate. , paymentDates_firstPaymentDate :: Maybe Xsd.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 Xsd.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. } deriving (Eq,Show) instance SchemaType PaymentDates where parseSchemaType s = do (pos,e) <- posnElement [s] a0 <- optional $ getAttribute "id" e pos commit $ interior e $ return (PaymentDates a0) `apply` optional (oneOf' [ ("CalculationPeriodDatesReference", fmap OneOf3 (parseSchemaType "calculationPeriodDatesReference")) , ("ResetDatesReference", fmap TwoOf3 (parseSchemaType "resetDatesReference")) , ("ValuationDatesReference", fmap ThreeOf3 (parseSchemaType "valuationDatesReference")) ]) `apply` parseSchemaType "paymentFrequency" `apply` optional (parseSchemaType "firstPaymentDate") `apply` optional (parseSchemaType "lastRegularPaymentDate") `apply` optional (parseSchemaType "payRelativeTo") `apply` optional (parseSchemaType "paymentDaysOffset") `apply` optional (parseSchemaType "paymentDatesAdjustments") schemaTypeToXML s x@PaymentDates{} = toXMLElement s [ maybe [] (toXMLAttribute "id") $ paymentDates_ID x ] [ maybe [] (foldOneOf3 (schemaTypeToXML "calculationPeriodDatesReference") (schemaTypeToXML "resetDatesReference") (schemaTypeToXML "valuationDatesReference") ) $ paymentDates_choice0 x , schemaTypeToXML "paymentFrequency" $ paymentDates_paymentFrequency x , maybe [] (schemaTypeToXML "firstPaymentDate") $ paymentDates_firstPaymentDate x , maybe [] (schemaTypeToXML "lastRegularPaymentDate") $ paymentDates_lastRegularPaymentDate x , maybe [] (schemaTypeToXML "payRelativeTo") $ paymentDates_payRelativeTo x , maybe [] (schemaTypeToXML "paymentDaysOffset") $ paymentDates_paymentDaysOffset x , maybe [] (schemaTypeToXML "paymentDatesAdjustments") $ paymentDates_adjustments x ] -- | Reference to a payment dates structure. data PaymentDatesReference = PaymentDatesReference { paymentDatesRef_href :: Xsd.IDREF } deriving (Eq,Show) instance SchemaType PaymentDatesReference where parseSchemaType s = do (pos,e) <- posnElement [s] a0 <- getAttribute "href" e pos commit $ interior e $ return (PaymentDatesReference a0) schemaTypeToXML s x@PaymentDatesReference{} = toXMLElement s [ toXMLAttribute "href" $ paymentDatesRef_href x ] [] instance Extension PaymentDatesReference Reference where supertype v = Reference_PaymentDatesReference v -- | A type defining the parameters used to get a price quote to -- replace the settlement rate option that is disrupted. data PriceSourceDisruption = PriceSourceDisruption { 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. } deriving (Eq,Show) instance SchemaType PriceSourceDisruption where parseSchemaType s = do (pos,e) <- posnElement [s] commit $ interior e $ return PriceSourceDisruption `apply` optional (parseSchemaType "fallbackReferencePrice") schemaTypeToXML s x@PriceSourceDisruption{} = toXMLElement s [] [ maybe [] (schemaTypeToXML "fallbackReferencePrice") $ priceSourceDisrup_fallbackReferencePrice x ] -- | A type defining a principal exchange amount and adjusted -- exchange date. The type forms part of the cashflow -- representation of a swap stream. data PrincipalExchange = PrincipalExchange { princExch_ID :: Maybe Xsd.ID , princExch_unadjustedPrincipalExchangeDate :: Maybe Xsd.Date , princExch_adjustedPrincipalExchangeDate :: Maybe Xsd.Date -- ^ The principal exchange date. This date should already be -- adjusted for any applicable business day convention. , principalExchange_amount :: Maybe Xsd.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 Xsd.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. } deriving (Eq,Show) instance SchemaType PrincipalExchange where parseSchemaType s = do (pos,e) <- posnElement [s] a0 <- optional $ getAttribute "id" e pos commit $ interior e $ return (PrincipalExchange a0) `apply` optional (parseSchemaType "unadjustedPrincipalExchangeDate") `apply` optional (parseSchemaType "adjustedPrincipalExchangeDate") `apply` optional (parseSchemaType "principalExchangeAmount") `apply` optional (parseSchemaType "discountFactor") `apply` optional (parseSchemaType "presentValuePrincipalExchangeAmount") schemaTypeToXML s x@PrincipalExchange{} = toXMLElement s [ maybe [] (toXMLAttribute "id") $ princExch_ID x ] [ maybe [] (schemaTypeToXML "unadjustedPrincipalExchangeDate") $ princExch_unadjustedPrincipalExchangeDate x , maybe [] (schemaTypeToXML "adjustedPrincipalExchangeDate") $ princExch_adjustedPrincipalExchangeDate x , maybe [] (schemaTypeToXML "principalExchangeAmount") $ principalExchange_amount x , maybe [] (schemaTypeToXML "discountFactor") $ princExch_discountFactor x , maybe [] (schemaTypeToXML "presentValuePrincipalExchangeAmount") $ princExch_presentValuePrincipalExchangeAmount x ] -- | Reference to relevant underlying date. data RelevantUnderlyingDateReference = RelevantUnderlyingDateReference { relevUnderlyDateRef_href :: Xsd.IDREF } deriving (Eq,Show) instance SchemaType RelevantUnderlyingDateReference where parseSchemaType s = do (pos,e) <- posnElement [s] a0 <- getAttribute "href" e pos commit $ interior e $ return (RelevantUnderlyingDateReference a0) schemaTypeToXML s x@RelevantUnderlyingDateReference{} = toXMLElement s [ toXMLAttribute "href" $ relevUnderlyDateRef_href x ] [] instance Extension RelevantUnderlyingDateReference Reference where supertype v = Reference_RelevantUnderlyingDateReference v -- | 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. data ResetDates = ResetDates { resetDates_ID :: Maybe Xsd.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. } deriving (Eq,Show) instance SchemaType ResetDates where parseSchemaType s = do (pos,e) <- posnElement [s] a0 <- optional $ getAttribute "id" e pos commit $ interior e $ return (ResetDates a0) `apply` optional (parseSchemaType "calculationPeriodDatesReference") `apply` optional (parseSchemaType "resetRelativeTo") `apply` optional (parseSchemaType "initialFixingDate") `apply` optional (parseSchemaType "fixingDates") `apply` optional (parseSchemaType "rateCutOffDaysOffset") `apply` parseSchemaType "resetFrequency" `apply` optional (parseSchemaType "resetDatesAdjustments") schemaTypeToXML s x@ResetDates{} = toXMLElement s [ maybe [] (toXMLAttribute "id") $ resetDates_ID x ] [ maybe [] (schemaTypeToXML "calculationPeriodDatesReference") $ resetDates_calculationPeriodDatesReference x , maybe [] (schemaTypeToXML "resetRelativeTo") $ resetDates_resetRelativeTo x , maybe [] (schemaTypeToXML "initialFixingDate") $ resetDates_initialFixingDate x , maybe [] (schemaTypeToXML "fixingDates") $ resetDates_fixingDates x , maybe [] (schemaTypeToXML "rateCutOffDaysOffset") $ resetDates_rateCutOffDaysOffset x , schemaTypeToXML "resetFrequency" $ resetDates_resetFrequency x , maybe [] (schemaTypeToXML "resetDatesAdjustments") $ resetDates_adjustments x ] -- | Reference to a reset dates component. data ResetDatesReference = ResetDatesReference { resetDatesRef_href :: Xsd.IDREF } deriving (Eq,Show) instance SchemaType ResetDatesReference where parseSchemaType s = do (pos,e) <- posnElement [s] a0 <- getAttribute "href" e pos commit $ interior e $ return (ResetDatesReference a0) schemaTypeToXML s x@ResetDatesReference{} = toXMLElement s [ toXMLAttribute "href" $ resetDatesRef_href x ] [] instance Extension ResetDatesReference Reference where supertype v = Reference_ResetDatesReference v -- | A type defining the specification of settlement terms, -- occuring when the settlement currency is different to the -- notional currency of the trade. data SettlementProvision = SettlementProvision { 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. } deriving (Eq,Show) instance SchemaType SettlementProvision where parseSchemaType s = do (pos,e) <- posnElement [s] commit $ interior e $ return SettlementProvision `apply` optional (parseSchemaType "settlementCurrency") `apply` optional (parseSchemaType "nonDeliverableSettlement") schemaTypeToXML s x@SettlementProvision{} = toXMLElement s [] [ maybe [] (schemaTypeToXML "settlementCurrency") $ settlProvis_settlementCurrency x , maybe [] (schemaTypeToXML "nonDeliverableSettlement") $ settlProvis_nonDeliverableSettlement x ] -- | 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 SettlementRateOption = SettlementRateOption Scheme SettlementRateOptionAttributes deriving (Eq,Show) data SettlementRateOptionAttributes = SettlementRateOptionAttributes { settlRateOptionAttrib_settlementRateOptionScheme :: Maybe Xsd.AnyURI } deriving (Eq,Show) instance SchemaType SettlementRateOption where parseSchemaType s = do (pos,e) <- posnElement [s] commit $ do a0 <- optional $ getAttribute "settlementRateOptionScheme" e pos reparse [CElem e pos] v <- parseSchemaType s return $ SettlementRateOption v (SettlementRateOptionAttributes a0) schemaTypeToXML s (SettlementRateOption bt at) = addXMLAttributes [ maybe [] (toXMLAttribute "settlementRateOptionScheme") $ settlRateOptionAttrib_settlementRateOptionScheme at ] $ schemaTypeToXML s bt instance Extension SettlementRateOption Scheme where supertype (SettlementRateOption s _) = s -- | A type describing the buyer and seller of an option. data SinglePartyOption = SinglePartyOption { 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. } deriving (Eq,Show) instance SchemaType SinglePartyOption where parseSchemaType s = do (pos,e) <- posnElement [s] commit $ interior e $ return SinglePartyOption `apply` optional (parseSchemaType "buyerPartyReference") `apply` optional (parseSchemaType "buyerAccountReference") `apply` optional (parseSchemaType "sellerPartyReference") `apply` optional (parseSchemaType "sellerAccountReference") schemaTypeToXML s x@SinglePartyOption{} = toXMLElement s [] [ maybe [] (schemaTypeToXML "buyerPartyReference") $ singlePartyOption_buyerPartyReference x , maybe [] (schemaTypeToXML "buyerAccountReference") $ singlePartyOption_buyerAccountReference x , maybe [] (schemaTypeToXML "sellerPartyReference") $ singlePartyOption_sellerPartyReference x , maybe [] (schemaTypeToXML "sellerAccountReference") $ singlePartyOption_sellerAccountReference x ] -- | 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. data StubCalculationPeriodAmount = StubCalculationPeriodAmount { 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. } deriving (Eq,Show) instance SchemaType StubCalculationPeriodAmount where parseSchemaType s = do (pos,e) <- posnElement [s] commit $ interior e $ return StubCalculationPeriodAmount `apply` optional (parseSchemaType "calculationPeriodDatesReference") `apply` optional (parseSchemaType "initialStub") `apply` optional (parseSchemaType "finalStub") schemaTypeToXML s x@StubCalculationPeriodAmount{} = toXMLElement s [] [ maybe [] (schemaTypeToXML "calculationPeriodDatesReference") $ stubCalcPeriodAmount_calculationPeriodDatesReference x , maybe [] (schemaTypeToXML "initialStub") $ stubCalcPeriodAmount_initialStub x , maybe [] (schemaTypeToXML "finalStub") $ stubCalcPeriodAmount_finalStub x ] -- | A type defining swap streams and additional payments -- between the principal parties involved in the swap. data Swap = Swap { swap_ID :: Maybe Xsd.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. } deriving (Eq,Show) instance SchemaType Swap where parseSchemaType s = do (pos,e) <- posnElement [s] a0 <- optional $ getAttribute "id" e pos commit $ interior e $ return (Swap a0) `apply` optional (parseSchemaType "primaryAssetClass") `apply` many (parseSchemaType "secondaryAssetClass") `apply` many (parseSchemaType "productType") `apply` many (parseSchemaType "productId") `apply` many1 (parseSchemaType "swapStream") `apply` optional (parseSchemaType "earlyTerminationProvision") `apply` optional (parseSchemaType "cancelableProvision") `apply` optional (parseSchemaType "extendibleProvision") `apply` many (parseSchemaType "additionalPayment") `apply` optional (parseSchemaType "additionalTerms") schemaTypeToXML s x@Swap{} = toXMLElement s [ maybe [] (toXMLAttribute "id") $ swap_ID x ] [ maybe [] (schemaTypeToXML "primaryAssetClass") $ swap_primaryAssetClass x , concatMap (schemaTypeToXML "secondaryAssetClass") $ swap_secondaryAssetClass x , concatMap (schemaTypeToXML "productType") $ swap_productType x , concatMap (schemaTypeToXML "productId") $ swap_productId x , concatMap (schemaTypeToXML "swapStream") $ swap_stream x , maybe [] (schemaTypeToXML "earlyTerminationProvision") $ swap_earlyTerminationProvision x , maybe [] (schemaTypeToXML "cancelableProvision") $ swap_cancelableProvision x , maybe [] (schemaTypeToXML "extendibleProvision") $ swap_extendibleProvision x , concatMap (schemaTypeToXML "additionalPayment") $ swap_additionalPayment x , maybe [] (schemaTypeToXML "additionalTerms") $ swap_additionalTerms x ] instance Extension Swap Product where supertype v = Product_Swap v -- | Additional terms to a swap contract. data SwapAdditionalTerms = SwapAdditionalTerms { swapAddTerms_bondReference :: Maybe BondReference -- ^ Reference to a bond underlyer to represent an asset swap or -- Condition Precedent Bond. } deriving (Eq,Show) instance SchemaType SwapAdditionalTerms where parseSchemaType s = do (pos,e) <- posnElement [s] commit $ interior e $ return SwapAdditionalTerms `apply` optional (parseSchemaType "bondReference") schemaTypeToXML s x@SwapAdditionalTerms{} = toXMLElement s [] [ maybe [] (schemaTypeToXML "bondReference") $ swapAddTerms_bondReference x ] -- | A type to define an option on a swap. data Swaption = Swaption { swaption_ID :: Maybe Xsd.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, -- put/call is the default option type, while payer/receiver -- 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 :: Xsd.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 } deriving (Eq,Show) instance SchemaType Swaption where parseSchemaType s = do (pos,e) <- posnElement [s] a0 <- optional $ getAttribute "id" e pos commit $ interior e $ return (Swaption a0) `apply` optional (parseSchemaType "primaryAssetClass") `apply` many (parseSchemaType "secondaryAssetClass") `apply` many (parseSchemaType "productType") `apply` many (parseSchemaType "productId") `apply` optional (parseSchemaType "buyerPartyReference") `apply` optional (parseSchemaType "buyerAccountReference") `apply` optional (parseSchemaType "sellerPartyReference") `apply` optional (parseSchemaType "sellerAccountReference") `apply` many1 (parseSchemaType "premium") `apply` optional (parseSchemaType "optionType") `apply` elementExercise `apply` optional (parseSchemaType "exerciseProcedure") `apply` optional (parseSchemaType "calculationAgent") `apply` optional (oneOf' [ ("CashSettlement", fmap OneOf2 (parseSchemaType "cashSettlement")) , ("SwaptionPhysicalSettlement", fmap TwoOf2 (parseSchemaType "physicalSettlement")) ]) `apply` parseSchemaType "swaptionStraddle" `apply` optional (parseSchemaType "swaptionAdjustedDates") `apply` parseSchemaType "swap" schemaTypeToXML s x@Swaption{} = toXMLElement s [ maybe [] (toXMLAttribute "id") $ swaption_ID x ] [ maybe [] (schemaTypeToXML "primaryAssetClass") $ swaption_primaryAssetClass x , concatMap (schemaTypeToXML "secondaryAssetClass") $ swaption_secondaryAssetClass x , concatMap (schemaTypeToXML "productType") $ swaption_productType x , concatMap (schemaTypeToXML "productId") $ swaption_productId x , maybe [] (schemaTypeToXML "buyerPartyReference") $ swaption_buyerPartyReference x , maybe [] (schemaTypeToXML "buyerAccountReference") $ swaption_buyerAccountReference x , maybe [] (schemaTypeToXML "sellerPartyReference") $ swaption_sellerPartyReference x , maybe [] (schemaTypeToXML "sellerAccountReference") $ swaption_sellerAccountReference x , concatMap (schemaTypeToXML "premium") $ swaption_premium x , maybe [] (schemaTypeToXML "optionType") $ swaption_optionType x , elementToXMLExercise $ swaption_exercise x , maybe [] (schemaTypeToXML "exerciseProcedure") $ swaption_exerciseProcedure x , maybe [] (schemaTypeToXML "calculationAgent") $ swaption_calculationAgent x , maybe [] (foldOneOf2 (schemaTypeToXML "cashSettlement") (schemaTypeToXML "physicalSettlement") ) $ swaption_choice13 x , schemaTypeToXML "swaptionStraddle" $ swaption_straddle x , maybe [] (schemaTypeToXML "swaptionAdjustedDates") $ swaption_adjustedDates x , schemaTypeToXML "swap" $ swaption_swap x ] instance Extension Swaption Product where supertype v = Product_Swaption v -- | A type describing the adjusted dates associated with -- swaption exercise and settlement. data SwaptionAdjustedDates = SwaptionAdjustedDates { swaptAdjustDates_exerciseEvent :: [ExerciseEvent] -- ^ The adjusted dates associated with an individual swaption -- exercise date. } deriving (Eq,Show) instance SchemaType SwaptionAdjustedDates where parseSchemaType s = do (pos,e) <- posnElement [s] commit $ interior e $ return SwaptionAdjustedDates `apply` many (parseSchemaType "exerciseEvent") schemaTypeToXML s x@SwaptionAdjustedDates{} = toXMLElement s [] [ concatMap (schemaTypeToXML "exerciseEvent") $ swaptAdjustDates_exerciseEvent x ] data SwaptionPhysicalSettlement = SwaptionPhysicalSettlement { swaptPhysicSettl_clearedPhysicalSettlement :: Maybe Xsd.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). } deriving (Eq,Show) instance SchemaType SwaptionPhysicalSettlement where parseSchemaType s = do (pos,e) <- posnElement [s] commit $ interior e $ return SwaptionPhysicalSettlement `apply` optional (parseSchemaType "clearedPhysicalSettlement") schemaTypeToXML s x@SwaptionPhysicalSettlement{} = toXMLElement s [] [ maybe [] (schemaTypeToXML "clearedPhysicalSettlement") $ swaptPhysicSettl_clearedPhysicalSettlement x ] -- | Reference to a Valuation dates node. data ValuationDatesReference = ValuationDatesReference { valDatesRef_href :: Xsd.IDREF } deriving (Eq,Show) instance SchemaType ValuationDatesReference where parseSchemaType s = do (pos,e) <- posnElement [s] a0 <- getAttribute "href" e pos commit $ interior e $ return (ValuationDatesReference a0) schemaTypeToXML s x@ValuationDatesReference{} = toXMLElement s [ toXMLAttribute "href" $ valDatesRef_href x ] [] instance Extension ValuationDatesReference Reference where supertype v = Reference_ValuationDatesReference v -- | Specifies how long to wait to get a quote from a settlement -- rate option upon a price source disruption. data ValuationPostponement = ValuationPostponement { valPostp_maximumDaysOfPostponement :: Maybe Xsd.PositiveInteger -- ^ The maximum number of days to wait for a quote from the -- disrupted settlement rate option before proceding to the -- next method. } deriving (Eq,Show) instance SchemaType ValuationPostponement where parseSchemaType s = do (pos,e) <- posnElement [s] commit $ interior e $ return ValuationPostponement `apply` optional (parseSchemaType "maximumDaysOfPostponement") schemaTypeToXML s x@ValuationPostponement{} = toXMLElement s [] [ maybe [] (schemaTypeToXML "maximumDaysOfPostponement") $ valPostp_maximumDaysOfPostponement x ] -- | A type defining the parameters required for each of the -- ISDA defined yield curve methods for cash settlement. data YieldCurveMethod = YieldCurveMethod { 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) } deriving (Eq,Show) instance SchemaType YieldCurveMethod where parseSchemaType s = do (pos,e) <- posnElement [s] commit $ interior e $ return YieldCurveMethod `apply` optional (parseSchemaType "settlementRateSource") `apply` optional (parseSchemaType "quotationRateType") schemaTypeToXML s x@YieldCurveMethod{} = toXMLElement s [] [ maybe [] (schemaTypeToXML "settlementRateSource") $ yieldCurveMethod_settlementRateSource x , maybe [] (schemaTypeToXML "quotationRateType") $ yieldCurveMethod_quotationRateType x ] -- | A product to represent a single known payment. elementBulletPayment :: XMLParser BulletPayment elementBulletPayment = parseSchemaType "bulletPayment" elementToXMLBulletPayment :: BulletPayment -> [Content ()] elementToXMLBulletPayment = schemaTypeToXML "bulletPayment" -- | A cap, floor or cap floor structures product definition. elementCapFloor :: XMLParser CapFloor elementCapFloor = parseSchemaType "capFloor" elementToXMLCapFloor :: CapFloor -> [Content ()] elementToXMLCapFloor = schemaTypeToXML "capFloor" -- | A floating rate calculation definition. elementFloatingRateCalculation :: XMLParser FloatingRateCalculation elementFloatingRateCalculation = parseSchemaType "floatingRateCalculation" elementToXMLFloatingRateCalculation :: FloatingRateCalculation -> [Content ()] elementToXMLFloatingRateCalculation = schemaTypeToXML "floatingRateCalculation" -- | A forward rate agreement product definition. elementFra :: XMLParser Fra elementFra = parseSchemaType "fra" elementToXMLFra :: Fra -> [Content ()] elementToXMLFra = schemaTypeToXML "fra" -- | An inflation rate calculation definition. elementInflationRateCalculation :: XMLParser InflationRateCalculation elementInflationRateCalculation = parseSchemaType "inflationRateCalculation" elementToXMLInflationRateCalculation :: InflationRateCalculation -> [Content ()] elementToXMLInflationRateCalculation = schemaTypeToXML "inflationRateCalculation" -- | The base element for the floating rate calculation -- definitions. elementRateCalculation :: XMLParser Rate elementRateCalculation = fmap supertype elementInflationRateCalculation `onFail` fmap supertype elementFloatingRateCalculation `onFail` fail "Parse failed when expecting an element in the substitution group for\n\ \ ,\n\ \ namely one of:\n\ \, " elementToXMLRateCalculation :: Rate -> [Content ()] elementToXMLRateCalculation = schemaTypeToXML "rateCalculation" -- | A swap product definition. elementSwap :: XMLParser Swap elementSwap = parseSchemaType "swap" elementToXMLSwap :: Swap -> [Content ()] elementToXMLSwap = schemaTypeToXML "swap" -- | A swaption product definition. elementSwaption :: XMLParser Swaption elementSwaption = parseSchemaType "swaption" elementToXMLSwaption :: Swaption -> [Content ()] elementToXMLSwaption = schemaTypeToXML "swaption"