{-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies #-} {-# OPTIONS_GHC -fno-warn-duplicate-exports #-} module Data.FpML.V53.Doc ( module Data.FpML.V53.Doc , 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 qualified Text.XML.HaXml.Schema.PrimitiveTypes as Xsd import {-# SOURCE #-} Data.FpML.V53.Asset -- | A type representing a value corresponding to an identifier -- for a parameter describing a query portfolio. newtype QueryParameterValue = QueryParameterValue Xsd.XsdString instance Eq QueryParameterValue instance Show QueryParameterValue instance Restricts QueryParameterValue Xsd.XsdString instance SchemaType QueryParameterValue instance SimpleType QueryParameterValue data Allocation instance Eq Allocation instance Show Allocation instance SchemaType Allocation data Allocations instance Eq Allocations instance Show Allocations instance SchemaType Allocations -- | A specific approval state in the workflow. data Approval instance Eq Approval instance Show Approval instance SchemaType Approval data Approvals instance Eq Approvals instance Show Approvals instance SchemaType Approvals -- | A type used to record the differences between the current -- trade and another indicated trade. data BestFitTrade instance Eq BestFitTrade instance Show BestFitTrade instance SchemaType BestFitTrade -- | A type for defining the obligations of the counterparty -- subject to credit support requirements. data Collateral instance Eq Collateral instance Show Collateral instance SchemaType Collateral -- | A contact id identifier allocated by a party. FpML does not -- define the domain values associated with this element. data ContractId data ContractIdAttributes instance Eq ContractId instance Eq ContractIdAttributes instance Show ContractId instance Show ContractIdAttributes instance SchemaType ContractId instance Extension ContractId Scheme -- | A type defining a contract identifier issued by the -- indicated party. data ContractIdentifier instance Eq ContractIdentifier instance Show ContractIdentifier instance SchemaType ContractIdentifier data CreditDerivativesNotices instance Eq CreditDerivativesNotices instance Show CreditDerivativesNotices instance SchemaType CreditDerivativesNotices -- | A type defining a content model that is backwards -- compatible with older FpML releases and which can be used -- to contain sets of data without expressing any processing -- intention. data DataDocument instance Eq DataDocument instance Show DataDocument instance SchemaType DataDocument instance Extension DataDocument Document -- | The abstract base type from which all FpML compliant -- messages and documents must be derived. data Document instance Eq Document instance Show Document instance SchemaType Document -- | A type defining the trade execution date time and the -- source of it. For use inside containing types which already -- have a Reference to a Party that has assigned this trade -- execution date time. data ExecutionDateTime data ExecutionDateTimeAttributes instance Eq ExecutionDateTime instance Eq ExecutionDateTimeAttributes instance Show ExecutionDateTime instance Show ExecutionDateTimeAttributes instance SchemaType ExecutionDateTime instance Extension ExecutionDateTime Xsd.DateTime data FirstPeriodStartDate data FirstPeriodStartDateAttributes instance Eq FirstPeriodStartDate instance Eq FirstPeriodStartDateAttributes instance Show FirstPeriodStartDate instance Show FirstPeriodStartDateAttributes instance SchemaType FirstPeriodStartDate instance Extension FirstPeriodStartDate Xsd.Date data IndependentAmount instance Eq IndependentAmount instance Show IndependentAmount instance SchemaType IndependentAmount -- | The economics of a trade of a multiply traded instrument. data InstrumentTradeDetails instance Eq InstrumentTradeDetails instance Show InstrumentTradeDetails instance SchemaType InstrumentTradeDetails instance Extension InstrumentTradeDetails Product -- | A structure describing the amount of an instrument that was -- traded. data InstrumentTradeQuantity instance Eq InstrumentTradeQuantity instance Show InstrumentTradeQuantity instance SchemaType InstrumentTradeQuantity -- | A structure describing the price paid for the instrument. data InstrumentTradePricing instance Eq InstrumentTradePricing instance Show InstrumentTradePricing instance SchemaType InstrumentTradePricing -- | A structure describing the value in "native" currency of an -- instrument that was traded. data InstrumentTradePrincipal instance Eq InstrumentTradePrincipal instance Show InstrumentTradePrincipal instance SchemaType InstrumentTradePrincipal -- | The data type used for link identifiers. data LinkId data LinkIdAttributes instance Eq LinkId instance Eq LinkIdAttributes instance Show LinkId instance Show LinkIdAttributes instance SchemaType LinkId instance Extension LinkId Scheme -- | A structure including a net and/or a gross amount and -- possibly fees and commissions. data NetAndGross instance Eq NetAndGross instance Show NetAndGross instance SchemaType NetAndGross -- | A type to represent a portfolio name for a particular -- party. data PartyPortfolioName instance Eq PartyPortfolioName instance Show PartyPortfolioName instance SchemaType PartyPortfolioName -- | A type defining one or more trade identifiers allocated to -- the trade by a party. A link identifier allows the trade to -- be associated with other related trades, e.g. trades -- forming part of a larger structured transaction. It is -- expected that for external communication of trade there -- will be only one tradeId sent in the document per party. data PartyTradeIdentifier instance Eq PartyTradeIdentifier instance Show PartyTradeIdentifier instance SchemaType PartyTradeIdentifier instance Extension PartyTradeIdentifier TradeIdentifier -- | A type containing multiple partyTradeIdentifier. data PartyTradeIdentifiers instance Eq PartyTradeIdentifiers instance Show PartyTradeIdentifiers instance SchemaType PartyTradeIdentifiers -- | A type defining additional information that may be recorded -- against a trade. data PartyTradeInformation instance Eq PartyTradeInformation instance Show PartyTradeInformation instance SchemaType PartyTradeInformation -- | Code that describes what type of allocation applies to the -- trade. Options include Unallocated, ToBeAllocated, -- Allocated. data AllocationReportingStatus data AllocationReportingStatusAttributes instance Eq AllocationReportingStatus instance Eq AllocationReportingStatusAttributes instance Show AllocationReportingStatus instance Show AllocationReportingStatusAttributes instance SchemaType AllocationReportingStatus instance Extension AllocationReportingStatus Scheme -- | The current status value of a clearing request. data ClearingStatusValue data ClearingStatusValueAttributes instance Eq ClearingStatusValue instance Eq ClearingStatusValueAttributes instance Show ClearingStatusValue instance Show ClearingStatusValueAttributes instance SchemaType ClearingStatusValue instance Extension ClearingStatusValue Scheme -- | Code that describes what type of collateral is posted by a -- party to a transaction. Options include Uncollateralized, -- Partial, Full, One-Way. data CollateralizationType data CollateralizationTypeAttributes instance Eq CollateralizationType instance Eq CollateralizationTypeAttributes instance Show CollateralizationType instance Show CollateralizationTypeAttributes instance SchemaType CollateralizationType instance Extension CollateralizationType Scheme -- | Records supporting information justifying an end user -- exception under 17 CFR part 39. data EndUserExceptionDeclaration instance Eq EndUserExceptionDeclaration instance Show EndUserExceptionDeclaration instance SchemaType EndUserExceptionDeclaration -- | A credit arrangement used in support of swaps trading. data CreditDocument data CreditDocumentAttributes instance Eq CreditDocument instance Eq CreditDocumentAttributes instance Show CreditDocument instance Show CreditDocumentAttributes instance SchemaType CreditDocument instance Extension CreditDocument Scheme -- | A characteristic of an organization used in declaring an -- end-user exception. data OrganizationCharacteristic data OrganizationCharacteristicAttributes instance Eq OrganizationCharacteristic instance Eq OrganizationCharacteristicAttributes instance Show OrganizationCharacteristic instance Show OrganizationCharacteristicAttributes instance SchemaType OrganizationCharacteristic instance Extension OrganizationCharacteristic Scheme -- | A characteristic of a transaction used in declaring an -- end-user exception. data TransactionCharacteristic data TransactionCharacteristicAttributes instance Eq TransactionCharacteristic instance Eq TransactionCharacteristicAttributes instance Show TransactionCharacteristic instance Show TransactionCharacteristicAttributes instance SchemaType TransactionCharacteristic instance Extension TransactionCharacteristic Scheme -- | A value that explains the reason or purpose that -- information is being reported. Examples might include -- RealTimePublic reporting, PrimaryEconomicTerms reporting, -- Confirmation reporting, or Snapshot reporting. data ReportingPurpose data ReportingPurposeAttributes instance Eq ReportingPurpose instance Eq ReportingPurposeAttributes instance Show ReportingPurpose instance Show ReportingPurposeAttributes instance SchemaType ReportingPurpose instance Extension ReportingPurpose Scheme -- | Provides information about a regulator or other supervisory -- body that an organization is registered with. data SupervisorRegistration instance Eq SupervisorRegistration instance Show SupervisorRegistration instance SchemaType SupervisorRegistration -- | Provides information about how the information in this -- message is applicable to a regulatory reporting process. data ReportingRegime instance Eq ReportingRegime instance Show ReportingRegime instance SchemaType ReportingRegime -- | An ID assigned by a regulator to an organization registered -- with it. (NOTE: should this just by represented by an -- alternate party ID?) data RegulatorId data RegulatorIdAttributes instance Eq RegulatorId instance Eq RegulatorIdAttributes instance Show RegulatorId instance Show RegulatorIdAttributes instance SchemaType RegulatorId instance Extension RegulatorId Scheme -- | Allows timing information about when a trade was processed -- and reported to be recorded. data TradeProcessingTimestamps instance Eq TradeProcessingTimestamps instance Show TradeProcessingTimestamps instance SchemaType TradeProcessingTimestamps -- | A generic trade timestamp data TradeTimestamp instance Eq TradeTimestamp instance Show TradeTimestamp instance SchemaType TradeTimestamp -- | The type or meaning of a timestamp. data TimestampTypeScheme data TimestampTypeSchemeAttributes instance Eq TimestampTypeScheme instance Eq TimestampTypeSchemeAttributes instance Show TimestampTypeScheme instance Show TimestampTypeSchemeAttributes instance SchemaType TimestampTypeScheme instance Extension TimestampTypeScheme Scheme -- | An identifier of an reporting regime or format used for -- regulatory reporting, for example DoddFrankAct, MiFID, -- HongKongOTCDRepository, etc. data ReportingRegimeName data ReportingRegimeNameAttributes instance Eq ReportingRegimeName instance Eq ReportingRegimeNameAttributes instance Show ReportingRegimeName instance Show ReportingRegimeNameAttributes instance SchemaType ReportingRegimeName instance Extension ReportingRegimeName Scheme -- | An identifier of an organization that supervises or -- regulates trading activity, e.g. CFTC, SEC, FSA, ODRF, etc. data SupervisoryBody data SupervisoryBodyAttributes instance Eq SupervisoryBody instance Eq SupervisoryBodyAttributes instance Show SupervisoryBody instance Show SupervisoryBodyAttributes instance SchemaType SupervisoryBody instance Extension SupervisoryBody Scheme -- | A type used to represent the type of market where a trade -- can be executed. data ExecutionVenueType data ExecutionVenueTypeAttributes instance Eq ExecutionVenueType instance Eq ExecutionVenueTypeAttributes instance Show ExecutionVenueType instance Show ExecutionVenueTypeAttributes instance SchemaType ExecutionVenueType instance Extension ExecutionVenueType Scheme -- | A type used to represent the type of market where a trade -- can be executed. data ExecutionType data ExecutionTypeAttributes instance Eq ExecutionType instance Eq ExecutionTypeAttributes instance Show ExecutionType instance Show ExecutionTypeAttributes instance SchemaType ExecutionType instance Extension ExecutionType Scheme -- | A type used to represent the type of mechanism that can be -- used to confirm a trade. data ConfirmationMethod data ConfirmationMethodAttributes instance Eq ConfirmationMethod instance Eq ConfirmationMethodAttributes instance Show ConfirmationMethod instance Show ConfirmationMethodAttributes instance SchemaType ConfirmationMethod instance Extension ConfirmationMethod Scheme data PaymentDetail instance Eq PaymentDetail instance Show PaymentDetail instance SchemaType PaymentDetail instance Extension PaymentDetail PaymentBase -- | The abstract base type from which all calculation rules of -- the independent amount must be derived. data PaymentRule instance Eq PaymentRule instance Show PaymentRule instance SchemaType PaymentRule -- | A type defining a content model for a calculation rule -- defined as percentage of the notional amount. data PercentageRule instance Eq PercentageRule instance Show PercentageRule instance SchemaType PercentageRule instance Extension PercentageRule PaymentRule -- | A type representing an arbitary grouping of trade -- references. data Portfolio instance Eq Portfolio instance Show Portfolio instance SchemaType Portfolio -- | The data type used for portfolio names. data PortfolioName data PortfolioNameAttributes instance Eq PortfolioName instance Eq PortfolioNameAttributes instance Show PortfolioName instance Show PortfolioNameAttributes instance SchemaType PortfolioName instance Extension PortfolioName Scheme -- | A type representing criteria for defining a query -- portfolio. The criteria are made up of a QueryParameterId, -- QueryParameterValue and QueryParameterOperator. data QueryParameter instance Eq QueryParameter instance Show QueryParameter instance SchemaType QueryParameter -- | A type representing an identifier for a parameter -- describing a query portfolio. An identifier can be anything -- from a product name like swap to a termination date. data QueryParameterId data QueryParameterIdAttributes instance Eq QueryParameterId instance Eq QueryParameterIdAttributes instance Show QueryParameterId instance Show QueryParameterIdAttributes instance SchemaType QueryParameterId instance Extension QueryParameterId Scheme -- | A type representing an operator describing the relationship -- of a value to its corresponding identifier for a parameter -- describing a query portfolio. Possible relationships -- include equals, not equals, less than, greater than. -- Possible operators are listed in the -- queryParameterOperatorScheme. data QueryParameterOperator data QueryParameterOperatorAttributes instance Eq QueryParameterOperator instance Eq QueryParameterOperatorAttributes instance Show QueryParameterOperator instance Show QueryParameterOperatorAttributes instance SchemaType QueryParameterOperator instance Extension QueryParameterOperator Scheme -- | A type representing a portfolio obtained by querying the -- set of trades held in a repository. It contains trades -- matching the intersection of all criteria specified using -- one or more queryParameters or trades matching the union of -- two or more child queryPortfolios. data QueryPortfolio instance Eq QueryPortfolio instance Show QueryPortfolio instance SchemaType QueryPortfolio instance Extension QueryPortfolio Portfolio -- | A type containing a code representing the role of a party -- in a report, e.g. the originator, the recipient, the -- counterparty, etc. This is used to clarify which -- participant's information is being reported. data ReportingRole data ReportingRoleAttributes instance Eq ReportingRole instance Eq ReportingRoleAttributes instance Show ReportingRole instance Show ReportingRoleAttributes instance SchemaType ReportingRole instance Extension ReportingRole Scheme -- | A type defining a group of products making up a single -- trade. data Strategy instance Eq Strategy instance Show Strategy instance SchemaType Strategy instance Extension Strategy Product -- | A type defining an FpML trade. data Trade instance Eq Trade instance Show Trade instance SchemaType Trade -- | A scheme used to categorize positions. data TradeCategory data TradeCategoryAttributes instance Eq TradeCategory instance Eq TradeCategoryAttributes instance Show TradeCategory instance Show TradeCategoryAttributes instance SchemaType TradeCategory instance Extension TradeCategory Scheme -- | A type used to record the details of a difference between -- two business objects/ data TradeDifference instance Eq TradeDifference instance Show TradeDifference instance SchemaType TradeDifference -- | A type defining trade related information which is not -- product specific. data TradeHeader instance Eq TradeHeader instance Show TradeHeader instance SchemaType TradeHeader -- | A trade reference identifier allocated by a party. 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. data TradeId data TradeIdAttributes instance Eq TradeId instance Eq TradeIdAttributes instance Show TradeId instance Show TradeIdAttributes instance SchemaType TradeId instance Extension TradeId Scheme -- | A type defining a trade identifier issued by the indicated -- party. data TradeIdentifier instance Eq TradeIdentifier instance Show TradeIdentifier instance SchemaType TradeIdentifier -- | The data type used for issuer identifiers. data IssuerId data IssuerIdAttributes instance Eq IssuerId instance Eq IssuerIdAttributes instance Show IssuerId instance Show IssuerIdAttributes instance SchemaType IssuerId instance Extension IssuerId Scheme data Trader data TraderAttributes instance Eq Trader instance Eq TraderAttributes instance Show Trader instance Show TraderAttributes instance SchemaType Trader instance Extension Trader Scheme -- | A reference identifying a rule within a validation scheme. data Validation data ValidationAttributes instance Eq Validation instance Eq ValidationAttributes instance Show Validation instance Show ValidationAttributes instance SchemaType Validation instance Extension Validation Scheme -- | Contract Id with Version Support data VersionedContractId instance Eq VersionedContractId instance Show VersionedContractId instance SchemaType VersionedContractId -- | Trade Id with Version Support data VersionedTradeId instance Eq VersionedTradeId instance Show VersionedTradeId instance SchemaType VersionedTradeId -- | A type to hold trades of multiply-traded instruments. -- Typically this will be used to represent the trade -- resulting from a physically-settled OTC product where the -- underlying is a security, for example the exercise of a -- physically-settled option. elementInstrumentTradeDetails :: XMLParser InstrumentTradeDetails elementToXMLInstrumentTradeDetails :: InstrumentTradeDetails -> [Content ()] -- | A strategy product. elementStrategy :: XMLParser Strategy elementToXMLStrategy :: Strategy -> [Content ()]