{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE TypeSynonymInstances #-}
#ifdef ghcjs_HOST_OS
{-# LANGUAGE ForeignFunctionInterface, JavaScriptFFI #-}
#endif
module Language.Javascript.JSaddle.Properties (
getProp, unsafeGetProp
, objGetPropertyByName
, objGetPropertyAtIndex
, setProp, unsafeSetProp
, objSetPropertyByName
, objSetPropertyAtIndex
) where
import Language.Javascript.JSaddle.Monad (JSM)
import Language.Javascript.JSaddle.Types (JSVal, Object(..))
import JavaScript.Object.Internal (getProp, unsafeGetProp, setProp, unsafeSetProp)
#ifdef ghcjs_HOST_OS
import GHCJS.Marshal (ToJSVal(..))
#else
import GHCJS.Marshal.Internal (ToJSVal(..))
import Language.Javascript.JSaddle.Native
(withObject, withToJSVal)
import Language.Javascript.JSaddle.Run
(AsyncCommand(..), sendLazyCommand, sendAsyncCommand)
#endif
import Language.Javascript.JSaddle.Arguments ()
import Language.Javascript.JSaddle.String ()
import Language.Javascript.JSaddle.Marshal.String (ToJSString(..))
objGetPropertyByName :: ToJSString name
=> Object
-> name
-> JSM JSVal
objGetPropertyByName this name = unsafeGetProp (toJSString name) this
objGetPropertyAtIndex :: Object
-> Int
-> JSM JSVal
#ifdef ghcjs_HOST_OS
objGetPropertyAtIndex this index = js_tryIndex index this
foreign import javascript unsafe "$r=$2[$1]"
js_tryIndex :: Int -> Object -> IO JSVal
#else
objGetPropertyAtIndex this index =
withObject this $ \rthis -> sendLazyCommand $ GetPropertyAtIndex rthis index
#endif
objSetPropertyByName :: (ToJSString name, ToJSVal val)
=> Object
-> name
-> val
-> JSM ()
objSetPropertyByName this name val = do
vref <- toJSVal val
unsafeSetProp (toJSString name) vref this
objSetPropertyAtIndex :: (ToJSVal val)
=> Object
-> Int
-> val
-> JSM ()
#ifdef ghcjs_HOST_OS
objSetPropertyAtIndex this index val = do
vref <- toJSVal val
js_trySetAtIndex index this vref
foreign import javascript unsafe "$2[$1]=$3"
js_trySetAtIndex :: Int -> Object -> JSVal -> IO ()
#else
objSetPropertyAtIndex this index val =
withObject this $ \rthis ->
withToJSVal val $ \rval ->
sendAsyncCommand $ SetPropertyAtIndex rthis index rval
#endif