{-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies #-} {-# OPTIONS_GHC -fno-warn-duplicate-exports #-} module Data.FpML.V53.Msg ( module Data.FpML.V53.Msg , module Data.FpML.V53.Doc ) 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.Doc data Acknowledgement instance Eq Acknowledgement instance Show Acknowledgement instance SchemaType Acknowledgement instance Extension Acknowledgement ResponseMessage instance Extension Acknowledgement Message instance Extension Acknowledgement Document -- | Provides extra information not represented in the model -- that may be useful in processing the message i.e. -- diagnosing the reason for failure. data AdditionalData instance Eq AdditionalData instance Show AdditionalData instance SchemaType AdditionalData -- | A type defining the content model for a request message -- that can be subsequently corrected or retracted. data CorrectableRequestMessage instance Eq CorrectableRequestMessage instance Show CorrectableRequestMessage instance SchemaType CorrectableRequestMessage instance Extension CorrectableRequestMessage RequestMessage instance Extension CorrectableRequestMessage Message instance Extension CorrectableRequestMessage Document -- | A type defining a correlation identifier and qualifying -- scheme data CorrelationId data CorrelationIdAttributes instance Eq CorrelationId instance Eq CorrelationIdAttributes instance Show CorrelationId instance Show CorrelationIdAttributes instance SchemaType CorrelationId instance Extension CorrelationId Xsd.NormalizedString -- | Identification of a business event, for example through its -- correlation id or a business identifier. data EventIdentifier instance Eq EventIdentifier instance Show EventIdentifier instance SchemaType EventIdentifier -- | A coding scheme used to describe the matching/confirmation -- status of a trade, post-trade event, position, or cash -- flows. data EventStatus data EventStatusAttributes instance Eq EventStatus instance Eq EventStatusAttributes instance Show EventStatus instance Show EventStatusAttributes instance SchemaType EventStatus instance Extension EventStatus Scheme -- | A type used in event status enquiry messages which relates -- an event identifier to its current status value. data EventStatusItem instance Eq EventStatusItem instance Show EventStatusItem instance SchemaType EventStatusItem -- | A type defining the content model for a message normally -- generated in response to a requestEventStatus request. data EventStatusResponse instance Eq EventStatusResponse instance Show EventStatusResponse instance SchemaType EventStatusResponse instance Extension EventStatusResponse ResponseMessage instance Extension EventStatusResponse Message instance Extension EventStatusResponse Document -- | A type defining the basic content for a message sent to -- inform another system that some exception has been -- detected. data Exception instance Eq Exception instance Show Exception instance SchemaType Exception instance Extension Exception Message instance Extension Exception Document -- | A type defining the content model for an exception message -- header. data ExceptionMessageHeader instance Eq ExceptionMessageHeader instance Show ExceptionMessageHeader instance SchemaType ExceptionMessageHeader instance Extension ExceptionMessageHeader MessageHeader -- | A type defining the basic structure of all FpML messages -- which is refined by its derived types. data Message instance Eq Message instance Show Message instance SchemaType Message instance Extension Message Document -- | A type holding a structure that is unvalidated data UnprocessedElementWrapper instance Eq UnprocessedElementWrapper instance Show UnprocessedElementWrapper instance SchemaType UnprocessedElementWrapper -- | The data type used for identifying a message address. data MessageAddress data MessageAddressAttributes instance Eq MessageAddress instance Eq MessageAddressAttributes instance Show MessageAddress instance Show MessageAddressAttributes instance SchemaType MessageAddress instance Extension MessageAddress Scheme -- | A type defining the content model for a generic message -- header that is refined by its derived classes. data MessageHeader instance Eq MessageHeader instance Show MessageHeader instance SchemaType MessageHeader -- | The data type use for message identifiers. data MessageId data MessageIdAttributes instance Eq MessageId instance Eq MessageIdAttributes instance Show MessageId instance Show MessageIdAttributes instance SchemaType MessageId instance Extension MessageId Scheme -- | A type defining the content model for a request message -- that cannot be subsequently corrected or retracted. data NonCorrectableRequestMessage instance Eq NonCorrectableRequestMessage instance Show NonCorrectableRequestMessage instance SchemaType NonCorrectableRequestMessage instance Extension NonCorrectableRequestMessage RequestMessage instance Extension NonCorrectableRequestMessage Message instance Extension NonCorrectableRequestMessage Document -- | A type defining the basic content for a message sent to -- inform another system that some 'business event' has -- occured. Notifications are not expected to be replied to. data NotificationMessage instance Eq NotificationMessage instance Show NotificationMessage instance SchemaType NotificationMessage instance Extension NotificationMessage Message -- | A type that refines the generic message header to match the -- requirements of a NotificationMessage. data NotificationMessageHeader instance Eq NotificationMessageHeader instance Show NotificationMessageHeader instance SchemaType NotificationMessageHeader instance Extension NotificationMessageHeader MessageHeader -- | A version of a specification document used by the message -- generator to format the document. data ImplementationSpecification instance Eq ImplementationSpecification instance Show ImplementationSpecification instance SchemaType ImplementationSpecification data ImplementationSpecificationVersion data ImplementationSpecificationVersionAttributes instance Eq ImplementationSpecificationVersion instance Eq ImplementationSpecificationVersionAttributes instance Show ImplementationSpecificationVersion instance Show ImplementationSpecificationVersionAttributes instance SchemaType ImplementationSpecificationVersion instance Extension ImplementationSpecificationVersion Scheme -- | A type defining additional information that may be recorded -- against a message. data PartyMessageInformation instance Eq PartyMessageInformation instance Show PartyMessageInformation instance SchemaType PartyMessageInformation -- | A structure used to group together individual messages that -- can be acted on at a group level. data PortfolioReference instance Eq PortfolioReference instance Show PortfolioReference instance SchemaType PortfolioReference instance Extension PortfolioReference PortfolioReferenceBase -- | A structure used to group together individual messages that -- can be acted on at a group level. data PortfolioConstituentReference instance Eq PortfolioConstituentReference instance Show PortfolioConstituentReference instance SchemaType PortfolioConstituentReference instance Extension PortfolioConstituentReference PortfolioReferenceBase -- | A structure used to identify a portfolio in a message. data PortfolioReferenceBase instance Eq PortfolioReferenceBase instance Show PortfolioReferenceBase instance SchemaType PortfolioReferenceBase -- | Provides a lexical location (i.e. a line number and -- character for bad XML) or an XPath location (i.e. place to -- identify the bad location for valid XML). data ProblemLocation data ProblemLocationAttributes instance Eq ProblemLocation instance Eq ProblemLocationAttributes instance Show ProblemLocation instance Show ProblemLocationAttributes instance SchemaType ProblemLocation instance Extension ProblemLocation Xsd.NormalizedString -- | A type defining a content model for describing the nature -- and possible location of a error within a previous message. data Reason instance Eq Reason instance Show Reason instance SchemaType Reason -- | Defines a list of machine interpretable error codes. data ReasonCode data ReasonCodeAttributes instance Eq ReasonCode instance Eq ReasonCodeAttributes instance Show ReasonCode instance Show ReasonCodeAttributes instance SchemaType ReasonCode instance Extension ReasonCode Scheme -- | A type that allows the specific report and section to be -- identified. data ReportIdentification instance Eq ReportIdentification instance Show ReportIdentification instance SchemaType ReportIdentification instance Extension ReportIdentification ReportSectionIdentification -- | A type that allows the specific report and section to be -- identified. data ReportSectionIdentification instance Eq ReportSectionIdentification instance Show ReportSectionIdentification instance SchemaType ReportSectionIdentification -- | A type that can be used to hold an identifier for a report -- instance. data ReportId data ReportIdAttributes instance Eq ReportId instance Eq ReportIdAttributes instance Show ReportId instance Show ReportIdAttributes instance SchemaType ReportId instance Extension ReportId Scheme -- | A type defining the content model for a message allowing -- one party to query the status of one event (trade or -- post-trade event) previously sent to another party. data RequestEventStatus instance Eq RequestEventStatus instance Show RequestEventStatus instance SchemaType RequestEventStatus instance Extension RequestEventStatus NonCorrectableRequestMessage instance Extension RequestEventStatus RequestMessage instance Extension RequestEventStatus Message instance Extension RequestEventStatus Document -- | A type that can be used to identify the type of business -- process in a request. Examples include Allocation, -- Clearing, Confirmation, etc. data BusinessProcess data BusinessProcessAttributes instance Eq BusinessProcess instance Eq BusinessProcessAttributes instance Show BusinessProcess instance Show BusinessProcessAttributes instance SchemaType BusinessProcess instance Extension BusinessProcess Scheme -- | A type defining the basic content of a message that -- requests the receiver to perform some business operation -- determined by the message type and its content. data RequestMessage instance Eq RequestMessage instance Show RequestMessage instance SchemaType RequestMessage instance Extension RequestMessage Message -- | A type refining the generic message header content to make -- it specific to request messages. data RequestMessageHeader instance Eq RequestMessageHeader instance Show RequestMessageHeader instance SchemaType RequestMessageHeader instance Extension RequestMessageHeader MessageHeader -- | A message to request that a message be retransmitted. The -- original message will typically be a component of a group -- of messages, such as a portfolio or a report in multiple -- parts. data RequestRetransmission instance Eq RequestRetransmission instance Show RequestRetransmission instance SchemaType RequestRetransmission instance Extension RequestRetransmission NonCorrectableRequestMessage instance Extension RequestRetransmission RequestMessage instance Extension RequestRetransmission Message instance Extension RequestRetransmission Document -- | A type refining the generic message content model to make -- it specific to response messages. data ResponseMessage instance Eq ResponseMessage instance Show ResponseMessage instance SchemaType ResponseMessage instance Extension ResponseMessage Message -- | A type refining the generic message header to make it -- specific to response messages. data ResponseMessageHeader instance Eq ResponseMessageHeader instance Show ResponseMessageHeader instance SchemaType ResponseMessageHeader instance Extension ResponseMessageHeader MessageHeader -- | Event Status messages. elementRequestEventStatus :: XMLParser RequestEventStatus elementToXMLRequestEventStatus :: RequestEventStatus -> [Content ()] elementRequestRetransmission :: XMLParser RequestRetransmission elementToXMLRequestRetransmission :: RequestRetransmission -> [Content ()] -- | A type defining the content model for a message that allows -- a service to send a notification message to a user of the -- service. data ServiceNotification instance Eq ServiceNotification instance Show ServiceNotification instance SchemaType ServiceNotification instance Extension ServiceNotification NotificationMessage instance Extension ServiceNotification Message instance Extension ServiceNotification Document -- | A type defining the content model for report on the status -- of the processing by a service. In the future we may wish -- to provide some kind of scope or other qualification for -- the event, e.g. the currencies, products, or books to which -- it applies. data ServiceProcessingStatus instance Eq ServiceProcessingStatus instance Show ServiceProcessingStatus instance SchemaType ServiceProcessingStatus -- | A type that can be used to describe the availability or -- other state of a service, e.g. Available, Unavaialble. data ServiceStatus data ServiceStatusAttributes instance Eq ServiceStatus instance Eq ServiceStatusAttributes instance Show ServiceStatus instance Show ServiceStatusAttributes instance SchemaType ServiceStatus instance Extension ServiceStatus Scheme -- | A type that can be used to describe the processing phase of -- a service. For example, EndOfDay, Intraday. data ServiceProcessingCycle data ServiceProcessingCycleAttributes instance Eq ServiceProcessingCycle instance Eq ServiceProcessingCycleAttributes instance Show ServiceProcessingCycle instance Show ServiceProcessingCycleAttributes instance SchemaType ServiceProcessingCycle instance Extension ServiceProcessingCycle Scheme -- | A type that can be used to describe what stage of -- processing a service is in. For example, Netting or -- Valuation. data ServiceProcessingStep data ServiceProcessingStepAttributes instance Eq ServiceProcessingStep instance Eq ServiceProcessingStepAttributes instance Show ServiceProcessingStep instance Show ServiceProcessingStepAttributes instance SchemaType ServiceProcessingStep instance Extension ServiceProcessingStep Scheme -- | A type that can be used to describe a stage or step in -- processing provided by a service, for example processing -- completed. data ServiceProcessingEvent data ServiceProcessingEventAttributes instance Eq ServiceProcessingEvent instance Eq ServiceProcessingEventAttributes instance Show ServiceProcessingEvent instance Show ServiceProcessingEventAttributes instance SchemaType ServiceProcessingEvent instance Extension ServiceProcessingEvent Scheme -- | A type defining the content model for a human-readable -- notification to the users of a service. data ServiceAdvisory instance Eq ServiceAdvisory instance Show ServiceAdvisory instance SchemaType ServiceAdvisory -- | A type that can be used to describe the category of an -- advisory message, e.g.. Availability, Rules, Products, -- etc., etc.. data ServiceAdvisoryCategory data ServiceAdvisoryCategoryAttributes instance Eq ServiceAdvisoryCategory instance Eq ServiceAdvisoryCategoryAttributes instance Show ServiceAdvisoryCategory instance Show ServiceAdvisoryCategoryAttributes instance SchemaType ServiceAdvisoryCategory instance Extension ServiceAdvisoryCategory Scheme data VerificationStatusNotification instance Eq VerificationStatusNotification instance Show VerificationStatusNotification instance SchemaType VerificationStatusNotification instance Extension VerificationStatusNotification NonCorrectableRequestMessage instance Extension VerificationStatusNotification RequestMessage instance Extension VerificationStatusNotification Message instance Extension VerificationStatusNotification Document -- | The verification status of the position as reported by the -- sender (Verified, Disputed). data VerificationStatus data VerificationStatusAttributes instance Eq VerificationStatus instance Eq VerificationStatusAttributes instance Show VerificationStatus instance Show VerificationStatusAttributes instance SchemaType VerificationStatus instance Extension VerificationStatus Scheme elementEventStatusResponse :: XMLParser EventStatusResponse elementToXMLEventStatusResponse :: EventStatusResponse -> [Content ()] elementEventStatusException :: XMLParser Exception elementToXMLEventStatusException :: Exception -> [Content ()] -- | The root element used for rejected message exceptions elementMessageRejected :: XMLParser Exception elementToXMLMessageRejected :: Exception -> [Content ()] elementServiceNotification :: XMLParser ServiceNotification elementToXMLServiceNotification :: ServiceNotification -> [Content ()] elementServiceNotificationException :: XMLParser Exception elementToXMLServiceNotificationException :: Exception -> [Content ()] elementVerificationStatusNotification :: XMLParser VerificationStatusNotification elementToXMLVerificationStatusNotification :: VerificationStatusNotification -> [Content ()] elementVerificationStatusException :: XMLParser Exception elementToXMLVerificationStatusException :: Exception -> [Content ()] elementVerificationStatusAcknowledgement :: XMLParser Acknowledgement elementToXMLVerificationStatusAcknowledgement :: Acknowledgement -> [Content ()]