-- | <http://strava.github.io/api/v3/streams/>
module Strive.Actions.Streams
  ( getActivityStreams,
    getEffortStreams,
    getSegmentStreams,
  )
where

import Data.Aeson (FromJSON)
import Data.List (intercalate)
import Network.HTTP.Types (toQuery)
import Strive.Aliases (Result, StreamId)
import Strive.Client (Client)
import Strive.Enums (StreamType)
import Strive.Internal.HTTP (get)
import Strive.Options (GetStreamsOptions)
import Strive.Types (StreamDetailed)

-- | <http://strava.github.io/api/v3/streams/#activity>
getActivityStreams ::
  Client ->
  StreamId ->
  [StreamType] ->
  GetStreamsOptions ->
  IO (Result [StreamDetailed])
getActivityStreams :: Client
-> StreamId
-> [StreamType]
-> GetStreamsOptions
-> IO (Result [StreamDetailed])
getActivityStreams = forall a b c. (a -> b -> c) -> b -> a -> c
flip forall a.
FromJSON a =>
Client
-> String
-> StreamId
-> [StreamType]
-> GetStreamsOptions
-> IO (Result a)
getStreams String
"activities"

-- | <http://strava.github.io/api/v3/streams/#effort>
getEffortStreams ::
  Client ->
  StreamId ->
  [StreamType] ->
  GetStreamsOptions ->
  IO (Result [StreamDetailed])
getEffortStreams :: Client
-> StreamId
-> [StreamType]
-> GetStreamsOptions
-> IO (Result [StreamDetailed])
getEffortStreams = forall a b c. (a -> b -> c) -> b -> a -> c
flip forall a.
FromJSON a =>
Client
-> String
-> StreamId
-> [StreamType]
-> GetStreamsOptions
-> IO (Result a)
getStreams String
"segment_efforts"

-- | <http://strava.github.io/api/v3/streams/#segment>
getSegmentStreams ::
  Client ->
  StreamId ->
  [StreamType] ->
  GetStreamsOptions ->
  IO (Result [StreamDetailed])
getSegmentStreams :: Client
-> StreamId
-> [StreamType]
-> GetStreamsOptions
-> IO (Result [StreamDetailed])
getSegmentStreams = forall a b c. (a -> b -> c) -> b -> a -> c
flip forall a.
FromJSON a =>
Client
-> String
-> StreamId
-> [StreamType]
-> GetStreamsOptions
-> IO (Result a)
getStreams String
"segments"

getStreams ::
  (FromJSON a) =>
  Client ->
  String ->
  StreamId ->
  [StreamType] ->
  GetStreamsOptions ->
  IO (Result a)
getStreams :: forall a.
FromJSON a =>
Client
-> String
-> StreamId
-> [StreamType]
-> GetStreamsOptions
-> IO (Result a)
getStreams Client
client String
kind StreamId
id_ [StreamType]
types GetStreamsOptions
options = forall q j.
(QueryLike q, FromJSON j) =>
Client -> String -> q -> IO (Result j)
get Client
client String
resource Query
query
  where
    resource :: String
resource =
      forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
        [ String
"api/v3/",
          String
kind,
          String
"/",
          forall a. Show a => a -> String
show StreamId
id_,
          String
"/streams/",
          forall a. [a] -> [[a]] -> [a]
intercalate String
"," (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Show a => a -> String
show [StreamType]
types)
        ]
    query :: Query
query = forall a. QueryLike a => a -> Query
toQuery GetStreamsOptions
options