{-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies #-} {-# OPTIONS_GHC -fno-warn-duplicate-exports #-} module Data.FpML.V53.Main ( module Data.FpML.V53.Main , module Data.FpML.V53.Generic , module Data.FpML.V53.Standard , module Data.FpML.V53.IRD , module Data.FpML.V53.FX , module Data.FpML.V53.Eqd , module Data.FpML.V53.Swaps.Return , module Data.FpML.V53.CD , module Data.FpML.V53.Option.Bond , module Data.FpML.V53.Swaps.Correlation , module Data.FpML.V53.Swaps.Dividend , module Data.FpML.V53.Swaps.Variance , module Data.FpML.V53.Com , module Data.FpML.V53.Notification.CreditEvent , module Data.FpML.V53.Reporting.Valuation , module Data.FpML.V53.Processes.Recordkeeping , module Data.FpML.V53.Valuation ) where import Text.XML.HaXml.Schema.Schema (SchemaType(..),SimpleType(..),Extension(..),Restricts(..)) import Text.XML.HaXml.Schema.Schema as Schema import Text.XML.HaXml.OneOfN import qualified Text.XML.HaXml.Schema.PrimitiveTypes as Xsd import Data.FpML.V53.Generic import Data.FpML.V53.Standard import Data.FpML.V53.IRD import Data.FpML.V53.FX import Data.FpML.V53.Eqd import Data.FpML.V53.Swaps.Return import Data.FpML.V53.CD import Data.FpML.V53.Option.Bond import Data.FpML.V53.Swaps.Correlation import Data.FpML.V53.Swaps.Dividend import Data.FpML.V53.Swaps.Variance import Data.FpML.V53.Com import Data.FpML.V53.Notification.CreditEvent import Data.FpML.V53.Reporting.Valuation import Data.FpML.V53.Processes.Recordkeeping import Data.FpML.V53.Valuation -- Some hs-boot imports are required, for fwd-declaring types. -- | products -- | business process messaging -- | reporting and settlement -- | A type defining a content model that includes valuation -- (pricing and risk) data without expressing any processing -- intention. data ValuationDocument = ValuationDocument { valDocum_fpmlVersion :: Xsd.XsdString -- ^ Indicate which version of the FpML Schema an FpML message -- adheres to. , valDocum_expectedBuild :: Maybe Xsd.PositiveInteger -- ^ This optional attribute can be supplied by a message -- creator in an FpML instance to specify which build number -- of the schema was used to define the message when it was -- generated. , valDocum_actualBuild :: Maybe Xsd.PositiveInteger -- ^ The specific build number of this schema version. This -- attribute is not included in an instance document. Instead, -- it is supplied by the XML parser when the document is -- validated against the FpML schema and indicates the build -- number of the schema file. Every time FpML publishes a -- change to the schema, validation rules, or examples within -- a version (e.g., version 4.2) the actual build number is -- incremented. If no changes have been made between releases -- within a version (i.e. from Trial Recommendation to -- Recommendation) the actual build number stays the same. , valDocum_validation :: [Validation] -- ^ A list of validation sets the sender asserts the document -- is valid with respect to. , valDocum_choice1 :: (Maybe (OneOf2 Xsd.Boolean Xsd.Boolean)) -- ^ Choice between: -- -- (1) Indicates if this message corrects an earlier request. -- -- (2) Indicates if this message corrects an earlier request. , valDocum_onBehalfOf :: Maybe OnBehalfOf -- ^ Indicates which party (and accounts) a trade is being -- processed for. , valDocum_originatingEvent :: Maybe OriginatingEvent , valDocum_trade :: [Trade] -- ^ The root element in an FpML trade document. , valDocum_party :: [Party] , valDocum_account :: [Account] -- ^ Optional account information used to precisely define the -- origination and destination of financial instruments. , valDocum_market :: [Market] -- ^ This is a global element used for creating global types. It -- holds Market information, e.g. curves, surfaces, quotes, -- etc. , valDocum_valuationSet :: [ValuationSet] } deriving (Eq,Show) instance SchemaType ValuationDocument where parseSchemaType s = do (pos,e) <- posnElement [s] a0 <- getAttribute "fpmlVersion" e pos a1 <- optional $ getAttribute "expectedBuild" e pos a2 <- optional $ getAttribute "actualBuild" e pos commit $ interior e $ return (ValuationDocument a0 a1 a2) `apply` many (parseSchemaType "validation") `apply` optional (oneOf' [ ("Xsd.Boolean", fmap OneOf2 (parseSchemaType "isCorrection")) , ("Xsd.Boolean", fmap TwoOf2 (parseSchemaType "isCancellation")) ]) `apply` optional (parseSchemaType "onBehalfOf") `apply` optional (parseSchemaType "originatingEvent") `apply` many1 (parseSchemaType "trade") `apply` many (parseSchemaType "party") `apply` many (parseSchemaType "account") `apply` many (elementMarket) `apply` many (elementValuationSet) schemaTypeToXML s x@ValuationDocument{} = toXMLElement s [ toXMLAttribute "fpmlVersion" $ valDocum_fpmlVersion x , maybe [] (toXMLAttribute "expectedBuild") $ valDocum_expectedBuild x , maybe [] (toXMLAttribute "actualBuild") $ valDocum_actualBuild x ] [ concatMap (schemaTypeToXML "validation") $ valDocum_validation x , maybe [] (foldOneOf2 (schemaTypeToXML "isCorrection") (schemaTypeToXML "isCancellation") ) $ valDocum_choice1 x , maybe [] (schemaTypeToXML "onBehalfOf") $ valDocum_onBehalfOf x , maybe [] (schemaTypeToXML "originatingEvent") $ valDocum_originatingEvent x , concatMap (schemaTypeToXML "trade") $ valDocum_trade x , concatMap (schemaTypeToXML "party") $ valDocum_party x , concatMap (schemaTypeToXML "account") $ valDocum_account x , concatMap (elementToXMLMarket) $ valDocum_market x , concatMap (elementToXMLValuationSet) $ valDocum_valuationSet x ] instance Extension ValuationDocument DataDocument where supertype (ValuationDocument a0 a1 a2 e0 e1 e2 e3 e4 e5 e6 e7 e8) = DataDocument a0 a1 a2 e0 e1 e2 e3 e4 e5 e6 instance Extension ValuationDocument Document where supertype = (supertype :: DataDocument -> Document) . (supertype :: ValuationDocument -> DataDocument) -- | A document containing trade and/or portfolio and/or party -- data without expressing any processing intention. elementDataDocument :: XMLParser DataDocument elementDataDocument = parseSchemaType "dataDocument" elementToXMLDataDocument :: DataDocument -> [Content ()] elementToXMLDataDocument = schemaTypeToXML "dataDocument" -- | A document that includes trade and/or valuation (pricing -- and risk) data without expressing any processing intention. elementValuationDocument :: XMLParser ValuationDocument elementValuationDocument = parseSchemaType "valuationDocument" elementToXMLValuationDocument :: ValuationDocument -> [Content ()] elementToXMLValuationDocument = schemaTypeToXML "valuationDocument"