{-# LANGUAGE OverloadedStrings #-}
module Web.Data.Yahoo.Response (PriceResponse(..), tryParse, tryParseAsPrice) where
import Data.ByteString.Char8 (unpack)
import Data.ByteString.Lazy (ByteString)
import Data.Csv (FromField(..), FromNamedRecord(..), (.:), decodeByName)
import Data.Time (defaultTimeLocale)
import Data.Time.Calendar (Day)
import Data.Time.Format (parseTimeM)
import Data.Vector (toList)
import Web.Data.Yahoo.Utils (right)
instance FromField Day where
parseField :: Field -> Parser Day
parseField = Bool -> TimeLocale -> String -> String -> Parser Day
forall (m :: * -> *) t.
(MonadFail m, ParseTime t) =>
Bool -> TimeLocale -> String -> String -> m t
parseTimeM Bool
True TimeLocale
defaultTimeLocale String
"%Y-%m-%d" (String -> Parser Day) -> (Field -> String) -> Field -> Parser Day
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Field -> String
unpack
data PriceResponse = PriceResponse {
PriceResponse -> Day
date :: Day,
PriceResponse -> Double
open :: Double,
PriceResponse -> Double
high :: Double,
PriceResponse -> Double
low :: Double,
PriceResponse -> Double
close :: Double,
PriceResponse -> Double
adjClose :: Double,
PriceResponse -> Double
volume :: Double
} deriving (Int -> PriceResponse -> ShowS
[PriceResponse] -> ShowS
PriceResponse -> String
(Int -> PriceResponse -> ShowS)
-> (PriceResponse -> String)
-> ([PriceResponse] -> ShowS)
-> Show PriceResponse
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PriceResponse] -> ShowS
$cshowList :: [PriceResponse] -> ShowS
show :: PriceResponse -> String
$cshow :: PriceResponse -> String
showsPrec :: Int -> PriceResponse -> ShowS
$cshowsPrec :: Int -> PriceResponse -> ShowS
Show, PriceResponse -> PriceResponse -> Bool
(PriceResponse -> PriceResponse -> Bool)
-> (PriceResponse -> PriceResponse -> Bool) -> Eq PriceResponse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PriceResponse -> PriceResponse -> Bool
$c/= :: PriceResponse -> PriceResponse -> Bool
== :: PriceResponse -> PriceResponse -> Bool
$c== :: PriceResponse -> PriceResponse -> Bool
Eq)
instance FromNamedRecord PriceResponse where
parseNamedRecord :: NamedRecord -> Parser PriceResponse
parseNamedRecord NamedRecord
r =
Day
-> Double
-> Double
-> Double
-> Double
-> Double
-> Double
-> PriceResponse
PriceResponse
(Day
-> Double
-> Double
-> Double
-> Double
-> Double
-> Double
-> PriceResponse)
-> Parser Day
-> Parser
(Double
-> Double -> Double -> Double -> Double -> Double -> PriceResponse)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> NamedRecord
r NamedRecord -> Field -> Parser Day
forall a. FromField a => NamedRecord -> Field -> Parser a
.: Field
"Date"
Parser
(Double
-> Double -> Double -> Double -> Double -> Double -> PriceResponse)
-> Parser Double
-> Parser
(Double -> Double -> Double -> Double -> Double -> PriceResponse)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> NamedRecord
r NamedRecord -> Field -> Parser Double
forall a. FromField a => NamedRecord -> Field -> Parser a
.: Field
"Open"
Parser
(Double -> Double -> Double -> Double -> Double -> PriceResponse)
-> Parser Double
-> Parser (Double -> Double -> Double -> Double -> PriceResponse)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> NamedRecord
r NamedRecord -> Field -> Parser Double
forall a. FromField a => NamedRecord -> Field -> Parser a
.: Field
"High"
Parser (Double -> Double -> Double -> Double -> PriceResponse)
-> Parser Double
-> Parser (Double -> Double -> Double -> PriceResponse)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> NamedRecord
r NamedRecord -> Field -> Parser Double
forall a. FromField a => NamedRecord -> Field -> Parser a
.: Field
"Low"
Parser (Double -> Double -> Double -> PriceResponse)
-> Parser Double -> Parser (Double -> Double -> PriceResponse)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> NamedRecord
r NamedRecord -> Field -> Parser Double
forall a. FromField a => NamedRecord -> Field -> Parser a
.: Field
"Close"
Parser (Double -> Double -> PriceResponse)
-> Parser Double -> Parser (Double -> PriceResponse)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> NamedRecord
r NamedRecord -> Field -> Parser Double
forall a. FromField a => NamedRecord -> Field -> Parser a
.: Field
"Adj Close"
Parser (Double -> PriceResponse)
-> Parser Double -> Parser PriceResponse
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> NamedRecord
r NamedRecord -> Field -> Parser Double
forall a. FromField a => NamedRecord -> Field -> Parser a
.: Field
"Volume"
tryParse :: FromNamedRecord a => ByteString -> Either String [a]
tryParse :: ByteString -> Either String [a]
tryParse = ((Header, Vector a) -> [a])
-> Either String (Header, Vector a) -> Either String [a]
forall t b a. (t -> b) -> Either a t -> Either a b
right (Vector a -> [a]
forall a. Vector a -> [a]
toList (Vector a -> [a])
-> ((Header, Vector a) -> Vector a) -> (Header, Vector a) -> [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Header, Vector a) -> Vector a
forall a b. (a, b) -> b
snd) (Either String (Header, Vector a) -> Either String [a])
-> (ByteString -> Either String (Header, Vector a))
-> ByteString
-> Either String [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Either String (Header, Vector a)
forall a.
FromNamedRecord a =>
ByteString -> Either String (Header, Vector a)
decodeByName
tryParseAsPrice :: ByteString -> Either String [PriceResponse]
tryParseAsPrice :: ByteString -> Either String [PriceResponse]
tryParseAsPrice = ByteString -> Either String [PriceResponse]
forall a. FromNamedRecord a => ByteString -> Either String [a]
tryParse