opentok-0.0.3: An OpenTok SDK for Haskell

Safe HaskellNone
LanguageHaskell2010

OpenTok.Archive

Synopsis

Documentation

data OutputMode Source #

Composed means that streams will be composed into a single file

Individual means that an individual file will be created for each stream

Constructors

Composed 
Individual 
Instances
Data OutputMode Source # 
Instance details

Defined in OpenTok.Archive

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OutputMode -> c OutputMode #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OutputMode #

toConstr :: OutputMode -> Constr #

dataTypeOf :: OutputMode -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c OutputMode) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OutputMode) #

gmapT :: (forall b. Data b => b -> b) -> OutputMode -> OutputMode #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OutputMode -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OutputMode -> r #

gmapQ :: (forall d. Data d => d -> u) -> OutputMode -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> OutputMode -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> OutputMode -> m OutputMode #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OutputMode -> m OutputMode #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OutputMode -> m OutputMode #

Show OutputMode Source # 
Instance details

Defined in OpenTok.Archive

Generic OutputMode Source # 
Instance details

Defined in OpenTok.Archive

Associated Types

type Rep OutputMode :: * -> * #

ToJSON OutputMode Source # 
Instance details

Defined in OpenTok.Archive

FromJSON OutputMode Source # 
Instance details

Defined in OpenTok.Archive

type Rep OutputMode Source # 
Instance details

Defined in OpenTok.Archive

type Rep OutputMode = D1 (MetaData "OutputMode" "OpenTok.Archive" "opentok-0.0.3-4rI6lmTYEfEHdBdMKk9ANr" False) (C1 (MetaCons "Composed" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Individual" PrefixI False) (U1 :: * -> *))

data ArchiveOptions Source #

Defines options for an Archive

sessionId: The session to be archived

hasAudio: Whether the archive will record audio

hasVideo: Whether the archive will record video

name: The name of the archive

Whether all streams in the archive are recorded to a single file (Composed) or to individual files (Individual)

The resolution of the archive, either SD (the default, 640 x 480), or HD (1280 x 720)

Instances
Show ArchiveOptions Source # 
Instance details

Defined in OpenTok.Archive

Generic ArchiveOptions Source # 
Instance details

Defined in OpenTok.Archive

Associated Types

type Rep ArchiveOptions :: * -> * #

ToJSON ArchiveOptions Source # 
Instance details

Defined in OpenTok.Archive

type Rep ArchiveOptions Source # 
Instance details

Defined in OpenTok.Archive

archiveOpts :: ArchiveOptions Source #

Default Archive options

ArchiveOptions
  { _hasVideo   = True
  , _name       = Nothing
  , _outputMode = Composed
  , _resolution = SD
  , _sessionId  = ""
}

data ArchiveStatus Source #

Status of an OpenTok Archive

Instances
Data ArchiveStatus Source # 
Instance details

Defined in OpenTok.Archive

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ArchiveStatus -> c ArchiveStatus #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ArchiveStatus #

toConstr :: ArchiveStatus -> Constr #

dataTypeOf :: ArchiveStatus -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ArchiveStatus) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ArchiveStatus) #

gmapT :: (forall b. Data b => b -> b) -> ArchiveStatus -> ArchiveStatus #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ArchiveStatus -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ArchiveStatus -> r #

gmapQ :: (forall d. Data d => d -> u) -> ArchiveStatus -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ArchiveStatus -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ArchiveStatus -> m ArchiveStatus #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ArchiveStatus -> m ArchiveStatus #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ArchiveStatus -> m ArchiveStatus #

Show ArchiveStatus Source # 
Instance details

Defined in OpenTok.Archive

Generic ArchiveStatus Source # 
Instance details

Defined in OpenTok.Archive

Associated Types

type Rep ArchiveStatus :: * -> * #

ToJSON ArchiveStatus Source # 
Instance details

Defined in OpenTok.Archive

FromJSON ArchiveStatus Source # 
Instance details

Defined in OpenTok.Archive

type Rep ArchiveStatus Source # 
Instance details

Defined in OpenTok.Archive

type Rep ArchiveStatus = D1 (MetaData "ArchiveStatus" "OpenTok.Archive" "opentok-0.0.3-4rI6lmTYEfEHdBdMKk9ANr" False) ((C1 (MetaCons "Available" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "Expired" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Failed" PrefixI False) (U1 :: * -> *))) :+: ((C1 (MetaCons "Paused" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Started" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "Stopped" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Uploaded" PrefixI False) (U1 :: * -> *))))

data Archive Source #

An OpenTok 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
}
Instances
Show Archive Source # 
Instance details

Defined in OpenTok.Archive

Generic Archive Source # 
Instance details

Defined in OpenTok.Archive

Associated Types

type Rep Archive :: * -> * #

Methods

from :: Archive -> Rep Archive x #

to :: Rep Archive x -> Archive #

FromJSON Archive Source # 
Instance details

Defined in OpenTok.Archive

type Rep Archive Source # 
Instance details

Defined in OpenTok.Archive

type Rep Archive = D1 (MetaData "Archive" "OpenTok.Archive" "opentok-0.0.3-4rI6lmTYEfEHdBdMKk9ANr" False) (C1 (MetaCons "Archive" PrefixI True) (((S1 (MetaSel (Just "id") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: (S1 (MetaSel (Just "status") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: S1 (MetaSel (Just "createdAt") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Integer))) :*: ((S1 (MetaSel (Just "size") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Float) :*: S1 (MetaSel (Just "partnerId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) :*: (S1 (MetaSel (Just "url") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe String)) :*: S1 (MetaSel (Just "resolution") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ArchiveResolution)))) :*: (((S1 (MetaSel (Just "outputMode") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 OutputMode) :*: S1 (MetaSel (Just "hasAudio") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) :*: (S1 (MetaSel (Just "hasVideo") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool) :*: S1 (MetaSel (Just "reason") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String))) :*: ((S1 (MetaSel (Just "name") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: S1 (MetaSel (Just "updatedAt") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Integer)) :*: (S1 (MetaSel (Just "duration") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Float) :*: S1 (MetaSel (Just "sessionId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String))))))