| Copyright | (c) Christopher Reichert 2014 |
|---|---|
| License | AllRightsReserved |
| Maintainer | Christopher Reichert <creichert@reichertbrothers.com> |
| Stability | experimental |
| Portability | GNU/Linux, FreeBSD |
| Safe Haskell | None |
| Language | Haskell2010 |
Web.Ebay
Contents
Description
Haskell SDK for Ebay Finding API
Synopsis
- searchWithVerb :: MonadIO m => EbayConfig -> FindVerb -> Search -> Manager -> m (Maybe SearchResponse)
- simpleSearchWithVerb :: EbayConfig -> SearchRequest -> IO (Maybe SearchResponse)
- defaultEbayConfig :: EbayConfig
- data Search = Search {}
- data SearchRequest = SearchRequest {}
- data SearchResponse = SearchResponse FindVerb SearchResult
- data SearchResult = SearchResult {}
- data SearchItem = SearchItem {
- searchItemId :: !Text
- searchItemTitle :: !Text
- searchItemSubtitle :: !(Maybe Text)
- searchItemTopRatedListing :: !Bool
- searchItemViewItemUrl :: !Text
- searchItemGalleryUrl :: !(Maybe Text)
- searchItemGalleryPlusPictureUrl :: !(Maybe Text)
- searchItemPictureLargeUrl :: !(Maybe Text)
- searchItemCondition :: Condition
- searchItemSellingStatus :: SellingStatus
- searchItemListingInfo :: Maybe ListingInfo
- data SellingStatus = SellingStatus {}
- data SortOrder
- data FindVerb
- data EbayConfig = EbayConfig {}
- data SellingState
- newtype ItemFilter = ItemFilter (Text, Text)
- data Condition = Condition Text Text
- data ListingInfo = ListingInfo {
- listingInfoBestOfferEnabled :: !Bool
- listingInfoBuyItNowAvailable :: !Bool
- listingInfoBuyItNowPrice :: !(Maybe Text)
- listingInfoConvertedBuyItNowPrice :: !(Maybe Text)
- listingInfoEndTime :: !UTCTime
- listingInfoGift :: !Bool
- listingInfoType :: ListingType
- listingInfoStartTime :: !UTCTime
- data OutputSelector
- data ProductId
- data GalleryInfo = GalleryInfo {
- galleryInfoUrls :: ![Text]
- data AffiliateInfo = AffiliateInfo {}
Functions
Arguments
| :: MonadIO m | |
| => EbayConfig | api configuration |
| -> FindVerb | action to run |
| -> Search | search request |
| -> Manager | http connection manager |
| -> m (Maybe SearchResponse) |
Runs an eBay Finding API search
simpleSearchWithVerb :: EbayConfig -> SearchRequest -> IO (Maybe SearchResponse) Source #
defaultEbayConfig :: EbayConfig Source #
Default Ebay configuration for working with the finding API in a sandbox.
Ebay API types.
Generic search query for ebay api.
Constructors
| Search | |
data SearchRequest Source #
Ebay Finding API search request.
Constructors
| SearchRequest | |
Instances
| Show SearchRequest Source # | |
Defined in Web.Ebay Methods showsPrec :: Int -> SearchRequest -> ShowS # show :: SearchRequest -> String # showList :: [SearchRequest] -> ShowS # | |
| ToJSON SearchRequest Source # | |
Defined in Web.Ebay Methods toJSON :: SearchRequest -> Value # toEncoding :: SearchRequest -> Encoding # toJSONList :: [SearchRequest] -> Value # toEncodingList :: [SearchRequest] -> Encoding # | |
data SearchResponse Source #
Represents a Response from the eBay finding api
TODO: Search responses technically have a list of SearchResult
Constructors
| SearchResponse FindVerb SearchResult |
Instances
| Show SearchResponse Source # | |
Defined in Web.Ebay Methods showsPrec :: Int -> SearchResponse -> ShowS # show :: SearchResponse -> String # showList :: [SearchResponse] -> ShowS # | |
| FromJSON SearchResponse Source # | |
Defined in Web.Ebay Methods parseJSON :: Value -> Parser SearchResponse # parseJSONList :: Value -> Parser [SearchResponse] # | |
data SearchResult Source #
Constructors
| SearchResult | |
Fields | |
Instances
| Show SearchResult Source # | |
Defined in Web.Ebay Methods showsPrec :: Int -> SearchResult -> ShowS # show :: SearchResult -> String # showList :: [SearchResult] -> ShowS # | |
| FromJSON SearchResult Source # | |
Defined in Web.Ebay | |
data SearchItem Source #
A single ebay listing item
Note that some fields have not yet been implemented from the ebay api documentation.
Constructors
Instances
| Show SearchItem Source # | |
Defined in Web.Ebay Methods showsPrec :: Int -> SearchItem -> ShowS # show :: SearchItem -> String # showList :: [SearchItem] -> ShowS # | |
| FromJSON SearchItem Source # | |
Defined in Web.Ebay | |
data SellingStatus Source #
Constructors
| SellingStatus | |
Instances
| Show SellingStatus Source # | |
Defined in Web.Ebay Methods showsPrec :: Int -> SellingStatus -> ShowS # show :: SellingStatus -> String # showList :: [SellingStatus] -> ShowS # | |
| FromJSON SellingStatus Source # | |
Defined in Web.Ebay Methods parseJSON :: Value -> Parser SellingStatus # parseJSONList :: Value -> Parser [SellingStatus] # | |
Constructors
| EndTimeSoonest | |
| BestMatch | |
| BidCountFewest | |
| BidCountMost | |
| CountryAscending | |
| CountryDescending | |
| CurrentPriceHighest | |
| DistanceNearest | |
| PricePlusShipingHighest | |
| PricePlusShippingLowest | |
| StartTimeNewest |
Instances
| Show SortOrder Source # | |
| Generic SortOrder Source # | |
| ToJSON SortOrder Source # | |
| type Rep SortOrder Source # | |
Defined in Web.Ebay type Rep SortOrder = D1 (MetaData "SortOrder" "Web.Ebay" "hsebaysdk-0.4.1.0-8lPgq7ZPKhZ6ebd2oOxukk" False) (((C1 (MetaCons "EndTimeSoonest" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "BestMatch" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "BidCountFewest" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "BidCountMost" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CountryAscending" PrefixI False) (U1 :: Type -> Type)))) :+: ((C1 (MetaCons "CountryDescending" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "CurrentPriceHighest" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "DistanceNearest" PrefixI False) (U1 :: Type -> Type))) :+: (C1 (MetaCons "PricePlusShipingHighest" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "PricePlusShippingLowest" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "StartTimeNewest" PrefixI False) (U1 :: Type -> Type))))) | |
Support verbs in finding api
verb jargon taken from eBay docs.
data EbayConfig Source #
Ebay api configuration.
Constructors
| EbayConfig | |
Fields
| |
Instances
| Show EbayConfig Source # | |
Defined in Web.Ebay Methods showsPrec :: Int -> EbayConfig -> ShowS # show :: EbayConfig -> String # showList :: [EbayConfig] -> ShowS # | |
data SellingState Source #
Constructors
| Active | |
| Canceled | |
| Ended | |
| EndedWithSales | |
| EndedWithoutSales |
Instances
| Eq SellingState Source # | |
Defined in Web.Ebay | |
| Show SellingState Source # | |
Defined in Web.Ebay Methods showsPrec :: Int -> SellingState -> ShowS # show :: SellingState -> String # showList :: [SellingState] -> ShowS # | |
| Generic SellingState Source # | |
| FromJSON SellingState Source # | |
Defined in Web.Ebay | |
| type Rep SellingState Source # | |
Defined in Web.Ebay type Rep SellingState = D1 (MetaData "SellingState" "Web.Ebay" "hsebaysdk-0.4.1.0-8lPgq7ZPKhZ6ebd2oOxukk" False) ((C1 (MetaCons "Active" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Canceled" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Ended" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "EndedWithSales" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "EndedWithoutSales" PrefixI False) (U1 :: Type -> Type)))) | |
newtype ItemFilter Source #
Constructors
| ItemFilter (Text, Text) |
Instances
| Show ItemFilter Source # | |
Defined in Web.Ebay Methods showsPrec :: Int -> ItemFilter -> ShowS # show :: ItemFilter -> String # showList :: [ItemFilter] -> ShowS # | |
| ToJSON ItemFilter Source # | |
Defined in Web.Ebay Methods toJSON :: ItemFilter -> Value # toEncoding :: ItemFilter -> Encoding # toJSONList :: [ItemFilter] -> Value # toEncodingList :: [ItemFilter] -> Encoding # | |
Condition is made up of condition id condition display name
data ListingInfo Source #
Constructors
| ListingInfo | |
Fields
| |
Instances
| Show ListingInfo Source # | |
Defined in Web.Ebay Methods showsPrec :: Int -> ListingInfo -> ShowS # show :: ListingInfo -> String # showList :: [ListingInfo] -> ShowS # | |
| FromJSON ListingInfo Source # | |
Defined in Web.Ebay | |
data OutputSelector Source #
Constructors
| AspectHistogram | |
| CategoryHistogram | |
| ConditionHistogram | |
| GalleryInfoOutput | |
| PictureURLLarge | |
| PictureURLSuperSize | |
| SellerInfo | |
| StoreInfo | |
| UnitPriceInfo |
Instances
data GalleryInfo Source #
Constructors
| GalleryInfo | |
Fields
| |
Instances
| Show GalleryInfo Source # | |
Defined in Web.Ebay Methods showsPrec :: Int -> GalleryInfo -> ShowS # show :: GalleryInfo -> String # showList :: [GalleryInfo] -> ShowS # | |
data AffiliateInfo Source #
Constructors
| AffiliateInfo | |
Fields
| |
Instances
| Eq AffiliateInfo Source # | |
Defined in Web.Ebay Methods (==) :: AffiliateInfo -> AffiliateInfo -> Bool # (/=) :: AffiliateInfo -> AffiliateInfo -> Bool # | |
| Read AffiliateInfo Source # | |
Defined in Web.Ebay Methods readsPrec :: Int -> ReadS AffiliateInfo # readList :: ReadS [AffiliateInfo] # | |
| Show AffiliateInfo Source # | |
Defined in Web.Ebay Methods showsPrec :: Int -> AffiliateInfo -> ShowS # show :: AffiliateInfo -> String # showList :: [AffiliateInfo] -> ShowS # | |
| ToJSON AffiliateInfo Source # | |
Defined in Web.Ebay Methods toJSON :: AffiliateInfo -> Value # toEncoding :: AffiliateInfo -> Encoding # toJSONList :: [AffiliateInfo] -> Value # toEncodingList :: [AffiliateInfo] -> Encoding # | |