module Strive.Options.Segments
( GetStarredSegmentsOptions,
GetSegmentEffortsOptions (..),
GetSegmentLeaderboardOptions (..),
ExploreSegmentsOptions (..),
)
where
import Data.Aeson (encode)
import Data.ByteString.Char8 (unpack)
import Data.ByteString.Lazy (toStrict)
import Data.Default (Default, def)
import Data.Time.Clock (UTCTime)
import Network.HTTP.Types (QueryLike, toQuery)
import Strive.Enums
( AgeGroup,
Gender,
SegmentActivityType (Riding),
WeightClass,
)
import Strive.Internal.Options (PaginationOptions)
type GetStarredSegmentsOptions = PaginationOptions
data GetSegmentEffortsOptions = GetSegmentEffortsOptions
{ GetSegmentEffortsOptions -> Maybe Integer
getSegmentEffortsOptions_athleteId :: Maybe Integer,
GetSegmentEffortsOptions -> Maybe (UTCTime, UTCTime)
getSegmentEffortsOptions_range :: Maybe (UTCTime, UTCTime),
GetSegmentEffortsOptions -> Integer
getSegmentEffortsOptions_page :: Integer,
GetSegmentEffortsOptions -> Integer
getSegmentEffortsOptions_perPage :: Integer
}
deriving (Int -> GetSegmentEffortsOptions -> ShowS
[GetSegmentEffortsOptions] -> ShowS
GetSegmentEffortsOptions -> String
(Int -> GetSegmentEffortsOptions -> ShowS)
-> (GetSegmentEffortsOptions -> String)
-> ([GetSegmentEffortsOptions] -> ShowS)
-> Show GetSegmentEffortsOptions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GetSegmentEffortsOptions -> ShowS
showsPrec :: Int -> GetSegmentEffortsOptions -> ShowS
$cshow :: GetSegmentEffortsOptions -> String
show :: GetSegmentEffortsOptions -> String
$cshowList :: [GetSegmentEffortsOptions] -> ShowS
showList :: [GetSegmentEffortsOptions] -> ShowS
Show)
instance Default GetSegmentEffortsOptions where
def :: GetSegmentEffortsOptions
def =
GetSegmentEffortsOptions
{ getSegmentEffortsOptions_athleteId :: Maybe Integer
getSegmentEffortsOptions_athleteId = Maybe Integer
forall a. Maybe a
Nothing,
getSegmentEffortsOptions_range :: Maybe (UTCTime, UTCTime)
getSegmentEffortsOptions_range = Maybe (UTCTime, UTCTime)
forall a. Maybe a
Nothing,
getSegmentEffortsOptions_page :: Integer
getSegmentEffortsOptions_page = Integer
1,
getSegmentEffortsOptions_perPage :: Integer
getSegmentEffortsOptions_perPage = Integer
200
}
instance QueryLike GetSegmentEffortsOptions where
toQuery :: GetSegmentEffortsOptions -> Query
toQuery GetSegmentEffortsOptions
options =
[(String, Maybe String)] -> Query
forall a. QueryLike a => a -> Query
toQuery
[ (String
"athlete_id", (Integer -> String) -> Maybe Integer -> Maybe String
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Integer -> String
forall a. Show a => a -> String
show (GetSegmentEffortsOptions -> Maybe Integer
getSegmentEffortsOptions_athleteId GetSegmentEffortsOptions
options)),
( String
"start_date_local",
((UTCTime, UTCTime) -> String)
-> Maybe (UTCTime, UTCTime) -> Maybe String
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap
(ByteString -> String
unpack (ByteString -> String)
-> ((UTCTime, UTCTime) -> ByteString)
-> (UTCTime, UTCTime)
-> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
toStrict (ByteString -> ByteString)
-> ((UTCTime, UTCTime) -> ByteString)
-> (UTCTime, UTCTime)
-> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UTCTime -> ByteString
forall a. ToJSON a => a -> ByteString
encode (UTCTime -> ByteString)
-> ((UTCTime, UTCTime) -> UTCTime)
-> (UTCTime, UTCTime)
-> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (UTCTime, UTCTime) -> UTCTime
forall a b. (a, b) -> a
fst)
(GetSegmentEffortsOptions -> Maybe (UTCTime, UTCTime)
getSegmentEffortsOptions_range GetSegmentEffortsOptions
options)
),
( String
"end_date_local",
((UTCTime, UTCTime) -> String)
-> Maybe (UTCTime, UTCTime) -> Maybe String
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap
(ByteString -> String
unpack (ByteString -> String)
-> ((UTCTime, UTCTime) -> ByteString)
-> (UTCTime, UTCTime)
-> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
toStrict (ByteString -> ByteString)
-> ((UTCTime, UTCTime) -> ByteString)
-> (UTCTime, UTCTime)
-> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UTCTime -> ByteString
forall a. ToJSON a => a -> ByteString
encode (UTCTime -> ByteString)
-> ((UTCTime, UTCTime) -> UTCTime)
-> (UTCTime, UTCTime)
-> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (UTCTime, UTCTime) -> UTCTime
forall a b. (a, b) -> b
snd)
(GetSegmentEffortsOptions -> Maybe (UTCTime, UTCTime)
getSegmentEffortsOptions_range GetSegmentEffortsOptions
options)
),
(String
"page", String -> Maybe String
forall a. a -> Maybe a
Just (Integer -> String
forall a. Show a => a -> String
show (GetSegmentEffortsOptions -> Integer
getSegmentEffortsOptions_page GetSegmentEffortsOptions
options))),
(String
"per_page", String -> Maybe String
forall a. a -> Maybe a
Just (Integer -> String
forall a. Show a => a -> String
show (GetSegmentEffortsOptions -> Integer
getSegmentEffortsOptions_perPage GetSegmentEffortsOptions
options)))
]
data GetSegmentLeaderboardOptions = GetSegmentLeaderboardOptions
{ GetSegmentLeaderboardOptions -> Maybe Gender
getSegmentLeaderboardOptions_gender :: Maybe Gender,
GetSegmentLeaderboardOptions -> Maybe AgeGroup
getSegmentLeaderboardOptions_ageGroup :: Maybe AgeGroup,
GetSegmentLeaderboardOptions -> Maybe WeightClass
getSegmentLeaderboardOptions_weightClass :: Maybe WeightClass,
GetSegmentLeaderboardOptions -> Maybe Bool
getSegmentLeaderboardOptions_following :: Maybe Bool,
GetSegmentLeaderboardOptions -> Maybe Integer
getSegmentLeaderboardOptions_clubId :: Maybe Integer,
GetSegmentLeaderboardOptions -> Maybe String
getSegmentLeaderboardOptions_dateRange :: Maybe String,
GetSegmentLeaderboardOptions -> Maybe Integer
getSegmentLeaderboardOptions_contextEntries :: Maybe Integer,
GetSegmentLeaderboardOptions -> Integer
getSegmentLeaderboardOptions_page :: Integer,
GetSegmentLeaderboardOptions -> Integer
getSegmentLeaderboardOptions_perPage :: Integer
}
deriving (Int -> GetSegmentLeaderboardOptions -> ShowS
[GetSegmentLeaderboardOptions] -> ShowS
GetSegmentLeaderboardOptions -> String
(Int -> GetSegmentLeaderboardOptions -> ShowS)
-> (GetSegmentLeaderboardOptions -> String)
-> ([GetSegmentLeaderboardOptions] -> ShowS)
-> Show GetSegmentLeaderboardOptions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GetSegmentLeaderboardOptions -> ShowS
showsPrec :: Int -> GetSegmentLeaderboardOptions -> ShowS
$cshow :: GetSegmentLeaderboardOptions -> String
show :: GetSegmentLeaderboardOptions -> String
$cshowList :: [GetSegmentLeaderboardOptions] -> ShowS
showList :: [GetSegmentLeaderboardOptions] -> ShowS
Show)
instance Default GetSegmentLeaderboardOptions where
def :: GetSegmentLeaderboardOptions
def =
GetSegmentLeaderboardOptions
{ getSegmentLeaderboardOptions_gender :: Maybe Gender
getSegmentLeaderboardOptions_gender = Maybe Gender
forall a. Maybe a
Nothing,
getSegmentLeaderboardOptions_ageGroup :: Maybe AgeGroup
getSegmentLeaderboardOptions_ageGroup = Maybe AgeGroup
forall a. Maybe a
Nothing,
getSegmentLeaderboardOptions_weightClass :: Maybe WeightClass
getSegmentLeaderboardOptions_weightClass = Maybe WeightClass
forall a. Maybe a
Nothing,
getSegmentLeaderboardOptions_following :: Maybe Bool
getSegmentLeaderboardOptions_following = Maybe Bool
forall a. Maybe a
Nothing,
getSegmentLeaderboardOptions_clubId :: Maybe Integer
getSegmentLeaderboardOptions_clubId = Maybe Integer
forall a. Maybe a
Nothing,
getSegmentLeaderboardOptions_dateRange :: Maybe String
getSegmentLeaderboardOptions_dateRange = Maybe String
forall a. Maybe a
Nothing,
getSegmentLeaderboardOptions_contextEntries :: Maybe Integer
getSegmentLeaderboardOptions_contextEntries = Maybe Integer
forall a. Maybe a
Nothing,
getSegmentLeaderboardOptions_page :: Integer
getSegmentLeaderboardOptions_page = Integer
1,
getSegmentLeaderboardOptions_perPage :: Integer
getSegmentLeaderboardOptions_perPage = Integer
200
}
instance QueryLike GetSegmentLeaderboardOptions where
toQuery :: GetSegmentLeaderboardOptions -> Query
toQuery GetSegmentLeaderboardOptions
options =
[(String, Maybe String)] -> Query
forall a. QueryLike a => a -> Query
toQuery
[ (String
"gender", (Gender -> String) -> Maybe Gender -> Maybe String
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Gender -> String
forall a. Show a => a -> String
show (GetSegmentLeaderboardOptions -> Maybe Gender
getSegmentLeaderboardOptions_gender GetSegmentLeaderboardOptions
options)),
(String
"age_group", (AgeGroup -> String) -> Maybe AgeGroup -> Maybe String
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap AgeGroup -> String
forall a. Show a => a -> String
show (GetSegmentLeaderboardOptions -> Maybe AgeGroup
getSegmentLeaderboardOptions_ageGroup GetSegmentLeaderboardOptions
options)),
( String
"weight_class",
(WeightClass -> String) -> Maybe WeightClass -> Maybe String
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap WeightClass -> String
forall a. Show a => a -> String
show (GetSegmentLeaderboardOptions -> Maybe WeightClass
getSegmentLeaderboardOptions_weightClass GetSegmentLeaderboardOptions
options)
),
( String
"following",
(Bool -> String) -> Maybe Bool -> Maybe String
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap
(ByteString -> String
unpack (ByteString -> String) -> (Bool -> ByteString) -> Bool -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
toStrict (ByteString -> ByteString)
-> (Bool -> ByteString) -> Bool -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> ByteString
forall a. ToJSON a => a -> ByteString
encode)
(GetSegmentLeaderboardOptions -> Maybe Bool
getSegmentLeaderboardOptions_following GetSegmentLeaderboardOptions
options)
),
(String
"club_id", (Integer -> String) -> Maybe Integer -> Maybe String
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Integer -> String
forall a. Show a => a -> String
show (GetSegmentLeaderboardOptions -> Maybe Integer
getSegmentLeaderboardOptions_clubId GetSegmentLeaderboardOptions
options)),
(String
"date_range", GetSegmentLeaderboardOptions -> Maybe String
getSegmentLeaderboardOptions_dateRange GetSegmentLeaderboardOptions
options),
( String
"context_entries",
(Integer -> String) -> Maybe Integer -> Maybe String
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Integer -> String
forall a. Show a => a -> String
show (GetSegmentLeaderboardOptions -> Maybe Integer
getSegmentLeaderboardOptions_contextEntries GetSegmentLeaderboardOptions
options)
),
(String
"page", String -> Maybe String
forall a. a -> Maybe a
Just (Integer -> String
forall a. Show a => a -> String
show (GetSegmentLeaderboardOptions -> Integer
getSegmentLeaderboardOptions_page GetSegmentLeaderboardOptions
options))),
(String
"per_page", String -> Maybe String
forall a. a -> Maybe a
Just (Integer -> String
forall a. Show a => a -> String
show (GetSegmentLeaderboardOptions -> Integer
getSegmentLeaderboardOptions_perPage GetSegmentLeaderboardOptions
options)))
]
data ExploreSegmentsOptions = ExploreSegmentsOptions
{ ExploreSegmentsOptions -> SegmentActivityType
exploreSegmentsOptions_activityType :: SegmentActivityType,
ExploreSegmentsOptions -> Integer
exploreSegmentsOptions_minCat :: Integer,
ExploreSegmentsOptions -> Integer
exploreSegmentsOptions_maxCat :: Integer
}
deriving (Int -> ExploreSegmentsOptions -> ShowS
[ExploreSegmentsOptions] -> ShowS
ExploreSegmentsOptions -> String
(Int -> ExploreSegmentsOptions -> ShowS)
-> (ExploreSegmentsOptions -> String)
-> ([ExploreSegmentsOptions] -> ShowS)
-> Show ExploreSegmentsOptions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ExploreSegmentsOptions -> ShowS
showsPrec :: Int -> ExploreSegmentsOptions -> ShowS
$cshow :: ExploreSegmentsOptions -> String
show :: ExploreSegmentsOptions -> String
$cshowList :: [ExploreSegmentsOptions] -> ShowS
showList :: [ExploreSegmentsOptions] -> ShowS
Show)
instance Default ExploreSegmentsOptions where
def :: ExploreSegmentsOptions
def =
ExploreSegmentsOptions
{ exploreSegmentsOptions_activityType :: SegmentActivityType
exploreSegmentsOptions_activityType = SegmentActivityType
Riding,
exploreSegmentsOptions_minCat :: Integer
exploreSegmentsOptions_minCat = Integer
0,
exploreSegmentsOptions_maxCat :: Integer
exploreSegmentsOptions_maxCat = Integer
5
}
instance QueryLike ExploreSegmentsOptions where
toQuery :: ExploreSegmentsOptions -> Query
toQuery ExploreSegmentsOptions
options =
[(String, String)] -> Query
forall a. QueryLike a => a -> Query
toQuery
[ (String
"activity_type", SegmentActivityType -> String
forall a. Show a => a -> String
show (ExploreSegmentsOptions -> SegmentActivityType
exploreSegmentsOptions_activityType ExploreSegmentsOptions
options)),
(String
"min_cat", Integer -> String
forall a. Show a => a -> String
show (ExploreSegmentsOptions -> Integer
exploreSegmentsOptions_minCat ExploreSegmentsOptions
options)),
(String
"max_cat", Integer -> String
forall a. Show a => a -> String
show (ExploreSegmentsOptions -> Integer
exploreSegmentsOptions_maxCat ExploreSegmentsOptions
options))
]