{-# LANGUAGE PatternSynonyms, ForeignFunctionInterface, JavaScriptFFI #-} module GHCJS.DOM.JSFFI.Generated.RTCPeerConnection (js_newRTCPeerConnection, newRTCPeerConnection, js_createOffer, createOffer, js_createAnswer, createAnswer, js_setLocalDescription, setLocalDescription, js_setRemoteDescription, setRemoteDescription, js_updateIce, updateIce, js_addIceCandidate, addIceCandidate, js_getLocalStreams, getLocalStreams, js_getRemoteStreams, getRemoteStreams, js_getStreamById, getStreamById, js_getConfiguration, getConfiguration, js_addStream, addStream, js_removeStream, removeStream, js_getStats, getStats, js_createDataChannel, createDataChannel, js_createDTMFSender, createDTMFSender, js_close, close, js_getLocalDescription, getLocalDescription, js_getRemoteDescription, getRemoteDescription, js_getSignalingState, getSignalingState, js_getIceGatheringState, getIceGatheringState, js_getIceConnectionState, getIceConnectionState, negotiationNeeded, iceCandidate, signalingStateChange, addStreamEvent, removeStreamEvent, iceConnectionStateChange, dataChannel, RTCPeerConnection, castToRTCPeerConnection, gTypeRTCPeerConnection) where import Prelude ((.), (==), (>>=), return, IO, Int, Float, Double, Bool(..), Maybe, maybe, fromIntegral, round, fmap, Show, Read, Eq, Ord) import Data.Typeable (Typeable) import GHCJS.Types (JSVal(..), JSString) import GHCJS.Foreign (jsNull) import GHCJS.Foreign.Callback (syncCallback, asyncCallback, syncCallback1, asyncCallback1, syncCallback2, asyncCallback2, OnBlocked(..)) import GHCJS.Marshal (ToJSVal(..), FromJSVal(..)) import GHCJS.Marshal.Pure (PToJSVal(..), PFromJSVal(..)) import Control.Monad.IO.Class (MonadIO(..)) import Data.Int (Int64) import Data.Word (Word, Word64) import GHCJS.DOM.Types import Control.Applicative ((<$>)) import GHCJS.DOM.EventTargetClosures (EventName, unsafeEventName) import GHCJS.DOM.Enums foreign import javascript unsafe "new window[\"webkitRTCPeerConnection\"]($1)" js_newRTCPeerConnection :: Nullable Dictionary -> IO RTCPeerConnection -- | newRTCPeerConnection :: (MonadIO m, IsDictionary rtcConfiguration) => Maybe rtcConfiguration -> m RTCPeerConnection newRTCPeerConnection rtcConfiguration = liftIO (js_newRTCPeerConnection (maybeToNullable (fmap toDictionary rtcConfiguration))) foreign import javascript unsafe "$1[\"createOffer\"]($2, $3, $4)" js_createOffer :: RTCPeerConnection -> Nullable RTCSessionDescriptionCallback -> Nullable RTCPeerConnectionErrorCallback -> Nullable Dictionary -> IO () -- | createOffer :: (MonadIO m, IsDictionary offerOptions) => RTCPeerConnection -> Maybe RTCSessionDescriptionCallback -> Maybe RTCPeerConnectionErrorCallback -> Maybe offerOptions -> m () createOffer self successCallback failureCallback offerOptions = liftIO (js_createOffer (self) (maybeToNullable successCallback) (maybeToNullable failureCallback) (maybeToNullable (fmap toDictionary offerOptions))) foreign import javascript unsafe "$1[\"createAnswer\"]($2, $3, $4)" js_createAnswer :: RTCPeerConnection -> Nullable RTCSessionDescriptionCallback -> Nullable RTCPeerConnectionErrorCallback -> Nullable Dictionary -> IO () -- | createAnswer :: (MonadIO m, IsDictionary answerOptions) => RTCPeerConnection -> Maybe RTCSessionDescriptionCallback -> Maybe RTCPeerConnectionErrorCallback -> Maybe answerOptions -> m () createAnswer self successCallback failureCallback answerOptions = liftIO (js_createAnswer (self) (maybeToNullable successCallback) (maybeToNullable failureCallback) (maybeToNullable (fmap toDictionary answerOptions))) foreign import javascript unsafe "$1[\"setLocalDescription\"]($2,\n$3, $4)" js_setLocalDescription :: RTCPeerConnection -> Nullable RTCSessionDescription -> Nullable VoidCallback -> Nullable RTCPeerConnectionErrorCallback -> IO () -- | setLocalDescription :: (MonadIO m) => RTCPeerConnection -> Maybe RTCSessionDescription -> Maybe VoidCallback -> Maybe RTCPeerConnectionErrorCallback -> m () setLocalDescription self description successCallback failureCallback = liftIO (js_setLocalDescription (self) (maybeToNullable description) (maybeToNullable successCallback) (maybeToNullable failureCallback)) foreign import javascript unsafe "$1[\"setRemoteDescription\"]($2,\n$3, $4)" js_setRemoteDescription :: RTCPeerConnection -> Nullable RTCSessionDescription -> Nullable VoidCallback -> Nullable RTCPeerConnectionErrorCallback -> IO () -- | setRemoteDescription :: (MonadIO m) => RTCPeerConnection -> Maybe RTCSessionDescription -> Maybe VoidCallback -> Maybe RTCPeerConnectionErrorCallback -> m () setRemoteDescription self description successCallback failureCallback = liftIO (js_setRemoteDescription (self) (maybeToNullable description) (maybeToNullable successCallback) (maybeToNullable failureCallback)) foreign import javascript unsafe "$1[\"updateIce\"]($2)" js_updateIce :: RTCPeerConnection -> Nullable Dictionary -> IO () -- | updateIce :: (MonadIO m, IsDictionary configuration) => RTCPeerConnection -> Maybe configuration -> m () updateIce self configuration = liftIO (js_updateIce (self) (maybeToNullable (fmap toDictionary configuration))) foreign import javascript unsafe "$1[\"addIceCandidate\"]($2, $3,\n$4)" js_addIceCandidate :: RTCPeerConnection -> Nullable RTCIceCandidate -> Nullable VoidCallback -> Nullable RTCPeerConnectionErrorCallback -> IO () -- | addIceCandidate :: (MonadIO m) => RTCPeerConnection -> Maybe RTCIceCandidate -> Maybe VoidCallback -> Maybe RTCPeerConnectionErrorCallback -> m () addIceCandidate self candidate successCallback failureCallback = liftIO (js_addIceCandidate (self) (maybeToNullable candidate) (maybeToNullable successCallback) (maybeToNullable failureCallback)) foreign import javascript unsafe "$1[\"getLocalStreams\"]()" js_getLocalStreams :: RTCPeerConnection -> IO JSVal -- | getLocalStreams :: (MonadIO m) => RTCPeerConnection -> m [Maybe MediaStream] getLocalStreams self = liftIO ((js_getLocalStreams (self)) >>= fromJSValUnchecked) foreign import javascript unsafe "$1[\"getRemoteStreams\"]()" js_getRemoteStreams :: RTCPeerConnection -> IO JSVal -- | getRemoteStreams :: (MonadIO m) => RTCPeerConnection -> m [Maybe MediaStream] getRemoteStreams self = liftIO ((js_getRemoteStreams (self)) >>= fromJSValUnchecked) foreign import javascript unsafe "$1[\"getStreamById\"]($2)" js_getStreamById :: RTCPeerConnection -> JSString -> IO (Nullable MediaStream) -- | getStreamById :: (MonadIO m, ToJSString streamId) => RTCPeerConnection -> streamId -> m (Maybe MediaStream) getStreamById self streamId = liftIO (nullableToMaybe <$> (js_getStreamById (self) (toJSString streamId))) foreign import javascript unsafe "$1[\"getConfiguration\"]()" js_getConfiguration :: RTCPeerConnection -> IO (Nullable RTCConfiguration) -- | getConfiguration :: (MonadIO m) => RTCPeerConnection -> m (Maybe RTCConfiguration) getConfiguration self = liftIO (nullableToMaybe <$> (js_getConfiguration (self))) foreign import javascript unsafe "$1[\"addStream\"]($2)" js_addStream :: RTCPeerConnection -> Nullable MediaStream -> IO () -- | addStream :: (MonadIO m) => RTCPeerConnection -> Maybe MediaStream -> m () addStream self stream = liftIO (js_addStream (self) (maybeToNullable stream)) foreign import javascript unsafe "$1[\"removeStream\"]($2)" js_removeStream :: RTCPeerConnection -> Nullable MediaStream -> IO () -- | removeStream :: (MonadIO m) => RTCPeerConnection -> Maybe MediaStream -> m () removeStream self stream = liftIO (js_removeStream (self) (maybeToNullable stream)) foreign import javascript unsafe "$1[\"getStats\"]($2, $3, $4)" js_getStats :: RTCPeerConnection -> Nullable RTCStatsCallback -> Nullable RTCPeerConnectionErrorCallback -> Nullable MediaStreamTrack -> IO () -- | getStats :: (MonadIO m, IsMediaStreamTrack selector) => RTCPeerConnection -> Maybe RTCStatsCallback -> Maybe RTCPeerConnectionErrorCallback -> Maybe selector -> m () getStats self successCallback failureCallback selector = liftIO (js_getStats (self) (maybeToNullable successCallback) (maybeToNullable failureCallback) (maybeToNullable (fmap toMediaStreamTrack selector))) foreign import javascript unsafe "$1[\"createDataChannel\"]($2, $3)" js_createDataChannel :: RTCPeerConnection -> Nullable JSString -> Nullable Dictionary -> IO (Nullable RTCDataChannel) -- | createDataChannel :: (MonadIO m, ToJSString label, IsDictionary options) => RTCPeerConnection -> Maybe label -> Maybe options -> m (Maybe RTCDataChannel) createDataChannel self label options = liftIO (nullableToMaybe <$> (js_createDataChannel (self) (toMaybeJSString label) (maybeToNullable (fmap toDictionary options)))) foreign import javascript unsafe "$1[\"createDTMFSender\"]($2)" js_createDTMFSender :: RTCPeerConnection -> Nullable MediaStreamTrack -> IO (Nullable RTCDTMFSender) -- | createDTMFSender :: (MonadIO m, IsMediaStreamTrack track) => RTCPeerConnection -> Maybe track -> m (Maybe RTCDTMFSender) createDTMFSender self track = liftIO (nullableToMaybe <$> (js_createDTMFSender (self) (maybeToNullable (fmap toMediaStreamTrack track)))) foreign import javascript unsafe "$1[\"close\"]()" js_close :: RTCPeerConnection -> IO () -- | close :: (MonadIO m) => RTCPeerConnection -> m () close self = liftIO (js_close (self)) foreign import javascript unsafe "$1[\"localDescription\"]" js_getLocalDescription :: RTCPeerConnection -> IO (Nullable RTCSessionDescription) -- | getLocalDescription :: (MonadIO m) => RTCPeerConnection -> m (Maybe RTCSessionDescription) getLocalDescription self = liftIO (nullableToMaybe <$> (js_getLocalDescription (self))) foreign import javascript unsafe "$1[\"remoteDescription\"]" js_getRemoteDescription :: RTCPeerConnection -> IO (Nullable RTCSessionDescription) -- | getRemoteDescription :: (MonadIO m) => RTCPeerConnection -> m (Maybe RTCSessionDescription) getRemoteDescription self = liftIO (nullableToMaybe <$> (js_getRemoteDescription (self))) foreign import javascript unsafe "$1[\"signalingState\"]" js_getSignalingState :: RTCPeerConnection -> IO JSString -- | getSignalingState :: (MonadIO m, FromJSString result) => RTCPeerConnection -> m result getSignalingState self = liftIO (fromJSString <$> (js_getSignalingState (self))) foreign import javascript unsafe "$1[\"iceGatheringState\"]" js_getIceGatheringState :: RTCPeerConnection -> IO JSString -- | getIceGatheringState :: (MonadIO m, FromJSString result) => RTCPeerConnection -> m result getIceGatheringState self = liftIO (fromJSString <$> (js_getIceGatheringState (self))) foreign import javascript unsafe "$1[\"iceConnectionState\"]" js_getIceConnectionState :: RTCPeerConnection -> IO JSString -- | getIceConnectionState :: (MonadIO m, FromJSString result) => RTCPeerConnection -> m result getIceConnectionState self = liftIO (fromJSString <$> (js_getIceConnectionState (self))) -- | negotiationNeeded :: EventName RTCPeerConnection Event negotiationNeeded = unsafeEventName (toJSString "negotiationneeded") -- | iceCandidate :: EventName RTCPeerConnection RTCIceCandidateEvent iceCandidate = unsafeEventName (toJSString "icecandidate") -- | signalingStateChange :: EventName RTCPeerConnection Event signalingStateChange = unsafeEventName (toJSString "signalingstatechange") -- | addStreamEvent :: EventName RTCPeerConnection Event addStreamEvent = unsafeEventName (toJSString "addstream") -- | removeStreamEvent :: EventName RTCPeerConnection Event removeStreamEvent = unsafeEventName (toJSString "removestream") -- | iceConnectionStateChange :: EventName RTCPeerConnection Event iceConnectionStateChange = unsafeEventName (toJSString "iceconnectionstatechange") -- | dataChannel :: EventName RTCPeerConnection Event dataChannel = unsafeEventName (toJSString "datachannel")