{-# LANGUAGE CPP #-} {-# LANGUAGE PatternSynonyms #-} {-# LANGUAGE ForeignFunctionInterface #-} {-# LANGUAGE JavaScriptFFI #-} -- For HasCallStack compatibility {-# LANGUAGE ImplicitParams, ConstraintKinds, KindSignatures #-} module GHCJS.DOM.JSFFI.Generated.SpeechSynthesisUtterance (js_newSpeechSynthesisUtterance, newSpeechSynthesisUtterance, js_setText, setText, js_getText, getText, js_setLang, setLang, js_getLang, getLang, js_setVoice, setVoice, js_getVoice, getVoice, getVoiceUnsafe, getVoiceUnchecked, js_setVolume, setVolume, js_getVolume, getVolume, js_setRate, setRate, js_getRate, getRate, js_setPitch, setPitch, js_getPitch, getPitch, start, end, error, pause, resume, mark, boundary, SpeechSynthesisUtterance(..), gTypeSpeechSynthesisUtterance) where import Prelude ((.), (==), (>>=), return, IO, Int, Float, Double, Bool(..), Maybe, maybe, fromIntegral, round, fmap, Show, Read, Eq, Ord) import qualified Prelude (error) 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 (void) import Control.Monad.IO.Class (MonadIO(..)) import Data.Int (Int64) import Data.Word (Word, Word64) import Data.Maybe (fromJust) import GHCJS.DOM.Types import Control.Applicative ((<$>)) import GHCJS.DOM.EventTargetClosures (EventName, unsafeEventName) import GHCJS.DOM.JSFFI.Generated.Enums #if MIN_VERSION_base(4,9,0) import GHC.Stack (HasCallStack) #elif MIN_VERSION_base(4,8,0) import GHC.Stack (CallStack) import GHC.Exts (Constraint) type HasCallStack = ((?callStack :: CallStack) :: Constraint) #else import GHC.Exts (Constraint) type HasCallStack = (() :: Constraint) #endif foreign import javascript unsafe "new window[\"SpeechSynthesisUtterance\"]($1)" js_newSpeechSynthesisUtterance :: JSString -> IO SpeechSynthesisUtterance -- | newSpeechSynthesisUtterance :: (MonadIO m, ToJSString text) => text -> m SpeechSynthesisUtterance newSpeechSynthesisUtterance text = liftIO (js_newSpeechSynthesisUtterance (toJSString text)) foreign import javascript unsafe "$1[\"text\"] = $2;" js_setText :: SpeechSynthesisUtterance -> JSString -> IO () -- | setText :: (MonadIO m, ToJSString val) => SpeechSynthesisUtterance -> val -> m () setText self val = liftIO (js_setText (self) (toJSString val)) foreign import javascript unsafe "$1[\"text\"]" js_getText :: SpeechSynthesisUtterance -> IO JSString -- | getText :: (MonadIO m, FromJSString result) => SpeechSynthesisUtterance -> m result getText self = liftIO (fromJSString <$> (js_getText (self))) foreign import javascript unsafe "$1[\"lang\"] = $2;" js_setLang :: SpeechSynthesisUtterance -> JSString -> IO () -- | setLang :: (MonadIO m, ToJSString val) => SpeechSynthesisUtterance -> val -> m () setLang self val = liftIO (js_setLang (self) (toJSString val)) foreign import javascript unsafe "$1[\"lang\"]" js_getLang :: SpeechSynthesisUtterance -> IO JSString -- | getLang :: (MonadIO m, FromJSString result) => SpeechSynthesisUtterance -> m result getLang self = liftIO (fromJSString <$> (js_getLang (self))) foreign import javascript unsafe "$1[\"voice\"] = $2;" js_setVoice :: SpeechSynthesisUtterance -> Nullable SpeechSynthesisVoice -> IO () -- | setVoice :: (MonadIO m) => SpeechSynthesisUtterance -> Maybe SpeechSynthesisVoice -> m () setVoice self val = liftIO (js_setVoice (self) (maybeToNullable val)) foreign import javascript unsafe "$1[\"voice\"]" js_getVoice :: SpeechSynthesisUtterance -> IO (Nullable SpeechSynthesisVoice) -- | getVoice :: (MonadIO m) => SpeechSynthesisUtterance -> m (Maybe SpeechSynthesisVoice) getVoice self = liftIO (nullableToMaybe <$> (js_getVoice (self))) -- | getVoiceUnsafe :: (MonadIO m, HasCallStack) => SpeechSynthesisUtterance -> m SpeechSynthesisVoice getVoiceUnsafe self = liftIO ((nullableToMaybe <$> (js_getVoice (self))) >>= maybe (Prelude.error "Nothing to return") return) -- | getVoiceUnchecked :: (MonadIO m) => SpeechSynthesisUtterance -> m SpeechSynthesisVoice getVoiceUnchecked self = liftIO (fromJust . nullableToMaybe <$> (js_getVoice (self))) foreign import javascript unsafe "$1[\"volume\"] = $2;" js_setVolume :: SpeechSynthesisUtterance -> Float -> IO () -- | setVolume :: (MonadIO m) => SpeechSynthesisUtterance -> Float -> m () setVolume self val = liftIO (js_setVolume (self) val) foreign import javascript unsafe "$1[\"volume\"]" js_getVolume :: SpeechSynthesisUtterance -> IO Float -- | getVolume :: (MonadIO m) => SpeechSynthesisUtterance -> m Float getVolume self = liftIO (js_getVolume (self)) foreign import javascript unsafe "$1[\"rate\"] = $2;" js_setRate :: SpeechSynthesisUtterance -> Float -> IO () -- | setRate :: (MonadIO m) => SpeechSynthesisUtterance -> Float -> m () setRate self val = liftIO (js_setRate (self) val) foreign import javascript unsafe "$1[\"rate\"]" js_getRate :: SpeechSynthesisUtterance -> IO Float -- | getRate :: (MonadIO m) => SpeechSynthesisUtterance -> m Float getRate self = liftIO (js_getRate (self)) foreign import javascript unsafe "$1[\"pitch\"] = $2;" js_setPitch :: SpeechSynthesisUtterance -> Float -> IO () -- | setPitch :: (MonadIO m) => SpeechSynthesisUtterance -> Float -> m () setPitch self val = liftIO (js_setPitch (self) val) foreign import javascript unsafe "$1[\"pitch\"]" js_getPitch :: SpeechSynthesisUtterance -> IO Float -- | getPitch :: (MonadIO m) => SpeechSynthesisUtterance -> m Float getPitch self = liftIO (js_getPitch (self)) -- | start :: EventName SpeechSynthesisUtterance Event start = unsafeEventName (toJSString "start") -- | end :: EventName SpeechSynthesisUtterance Event end = unsafeEventName (toJSString "end") -- | error :: EventName SpeechSynthesisUtterance UIEvent error = unsafeEventName (toJSString "error") -- | pause :: EventName SpeechSynthesisUtterance Event pause = unsafeEventName (toJSString "pause") -- | resume :: EventName SpeechSynthesisUtterance Event resume = unsafeEventName (toJSString "resume") -- | mark :: EventName SpeechSynthesisUtterance Event mark = unsafeEventName (toJSString "mark") -- | boundary :: EventName SpeechSynthesisUtterance Event boundary = unsafeEventName (toJSString "boundary")