{-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies #-}
{-# OPTIONS_GHC -fno-warn-duplicate-exports #-}
module Data.FpML.V53.Standard
  ( module Data.FpML.V53.Standard
  , module Data.FpML.V53.Shared
  , module Data.FpML.V53.Asset
  ) where
 
import Text.XML.HaXml.Schema.Schema (SchemaType(..),SimpleType(..),Extension(..),Restricts(..))
import Text.XML.HaXml.Schema.Schema as Schema
import Text.XML.HaXml.OneOfN
import qualified Text.XML.HaXml.Schema.PrimitiveTypes as Xsd
import Data.FpML.V53.Shared
import Data.FpML.V53.Asset
 
-- Some hs-boot imports are required, for fwd-declaring types.
 
-- | A product to represent a standardized OTC derivative 
--   transaction whose economics do not need to be fully 
--   described using an FpML schema because they are implied by 
--   the product ID.
elementStandardProduct :: XMLParser StandardProduct
elementStandardProduct = parseSchemaType "standardProduct"
elementToXMLStandardProduct :: StandardProduct -> [Content ()]
elementToXMLStandardProduct = schemaTypeToXML "standardProduct"
 
-- | Simple product representation providing key information 
--   about a variety of different products
data StandardProduct = StandardProduct
        { stdProduct_ID :: Maybe Xsd.ID
        , stdProduct_primaryAssetClass :: Maybe AssetClass
          -- ^ A classification of the most important risk class of the 
          --   trade. FpML defines a simple asset class categorization 
          --   using a coding scheme.
        , stdProduct_secondaryAssetClass :: [AssetClass]
          -- ^ A classification of additional risk classes of the trade, 
          --   if any. FpML defines a simple asset class categorization 
          --   using a coding scheme.
        , stdProduct_productType :: [ProductType]
          -- ^ A classification of the type of product. FpML defines a 
          --   simple product categorization using a coding scheme.
        , stdProduct_productId :: [ProductId]
          -- ^ A product reference identifier. The product ID is an 
          --   identifier that describes the key economic characteristics 
          --   of the trade type, with the exception of concepts such as 
          --   size (notional, quantity, number of units) and price (fixed 
          --   rate, strike, etc.) that are negotiated for each 
          --   transaction. It can be used to hold identifiers such as the 
          --   "UPI" (universal product identifier) required by certain 
          --   regulatory reporting rules. It can also be used to hold 
          --   identifiers of benchmark products or product temnplates 
          --   used by certain trading systems or facilities. FpML does 
          --   not define the domain values associated with this element. 
          --   Note that the domain values for this element are not 
          --   strictly an enumerated list.
        , stdProduct_notional :: CashflowNotional
          -- ^ The notional amount that was traded.
        , stdProduct_quote :: [BasicQuotation]
          -- ^ Pricing information for the trade.
        }
        deriving (Eq,Show)
instance SchemaType StandardProduct where
    parseSchemaType s = do
        (pos,e) <- posnElement [s]
        a0 <- optional $ getAttribute "id" e pos
        commit $ interior e $ return (StandardProduct a0)
            `apply` optional (parseSchemaType "primaryAssetClass")
            `apply` many (parseSchemaType "secondaryAssetClass")
            `apply` many (parseSchemaType "productType")
            `apply` many (parseSchemaType "productId")
            `apply` parseSchemaType "notional"
            `apply` many1 (parseSchemaType "quote")
    schemaTypeToXML s x@StandardProduct{} =
        toXMLElement s [ maybe [] (toXMLAttribute "id") $ stdProduct_ID x
                       ]
            [ maybe [] (schemaTypeToXML "primaryAssetClass") $ stdProduct_primaryAssetClass x
            , concatMap (schemaTypeToXML "secondaryAssetClass") $ stdProduct_secondaryAssetClass x
            , concatMap (schemaTypeToXML "productType") $ stdProduct_productType x
            , concatMap (schemaTypeToXML "productId") $ stdProduct_productId x
            , schemaTypeToXML "notional" $ stdProduct_notional x
            , concatMap (schemaTypeToXML "quote") $ stdProduct_quote x
            ]
instance Extension StandardProduct Product where
    supertype v = Product_StandardProduct v