{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE ImplicitParams, ConstraintKinds, KindSignatures #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
module JSDOM.Generated.ApplePayError
(newApplePayError, setCode, getCode, setContactField,
getContactField, getContactFieldUnsafe, getContactFieldUnchecked,
setMessage, getMessage, ApplePayError(..), gTypeApplePayError)
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 Data.Traversable (mapM)
import Language.Javascript.JSaddle (JSM(..), JSVal(..), JSString, strictEqual, toJSVal, valToStr, valToNumber, valToBool, js, jss, jsf, jsg, function, asyncFunction, new, array, jsUndefined, (!), (!!))
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, unsafeEventNameAsync)
import JSDOM.Enums
newApplePayError ::
(MonadDOM m, ToJSString message) =>
ApplePayErrorCode ->
Maybe ApplePayErrorContactField -> Maybe message -> m ApplePayError
newApplePayError errorCode contactField message
= liftDOM
(ApplePayError <$>
new (jsg "ApplePayError")
[toJSVal errorCode, toJSVal contactField, toJSVal message])
setCode ::
(MonadDOM m) => ApplePayError -> ApplePayErrorCode -> m ()
setCode self val = liftDOM (self ^. jss "code" (toJSVal val))
getCode :: (MonadDOM m) => ApplePayError -> m ApplePayErrorCode
getCode self = liftDOM ((self ^. js "code") >>= fromJSValUnchecked)
setContactField ::
(MonadDOM m) =>
ApplePayError -> Maybe ApplePayErrorContactField -> m ()
setContactField self val
= liftDOM (self ^. jss "contactField" (toJSVal val))
getContactField ::
(MonadDOM m) =>
ApplePayError -> m (Maybe ApplePayErrorContactField)
getContactField self
= liftDOM ((self ^. js "contactField") >>= fromJSVal)
getContactFieldUnsafe ::
(MonadDOM m, HasCallStack) =>
ApplePayError -> m ApplePayErrorContactField
getContactFieldUnsafe self
= liftDOM
(((self ^. js "contactField") >>= fromJSVal) >>=
maybe (Prelude.error "Nothing to return") return)
getContactFieldUnchecked ::
(MonadDOM m) => ApplePayError -> m ApplePayErrorContactField
getContactFieldUnchecked self
= liftDOM ((self ^. js "contactField") >>= fromJSValUnchecked)
setMessage ::
(MonadDOM m, ToJSString val) => ApplePayError -> val -> m ()
setMessage self val = liftDOM (self ^. jss "message" (toJSVal val))
getMessage ::
(MonadDOM m, FromJSString result) => ApplePayError -> m result
getMessage self
= liftDOM ((self ^. js "message") >>= fromJSValUnchecked)