{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE TemplateHaskell #-}
module OpenTok.Archive
  ( OutputMode(Composed, Individual)
  , ArchiveResolution(SD, HD)
  , ArchiveOptions
    ( _hasAudio
    , _hasAudio
    , _name
    , _outputMode
    , _resolution
    , _sessionId
    )
  , archiveOpts
  , ArchiveStatus(Available, Expired, Failed, Paused, Started, Stopped, Uploaded)
  , Archive
    ( id
    , status
    , createdAt
    , size
    , partnerId
    , url
    , resolution
    , outputMode
    , hasAudio
    , hasVideo
    , reason
    , name
    , updatedAt
    , duration
    , sessionId
    )
  , start
  , stop
  )
where
import           Prelude                        ( )
import           Prelude.Compat
import           Data.Aeson
import           Data.Aeson.Types
import           Data.Aeson.TH
import           Data.Data
import           Data.Semigroup                 ( (<>) )
import           Data.Strings                   ( strToLower )
import           GHC.Generics
import           OpenTok.Client
import           OpenTok.Types
data OutputMode = Composed | Individual deriving (Data, Generic, Typeable)
instance Show OutputMode where
  show = strToLower . showConstr . toConstr
deriveJSON defaultOptions { constructorTagModifier = strToLower } ''OutputMode
data ArchiveResolution = SD | HD
instance Show ArchiveResolution where
  show SD = "640x480 (SD)"
  show HD = "1280x720 (HD)"
instance ToJSON ArchiveResolution where
  toJSON SD = String "640x480"
  toJSON HD = String "1280x720"
instance FromJSON ArchiveResolution where
  parseJSON (String s) = case s of
    "640x480" -> pure SD
    "1280x720" -> pure HD
    _ -> typeMismatch "Could not parse ArchiveResolution" (String s)
  parseJSON x = typeMismatch "Expected String" x
data ArchiveOptions =  ArchiveOptions {
  _hasAudio :: Bool,
  _hasVideo :: Bool,
  _name :: Maybe String,
  _outputMode :: OutputMode,
  _resolution :: ArchiveResolution,
  _sessionId :: SessionId
} deriving (Generic, Show)
instance ToJSON ArchiveOptions where
  toJSON = genericToJSON defaultOptions { omitNothingFields = True, fieldLabelModifier = drop 1 }
archiveOpts :: ArchiveOptions
archiveOpts = ArchiveOptions
  { _hasAudio   = True
  , _hasVideo   = True
  , _name       = Nothing
  , _outputMode = Composed
  , _resolution = SD
  , _sessionId  = ""
  }
data ArchiveStatus = Available | Expired | Failed | Paused | Started | Stopped | Uploaded deriving (Data, Generic, Typeable)
deriveJSON defaultOptions { constructorTagModifier = strToLower } ''ArchiveStatus
instance Show ArchiveStatus where
  show = strToLower . showConstr . toConstr
data Archive = Archive {
  id :: String,
  status :: String,
  createdAt :: Integer,
  size :: Float,
  partnerId :: Int,
  url :: Maybe String,
  resolution :: ArchiveResolution,
  outputMode :: OutputMode,
  hasAudio :: Bool,
  hasVideo :: Bool,
  reason :: String,
  name :: String,
  updatedAt :: Integer,
  duration :: Float,
  sessionId :: String
} deriving (Show, Generic)
instance FromJSON Archive where
  parseJSON = genericParseJSON defaultOptions
start :: Client -> ArchiveOptions -> IO (Either OTError Archive)
start c opts = do
  let path = "/v2/project/" <> _apiKey c <> "/archive"
  response <- postWithBody c path (Just opts) :: IO (Either ClientError Archive)
  case response of
    Right archive -> pure $ Right archive
    Left  e       -> pure $ Left $ "Failed to start archive: " <> message e
stop :: Client -> ArchiveId -> IO (Either OTError Archive)
stop c aId = do
  let path = "/v2/project/" <> _apiKey c <> "/archive/" <> aId <> "/stop"
  response <- post c path :: IO (Either ClientError Archive)
  case response of
    Right archive -> pure $ Right archive
    Left  e       -> pure $ Left $ "An error occurred in attempting to stop an archive: " <> message e