{-# LANGUAGE ForeignFunctionInterface #-} {-# LANGUAGE JavaScriptFFI #-} module GHCJS.DOM.JSFFI.SpeechRecognition (newSpeechRecognition, getMaxAlternatives, setMaxAlternatives, getGrammars, setGrammars, getLang, setLang, getInterimResults, setInterimResults, getContinuous, setContinuous, audiostart, audioend, end, error, nomatch, result, soundstart, soundend, speechstart, speechend, start, abort, startRecognition, stop, SpeechRecognition(..), gTypeSpeechRecognition) 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, jsUndefined) 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 Data.Traversable (mapM) import GHCJS.DOM.Types import Control.Applicative ((<$>)) import GHCJS.DOM.EventTargetClosures (EventName, unsafeEventName) import GHCJS.DOM.JSFFI.Generated.Enums foreign import javascript unsafe "new window[\"webkitSpeechRecognition\"]()" js_newSpeechRecognition :: IO SpeechRecognition -- | newSpeechRecognition :: (MonadIO m) => m SpeechRecognition newSpeechRecognition = liftIO (js_newSpeechRecognition) foreign import javascript unsafe "$1[\"maxAlternatives\"]" js_speechRecognitionGetMaxAlternatives :: SpeechRecognition -> IO (Word) -- | getMaxAlternatives :: (MonadIO m) => SpeechRecognition -> m Word getMaxAlternatives self = liftIO (js_speechRecognitionGetMaxAlternatives self) foreign import javascript unsafe "$1[\"maxAlternatives\"] = $2;" js_speechRecognitionMaxAlternatives :: SpeechRecognition -> Word -> IO () -- | setMaxAlternatives :: (MonadIO m) => SpeechRecognition -> Word -> m () setMaxAlternatives self maxAlt = liftIO (js_speechRecognitionMaxAlternatives self maxAlt) foreign import javascript unsafe "$1[\"grammars\"]" js_speechRecognitionGetGrammars :: SpeechRecognition -> IO SpeechGrammarList -- | getGrammars :: (MonadIO m) => SpeechRecognition -> m (SpeechGrammarList) getGrammars self = liftIO (js_speechRecognitionGetGrammars self) foreign import javascript unsafe "$1[\"grammars\"] = $2;" js_speechRecognitionSetGrammars :: SpeechRecognition -> SpeechGrammarList -> IO () -- | setGrammars :: (MonadIO m) => SpeechRecognition -> SpeechGrammarList -> m () setGrammars self grammars = liftIO (js_speechRecognitionSetGrammars self grammars) foreign import javascript unsafe "$1[\"lang\"]" js_speechRecognitionGetLang :: SpeechRecognition -> IO JSString -- | getLang :: (MonadIO m, FromJSString result) => SpeechRecognition -> m (result) getLang self = liftIO (fromJSString <$> (js_speechRecognitionGetLang self)) foreign import javascript unsafe "$1[\"lang\"] = $2;" js_speechRecognitionSetLang :: SpeechRecognition -> JSString -> IO () -- | setLang :: (MonadIO m, ToJSString lang) => SpeechRecognition -> lang -> m () setLang self lang = liftIO (js_speechRecognitionSetLang self (toJSString lang)) foreign import javascript unsafe "$1[\"interimResults\"]" js_speechRecognitionGetInterimResults :: SpeechRecognition -> IO Bool -- | getInterimResults :: (MonadIO m) => SpeechRecognition -> m (Bool) getInterimResults self = liftIO (js_speechRecognitionGetInterimResults self) foreign import javascript unsafe "$1[\"interimResults\"] = $2;" js_speechRecognitionSetInterimResults :: SpeechRecognition -> Bool -> IO () -- | setInterimResults :: (MonadIO m) => SpeechRecognition -> Bool -> m () setInterimResults self val = liftIO (js_speechRecognitionSetInterimResults self val) foreign import javascript unsafe "$1[\"continuous\"]" js_speechRecognitionGetContinuous :: SpeechRecognition -> IO Bool -- | getContinuous :: (MonadIO m) => SpeechRecognition -> m (Bool) getContinuous self = liftIO (js_speechRecognitionGetContinuous self) foreign import javascript unsafe "$1[\"continuous\"] = $2;" js_speechRecognitionSetContinuous :: SpeechRecognition -> Bool -> IO () -- | setContinuous :: (MonadIO m) => SpeechRecognition -> Bool -> m () setContinuous self val = liftIO (js_speechRecognitionSetContinuous self val) -- | audiostart :: EventName SpeechRecognition Event audiostart = unsafeEventName (toJSString "audiostart") -- | audioend :: EventName SpeechRecognition Event audioend = unsafeEventName (toJSString "audioend") -- | end :: EventName SpeechRecognition Event end = unsafeEventName (toJSString "end") -- | error :: EventName SpeechRecognition SpeechRecognitionError error = unsafeEventName (toJSString "error") -- | nomatch :: EventName SpeechRecognition SpeechRecognitionEvent nomatch = unsafeEventName (toJSString "nomatch") -- | result :: EventName SpeechRecognition SpeechRecognitionEvent result = unsafeEventName (toJSString "result") -- | soundstart :: EventName SpeechRecognition Event soundstart = unsafeEventName (toJSString "soundstart") -- | soundend :: EventName SpeechRecognition Event soundend = unsafeEventName (toJSString "soundend") -- | speechstart :: EventName SpeechRecognition Event speechstart = unsafeEventName (toJSString "speechstart") -- | speechend :: EventName SpeechRecognition Event speechend = unsafeEventName (toJSString "speechend") -- | start :: EventName SpeechRecognition Event start = unsafeEventName (toJSString "start") foreign import javascript unsafe "$1[\"abort\"]()" js_speechRecognitionAbort :: SpeechRecognition -> IO () -- | abort :: (MonadIO m) => SpeechRecognition -> m () abort self = liftIO (js_speechRecognitionAbort self) foreign import javascript unsafe "$1[\"start\"]()" js_speechRecognitionStart :: SpeechRecognition -> IO () -- | startRecognition :: (MonadIO m) => SpeechRecognition -> m () startRecognition self = liftIO (js_speechRecognitionStart self) foreign import javascript unsafe "$1[\"stop\"]()" js_speechRecognitionStop :: SpeechRecognition -> IO () -- | stop :: (MonadIO m) => SpeechRecognition -> m () stop self = liftIO (js_speechRecognitionStop self)