module Web.Yahoo.Finance.YQL.Internal.Types (
    Quote(..)
  , StockSymbol(..)
  , YQLQuery(..)
  , YQLResponse(..)
  ) where
import Control.Applicative ((<|>))
import Data.Aeson
import Data.Aeson.Types (Parser)
import Data.Foldable (fold)
import Data.List (intersperse)
import Data.Monoid ((<>))
import Data.Text (Text)
import Data.Time
import qualified Data.Vector as V
import GHC.Generics
import Web.HttpApiData
#if !MIN_VERSION_servant(0, 5, 0)
import Servant.Common.Text
#endif
#if !MIN_VERSION_base(4,8,0)
import Control.Applicative
#endif
data YQLQuery = YQLQuery {
  yqlQuery :: [StockSymbol]
} deriving (Eq, Show, Generic)
instance ToHttpApiData YQLQuery where
  toUrlPiece :: YQLQuery -> Text
  toUrlPiece (YQLQuery {..}) = "select * from yahoo.finance.quotes where symbol in (" <> toUrlPiece yqlQuery <> ")"
#if !MIN_VERSION_servant(0, 5, 0)
instance ToText YQLQuery where
  toText (YQLQuery {..}) = "select * from yahoo.finance.quotes where symbol in (" <> toText yqlQuery <> ")"
#endif
newtype StockSymbol = StockSymbol { unStockSymbol :: Text }
  deriving (Eq, Generic, Ord, Show)
instance ToHttpApiData StockSymbol where
  toUrlPiece :: StockSymbol -> Text
  toUrlPiece (StockSymbol {..}) = "\"" <> unStockSymbol <> "\""
#if !MIN_VERSION_servant(0, 5, 0)
  
  
  
  
instance ToText StockSymbol where
  toText (StockSymbol {..}) = "\"" <> unStockSymbol <> "\""
#endif
instance ToHttpApiData [StockSymbol] where
  toUrlPiece :: [StockSymbol] -> Text
  toUrlPiece = fold . intersperse "," . fmap toUrlPiece
#if !MIN_VERSION_servant(0, 5, 0)
  
  
  
  
instance ToText [StockSymbol] where
  toText = fold . intersperse "," . fmap toUrlPiece
#endif
data YQLResponse = YQLResponse {
  responseCount   :: Int
, responseCreated :: UTCTime
, responseLang    :: Text
, responseQuotes  :: [Maybe Quote]
} deriving (Eq, Read, Show, Generic)
instance FromJSON YQLResponse where
  parseJSON = withObject "YQLResponse" $ \o -> do
    innerO <- o .: "query"
    results <- innerO .: "results"
    innerQuotes  <- results .: "quote"
    
    
    
    quotes <- case innerQuotes of
      (Object _) -> (:[]) <$> (parseJSON innerQuotes <|> pure Nothing) :: Parser [Maybe Quote]
      (Array  a) -> sequence $ (\x -> parseJSON x <|> pure Nothing) <$> (V.toList a)
      _ -> fail "responseQuotes expects to find an object or array with the key 'quote'"
    YQLResponse <$> innerO .: "count"
                <*> innerO .: "created"
                <*> innerO .: "lang"
                <*> pure quotes
data Quote = Quote {
  quoteAverageDailyVolume   :: Text
, quoteChange               :: Text
, quoteDaysLow              :: Text
, quoteDaysHigh             :: Text
, quoteYearLow              :: Text
, quoteYearHigh             :: Text
, quoteMarketCapitalization :: Text
, quoteLastTradePriceOnly   :: Text
, quoteDaysRange            :: Text
, quoteName                 :: Text
, quoteSymbol               :: Text
, quoteVolume               :: Text
, quoteStockExchange        :: Text
} deriving (Eq, Read, Show, Generic)
instance FromJSON Quote where
  parseJSON = withObject "Quote" $ \o ->
    Quote <$> o .: "AverageDailyVolume"
          <*> o .: "Change"
          <*> o .: "DaysLow"
          <*> o .: "DaysHigh"
          <*> o .: "YearLow"
          <*> o .: "YearHigh"
          <*> o .: "MarketCapitalization"
          <*> o .: "LastTradePriceOnly"
          <*> o .: "DaysRange"
          <*> o .: "Name"
          <*> o .: "Symbol"
          <*> o .: "Volume"
          <*> o .: "StockExchange"