{-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies #-} {-# OPTIONS_GHC -fno-warn-duplicate-exports #-} module Data.FpML.V53.Asset ( module Data.FpML.V53.Asset , module Data.FpML.V53.Shared ) 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.Shared data ActualPrice instance Eq ActualPrice instance Show ActualPrice instance SchemaType ActualPrice -- | A reference to an asset, e.g. a portfolio, trade, or -- reference instrument.. data AnyAssetReference instance Eq AnyAssetReference instance Show AnyAssetReference instance SchemaType AnyAssetReference instance Extension AnyAssetReference Reference -- | Abstract base class for all underlying assets. data Asset instance Eq Asset instance Show Asset instance SchemaType Asset -- | A scheme identifying the types of measures that can be used -- to describe an asset. data AssetMeasureType data AssetMeasureTypeAttributes instance Eq AssetMeasureType instance Eq AssetMeasureTypeAttributes instance Show AssetMeasureType instance Show AssetMeasureTypeAttributes instance SchemaType AssetMeasureType instance Extension AssetMeasureType Scheme -- | A scheme identifying the types of pricing model used to -- evaluate the price of an asset. Examples include Intrinsic, -- ClosedForm, MonteCarlo, BackwardInduction. data PricingModel data PricingModelAttributes instance Eq PricingModel instance Eq PricingModelAttributes instance Show PricingModel instance Show PricingModelAttributes instance SchemaType PricingModel instance Extension PricingModel Scheme -- | Characterise the asset pool behind an asset backed bond. data AssetPool instance Eq AssetPool instance Show AssetPool instance SchemaType AssetPool -- | Reference to an underlying asset. data AssetReference instance Eq AssetReference instance Show AssetReference instance SchemaType AssetReference instance Extension AssetReference Reference -- | Some kind of numerical measure about an asset, eg. its NPV, -- together with characteristics of that measure. data BasicQuotation instance Eq BasicQuotation instance Show BasicQuotation instance SchemaType BasicQuotation -- | A type describing the underlyer features of a basket swap. -- Each of the basket constituents are described through an -- embedded component, the basketConstituentsType. data Basket instance Eq Basket instance Show Basket instance SchemaType Basket instance Extension Basket Asset -- | A type describing each of the constituents of a basket. data BasketConstituent instance Eq BasketConstituent instance Show BasketConstituent instance SchemaType BasketConstituent data BasketId data BasketIdAttributes instance Eq BasketId instance Eq BasketIdAttributes instance Show BasketId instance Show BasketIdAttributes instance SchemaType BasketId instance Extension BasketId Scheme data BasketName data BasketNameAttributes instance Eq BasketName instance Eq BasketNameAttributes instance Show BasketName instance Show BasketNameAttributes instance SchemaType BasketName instance Extension BasketName Scheme -- | An exchange traded bond. data Bond instance Eq Bond instance Show Bond instance SchemaType Bond instance Extension Bond UnderlyingAsset instance Extension Bond IdentifiedAsset instance Extension Bond Asset data Cash instance Eq Cash instance Show Cash instance SchemaType Cash instance Extension Cash Asset -- | A type describing the commission that will be charged for -- each of the hedge transactions. data Commission instance Eq Commission instance Show Commission instance SchemaType Commission -- | A type describing a commodity underlying asset. data Commodity instance Eq Commodity instance Show Commodity instance SchemaType Commodity instance Extension Commodity IdentifiedAsset instance Extension Commodity Asset data CommodityBase data CommodityBaseAttributes instance Eq CommodityBase instance Eq CommodityBaseAttributes instance Show CommodityBase instance Show CommodityBaseAttributes instance SchemaType CommodityBase instance Extension CommodityBase Scheme -- | Defines a commodity business day calendar. data CommodityBusinessCalendar data CommodityBusinessCalendarAttributes instance Eq CommodityBusinessCalendar instance Eq CommodityBusinessCalendarAttributes instance Show CommodityBusinessCalendar instance Show CommodityBusinessCalendarAttributes instance SchemaType CommodityBusinessCalendar instance Extension CommodityBusinessCalendar Scheme -- | Specifies the time with respect to a commodity business -- calendar. data CommodityBusinessCalendarTime instance Eq CommodityBusinessCalendarTime instance Show CommodityBusinessCalendarTime instance SchemaType CommodityBusinessCalendarTime data CommodityDetails data CommodityDetailsAttributes instance Eq CommodityDetails instance Eq CommodityDetailsAttributes instance Show CommodityDetails instance Show CommodityDetailsAttributes instance SchemaType CommodityDetails instance Extension CommodityDetails Scheme -- | A type describing the weight of each of the underlyer -- constituent within the basket, either in absolute or -- relative terms. data ConstituentWeight instance Eq ConstituentWeight instance Show ConstituentWeight instance SchemaType ConstituentWeight data ConvertibleBond instance Eq ConvertibleBond instance Show ConvertibleBond instance SchemaType ConvertibleBond instance Extension ConvertibleBond Bond instance Extension ConvertibleBond UnderlyingAsset instance Extension ConvertibleBond IdentifiedAsset instance Extension ConvertibleBond Asset -- | Defines a scheme of values for specifiying if the bond has -- a variable coupon, step-up/down coupon or a zero-coupon. data CouponType data CouponTypeAttributes instance Eq CouponType instance Eq CouponTypeAttributes instance Show CouponType instance Show CouponTypeAttributes instance SchemaType CouponType instance Extension CouponType Scheme -- | Abstract base class for instruments intended to be used -- primarily for building curves. data CurveInstrument instance Eq CurveInstrument instance Show CurveInstrument instance SchemaType CurveInstrument instance Extension CurveInstrument IdentifiedAsset data Deposit instance Eq Deposit instance Show Deposit instance SchemaType Deposit instance Extension Deposit UnderlyingAsset instance Extension Deposit IdentifiedAsset instance Extension Deposit Asset -- | A type describing the dividend payout ratio associated with -- an equity underlyer. In certain cases the actual ratio is -- not known on trade inception, and only general conditions -- are then specified. data DividendPayout instance Eq DividendPayout instance Show DividendPayout instance SchemaType DividendPayout -- | An exchange traded equity asset. data EquityAsset instance Eq EquityAsset instance Show EquityAsset instance SchemaType EquityAsset instance Extension EquityAsset ExchangeTraded instance Extension EquityAsset UnderlyingAsset instance Extension EquityAsset IdentifiedAsset instance Extension EquityAsset Asset -- | An abstract base class for all exchange traded financial -- products. data ExchangeTraded instance Eq ExchangeTraded instance Show ExchangeTraded instance SchemaType ExchangeTraded instance Extension ExchangeTraded UnderlyingAsset -- | Abstract base class for all exchange traded financial -- products with a price which is calculated from exchange -- traded constituents. data ExchangeTradedCalculatedPrice instance Eq ExchangeTradedCalculatedPrice instance Show ExchangeTradedCalculatedPrice instance SchemaType ExchangeTradedCalculatedPrice instance Extension ExchangeTradedCalculatedPrice ExchangeTraded -- | An exchange traded derivative contract. data ExchangeTradedContract instance Eq ExchangeTradedContract instance Show ExchangeTradedContract instance SchemaType ExchangeTradedContract instance Extension ExchangeTradedContract ExchangeTraded instance Extension ExchangeTradedContract UnderlyingAsset instance Extension ExchangeTradedContract IdentifiedAsset instance Extension ExchangeTradedContract Asset -- | An exchange traded fund whose price depends on exchange -- traded constituents. data ExchangeTradedFund instance Eq ExchangeTradedFund instance Show ExchangeTradedFund instance SchemaType ExchangeTradedFund instance Extension ExchangeTradedFund ExchangeTradedCalculatedPrice instance Extension ExchangeTradedFund ExchangeTraded instance Extension ExchangeTradedFund UnderlyingAsset instance Extension ExchangeTradedFund IdentifiedAsset instance Extension ExchangeTradedFund Asset -- | A type describing the type of loan facility. data FacilityType data FacilityTypeAttributes instance Eq FacilityType instance Eq FacilityTypeAttributes instance Show FacilityType instance Show FacilityTypeAttributes instance SchemaType FacilityType instance Extension FacilityType Scheme -- | An exchange traded future contract. data Future instance Eq Future instance Show Future instance SchemaType Future instance Extension Future ExchangeTraded instance Extension Future UnderlyingAsset instance Extension Future IdentifiedAsset instance Extension Future Asset -- | A type defining a short form unique identifier for a future -- contract. data FutureId data FutureIdAttributes instance Eq FutureId instance Eq FutureIdAttributes instance Show FutureId instance Show FutureIdAttributes instance SchemaType FutureId instance Extension FutureId Scheme data FxConversion instance Eq FxConversion instance Show FxConversion instance SchemaType FxConversion data FxRateAsset instance Eq FxRateAsset instance Show FxRateAsset instance SchemaType FxRateAsset instance Extension FxRateAsset UnderlyingAsset instance Extension FxRateAsset IdentifiedAsset instance Extension FxRateAsset Asset -- | A generic type describing an identified asset. data IdentifiedAsset instance Eq IdentifiedAsset instance Show IdentifiedAsset instance SchemaType IdentifiedAsset instance Extension IdentifiedAsset Asset -- | A published index whose price depends on exchange traded -- constituents. data Index instance Eq Index instance Show Index instance SchemaType Index instance Extension Index ExchangeTradedCalculatedPrice instance Extension Index ExchangeTraded instance Extension Index UnderlyingAsset instance Extension Index IdentifiedAsset instance Extension Index Asset -- | A type describing the liens associated with a loan -- facility. data Lien data LienAttributes instance Eq Lien instance Eq LienAttributes instance Show Lien instance Show LienAttributes instance SchemaType Lien instance Extension Lien Scheme -- | A type describing a loan underlying asset. data Loan instance Eq Loan instance Show Loan instance SchemaType Loan instance Extension Loan UnderlyingAsset instance Extension Loan IdentifiedAsset instance Extension Loan Asset -- | A type describing a mortgage asset. data Mortgage instance Eq Mortgage instance Show Mortgage instance SchemaType Mortgage instance Extension Mortgage UnderlyingAsset instance Extension Mortgage IdentifiedAsset instance Extension Mortgage Asset -- | A type describing the typology of mortgage obligations. data MortgageSector data MortgageSectorAttributes instance Eq MortgageSector instance Eq MortgageSectorAttributes instance Show MortgageSector instance Show MortgageSectorAttributes instance SchemaType MortgageSector instance Extension MortgageSector Scheme data MutualFund instance Eq MutualFund instance Show MutualFund instance SchemaType MutualFund instance Extension MutualFund UnderlyingAsset instance Extension MutualFund IdentifiedAsset instance Extension MutualFund Asset -- | A structure representing a pending dividend or coupon -- payment. data PendingPayment instance Eq PendingPayment instance Show PendingPayment instance SchemaType PendingPayment instance Extension PendingPayment PaymentBase -- | A type describing the strike price. data Price instance Eq Price instance Show Price instance SchemaType Price -- | The units in which a price is quoted. data PriceQuoteUnits data PriceQuoteUnitsAttributes instance Eq PriceQuoteUnits instance Eq PriceQuoteUnitsAttributes instance Show PriceQuoteUnits instance Show PriceQuoteUnitsAttributes instance SchemaType PriceQuoteUnits instance Extension PriceQuoteUnits Scheme data QuantityUnit data QuantityUnitAttributes instance Eq QuantityUnit instance Eq QuantityUnitAttributes instance Show QuantityUnit instance Show QuantityUnitAttributes instance SchemaType QuantityUnit instance Extension QuantityUnit Scheme -- | A type representing a set of characteristics that describe -- a quotation. data QuotationCharacteristics instance Eq QuotationCharacteristics instance Show QuotationCharacteristics instance SchemaType QuotationCharacteristics -- | The type of the time of the quote. data QuoteTiming data QuoteTimingAttributes instance Eq QuoteTiming instance Eq QuoteTimingAttributes instance Show QuoteTiming instance Show QuoteTimingAttributes instance SchemaType QuoteTiming instance Extension QuoteTiming Scheme data RateIndex instance Eq RateIndex instance Show RateIndex instance SchemaType RateIndex instance Extension RateIndex UnderlyingAsset instance Extension RateIndex IdentifiedAsset instance Extension RateIndex Asset -- | A scheme identifying the type of currency that was used to -- report the value of an asset. For example, this could -- contain values like SettlementCurrency, QuoteCurrency, -- UnitCurrency, etc. data ReportingCurrencyType data ReportingCurrencyTypeAttributes instance Eq ReportingCurrencyType instance Eq ReportingCurrencyTypeAttributes instance Show ReportingCurrencyType instance Show ReportingCurrencyTypeAttributes instance SchemaType ReportingCurrencyType instance Extension ReportingCurrencyType Scheme data SimpleCreditDefaultSwap instance Eq SimpleCreditDefaultSwap instance Show SimpleCreditDefaultSwap instance SchemaType SimpleCreditDefaultSwap instance Extension SimpleCreditDefaultSwap UnderlyingAsset instance Extension SimpleCreditDefaultSwap IdentifiedAsset instance Extension SimpleCreditDefaultSwap Asset data SimpleFra instance Eq SimpleFra instance Show SimpleFra instance SchemaType SimpleFra instance Extension SimpleFra UnderlyingAsset instance Extension SimpleFra IdentifiedAsset instance Extension SimpleFra Asset data SimpleIRSwap instance Eq SimpleIRSwap instance Show SimpleIRSwap instance SchemaType SimpleIRSwap instance Extension SimpleIRSwap UnderlyingAsset instance Extension SimpleIRSwap IdentifiedAsset instance Extension SimpleIRSwap Asset -- | A type describing a single underlyer data SingleUnderlyer instance Eq SingleUnderlyer instance Show SingleUnderlyer instance SchemaType SingleUnderlyer -- | Defines an identifier for a specific location or region -- which translates into a combination of rules for -- calculating the UTC offset. data TimeZone data TimeZoneAttributes instance Eq TimeZone instance Eq TimeZoneAttributes instance Show TimeZone instance Show TimeZoneAttributes instance SchemaType TimeZone instance Extension TimeZone Scheme -- | A type describing the whole set of possible underlyers: -- single underlyers or multiple underlyers, each of these -- having either security or index components. data Underlyer instance Eq Underlyer instance Show Underlyer instance SchemaType Underlyer -- | Abstract base class for all underlying assets. data UnderlyingAsset instance Eq UnderlyingAsset instance Show UnderlyingAsset instance SchemaType UnderlyingAsset instance Extension UnderlyingAsset IdentifiedAsset data UnderlyingAssetTranche data UnderlyingAssetTrancheAttributes instance Eq UnderlyingAssetTranche instance Eq UnderlyingAssetTrancheAttributes instance Show UnderlyingAssetTranche instance Show UnderlyingAssetTrancheAttributes instance SchemaType UnderlyingAssetTranche instance Extension UnderlyingAssetTranche Scheme -- | Defines the underlying asset when it is a basket. elementBasket :: XMLParser Basket elementToXMLBasket :: Basket -> [Content ()] -- | Identifies the underlying asset when it is a series or a -- class of bonds. elementBond :: XMLParser Bond elementToXMLBond :: Bond -> [Content ()] -- | Identifies a simple underlying asset type that is a cash -- payment. Used for specifying discounting factors for future -- cash flows in the pricing and risk model. elementCash :: XMLParser Cash elementToXMLCash :: Cash -> [Content ()] -- | Identifies the underlying asset when it is a listed -- commodity. elementCommodity :: XMLParser Commodity elementToXMLCommodity :: Commodity -> [Content ()] -- | Identifies the underlying asset when it is a convertible -- bond. elementConvertibleBond :: XMLParser ConvertibleBond elementToXMLConvertibleBond :: ConvertibleBond -> [Content ()] -- | Defines the underlying asset when it is a curve instrument. elementCurveInstrument :: XMLParser Asset -- | Identifies a simple underlying asset that is a term -- deposit. elementDeposit :: XMLParser Deposit elementToXMLDeposit :: Deposit -> [Content ()] -- | Identifies the underlying asset when it is a listed equity. elementEquity :: XMLParser EquityAsset elementToXMLEquity :: EquityAsset -> [Content ()] -- | Identifies the underlying asset when it is an -- exchange-traded fund. elementExchangeTradedFund :: XMLParser ExchangeTradedFund elementToXMLExchangeTradedFund :: ExchangeTradedFund -> [Content ()] -- | Identifies the underlying asset when it is a listed future -- contract. elementFuture :: XMLParser Future elementToXMLFuture :: Future -> [Content ()] -- | Identifies a simple underlying asset type that is an FX -- rate. Used for specifying FX rates in the pricing and risk -- model. elementFx :: XMLParser FxRateAsset elementToXMLFx :: FxRateAsset -> [Content ()] -- | Identifies the underlying asset when it is a financial -- index. elementIndex :: XMLParser Index elementToXMLIndex :: Index -> [Content ()] -- | Identifies a simple underlying asset that is a loan. elementLoan :: XMLParser Loan elementToXMLLoan :: Loan -> [Content ()] -- | Identifies a mortgage backed security. elementMortgage :: XMLParser Mortgage elementToXMLMortgage :: Mortgage -> [Content ()] -- | Identifies the class of unit issued by a fund. elementMutualFund :: XMLParser MutualFund elementToXMLMutualFund :: MutualFund -> [Content ()] -- | Identifies a simple underlying asset that is an interest -- rate index. Used for specifying benchmark assets in the -- market environment in the pricing and risk model. elementRateIndex :: XMLParser RateIndex elementToXMLRateIndex :: RateIndex -> [Content ()] -- | Identifies a simple underlying asset that is a credit -- default swap. elementSimpleCreditDefaultSwap :: XMLParser SimpleCreditDefaultSwap elementToXMLSimpleCreditDefaultSwap :: SimpleCreditDefaultSwap -> [Content ()] -- | Identifies a simple underlying asset that is a forward rate -- agreement. elementSimpleFra :: XMLParser SimpleFra elementToXMLSimpleFra :: SimpleFra -> [Content ()] -- | Identifies a simple underlying asset that is a swap. elementSimpleIrSwap :: XMLParser SimpleIRSwap elementToXMLSimpleIrSwap :: SimpleIRSwap -> [Content ()] -- | Define the underlying asset, either a listed security or -- other instrument. elementUnderlyingAsset :: XMLParser Asset