Safe Haskell | None |
---|---|
Language | Haskell2010 |
OpenTok.Archive
Synopsis
- data OutputMode
- data ArchiveResolution
- data ArchiveOptions
- archiveOpts :: ArchiveOptions
- data ArchiveStatus
- data Archive
- data ListArchiveOptions
- listArchiveOpts :: ListArchiveOptions
- data ArchiveCollection
- start :: Client -> ArchiveOptions -> IO (Either OTError Archive)
- stop :: Client -> ArchiveId -> IO (Either OTError Archive)
- list :: Client -> ListArchiveOptions -> IO (Either OTError ArchiveCollection)
- delete :: Client -> ArchiveId -> IO (Either OTError ArchiveId)
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 # | |
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 # | |
Defined in OpenTok.Archive Methods showsPrec :: Int -> OutputMode -> ShowS # show :: OutputMode -> String # showList :: [OutputMode] -> ShowS # | |
Generic OutputMode Source # | |
Defined in OpenTok.Archive Associated Types type Rep OutputMode :: * -> * # | |
ToJSON OutputMode Source # | |
Defined in OpenTok.Archive Methods toJSON :: OutputMode -> Value # toEncoding :: OutputMode -> Encoding # toJSONList :: [OutputMode] -> Value # toEncodingList :: [OutputMode] -> Encoding # | |
FromJSON OutputMode Source # | |
Defined in OpenTok.Archive | |
type Rep OutputMode Source # | |
data ArchiveResolution Source #
SD (Standard Definition 640 x 480)
HD (High Definition 1280 x 720)
Instances
Show ArchiveResolution Source # | |
Defined in OpenTok.Archive Methods showsPrec :: Int -> ArchiveResolution -> ShowS # show :: ArchiveResolution -> String # showList :: [ArchiveResolution] -> ShowS # | |
ToJSON ArchiveResolution Source # | |
Defined in OpenTok.Archive Methods toJSON :: ArchiveResolution -> Value # toEncoding :: ArchiveResolution -> Encoding # toJSONList :: [ArchiveResolution] -> Value # toEncodingList :: [ArchiveResolution] -> Encoding # | |
FromJSON ArchiveResolution Source # | |
Defined in OpenTok.Archive Methods parseJSON :: Value -> Parser ArchiveResolution # parseJSONList :: Value -> Parser [ArchiveResolution] # |
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
data ArchiveStatus Source #
Status of an OpenTok Archive
Instances
An OpenTok Archive
Archive { id ::String
, status ::ArchiveStatus
, createdAt ::Integer
, size ::Int
, partnerId ::Int
, url :: MaybeString
, resolution ::ArchiveResolution
, outputMode ::OutputMode
, hasAudio ::Bool
, hasVideo ::Bool
, reason ::String
, name ::String
, updatedAt ::Integer
, duration ::Int
, sessionId ::String
}
Instances
data ListArchiveOptions Source #
listArchiveOpts :: ListArchiveOptions Source #
Default List Archive options
ListArchiveOptions
{ _forSessionId = Nothing
, _offset = 0
, _count = 50
}
data ArchiveCollection Source #
Instances
list :: Client -> ListArchiveOptions -> IO (Either OTError ArchiveCollection) Source #