-- | 'Strive.Actions.Segments'
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)

-- | 'Strive.Actions.getStarredSegments'
type GetStarredSegmentsOptions = PaginationOptions

-- | 'Strive.Actions.getSegmentEfforts'
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
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetSegmentEffortsOptions] -> ShowS
$cshowList :: [GetSegmentEffortsOptions] -> ShowS
show :: GetSegmentEffortsOptions -> String
$cshow :: GetSegmentEffortsOptions -> String
showsPrec :: Int -> GetSegmentEffortsOptions -> ShowS
$cshowsPrec :: Int -> GetSegmentEffortsOptions -> ShowS
Show

instance Default GetSegmentEffortsOptions where
  def :: GetSegmentEffortsOptions
def = GetSegmentEffortsOptions
    { getSegmentEffortsOptions_athleteId :: Maybe Integer
getSegmentEffortsOptions_athleteId = forall a. Maybe a
Nothing
    , getSegmentEffortsOptions_range :: Maybe (UTCTime, UTCTime)
getSegmentEffortsOptions_range = 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 = forall a. QueryLike a => a -> Query
toQuery
    [ (String
"athlete_id", forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Show a => a -> String
show (GetSegmentEffortsOptions -> Maybe Integer
getSegmentEffortsOptions_athleteId GetSegmentEffortsOptions
options))
    , ( String
"start_date_local"
      , forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap
        (ByteString -> String
unpack forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
toStrict forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. ToJSON a => a -> ByteString
encode forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> a
fst)
        (GetSegmentEffortsOptions -> Maybe (UTCTime, UTCTime)
getSegmentEffortsOptions_range GetSegmentEffortsOptions
options)
      )
    , ( String
"end_date_local"
      , forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap
        (ByteString -> String
unpack forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
toStrict forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. ToJSON a => a -> ByteString
encode forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> b
snd)
        (GetSegmentEffortsOptions -> Maybe (UTCTime, UTCTime)
getSegmentEffortsOptions_range GetSegmentEffortsOptions
options)
      )
    , (String
"page", forall a. a -> Maybe a
Just (forall a. Show a => a -> String
show (GetSegmentEffortsOptions -> Integer
getSegmentEffortsOptions_page GetSegmentEffortsOptions
options)))
    , (String
"per_page", forall a. a -> Maybe a
Just (forall a. Show a => a -> String
show (GetSegmentEffortsOptions -> Integer
getSegmentEffortsOptions_perPage GetSegmentEffortsOptions
options)))
    ]

-- | 'Strive.Actions.getSegmentLeaderboard'
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
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetSegmentLeaderboardOptions] -> ShowS
$cshowList :: [GetSegmentLeaderboardOptions] -> ShowS
show :: GetSegmentLeaderboardOptions -> String
$cshow :: GetSegmentLeaderboardOptions -> String
showsPrec :: Int -> GetSegmentLeaderboardOptions -> ShowS
$cshowsPrec :: Int -> GetSegmentLeaderboardOptions -> ShowS
Show

instance Default GetSegmentLeaderboardOptions where
  def :: GetSegmentLeaderboardOptions
def = GetSegmentLeaderboardOptions
    { getSegmentLeaderboardOptions_gender :: Maybe Gender
getSegmentLeaderboardOptions_gender = forall a. Maybe a
Nothing
    , getSegmentLeaderboardOptions_ageGroup :: Maybe AgeGroup
getSegmentLeaderboardOptions_ageGroup = forall a. Maybe a
Nothing
    , getSegmentLeaderboardOptions_weightClass :: Maybe WeightClass
getSegmentLeaderboardOptions_weightClass = forall a. Maybe a
Nothing
    , getSegmentLeaderboardOptions_following :: Maybe Bool
getSegmentLeaderboardOptions_following = forall a. Maybe a
Nothing
    , getSegmentLeaderboardOptions_clubId :: Maybe Integer
getSegmentLeaderboardOptions_clubId = forall a. Maybe a
Nothing
    , getSegmentLeaderboardOptions_dateRange :: Maybe String
getSegmentLeaderboardOptions_dateRange = forall a. Maybe a
Nothing
    , getSegmentLeaderboardOptions_contextEntries :: Maybe Integer
getSegmentLeaderboardOptions_contextEntries = 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 = forall a. QueryLike a => a -> Query
toQuery
    [ (String
"gender", forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Show a => a -> String
show (GetSegmentLeaderboardOptions -> Maybe Gender
getSegmentLeaderboardOptions_gender GetSegmentLeaderboardOptions
options))
    , (String
"age_group", forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Show a => a -> String
show (GetSegmentLeaderboardOptions -> Maybe AgeGroup
getSegmentLeaderboardOptions_ageGroup GetSegmentLeaderboardOptions
options))
    , ( String
"weight_class"
      , forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Show a => a -> String
show (GetSegmentLeaderboardOptions -> Maybe WeightClass
getSegmentLeaderboardOptions_weightClass GetSegmentLeaderboardOptions
options)
      )
    , ( String
"following"
      , forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap
        (ByteString -> String
unpack forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
toStrict forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. ToJSON a => a -> ByteString
encode)
        (GetSegmentLeaderboardOptions -> Maybe Bool
getSegmentLeaderboardOptions_following GetSegmentLeaderboardOptions
options)
      )
    , (String
"club_id", forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap 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"
      , forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Show a => a -> String
show (GetSegmentLeaderboardOptions -> Maybe Integer
getSegmentLeaderboardOptions_contextEntries GetSegmentLeaderboardOptions
options)
      )
    , (String
"page", forall a. a -> Maybe a
Just (forall a. Show a => a -> String
show (GetSegmentLeaderboardOptions -> Integer
getSegmentLeaderboardOptions_page GetSegmentLeaderboardOptions
options)))
    , (String
"per_page", forall a. a -> Maybe a
Just (forall a. Show a => a -> String
show (GetSegmentLeaderboardOptions -> Integer
getSegmentLeaderboardOptions_perPage GetSegmentLeaderboardOptions
options)))
    ]

-- | 'Strive.Actions.exploreSegments'
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
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ExploreSegmentsOptions] -> ShowS
$cshowList :: [ExploreSegmentsOptions] -> ShowS
show :: ExploreSegmentsOptions -> String
$cshow :: ExploreSegmentsOptions -> String
showsPrec :: Int -> ExploreSegmentsOptions -> ShowS
$cshowsPrec :: Int -> 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 = forall a. QueryLike a => a -> Query
toQuery
    [ (String
"activity_type", forall a. Show a => a -> String
show (ExploreSegmentsOptions -> SegmentActivityType
exploreSegmentsOptions_activityType ExploreSegmentsOptions
options))
    , (String
"min_cat", forall a. Show a => a -> String
show (ExploreSegmentsOptions -> Integer
exploreSegmentsOptions_minCat ExploreSegmentsOptions
options))
    , (String
"max_cat", forall a. Show a => a -> String
show (ExploreSegmentsOptions -> Integer
exploreSegmentsOptions_maxCat ExploreSegmentsOptions
options))
    ]