{-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies #-} {-# OPTIONS_GHC -fno-warn-duplicate-exports #-} module Data.FpML.V53.Shared ( module Data.FpML.V53.Shared , module Data.FpML.V53.Enum ) where import Text.XML.HaXml.Schema.Schema (SchemaType(..),SimpleType(..),Extension(..),Restricts(..)) import Text.XML.HaXml.Schema.Schema as Schema import qualified Text.XML.HaXml.Schema.PrimitiveTypes as Xsd import {-# SOURCE #-} Data.FpML.V53.Enum -- | A type defining a number specified as a decimal between -1 -- and 1 inclusive. newtype CorrelationValue = CorrelationValue Xsd.Decimal instance Eq CorrelationValue instance Show CorrelationValue instance Restricts CorrelationValue Xsd.Decimal instance SchemaType CorrelationValue instance SimpleType CorrelationValue -- | A type defining a time specified in hh:mm:ss format where -- the second component must be '00', e.g. 11am would be -- represented as 11:00:00. newtype HourMinuteTime = HourMinuteTime Xsd.Time instance Eq HourMinuteTime instance Show HourMinuteTime instance Restricts HourMinuteTime Xsd.Time instance SchemaType HourMinuteTime instance SimpleType HourMinuteTime -- | A type defining a number specified as non negative decimal -- greater than 0 inclusive. newtype NonNegativeDecimal = NonNegativeDecimal Xsd.Decimal instance Eq NonNegativeDecimal instance Show NonNegativeDecimal instance Restricts NonNegativeDecimal Xsd.Decimal instance SchemaType NonNegativeDecimal instance SimpleType NonNegativeDecimal -- | A type defining a number specified as positive decimal -- greater than 0 exclusive. newtype PositiveDecimal = PositiveDecimal Xsd.Decimal instance Eq PositiveDecimal instance Show PositiveDecimal instance Restricts PositiveDecimal Xsd.Decimal instance SchemaType PositiveDecimal instance SimpleType PositiveDecimal -- | A type defining a percentage specified as decimal from 0 to -- 1. A percentage of 5% would be represented as 0.05. newtype RestrictedPercentage = RestrictedPercentage Xsd.Decimal instance Eq RestrictedPercentage instance Show RestrictedPercentage instance Restricts RestrictedPercentage Xsd.Decimal instance SchemaType RestrictedPercentage instance SimpleType RestrictedPercentage -- | The base class for all types which define coding schemes. newtype Scheme = Scheme Xsd.NormalizedString instance Eq Scheme instance Show Scheme instance Restricts Scheme Xsd.NormalizedString instance SchemaType Scheme instance SimpleType Scheme -- | A type defining a token of length between 1 and 60 -- characters inclusive. newtype Token60 = Token60 Xsd.Token instance Eq Token60 instance Show Token60 instance Restricts Token60 Xsd.Token instance SchemaType Token60 instance SimpleType Token60 -- | A generic account that represents any party's account at -- another party. Parties may be identified by the account at -- another party. data Account instance Eq Account instance Show Account instance SchemaType Account -- | The data type used for account identifiers. data AccountId data AccountIdAttributes instance Eq AccountId instance Eq AccountIdAttributes instance Show AccountId instance Show AccountIdAttributes instance SchemaType AccountId instance Extension AccountId Scheme -- | The data type used for the name of the account. data AccountName data AccountNameAttributes instance Eq AccountName instance Eq AccountNameAttributes instance Show AccountName instance Show AccountNameAttributes instance SchemaType AccountName instance Extension AccountName Scheme -- | Reference to an account. data AccountReference instance Eq AccountReference instance Show AccountReference instance SchemaType AccountReference instance Extension AccountReference Reference -- | A type that represents a physical postal address. data Address instance Eq Address instance Show Address instance SchemaType Address -- | A type that represents information about a unit within an -- organization. data BusinessUnit instance Eq BusinessUnit instance Show BusinessUnit instance SchemaType BusinessUnit -- | A type that represents information about a person connected -- with a trade or business process. data Person instance Eq Person instance Show Person instance SchemaType Person newtype Initial = Initial Xsd.NormalizedString instance Eq Initial instance Show Initial instance Restricts Initial Xsd.NormalizedString instance SchemaType Initial instance SimpleType Initial -- | An identifier used to identify an individual person. data PersonId data PersonIdAttributes instance Eq PersonId instance Eq PersonIdAttributes instance Show PersonId instance Show PersonIdAttributes instance SchemaType PersonId instance Extension PersonId Scheme -- | A type used to record information about a unit, -- subdivision, desk, or other similar business entity. data Unit data UnitAttributes instance Eq Unit instance Eq UnitAttributes instance Show Unit instance Show UnitAttributes instance SchemaType Unit instance Extension Unit Scheme -- | A type that represents how to contact an individual or -- organization. data ContactInformation instance Eq ContactInformation instance Show ContactInformation instance SchemaType ContactInformation -- | A type that represents a telephonic contact. data TelephoneNumber instance Eq TelephoneNumber instance Show TelephoneNumber instance SchemaType TelephoneNumber -- | A type for defining a date that shall be subject to -- adjustment if it 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. data AdjustableDate instance Eq AdjustableDate instance Show AdjustableDate instance SchemaType AdjustableDate -- | A type that is different from AdjustableDate in two -- regards. First, date adjustments can be specified with -- either a dateAdjustments element or a reference to an -- existing dateAdjustments element. Second, it does not -- require the specification of date adjustments. data AdjustableDate2 instance Eq AdjustableDate2 instance Show AdjustableDate2 instance SchemaType AdjustableDate2 -- | A type for defining 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 dates. data AdjustableDates instance Eq AdjustableDates instance Show AdjustableDates instance SchemaType AdjustableDates -- | A type for defining a series of dates, either as a list of -- adjustable dates, or a as a repeating sequence from a base -- date data AdjustableDatesOrRelativeDateOffset instance Eq AdjustableDatesOrRelativeDateOffset instance Show AdjustableDatesOrRelativeDateOffset instance SchemaType AdjustableDatesOrRelativeDateOffset -- | A type for defining a date that shall be subject to -- adjustment if it 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. data AdjustableOrAdjustedDate instance Eq AdjustableOrAdjustedDate instance Show AdjustableOrAdjustedDate instance SchemaType AdjustableOrAdjustedDate -- | A type giving the choice between defining a date as an -- explicit date together with applicable adjustments or as -- relative to some other (anchor) date. data AdjustableOrRelativeDate instance Eq AdjustableOrRelativeDate instance Show AdjustableOrRelativeDate instance SchemaType AdjustableOrRelativeDate -- | A type giving the choice between defining a series of dates -- as an explicit list of dates together with applicable -- adjustments or as relative to some other series of (anchor) -- dates. data AdjustableOrRelativeDates instance Eq AdjustableOrRelativeDates instance Show AdjustableOrRelativeDates instance SchemaType AdjustableOrRelativeDates data AdjustableRelativeOrPeriodicDates instance Eq AdjustableRelativeOrPeriodicDates instance Show AdjustableRelativeOrPeriodicDates instance SchemaType AdjustableRelativeOrPeriodicDates -- | A type giving the choice between defining a series of dates -- as an explicit list of dates together with applicable -- adjustments, or as relative to some other series of -- (anchor) dates, or as a set of factors to specify periodic -- occurences. data AdjustableRelativeOrPeriodicDates2 instance Eq AdjustableRelativeOrPeriodicDates2 instance Show AdjustableRelativeOrPeriodicDates2 instance SchemaType AdjustableRelativeOrPeriodicDates2 -- | A type defining a date (referred to as the derived date) as -- a relative offset from another date (referred to as the -- anchor date) plus optional date adjustments. data AdjustedRelativeDateOffset instance Eq AdjustedRelativeDateOffset instance Show AdjustedRelativeDateOffset instance SchemaType AdjustedRelativeDateOffset instance Extension AdjustedRelativeDateOffset RelativeDateOffset instance Extension AdjustedRelativeDateOffset Offset instance Extension AdjustedRelativeDateOffset Period data AgreementType data AgreementTypeAttributes instance Eq AgreementType instance Eq AgreementTypeAttributes instance Show AgreementType instance Show AgreementTypeAttributes instance SchemaType AgreementType instance Extension AgreementType Scheme data AgreementVersion data AgreementVersionAttributes instance Eq AgreementVersion instance Eq AgreementVersionAttributes instance Show AgreementVersion instance Show AgreementVersionAttributes instance SchemaType AgreementVersion instance Extension AgreementVersion Scheme -- | A type defining the exercise period for an American style -- option together with any rules governing the notional -- amount of the underlying which can be exercised on any -- given exercise date and any associated exercise fees. data AmericanExercise instance Eq AmericanExercise instance Show AmericanExercise instance SchemaType AmericanExercise instance Extension AmericanExercise Exercise -- | Specifies a reference to a monetary amount. data AmountReference instance Eq AmountReference instance Show AmountReference instance SchemaType AmountReference instance Extension AmountReference Reference -- | A type defining a currency amount or a currency amount -- schedule. data AmountSchedule instance Eq AmountSchedule instance Show AmountSchedule instance SchemaType AmountSchedule instance Extension AmountSchedule Schedule data AssetClass data AssetClassAttributes instance Eq AssetClass instance Eq AssetClassAttributes instance Show AssetClass instance Show AssetClassAttributes instance SchemaType AssetClass instance Extension AssetClass Scheme -- | A type to define automatic exercise of a swaption. With -- automatic exercise the option is deemed to have exercised -- if it is in the money by more than the threshold amount on -- the exercise date. data AutomaticExercise instance Eq AutomaticExercise instance Show AutomaticExercise instance SchemaType AutomaticExercise -- | To indicate the limitation percentage and limitation -- period. data AverageDailyTradingVolumeLimit instance Eq AverageDailyTradingVolumeLimit instance Show AverageDailyTradingVolumeLimit instance SchemaType AverageDailyTradingVolumeLimit -- | A type defining the beneficiary of the funds. data Beneficiary instance Eq Beneficiary instance Show Beneficiary instance SchemaType Beneficiary -- | A type defining the Bermuda option exercise dates and the -- expiration date together with any rules govenerning the -- notional amount of the underlying which can be exercised on -- any given exercise date and any associated exercise fee. data BermudaExercise instance Eq BermudaExercise instance Show BermudaExercise instance SchemaType BermudaExercise instance Extension BermudaExercise Exercise -- | Identifies the market sector in which the trade has been -- arranged. data BrokerConfirmation instance Eq BrokerConfirmation instance Show BrokerConfirmation instance SchemaType BrokerConfirmation -- | Identifies the market sector in which the trade has been -- arranged. data BrokerConfirmationType data BrokerConfirmationTypeAttributes instance Eq BrokerConfirmationType instance Eq BrokerConfirmationTypeAttributes instance Show BrokerConfirmationType instance Show BrokerConfirmationTypeAttributes instance SchemaType BrokerConfirmationType instance Extension BrokerConfirmationType Scheme -- | A code identifying a business day calendar location. A -- business day calendar location is drawn from the list -- identified by the business day calendar location scheme. data BusinessCenter data BusinessCenterAttributes instance Eq BusinessCenter instance Eq BusinessCenterAttributes instance Show BusinessCenter instance Show BusinessCenterAttributes instance SchemaType BusinessCenter instance Extension BusinessCenter Scheme -- | A type for defining business day calendar used in -- determining whether a day is a business day or not. A list -- of business day calendar locations may be ordered in the -- document alphabetically based on business day calendar -- location code. An FpML document containing an unordered -- business day calendar location list is still regarded as a -- conformant document. data BusinessCenters instance Eq BusinessCenters instance Show BusinessCenters instance SchemaType BusinessCenters -- | A pointer style reference to a set of business day calendar -- defined elsewhere in the document. data BusinessCentersReference instance Eq BusinessCentersReference instance Show BusinessCentersReference instance SchemaType BusinessCentersReference instance Extension BusinessCentersReference Reference -- | A type for defining a time with respect to a business day -- calendar location. For example, 11:00am London time. data BusinessCenterTime instance Eq BusinessCenterTime instance Show BusinessCenterTime instance SchemaType BusinessCenterTime -- | A type defining a range of contiguous business days by -- defining an unadjusted first date, an unadjusted last date -- and a business day convention and business centers for -- adjusting the first and last dates if they would otherwise -- fall on a non business day in the specified business -- centers. The days between the first and last date must also -- be good business days in the specified centers to be -- counted in the range. data BusinessDateRange instance Eq BusinessDateRange instance Show BusinessDateRange instance SchemaType BusinessDateRange instance Extension BusinessDateRange DateRange -- | A type defining the business day convention and financial -- business centers used for adjusting any relevant date if it -- would otherwise fall on a day that is not a business day in -- the specified business centers. data BusinessDayAdjustments instance Eq BusinessDayAdjustments instance Show BusinessDayAdjustments instance SchemaType BusinessDayAdjustments -- | Reference to a business day adjustments structure. data BusinessDayAdjustmentsReference instance Eq BusinessDayAdjustmentsReference instance Show BusinessDayAdjustmentsReference instance SchemaType BusinessDayAdjustmentsReference instance Extension BusinessDayAdjustmentsReference Reference -- | A type defining the ISDA calculation agent responsible for -- performing duties as defined in the applicable product -- definitions. data CalculationAgent instance Eq CalculationAgent instance Show CalculationAgent instance SchemaType CalculationAgent -- | A type defining the frequency at which calculation period -- end dates occur within the regular part of the calculation -- period schedule and thier roll date convention. In case the -- calculation frequency is of value T (term), the period is -- defined by the -- swap\swapStream\calculationPerioDates\effectiveDate and the -- swap\swapStream\calculationPerioDates\terminationDate. data CalculationPeriodFrequency instance Eq CalculationPeriodFrequency instance Show CalculationPeriodFrequency instance SchemaType CalculationPeriodFrequency instance Extension CalculationPeriodFrequency Frequency -- | An identifier used to identify a single component cashflow. data CashflowId data CashflowIdAttributes instance Eq CashflowId instance Eq CashflowIdAttributes instance Show CashflowId instance Show CashflowIdAttributes instance SchemaType CashflowId instance Extension CashflowId Scheme -- | The notional/principal value/quantity/volume used to -- compute the cashflow. data CashflowNotional instance Eq CashflowNotional instance Show CashflowNotional instance SchemaType CashflowNotional -- | A coding scheme used to describe the type or purpose of a -- cash flow or cash flow component. data CashflowType data CashflowTypeAttributes instance Eq CashflowType instance Eq CashflowTypeAttributes instance Show CashflowType instance Show CashflowTypeAttributes instance SchemaType CashflowType instance Extension CashflowType Scheme -- | A type defining the list of reference institutions polled -- for relevant rates or prices when determining the cash -- settlement amount for a product where cash settlement is -- applicable. data CashSettlementReferenceBanks instance Eq CashSettlementReferenceBanks instance Show CashSettlementReferenceBanks instance SchemaType CashSettlementReferenceBanks -- | Unless otherwise specified, the principal clearance system -- customarily used for settling trades in the relevant -- underlying. data ClearanceSystem data ClearanceSystemAttributes instance Eq ClearanceSystem instance Eq ClearanceSystemAttributes instance Show ClearanceSystem instance Show ClearanceSystemAttributes instance SchemaType ClearanceSystem instance Extension ClearanceSystem Scheme -- | The definitions, such as those published by ISDA, that will -- define the terms of the trade. data ContractualDefinitions data ContractualDefinitionsAttributes instance Eq ContractualDefinitions instance Eq ContractualDefinitionsAttributes instance Show ContractualDefinitions instance Show ContractualDefinitionsAttributes instance SchemaType ContractualDefinitions instance Extension ContractualDefinitions Scheme data ContractualMatrix instance Eq ContractualMatrix instance Show ContractualMatrix instance SchemaType ContractualMatrix -- | A contractual supplement (such as those published by ISDA) -- that will apply to the trade. data ContractualSupplement data ContractualSupplementAttributes instance Eq ContractualSupplement instance Eq ContractualSupplementAttributes instance Show ContractualSupplement instance Show ContractualSupplementAttributes instance SchemaType ContractualSupplement instance Extension ContractualSupplement Scheme -- | A contractual supplement (such as those published by ISDA) -- and its publication date that will apply to the trade. data ContractualTermsSupplement instance Eq ContractualTermsSupplement instance Show ContractualTermsSupplement instance SchemaType ContractualTermsSupplement -- | A type that describes the information to identify a -- correspondent bank that will make delivery of the funds on -- the paying bank's behalf in the country where the payment -- is to be made. data CorrespondentInformation instance Eq CorrespondentInformation instance Show CorrespondentInformation instance SchemaType CorrespondentInformation -- | The code representation of a country or an area of special -- sovereignty. By default it is a valid 2 character country -- code as defined by the ISO standard 3166-1 alpha-2 - Codes -- for representation of countries -- http://www.niso.org/standards/resources/3166.html. data CountryCode data CountryCodeAttributes instance Eq CountryCode instance Eq CountryCodeAttributes instance Show CountryCode instance Show CountryCodeAttributes instance SchemaType CountryCode instance Extension CountryCode Xsd.Token -- | The repayment precedence of a debt instrument. data CreditSeniority data CreditSeniorityAttributes instance Eq CreditSeniority instance Eq CreditSeniorityAttributes instance Show CreditSeniority instance Show CreditSeniorityAttributes instance SchemaType CreditSeniority instance Extension CreditSeniority Scheme -- | The agreement executed between the parties and intended to -- govern collateral arrangement for all OTC derivatives -- transactions between those parties. data CreditSupportAgreement instance Eq CreditSupportAgreement instance Show CreditSupportAgreement instance SchemaType CreditSupportAgreement data CreditSupportAgreementIdentifier data CreditSupportAgreementIdentifierAttributes instance Eq CreditSupportAgreementIdentifier instance Eq CreditSupportAgreementIdentifierAttributes instance Show CreditSupportAgreementIdentifier instance Show CreditSupportAgreementIdentifierAttributes instance SchemaType CreditSupportAgreementIdentifier instance Extension CreditSupportAgreementIdentifier Scheme data CreditSupportAgreementType data CreditSupportAgreementTypeAttributes instance Eq CreditSupportAgreementType instance Eq CreditSupportAgreementTypeAttributes instance Show CreditSupportAgreementType instance Show CreditSupportAgreementTypeAttributes instance SchemaType CreditSupportAgreementType instance Extension CreditSupportAgreementType Scheme -- | A party's credit rating. data CreditRating data CreditRatingAttributes instance Eq CreditRating instance Eq CreditRatingAttributes instance Show CreditRating instance Show CreditRatingAttributes instance SchemaType CreditRating instance Extension CreditRating Scheme -- | The code representation of a currency or fund. By default -- it is a valid currency code as defined by the ISO standard -- 4217 - Codes for representation of currencies and funds -- http://www.iso.org/iso/en/prods-services/popstds/currencycodeslist.html. data Currency data CurrencyAttributes instance Eq Currency instance Eq CurrencyAttributes instance Show Currency instance Show CurrencyAttributes instance SchemaType Currency instance Extension Currency Scheme -- | List of Dates data DateList instance Eq DateList instance Show DateList instance SchemaType DateList -- | A type defining an offset used in calculating a date when -- this date is defined in reference to another date through a -- date offset. The type includes the convention for adjusting -- the date and an optional sequence element to indicate the -- order in a sequence of multiple date offsets. data DateOffset instance Eq DateOffset instance Show DateOffset instance SchemaType DateOffset instance Extension DateOffset Offset instance Extension DateOffset Period -- | A type defining a contiguous series of calendar dates. The -- date range is defined as all the dates between and -- including the first and the last date. The first date must -- fall before the last date. data DateRange instance Eq DateRange instance Show DateRange instance SchemaType DateRange -- | Reference to an identified date or a complex date -- structure. data DateReference instance Eq DateReference instance Show DateReference instance SchemaType DateReference instance Extension DateReference Reference -- | List of DateTimes data DateTimeList instance Eq DateTimeList instance Show DateTimeList instance SchemaType DateTimeList -- | The specification for how the number of days between two -- dates is calculated for purposes of calculation of a fixed -- or floating payment amount and the basis for how many days -- are assumed to be in a year. Day Count Fraction is an ISDA -- term. The equivalent AFB (Association Francaise de Banques) -- term is Calculation Basis. data DayCountFraction data DayCountFractionAttributes instance Eq DayCountFraction instance Eq DayCountFractionAttributes instance Show DayCountFraction instance Show DayCountFractionAttributes instance SchemaType DayCountFraction instance Extension DayCountFraction Scheme -- | Coding scheme that specifies the method according to which -- an amount or a date is determined. data DeterminationMethod data DeterminationMethodAttributes instance Eq DeterminationMethod instance Eq DeterminationMethodAttributes instance Show DeterminationMethod instance Show DeterminationMethodAttributes instance SchemaType DeterminationMethod instance Extension DeterminationMethod Scheme -- | A reference to the return swap notional determination -- method. data DeterminationMethodReference instance Eq DeterminationMethodReference instance Show DeterminationMethodReference instance SchemaType DeterminationMethodReference instance Extension DeterminationMethodReference Reference -- | An entity for defining the definitions that govern the -- document and should include the year and type of -- definitions referenced, along with any relevant -- documentation (such as master agreement) and the date it -- was signed. data Documentation instance Eq Documentation instance Show Documentation instance SchemaType Documentation -- | A for holding information about documents external to the -- FpML. data ExternalDocument instance Eq ExternalDocument instance Show ExternalDocument instance SchemaType ExternalDocument -- | A special type that allows references to HTTP attachments -- identified with an HTTP "Content-ID" header, as is done -- with SOAP with Attachments -- (http://www.w3.org/TR/SOAP-attachments). Unlike with a -- normal FpML @href, the type is not IDREF, as the target is -- not identified by an XML @id attribute. data HTTPAttachmentReference instance Eq HTTPAttachmentReference instance Show HTTPAttachmentReference instance SchemaType HTTPAttachmentReference instance Extension HTTPAttachmentReference Reference -- | A special type meant to be used for elements with no -- content and no attributes. data Empty instance Eq Empty instance Show Empty instance SchemaType Empty -- | A legal entity identifier (e.g. RED entity code). data EntityId data EntityIdAttributes instance Eq EntityId instance Eq EntityIdAttributes instance Show EntityId instance Show EntityIdAttributes instance SchemaType EntityId instance Extension EntityId Scheme -- | The name of the reference entity. A free format string. -- FpML does not define usage rules for this element. data EntityName data EntityNameAttributes instance Eq EntityName instance Eq EntityNameAttributes instance Show EntityName instance Show EntityNameAttributes instance SchemaType EntityName instance Extension EntityName Scheme -- | A type defining the exercise period for a European style -- option together with any rules governing the notional -- amount of the underlying which can be exercised on any -- given exercise date and any associated exercise fees. data EuropeanExercise instance Eq EuropeanExercise instance Show EuropeanExercise instance SchemaType EuropeanExercise instance Extension EuropeanExercise Exercise -- | A short form unique identifier for an exchange. If the -- element is not present then the exchange shall be the -- primary exchange on which the underlying is listed. The -- term "Exchange" is assumed to have the meaning as defined -- in the ISDA 2002 Equity Derivatives Definitions. data ExchangeId data ExchangeIdAttributes instance Eq ExchangeId instance Eq ExchangeIdAttributes instance Show ExchangeId instance Show ExchangeIdAttributes instance SchemaType ExchangeId instance Extension ExchangeId Scheme -- | The abstract base class for all types which define way in -- which options may be exercised. data Exercise instance Eq Exercise instance Show Exercise instance SchemaType Exercise -- | A type defining the fee payable on exercise of an option. -- This fee may be defined as an amount or a percentage of the -- notional exercised. data ExerciseFee instance Eq ExerciseFee instance Show ExerciseFee instance SchemaType ExerciseFee -- | A type to define a fee or schedule of fees to be payable on -- the exercise of an option. This fee may be defined as an -- amount or a percentage of the notional exercised. data ExerciseFeeSchedule instance Eq ExerciseFeeSchedule instance Show ExerciseFeeSchedule instance SchemaType ExerciseFeeSchedule -- | A type defining to whom and where notice of execution -- should be given. The partyReference refers to one of the -- principal parties of the trade. If present the -- exerciseNoticePartyReference refers to a party, other than -- the principal party, to whome notice should be given. data ExerciseNotice instance Eq ExerciseNotice instance Show ExerciseNotice instance SchemaType ExerciseNotice -- | A type describing how notice of exercise should be given. -- This can be either manual or automatic. data ExerciseProcedure instance Eq ExerciseProcedure instance Show ExerciseProcedure instance SchemaType ExerciseProcedure -- | A type describing how notice of exercise should be given. -- This can be either manual or automatic. data ExerciseProcedureOption instance Eq ExerciseProcedureOption instance Show ExerciseProcedureOption instance SchemaType ExerciseProcedureOption -- | A type defining a floating rate. data FloatingRate instance Eq FloatingRate instance Show FloatingRate instance SchemaType FloatingRate instance Extension FloatingRate Rate -- | A type defining the floating rate and definitions relating -- to the calculation of floating rate amounts. data FloatingRateCalculation instance Eq FloatingRateCalculation instance Show FloatingRateCalculation instance SchemaType FloatingRateCalculation instance Extension FloatingRateCalculation FloatingRate instance Extension FloatingRateCalculation Rate -- | The ISDA Floating Rate Option, i.e. the floating rate -- index. data FloatingRateIndex data FloatingRateIndexAttributes instance Eq FloatingRateIndex instance Eq FloatingRateIndexAttributes instance Show FloatingRateIndex instance Show FloatingRateIndexAttributes instance SchemaType FloatingRateIndex instance Extension FloatingRateIndex Scheme -- | A type defining a rate index. data ForecastRateIndex instance Eq ForecastRateIndex instance Show ForecastRateIndex instance SchemaType ForecastRateIndex -- | A type describing a financial formula, with its description -- and components. data Formula instance Eq Formula instance Show Formula instance SchemaType Formula -- | Elements describing the components of the formula. The name -- attribute points to a value used in the math element. The -- href attribute points to a numeric value defined elsewhere -- in the document that is used by the formula component. data FormulaComponent instance Eq FormulaComponent instance Show FormulaComponent instance SchemaType FormulaComponent -- | A type defining a time frequency, e.g. one day, three -- months. Used for specifying payment or calculation -- frequencies at which the value T (Term) is applicable. data Frequency instance Eq Frequency instance Show Frequency instance SchemaType Frequency -- | A type defining a currency amount as at a future value -- date. data FutureValueAmount instance Eq FutureValueAmount instance Show FutureValueAmount instance SchemaType FutureValueAmount instance Extension FutureValueAmount NonNegativeMoney instance Extension FutureValueAmount MoneyBase -- | A type that specifies the source for and timing of a fixing -- of an exchange rate. This is used in the agreement of -- non-deliverable forward trades as well as various types of -- FX OTC options that require observations against a -- particular rate. data FxFixing instance Eq FxFixing instance Show FxFixing instance SchemaType FxFixing -- | A type that is used for describing cash settlement of an -- option / non deliverable forward. It includes the currency -- to settle into together with the fixings required to -- calculate the currency amount. data FxCashSettlement instance Eq FxCashSettlement instance Show FxCashSettlement instance SchemaType FxCashSettlement -- | A type describing the rate of a currency conversion: pair -- of currency, quotation mode and exchange rate. data FxRate instance Eq FxRate instance Show FxRate instance SchemaType FxRate -- | A type defining the source and time for an fx rate. data FxSpotRateSource instance Eq FxSpotRateSource instance Show FxSpotRateSource instance SchemaType FxSpotRateSource -- | An entity for defining a generic agreement executed between -- two parties for any purpose. data GenericAgreement instance Eq GenericAgreement instance Show GenericAgreement instance SchemaType GenericAgreement -- | Identification of the law governing the transaction. data GoverningLaw data GoverningLawAttributes instance Eq GoverningLaw instance Eq GoverningLawAttributes instance Show GoverningLaw instance Show GoverningLawAttributes instance SchemaType GoverningLaw instance Extension GoverningLaw Scheme -- | A payment component owed from one party to the other for -- the cash flow date. This payment component should by of -- only a single type, e.g. a fee or a cashflow from a -- cashflow stream. data GrossCashflow instance Eq GrossCashflow instance Show GrossCashflow instance SchemaType GrossCashflow -- | Specifies Currency with ID attribute. data IdentifiedCurrency data IdentifiedCurrencyAttributes instance Eq IdentifiedCurrency instance Eq IdentifiedCurrencyAttributes instance Show IdentifiedCurrency instance Show IdentifiedCurrencyAttributes instance SchemaType IdentifiedCurrency instance Extension IdentifiedCurrency Currency -- | Reference to a currency with ID attribute data IdentifiedCurrencyReference instance Eq IdentifiedCurrencyReference instance Show IdentifiedCurrencyReference instance SchemaType IdentifiedCurrencyReference instance Extension IdentifiedCurrencyReference Reference -- | A date which can be referenced elsewhere. data IdentifiedDate data IdentifiedDateAttributes instance Eq IdentifiedDate instance Eq IdentifiedDateAttributes instance Show IdentifiedDate instance Show IdentifiedDateAttributes instance SchemaType IdentifiedDate instance Extension IdentifiedDate Xsd.Date -- | A type extending the PayerReceiverEnum type wih an id -- attribute. data IdentifiedPayerReceiver data IdentifiedPayerReceiverAttributes instance Eq IdentifiedPayerReceiver instance Eq IdentifiedPayerReceiverAttributes instance Show IdentifiedPayerReceiver instance Show IdentifiedPayerReceiverAttributes instance SchemaType IdentifiedPayerReceiver instance Extension IdentifiedPayerReceiver PayerReceiverEnum -- | A party's industry sector classification. data IndustryClassification data IndustryClassificationAttributes instance Eq IndustryClassification instance Eq IndustryClassificationAttributes instance Show IndustryClassification instance Show IndustryClassificationAttributes instance SchemaType IndustryClassification instance Extension IndustryClassification Scheme data InformationProvider data InformationProviderAttributes instance Eq InformationProvider instance Eq InformationProviderAttributes instance Show InformationProvider instance Show InformationProviderAttributes instance SchemaType InformationProvider instance Extension InformationProvider Scheme -- | A type defining the source for a piece of information (e.g. -- a rate refix or an fx fixing). data InformationSource instance Eq InformationSource instance Show InformationSource instance SchemaType InformationSource -- | A short form unique identifier for a security. data InstrumentId data InstrumentIdAttributes instance Eq InstrumentId instance Eq InstrumentIdAttributes instance Show InstrumentId instance Show InstrumentIdAttributes instance SchemaType InstrumentId instance Extension InstrumentId Scheme -- | A type defining the way in which interests are accrued: the -- applicable rate (fixed or floating reference) and the -- compounding method. data InterestAccrualsCompoundingMethod instance Eq InterestAccrualsCompoundingMethod instance Show InterestAccrualsCompoundingMethod instance SchemaType InterestAccrualsCompoundingMethod instance Extension InterestAccrualsCompoundingMethod InterestAccrualsMethod -- | A type describing the method for accruing interests on -- dividends. Can be either a fixed rate reference or a -- floating rate reference. data InterestAccrualsMethod instance Eq InterestAccrualsMethod instance Show InterestAccrualsMethod instance SchemaType InterestAccrualsMethod -- | A type that describes the information to identify an -- intermediary through which payment will be made by the -- correspondent bank to the ultimate beneficiary of the -- funds. data IntermediaryInformation instance Eq IntermediaryInformation instance Show IntermediaryInformation instance SchemaType IntermediaryInformation -- | The type of interpolation used. data InterpolationMethod data InterpolationMethodAttributes instance Eq InterpolationMethod instance Eq InterpolationMethodAttributes instance Show InterpolationMethod instance Show InterpolationMethodAttributes instance SchemaType InterpolationMethod instance Extension InterpolationMethod Scheme -- | The data type used for indicating the language of the -- resource, described using the ISO 639-2/T Code. data Language data LanguageAttributes instance Eq Language instance Eq LanguageAttributes instance Show Language instance Show LanguageAttributes instance SchemaType Language instance Extension Language Scheme -- | A supertype of leg. All swap legs extend this type. data Leg instance Eq Leg instance Show Leg instance SchemaType Leg -- | A type defining a legal entity. data LegalEntity instance Eq LegalEntity instance Show LegalEntity instance SchemaType LegalEntity -- | References a credit entity defined elsewhere in the -- document. data LegalEntityReference instance Eq LegalEntityReference instance Show LegalEntityReference instance SchemaType LegalEntityReference instance Extension LegalEntityReference Reference -- | A type to define the main publication source. data MainPublication data MainPublicationAttributes instance Eq MainPublication instance Eq MainPublicationAttributes instance Show MainPublication instance Show MainPublicationAttributes instance SchemaType MainPublication instance Extension MainPublication Scheme -- | A type defining manual exercise, i.e. that the option buyer -- counterparty must give notice to the option seller of -- exercise. data ManualExercise instance Eq ManualExercise instance Show ManualExercise instance SchemaType ManualExercise -- | An entity for defining the agreement executed between the -- parties and intended to govern all OTC derivatives -- transactions between those parties. data MasterAgreement instance Eq MasterAgreement instance Show MasterAgreement instance SchemaType MasterAgreement data MasterAgreementType data MasterAgreementTypeAttributes instance Eq MasterAgreementType instance Eq MasterAgreementTypeAttributes instance Show MasterAgreementType instance Show MasterAgreementTypeAttributes instance SchemaType MasterAgreementType instance Extension MasterAgreementType Scheme data MasterAgreementVersion data MasterAgreementVersionAttributes instance Eq MasterAgreementVersion instance Eq MasterAgreementVersionAttributes instance Show MasterAgreementVersion instance Show MasterAgreementVersionAttributes instance SchemaType MasterAgreementVersion instance Extension MasterAgreementVersion Scheme -- | An entity for defining the master confirmation agreement -- executed between the parties. data MasterConfirmation instance Eq MasterConfirmation instance Show MasterConfirmation instance SchemaType MasterConfirmation data MasterConfirmationAnnexType data MasterConfirmationAnnexTypeAttributes instance Eq MasterConfirmationAnnexType instance Eq MasterConfirmationAnnexTypeAttributes instance Show MasterConfirmationAnnexType instance Show MasterConfirmationAnnexTypeAttributes instance SchemaType MasterConfirmationAnnexType instance Extension MasterConfirmationAnnexType Scheme data MasterConfirmationType data MasterConfirmationTypeAttributes instance Eq MasterConfirmationType instance Eq MasterConfirmationTypeAttributes instance Show MasterConfirmationType instance Show MasterConfirmationTypeAttributes instance SchemaType MasterConfirmationType instance Extension MasterConfirmationType Scheme -- | An identifier used to identify matched cashflows. data MatchId data MatchIdAttributes instance Eq MatchId instance Eq MatchIdAttributes instance Show MatchId instance Show MatchIdAttributes instance SchemaType MatchId instance Extension MatchId Scheme -- | A type defining a mathematical expression. data Math instance Eq Math instance Show Math instance SchemaType Math data MatrixType data MatrixTypeAttributes instance Eq MatrixType instance Eq MatrixTypeAttributes instance Show MatrixType instance Show MatrixTypeAttributes instance SchemaType MatrixType instance Extension MatrixType Scheme data MatrixTerm data MatrixTermAttributes instance Eq MatrixTerm instance Eq MatrixTermAttributes instance Show MatrixTerm instance Show MatrixTermAttributes instance SchemaType MatrixTerm instance Extension MatrixTerm Scheme -- | The type that indicates the type of media used to store the -- content. MimeType is used to determine the software -- product(s) that can read the content. MIME types are -- described in RFC 2046. data MimeType data MimeTypeAttributes instance Eq MimeType instance Eq MimeTypeAttributes instance Show MimeType instance Show MimeTypeAttributes instance SchemaType MimeType instance Extension MimeType Scheme -- | A type defining a currency amount. data Money instance Eq Money instance Show Money instance SchemaType Money instance Extension Money MoneyBase -- | Abstract base class for all money types. data MoneyBase instance Eq MoneyBase instance Show MoneyBase instance SchemaType MoneyBase -- | A type defining multiple exercises. As defining in the 2000 -- ISDA Definitions, Section 12.4. Multiple Exercise, the -- buyer of the option has the right to exercise all or less -- than all the unexercised notional amount of the underlying -- swap on one or more days in the exercise period, but on any -- such day may not exercise less than the minimum notional -- amount or more than the maximum notional amount, and if an -- integral multiple amount is specified, the notional -- exercised must be equal to or, be an integral multiple of, -- the integral multiple amount. data MultipleExercise instance Eq MultipleExercise instance Show MultipleExercise instance SchemaType MultipleExercise -- | A type defining a currency amount or a currency amount -- schedule. data NonNegativeAmountSchedule instance Eq NonNegativeAmountSchedule instance Show NonNegativeAmountSchedule instance SchemaType NonNegativeAmountSchedule instance Extension NonNegativeAmountSchedule NonNegativeSchedule -- | A type defining a non negative money amount. data NonNegativeMoney instance Eq NonNegativeMoney instance Show NonNegativeMoney instance SchemaType NonNegativeMoney instance Extension NonNegativeMoney MoneyBase -- | A complex type to specify non negative payments. data NonNegativePayment instance Eq NonNegativePayment instance Show NonNegativePayment instance SchemaType NonNegativePayment instance Extension NonNegativePayment PaymentBaseExtended instance Extension NonNegativePayment PaymentBase -- | A type defining a schedule of non-negative rates or amounts -- in terms of an initial value and then a series of step date -- and value pairs. On each step date the rate or amount -- changes to the new step value. The series of step date and -- value pairs are optional. If not specified, this implies -- that the initial value remains unchanged over time. data NonNegativeSchedule instance Eq NonNegativeSchedule instance Show NonNegativeSchedule instance SchemaType NonNegativeSchedule -- | A type defining a step date and non-negative step value -- pair. This step definitions are used to define varying rate -- or amount schedules, e.g. a notional amortization or a -- step-up coupon schedule. data NonNegativeStep instance Eq NonNegativeStep instance Show NonNegativeStep instance SchemaType NonNegativeStep instance Extension NonNegativeStep StepBase -- | A complex type to specify the notional amount. data NotionalAmount instance Eq NotionalAmount instance Show NotionalAmount instance SchemaType NotionalAmount instance Extension NotionalAmount NonNegativeMoney instance Extension NotionalAmount MoneyBase -- | A reference to the notional amount. data NotionalAmountReference instance Eq NotionalAmountReference instance Show NotionalAmountReference instance SchemaType NotionalAmountReference instance Extension NotionalAmountReference Reference -- | A reference to the notional amount. data NotionalReference instance Eq NotionalReference instance Show NotionalReference instance SchemaType NotionalReference instance Extension NotionalReference Reference -- | A type defining an offset used in calculating a new date -- relative to a reference date. Currently, the only offsets -- defined are expected to be expressed as either calendar or -- business day offsets. data Offset instance Eq Offset instance Show Offset instance SchemaType Offset instance Extension Offset Period -- | Allows the specification of a time that may be on a day -- prior or subsequent to the day in question. This type is -- intended for use with a day of the week (i.e. where no -- actual date is specified) as part of, for example, a period -- that runs from 23:00-07:00 on a series of days and where -- holidays on the actual days would affect the entire time -- period. data OffsetPrevailingTime instance Eq OffsetPrevailingTime instance Show OffsetPrevailingTime instance SchemaType OffsetPrevailingTime data OnBehalfOf instance Eq OnBehalfOf instance Show OnBehalfOf instance SchemaType OnBehalfOf data OriginatingEvent data OriginatingEventAttributes instance Eq OriginatingEvent instance Eq OriginatingEventAttributes instance Show OriginatingEvent instance Show OriginatingEventAttributes instance SchemaType OriginatingEvent instance Extension OriginatingEvent Scheme -- | A type defining partial exercise. As defined in the 2000 -- ISDA Definitions, Section 12.3 Partial Exercise, the buyer -- of the option may exercise all or less than all the -- notional amount of the underlying swap but may not be less -- than the minimum notional amount (if specified) and must be -- an integral multiple of the integral multiple amount if -- specified. data PartialExercise instance Eq PartialExercise instance Show PartialExercise instance SchemaType PartialExercise data Party instance Eq Party instance Show Party instance SchemaType Party -- | The data type used for party identifiers. data PartyId data PartyIdAttributes instance Eq PartyId instance Eq PartyIdAttributes instance Show PartyId instance Show PartyIdAttributes instance SchemaType PartyId instance Extension PartyId Scheme -- | The data type used for the legal name of an organization. data PartyName data PartyNameAttributes instance Eq PartyName instance Eq PartyNameAttributes instance Show PartyName instance Show PartyNameAttributes instance SchemaType PartyName instance Extension PartyName Scheme -- | Reference to a party. data PartyReference instance Eq PartyReference instance Show PartyReference instance SchemaType PartyReference instance Extension PartyReference Reference data PartyRelationship instance Eq PartyRelationship instance Show PartyRelationship instance SchemaType PartyRelationship -- | A description of the legal agreement(s) and definitions -- that document a party's relationships with other parties data PartyRelationshipDocumentation instance Eq PartyRelationshipDocumentation instance Show PartyRelationshipDocumentation instance SchemaType PartyRelationshipDocumentation -- | A type describing a role played by a party in one or more -- transactions. Examples include roles such as guarantor, -- custodian, confirmation service provider, etc. This can be -- extended to provide custom roles. data PartyRole data PartyRoleAttributes instance Eq PartyRole instance Eq PartyRoleAttributes instance Show PartyRole instance Show PartyRoleAttributes instance SchemaType PartyRole instance Extension PartyRole Scheme -- | A type refining the role a role played by a party in one or -- more transactions. Examples include "AllPositions" and -- "SomePositions" for Guarantor. This can be extended to -- provide custom types. data PartyRoleType data PartyRoleTypeAttributes instance Eq PartyRoleType instance Eq PartyRoleTypeAttributes instance Show PartyRoleType instance Show PartyRoleTypeAttributes instance SchemaType PartyRoleType instance Extension PartyRoleType Scheme -- | Reference to an organizational unit. data BusinessUnitReference instance Eq BusinessUnitReference instance Show BusinessUnitReference instance SchemaType BusinessUnitReference instance Extension BusinessUnitReference Reference -- | Reference to an individual. data PersonReference instance Eq PersonReference instance Show PersonReference instance SchemaType PersonReference instance Extension PersonReference Reference -- | A reference to a partyTradeIdentifier object. data PartyTradeIdentifierReference instance Eq PartyTradeIdentifierReference instance Show PartyTradeIdentifierReference instance SchemaType PartyTradeIdentifierReference instance Extension PartyTradeIdentifierReference Reference -- | A type for defining payments data Payment instance Eq Payment instance Show Payment instance SchemaType Payment instance Extension Payment PaymentBase -- | An abstract base class for payment types. data PaymentBase instance Eq PaymentBase instance Show PaymentBase instance SchemaType PaymentBase -- | Base type for payments. data PaymentBaseExtended instance Eq PaymentBaseExtended instance Show PaymentBaseExtended instance SchemaType PaymentBaseExtended instance Extension PaymentBaseExtended PaymentBase -- | Details on the referenced payment. e.g. Its cashflow -- components, settlement details. data PaymentDetails instance Eq PaymentDetails instance Show PaymentDetails instance SchemaType PaymentDetails -- | An identifier used to identify a matchable payment. data PaymentId data PaymentIdAttributes instance Eq PaymentId instance Eq PaymentIdAttributes instance Show PaymentId instance Show PaymentIdAttributes instance SchemaType PaymentId instance Extension PaymentId Scheme -- | Reference to a payment. data PaymentReference instance Eq PaymentReference instance Show PaymentReference instance SchemaType PaymentReference instance Extension PaymentReference Reference data PaymentType data PaymentTypeAttributes instance Eq PaymentType instance Eq PaymentTypeAttributes instance Show PaymentType instance Show PaymentTypeAttributes instance SchemaType PaymentType instance Extension PaymentType Scheme -- | A type to define recurring periods or time offsets. data Period instance Eq Period instance Show Period instance SchemaType Period data PeriodicDates instance Eq PeriodicDates instance Show PeriodicDates instance SchemaType PeriodicDates -- | A type defining a currency amount or a currency amount -- schedule. data PositiveAmountSchedule instance Eq PositiveAmountSchedule instance Show PositiveAmountSchedule instance SchemaType PositiveAmountSchedule instance Extension PositiveAmountSchedule PositiveSchedule -- | A type defining a positive money amount data PositiveMoney instance Eq PositiveMoney instance Show PositiveMoney instance SchemaType PositiveMoney instance Extension PositiveMoney MoneyBase -- | A complex type to specify positive payments. data PositivePayment instance Eq PositivePayment instance Show PositivePayment instance SchemaType PositivePayment instance Extension PositivePayment PaymentBaseExtended instance Extension PositivePayment PaymentBase -- | A type defining a schedule of strictly-postive rates or -- amounts in terms of an initial value and then a series of -- step date and value pairs. On each step date the rate or -- amount changes to the new step value. The series of step -- date and value pairs are optional. If not specified, this -- implies that the initial value remains unchanged over time. data PositiveSchedule instance Eq PositiveSchedule instance Show PositiveSchedule instance SchemaType PositiveSchedule -- | A type defining a step date and strictly-positive step -- value pair. This step definitions are used to define -- varying rate or amount schedules, e.g. a notional -- amortization or a step-up coupon schedule. data PositiveStep instance Eq PositiveStep instance Show PositiveStep instance SchemaType PositiveStep instance Extension PositiveStep StepBase -- | A type for defining a time with respect to a geographic -- location, for example 11:00 Phoenix, USA. This type should -- be used where a wider range of locations than those -- available as business centres is required. data PrevailingTime instance Eq PrevailingTime instance Show PrevailingTime instance SchemaType PrevailingTime -- | An abstract pricing structure base type. Used as a base for -- structures such as yield curves and volatility matrices. data PricingStructure instance Eq PricingStructure instance Show PricingStructure instance SchemaType PricingStructure -- | Reference to a pricing structure or any derived components -- (i.e. yield curve). data PricingStructureReference instance Eq PricingStructureReference instance Show PricingStructureReference instance SchemaType PricingStructureReference instance Extension PricingStructureReference Reference -- | A type defining which principal exchanges occur for the -- stream. data PrincipalExchanges instance Eq PrincipalExchanges instance Show PrincipalExchanges instance SchemaType PrincipalExchanges -- | The base type which all FpML products extend. data Product instance Eq Product instance Show Product instance SchemaType Product data ProductId data ProductIdAttributes instance Eq ProductId instance Eq ProductIdAttributes instance Show ProductId instance Show ProductIdAttributes instance SchemaType ProductId instance Extension ProductId Scheme -- | Reference to a full FpML product. data ProductReference instance Eq ProductReference instance Show ProductReference instance SchemaType ProductReference instance Extension ProductReference Reference data ProductType data ProductTypeAttributes instance Eq ProductType instance Eq ProductTypeAttributes instance Show ProductType instance Show ProductTypeAttributes instance SchemaType ProductType instance Extension ProductType Scheme -- | A type that describes the composition of a rate that has -- been quoted or is to be quoted. This includes the two -- currencies and the quotation relationship between the two -- currencies and is used as a building block throughout the -- FX specification. data QuotedCurrencyPair instance Eq QuotedCurrencyPair instance Show QuotedCurrencyPair instance SchemaType QuotedCurrencyPair -- | The abstract base class for all types which define interest -- rate streams. data Rate instance Eq Rate instance Show Rate instance SchemaType Rate -- | Reference to any rate (floating, inflation) derived from -- the abstract Rate component. data RateReference instance Eq RateReference instance Show RateReference instance SchemaType RateReference -- | A type defining parameters associated with an individual -- observation or fixing. This type forms part of the cashflow -- representation of a stream. data RateObservation instance Eq RateObservation instance Show RateObservation instance SchemaType RateObservation data RateSourcePage data RateSourcePageAttributes instance Eq RateSourcePage instance Eq RateSourcePageAttributes instance Show RateSourcePage instance Show RateSourcePageAttributes instance SchemaType RateSourcePage instance Extension RateSourcePage Scheme -- | The abstract base class for all types which define -- intra-document pointers. data Reference instance Eq Reference instance Show Reference instance SchemaType Reference -- | Specifies the reference amount using a scheme. data ReferenceAmount data ReferenceAmountAttributes instance Eq ReferenceAmount instance Eq ReferenceAmountAttributes instance Show ReferenceAmount instance Show ReferenceAmountAttributes instance SchemaType ReferenceAmount instance Extension ReferenceAmount Scheme -- | A type to describe an institution (party) identified by -- means of a coding scheme and an optional name. data ReferenceBank instance Eq ReferenceBank instance Show ReferenceBank instance SchemaType ReferenceBank data ReferenceBankId data ReferenceBankIdAttributes instance Eq ReferenceBankId instance Eq ReferenceBankIdAttributes instance Show ReferenceBankId instance Show ReferenceBankIdAttributes instance SchemaType ReferenceBankId instance Extension ReferenceBankId Scheme data RelatedBusinessUnit instance Eq RelatedBusinessUnit instance Show RelatedBusinessUnit instance SchemaType RelatedBusinessUnit data RelatedParty instance Eq RelatedParty instance Show RelatedParty instance SchemaType RelatedParty data RelatedPerson instance Eq RelatedPerson instance Show RelatedPerson instance SchemaType RelatedPerson -- | A type describing a role played by a unit in one or more -- transactions. Examples include roles such as Trader, -- Collateral, Confirmation, Settlement, etc. This can be -- extended to provide custom roles. data BusinessUnitRole data BusinessUnitRoleAttributes instance Eq BusinessUnitRole instance Eq BusinessUnitRoleAttributes instance Show BusinessUnitRole instance Show BusinessUnitRoleAttributes instance SchemaType BusinessUnitRole instance Extension BusinessUnitRole Scheme -- | A type describing a role played by a person in one or more -- transactions. Examples include roles such as Trader, -- Broker, MiddleOffice, Legal, etc. This can be extended to -- provide custom roles. data PersonRole data PersonRoleAttributes instance Eq PersonRole instance Eq PersonRoleAttributes instance Show PersonRole instance Show PersonRoleAttributes instance SchemaType PersonRole instance Extension PersonRole Scheme -- | A type defining a date (referred to as the derived date) as -- a relative offset from another date (referred to as the -- anchor date). If the anchor date is itself an adjustable -- date then the offset is assumed to be calculated from the -- adjusted anchor date. A number of different scenarios can -- be supported, namely; 1) the derived date may simply be a -- number of calendar periods (days, weeks, months or years) -- preceding or following the anchor date; 2) the unadjusted -- derived date may be a number of calendar periods (days, -- weeks, months or years) preceding or following the anchor -- date with the resulting unadjusted derived date subject to -- adjustment in accordance with a specified business day -- convention, i.e. the derived date must fall on a good -- business day; 3) the derived date may be a number of -- business days preceding or following the anchor date. Note -- that the businessDayConvention specifies any required -- adjustment to the unadjusted derived date. A negative or -- positive value in the periodMultiplier indicates whether -- the unadjusted derived precedes or follows the anchor date. -- The businessDayConvention should contain a value NONE if -- the day type element contains a value of Business (since -- specifying a negative or positive business days offset -- would already guarantee that the derived date would fall on -- a good business day in the specified business centers). data RelativeDateOffset instance Eq RelativeDateOffset instance Show RelativeDateOffset instance SchemaType RelativeDateOffset instance Extension RelativeDateOffset Offset instance Extension RelativeDateOffset Period -- | A type describing a set of dates defined as relative to -- another set of dates. data RelativeDates instance Eq RelativeDates instance Show RelativeDates instance SchemaType RelativeDates instance Extension RelativeDates RelativeDateOffset instance Extension RelativeDates Offset instance Extension RelativeDates Period -- | A type describing a date when this date is defined in -- reference to another date through one or several date -- offsets. data RelativeDateSequence instance Eq RelativeDateSequence instance Show RelativeDateSequence instance SchemaType RelativeDateSequence -- | A date with a required identifier which can be referenced -- elsewhere. data RequiredIdentifierDate data RequiredIdentifierDateAttributes instance Eq RequiredIdentifierDate instance Eq RequiredIdentifierDateAttributes instance Show RequiredIdentifierDate instance Show RequiredIdentifierDateAttributes instance SchemaType RequiredIdentifierDate instance Extension RequiredIdentifierDate Xsd.Date -- | A type defining the reset frequency. In the case of a -- weekly reset, also specifies the day of the week that the -- reset occurs. If the reset frequency is greater than the -- calculation period frequency the this implies that more or -- more reset dates is established for each calculation period -- and some form of rate averaginhg is applicable. The -- specific averaging method of calculation is specified in -- FloatingRateCalculation. In case the reset frequency is of -- value T (term), the period is defined by the -- swap\swapStream\calculationPerioDates\effectiveDate and the -- swap\swapStream\calculationPerioDates\terminationDate. data ResetFrequency instance Eq ResetFrequency instance Show ResetFrequency instance SchemaType ResetFrequency instance Extension ResetFrequency Frequency data RequestedAction data RequestedActionAttributes instance Eq RequestedAction instance Eq RequestedActionAttributes instance Show RequestedAction instance Show RequestedActionAttributes instance SchemaType RequestedAction instance Extension RequestedAction Scheme -- | Describes the resource that contains the media -- representation of a business event (i.e used for stating -- the Publicly Available Information). For example, can -- describe a file or a URL that represents the event. This -- type is an extended version of a type defined by RIXML -- (www.rixml.org). data Resource instance Eq Resource instance Show Resource instance SchemaType Resource -- | The data type used for resource identifiers. data ResourceId data ResourceIdAttributes instance Eq ResourceId instance Eq ResourceIdAttributes instance Show ResourceId instance Show ResourceIdAttributes instance SchemaType ResourceId instance Extension ResourceId Scheme -- | The type that indicates the length of the resource. data ResourceLength instance Eq ResourceLength instance Show ResourceLength instance SchemaType ResourceLength -- | The data type used for describing the type or purpose of a -- resource, e.g. "Confirmation". data ResourceType data ResourceTypeAttributes instance Eq ResourceType instance Eq ResourceTypeAttributes instance Show ResourceType instance Show ResourceTypeAttributes instance SchemaType ResourceType instance Extension ResourceType Scheme -- | A reference to the return swap notional amount. data ReturnSwapNotionalAmountReference instance Eq ReturnSwapNotionalAmountReference instance Show ReturnSwapNotionalAmountReference instance SchemaType ReturnSwapNotionalAmountReference instance Extension ReturnSwapNotionalAmountReference Reference -- | A type defining a rounding direction and precision to be -- used in the rounding of a rate. data Rounding instance Eq Rounding instance Show Rounding instance SchemaType Rounding -- | A type that provides three alternative ways of identifying -- a party involved in the routing of a payment. The -- identification may use payment system identifiers only; -- actual name, address and other reference information; or a -- combination of both. data Routing instance Eq Routing instance Show Routing instance SchemaType Routing -- | A type that models name, address and supplementary textual -- information for the purposes of identifying a party -- involved in the routing of a payment. data RoutingExplicitDetails instance Eq RoutingExplicitDetails instance Show RoutingExplicitDetails instance SchemaType RoutingExplicitDetails data RoutingId data RoutingIdAttributes instance Eq RoutingId instance Eq RoutingIdAttributes instance Show RoutingId instance Show RoutingIdAttributes instance SchemaType RoutingId instance Extension RoutingId Scheme -- | A type that provides for identifying a party involved in -- the routing of a payment by means of one or more standard -- identification codes. For example, both a SWIFT BIC code -- and a national bank identifier may be required. data RoutingIds instance Eq RoutingIds instance Show RoutingIds instance SchemaType RoutingIds -- | A type that provides a combination of payment system -- identification codes with physical postal address details, -- for the purposes of identifying a party involved in the -- routing of a payment. data RoutingIdsAndExplicitDetails instance Eq RoutingIdsAndExplicitDetails instance Show RoutingIdsAndExplicitDetails instance SchemaType RoutingIdsAndExplicitDetails -- | A type defining a schedule of rates or amounts in terms of -- an initial value and then a series of step date and value -- pairs. On each step date the rate or amount changes to the -- new step value. The series of step date and value pairs are -- optional. If not specified, this implies that the initial -- value remains unchanged over time. data Schedule instance Eq Schedule instance Show Schedule instance SchemaType Schedule -- | Reference to a schedule of rates or amounts. data ScheduleReference instance Eq ScheduleReference instance Show ScheduleReference instance SchemaType ScheduleReference instance Extension ScheduleReference Reference -- | A type that represents the choice of methods for settling a -- potential currency payment resulting from a trade: by means -- of a standard settlement instruction, by netting it out -- with other payments, or with an explicit settlement -- instruction. data SettlementInformation instance Eq SettlementInformation instance Show SettlementInformation instance SchemaType SettlementInformation -- | A type that models a complete instruction for settling a -- currency payment, including the settlement method to be -- used, the correspondent bank, any intermediary banks and -- the ultimate beneficary. data SettlementInstruction instance Eq SettlementInstruction instance Show SettlementInstruction instance SchemaType SettlementInstruction data SettlementMethod data SettlementMethodAttributes instance Eq SettlementMethod instance Eq SettlementMethodAttributes instance Show SettlementMethod instance Show SettlementMethodAttributes instance SchemaType SettlementMethod instance Extension SettlementMethod Scheme -- | Coding scheme that specifies the settlement price default -- election. data SettlementPriceDefaultElection data SettlementPriceDefaultElectionAttributes instance Eq SettlementPriceDefaultElection instance Eq SettlementPriceDefaultElectionAttributes instance Show SettlementPriceDefaultElection instance Show SettlementPriceDefaultElectionAttributes instance SchemaType SettlementPriceDefaultElection instance Extension SettlementPriceDefaultElection Scheme -- | The source from which the settlement price is to be -- obtained, e.g. a Reuters page, Prezzo di Riferimento, etc. data SettlementPriceSource data SettlementPriceSourceAttributes instance Eq SettlementPriceSource instance Eq SettlementPriceSourceAttributes instance Show SettlementPriceSource instance Show SettlementPriceSourceAttributes instance SchemaType SettlementPriceSource instance Extension SettlementPriceSource Scheme -- | A type describing the method for obtaining a settlement -- rate. data SettlementRateSource instance Eq SettlementRateSource instance Show SettlementRateSource instance SchemaType SettlementRateSource -- | TBA data SharedAmericanExercise instance Eq SharedAmericanExercise instance Show SharedAmericanExercise instance SchemaType SharedAmericanExercise instance Extension SharedAmericanExercise Exercise -- | A complex type to specified payments in a simpler fashion -- than the Payment type. This construct should be used from -- the version 4.3 onwards. data SimplePayment instance Eq SimplePayment instance Show SimplePayment instance SchemaType SimplePayment instance Extension SimplePayment PaymentBase -- | A type that supports the division of a gross settlement -- amount into a number of split settlements, each requiring -- its own settlement instruction. data SplitSettlement instance Eq SplitSettlement instance Show SplitSettlement instance SchemaType SplitSettlement -- | Adds an optional spread type element to the Schedule to -- identify a long or short spread value. data SpreadSchedule instance Eq SpreadSchedule instance Show SpreadSchedule instance SchemaType SpreadSchedule instance Extension SpreadSchedule Schedule -- | Provides a reference to a spread schedule. data SpreadScheduleReference instance Eq SpreadScheduleReference instance Show SpreadScheduleReference instance SchemaType SpreadScheduleReference instance Extension SpreadScheduleReference Reference -- | Defines a Spread Type Scheme to identify a long or short -- spread value. data SpreadScheduleType data SpreadScheduleTypeAttributes instance Eq SpreadScheduleType instance Eq SpreadScheduleTypeAttributes instance Show SpreadScheduleType instance Show SpreadScheduleTypeAttributes instance SchemaType SpreadScheduleType instance Extension SpreadScheduleType Scheme -- | A type defining a step date and step value pair. This step -- definitions are used to define varying rate or amount -- schedules, e.g. a notional amortization or a step-up coupon -- schedule. data Step instance Eq Step instance Show Step instance SchemaType Step instance Extension Step StepBase -- | A type defining a step date and step value pair. This step -- definitions are used to define varying rate or amount -- schedules, e.g. a notional amortization or a step-up coupon -- schedule. data StepBase instance Eq StepBase instance Show StepBase instance SchemaType StepBase -- | A type that describes the set of street and building number -- information that identifies a postal address within a city. data StreetAddress instance Eq StreetAddress instance Show StreetAddress instance SchemaType StreetAddress -- | A type describing a single cap or floor rate. data Strike instance Eq Strike instance Show Strike instance SchemaType Strike -- | A type describing a schedule of cap or floor rates. data StrikeSchedule instance Eq StrikeSchedule instance Show StrikeSchedule instance SchemaType StrikeSchedule instance Extension StrikeSchedule Schedule -- | A type defining how a stub calculation period amount is -- calculated and the start and end date of the stub. A single -- floating rate tenor different to that used for the regular -- part of the calculation periods schedule may be specified, -- or two floating rate tenors many be specified. If two -- floating rate tenors are specified then Linear -- Interpolation (in accordance with the 2000 ISDA -- Definitions, Section 8.3 Interpolation) is assumed to -- apply. Alternatively, an actual known stub rate or stub -- amount may be specified. data Stub instance Eq Stub instance Show Stub instance SchemaType Stub instance Extension Stub StubValue -- | A type defining how a stub calculation period 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 rate tenors many -- be specified. If two floating rate tenors are specified -- then Linear Interpolation (in accordance with the 2000 ISDA -- Definitions, Section 8.3 Interpolation) is assumed to -- apply. Alternatively, an actual known stub rate or stub -- amount may be specified. data StubValue instance Eq StubValue instance Show StubValue instance SchemaType StubValue -- | A geophraphic location for the purposes of defining a -- prevailing time according to the tz database. data TimezoneLocation data TimezoneLocationAttributes instance Eq TimezoneLocation instance Eq TimezoneLocationAttributes instance Show TimezoneLocation instance Show TimezoneLocationAttributes instance SchemaType TimezoneLocation instance Extension TimezoneLocation Scheme -- | The parameters for defining the exercise period for an -- American style option together with any rules governing the -- notional amount of the underlying which can be exercised on -- any given exercise date and any associated exercise fees. elementAmericanExercise :: XMLParser AmericanExercise elementToXMLAmericanExercise :: AmericanExercise -> [Content ()] -- | The parameters for defining the exercise period for a -- Bermuda style option together with any rules governing the -- notional amount of the underlying which can be exercised on -- any given exercise date and any associated exercise fees. elementBermudaExercise :: XMLParser BermudaExercise elementToXMLBermudaExercise :: BermudaExercise -> [Content ()] -- | The parameters for defining the exercise period for a -- European style option together with any rules governing the -- notional amount of the underlying which can be exercised on -- any given exercise date and any associated exercise fees. elementEuropeanExercise :: XMLParser EuropeanExercise elementToXMLEuropeanExercise :: EuropeanExercise -> [Content ()] -- | An placeholder for the actual option exercise definitions. elementExercise :: XMLParser Exercise elementProduct :: XMLParser Product elementToXMLProduct :: Product -> [Content ()] -- | A code that describes what type of role an organization -- plays, for example a SwapsDealer, a Major Swaps -- Participant, or Other data OrganizationType data OrganizationTypeAttributes instance Eq OrganizationType instance Eq OrganizationTypeAttributes instance Show OrganizationType instance Show OrganizationTypeAttributes instance SchemaType OrganizationType instance Extension OrganizationType Xsd.Token