{-# LANGUAGE PatternSynonyms #-} -- For HasCallStack compatibility {-# LANGUAGE ImplicitParams, ConstraintKinds, KindSignatures #-} {-# OPTIONS_GHC -fno-warn-unused-imports #-} module JSDOM.Generated.ReadableStream (newReadableStream, read, read_, readUnsafe, readUnchecked, cancel, cancel_, cancelUnsafe, cancelUnchecked, pipeTo, pipeTo_, pipeToUnsafe, pipeToUnchecked, pipeThrough, pipeThrough_, pipeThroughUnsafe, pipeThroughUnchecked, getState, getClosed, getClosedUnsafe, getClosedUnchecked, getReady, getReadyUnsafe, getReadyUnchecked, ReadableStream(..), gTypeReadableStream) where import Prelude ((.), (==), (>>=), return, IO, Int, Float, Double, Bool(..), Maybe, maybe, fromIntegral, round, realToFrac, fmap, Show, Read, Eq, Ord, Maybe(..)) import qualified Prelude (error) import Data.Typeable (Typeable) import Language.Javascript.JSaddle (JSM(..), JSVal(..), JSString, strictEqual, toJSVal, valToStr, valToNumber, valToBool, js, jss, jsf, jsg, function, new, array) import Data.Int (Int64) import Data.Word (Word, Word64) import JSDOM.Types import Control.Applicative ((<$>)) import Control.Monad (void) import Control.Lens.Operators ((^.)) import JSDOM.EventTargetClosures (EventName, unsafeEventName) import JSDOM.Enums -- | newReadableStream :: (MonadDOM m) => JSVal -> m ReadableStream newReadableStream properties = liftDOM (ReadableStream <$> new (jsg "ReadableStream") [toJSVal properties]) -- | read :: (MonadDOM m) => ReadableStream -> m (Maybe GObject) read self = liftDOM ((self ^. jsf "read" ()) >>= fromJSVal) -- | read_ :: (MonadDOM m) => ReadableStream -> m () read_ self = liftDOM (void (self ^. jsf "read" ())) -- | readUnsafe :: (MonadDOM m, HasCallStack) => ReadableStream -> m GObject readUnsafe self = liftDOM (((self ^. jsf "read" ()) >>= fromJSVal) >>= maybe (Prelude.error "Nothing to return") return) -- | readUnchecked :: (MonadDOM m) => ReadableStream -> m GObject readUnchecked self = liftDOM ((self ^. jsf "read" ()) >>= fromJSValUnchecked) -- | cancel :: (MonadDOM m, ToJSString reason) => ReadableStream -> reason -> m (Maybe Promise) cancel self reason = liftDOM ((self ^. jsf "cancel" [toJSVal reason]) >>= fromJSVal) -- | cancel_ :: (MonadDOM m, ToJSString reason) => ReadableStream -> reason -> m () cancel_ self reason = liftDOM (void (self ^. jsf "cancel" [toJSVal reason])) -- | cancelUnsafe :: (MonadDOM m, ToJSString reason, HasCallStack) => ReadableStream -> reason -> m Promise cancelUnsafe self reason = liftDOM (((self ^. jsf "cancel" [toJSVal reason]) >>= fromJSVal) >>= maybe (Prelude.error "Nothing to return") return) -- | cancelUnchecked :: (MonadDOM m, ToJSString reason) => ReadableStream -> reason -> m Promise cancelUnchecked self reason = liftDOM ((self ^. jsf "cancel" [toJSVal reason]) >>= fromJSValUnchecked) -- | pipeTo :: (MonadDOM m) => ReadableStream -> JSVal -> JSVal -> m (Maybe Promise) pipeTo self streams options = liftDOM ((self ^. jsf "pipeTo" [toJSVal streams, toJSVal options]) >>= fromJSVal) -- | pipeTo_ :: (MonadDOM m) => ReadableStream -> JSVal -> JSVal -> m () pipeTo_ self streams options = liftDOM (void (self ^. jsf "pipeTo" [toJSVal streams, toJSVal options])) -- | pipeToUnsafe :: (MonadDOM m, HasCallStack) => ReadableStream -> JSVal -> JSVal -> m Promise pipeToUnsafe self streams options = liftDOM (((self ^. jsf "pipeTo" [toJSVal streams, toJSVal options]) >>= fromJSVal) >>= maybe (Prelude.error "Nothing to return") return) -- | pipeToUnchecked :: (MonadDOM m) => ReadableStream -> JSVal -> JSVal -> m Promise pipeToUnchecked self streams options = liftDOM ((self ^. jsf "pipeTo" [toJSVal streams, toJSVal options]) >>= fromJSValUnchecked) -- | pipeThrough :: (MonadDOM m) => ReadableStream -> JSVal -> JSVal -> m (Maybe GObject) pipeThrough self dest options = liftDOM ((self ^. jsf "pipeThrough" [toJSVal dest, toJSVal options]) >>= fromJSVal) -- | pipeThrough_ :: (MonadDOM m) => ReadableStream -> JSVal -> JSVal -> m () pipeThrough_ self dest options = liftDOM (void (self ^. jsf "pipeThrough" [toJSVal dest, toJSVal options])) -- | pipeThroughUnsafe :: (MonadDOM m, HasCallStack) => ReadableStream -> JSVal -> JSVal -> m GObject pipeThroughUnsafe self dest options = liftDOM (((self ^. jsf "pipeThrough" [toJSVal dest, toJSVal options]) >>= fromJSVal) >>= maybe (Prelude.error "Nothing to return") return) -- | pipeThroughUnchecked :: (MonadDOM m) => ReadableStream -> JSVal -> JSVal -> m GObject pipeThroughUnchecked self dest options = liftDOM ((self ^. jsf "pipeThrough" [toJSVal dest, toJSVal options]) >>= fromJSValUnchecked) -- | getState :: (MonadDOM m) => ReadableStream -> m ReadableStreamStateType getState self = liftDOM ((self ^. js "state") >>= fromJSValUnchecked) -- | getClosed :: (MonadDOM m) => ReadableStream -> m (Maybe Promise) getClosed self = liftDOM ((self ^. js "closed") >>= fromJSVal) -- | getClosedUnsafe :: (MonadDOM m, HasCallStack) => ReadableStream -> m Promise getClosedUnsafe self = liftDOM (((self ^. js "closed") >>= fromJSVal) >>= maybe (Prelude.error "Nothing to return") return) -- | getClosedUnchecked :: (MonadDOM m) => ReadableStream -> m Promise getClosedUnchecked self = liftDOM ((self ^. js "closed") >>= fromJSValUnchecked) -- | getReady :: (MonadDOM m) => ReadableStream -> m (Maybe Promise) getReady self = liftDOM ((self ^. js "ready") >>= fromJSVal) -- | getReadyUnsafe :: (MonadDOM m, HasCallStack) => ReadableStream -> m Promise getReadyUnsafe self = liftDOM (((self ^. js "ready") >>= fromJSVal) >>= maybe (Prelude.error "Nothing to return") return) -- | getReadyUnchecked :: (MonadDOM m) => ReadableStream -> m Promise getReadyUnchecked self = liftDOM ((self ^. js "ready") >>= fromJSValUnchecked)