{-# LANGUAGE PatternSynonyms #-}
-- For HasCallStack compatibility
{-# LANGUAGE ImplicitParams, ConstraintKinds, KindSignatures #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
module JSDOM.Generated.Enums
       (KeyType(..), ToJSVal, FromJSVal, js_KeyTypePublic,
        js_KeyTypePrivate, js_KeyTypeSecret, CryptoKeyUsage(..),
        js_CryptoKeyUsageEncrypt, js_CryptoKeyUsageDecrypt,
        js_CryptoKeyUsageSign, js_CryptoKeyUsageVerify,
        js_CryptoKeyUsageDeriveKey, js_CryptoKeyUsageDeriveBits,
        js_CryptoKeyUsageWrapKey, js_CryptoKeyUsageUnwrapKey,
        KeyFormat(..), js_KeyFormatRaw, js_KeyFormatSpki,
        js_KeyFormatPkcs8, js_KeyFormatJwk, FontFaceLoadStatus(..),
        js_FontFaceLoadStatusUnloaded, js_FontFaceLoadStatusLoading,
        js_FontFaceLoadStatusLoaded, js_FontFaceLoadStatusError,
        FontFaceSetLoadStatus(..), js_FontFaceSetLoadStatusLoading,
        js_FontFaceSetLoadStatusLoaded, VisibilityState(..),
        js_VisibilityStateHidden, js_VisibilityStateVisible,
        js_VisibilityStatePrerender, DocumentReadyState(..),
        js_DocumentReadyStateLoading, js_DocumentReadyStateInteractive,
        js_DocumentReadyStateComplete, ShadowRootMode(..),
        js_ShadowRootModeUserAgent, js_ShadowRootModeClosed,
        js_ShadowRootModeOpen, BlobLineEndings(..),
        js_BlobLineEndingsTransparent, js_BlobLineEndingsNative,
        ImageSmoothingQuality(..), js_ImageSmoothingQualityLow,
        js_ImageSmoothingQualityMedium, js_ImageSmoothingQualityHigh,
        CanvasWindingRule(..), js_CanvasWindingRuleNonzero,
        js_CanvasWindingRuleEvenodd, WebGLPowerPreference(..),
        js_WebGLPowerPreferenceDefault, js_WebGLPowerPreferenceLowPower,
        js_WebGLPowerPreferenceHighPerformance, WebGPUCompareFunction(..),
        js_WebGPUCompareFunctionNever, js_WebGPUCompareFunctionLess,
        js_WebGPUCompareFunctionEqual, js_WebGPUCompareFunctionLessequal,
        js_WebGPUCompareFunctionGreater, js_WebGPUCompareFunctionNotequal,
        js_WebGPUCompareFunctionGreaterequal,
        js_WebGPUCompareFunctionAlways, WebGPUPixelFormat(..),
        js_WebGPUPixelFormatBGRA8Unorm, WebGPULoadAction(..),
        js_WebGPULoadActionDontcare, js_WebGPULoadActionLoad,
        js_WebGPULoadActionClear, WebGPUStoreAction(..),
        js_WebGPUStoreActionDontcare, js_WebGPUStoreActionStore,
        js_WebGPUStoreActionMultisampleresolve, WebGPUPrimitiveType(..),
        js_WebGPUPrimitiveTypePoint, js_WebGPUPrimitiveTypeLine,
        js_WebGPUPrimitiveTypeLinestrip, js_WebGPUPrimitiveTypeTriangle,
        js_WebGPUPrimitiveTypeTrianglestrip, WebGPUFunctionType(..),
        js_WebGPUFunctionTypeFragment, js_WebGPUFunctionTypeVertex,
        WebGPUStencilOperation(..), js_WebGPUStencilOperationKeep,
        js_WebGPUStencilOperationZero, js_WebGPUStencilOperationReplace,
        js_WebGPUStencilOperationIncrementclamp,
        js_WebGPUStencilOperationDecrementclamp,
        js_WebGPUStencilOperationInvert,
        js_WebGPUStencilOperationIncrementwrap,
        js_WebGPUStencilOperationDecrementwrap, WebGPUStatus(..),
        js_WebGPUStatusNotenqueued, js_WebGPUStatusEnqueued,
        js_WebGPUStatusCommitted, js_WebGPUStatusScheduled,
        js_WebGPUStatusCompleted, js_WebGPUStatusError,
        WebGPUSamplerAddressMode(..),
        js_WebGPUSamplerAddressModeClamptoedge,
        js_WebGPUSamplerAddressModeMirrorclamptoedge,
        js_WebGPUSamplerAddressModeRepeat,
        js_WebGPUSamplerAddressModeMirrorrepeat,
        js_WebGPUSamplerAddressModeClamptozero,
        WebGPUSamplerMinMagFilter(..), js_WebGPUSamplerMinMagFilterNearest,
        js_WebGPUSamplerMinMagFilterLinear, WebGPUSamplerMipFilter(..),
        js_WebGPUSamplerMipFilterNotmipmapped,
        js_WebGPUSamplerMipFilterNearest, js_WebGPUSamplerMipFilterLinear,
        WebGPUCullMode(..), js_WebGPUCullModeNone, js_WebGPUCullModeFront,
        js_WebGPUCullModeBack, WebGPUIndexType(..),
        js_WebGPUIndexTypeUint16, js_WebGPUIndexTypeUint32,
        WebGPUVisibilityResultMode(..),
        js_WebGPUVisibilityResultModeDisabled,
        js_WebGPUVisibilityResultModeBoolean,
        js_WebGPUVisibilityResultModeCounting, WebGPUWinding(..),
        js_WebGPUWindingClockwise, js_WebGPUWindingCounterclockwise,
        WebGPUDepthClipMode(..), js_WebGPUDepthClipModeClip,
        js_WebGPUDepthClipModeClamp, WebGPUTriangleFillMode(..),
        js_WebGPUTriangleFillModeFill, js_WebGPUTriangleFillModeLines,
        WebGPUCPUCacheMode(..), js_WebGPUCPUCacheModeDefaultcache,
        js_WebGPUCPUCacheModeWritecombined, WebGPUStorageMode(..),
        js_WebGPUStorageModeShared, js_WebGPUStorageModeManaged,
        js_WebGPUStorageModePrivate, WebGPUResourceOptions(..),
        js_WebGPUResourceOptionsCpucachemodedefaultcache,
        js_WebGPUResourceOptionsCpucachemodewritecombined,
        js_WebGPUResourceOptionsStoragemodeshared,
        js_WebGPUResourceOptionsStoragemodemanaged,
        js_WebGPUResourceOptionsStoragemodeprivate,
        js_WebGPUResourceOptionsOptioncpucachemodedefaultcache,
        js_WebGPUResourceOptionsOptioncpucachemodewritecombined,
        WebGPUTextureUsage(..), js_WebGPUTextureUsageUnknown,
        js_WebGPUTextureUsageShaderread, js_WebGPUTextureUsageShaderwrite,
        js_WebGPUTextureUsageRendertarget,
        js_WebGPUTextureUsagePixelformatview, WebGPUBlendOperation(..),
        js_WebGPUBlendOperationAdd, js_WebGPUBlendOperationSubtract,
        js_WebGPUBlendOperationReversesubtract, js_WebGPUBlendOperationMin,
        js_WebGPUBlendOperationMax, WebGPUBlendFactor(..),
        js_WebGPUBlendFactorZero, js_WebGPUBlendFactorOne,
        js_WebGPUBlendFactorSourcecolor,
        js_WebGPUBlendFactorOneminussourcecolor,
        js_WebGPUBlendFactorSourcealpha,
        js_WebGPUBlendFactorOneminussourcealpha,
        js_WebGPUBlendFactorDestinationcolor,
        js_WebGPUBlendFactorOneminusdestinationcolor,
        js_WebGPUBlendFactorDestinationalpha,
        js_WebGPUBlendFactorOneminusdestinationalpha,
        js_WebGPUBlendFactorSourcealphasaturated,
        js_WebGPUBlendFactorBlendcolor,
        js_WebGPUBlendFactorOneminusblendcolor,
        js_WebGPUBlendFactorBlendalpha,
        js_WebGPUBlendFactorOneminusblendalpha, WebGPUColorWriteMask(..),
        js_WebGPUColorWriteMaskNone, js_WebGPUColorWriteMaskRed,
        js_WebGPUColorWriteMaskGreen, js_WebGPUColorWriteMaskBlue,
        js_WebGPUColorWriteMaskAlpha, js_WebGPUColorWriteMaskAll,
        WebGPUMultisampleDepthResolveFilter(..),
        js_WebGPUMultisampleDepthResolveFilterSample0,
        js_WebGPUMultisampleDepthResolveFilterMin,
        js_WebGPUMultisampleDepthResolveFilterMax, WebGPUFeatureSet(..),
        js_WebGPUFeatureSetLevel1, js_WebGPUFeatureSetLevel2,
        VideoPresentationMode(..), js_VideoPresentationModeFullscreen,
        js_VideoPresentationModePictureInPicture,
        js_VideoPresentationModeInline, TextTrackMode(..),
        js_TextTrackModeDisabled, js_TextTrackModeHidden,
        js_TextTrackModeShowing, TextTrackKind(..),
        js_TextTrackKindSubtitles, js_TextTrackKindCaptions,
        js_TextTrackKindDescriptions, js_TextTrackKindChapters,
        js_TextTrackKindMetadata, js_TextTrackKindForced,
        ApplePayErrorCode(..), js_ApplePayErrorCodeUnknown,
        js_ApplePayErrorCodeShippingContactInvalid,
        js_ApplePayErrorCodeBillingContactInvalid,
        js_ApplePayErrorCodeAddressUnservicable,
        ApplePayErrorContactField(..),
        js_ApplePayErrorContactFieldPhoneNumber,
        js_ApplePayErrorContactFieldEmailAddress,
        js_ApplePayErrorContactFieldName,
        js_ApplePayErrorContactFieldPostalAddress,
        js_ApplePayErrorContactFieldAddressLines,
        js_ApplePayErrorContactFieldLocality,
        js_ApplePayErrorContactFieldPostalCode,
        js_ApplePayErrorContactFieldAdministrativeArea,
        js_ApplePayErrorContactFieldCountry, ApplePayLineItemType(..),
        js_ApplePayLineItemTypePending, js_ApplePayLineItemTypeFinal,
        ApplePayPaymentMethodType(..), js_ApplePayPaymentMethodTypeDebit,
        js_ApplePayPaymentMethodTypeCredit,
        js_ApplePayPaymentMethodTypePrepaid,
        js_ApplePayPaymentMethodTypeStore,
        ApplePayPaymentPassActivationState(..),
        js_ApplePayPaymentPassActivationStateActivated,
        js_ApplePayPaymentPassActivationStateRequiresActivation,
        js_ApplePayPaymentPassActivationStateActivating,
        js_ApplePayPaymentPassActivationStateSuspended,
        js_ApplePayPaymentPassActivationStateDeactivated,
        ApplePayMerchantCapability(..),
        js_ApplePayMerchantCapabilitySupports3DS,
        js_ApplePayMerchantCapabilitySupportsEMV,
        js_ApplePayMerchantCapabilitySupportsCredit,
        js_ApplePayMerchantCapabilitySupportsDebit,
        ApplePayContactField(..), js_ApplePayContactFieldEmail,
        js_ApplePayContactFieldName, js_ApplePayContactFieldPhone,
        js_ApplePayContactFieldPostalAddress, ApplePayShippingType(..),
        js_ApplePayShippingTypeShipping, js_ApplePayShippingTypeDelivery,
        js_ApplePayShippingTypeStorePickup,
        js_ApplePayShippingTypeServicePickup, MediaKeyMessageType(..),
        js_MediaKeyMessageTypeLicenseRequest,
        js_MediaKeyMessageTypeLicenseRenewal,
        js_MediaKeyMessageTypeLicenseRelease,
        js_MediaKeyMessageTypeIndividualizationRequest,
        MediaKeySessionType(..), js_MediaKeySessionTypeTemporary,
        js_MediaKeySessionTypePersistentUsageRecord,
        js_MediaKeySessionTypePersistentLicense, MediaKeysRequirement(..),
        js_MediaKeysRequirementRequired, js_MediaKeysRequirementOptional,
        js_MediaKeysRequirementNotAllowed, MediaKeyStatus(..),
        js_MediaKeyStatusUsable, js_MediaKeyStatusExpired,
        js_MediaKeyStatusReleased, js_MediaKeyStatusOutputRestricted,
        js_MediaKeyStatusOutputDownscaled, js_MediaKeyStatusStatusPending,
        js_MediaKeyStatusInternalError, RequestType(..), js_RequestType,
        js_RequestTypeAudio, js_RequestTypeFont, js_RequestTypeImage,
        js_RequestTypeScript, js_RequestTypeStyle, js_RequestTypeTrack,
        js_RequestTypeVideo, RequestDestination(..), js_RequestDestination,
        js_RequestDestinationDocument, js_RequestDestinationSharedworker,
        js_RequestDestinationSubresource, js_RequestDestinationUnknown,
        js_RequestDestinationWorker, RequestMode(..),
        js_RequestModeNavigate, js_RequestModeSameOrigin,
        js_RequestModeNoCors, js_RequestModeCors, RequestCredentials(..),
        js_RequestCredentialsOmit, js_RequestCredentialsSameOrigin,
        js_RequestCredentialsInclude, RequestCache(..),
        js_RequestCacheDefault, js_RequestCacheNoStore,
        js_RequestCacheReload, js_RequestCacheNoCache,
        js_RequestCacheForceCache, js_RequestCacheOnlyIfCached,
        RequestRedirect(..), js_RequestRedirectFollow,
        js_RequestRedirectError, js_RequestRedirectManual,
        ReferrerPolicy(..), js_ReferrerPolicy, js_ReferrerPolicyNoReferrer,
        js_ReferrerPolicyNoReferrerWhenDowngrade, js_ReferrerPolicyOrigin,
        js_ReferrerPolicyOriginWhenCrossOrigin, js_ReferrerPolicyUnsafeUrl,
        ResponseType(..), js_ResponseTypeBasic, js_ResponseTypeCors,
        js_ResponseTypeDefault, js_ResponseTypeError,
        js_ResponseTypeOpaque, js_ResponseTypeOpaqueredirect,
        IDBCursorDirection(..), js_IDBCursorDirectionNext,
        js_IDBCursorDirectionNextunique, js_IDBCursorDirectionPrev,
        js_IDBCursorDirectionPrevunique, IDBRequestReadyState(..),
        js_IDBRequestReadyStatePending, js_IDBRequestReadyStateDone,
        IDBTransactionMode(..), js_IDBTransactionModeReadonly,
        js_IDBTransactionModeReadwrite, js_IDBTransactionModeVersionchange,
        DeviceType(..), js_DeviceTypeNone, js_DeviceTypeAirplay,
        js_DeviceTypeTvout, MediaSessionKind(..),
        js_MediaSessionKindContent, js_MediaSessionKindTransient,
        js_MediaSessionKindTransientSolo, js_MediaSessionKindAmbient,
        EndOfStreamError(..), js_EndOfStreamErrorNetwork,
        js_EndOfStreamErrorDecode, ReadyState(..), js_ReadyStateClosed,
        js_ReadyStateOpen, js_ReadyStateEnded, AppendMode(..),
        js_AppendModeSegments, js_AppendModeSequence, MediaDeviceKind(..),
        js_MediaDeviceKindAudioinput, js_MediaDeviceKindAudiooutput,
        js_MediaDeviceKindVideoinput, MediaStreamTrackState(..),
        js_MediaStreamTrackStateLive, js_MediaStreamTrackStateEnded,
        RTCIceTransportPolicy(..), js_RTCIceTransportPolicyRelay,
        js_RTCIceTransportPolicyAll, RTCBundlePolicy(..),
        js_RTCBundlePolicyBalanced, js_RTCBundlePolicyMaxCompat,
        js_RTCBundlePolicyMaxBundle, RTCDataChannelState(..),
        js_RTCDataChannelStateConnecting, js_RTCDataChannelStateOpen,
        js_RTCDataChannelStateClosing, js_RTCDataChannelStateClosed,
        RTCIceConnectionState(..), js_RTCIceConnectionStateNew,
        js_RTCIceConnectionStateChecking,
        js_RTCIceConnectionStateConnected,
        js_RTCIceConnectionStateCompleted, js_RTCIceConnectionStateFailed,
        js_RTCIceConnectionStateDisconnected,
        js_RTCIceConnectionStateClosed, RTCIceGatheringState(..),
        js_RTCIceGatheringStateNew, js_RTCIceGatheringStateGathering,
        js_RTCIceGatheringStateComplete, RTCIceTransportState(..),
        js_RTCIceTransportStateNew, js_RTCIceTransportStateChecking,
        js_RTCIceTransportStateConnected, js_RTCIceTransportStateCompleted,
        js_RTCIceTransportStateFailed, js_RTCIceTransportStateDisconnected,
        js_RTCIceTransportStateClosed, RTCPeerConnectionState(..),
        js_RTCPeerConnectionStateNew, js_RTCPeerConnectionStateConnecting,
        js_RTCPeerConnectionStateConnected,
        js_RTCPeerConnectionStateDisconnected,
        js_RTCPeerConnectionStateFailed, js_RTCPeerConnectionStateClosed,
        RTCDegradationPreference(..),
        js_RTCDegradationPreferenceMaintainFramerate,
        js_RTCDegradationPreferenceMaintainResolution,
        js_RTCDegradationPreferenceBalanced, RTCDtxStatus(..),
        js_RTCDtxStatusDisabled, js_RTCDtxStatusEnabled,
        RTCPriorityType(..), js_RTCPriorityTypeVeryLow,
        js_RTCPriorityTypeLow, js_RTCPriorityTypeMedium,
        js_RTCPriorityTypeHigh, RTCRtpTransceiverDirection(..),
        js_RTCRtpTransceiverDirectionSendrecv,
        js_RTCRtpTransceiverDirectionSendonly,
        js_RTCRtpTransceiverDirectionRecvonly,
        js_RTCRtpTransceiverDirectionInactive, RTCSdpType(..),
        js_RTCSdpTypeOffer, js_RTCSdpTypePranswer, js_RTCSdpTypeAnswer,
        js_RTCSdpTypeRollback, RTCSignalingState(..),
        js_RTCSignalingStateStable, js_RTCSignalingStateHaveLocalOffer,
        js_RTCSignalingStateHaveRemoteOffer,
        js_RTCSignalingStateHaveLocalPranswer,
        js_RTCSignalingStateHaveRemotePranswer, RTCStatsType(..),
        js_RTCStatsTypeCodec, js_RTCStatsTypeInboundRtp,
        js_RTCStatsTypeOutboundRtp, js_RTCStatsTypePeerConnection,
        js_RTCStatsTypeDataChannel, js_RTCStatsTypeTrack,
        js_RTCStatsTypeTransport, js_RTCStatsTypeCandidatePair,
        js_RTCStatsTypeLocalCandidate, js_RTCStatsTypeRemoteCandidate,
        js_RTCStatsTypeCertificate, NotificationDirection(..),
        js_NotificationDirectionAuto, js_NotificationDirectionLtr,
        js_NotificationDirectionRtl, AudioContextState(..),
        js_AudioContextStateSuspended, js_AudioContextStateRunning,
        js_AudioContextStateInterrupted, js_AudioContextStateClosed,
        BiquadFilterType(..), js_BiquadFilterTypeLowpass,
        js_BiquadFilterTypeHighpass, js_BiquadFilterTypeBandpass,
        js_BiquadFilterTypeLowshelf, js_BiquadFilterTypeHighshelf,
        js_BiquadFilterTypePeaking, js_BiquadFilterTypeNotch,
        js_BiquadFilterTypeAllpass, OscillatorType(..),
        js_OscillatorTypeSine, js_OscillatorTypeSquare,
        js_OscillatorTypeSawtooth, js_OscillatorTypeTriangle,
        js_OscillatorTypeCustom, PanningModelType(..),
        js_PanningModelTypeEqualpower, js_PanningModelTypeHRTF,
        DistanceModelType(..), js_DistanceModelTypeLinear,
        js_DistanceModelTypeInverse, js_DistanceModelTypeExponential,
        OverSampleType(..), js_OverSampleTypeNone, js_OverSampleType2x,
        js_OverSampleType4x, ScrollRestoration(..),
        js_ScrollRestorationAuto, js_ScrollRestorationManual,
        XMLHttpRequestResponseType(..), js_XMLHttpRequestResponseType,
        js_XMLHttpRequestResponseTypeArraybuffer,
        js_XMLHttpRequestResponseTypeBlob,
        js_XMLHttpRequestResponseTypeDocument,
        js_XMLHttpRequestResponseTypeJson,
        js_XMLHttpRequestResponseTypeText)
       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 ((^.))
 
data KeyType = KeyTypePublic
             | KeyTypePrivate
             | KeyTypeSecret
             deriving (Int -> KeyType -> ShowS
[KeyType] -> ShowS
KeyType -> String
(Int -> KeyType -> ShowS)
-> (KeyType -> String) -> ([KeyType] -> ShowS) -> Show KeyType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [KeyType] -> ShowS
$cshowList :: [KeyType] -> ShowS
show :: KeyType -> String
$cshow :: KeyType -> String
showsPrec :: Int -> KeyType -> ShowS
$cshowsPrec :: Int -> KeyType -> ShowS
Show, ReadPrec [KeyType]
ReadPrec KeyType
Int -> ReadS KeyType
ReadS [KeyType]
(Int -> ReadS KeyType)
-> ReadS [KeyType]
-> ReadPrec KeyType
-> ReadPrec [KeyType]
-> Read KeyType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [KeyType]
$creadListPrec :: ReadPrec [KeyType]
readPrec :: ReadPrec KeyType
$creadPrec :: ReadPrec KeyType
readList :: ReadS [KeyType]
$creadList :: ReadS [KeyType]
readsPrec :: Int -> ReadS KeyType
$creadsPrec :: Int -> ReadS KeyType
Read, KeyType -> KeyType -> Bool
(KeyType -> KeyType -> Bool)
-> (KeyType -> KeyType -> Bool) -> Eq KeyType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: KeyType -> KeyType -> Bool
$c/= :: KeyType -> KeyType -> Bool
== :: KeyType -> KeyType -> Bool
$c== :: KeyType -> KeyType -> Bool
Eq, Eq KeyType
Eq KeyType
-> (KeyType -> KeyType -> Ordering)
-> (KeyType -> KeyType -> Bool)
-> (KeyType -> KeyType -> Bool)
-> (KeyType -> KeyType -> Bool)
-> (KeyType -> KeyType -> Bool)
-> (KeyType -> KeyType -> KeyType)
-> (KeyType -> KeyType -> KeyType)
-> Ord KeyType
KeyType -> KeyType -> Bool
KeyType -> KeyType -> Ordering
KeyType -> KeyType -> KeyType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: KeyType -> KeyType -> KeyType
$cmin :: KeyType -> KeyType -> KeyType
max :: KeyType -> KeyType -> KeyType
$cmax :: KeyType -> KeyType -> KeyType
>= :: KeyType -> KeyType -> Bool
$c>= :: KeyType -> KeyType -> Bool
> :: KeyType -> KeyType -> Bool
$c> :: KeyType -> KeyType -> Bool
<= :: KeyType -> KeyType -> Bool
$c<= :: KeyType -> KeyType -> Bool
< :: KeyType -> KeyType -> Bool
$c< :: KeyType -> KeyType -> Bool
compare :: KeyType -> KeyType -> Ordering
$ccompare :: KeyType -> KeyType -> Ordering
$cp1Ord :: Eq KeyType
Ord, Typeable)
 
instance ToJSVal KeyType where
        toJSVal :: KeyType -> JSM JSVal
toJSVal KeyType
KeyTypePublic = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_KeyTypePublic
        toJSVal KeyType
KeyTypePrivate = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_KeyTypePrivate
        toJSVal KeyType
KeyTypeSecret = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_KeyTypeSecret
 
instance FromJSVal KeyType where
        fromJSVal :: JSVal -> JSM (Maybe KeyType)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_KeyTypePublic JSM Bool -> (Bool -> JSM (Maybe KeyType)) -> JSM (Maybe KeyType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe KeyType -> JSM (Maybe KeyType)
forall (m :: * -> *) a. Monad m => a -> m a
return (KeyType -> Maybe KeyType
forall a. a -> Maybe a
Just KeyType
KeyTypePublic)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_KeyTypePrivate JSM Bool -> (Bool -> JSM (Maybe KeyType)) -> JSM (Maybe KeyType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe KeyType -> JSM (Maybe KeyType)
forall (m :: * -> *) a. Monad m => a -> m a
return (KeyType -> Maybe KeyType
forall a. a -> Maybe a
Just KeyType
KeyTypePrivate)
                                 Bool
False
                                   -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_KeyTypeSecret JSM Bool -> (Bool -> JSM (Maybe KeyType)) -> JSM (Maybe KeyType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                        \ Bool
r ->
                                          case Bool
r of
                                              Bool
True -> Maybe KeyType -> JSM (Maybe KeyType)
forall (m :: * -> *) a. Monad m => a -> m a
return (KeyType -> Maybe KeyType
forall a. a -> Maybe a
Just KeyType
KeyTypeSecret)
                                              Bool
False -> Maybe KeyType -> JSM (Maybe KeyType)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe KeyType
forall a. Maybe a
Nothing
js_KeyTypePublic :: String
js_KeyTypePublic = String
"public"
js_KeyTypePrivate :: String
js_KeyTypePrivate = String
"private"
js_KeyTypeSecret :: String
js_KeyTypeSecret = String
"secret"
 
data CryptoKeyUsage = CryptoKeyUsageEncrypt
                    | CryptoKeyUsageDecrypt
                    | CryptoKeyUsageSign
                    | CryptoKeyUsageVerify
                    | CryptoKeyUsageDeriveKey
                    | CryptoKeyUsageDeriveBits
                    | CryptoKeyUsageWrapKey
                    | CryptoKeyUsageUnwrapKey
                    deriving (Int -> CryptoKeyUsage -> ShowS
[CryptoKeyUsage] -> ShowS
CryptoKeyUsage -> String
(Int -> CryptoKeyUsage -> ShowS)
-> (CryptoKeyUsage -> String)
-> ([CryptoKeyUsage] -> ShowS)
-> Show CryptoKeyUsage
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CryptoKeyUsage] -> ShowS
$cshowList :: [CryptoKeyUsage] -> ShowS
show :: CryptoKeyUsage -> String
$cshow :: CryptoKeyUsage -> String
showsPrec :: Int -> CryptoKeyUsage -> ShowS
$cshowsPrec :: Int -> CryptoKeyUsage -> ShowS
Show, ReadPrec [CryptoKeyUsage]
ReadPrec CryptoKeyUsage
Int -> ReadS CryptoKeyUsage
ReadS [CryptoKeyUsage]
(Int -> ReadS CryptoKeyUsage)
-> ReadS [CryptoKeyUsage]
-> ReadPrec CryptoKeyUsage
-> ReadPrec [CryptoKeyUsage]
-> Read CryptoKeyUsage
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CryptoKeyUsage]
$creadListPrec :: ReadPrec [CryptoKeyUsage]
readPrec :: ReadPrec CryptoKeyUsage
$creadPrec :: ReadPrec CryptoKeyUsage
readList :: ReadS [CryptoKeyUsage]
$creadList :: ReadS [CryptoKeyUsage]
readsPrec :: Int -> ReadS CryptoKeyUsage
$creadsPrec :: Int -> ReadS CryptoKeyUsage
Read, CryptoKeyUsage -> CryptoKeyUsage -> Bool
(CryptoKeyUsage -> CryptoKeyUsage -> Bool)
-> (CryptoKeyUsage -> CryptoKeyUsage -> Bool) -> Eq CryptoKeyUsage
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CryptoKeyUsage -> CryptoKeyUsage -> Bool
$c/= :: CryptoKeyUsage -> CryptoKeyUsage -> Bool
== :: CryptoKeyUsage -> CryptoKeyUsage -> Bool
$c== :: CryptoKeyUsage -> CryptoKeyUsage -> Bool
Eq, Eq CryptoKeyUsage
Eq CryptoKeyUsage
-> (CryptoKeyUsage -> CryptoKeyUsage -> Ordering)
-> (CryptoKeyUsage -> CryptoKeyUsage -> Bool)
-> (CryptoKeyUsage -> CryptoKeyUsage -> Bool)
-> (CryptoKeyUsage -> CryptoKeyUsage -> Bool)
-> (CryptoKeyUsage -> CryptoKeyUsage -> Bool)
-> (CryptoKeyUsage -> CryptoKeyUsage -> CryptoKeyUsage)
-> (CryptoKeyUsage -> CryptoKeyUsage -> CryptoKeyUsage)
-> Ord CryptoKeyUsage
CryptoKeyUsage -> CryptoKeyUsage -> Bool
CryptoKeyUsage -> CryptoKeyUsage -> Ordering
CryptoKeyUsage -> CryptoKeyUsage -> CryptoKeyUsage
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CryptoKeyUsage -> CryptoKeyUsage -> CryptoKeyUsage
$cmin :: CryptoKeyUsage -> CryptoKeyUsage -> CryptoKeyUsage
max :: CryptoKeyUsage -> CryptoKeyUsage -> CryptoKeyUsage
$cmax :: CryptoKeyUsage -> CryptoKeyUsage -> CryptoKeyUsage
>= :: CryptoKeyUsage -> CryptoKeyUsage -> Bool
$c>= :: CryptoKeyUsage -> CryptoKeyUsage -> Bool
> :: CryptoKeyUsage -> CryptoKeyUsage -> Bool
$c> :: CryptoKeyUsage -> CryptoKeyUsage -> Bool
<= :: CryptoKeyUsage -> CryptoKeyUsage -> Bool
$c<= :: CryptoKeyUsage -> CryptoKeyUsage -> Bool
< :: CryptoKeyUsage -> CryptoKeyUsage -> Bool
$c< :: CryptoKeyUsage -> CryptoKeyUsage -> Bool
compare :: CryptoKeyUsage -> CryptoKeyUsage -> Ordering
$ccompare :: CryptoKeyUsage -> CryptoKeyUsage -> Ordering
$cp1Ord :: Eq CryptoKeyUsage
Ord, Typeable)
 
instance ToJSVal CryptoKeyUsage where
        toJSVal :: CryptoKeyUsage -> JSM JSVal
toJSVal CryptoKeyUsage
CryptoKeyUsageEncrypt = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_CryptoKeyUsageEncrypt
        toJSVal CryptoKeyUsage
CryptoKeyUsageDecrypt = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_CryptoKeyUsageDecrypt
        toJSVal CryptoKeyUsage
CryptoKeyUsageSign = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_CryptoKeyUsageSign
        toJSVal CryptoKeyUsage
CryptoKeyUsageVerify = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_CryptoKeyUsageVerify
        toJSVal CryptoKeyUsage
CryptoKeyUsageDeriveKey
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_CryptoKeyUsageDeriveKey
        toJSVal CryptoKeyUsage
CryptoKeyUsageDeriveBits
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_CryptoKeyUsageDeriveBits
        toJSVal CryptoKeyUsage
CryptoKeyUsageWrapKey = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_CryptoKeyUsageWrapKey
        toJSVal CryptoKeyUsage
CryptoKeyUsageUnwrapKey
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_CryptoKeyUsageUnwrapKey
 
instance FromJSVal CryptoKeyUsage where
        fromJSVal :: JSVal -> JSM (Maybe CryptoKeyUsage)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_CryptoKeyUsageEncrypt JSM Bool
-> (Bool -> JSM (Maybe CryptoKeyUsage))
-> JSM (Maybe CryptoKeyUsage)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe CryptoKeyUsage -> JSM (Maybe CryptoKeyUsage)
forall (m :: * -> *) a. Monad m => a -> m a
return (CryptoKeyUsage -> Maybe CryptoKeyUsage
forall a. a -> Maybe a
Just CryptoKeyUsage
CryptoKeyUsageEncrypt)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_CryptoKeyUsageDecrypt JSM Bool
-> (Bool -> JSM (Maybe CryptoKeyUsage))
-> JSM (Maybe CryptoKeyUsage)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe CryptoKeyUsage -> JSM (Maybe CryptoKeyUsage)
forall (m :: * -> *) a. Monad m => a -> m a
return (CryptoKeyUsage -> Maybe CryptoKeyUsage
forall a. a -> Maybe a
Just CryptoKeyUsage
CryptoKeyUsageDecrypt)
                                 Bool
False
                                   -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_CryptoKeyUsageSign JSM Bool
-> (Bool -> JSM (Maybe CryptoKeyUsage))
-> JSM (Maybe CryptoKeyUsage)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                        \ Bool
r ->
                                          case Bool
r of
                                              Bool
True -> Maybe CryptoKeyUsage -> JSM (Maybe CryptoKeyUsage)
forall (m :: * -> *) a. Monad m => a -> m a
return (CryptoKeyUsage -> Maybe CryptoKeyUsage
forall a. a -> Maybe a
Just CryptoKeyUsage
CryptoKeyUsageSign)
                                              Bool
False
                                                -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_CryptoKeyUsageVerify JSM Bool
-> (Bool -> JSM (Maybe CryptoKeyUsage))
-> JSM (Maybe CryptoKeyUsage)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                     \ Bool
r ->
                                                       case Bool
r of
                                                           Bool
True
                                                             -> Maybe CryptoKeyUsage -> JSM (Maybe CryptoKeyUsage)
forall (m :: * -> *) a. Monad m => a -> m a
return (CryptoKeyUsage -> Maybe CryptoKeyUsage
forall a. a -> Maybe a
Just CryptoKeyUsage
CryptoKeyUsageVerify)
                                                           Bool
False
                                                             -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                                  String
js_CryptoKeyUsageDeriveKey
                                                                  JSM Bool
-> (Bool -> JSM (Maybe CryptoKeyUsage))
-> JSM (Maybe CryptoKeyUsage)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                  \ Bool
r ->
                                                                    case Bool
r of
                                                                        Bool
True
                                                                          -> Maybe CryptoKeyUsage -> JSM (Maybe CryptoKeyUsage)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                               (CryptoKeyUsage -> Maybe CryptoKeyUsage
forall a. a -> Maybe a
Just
                                                                                  CryptoKeyUsage
CryptoKeyUsageDeriveKey)
                                                                        Bool
False
                                                                          -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                                               String
js_CryptoKeyUsageDeriveBits
                                                                               JSM Bool
-> (Bool -> JSM (Maybe CryptoKeyUsage))
-> JSM (Maybe CryptoKeyUsage)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                               \ Bool
r ->
                                                                                 case Bool
r of
                                                                                     Bool
True
                                                                                       -> Maybe CryptoKeyUsage -> JSM (Maybe CryptoKeyUsage)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                                            (CryptoKeyUsage -> Maybe CryptoKeyUsage
forall a. a -> Maybe a
Just
                                                                                               CryptoKeyUsage
CryptoKeyUsageDeriveBits)
                                                                                     Bool
False
                                                                                       -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                                                            String
js_CryptoKeyUsageWrapKey
                                                                                            JSM Bool
-> (Bool -> JSM (Maybe CryptoKeyUsage))
-> JSM (Maybe CryptoKeyUsage)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                                            \ Bool
r ->
                                                                                              case Bool
r
                                                                                                of
                                                                                                  Bool
True
                                                                                                    -> Maybe CryptoKeyUsage -> JSM (Maybe CryptoKeyUsage)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                                                         (CryptoKeyUsage -> Maybe CryptoKeyUsage
forall a. a -> Maybe a
Just
                                                                                                            CryptoKeyUsage
CryptoKeyUsageWrapKey)
                                                                                                  Bool
False
                                                                                                    -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                                                                         String
js_CryptoKeyUsageUnwrapKey
                                                                                                         JSM Bool
-> (Bool -> JSM (Maybe CryptoKeyUsage))
-> JSM (Maybe CryptoKeyUsage)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                                                         \ Bool
r
                                                                                                           ->
                                                                                                           case
                                                                                                             Bool
r
                                                                                                             of
                                                                                                               Bool
True
                                                                                                                 -> Maybe CryptoKeyUsage -> JSM (Maybe CryptoKeyUsage)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                                                                      (CryptoKeyUsage -> Maybe CryptoKeyUsage
forall a. a -> Maybe a
Just
                                                                                                                         CryptoKeyUsage
CryptoKeyUsageUnwrapKey)
                                                                                                               Bool
False
                                                                                                                 -> Maybe CryptoKeyUsage -> JSM (Maybe CryptoKeyUsage)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                                                                      Maybe CryptoKeyUsage
forall a. Maybe a
Nothing
js_CryptoKeyUsageEncrypt :: String
js_CryptoKeyUsageEncrypt = String
"encrypt"
js_CryptoKeyUsageDecrypt :: String
js_CryptoKeyUsageDecrypt = String
"decrypt"
js_CryptoKeyUsageSign :: String
js_CryptoKeyUsageSign = String
"sign"
js_CryptoKeyUsageVerify :: String
js_CryptoKeyUsageVerify = String
"verify"
js_CryptoKeyUsageDeriveKey :: String
js_CryptoKeyUsageDeriveKey = String
"deriveKey"
js_CryptoKeyUsageDeriveBits :: String
js_CryptoKeyUsageDeriveBits = String
"deriveBits"
js_CryptoKeyUsageWrapKey :: String
js_CryptoKeyUsageWrapKey = String
"wrapKey"
js_CryptoKeyUsageUnwrapKey :: String
js_CryptoKeyUsageUnwrapKey = String
"unwrapKey"
 
data KeyFormat = KeyFormatRaw
               | KeyFormatSpki
               | KeyFormatPkcs8
               | KeyFormatJwk
               deriving (Int -> KeyFormat -> ShowS
[KeyFormat] -> ShowS
KeyFormat -> String
(Int -> KeyFormat -> ShowS)
-> (KeyFormat -> String)
-> ([KeyFormat] -> ShowS)
-> Show KeyFormat
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [KeyFormat] -> ShowS
$cshowList :: [KeyFormat] -> ShowS
show :: KeyFormat -> String
$cshow :: KeyFormat -> String
showsPrec :: Int -> KeyFormat -> ShowS
$cshowsPrec :: Int -> KeyFormat -> ShowS
Show, ReadPrec [KeyFormat]
ReadPrec KeyFormat
Int -> ReadS KeyFormat
ReadS [KeyFormat]
(Int -> ReadS KeyFormat)
-> ReadS [KeyFormat]
-> ReadPrec KeyFormat
-> ReadPrec [KeyFormat]
-> Read KeyFormat
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [KeyFormat]
$creadListPrec :: ReadPrec [KeyFormat]
readPrec :: ReadPrec KeyFormat
$creadPrec :: ReadPrec KeyFormat
readList :: ReadS [KeyFormat]
$creadList :: ReadS [KeyFormat]
readsPrec :: Int -> ReadS KeyFormat
$creadsPrec :: Int -> ReadS KeyFormat
Read, KeyFormat -> KeyFormat -> Bool
(KeyFormat -> KeyFormat -> Bool)
-> (KeyFormat -> KeyFormat -> Bool) -> Eq KeyFormat
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: KeyFormat -> KeyFormat -> Bool
$c/= :: KeyFormat -> KeyFormat -> Bool
== :: KeyFormat -> KeyFormat -> Bool
$c== :: KeyFormat -> KeyFormat -> Bool
Eq, Eq KeyFormat
Eq KeyFormat
-> (KeyFormat -> KeyFormat -> Ordering)
-> (KeyFormat -> KeyFormat -> Bool)
-> (KeyFormat -> KeyFormat -> Bool)
-> (KeyFormat -> KeyFormat -> Bool)
-> (KeyFormat -> KeyFormat -> Bool)
-> (KeyFormat -> KeyFormat -> KeyFormat)
-> (KeyFormat -> KeyFormat -> KeyFormat)
-> Ord KeyFormat
KeyFormat -> KeyFormat -> Bool
KeyFormat -> KeyFormat -> Ordering
KeyFormat -> KeyFormat -> KeyFormat
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: KeyFormat -> KeyFormat -> KeyFormat
$cmin :: KeyFormat -> KeyFormat -> KeyFormat
max :: KeyFormat -> KeyFormat -> KeyFormat
$cmax :: KeyFormat -> KeyFormat -> KeyFormat
>= :: KeyFormat -> KeyFormat -> Bool
$c>= :: KeyFormat -> KeyFormat -> Bool
> :: KeyFormat -> KeyFormat -> Bool
$c> :: KeyFormat -> KeyFormat -> Bool
<= :: KeyFormat -> KeyFormat -> Bool
$c<= :: KeyFormat -> KeyFormat -> Bool
< :: KeyFormat -> KeyFormat -> Bool
$c< :: KeyFormat -> KeyFormat -> Bool
compare :: KeyFormat -> KeyFormat -> Ordering
$ccompare :: KeyFormat -> KeyFormat -> Ordering
$cp1Ord :: Eq KeyFormat
Ord, Typeable)
 
instance ToJSVal KeyFormat where
        toJSVal :: KeyFormat -> JSM JSVal
toJSVal KeyFormat
KeyFormatRaw = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_KeyFormatRaw
        toJSVal KeyFormat
KeyFormatSpki = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_KeyFormatSpki
        toJSVal KeyFormat
KeyFormatPkcs8 = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_KeyFormatPkcs8
        toJSVal KeyFormat
KeyFormatJwk = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_KeyFormatJwk
 
instance FromJSVal KeyFormat where
        fromJSVal :: JSVal -> JSM (Maybe KeyFormat)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_KeyFormatRaw JSM Bool
-> (Bool -> JSM (Maybe KeyFormat)) -> JSM (Maybe KeyFormat)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe KeyFormat -> JSM (Maybe KeyFormat)
forall (m :: * -> *) a. Monad m => a -> m a
return (KeyFormat -> Maybe KeyFormat
forall a. a -> Maybe a
Just KeyFormat
KeyFormatRaw)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_KeyFormatSpki JSM Bool
-> (Bool -> JSM (Maybe KeyFormat)) -> JSM (Maybe KeyFormat)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe KeyFormat -> JSM (Maybe KeyFormat)
forall (m :: * -> *) a. Monad m => a -> m a
return (KeyFormat -> Maybe KeyFormat
forall a. a -> Maybe a
Just KeyFormat
KeyFormatSpki)
                                 Bool
False
                                   -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_KeyFormatPkcs8 JSM Bool
-> (Bool -> JSM (Maybe KeyFormat)) -> JSM (Maybe KeyFormat)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                        \ Bool
r ->
                                          case Bool
r of
                                              Bool
True -> Maybe KeyFormat -> JSM (Maybe KeyFormat)
forall (m :: * -> *) a. Monad m => a -> m a
return (KeyFormat -> Maybe KeyFormat
forall a. a -> Maybe a
Just KeyFormat
KeyFormatPkcs8)
                                              Bool
False
                                                -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_KeyFormatJwk JSM Bool
-> (Bool -> JSM (Maybe KeyFormat)) -> JSM (Maybe KeyFormat)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                     \ Bool
r ->
                                                       case Bool
r of
                                                           Bool
True -> Maybe KeyFormat -> JSM (Maybe KeyFormat)
forall (m :: * -> *) a. Monad m => a -> m a
return (KeyFormat -> Maybe KeyFormat
forall a. a -> Maybe a
Just KeyFormat
KeyFormatJwk)
                                                           Bool
False -> Maybe KeyFormat -> JSM (Maybe KeyFormat)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe KeyFormat
forall a. Maybe a
Nothing
js_KeyFormatRaw :: String
js_KeyFormatRaw = String
"raw"
js_KeyFormatSpki :: String
js_KeyFormatSpki = String
"spki"
js_KeyFormatPkcs8 :: String
js_KeyFormatPkcs8 = String
"pkcs8"
js_KeyFormatJwk :: String
js_KeyFormatJwk = String
"jwk"
 
data FontFaceLoadStatus = FontFaceLoadStatusUnloaded
                        | FontFaceLoadStatusLoading
                        | FontFaceLoadStatusLoaded
                        | FontFaceLoadStatusError
                        deriving (Int -> FontFaceLoadStatus -> ShowS
[FontFaceLoadStatus] -> ShowS
FontFaceLoadStatus -> String
(Int -> FontFaceLoadStatus -> ShowS)
-> (FontFaceLoadStatus -> String)
-> ([FontFaceLoadStatus] -> ShowS)
-> Show FontFaceLoadStatus
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FontFaceLoadStatus] -> ShowS
$cshowList :: [FontFaceLoadStatus] -> ShowS
show :: FontFaceLoadStatus -> String
$cshow :: FontFaceLoadStatus -> String
showsPrec :: Int -> FontFaceLoadStatus -> ShowS
$cshowsPrec :: Int -> FontFaceLoadStatus -> ShowS
Show, ReadPrec [FontFaceLoadStatus]
ReadPrec FontFaceLoadStatus
Int -> ReadS FontFaceLoadStatus
ReadS [FontFaceLoadStatus]
(Int -> ReadS FontFaceLoadStatus)
-> ReadS [FontFaceLoadStatus]
-> ReadPrec FontFaceLoadStatus
-> ReadPrec [FontFaceLoadStatus]
-> Read FontFaceLoadStatus
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [FontFaceLoadStatus]
$creadListPrec :: ReadPrec [FontFaceLoadStatus]
readPrec :: ReadPrec FontFaceLoadStatus
$creadPrec :: ReadPrec FontFaceLoadStatus
readList :: ReadS [FontFaceLoadStatus]
$creadList :: ReadS [FontFaceLoadStatus]
readsPrec :: Int -> ReadS FontFaceLoadStatus
$creadsPrec :: Int -> ReadS FontFaceLoadStatus
Read, FontFaceLoadStatus -> FontFaceLoadStatus -> Bool
(FontFaceLoadStatus -> FontFaceLoadStatus -> Bool)
-> (FontFaceLoadStatus -> FontFaceLoadStatus -> Bool)
-> Eq FontFaceLoadStatus
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FontFaceLoadStatus -> FontFaceLoadStatus -> Bool
$c/= :: FontFaceLoadStatus -> FontFaceLoadStatus -> Bool
== :: FontFaceLoadStatus -> FontFaceLoadStatus -> Bool
$c== :: FontFaceLoadStatus -> FontFaceLoadStatus -> Bool
Eq, Eq FontFaceLoadStatus
Eq FontFaceLoadStatus
-> (FontFaceLoadStatus -> FontFaceLoadStatus -> Ordering)
-> (FontFaceLoadStatus -> FontFaceLoadStatus -> Bool)
-> (FontFaceLoadStatus -> FontFaceLoadStatus -> Bool)
-> (FontFaceLoadStatus -> FontFaceLoadStatus -> Bool)
-> (FontFaceLoadStatus -> FontFaceLoadStatus -> Bool)
-> (FontFaceLoadStatus -> FontFaceLoadStatus -> FontFaceLoadStatus)
-> (FontFaceLoadStatus -> FontFaceLoadStatus -> FontFaceLoadStatus)
-> Ord FontFaceLoadStatus
FontFaceLoadStatus -> FontFaceLoadStatus -> Bool
FontFaceLoadStatus -> FontFaceLoadStatus -> Ordering
FontFaceLoadStatus -> FontFaceLoadStatus -> FontFaceLoadStatus
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: FontFaceLoadStatus -> FontFaceLoadStatus -> FontFaceLoadStatus
$cmin :: FontFaceLoadStatus -> FontFaceLoadStatus -> FontFaceLoadStatus
max :: FontFaceLoadStatus -> FontFaceLoadStatus -> FontFaceLoadStatus
$cmax :: FontFaceLoadStatus -> FontFaceLoadStatus -> FontFaceLoadStatus
>= :: FontFaceLoadStatus -> FontFaceLoadStatus -> Bool
$c>= :: FontFaceLoadStatus -> FontFaceLoadStatus -> Bool
> :: FontFaceLoadStatus -> FontFaceLoadStatus -> Bool
$c> :: FontFaceLoadStatus -> FontFaceLoadStatus -> Bool
<= :: FontFaceLoadStatus -> FontFaceLoadStatus -> Bool
$c<= :: FontFaceLoadStatus -> FontFaceLoadStatus -> Bool
< :: FontFaceLoadStatus -> FontFaceLoadStatus -> Bool
$c< :: FontFaceLoadStatus -> FontFaceLoadStatus -> Bool
compare :: FontFaceLoadStatus -> FontFaceLoadStatus -> Ordering
$ccompare :: FontFaceLoadStatus -> FontFaceLoadStatus -> Ordering
$cp1Ord :: Eq FontFaceLoadStatus
Ord, Typeable)
 
instance ToJSVal FontFaceLoadStatus where
        toJSVal :: FontFaceLoadStatus -> JSM JSVal
toJSVal FontFaceLoadStatus
FontFaceLoadStatusUnloaded
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_FontFaceLoadStatusUnloaded
        toJSVal FontFaceLoadStatus
FontFaceLoadStatusLoading
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_FontFaceLoadStatusLoading
        toJSVal FontFaceLoadStatus
FontFaceLoadStatusLoaded
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_FontFaceLoadStatusLoaded
        toJSVal FontFaceLoadStatus
FontFaceLoadStatusError
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_FontFaceLoadStatusError
 
instance FromJSVal FontFaceLoadStatus where
        fromJSVal :: JSVal -> JSM (Maybe FontFaceLoadStatus)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_FontFaceLoadStatusUnloaded JSM Bool
-> (Bool -> JSM (Maybe FontFaceLoadStatus))
-> JSM (Maybe FontFaceLoadStatus)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe FontFaceLoadStatus -> JSM (Maybe FontFaceLoadStatus)
forall (m :: * -> *) a. Monad m => a -> m a
return (FontFaceLoadStatus -> Maybe FontFaceLoadStatus
forall a. a -> Maybe a
Just FontFaceLoadStatus
FontFaceLoadStatusUnloaded)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_FontFaceLoadStatusLoading JSM Bool
-> (Bool -> JSM (Maybe FontFaceLoadStatus))
-> JSM (Maybe FontFaceLoadStatus)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe FontFaceLoadStatus -> JSM (Maybe FontFaceLoadStatus)
forall (m :: * -> *) a. Monad m => a -> m a
return (FontFaceLoadStatus -> Maybe FontFaceLoadStatus
forall a. a -> Maybe a
Just FontFaceLoadStatus
FontFaceLoadStatusLoading)
                                 Bool
False
                                   -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_FontFaceLoadStatusLoaded JSM Bool
-> (Bool -> JSM (Maybe FontFaceLoadStatus))
-> JSM (Maybe FontFaceLoadStatus)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                        \ Bool
r ->
                                          case Bool
r of
                                              Bool
True -> Maybe FontFaceLoadStatus -> JSM (Maybe FontFaceLoadStatus)
forall (m :: * -> *) a. Monad m => a -> m a
return (FontFaceLoadStatus -> Maybe FontFaceLoadStatus
forall a. a -> Maybe a
Just FontFaceLoadStatus
FontFaceLoadStatusLoaded)
                                              Bool
False
                                                -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_FontFaceLoadStatusError JSM Bool
-> (Bool -> JSM (Maybe FontFaceLoadStatus))
-> JSM (Maybe FontFaceLoadStatus)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                     \ Bool
r ->
                                                       case Bool
r of
                                                           Bool
True
                                                             -> Maybe FontFaceLoadStatus -> JSM (Maybe FontFaceLoadStatus)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                  (FontFaceLoadStatus -> Maybe FontFaceLoadStatus
forall a. a -> Maybe a
Just FontFaceLoadStatus
FontFaceLoadStatusError)
                                                           Bool
False -> Maybe FontFaceLoadStatus -> JSM (Maybe FontFaceLoadStatus)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe FontFaceLoadStatus
forall a. Maybe a
Nothing
js_FontFaceLoadStatusUnloaded :: String
js_FontFaceLoadStatusUnloaded = String
"unloaded"
js_FontFaceLoadStatusLoading :: String
js_FontFaceLoadStatusLoading = String
"loading"
js_FontFaceLoadStatusLoaded :: String
js_FontFaceLoadStatusLoaded = String
"loaded"
js_FontFaceLoadStatusError :: String
js_FontFaceLoadStatusError = String
"error"
 
data FontFaceSetLoadStatus = FontFaceSetLoadStatusLoading
                           | FontFaceSetLoadStatusLoaded
                           deriving (Int -> FontFaceSetLoadStatus -> ShowS
[FontFaceSetLoadStatus] -> ShowS
FontFaceSetLoadStatus -> String
(Int -> FontFaceSetLoadStatus -> ShowS)
-> (FontFaceSetLoadStatus -> String)
-> ([FontFaceSetLoadStatus] -> ShowS)
-> Show FontFaceSetLoadStatus
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FontFaceSetLoadStatus] -> ShowS
$cshowList :: [FontFaceSetLoadStatus] -> ShowS
show :: FontFaceSetLoadStatus -> String
$cshow :: FontFaceSetLoadStatus -> String
showsPrec :: Int -> FontFaceSetLoadStatus -> ShowS
$cshowsPrec :: Int -> FontFaceSetLoadStatus -> ShowS
Show, ReadPrec [FontFaceSetLoadStatus]
ReadPrec FontFaceSetLoadStatus
Int -> ReadS FontFaceSetLoadStatus
ReadS [FontFaceSetLoadStatus]
(Int -> ReadS FontFaceSetLoadStatus)
-> ReadS [FontFaceSetLoadStatus]
-> ReadPrec FontFaceSetLoadStatus
-> ReadPrec [FontFaceSetLoadStatus]
-> Read FontFaceSetLoadStatus
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [FontFaceSetLoadStatus]
$creadListPrec :: ReadPrec [FontFaceSetLoadStatus]
readPrec :: ReadPrec FontFaceSetLoadStatus
$creadPrec :: ReadPrec FontFaceSetLoadStatus
readList :: ReadS [FontFaceSetLoadStatus]
$creadList :: ReadS [FontFaceSetLoadStatus]
readsPrec :: Int -> ReadS FontFaceSetLoadStatus
$creadsPrec :: Int -> ReadS FontFaceSetLoadStatus
Read, FontFaceSetLoadStatus -> FontFaceSetLoadStatus -> Bool
(FontFaceSetLoadStatus -> FontFaceSetLoadStatus -> Bool)
-> (FontFaceSetLoadStatus -> FontFaceSetLoadStatus -> Bool)
-> Eq FontFaceSetLoadStatus
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FontFaceSetLoadStatus -> FontFaceSetLoadStatus -> Bool
$c/= :: FontFaceSetLoadStatus -> FontFaceSetLoadStatus -> Bool
== :: FontFaceSetLoadStatus -> FontFaceSetLoadStatus -> Bool
$c== :: FontFaceSetLoadStatus -> FontFaceSetLoadStatus -> Bool
Eq, Eq FontFaceSetLoadStatus
Eq FontFaceSetLoadStatus
-> (FontFaceSetLoadStatus -> FontFaceSetLoadStatus -> Ordering)
-> (FontFaceSetLoadStatus -> FontFaceSetLoadStatus -> Bool)
-> (FontFaceSetLoadStatus -> FontFaceSetLoadStatus -> Bool)
-> (FontFaceSetLoadStatus -> FontFaceSetLoadStatus -> Bool)
-> (FontFaceSetLoadStatus -> FontFaceSetLoadStatus -> Bool)
-> (FontFaceSetLoadStatus
    -> FontFaceSetLoadStatus -> FontFaceSetLoadStatus)
-> (FontFaceSetLoadStatus
    -> FontFaceSetLoadStatus -> FontFaceSetLoadStatus)
-> Ord FontFaceSetLoadStatus
FontFaceSetLoadStatus -> FontFaceSetLoadStatus -> Bool
FontFaceSetLoadStatus -> FontFaceSetLoadStatus -> Ordering
FontFaceSetLoadStatus
-> FontFaceSetLoadStatus -> FontFaceSetLoadStatus
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: FontFaceSetLoadStatus
-> FontFaceSetLoadStatus -> FontFaceSetLoadStatus
$cmin :: FontFaceSetLoadStatus
-> FontFaceSetLoadStatus -> FontFaceSetLoadStatus
max :: FontFaceSetLoadStatus
-> FontFaceSetLoadStatus -> FontFaceSetLoadStatus
$cmax :: FontFaceSetLoadStatus
-> FontFaceSetLoadStatus -> FontFaceSetLoadStatus
>= :: FontFaceSetLoadStatus -> FontFaceSetLoadStatus -> Bool
$c>= :: FontFaceSetLoadStatus -> FontFaceSetLoadStatus -> Bool
> :: FontFaceSetLoadStatus -> FontFaceSetLoadStatus -> Bool
$c> :: FontFaceSetLoadStatus -> FontFaceSetLoadStatus -> Bool
<= :: FontFaceSetLoadStatus -> FontFaceSetLoadStatus -> Bool
$c<= :: FontFaceSetLoadStatus -> FontFaceSetLoadStatus -> Bool
< :: FontFaceSetLoadStatus -> FontFaceSetLoadStatus -> Bool
$c< :: FontFaceSetLoadStatus -> FontFaceSetLoadStatus -> Bool
compare :: FontFaceSetLoadStatus -> FontFaceSetLoadStatus -> Ordering
$ccompare :: FontFaceSetLoadStatus -> FontFaceSetLoadStatus -> Ordering
$cp1Ord :: Eq FontFaceSetLoadStatus
Ord, Typeable)
 
instance ToJSVal FontFaceSetLoadStatus where
        toJSVal :: FontFaceSetLoadStatus -> JSM JSVal
toJSVal FontFaceSetLoadStatus
FontFaceSetLoadStatusLoading
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_FontFaceSetLoadStatusLoading
        toJSVal FontFaceSetLoadStatus
FontFaceSetLoadStatusLoaded
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_FontFaceSetLoadStatusLoaded
 
instance FromJSVal FontFaceSetLoadStatus where
        fromJSVal :: JSVal -> JSM (Maybe FontFaceSetLoadStatus)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_FontFaceSetLoadStatusLoading JSM Bool
-> (Bool -> JSM (Maybe FontFaceSetLoadStatus))
-> JSM (Maybe FontFaceSetLoadStatus)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe FontFaceSetLoadStatus -> JSM (Maybe FontFaceSetLoadStatus)
forall (m :: * -> *) a. Monad m => a -> m a
return (FontFaceSetLoadStatus -> Maybe FontFaceSetLoadStatus
forall a. a -> Maybe a
Just FontFaceSetLoadStatus
FontFaceSetLoadStatusLoading)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_FontFaceSetLoadStatusLoaded JSM Bool
-> (Bool -> JSM (Maybe FontFaceSetLoadStatus))
-> JSM (Maybe FontFaceSetLoadStatus)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe FontFaceSetLoadStatus -> JSM (Maybe FontFaceSetLoadStatus)
forall (m :: * -> *) a. Monad m => a -> m a
return (FontFaceSetLoadStatus -> Maybe FontFaceSetLoadStatus
forall a. a -> Maybe a
Just FontFaceSetLoadStatus
FontFaceSetLoadStatusLoaded)
                                 Bool
False -> Maybe FontFaceSetLoadStatus -> JSM (Maybe FontFaceSetLoadStatus)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe FontFaceSetLoadStatus
forall a. Maybe a
Nothing
js_FontFaceSetLoadStatusLoading :: String
js_FontFaceSetLoadStatusLoading = String
"loading"
js_FontFaceSetLoadStatusLoaded :: String
js_FontFaceSetLoadStatusLoaded = String
"loaded"
 
data VisibilityState = VisibilityStateHidden
                     | VisibilityStateVisible
                     | VisibilityStatePrerender
                     deriving (Int -> VisibilityState -> ShowS
[VisibilityState] -> ShowS
VisibilityState -> String
(Int -> VisibilityState -> ShowS)
-> (VisibilityState -> String)
-> ([VisibilityState] -> ShowS)
-> Show VisibilityState
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VisibilityState] -> ShowS
$cshowList :: [VisibilityState] -> ShowS
show :: VisibilityState -> String
$cshow :: VisibilityState -> String
showsPrec :: Int -> VisibilityState -> ShowS
$cshowsPrec :: Int -> VisibilityState -> ShowS
Show, ReadPrec [VisibilityState]
ReadPrec VisibilityState
Int -> ReadS VisibilityState
ReadS [VisibilityState]
(Int -> ReadS VisibilityState)
-> ReadS [VisibilityState]
-> ReadPrec VisibilityState
-> ReadPrec [VisibilityState]
-> Read VisibilityState
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [VisibilityState]
$creadListPrec :: ReadPrec [VisibilityState]
readPrec :: ReadPrec VisibilityState
$creadPrec :: ReadPrec VisibilityState
readList :: ReadS [VisibilityState]
$creadList :: ReadS [VisibilityState]
readsPrec :: Int -> ReadS VisibilityState
$creadsPrec :: Int -> ReadS VisibilityState
Read, VisibilityState -> VisibilityState -> Bool
(VisibilityState -> VisibilityState -> Bool)
-> (VisibilityState -> VisibilityState -> Bool)
-> Eq VisibilityState
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VisibilityState -> VisibilityState -> Bool
$c/= :: VisibilityState -> VisibilityState -> Bool
== :: VisibilityState -> VisibilityState -> Bool
$c== :: VisibilityState -> VisibilityState -> Bool
Eq, Eq VisibilityState
Eq VisibilityState
-> (VisibilityState -> VisibilityState -> Ordering)
-> (VisibilityState -> VisibilityState -> Bool)
-> (VisibilityState -> VisibilityState -> Bool)
-> (VisibilityState -> VisibilityState -> Bool)
-> (VisibilityState -> VisibilityState -> Bool)
-> (VisibilityState -> VisibilityState -> VisibilityState)
-> (VisibilityState -> VisibilityState -> VisibilityState)
-> Ord VisibilityState
VisibilityState -> VisibilityState -> Bool
VisibilityState -> VisibilityState -> Ordering
VisibilityState -> VisibilityState -> VisibilityState
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: VisibilityState -> VisibilityState -> VisibilityState
$cmin :: VisibilityState -> VisibilityState -> VisibilityState
max :: VisibilityState -> VisibilityState -> VisibilityState
$cmax :: VisibilityState -> VisibilityState -> VisibilityState
>= :: VisibilityState -> VisibilityState -> Bool
$c>= :: VisibilityState -> VisibilityState -> Bool
> :: VisibilityState -> VisibilityState -> Bool
$c> :: VisibilityState -> VisibilityState -> Bool
<= :: VisibilityState -> VisibilityState -> Bool
$c<= :: VisibilityState -> VisibilityState -> Bool
< :: VisibilityState -> VisibilityState -> Bool
$c< :: VisibilityState -> VisibilityState -> Bool
compare :: VisibilityState -> VisibilityState -> Ordering
$ccompare :: VisibilityState -> VisibilityState -> Ordering
$cp1Ord :: Eq VisibilityState
Ord, Typeable)
 
instance ToJSVal VisibilityState where
        toJSVal :: VisibilityState -> JSM JSVal
toJSVal VisibilityState
VisibilityStateHidden = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_VisibilityStateHidden
        toJSVal VisibilityState
VisibilityStateVisible = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_VisibilityStateVisible
        toJSVal VisibilityState
VisibilityStatePrerender
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_VisibilityStatePrerender
 
instance FromJSVal VisibilityState where
        fromJSVal :: JSVal -> JSM (Maybe VisibilityState)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_VisibilityStateHidden JSM Bool
-> (Bool -> JSM (Maybe VisibilityState))
-> JSM (Maybe VisibilityState)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe VisibilityState -> JSM (Maybe VisibilityState)
forall (m :: * -> *) a. Monad m => a -> m a
return (VisibilityState -> Maybe VisibilityState
forall a. a -> Maybe a
Just VisibilityState
VisibilityStateHidden)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_VisibilityStateVisible JSM Bool
-> (Bool -> JSM (Maybe VisibilityState))
-> JSM (Maybe VisibilityState)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe VisibilityState -> JSM (Maybe VisibilityState)
forall (m :: * -> *) a. Monad m => a -> m a
return (VisibilityState -> Maybe VisibilityState
forall a. a -> Maybe a
Just VisibilityState
VisibilityStateVisible)
                                 Bool
False
                                   -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_VisibilityStatePrerender JSM Bool
-> (Bool -> JSM (Maybe VisibilityState))
-> JSM (Maybe VisibilityState)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                        \ Bool
r ->
                                          case Bool
r of
                                              Bool
True -> Maybe VisibilityState -> JSM (Maybe VisibilityState)
forall (m :: * -> *) a. Monad m => a -> m a
return (VisibilityState -> Maybe VisibilityState
forall a. a -> Maybe a
Just VisibilityState
VisibilityStatePrerender)
                                              Bool
False -> Maybe VisibilityState -> JSM (Maybe VisibilityState)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe VisibilityState
forall a. Maybe a
Nothing
js_VisibilityStateHidden :: String
js_VisibilityStateHidden = String
"hidden"
js_VisibilityStateVisible :: String
js_VisibilityStateVisible = String
"visible"
js_VisibilityStatePrerender :: String
js_VisibilityStatePrerender = String
"prerender"
 
data DocumentReadyState = DocumentReadyStateLoading
                        | DocumentReadyStateInteractive
                        | DocumentReadyStateComplete
                        deriving (Int -> DocumentReadyState -> ShowS
[DocumentReadyState] -> ShowS
DocumentReadyState -> String
(Int -> DocumentReadyState -> ShowS)
-> (DocumentReadyState -> String)
-> ([DocumentReadyState] -> ShowS)
-> Show DocumentReadyState
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DocumentReadyState] -> ShowS
$cshowList :: [DocumentReadyState] -> ShowS
show :: DocumentReadyState -> String
$cshow :: DocumentReadyState -> String
showsPrec :: Int -> DocumentReadyState -> ShowS
$cshowsPrec :: Int -> DocumentReadyState -> ShowS
Show, ReadPrec [DocumentReadyState]
ReadPrec DocumentReadyState
Int -> ReadS DocumentReadyState
ReadS [DocumentReadyState]
(Int -> ReadS DocumentReadyState)
-> ReadS [DocumentReadyState]
-> ReadPrec DocumentReadyState
-> ReadPrec [DocumentReadyState]
-> Read DocumentReadyState
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DocumentReadyState]
$creadListPrec :: ReadPrec [DocumentReadyState]
readPrec :: ReadPrec DocumentReadyState
$creadPrec :: ReadPrec DocumentReadyState
readList :: ReadS [DocumentReadyState]
$creadList :: ReadS [DocumentReadyState]
readsPrec :: Int -> ReadS DocumentReadyState
$creadsPrec :: Int -> ReadS DocumentReadyState
Read, DocumentReadyState -> DocumentReadyState -> Bool
(DocumentReadyState -> DocumentReadyState -> Bool)
-> (DocumentReadyState -> DocumentReadyState -> Bool)
-> Eq DocumentReadyState
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DocumentReadyState -> DocumentReadyState -> Bool
$c/= :: DocumentReadyState -> DocumentReadyState -> Bool
== :: DocumentReadyState -> DocumentReadyState -> Bool
$c== :: DocumentReadyState -> DocumentReadyState -> Bool
Eq, Eq DocumentReadyState
Eq DocumentReadyState
-> (DocumentReadyState -> DocumentReadyState -> Ordering)
-> (DocumentReadyState -> DocumentReadyState -> Bool)
-> (DocumentReadyState -> DocumentReadyState -> Bool)
-> (DocumentReadyState -> DocumentReadyState -> Bool)
-> (DocumentReadyState -> DocumentReadyState -> Bool)
-> (DocumentReadyState -> DocumentReadyState -> DocumentReadyState)
-> (DocumentReadyState -> DocumentReadyState -> DocumentReadyState)
-> Ord DocumentReadyState
DocumentReadyState -> DocumentReadyState -> Bool
DocumentReadyState -> DocumentReadyState -> Ordering
DocumentReadyState -> DocumentReadyState -> DocumentReadyState
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: DocumentReadyState -> DocumentReadyState -> DocumentReadyState
$cmin :: DocumentReadyState -> DocumentReadyState -> DocumentReadyState
max :: DocumentReadyState -> DocumentReadyState -> DocumentReadyState
$cmax :: DocumentReadyState -> DocumentReadyState -> DocumentReadyState
>= :: DocumentReadyState -> DocumentReadyState -> Bool
$c>= :: DocumentReadyState -> DocumentReadyState -> Bool
> :: DocumentReadyState -> DocumentReadyState -> Bool
$c> :: DocumentReadyState -> DocumentReadyState -> Bool
<= :: DocumentReadyState -> DocumentReadyState -> Bool
$c<= :: DocumentReadyState -> DocumentReadyState -> Bool
< :: DocumentReadyState -> DocumentReadyState -> Bool
$c< :: DocumentReadyState -> DocumentReadyState -> Bool
compare :: DocumentReadyState -> DocumentReadyState -> Ordering
$ccompare :: DocumentReadyState -> DocumentReadyState -> Ordering
$cp1Ord :: Eq DocumentReadyState
Ord, Typeable)
 
instance ToJSVal DocumentReadyState where
        toJSVal :: DocumentReadyState -> JSM JSVal
toJSVal DocumentReadyState
DocumentReadyStateLoading
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_DocumentReadyStateLoading
        toJSVal DocumentReadyState
DocumentReadyStateInteractive
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_DocumentReadyStateInteractive
        toJSVal DocumentReadyState
DocumentReadyStateComplete
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_DocumentReadyStateComplete
 
instance FromJSVal DocumentReadyState where
        fromJSVal :: JSVal -> JSM (Maybe DocumentReadyState)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_DocumentReadyStateLoading JSM Bool
-> (Bool -> JSM (Maybe DocumentReadyState))
-> JSM (Maybe DocumentReadyState)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe DocumentReadyState -> JSM (Maybe DocumentReadyState)
forall (m :: * -> *) a. Monad m => a -> m a
return (DocumentReadyState -> Maybe DocumentReadyState
forall a. a -> Maybe a
Just DocumentReadyState
DocumentReadyStateLoading)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_DocumentReadyStateInteractive JSM Bool
-> (Bool -> JSM (Maybe DocumentReadyState))
-> JSM (Maybe DocumentReadyState)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe DocumentReadyState -> JSM (Maybe DocumentReadyState)
forall (m :: * -> *) a. Monad m => a -> m a
return (DocumentReadyState -> Maybe DocumentReadyState
forall a. a -> Maybe a
Just DocumentReadyState
DocumentReadyStateInteractive)
                                 Bool
False
                                   -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_DocumentReadyStateComplete JSM Bool
-> (Bool -> JSM (Maybe DocumentReadyState))
-> JSM (Maybe DocumentReadyState)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                        \ Bool
r ->
                                          case Bool
r of
                                              Bool
True -> Maybe DocumentReadyState -> JSM (Maybe DocumentReadyState)
forall (m :: * -> *) a. Monad m => a -> m a
return (DocumentReadyState -> Maybe DocumentReadyState
forall a. a -> Maybe a
Just DocumentReadyState
DocumentReadyStateComplete)
                                              Bool
False -> Maybe DocumentReadyState -> JSM (Maybe DocumentReadyState)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe DocumentReadyState
forall a. Maybe a
Nothing
js_DocumentReadyStateLoading :: String
js_DocumentReadyStateLoading = String
"loading"
js_DocumentReadyStateInteractive :: String
js_DocumentReadyStateInteractive = String
"interactive"
js_DocumentReadyStateComplete :: String
js_DocumentReadyStateComplete = String
"complete"
 
data ShadowRootMode = ShadowRootModeUserAgent
                    | ShadowRootModeClosed
                    | ShadowRootModeOpen
                    deriving (Int -> ShadowRootMode -> ShowS
[ShadowRootMode] -> ShowS
ShadowRootMode -> String
(Int -> ShadowRootMode -> ShowS)
-> (ShadowRootMode -> String)
-> ([ShadowRootMode] -> ShowS)
-> Show ShadowRootMode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ShadowRootMode] -> ShowS
$cshowList :: [ShadowRootMode] -> ShowS
show :: ShadowRootMode -> String
$cshow :: ShadowRootMode -> String
showsPrec :: Int -> ShadowRootMode -> ShowS
$cshowsPrec :: Int -> ShadowRootMode -> ShowS
Show, ReadPrec [ShadowRootMode]
ReadPrec ShadowRootMode
Int -> ReadS ShadowRootMode
ReadS [ShadowRootMode]
(Int -> ReadS ShadowRootMode)
-> ReadS [ShadowRootMode]
-> ReadPrec ShadowRootMode
-> ReadPrec [ShadowRootMode]
-> Read ShadowRootMode
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ShadowRootMode]
$creadListPrec :: ReadPrec [ShadowRootMode]
readPrec :: ReadPrec ShadowRootMode
$creadPrec :: ReadPrec ShadowRootMode
readList :: ReadS [ShadowRootMode]
$creadList :: ReadS [ShadowRootMode]
readsPrec :: Int -> ReadS ShadowRootMode
$creadsPrec :: Int -> ReadS ShadowRootMode
Read, ShadowRootMode -> ShadowRootMode -> Bool
(ShadowRootMode -> ShadowRootMode -> Bool)
-> (ShadowRootMode -> ShadowRootMode -> Bool) -> Eq ShadowRootMode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ShadowRootMode -> ShadowRootMode -> Bool
$c/= :: ShadowRootMode -> ShadowRootMode -> Bool
== :: ShadowRootMode -> ShadowRootMode -> Bool
$c== :: ShadowRootMode -> ShadowRootMode -> Bool
Eq, Eq ShadowRootMode
Eq ShadowRootMode
-> (ShadowRootMode -> ShadowRootMode -> Ordering)
-> (ShadowRootMode -> ShadowRootMode -> Bool)
-> (ShadowRootMode -> ShadowRootMode -> Bool)
-> (ShadowRootMode -> ShadowRootMode -> Bool)
-> (ShadowRootMode -> ShadowRootMode -> Bool)
-> (ShadowRootMode -> ShadowRootMode -> ShadowRootMode)
-> (ShadowRootMode -> ShadowRootMode -> ShadowRootMode)
-> Ord ShadowRootMode
ShadowRootMode -> ShadowRootMode -> Bool
ShadowRootMode -> ShadowRootMode -> Ordering
ShadowRootMode -> ShadowRootMode -> ShadowRootMode
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ShadowRootMode -> ShadowRootMode -> ShadowRootMode
$cmin :: ShadowRootMode -> ShadowRootMode -> ShadowRootMode
max :: ShadowRootMode -> ShadowRootMode -> ShadowRootMode
$cmax :: ShadowRootMode -> ShadowRootMode -> ShadowRootMode
>= :: ShadowRootMode -> ShadowRootMode -> Bool
$c>= :: ShadowRootMode -> ShadowRootMode -> Bool
> :: ShadowRootMode -> ShadowRootMode -> Bool
$c> :: ShadowRootMode -> ShadowRootMode -> Bool
<= :: ShadowRootMode -> ShadowRootMode -> Bool
$c<= :: ShadowRootMode -> ShadowRootMode -> Bool
< :: ShadowRootMode -> ShadowRootMode -> Bool
$c< :: ShadowRootMode -> ShadowRootMode -> Bool
compare :: ShadowRootMode -> ShadowRootMode -> Ordering
$ccompare :: ShadowRootMode -> ShadowRootMode -> Ordering
$cp1Ord :: Eq ShadowRootMode
Ord, Typeable)
 
instance ToJSVal ShadowRootMode where
        toJSVal :: ShadowRootMode -> JSM JSVal
toJSVal ShadowRootMode
ShadowRootModeUserAgent
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_ShadowRootModeUserAgent
        toJSVal ShadowRootMode
ShadowRootModeClosed = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_ShadowRootModeClosed
        toJSVal ShadowRootMode
ShadowRootModeOpen = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_ShadowRootModeOpen
 
instance FromJSVal ShadowRootMode where
        fromJSVal :: JSVal -> JSM (Maybe ShadowRootMode)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_ShadowRootModeUserAgent JSM Bool
-> (Bool -> JSM (Maybe ShadowRootMode))
-> JSM (Maybe ShadowRootMode)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe ShadowRootMode -> JSM (Maybe ShadowRootMode)
forall (m :: * -> *) a. Monad m => a -> m a
return (ShadowRootMode -> Maybe ShadowRootMode
forall a. a -> Maybe a
Just ShadowRootMode
ShadowRootModeUserAgent)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_ShadowRootModeClosed JSM Bool
-> (Bool -> JSM (Maybe ShadowRootMode))
-> JSM (Maybe ShadowRootMode)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe ShadowRootMode -> JSM (Maybe ShadowRootMode)
forall (m :: * -> *) a. Monad m => a -> m a
return (ShadowRootMode -> Maybe ShadowRootMode
forall a. a -> Maybe a
Just ShadowRootMode
ShadowRootModeClosed)
                                 Bool
False
                                   -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_ShadowRootModeOpen JSM Bool
-> (Bool -> JSM (Maybe ShadowRootMode))
-> JSM (Maybe ShadowRootMode)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                        \ Bool
r ->
                                          case Bool
r of
                                              Bool
True -> Maybe ShadowRootMode -> JSM (Maybe ShadowRootMode)
forall (m :: * -> *) a. Monad m => a -> m a
return (ShadowRootMode -> Maybe ShadowRootMode
forall a. a -> Maybe a
Just ShadowRootMode
ShadowRootModeOpen)
                                              Bool
False -> Maybe ShadowRootMode -> JSM (Maybe ShadowRootMode)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ShadowRootMode
forall a. Maybe a
Nothing
js_ShadowRootModeUserAgent :: String
js_ShadowRootModeUserAgent = String
"user-agent"
js_ShadowRootModeClosed :: String
js_ShadowRootModeClosed = String
"closed"
js_ShadowRootModeOpen :: String
js_ShadowRootModeOpen = String
"open"
 
data BlobLineEndings = BlobLineEndingsTransparent
                     | BlobLineEndingsNative
                     deriving (Int -> BlobLineEndings -> ShowS
[BlobLineEndings] -> ShowS
BlobLineEndings -> String
(Int -> BlobLineEndings -> ShowS)
-> (BlobLineEndings -> String)
-> ([BlobLineEndings] -> ShowS)
-> Show BlobLineEndings
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BlobLineEndings] -> ShowS
$cshowList :: [BlobLineEndings] -> ShowS
show :: BlobLineEndings -> String
$cshow :: BlobLineEndings -> String
showsPrec :: Int -> BlobLineEndings -> ShowS
$cshowsPrec :: Int -> BlobLineEndings -> ShowS
Show, ReadPrec [BlobLineEndings]
ReadPrec BlobLineEndings
Int -> ReadS BlobLineEndings
ReadS [BlobLineEndings]
(Int -> ReadS BlobLineEndings)
-> ReadS [BlobLineEndings]
-> ReadPrec BlobLineEndings
-> ReadPrec [BlobLineEndings]
-> Read BlobLineEndings
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [BlobLineEndings]
$creadListPrec :: ReadPrec [BlobLineEndings]
readPrec :: ReadPrec BlobLineEndings
$creadPrec :: ReadPrec BlobLineEndings
readList :: ReadS [BlobLineEndings]
$creadList :: ReadS [BlobLineEndings]
readsPrec :: Int -> ReadS BlobLineEndings
$creadsPrec :: Int -> ReadS BlobLineEndings
Read, BlobLineEndings -> BlobLineEndings -> Bool
(BlobLineEndings -> BlobLineEndings -> Bool)
-> (BlobLineEndings -> BlobLineEndings -> Bool)
-> Eq BlobLineEndings
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BlobLineEndings -> BlobLineEndings -> Bool
$c/= :: BlobLineEndings -> BlobLineEndings -> Bool
== :: BlobLineEndings -> BlobLineEndings -> Bool
$c== :: BlobLineEndings -> BlobLineEndings -> Bool
Eq, Eq BlobLineEndings
Eq BlobLineEndings
-> (BlobLineEndings -> BlobLineEndings -> Ordering)
-> (BlobLineEndings -> BlobLineEndings -> Bool)
-> (BlobLineEndings -> BlobLineEndings -> Bool)
-> (BlobLineEndings -> BlobLineEndings -> Bool)
-> (BlobLineEndings -> BlobLineEndings -> Bool)
-> (BlobLineEndings -> BlobLineEndings -> BlobLineEndings)
-> (BlobLineEndings -> BlobLineEndings -> BlobLineEndings)
-> Ord BlobLineEndings
BlobLineEndings -> BlobLineEndings -> Bool
BlobLineEndings -> BlobLineEndings -> Ordering
BlobLineEndings -> BlobLineEndings -> BlobLineEndings
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: BlobLineEndings -> BlobLineEndings -> BlobLineEndings
$cmin :: BlobLineEndings -> BlobLineEndings -> BlobLineEndings
max :: BlobLineEndings -> BlobLineEndings -> BlobLineEndings
$cmax :: BlobLineEndings -> BlobLineEndings -> BlobLineEndings
>= :: BlobLineEndings -> BlobLineEndings -> Bool
$c>= :: BlobLineEndings -> BlobLineEndings -> Bool
> :: BlobLineEndings -> BlobLineEndings -> Bool
$c> :: BlobLineEndings -> BlobLineEndings -> Bool
<= :: BlobLineEndings -> BlobLineEndings -> Bool
$c<= :: BlobLineEndings -> BlobLineEndings -> Bool
< :: BlobLineEndings -> BlobLineEndings -> Bool
$c< :: BlobLineEndings -> BlobLineEndings -> Bool
compare :: BlobLineEndings -> BlobLineEndings -> Ordering
$ccompare :: BlobLineEndings -> BlobLineEndings -> Ordering
$cp1Ord :: Eq BlobLineEndings
Ord, Typeable)
 
instance ToJSVal BlobLineEndings where
        toJSVal :: BlobLineEndings -> JSM JSVal
toJSVal BlobLineEndings
BlobLineEndingsTransparent
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_BlobLineEndingsTransparent
        toJSVal BlobLineEndings
BlobLineEndingsNative = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_BlobLineEndingsNative
 
instance FromJSVal BlobLineEndings where
        fromJSVal :: JSVal -> JSM (Maybe BlobLineEndings)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_BlobLineEndingsTransparent JSM Bool
-> (Bool -> JSM (Maybe BlobLineEndings))
-> JSM (Maybe BlobLineEndings)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe BlobLineEndings -> JSM (Maybe BlobLineEndings)
forall (m :: * -> *) a. Monad m => a -> m a
return (BlobLineEndings -> Maybe BlobLineEndings
forall a. a -> Maybe a
Just BlobLineEndings
BlobLineEndingsTransparent)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_BlobLineEndingsNative JSM Bool
-> (Bool -> JSM (Maybe BlobLineEndings))
-> JSM (Maybe BlobLineEndings)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe BlobLineEndings -> JSM (Maybe BlobLineEndings)
forall (m :: * -> *) a. Monad m => a -> m a
return (BlobLineEndings -> Maybe BlobLineEndings
forall a. a -> Maybe a
Just BlobLineEndings
BlobLineEndingsNative)
                                 Bool
False -> Maybe BlobLineEndings -> JSM (Maybe BlobLineEndings)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe BlobLineEndings
forall a. Maybe a
Nothing
js_BlobLineEndingsTransparent :: String
js_BlobLineEndingsTransparent = String
"transparent"
js_BlobLineEndingsNative :: String
js_BlobLineEndingsNative = String
"native"
 
data ImageSmoothingQuality = ImageSmoothingQualityLow
                           | ImageSmoothingQualityMedium
                           | ImageSmoothingQualityHigh
                           deriving (Int -> ImageSmoothingQuality -> ShowS
[ImageSmoothingQuality] -> ShowS
ImageSmoothingQuality -> String
(Int -> ImageSmoothingQuality -> ShowS)
-> (ImageSmoothingQuality -> String)
-> ([ImageSmoothingQuality] -> ShowS)
-> Show ImageSmoothingQuality
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ImageSmoothingQuality] -> ShowS
$cshowList :: [ImageSmoothingQuality] -> ShowS
show :: ImageSmoothingQuality -> String
$cshow :: ImageSmoothingQuality -> String
showsPrec :: Int -> ImageSmoothingQuality -> ShowS
$cshowsPrec :: Int -> ImageSmoothingQuality -> ShowS
Show, ReadPrec [ImageSmoothingQuality]
ReadPrec ImageSmoothingQuality
Int -> ReadS ImageSmoothingQuality
ReadS [ImageSmoothingQuality]
(Int -> ReadS ImageSmoothingQuality)
-> ReadS [ImageSmoothingQuality]
-> ReadPrec ImageSmoothingQuality
-> ReadPrec [ImageSmoothingQuality]
-> Read ImageSmoothingQuality
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ImageSmoothingQuality]
$creadListPrec :: ReadPrec [ImageSmoothingQuality]
readPrec :: ReadPrec ImageSmoothingQuality
$creadPrec :: ReadPrec ImageSmoothingQuality
readList :: ReadS [ImageSmoothingQuality]
$creadList :: ReadS [ImageSmoothingQuality]
readsPrec :: Int -> ReadS ImageSmoothingQuality
$creadsPrec :: Int -> ReadS ImageSmoothingQuality
Read, ImageSmoothingQuality -> ImageSmoothingQuality -> Bool
(ImageSmoothingQuality -> ImageSmoothingQuality -> Bool)
-> (ImageSmoothingQuality -> ImageSmoothingQuality -> Bool)
-> Eq ImageSmoothingQuality
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ImageSmoothingQuality -> ImageSmoothingQuality -> Bool
$c/= :: ImageSmoothingQuality -> ImageSmoothingQuality -> Bool
== :: ImageSmoothingQuality -> ImageSmoothingQuality -> Bool
$c== :: ImageSmoothingQuality -> ImageSmoothingQuality -> Bool
Eq, Eq ImageSmoothingQuality
Eq ImageSmoothingQuality
-> (ImageSmoothingQuality -> ImageSmoothingQuality -> Ordering)
-> (ImageSmoothingQuality -> ImageSmoothingQuality -> Bool)
-> (ImageSmoothingQuality -> ImageSmoothingQuality -> Bool)
-> (ImageSmoothingQuality -> ImageSmoothingQuality -> Bool)
-> (ImageSmoothingQuality -> ImageSmoothingQuality -> Bool)
-> (ImageSmoothingQuality
    -> ImageSmoothingQuality -> ImageSmoothingQuality)
-> (ImageSmoothingQuality
    -> ImageSmoothingQuality -> ImageSmoothingQuality)
-> Ord ImageSmoothingQuality
ImageSmoothingQuality -> ImageSmoothingQuality -> Bool
ImageSmoothingQuality -> ImageSmoothingQuality -> Ordering
ImageSmoothingQuality
-> ImageSmoothingQuality -> ImageSmoothingQuality
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ImageSmoothingQuality
-> ImageSmoothingQuality -> ImageSmoothingQuality
$cmin :: ImageSmoothingQuality
-> ImageSmoothingQuality -> ImageSmoothingQuality
max :: ImageSmoothingQuality
-> ImageSmoothingQuality -> ImageSmoothingQuality
$cmax :: ImageSmoothingQuality
-> ImageSmoothingQuality -> ImageSmoothingQuality
>= :: ImageSmoothingQuality -> ImageSmoothingQuality -> Bool
$c>= :: ImageSmoothingQuality -> ImageSmoothingQuality -> Bool
> :: ImageSmoothingQuality -> ImageSmoothingQuality -> Bool
$c> :: ImageSmoothingQuality -> ImageSmoothingQuality -> Bool
<= :: ImageSmoothingQuality -> ImageSmoothingQuality -> Bool
$c<= :: ImageSmoothingQuality -> ImageSmoothingQuality -> Bool
< :: ImageSmoothingQuality -> ImageSmoothingQuality -> Bool
$c< :: ImageSmoothingQuality -> ImageSmoothingQuality -> Bool
compare :: ImageSmoothingQuality -> ImageSmoothingQuality -> Ordering
$ccompare :: ImageSmoothingQuality -> ImageSmoothingQuality -> Ordering
$cp1Ord :: Eq ImageSmoothingQuality
Ord, Typeable)
 
instance ToJSVal ImageSmoothingQuality where
        toJSVal :: ImageSmoothingQuality -> JSM JSVal
toJSVal ImageSmoothingQuality
ImageSmoothingQualityLow
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_ImageSmoothingQualityLow
        toJSVal ImageSmoothingQuality
ImageSmoothingQualityMedium
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_ImageSmoothingQualityMedium
        toJSVal ImageSmoothingQuality
ImageSmoothingQualityHigh
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_ImageSmoothingQualityHigh
 
instance FromJSVal ImageSmoothingQuality where
        fromJSVal :: JSVal -> JSM (Maybe ImageSmoothingQuality)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_ImageSmoothingQualityLow JSM Bool
-> (Bool -> JSM (Maybe ImageSmoothingQuality))
-> JSM (Maybe ImageSmoothingQuality)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe ImageSmoothingQuality -> JSM (Maybe ImageSmoothingQuality)
forall (m :: * -> *) a. Monad m => a -> m a
return (ImageSmoothingQuality -> Maybe ImageSmoothingQuality
forall a. a -> Maybe a
Just ImageSmoothingQuality
ImageSmoothingQualityLow)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_ImageSmoothingQualityMedium JSM Bool
-> (Bool -> JSM (Maybe ImageSmoothingQuality))
-> JSM (Maybe ImageSmoothingQuality)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe ImageSmoothingQuality -> JSM (Maybe ImageSmoothingQuality)
forall (m :: * -> *) a. Monad m => a -> m a
return (ImageSmoothingQuality -> Maybe ImageSmoothingQuality
forall a. a -> Maybe a
Just ImageSmoothingQuality
ImageSmoothingQualityMedium)
                                 Bool
False
                                   -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_ImageSmoothingQualityHigh JSM Bool
-> (Bool -> JSM (Maybe ImageSmoothingQuality))
-> JSM (Maybe ImageSmoothingQuality)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                        \ Bool
r ->
                                          case Bool
r of
                                              Bool
True -> Maybe ImageSmoothingQuality -> JSM (Maybe ImageSmoothingQuality)
forall (m :: * -> *) a. Monad m => a -> m a
return (ImageSmoothingQuality -> Maybe ImageSmoothingQuality
forall a. a -> Maybe a
Just ImageSmoothingQuality
ImageSmoothingQualityHigh)
                                              Bool
False -> Maybe ImageSmoothingQuality -> JSM (Maybe ImageSmoothingQuality)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ImageSmoothingQuality
forall a. Maybe a
Nothing
js_ImageSmoothingQualityLow :: String
js_ImageSmoothingQualityLow = String
"low"
js_ImageSmoothingQualityMedium :: String
js_ImageSmoothingQualityMedium = String
"medium"
js_ImageSmoothingQualityHigh :: String
js_ImageSmoothingQualityHigh = String
"high"
 
data CanvasWindingRule = CanvasWindingRuleNonzero
                       | CanvasWindingRuleEvenodd
                       deriving (Int -> CanvasWindingRule -> ShowS
[CanvasWindingRule] -> ShowS
CanvasWindingRule -> String
(Int -> CanvasWindingRule -> ShowS)
-> (CanvasWindingRule -> String)
-> ([CanvasWindingRule] -> ShowS)
-> Show CanvasWindingRule
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CanvasWindingRule] -> ShowS
$cshowList :: [CanvasWindingRule] -> ShowS
show :: CanvasWindingRule -> String
$cshow :: CanvasWindingRule -> String
showsPrec :: Int -> CanvasWindingRule -> ShowS
$cshowsPrec :: Int -> CanvasWindingRule -> ShowS
Show, ReadPrec [CanvasWindingRule]
ReadPrec CanvasWindingRule
Int -> ReadS CanvasWindingRule
ReadS [CanvasWindingRule]
(Int -> ReadS CanvasWindingRule)
-> ReadS [CanvasWindingRule]
-> ReadPrec CanvasWindingRule
-> ReadPrec [CanvasWindingRule]
-> Read CanvasWindingRule
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CanvasWindingRule]
$creadListPrec :: ReadPrec [CanvasWindingRule]
readPrec :: ReadPrec CanvasWindingRule
$creadPrec :: ReadPrec CanvasWindingRule
readList :: ReadS [CanvasWindingRule]
$creadList :: ReadS [CanvasWindingRule]
readsPrec :: Int -> ReadS CanvasWindingRule
$creadsPrec :: Int -> ReadS CanvasWindingRule
Read, CanvasWindingRule -> CanvasWindingRule -> Bool
(CanvasWindingRule -> CanvasWindingRule -> Bool)
-> (CanvasWindingRule -> CanvasWindingRule -> Bool)
-> Eq CanvasWindingRule
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CanvasWindingRule -> CanvasWindingRule -> Bool
$c/= :: CanvasWindingRule -> CanvasWindingRule -> Bool
== :: CanvasWindingRule -> CanvasWindingRule -> Bool
$c== :: CanvasWindingRule -> CanvasWindingRule -> Bool
Eq, Eq CanvasWindingRule
Eq CanvasWindingRule
-> (CanvasWindingRule -> CanvasWindingRule -> Ordering)
-> (CanvasWindingRule -> CanvasWindingRule -> Bool)
-> (CanvasWindingRule -> CanvasWindingRule -> Bool)
-> (CanvasWindingRule -> CanvasWindingRule -> Bool)
-> (CanvasWindingRule -> CanvasWindingRule -> Bool)
-> (CanvasWindingRule -> CanvasWindingRule -> CanvasWindingRule)
-> (CanvasWindingRule -> CanvasWindingRule -> CanvasWindingRule)
-> Ord CanvasWindingRule
CanvasWindingRule -> CanvasWindingRule -> Bool
CanvasWindingRule -> CanvasWindingRule -> Ordering
CanvasWindingRule -> CanvasWindingRule -> CanvasWindingRule
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CanvasWindingRule -> CanvasWindingRule -> CanvasWindingRule
$cmin :: CanvasWindingRule -> CanvasWindingRule -> CanvasWindingRule
max :: CanvasWindingRule -> CanvasWindingRule -> CanvasWindingRule
$cmax :: CanvasWindingRule -> CanvasWindingRule -> CanvasWindingRule
>= :: CanvasWindingRule -> CanvasWindingRule -> Bool
$c>= :: CanvasWindingRule -> CanvasWindingRule -> Bool
> :: CanvasWindingRule -> CanvasWindingRule -> Bool
$c> :: CanvasWindingRule -> CanvasWindingRule -> Bool
<= :: CanvasWindingRule -> CanvasWindingRule -> Bool
$c<= :: CanvasWindingRule -> CanvasWindingRule -> Bool
< :: CanvasWindingRule -> CanvasWindingRule -> Bool
$c< :: CanvasWindingRule -> CanvasWindingRule -> Bool
compare :: CanvasWindingRule -> CanvasWindingRule -> Ordering
$ccompare :: CanvasWindingRule -> CanvasWindingRule -> Ordering
$cp1Ord :: Eq CanvasWindingRule
Ord, Typeable)
 
instance ToJSVal CanvasWindingRule where
        toJSVal :: CanvasWindingRule -> JSM JSVal
toJSVal CanvasWindingRule
CanvasWindingRuleNonzero
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_CanvasWindingRuleNonzero
        toJSVal CanvasWindingRule
CanvasWindingRuleEvenodd
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_CanvasWindingRuleEvenodd
 
instance FromJSVal CanvasWindingRule where
        fromJSVal :: JSVal -> JSM (Maybe CanvasWindingRule)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_CanvasWindingRuleNonzero JSM Bool
-> (Bool -> JSM (Maybe CanvasWindingRule))
-> JSM (Maybe CanvasWindingRule)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe CanvasWindingRule -> JSM (Maybe CanvasWindingRule)
forall (m :: * -> *) a. Monad m => a -> m a
return (CanvasWindingRule -> Maybe CanvasWindingRule
forall a. a -> Maybe a
Just CanvasWindingRule
CanvasWindingRuleNonzero)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_CanvasWindingRuleEvenodd JSM Bool
-> (Bool -> JSM (Maybe CanvasWindingRule))
-> JSM (Maybe CanvasWindingRule)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe CanvasWindingRule -> JSM (Maybe CanvasWindingRule)
forall (m :: * -> *) a. Monad m => a -> m a
return (CanvasWindingRule -> Maybe CanvasWindingRule
forall a. a -> Maybe a
Just CanvasWindingRule
CanvasWindingRuleEvenodd)
                                 Bool
False -> Maybe CanvasWindingRule -> JSM (Maybe CanvasWindingRule)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe CanvasWindingRule
forall a. Maybe a
Nothing
js_CanvasWindingRuleNonzero :: String
js_CanvasWindingRuleNonzero = String
"nonzero"
js_CanvasWindingRuleEvenodd :: String
js_CanvasWindingRuleEvenodd = String
"evenodd"
 
data WebGLPowerPreference = WebGLPowerPreferenceDefault
                          | WebGLPowerPreferenceLowPower
                          | WebGLPowerPreferenceHighPerformance
                          deriving (Int -> WebGLPowerPreference -> ShowS
[WebGLPowerPreference] -> ShowS
WebGLPowerPreference -> String
(Int -> WebGLPowerPreference -> ShowS)
-> (WebGLPowerPreference -> String)
-> ([WebGLPowerPreference] -> ShowS)
-> Show WebGLPowerPreference
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WebGLPowerPreference] -> ShowS
$cshowList :: [WebGLPowerPreference] -> ShowS
show :: WebGLPowerPreference -> String
$cshow :: WebGLPowerPreference -> String
showsPrec :: Int -> WebGLPowerPreference -> ShowS
$cshowsPrec :: Int -> WebGLPowerPreference -> ShowS
Show, ReadPrec [WebGLPowerPreference]
ReadPrec WebGLPowerPreference
Int -> ReadS WebGLPowerPreference
ReadS [WebGLPowerPreference]
(Int -> ReadS WebGLPowerPreference)
-> ReadS [WebGLPowerPreference]
-> ReadPrec WebGLPowerPreference
-> ReadPrec [WebGLPowerPreference]
-> Read WebGLPowerPreference
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [WebGLPowerPreference]
$creadListPrec :: ReadPrec [WebGLPowerPreference]
readPrec :: ReadPrec WebGLPowerPreference
$creadPrec :: ReadPrec WebGLPowerPreference
readList :: ReadS [WebGLPowerPreference]
$creadList :: ReadS [WebGLPowerPreference]
readsPrec :: Int -> ReadS WebGLPowerPreference
$creadsPrec :: Int -> ReadS WebGLPowerPreference
Read, WebGLPowerPreference -> WebGLPowerPreference -> Bool
(WebGLPowerPreference -> WebGLPowerPreference -> Bool)
-> (WebGLPowerPreference -> WebGLPowerPreference -> Bool)
-> Eq WebGLPowerPreference
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WebGLPowerPreference -> WebGLPowerPreference -> Bool
$c/= :: WebGLPowerPreference -> WebGLPowerPreference -> Bool
== :: WebGLPowerPreference -> WebGLPowerPreference -> Bool
$c== :: WebGLPowerPreference -> WebGLPowerPreference -> Bool
Eq, Eq WebGLPowerPreference
Eq WebGLPowerPreference
-> (WebGLPowerPreference -> WebGLPowerPreference -> Ordering)
-> (WebGLPowerPreference -> WebGLPowerPreference -> Bool)
-> (WebGLPowerPreference -> WebGLPowerPreference -> Bool)
-> (WebGLPowerPreference -> WebGLPowerPreference -> Bool)
-> (WebGLPowerPreference -> WebGLPowerPreference -> Bool)
-> (WebGLPowerPreference
    -> WebGLPowerPreference -> WebGLPowerPreference)
-> (WebGLPowerPreference
    -> WebGLPowerPreference -> WebGLPowerPreference)
-> Ord WebGLPowerPreference
WebGLPowerPreference -> WebGLPowerPreference -> Bool
WebGLPowerPreference -> WebGLPowerPreference -> Ordering
WebGLPowerPreference
-> WebGLPowerPreference -> WebGLPowerPreference
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: WebGLPowerPreference
-> WebGLPowerPreference -> WebGLPowerPreference
$cmin :: WebGLPowerPreference
-> WebGLPowerPreference -> WebGLPowerPreference
max :: WebGLPowerPreference
-> WebGLPowerPreference -> WebGLPowerPreference
$cmax :: WebGLPowerPreference
-> WebGLPowerPreference -> WebGLPowerPreference
>= :: WebGLPowerPreference -> WebGLPowerPreference -> Bool
$c>= :: WebGLPowerPreference -> WebGLPowerPreference -> Bool
> :: WebGLPowerPreference -> WebGLPowerPreference -> Bool
$c> :: WebGLPowerPreference -> WebGLPowerPreference -> Bool
<= :: WebGLPowerPreference -> WebGLPowerPreference -> Bool
$c<= :: WebGLPowerPreference -> WebGLPowerPreference -> Bool
< :: WebGLPowerPreference -> WebGLPowerPreference -> Bool
$c< :: WebGLPowerPreference -> WebGLPowerPreference -> Bool
compare :: WebGLPowerPreference -> WebGLPowerPreference -> Ordering
$ccompare :: WebGLPowerPreference -> WebGLPowerPreference -> Ordering
$cp1Ord :: Eq WebGLPowerPreference
Ord, Typeable)
 
instance ToJSVal WebGLPowerPreference where
        toJSVal :: WebGLPowerPreference -> JSM JSVal
toJSVal WebGLPowerPreference
WebGLPowerPreferenceDefault
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGLPowerPreferenceDefault
        toJSVal WebGLPowerPreference
WebGLPowerPreferenceLowPower
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGLPowerPreferenceLowPower
        toJSVal WebGLPowerPreference
WebGLPowerPreferenceHighPerformance
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGLPowerPreferenceHighPerformance
 
instance FromJSVal WebGLPowerPreference where
        fromJSVal :: JSVal -> JSM (Maybe WebGLPowerPreference)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_WebGLPowerPreferenceDefault JSM Bool
-> (Bool -> JSM (Maybe WebGLPowerPreference))
-> JSM (Maybe WebGLPowerPreference)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe WebGLPowerPreference -> JSM (Maybe WebGLPowerPreference)
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGLPowerPreference -> Maybe WebGLPowerPreference
forall a. a -> Maybe a
Just WebGLPowerPreference
WebGLPowerPreferenceDefault)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_WebGLPowerPreferenceLowPower JSM Bool
-> (Bool -> JSM (Maybe WebGLPowerPreference))
-> JSM (Maybe WebGLPowerPreference)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe WebGLPowerPreference -> JSM (Maybe WebGLPowerPreference)
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGLPowerPreference -> Maybe WebGLPowerPreference
forall a. a -> Maybe a
Just WebGLPowerPreference
WebGLPowerPreferenceLowPower)
                                 Bool
False
                                   -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_WebGLPowerPreferenceHighPerformance JSM Bool
-> (Bool -> JSM (Maybe WebGLPowerPreference))
-> JSM (Maybe WebGLPowerPreference)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                        \ Bool
r ->
                                          case Bool
r of
                                              Bool
True
                                                -> Maybe WebGLPowerPreference -> JSM (Maybe WebGLPowerPreference)
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGLPowerPreference -> Maybe WebGLPowerPreference
forall a. a -> Maybe a
Just WebGLPowerPreference
WebGLPowerPreferenceHighPerformance)
                                              Bool
False -> Maybe WebGLPowerPreference -> JSM (Maybe WebGLPowerPreference)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe WebGLPowerPreference
forall a. Maybe a
Nothing
js_WebGLPowerPreferenceDefault :: String
js_WebGLPowerPreferenceDefault = String
"default"
js_WebGLPowerPreferenceLowPower :: String
js_WebGLPowerPreferenceLowPower = String
"low-power"
js_WebGLPowerPreferenceHighPerformance :: String
js_WebGLPowerPreferenceHighPerformance = String
"high-performance"
 
data WebGPUCompareFunction = WebGPUCompareFunctionNever
                           | WebGPUCompareFunctionLess
                           | WebGPUCompareFunctionEqual
                           | WebGPUCompareFunctionLessequal
                           | WebGPUCompareFunctionGreater
                           | WebGPUCompareFunctionNotequal
                           | WebGPUCompareFunctionGreaterequal
                           | WebGPUCompareFunctionAlways
                           deriving (Int -> WebGPUCompareFunction -> ShowS
[WebGPUCompareFunction] -> ShowS
WebGPUCompareFunction -> String
(Int -> WebGPUCompareFunction -> ShowS)
-> (WebGPUCompareFunction -> String)
-> ([WebGPUCompareFunction] -> ShowS)
-> Show WebGPUCompareFunction
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WebGPUCompareFunction] -> ShowS
$cshowList :: [WebGPUCompareFunction] -> ShowS
show :: WebGPUCompareFunction -> String
$cshow :: WebGPUCompareFunction -> String
showsPrec :: Int -> WebGPUCompareFunction -> ShowS
$cshowsPrec :: Int -> WebGPUCompareFunction -> ShowS
Show, ReadPrec [WebGPUCompareFunction]
ReadPrec WebGPUCompareFunction
Int -> ReadS WebGPUCompareFunction
ReadS [WebGPUCompareFunction]
(Int -> ReadS WebGPUCompareFunction)
-> ReadS [WebGPUCompareFunction]
-> ReadPrec WebGPUCompareFunction
-> ReadPrec [WebGPUCompareFunction]
-> Read WebGPUCompareFunction
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [WebGPUCompareFunction]
$creadListPrec :: ReadPrec [WebGPUCompareFunction]
readPrec :: ReadPrec WebGPUCompareFunction
$creadPrec :: ReadPrec WebGPUCompareFunction
readList :: ReadS [WebGPUCompareFunction]
$creadList :: ReadS [WebGPUCompareFunction]
readsPrec :: Int -> ReadS WebGPUCompareFunction
$creadsPrec :: Int -> ReadS WebGPUCompareFunction
Read, WebGPUCompareFunction -> WebGPUCompareFunction -> Bool
(WebGPUCompareFunction -> WebGPUCompareFunction -> Bool)
-> (WebGPUCompareFunction -> WebGPUCompareFunction -> Bool)
-> Eq WebGPUCompareFunction
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WebGPUCompareFunction -> WebGPUCompareFunction -> Bool
$c/= :: WebGPUCompareFunction -> WebGPUCompareFunction -> Bool
== :: WebGPUCompareFunction -> WebGPUCompareFunction -> Bool
$c== :: WebGPUCompareFunction -> WebGPUCompareFunction -> Bool
Eq, Eq WebGPUCompareFunction
Eq WebGPUCompareFunction
-> (WebGPUCompareFunction -> WebGPUCompareFunction -> Ordering)
-> (WebGPUCompareFunction -> WebGPUCompareFunction -> Bool)
-> (WebGPUCompareFunction -> WebGPUCompareFunction -> Bool)
-> (WebGPUCompareFunction -> WebGPUCompareFunction -> Bool)
-> (WebGPUCompareFunction -> WebGPUCompareFunction -> Bool)
-> (WebGPUCompareFunction
    -> WebGPUCompareFunction -> WebGPUCompareFunction)
-> (WebGPUCompareFunction
    -> WebGPUCompareFunction -> WebGPUCompareFunction)
-> Ord WebGPUCompareFunction
WebGPUCompareFunction -> WebGPUCompareFunction -> Bool
WebGPUCompareFunction -> WebGPUCompareFunction -> Ordering
WebGPUCompareFunction
-> WebGPUCompareFunction -> WebGPUCompareFunction
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: WebGPUCompareFunction
-> WebGPUCompareFunction -> WebGPUCompareFunction
$cmin :: WebGPUCompareFunction
-> WebGPUCompareFunction -> WebGPUCompareFunction
max :: WebGPUCompareFunction
-> WebGPUCompareFunction -> WebGPUCompareFunction
$cmax :: WebGPUCompareFunction
-> WebGPUCompareFunction -> WebGPUCompareFunction
>= :: WebGPUCompareFunction -> WebGPUCompareFunction -> Bool
$c>= :: WebGPUCompareFunction -> WebGPUCompareFunction -> Bool
> :: WebGPUCompareFunction -> WebGPUCompareFunction -> Bool
$c> :: WebGPUCompareFunction -> WebGPUCompareFunction -> Bool
<= :: WebGPUCompareFunction -> WebGPUCompareFunction -> Bool
$c<= :: WebGPUCompareFunction -> WebGPUCompareFunction -> Bool
< :: WebGPUCompareFunction -> WebGPUCompareFunction -> Bool
$c< :: WebGPUCompareFunction -> WebGPUCompareFunction -> Bool
compare :: WebGPUCompareFunction -> WebGPUCompareFunction -> Ordering
$ccompare :: WebGPUCompareFunction -> WebGPUCompareFunction -> Ordering
$cp1Ord :: Eq WebGPUCompareFunction
Ord, Typeable)
 
instance ToJSVal WebGPUCompareFunction where
        toJSVal :: WebGPUCompareFunction -> JSM JSVal
toJSVal WebGPUCompareFunction
WebGPUCompareFunctionNever
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUCompareFunctionNever
        toJSVal WebGPUCompareFunction
WebGPUCompareFunctionLess
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUCompareFunctionLess
        toJSVal WebGPUCompareFunction
WebGPUCompareFunctionEqual
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUCompareFunctionEqual
        toJSVal WebGPUCompareFunction
WebGPUCompareFunctionLessequal
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUCompareFunctionLessequal
        toJSVal WebGPUCompareFunction
WebGPUCompareFunctionGreater
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUCompareFunctionGreater
        toJSVal WebGPUCompareFunction
WebGPUCompareFunctionNotequal
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUCompareFunctionNotequal
        toJSVal WebGPUCompareFunction
WebGPUCompareFunctionGreaterequal
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUCompareFunctionGreaterequal
        toJSVal WebGPUCompareFunction
WebGPUCompareFunctionAlways
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUCompareFunctionAlways
 
instance FromJSVal WebGPUCompareFunction where
        fromJSVal :: JSVal -> JSM (Maybe WebGPUCompareFunction)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_WebGPUCompareFunctionNever JSM Bool
-> (Bool -> JSM (Maybe WebGPUCompareFunction))
-> JSM (Maybe WebGPUCompareFunction)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe WebGPUCompareFunction -> JSM (Maybe WebGPUCompareFunction)
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPUCompareFunction -> Maybe WebGPUCompareFunction
forall a. a -> Maybe a
Just WebGPUCompareFunction
WebGPUCompareFunctionNever)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_WebGPUCompareFunctionLess JSM Bool
-> (Bool -> JSM (Maybe WebGPUCompareFunction))
-> JSM (Maybe WebGPUCompareFunction)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe WebGPUCompareFunction -> JSM (Maybe WebGPUCompareFunction)
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPUCompareFunction -> Maybe WebGPUCompareFunction
forall a. a -> Maybe a
Just WebGPUCompareFunction
WebGPUCompareFunctionLess)
                                 Bool
False
                                   -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_WebGPUCompareFunctionEqual JSM Bool
-> (Bool -> JSM (Maybe WebGPUCompareFunction))
-> JSM (Maybe WebGPUCompareFunction)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                        \ Bool
r ->
                                          case Bool
r of
                                              Bool
True -> Maybe WebGPUCompareFunction -> JSM (Maybe WebGPUCompareFunction)
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPUCompareFunction -> Maybe WebGPUCompareFunction
forall a. a -> Maybe a
Just WebGPUCompareFunction
WebGPUCompareFunctionEqual)
                                              Bool
False
                                                -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_WebGPUCompareFunctionLessequal
                                                     JSM Bool
-> (Bool -> JSM (Maybe WebGPUCompareFunction))
-> JSM (Maybe WebGPUCompareFunction)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                     \ Bool
r ->
                                                       case Bool
r of
                                                           Bool
True
                                                             -> Maybe WebGPUCompareFunction -> JSM (Maybe WebGPUCompareFunction)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                  (WebGPUCompareFunction -> Maybe WebGPUCompareFunction
forall a. a -> Maybe a
Just
                                                                     WebGPUCompareFunction
WebGPUCompareFunctionLessequal)
                                                           Bool
False
                                                             -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                                  String
js_WebGPUCompareFunctionGreater
                                                                  JSM Bool
-> (Bool -> JSM (Maybe WebGPUCompareFunction))
-> JSM (Maybe WebGPUCompareFunction)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                  \ Bool
r ->
                                                                    case Bool
r of
                                                                        Bool
True
                                                                          -> Maybe WebGPUCompareFunction -> JSM (Maybe WebGPUCompareFunction)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                               (WebGPUCompareFunction -> Maybe WebGPUCompareFunction
forall a. a -> Maybe a
Just
                                                                                  WebGPUCompareFunction
WebGPUCompareFunctionGreater)
                                                                        Bool
False
                                                                          -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                                               String
js_WebGPUCompareFunctionNotequal
                                                                               JSM Bool
-> (Bool -> JSM (Maybe WebGPUCompareFunction))
-> JSM (Maybe WebGPUCompareFunction)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                               \ Bool
r ->
                                                                                 case Bool
r of
                                                                                     Bool
True
                                                                                       -> Maybe WebGPUCompareFunction -> JSM (Maybe WebGPUCompareFunction)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                                            (WebGPUCompareFunction -> Maybe WebGPUCompareFunction
forall a. a -> Maybe a
Just
                                                                                               WebGPUCompareFunction
WebGPUCompareFunctionNotequal)
                                                                                     Bool
False
                                                                                       -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                                                            String
js_WebGPUCompareFunctionGreaterequal
                                                                                            JSM Bool
-> (Bool -> JSM (Maybe WebGPUCompareFunction))
-> JSM (Maybe WebGPUCompareFunction)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                                            \ Bool
r ->
                                                                                              case Bool
r
                                                                                                of
                                                                                                  Bool
True
                                                                                                    -> Maybe WebGPUCompareFunction -> JSM (Maybe WebGPUCompareFunction)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                                                         (WebGPUCompareFunction -> Maybe WebGPUCompareFunction
forall a. a -> Maybe a
Just
                                                                                                            WebGPUCompareFunction
WebGPUCompareFunctionGreaterequal)
                                                                                                  Bool
False
                                                                                                    -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                                                                         String
js_WebGPUCompareFunctionAlways
                                                                                                         JSM Bool
-> (Bool -> JSM (Maybe WebGPUCompareFunction))
-> JSM (Maybe WebGPUCompareFunction)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                                                         \ Bool
r
                                                                                                           ->
                                                                                                           case
                                                                                                             Bool
r
                                                                                                             of
                                                                                                               Bool
True
                                                                                                                 -> Maybe WebGPUCompareFunction -> JSM (Maybe WebGPUCompareFunction)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                                                                      (WebGPUCompareFunction -> Maybe WebGPUCompareFunction
forall a. a -> Maybe a
Just
                                                                                                                         WebGPUCompareFunction
WebGPUCompareFunctionAlways)
                                                                                                               Bool
False
                                                                                                                 -> Maybe WebGPUCompareFunction -> JSM (Maybe WebGPUCompareFunction)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                                                                      Maybe WebGPUCompareFunction
forall a. Maybe a
Nothing
js_WebGPUCompareFunctionNever :: String
js_WebGPUCompareFunctionNever = String
"never"
js_WebGPUCompareFunctionLess :: String
js_WebGPUCompareFunctionLess = String
"less"
js_WebGPUCompareFunctionEqual :: String
js_WebGPUCompareFunctionEqual = String
"equal"
js_WebGPUCompareFunctionLessequal :: String
js_WebGPUCompareFunctionLessequal = String
"lessequal"
js_WebGPUCompareFunctionGreater :: String
js_WebGPUCompareFunctionGreater = String
"greater"
js_WebGPUCompareFunctionNotequal :: String
js_WebGPUCompareFunctionNotequal = String
"notequal"
js_WebGPUCompareFunctionGreaterequal :: String
js_WebGPUCompareFunctionGreaterequal = String
"greaterequal"
js_WebGPUCompareFunctionAlways :: String
js_WebGPUCompareFunctionAlways = String
"always"
 
data WebGPUPixelFormat = WebGPUPixelFormatBGRA8Unorm
                       deriving (Int -> WebGPUPixelFormat -> ShowS
[WebGPUPixelFormat] -> ShowS
WebGPUPixelFormat -> String
(Int -> WebGPUPixelFormat -> ShowS)
-> (WebGPUPixelFormat -> String)
-> ([WebGPUPixelFormat] -> ShowS)
-> Show WebGPUPixelFormat
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WebGPUPixelFormat] -> ShowS
$cshowList :: [WebGPUPixelFormat] -> ShowS
show :: WebGPUPixelFormat -> String
$cshow :: WebGPUPixelFormat -> String
showsPrec :: Int -> WebGPUPixelFormat -> ShowS
$cshowsPrec :: Int -> WebGPUPixelFormat -> ShowS
Show, ReadPrec [WebGPUPixelFormat]
ReadPrec WebGPUPixelFormat
Int -> ReadS WebGPUPixelFormat
ReadS [WebGPUPixelFormat]
(Int -> ReadS WebGPUPixelFormat)
-> ReadS [WebGPUPixelFormat]
-> ReadPrec WebGPUPixelFormat
-> ReadPrec [WebGPUPixelFormat]
-> Read WebGPUPixelFormat
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [WebGPUPixelFormat]
$creadListPrec :: ReadPrec [WebGPUPixelFormat]
readPrec :: ReadPrec WebGPUPixelFormat
$creadPrec :: ReadPrec WebGPUPixelFormat
readList :: ReadS [WebGPUPixelFormat]
$creadList :: ReadS [WebGPUPixelFormat]
readsPrec :: Int -> ReadS WebGPUPixelFormat
$creadsPrec :: Int -> ReadS WebGPUPixelFormat
Read, WebGPUPixelFormat -> WebGPUPixelFormat -> Bool
(WebGPUPixelFormat -> WebGPUPixelFormat -> Bool)
-> (WebGPUPixelFormat -> WebGPUPixelFormat -> Bool)
-> Eq WebGPUPixelFormat
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WebGPUPixelFormat -> WebGPUPixelFormat -> Bool
$c/= :: WebGPUPixelFormat -> WebGPUPixelFormat -> Bool
== :: WebGPUPixelFormat -> WebGPUPixelFormat -> Bool
$c== :: WebGPUPixelFormat -> WebGPUPixelFormat -> Bool
Eq, Eq WebGPUPixelFormat
Eq WebGPUPixelFormat
-> (WebGPUPixelFormat -> WebGPUPixelFormat -> Ordering)
-> (WebGPUPixelFormat -> WebGPUPixelFormat -> Bool)
-> (WebGPUPixelFormat -> WebGPUPixelFormat -> Bool)
-> (WebGPUPixelFormat -> WebGPUPixelFormat -> Bool)
-> (WebGPUPixelFormat -> WebGPUPixelFormat -> Bool)
-> (WebGPUPixelFormat -> WebGPUPixelFormat -> WebGPUPixelFormat)
-> (WebGPUPixelFormat -> WebGPUPixelFormat -> WebGPUPixelFormat)
-> Ord WebGPUPixelFormat
WebGPUPixelFormat -> WebGPUPixelFormat -> Bool
WebGPUPixelFormat -> WebGPUPixelFormat -> Ordering
WebGPUPixelFormat -> WebGPUPixelFormat -> WebGPUPixelFormat
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: WebGPUPixelFormat -> WebGPUPixelFormat -> WebGPUPixelFormat
$cmin :: WebGPUPixelFormat -> WebGPUPixelFormat -> WebGPUPixelFormat
max :: WebGPUPixelFormat -> WebGPUPixelFormat -> WebGPUPixelFormat
$cmax :: WebGPUPixelFormat -> WebGPUPixelFormat -> WebGPUPixelFormat
>= :: WebGPUPixelFormat -> WebGPUPixelFormat -> Bool
$c>= :: WebGPUPixelFormat -> WebGPUPixelFormat -> Bool
> :: WebGPUPixelFormat -> WebGPUPixelFormat -> Bool
$c> :: WebGPUPixelFormat -> WebGPUPixelFormat -> Bool
<= :: WebGPUPixelFormat -> WebGPUPixelFormat -> Bool
$c<= :: WebGPUPixelFormat -> WebGPUPixelFormat -> Bool
< :: WebGPUPixelFormat -> WebGPUPixelFormat -> Bool
$c< :: WebGPUPixelFormat -> WebGPUPixelFormat -> Bool
compare :: WebGPUPixelFormat -> WebGPUPixelFormat -> Ordering
$ccompare :: WebGPUPixelFormat -> WebGPUPixelFormat -> Ordering
$cp1Ord :: Eq WebGPUPixelFormat
Ord, Typeable)
 
instance ToJSVal WebGPUPixelFormat where
        toJSVal :: WebGPUPixelFormat -> JSM JSVal
toJSVal WebGPUPixelFormat
WebGPUPixelFormatBGRA8Unorm
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUPixelFormatBGRA8Unorm
 
instance FromJSVal WebGPUPixelFormat where
        fromJSVal :: JSVal -> JSM (Maybe WebGPUPixelFormat)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_WebGPUPixelFormatBGRA8Unorm JSM Bool
-> (Bool -> JSM (Maybe WebGPUPixelFormat))
-> JSM (Maybe WebGPUPixelFormat)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe WebGPUPixelFormat -> JSM (Maybe WebGPUPixelFormat)
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPUPixelFormat -> Maybe WebGPUPixelFormat
forall a. a -> Maybe a
Just WebGPUPixelFormat
WebGPUPixelFormatBGRA8Unorm)
                    Bool
False -> Maybe WebGPUPixelFormat -> JSM (Maybe WebGPUPixelFormat)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe WebGPUPixelFormat
forall a. Maybe a
Nothing
js_WebGPUPixelFormatBGRA8Unorm :: String
js_WebGPUPixelFormatBGRA8Unorm = String
"BGRA8Unorm"
 
data WebGPULoadAction = WebGPULoadActionDontcare
                      | WebGPULoadActionLoad
                      | WebGPULoadActionClear
                      deriving (Int -> WebGPULoadAction -> ShowS
[WebGPULoadAction] -> ShowS
WebGPULoadAction -> String
(Int -> WebGPULoadAction -> ShowS)
-> (WebGPULoadAction -> String)
-> ([WebGPULoadAction] -> ShowS)
-> Show WebGPULoadAction
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WebGPULoadAction] -> ShowS
$cshowList :: [WebGPULoadAction] -> ShowS
show :: WebGPULoadAction -> String
$cshow :: WebGPULoadAction -> String
showsPrec :: Int -> WebGPULoadAction -> ShowS
$cshowsPrec :: Int -> WebGPULoadAction -> ShowS
Show, ReadPrec [WebGPULoadAction]
ReadPrec WebGPULoadAction
Int -> ReadS WebGPULoadAction
ReadS [WebGPULoadAction]
(Int -> ReadS WebGPULoadAction)
-> ReadS [WebGPULoadAction]
-> ReadPrec WebGPULoadAction
-> ReadPrec [WebGPULoadAction]
-> Read WebGPULoadAction
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [WebGPULoadAction]
$creadListPrec :: ReadPrec [WebGPULoadAction]
readPrec :: ReadPrec WebGPULoadAction
$creadPrec :: ReadPrec WebGPULoadAction
readList :: ReadS [WebGPULoadAction]
$creadList :: ReadS [WebGPULoadAction]
readsPrec :: Int -> ReadS WebGPULoadAction
$creadsPrec :: Int -> ReadS WebGPULoadAction
Read, WebGPULoadAction -> WebGPULoadAction -> Bool
(WebGPULoadAction -> WebGPULoadAction -> Bool)
-> (WebGPULoadAction -> WebGPULoadAction -> Bool)
-> Eq WebGPULoadAction
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WebGPULoadAction -> WebGPULoadAction -> Bool
$c/= :: WebGPULoadAction -> WebGPULoadAction -> Bool
== :: WebGPULoadAction -> WebGPULoadAction -> Bool
$c== :: WebGPULoadAction -> WebGPULoadAction -> Bool
Eq, Eq WebGPULoadAction
Eq WebGPULoadAction
-> (WebGPULoadAction -> WebGPULoadAction -> Ordering)
-> (WebGPULoadAction -> WebGPULoadAction -> Bool)
-> (WebGPULoadAction -> WebGPULoadAction -> Bool)
-> (WebGPULoadAction -> WebGPULoadAction -> Bool)
-> (WebGPULoadAction -> WebGPULoadAction -> Bool)
-> (WebGPULoadAction -> WebGPULoadAction -> WebGPULoadAction)
-> (WebGPULoadAction -> WebGPULoadAction -> WebGPULoadAction)
-> Ord WebGPULoadAction
WebGPULoadAction -> WebGPULoadAction -> Bool
WebGPULoadAction -> WebGPULoadAction -> Ordering
WebGPULoadAction -> WebGPULoadAction -> WebGPULoadAction
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: WebGPULoadAction -> WebGPULoadAction -> WebGPULoadAction
$cmin :: WebGPULoadAction -> WebGPULoadAction -> WebGPULoadAction
max :: WebGPULoadAction -> WebGPULoadAction -> WebGPULoadAction
$cmax :: WebGPULoadAction -> WebGPULoadAction -> WebGPULoadAction
>= :: WebGPULoadAction -> WebGPULoadAction -> Bool
$c>= :: WebGPULoadAction -> WebGPULoadAction -> Bool
> :: WebGPULoadAction -> WebGPULoadAction -> Bool
$c> :: WebGPULoadAction -> WebGPULoadAction -> Bool
<= :: WebGPULoadAction -> WebGPULoadAction -> Bool
$c<= :: WebGPULoadAction -> WebGPULoadAction -> Bool
< :: WebGPULoadAction -> WebGPULoadAction -> Bool
$c< :: WebGPULoadAction -> WebGPULoadAction -> Bool
compare :: WebGPULoadAction -> WebGPULoadAction -> Ordering
$ccompare :: WebGPULoadAction -> WebGPULoadAction -> Ordering
$cp1Ord :: Eq WebGPULoadAction
Ord, Typeable)
 
instance ToJSVal WebGPULoadAction where
        toJSVal :: WebGPULoadAction -> JSM JSVal
toJSVal WebGPULoadAction
WebGPULoadActionDontcare
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPULoadActionDontcare
        toJSVal WebGPULoadAction
WebGPULoadActionLoad = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPULoadActionLoad
        toJSVal WebGPULoadAction
WebGPULoadActionClear = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPULoadActionClear
 
instance FromJSVal WebGPULoadAction where
        fromJSVal :: JSVal -> JSM (Maybe WebGPULoadAction)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_WebGPULoadActionDontcare JSM Bool
-> (Bool -> JSM (Maybe WebGPULoadAction))
-> JSM (Maybe WebGPULoadAction)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe WebGPULoadAction -> JSM (Maybe WebGPULoadAction)
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPULoadAction -> Maybe WebGPULoadAction
forall a. a -> Maybe a
Just WebGPULoadAction
WebGPULoadActionDontcare)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_WebGPULoadActionLoad JSM Bool
-> (Bool -> JSM (Maybe WebGPULoadAction))
-> JSM (Maybe WebGPULoadAction)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe WebGPULoadAction -> JSM (Maybe WebGPULoadAction)
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPULoadAction -> Maybe WebGPULoadAction
forall a. a -> Maybe a
Just WebGPULoadAction
WebGPULoadActionLoad)
                                 Bool
False
                                   -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_WebGPULoadActionClear JSM Bool
-> (Bool -> JSM (Maybe WebGPULoadAction))
-> JSM (Maybe WebGPULoadAction)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                        \ Bool
r ->
                                          case Bool
r of
                                              Bool
True -> Maybe WebGPULoadAction -> JSM (Maybe WebGPULoadAction)
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPULoadAction -> Maybe WebGPULoadAction
forall a. a -> Maybe a
Just WebGPULoadAction
WebGPULoadActionClear)
                                              Bool
False -> Maybe WebGPULoadAction -> JSM (Maybe WebGPULoadAction)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe WebGPULoadAction
forall a. Maybe a
Nothing
js_WebGPULoadActionDontcare :: String
js_WebGPULoadActionDontcare = String
"dontcare"
js_WebGPULoadActionLoad :: String
js_WebGPULoadActionLoad = String
"load"
js_WebGPULoadActionClear :: String
js_WebGPULoadActionClear = String
"clear"
 
data WebGPUStoreAction = WebGPUStoreActionDontcare
                       | WebGPUStoreActionStore
                       | WebGPUStoreActionMultisampleresolve
                       deriving (Int -> WebGPUStoreAction -> ShowS
[WebGPUStoreAction] -> ShowS
WebGPUStoreAction -> String
(Int -> WebGPUStoreAction -> ShowS)
-> (WebGPUStoreAction -> String)
-> ([WebGPUStoreAction] -> ShowS)
-> Show WebGPUStoreAction
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WebGPUStoreAction] -> ShowS
$cshowList :: [WebGPUStoreAction] -> ShowS
show :: WebGPUStoreAction -> String
$cshow :: WebGPUStoreAction -> String
showsPrec :: Int -> WebGPUStoreAction -> ShowS
$cshowsPrec :: Int -> WebGPUStoreAction -> ShowS
Show, ReadPrec [WebGPUStoreAction]
ReadPrec WebGPUStoreAction
Int -> ReadS WebGPUStoreAction
ReadS [WebGPUStoreAction]
(Int -> ReadS WebGPUStoreAction)
-> ReadS [WebGPUStoreAction]
-> ReadPrec WebGPUStoreAction
-> ReadPrec [WebGPUStoreAction]
-> Read WebGPUStoreAction
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [WebGPUStoreAction]
$creadListPrec :: ReadPrec [WebGPUStoreAction]
readPrec :: ReadPrec WebGPUStoreAction
$creadPrec :: ReadPrec WebGPUStoreAction
readList :: ReadS [WebGPUStoreAction]
$creadList :: ReadS [WebGPUStoreAction]
readsPrec :: Int -> ReadS WebGPUStoreAction
$creadsPrec :: Int -> ReadS WebGPUStoreAction
Read, WebGPUStoreAction -> WebGPUStoreAction -> Bool
(WebGPUStoreAction -> WebGPUStoreAction -> Bool)
-> (WebGPUStoreAction -> WebGPUStoreAction -> Bool)
-> Eq WebGPUStoreAction
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WebGPUStoreAction -> WebGPUStoreAction -> Bool
$c/= :: WebGPUStoreAction -> WebGPUStoreAction -> Bool
== :: WebGPUStoreAction -> WebGPUStoreAction -> Bool
$c== :: WebGPUStoreAction -> WebGPUStoreAction -> Bool
Eq, Eq WebGPUStoreAction
Eq WebGPUStoreAction
-> (WebGPUStoreAction -> WebGPUStoreAction -> Ordering)
-> (WebGPUStoreAction -> WebGPUStoreAction -> Bool)
-> (WebGPUStoreAction -> WebGPUStoreAction -> Bool)
-> (WebGPUStoreAction -> WebGPUStoreAction -> Bool)
-> (WebGPUStoreAction -> WebGPUStoreAction -> Bool)
-> (WebGPUStoreAction -> WebGPUStoreAction -> WebGPUStoreAction)
-> (WebGPUStoreAction -> WebGPUStoreAction -> WebGPUStoreAction)
-> Ord WebGPUStoreAction
WebGPUStoreAction -> WebGPUStoreAction -> Bool
WebGPUStoreAction -> WebGPUStoreAction -> Ordering
WebGPUStoreAction -> WebGPUStoreAction -> WebGPUStoreAction
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: WebGPUStoreAction -> WebGPUStoreAction -> WebGPUStoreAction
$cmin :: WebGPUStoreAction -> WebGPUStoreAction -> WebGPUStoreAction
max :: WebGPUStoreAction -> WebGPUStoreAction -> WebGPUStoreAction
$cmax :: WebGPUStoreAction -> WebGPUStoreAction -> WebGPUStoreAction
>= :: WebGPUStoreAction -> WebGPUStoreAction -> Bool
$c>= :: WebGPUStoreAction -> WebGPUStoreAction -> Bool
> :: WebGPUStoreAction -> WebGPUStoreAction -> Bool
$c> :: WebGPUStoreAction -> WebGPUStoreAction -> Bool
<= :: WebGPUStoreAction -> WebGPUStoreAction -> Bool
$c<= :: WebGPUStoreAction -> WebGPUStoreAction -> Bool
< :: WebGPUStoreAction -> WebGPUStoreAction -> Bool
$c< :: WebGPUStoreAction -> WebGPUStoreAction -> Bool
compare :: WebGPUStoreAction -> WebGPUStoreAction -> Ordering
$ccompare :: WebGPUStoreAction -> WebGPUStoreAction -> Ordering
$cp1Ord :: Eq WebGPUStoreAction
Ord, Typeable)
 
instance ToJSVal WebGPUStoreAction where
        toJSVal :: WebGPUStoreAction -> JSM JSVal
toJSVal WebGPUStoreAction
WebGPUStoreActionDontcare
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUStoreActionDontcare
        toJSVal WebGPUStoreAction
WebGPUStoreActionStore = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUStoreActionStore
        toJSVal WebGPUStoreAction
WebGPUStoreActionMultisampleresolve
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUStoreActionMultisampleresolve
 
instance FromJSVal WebGPUStoreAction where
        fromJSVal :: JSVal -> JSM (Maybe WebGPUStoreAction)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_WebGPUStoreActionDontcare JSM Bool
-> (Bool -> JSM (Maybe WebGPUStoreAction))
-> JSM (Maybe WebGPUStoreAction)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe WebGPUStoreAction -> JSM (Maybe WebGPUStoreAction)
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPUStoreAction -> Maybe WebGPUStoreAction
forall a. a -> Maybe a
Just WebGPUStoreAction
WebGPUStoreActionDontcare)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_WebGPUStoreActionStore JSM Bool
-> (Bool -> JSM (Maybe WebGPUStoreAction))
-> JSM (Maybe WebGPUStoreAction)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe WebGPUStoreAction -> JSM (Maybe WebGPUStoreAction)
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPUStoreAction -> Maybe WebGPUStoreAction
forall a. a -> Maybe a
Just WebGPUStoreAction
WebGPUStoreActionStore)
                                 Bool
False
                                   -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_WebGPUStoreActionMultisampleresolve JSM Bool
-> (Bool -> JSM (Maybe WebGPUStoreAction))
-> JSM (Maybe WebGPUStoreAction)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                        \ Bool
r ->
                                          case Bool
r of
                                              Bool
True
                                                -> Maybe WebGPUStoreAction -> JSM (Maybe WebGPUStoreAction)
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPUStoreAction -> Maybe WebGPUStoreAction
forall a. a -> Maybe a
Just WebGPUStoreAction
WebGPUStoreActionMultisampleresolve)
                                              Bool
False -> Maybe WebGPUStoreAction -> JSM (Maybe WebGPUStoreAction)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe WebGPUStoreAction
forall a. Maybe a
Nothing
js_WebGPUStoreActionDontcare :: String
js_WebGPUStoreActionDontcare = String
"dontcare"
js_WebGPUStoreActionStore :: String
js_WebGPUStoreActionStore = String
"store"
js_WebGPUStoreActionMultisampleresolve :: String
js_WebGPUStoreActionMultisampleresolve = String
"multisampleresolve"
 
data WebGPUPrimitiveType = WebGPUPrimitiveTypePoint
                         | WebGPUPrimitiveTypeLine
                         | WebGPUPrimitiveTypeLinestrip
                         | WebGPUPrimitiveTypeTriangle
                         | WebGPUPrimitiveTypeTrianglestrip
                         deriving (Int -> WebGPUPrimitiveType -> ShowS
[WebGPUPrimitiveType] -> ShowS
WebGPUPrimitiveType -> String
(Int -> WebGPUPrimitiveType -> ShowS)
-> (WebGPUPrimitiveType -> String)
-> ([WebGPUPrimitiveType] -> ShowS)
-> Show WebGPUPrimitiveType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WebGPUPrimitiveType] -> ShowS
$cshowList :: [WebGPUPrimitiveType] -> ShowS
show :: WebGPUPrimitiveType -> String
$cshow :: WebGPUPrimitiveType -> String
showsPrec :: Int -> WebGPUPrimitiveType -> ShowS
$cshowsPrec :: Int -> WebGPUPrimitiveType -> ShowS
Show, ReadPrec [WebGPUPrimitiveType]
ReadPrec WebGPUPrimitiveType
Int -> ReadS WebGPUPrimitiveType
ReadS [WebGPUPrimitiveType]
(Int -> ReadS WebGPUPrimitiveType)
-> ReadS [WebGPUPrimitiveType]
-> ReadPrec WebGPUPrimitiveType
-> ReadPrec [WebGPUPrimitiveType]
-> Read WebGPUPrimitiveType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [WebGPUPrimitiveType]
$creadListPrec :: ReadPrec [WebGPUPrimitiveType]
readPrec :: ReadPrec WebGPUPrimitiveType
$creadPrec :: ReadPrec WebGPUPrimitiveType
readList :: ReadS [WebGPUPrimitiveType]
$creadList :: ReadS [WebGPUPrimitiveType]
readsPrec :: Int -> ReadS WebGPUPrimitiveType
$creadsPrec :: Int -> ReadS WebGPUPrimitiveType
Read, WebGPUPrimitiveType -> WebGPUPrimitiveType -> Bool
(WebGPUPrimitiveType -> WebGPUPrimitiveType -> Bool)
-> (WebGPUPrimitiveType -> WebGPUPrimitiveType -> Bool)
-> Eq WebGPUPrimitiveType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WebGPUPrimitiveType -> WebGPUPrimitiveType -> Bool
$c/= :: WebGPUPrimitiveType -> WebGPUPrimitiveType -> Bool
== :: WebGPUPrimitiveType -> WebGPUPrimitiveType -> Bool
$c== :: WebGPUPrimitiveType -> WebGPUPrimitiveType -> Bool
Eq, Eq WebGPUPrimitiveType
Eq WebGPUPrimitiveType
-> (WebGPUPrimitiveType -> WebGPUPrimitiveType -> Ordering)
-> (WebGPUPrimitiveType -> WebGPUPrimitiveType -> Bool)
-> (WebGPUPrimitiveType -> WebGPUPrimitiveType -> Bool)
-> (WebGPUPrimitiveType -> WebGPUPrimitiveType -> Bool)
-> (WebGPUPrimitiveType -> WebGPUPrimitiveType -> Bool)
-> (WebGPUPrimitiveType
    -> WebGPUPrimitiveType -> WebGPUPrimitiveType)
-> (WebGPUPrimitiveType
    -> WebGPUPrimitiveType -> WebGPUPrimitiveType)
-> Ord WebGPUPrimitiveType
WebGPUPrimitiveType -> WebGPUPrimitiveType -> Bool
WebGPUPrimitiveType -> WebGPUPrimitiveType -> Ordering
WebGPUPrimitiveType -> WebGPUPrimitiveType -> WebGPUPrimitiveType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: WebGPUPrimitiveType -> WebGPUPrimitiveType -> WebGPUPrimitiveType
$cmin :: WebGPUPrimitiveType -> WebGPUPrimitiveType -> WebGPUPrimitiveType
max :: WebGPUPrimitiveType -> WebGPUPrimitiveType -> WebGPUPrimitiveType
$cmax :: WebGPUPrimitiveType -> WebGPUPrimitiveType -> WebGPUPrimitiveType
>= :: WebGPUPrimitiveType -> WebGPUPrimitiveType -> Bool
$c>= :: WebGPUPrimitiveType -> WebGPUPrimitiveType -> Bool
> :: WebGPUPrimitiveType -> WebGPUPrimitiveType -> Bool
$c> :: WebGPUPrimitiveType -> WebGPUPrimitiveType -> Bool
<= :: WebGPUPrimitiveType -> WebGPUPrimitiveType -> Bool
$c<= :: WebGPUPrimitiveType -> WebGPUPrimitiveType -> Bool
< :: WebGPUPrimitiveType -> WebGPUPrimitiveType -> Bool
$c< :: WebGPUPrimitiveType -> WebGPUPrimitiveType -> Bool
compare :: WebGPUPrimitiveType -> WebGPUPrimitiveType -> Ordering
$ccompare :: WebGPUPrimitiveType -> WebGPUPrimitiveType -> Ordering
$cp1Ord :: Eq WebGPUPrimitiveType
Ord, Typeable)
 
instance ToJSVal WebGPUPrimitiveType where
        toJSVal :: WebGPUPrimitiveType -> JSM JSVal
toJSVal WebGPUPrimitiveType
WebGPUPrimitiveTypePoint
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUPrimitiveTypePoint
        toJSVal WebGPUPrimitiveType
WebGPUPrimitiveTypeLine
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUPrimitiveTypeLine
        toJSVal WebGPUPrimitiveType
WebGPUPrimitiveTypeLinestrip
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUPrimitiveTypeLinestrip
        toJSVal WebGPUPrimitiveType
WebGPUPrimitiveTypeTriangle
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUPrimitiveTypeTriangle
        toJSVal WebGPUPrimitiveType
WebGPUPrimitiveTypeTrianglestrip
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUPrimitiveTypeTrianglestrip
 
instance FromJSVal WebGPUPrimitiveType where
        fromJSVal :: JSVal -> JSM (Maybe WebGPUPrimitiveType)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_WebGPUPrimitiveTypePoint JSM Bool
-> (Bool -> JSM (Maybe WebGPUPrimitiveType))
-> JSM (Maybe WebGPUPrimitiveType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe WebGPUPrimitiveType -> JSM (Maybe WebGPUPrimitiveType)
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPUPrimitiveType -> Maybe WebGPUPrimitiveType
forall a. a -> Maybe a
Just WebGPUPrimitiveType
WebGPUPrimitiveTypePoint)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_WebGPUPrimitiveTypeLine JSM Bool
-> (Bool -> JSM (Maybe WebGPUPrimitiveType))
-> JSM (Maybe WebGPUPrimitiveType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe WebGPUPrimitiveType -> JSM (Maybe WebGPUPrimitiveType)
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPUPrimitiveType -> Maybe WebGPUPrimitiveType
forall a. a -> Maybe a
Just WebGPUPrimitiveType
WebGPUPrimitiveTypeLine)
                                 Bool
False
                                   -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_WebGPUPrimitiveTypeLinestrip JSM Bool
-> (Bool -> JSM (Maybe WebGPUPrimitiveType))
-> JSM (Maybe WebGPUPrimitiveType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                        \ Bool
r ->
                                          case Bool
r of
                                              Bool
True -> Maybe WebGPUPrimitiveType -> JSM (Maybe WebGPUPrimitiveType)
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPUPrimitiveType -> Maybe WebGPUPrimitiveType
forall a. a -> Maybe a
Just WebGPUPrimitiveType
WebGPUPrimitiveTypeLinestrip)
                                              Bool
False
                                                -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_WebGPUPrimitiveTypeTriangle
                                                     JSM Bool
-> (Bool -> JSM (Maybe WebGPUPrimitiveType))
-> JSM (Maybe WebGPUPrimitiveType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                     \ Bool
r ->
                                                       case Bool
r of
                                                           Bool
True
                                                             -> Maybe WebGPUPrimitiveType -> JSM (Maybe WebGPUPrimitiveType)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                  (WebGPUPrimitiveType -> Maybe WebGPUPrimitiveType
forall a. a -> Maybe a
Just WebGPUPrimitiveType
WebGPUPrimitiveTypeTriangle)
                                                           Bool
False
                                                             -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                                  String
js_WebGPUPrimitiveTypeTrianglestrip
                                                                  JSM Bool
-> (Bool -> JSM (Maybe WebGPUPrimitiveType))
-> JSM (Maybe WebGPUPrimitiveType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                  \ Bool
r ->
                                                                    case Bool
r of
                                                                        Bool
True
                                                                          -> Maybe WebGPUPrimitiveType -> JSM (Maybe WebGPUPrimitiveType)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                               (WebGPUPrimitiveType -> Maybe WebGPUPrimitiveType
forall a. a -> Maybe a
Just
                                                                                  WebGPUPrimitiveType
WebGPUPrimitiveTypeTrianglestrip)
                                                                        Bool
False -> Maybe WebGPUPrimitiveType -> JSM (Maybe WebGPUPrimitiveType)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe WebGPUPrimitiveType
forall a. Maybe a
Nothing
js_WebGPUPrimitiveTypePoint :: String
js_WebGPUPrimitiveTypePoint = String
"point"
js_WebGPUPrimitiveTypeLine :: String
js_WebGPUPrimitiveTypeLine = String
"line"
js_WebGPUPrimitiveTypeLinestrip :: String
js_WebGPUPrimitiveTypeLinestrip = String
"linestrip"
js_WebGPUPrimitiveTypeTriangle :: String
js_WebGPUPrimitiveTypeTriangle = String
"triangle"
js_WebGPUPrimitiveTypeTrianglestrip :: String
js_WebGPUPrimitiveTypeTrianglestrip = String
"trianglestrip"
 
data WebGPUFunctionType = WebGPUFunctionTypeFragment
                        | WebGPUFunctionTypeVertex
                        deriving (Int -> WebGPUFunctionType -> ShowS
[WebGPUFunctionType] -> ShowS
WebGPUFunctionType -> String
(Int -> WebGPUFunctionType -> ShowS)
-> (WebGPUFunctionType -> String)
-> ([WebGPUFunctionType] -> ShowS)
-> Show WebGPUFunctionType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WebGPUFunctionType] -> ShowS
$cshowList :: [WebGPUFunctionType] -> ShowS
show :: WebGPUFunctionType -> String
$cshow :: WebGPUFunctionType -> String
showsPrec :: Int -> WebGPUFunctionType -> ShowS
$cshowsPrec :: Int -> WebGPUFunctionType -> ShowS
Show, ReadPrec [WebGPUFunctionType]
ReadPrec WebGPUFunctionType
Int -> ReadS WebGPUFunctionType
ReadS [WebGPUFunctionType]
(Int -> ReadS WebGPUFunctionType)
-> ReadS [WebGPUFunctionType]
-> ReadPrec WebGPUFunctionType
-> ReadPrec [WebGPUFunctionType]
-> Read WebGPUFunctionType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [WebGPUFunctionType]
$creadListPrec :: ReadPrec [WebGPUFunctionType]
readPrec :: ReadPrec WebGPUFunctionType
$creadPrec :: ReadPrec WebGPUFunctionType
readList :: ReadS [WebGPUFunctionType]
$creadList :: ReadS [WebGPUFunctionType]
readsPrec :: Int -> ReadS WebGPUFunctionType
$creadsPrec :: Int -> ReadS WebGPUFunctionType
Read, WebGPUFunctionType -> WebGPUFunctionType -> Bool
(WebGPUFunctionType -> WebGPUFunctionType -> Bool)
-> (WebGPUFunctionType -> WebGPUFunctionType -> Bool)
-> Eq WebGPUFunctionType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WebGPUFunctionType -> WebGPUFunctionType -> Bool
$c/= :: WebGPUFunctionType -> WebGPUFunctionType -> Bool
== :: WebGPUFunctionType -> WebGPUFunctionType -> Bool
$c== :: WebGPUFunctionType -> WebGPUFunctionType -> Bool
Eq, Eq WebGPUFunctionType
Eq WebGPUFunctionType
-> (WebGPUFunctionType -> WebGPUFunctionType -> Ordering)
-> (WebGPUFunctionType -> WebGPUFunctionType -> Bool)
-> (WebGPUFunctionType -> WebGPUFunctionType -> Bool)
-> (WebGPUFunctionType -> WebGPUFunctionType -> Bool)
-> (WebGPUFunctionType -> WebGPUFunctionType -> Bool)
-> (WebGPUFunctionType -> WebGPUFunctionType -> WebGPUFunctionType)
-> (WebGPUFunctionType -> WebGPUFunctionType -> WebGPUFunctionType)
-> Ord WebGPUFunctionType
WebGPUFunctionType -> WebGPUFunctionType -> Bool
WebGPUFunctionType -> WebGPUFunctionType -> Ordering
WebGPUFunctionType -> WebGPUFunctionType -> WebGPUFunctionType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: WebGPUFunctionType -> WebGPUFunctionType -> WebGPUFunctionType
$cmin :: WebGPUFunctionType -> WebGPUFunctionType -> WebGPUFunctionType
max :: WebGPUFunctionType -> WebGPUFunctionType -> WebGPUFunctionType
$cmax :: WebGPUFunctionType -> WebGPUFunctionType -> WebGPUFunctionType
>= :: WebGPUFunctionType -> WebGPUFunctionType -> Bool
$c>= :: WebGPUFunctionType -> WebGPUFunctionType -> Bool
> :: WebGPUFunctionType -> WebGPUFunctionType -> Bool
$c> :: WebGPUFunctionType -> WebGPUFunctionType -> Bool
<= :: WebGPUFunctionType -> WebGPUFunctionType -> Bool
$c<= :: WebGPUFunctionType -> WebGPUFunctionType -> Bool
< :: WebGPUFunctionType -> WebGPUFunctionType -> Bool
$c< :: WebGPUFunctionType -> WebGPUFunctionType -> Bool
compare :: WebGPUFunctionType -> WebGPUFunctionType -> Ordering
$ccompare :: WebGPUFunctionType -> WebGPUFunctionType -> Ordering
$cp1Ord :: Eq WebGPUFunctionType
Ord, Typeable)
 
instance ToJSVal WebGPUFunctionType where
        toJSVal :: WebGPUFunctionType -> JSM JSVal
toJSVal WebGPUFunctionType
WebGPUFunctionTypeFragment
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUFunctionTypeFragment
        toJSVal WebGPUFunctionType
WebGPUFunctionTypeVertex
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUFunctionTypeVertex
 
instance FromJSVal WebGPUFunctionType where
        fromJSVal :: JSVal -> JSM (Maybe WebGPUFunctionType)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_WebGPUFunctionTypeFragment JSM Bool
-> (Bool -> JSM (Maybe WebGPUFunctionType))
-> JSM (Maybe WebGPUFunctionType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe WebGPUFunctionType -> JSM (Maybe WebGPUFunctionType)
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPUFunctionType -> Maybe WebGPUFunctionType
forall a. a -> Maybe a
Just WebGPUFunctionType
WebGPUFunctionTypeFragment)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_WebGPUFunctionTypeVertex JSM Bool
-> (Bool -> JSM (Maybe WebGPUFunctionType))
-> JSM (Maybe WebGPUFunctionType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe WebGPUFunctionType -> JSM (Maybe WebGPUFunctionType)
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPUFunctionType -> Maybe WebGPUFunctionType
forall a. a -> Maybe a
Just WebGPUFunctionType
WebGPUFunctionTypeVertex)
                                 Bool
False -> Maybe WebGPUFunctionType -> JSM (Maybe WebGPUFunctionType)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe WebGPUFunctionType
forall a. Maybe a
Nothing
js_WebGPUFunctionTypeFragment :: String
js_WebGPUFunctionTypeFragment = String
"fragment"
js_WebGPUFunctionTypeVertex :: String
js_WebGPUFunctionTypeVertex = String
"vertex"
 
data WebGPUStencilOperation = WebGPUStencilOperationKeep
                            | WebGPUStencilOperationZero
                            | WebGPUStencilOperationReplace
                            | WebGPUStencilOperationIncrementclamp
                            | WebGPUStencilOperationDecrementclamp
                            | WebGPUStencilOperationInvert
                            | WebGPUStencilOperationIncrementwrap
                            | WebGPUStencilOperationDecrementwrap
                            deriving (Int -> WebGPUStencilOperation -> ShowS
[WebGPUStencilOperation] -> ShowS
WebGPUStencilOperation -> String
(Int -> WebGPUStencilOperation -> ShowS)
-> (WebGPUStencilOperation -> String)
-> ([WebGPUStencilOperation] -> ShowS)
-> Show WebGPUStencilOperation
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WebGPUStencilOperation] -> ShowS
$cshowList :: [WebGPUStencilOperation] -> ShowS
show :: WebGPUStencilOperation -> String
$cshow :: WebGPUStencilOperation -> String
showsPrec :: Int -> WebGPUStencilOperation -> ShowS
$cshowsPrec :: Int -> WebGPUStencilOperation -> ShowS
Show, ReadPrec [WebGPUStencilOperation]
ReadPrec WebGPUStencilOperation
Int -> ReadS WebGPUStencilOperation
ReadS [WebGPUStencilOperation]
(Int -> ReadS WebGPUStencilOperation)
-> ReadS [WebGPUStencilOperation]
-> ReadPrec WebGPUStencilOperation
-> ReadPrec [WebGPUStencilOperation]
-> Read WebGPUStencilOperation
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [WebGPUStencilOperation]
$creadListPrec :: ReadPrec [WebGPUStencilOperation]
readPrec :: ReadPrec WebGPUStencilOperation
$creadPrec :: ReadPrec WebGPUStencilOperation
readList :: ReadS [WebGPUStencilOperation]
$creadList :: ReadS [WebGPUStencilOperation]
readsPrec :: Int -> ReadS WebGPUStencilOperation
$creadsPrec :: Int -> ReadS WebGPUStencilOperation
Read, WebGPUStencilOperation -> WebGPUStencilOperation -> Bool
(WebGPUStencilOperation -> WebGPUStencilOperation -> Bool)
-> (WebGPUStencilOperation -> WebGPUStencilOperation -> Bool)
-> Eq WebGPUStencilOperation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WebGPUStencilOperation -> WebGPUStencilOperation -> Bool
$c/= :: WebGPUStencilOperation -> WebGPUStencilOperation -> Bool
== :: WebGPUStencilOperation -> WebGPUStencilOperation -> Bool
$c== :: WebGPUStencilOperation -> WebGPUStencilOperation -> Bool
Eq, Eq WebGPUStencilOperation
Eq WebGPUStencilOperation
-> (WebGPUStencilOperation -> WebGPUStencilOperation -> Ordering)
-> (WebGPUStencilOperation -> WebGPUStencilOperation -> Bool)
-> (WebGPUStencilOperation -> WebGPUStencilOperation -> Bool)
-> (WebGPUStencilOperation -> WebGPUStencilOperation -> Bool)
-> (WebGPUStencilOperation -> WebGPUStencilOperation -> Bool)
-> (WebGPUStencilOperation
    -> WebGPUStencilOperation -> WebGPUStencilOperation)
-> (WebGPUStencilOperation
    -> WebGPUStencilOperation -> WebGPUStencilOperation)
-> Ord WebGPUStencilOperation
WebGPUStencilOperation -> WebGPUStencilOperation -> Bool
WebGPUStencilOperation -> WebGPUStencilOperation -> Ordering
WebGPUStencilOperation
-> WebGPUStencilOperation -> WebGPUStencilOperation
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: WebGPUStencilOperation
-> WebGPUStencilOperation -> WebGPUStencilOperation
$cmin :: WebGPUStencilOperation
-> WebGPUStencilOperation -> WebGPUStencilOperation
max :: WebGPUStencilOperation
-> WebGPUStencilOperation -> WebGPUStencilOperation
$cmax :: WebGPUStencilOperation
-> WebGPUStencilOperation -> WebGPUStencilOperation
>= :: WebGPUStencilOperation -> WebGPUStencilOperation -> Bool
$c>= :: WebGPUStencilOperation -> WebGPUStencilOperation -> Bool
> :: WebGPUStencilOperation -> WebGPUStencilOperation -> Bool
$c> :: WebGPUStencilOperation -> WebGPUStencilOperation -> Bool
<= :: WebGPUStencilOperation -> WebGPUStencilOperation -> Bool
$c<= :: WebGPUStencilOperation -> WebGPUStencilOperation -> Bool
< :: WebGPUStencilOperation -> WebGPUStencilOperation -> Bool
$c< :: WebGPUStencilOperation -> WebGPUStencilOperation -> Bool
compare :: WebGPUStencilOperation -> WebGPUStencilOperation -> Ordering
$ccompare :: WebGPUStencilOperation -> WebGPUStencilOperation -> Ordering
$cp1Ord :: Eq WebGPUStencilOperation
Ord, Typeable)
 
instance ToJSVal WebGPUStencilOperation where
        toJSVal :: WebGPUStencilOperation -> JSM JSVal
toJSVal WebGPUStencilOperation
WebGPUStencilOperationKeep
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUStencilOperationKeep
        toJSVal WebGPUStencilOperation
WebGPUStencilOperationZero
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUStencilOperationZero
        toJSVal WebGPUStencilOperation
WebGPUStencilOperationReplace
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUStencilOperationReplace
        toJSVal WebGPUStencilOperation
WebGPUStencilOperationIncrementclamp
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUStencilOperationIncrementclamp
        toJSVal WebGPUStencilOperation
WebGPUStencilOperationDecrementclamp
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUStencilOperationDecrementclamp
        toJSVal WebGPUStencilOperation
WebGPUStencilOperationInvert
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUStencilOperationInvert
        toJSVal WebGPUStencilOperation
WebGPUStencilOperationIncrementwrap
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUStencilOperationIncrementwrap
        toJSVal WebGPUStencilOperation
WebGPUStencilOperationDecrementwrap
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUStencilOperationDecrementwrap
 
instance FromJSVal WebGPUStencilOperation where
        fromJSVal :: JSVal -> JSM (Maybe WebGPUStencilOperation)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_WebGPUStencilOperationKeep JSM Bool
-> (Bool -> JSM (Maybe WebGPUStencilOperation))
-> JSM (Maybe WebGPUStencilOperation)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe WebGPUStencilOperation -> JSM (Maybe WebGPUStencilOperation)
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPUStencilOperation -> Maybe WebGPUStencilOperation
forall a. a -> Maybe a
Just WebGPUStencilOperation
WebGPUStencilOperationKeep)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_WebGPUStencilOperationZero JSM Bool
-> (Bool -> JSM (Maybe WebGPUStencilOperation))
-> JSM (Maybe WebGPUStencilOperation)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe WebGPUStencilOperation -> JSM (Maybe WebGPUStencilOperation)
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPUStencilOperation -> Maybe WebGPUStencilOperation
forall a. a -> Maybe a
Just WebGPUStencilOperation
WebGPUStencilOperationZero)
                                 Bool
False
                                   -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_WebGPUStencilOperationReplace JSM Bool
-> (Bool -> JSM (Maybe WebGPUStencilOperation))
-> JSM (Maybe WebGPUStencilOperation)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                        \ Bool
r ->
                                          case Bool
r of
                                              Bool
True -> Maybe WebGPUStencilOperation -> JSM (Maybe WebGPUStencilOperation)
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPUStencilOperation -> Maybe WebGPUStencilOperation
forall a. a -> Maybe a
Just WebGPUStencilOperation
WebGPUStencilOperationReplace)
                                              Bool
False
                                                -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                     String
js_WebGPUStencilOperationIncrementclamp
                                                     JSM Bool
-> (Bool -> JSM (Maybe WebGPUStencilOperation))
-> JSM (Maybe WebGPUStencilOperation)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                     \ Bool
r ->
                                                       case Bool
r of
                                                           Bool
True
                                                             -> Maybe WebGPUStencilOperation -> JSM (Maybe WebGPUStencilOperation)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                  (WebGPUStencilOperation -> Maybe WebGPUStencilOperation
forall a. a -> Maybe a
Just
                                                                     WebGPUStencilOperation
WebGPUStencilOperationIncrementclamp)
                                                           Bool
False
                                                             -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                                  String
js_WebGPUStencilOperationDecrementclamp
                                                                  JSM Bool
-> (Bool -> JSM (Maybe WebGPUStencilOperation))
-> JSM (Maybe WebGPUStencilOperation)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                  \ Bool
r ->
                                                                    case Bool
r of
                                                                        Bool
True
                                                                          -> Maybe WebGPUStencilOperation -> JSM (Maybe WebGPUStencilOperation)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                               (WebGPUStencilOperation -> Maybe WebGPUStencilOperation
forall a. a -> Maybe a
Just
                                                                                  WebGPUStencilOperation
WebGPUStencilOperationDecrementclamp)
                                                                        Bool
False
                                                                          -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                                               String
js_WebGPUStencilOperationInvert
                                                                               JSM Bool
-> (Bool -> JSM (Maybe WebGPUStencilOperation))
-> JSM (Maybe WebGPUStencilOperation)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                               \ Bool
r ->
                                                                                 case Bool
r of
                                                                                     Bool
True
                                                                                       -> Maybe WebGPUStencilOperation -> JSM (Maybe WebGPUStencilOperation)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                                            (WebGPUStencilOperation -> Maybe WebGPUStencilOperation
forall a. a -> Maybe a
Just
                                                                                               WebGPUStencilOperation
WebGPUStencilOperationInvert)
                                                                                     Bool
False
                                                                                       -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                                                            String
js_WebGPUStencilOperationIncrementwrap
                                                                                            JSM Bool
-> (Bool -> JSM (Maybe WebGPUStencilOperation))
-> JSM (Maybe WebGPUStencilOperation)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                                            \ Bool
r ->
                                                                                              case Bool
r
                                                                                                of
                                                                                                  Bool
True
                                                                                                    -> Maybe WebGPUStencilOperation -> JSM (Maybe WebGPUStencilOperation)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                                                         (WebGPUStencilOperation -> Maybe WebGPUStencilOperation
forall a. a -> Maybe a
Just
                                                                                                            WebGPUStencilOperation
WebGPUStencilOperationIncrementwrap)
                                                                                                  Bool
False
                                                                                                    -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                                                                         String
js_WebGPUStencilOperationDecrementwrap
                                                                                                         JSM Bool
-> (Bool -> JSM (Maybe WebGPUStencilOperation))
-> JSM (Maybe WebGPUStencilOperation)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                                                         \ Bool
r
                                                                                                           ->
                                                                                                           case
                                                                                                             Bool
r
                                                                                                             of
                                                                                                               Bool
True
                                                                                                                 -> Maybe WebGPUStencilOperation -> JSM (Maybe WebGPUStencilOperation)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                                                                      (WebGPUStencilOperation -> Maybe WebGPUStencilOperation
forall a. a -> Maybe a
Just
                                                                                                                         WebGPUStencilOperation
WebGPUStencilOperationDecrementwrap)
                                                                                                               Bool
False
                                                                                                                 -> Maybe WebGPUStencilOperation -> JSM (Maybe WebGPUStencilOperation)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                                                                      Maybe WebGPUStencilOperation
forall a. Maybe a
Nothing
js_WebGPUStencilOperationKeep :: String
js_WebGPUStencilOperationKeep = String
"keep"
js_WebGPUStencilOperationZero :: String
js_WebGPUStencilOperationZero = String
"zero"
js_WebGPUStencilOperationReplace :: String
js_WebGPUStencilOperationReplace = String
"replace"
js_WebGPUStencilOperationIncrementclamp :: String
js_WebGPUStencilOperationIncrementclamp = String
"incrementclamp"
js_WebGPUStencilOperationDecrementclamp :: String
js_WebGPUStencilOperationDecrementclamp = String
"decrementclamp"
js_WebGPUStencilOperationInvert :: String
js_WebGPUStencilOperationInvert = String
"invert"
js_WebGPUStencilOperationIncrementwrap :: String
js_WebGPUStencilOperationIncrementwrap = String
"incrementwrap"
js_WebGPUStencilOperationDecrementwrap :: String
js_WebGPUStencilOperationDecrementwrap = String
"decrementwrap"
 
data WebGPUStatus = WebGPUStatusNotenqueued
                  | WebGPUStatusEnqueued
                  | WebGPUStatusCommitted
                  | WebGPUStatusScheduled
                  | WebGPUStatusCompleted
                  | WebGPUStatusError
                  deriving (Int -> WebGPUStatus -> ShowS
[WebGPUStatus] -> ShowS
WebGPUStatus -> String
(Int -> WebGPUStatus -> ShowS)
-> (WebGPUStatus -> String)
-> ([WebGPUStatus] -> ShowS)
-> Show WebGPUStatus
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WebGPUStatus] -> ShowS
$cshowList :: [WebGPUStatus] -> ShowS
show :: WebGPUStatus -> String
$cshow :: WebGPUStatus -> String
showsPrec :: Int -> WebGPUStatus -> ShowS
$cshowsPrec :: Int -> WebGPUStatus -> ShowS
Show, ReadPrec [WebGPUStatus]
ReadPrec WebGPUStatus
Int -> ReadS WebGPUStatus
ReadS [WebGPUStatus]
(Int -> ReadS WebGPUStatus)
-> ReadS [WebGPUStatus]
-> ReadPrec WebGPUStatus
-> ReadPrec [WebGPUStatus]
-> Read WebGPUStatus
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [WebGPUStatus]
$creadListPrec :: ReadPrec [WebGPUStatus]
readPrec :: ReadPrec WebGPUStatus
$creadPrec :: ReadPrec WebGPUStatus
readList :: ReadS [WebGPUStatus]
$creadList :: ReadS [WebGPUStatus]
readsPrec :: Int -> ReadS WebGPUStatus
$creadsPrec :: Int -> ReadS WebGPUStatus
Read, WebGPUStatus -> WebGPUStatus -> Bool
(WebGPUStatus -> WebGPUStatus -> Bool)
-> (WebGPUStatus -> WebGPUStatus -> Bool) -> Eq WebGPUStatus
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WebGPUStatus -> WebGPUStatus -> Bool
$c/= :: WebGPUStatus -> WebGPUStatus -> Bool
== :: WebGPUStatus -> WebGPUStatus -> Bool
$c== :: WebGPUStatus -> WebGPUStatus -> Bool
Eq, Eq WebGPUStatus
Eq WebGPUStatus
-> (WebGPUStatus -> WebGPUStatus -> Ordering)
-> (WebGPUStatus -> WebGPUStatus -> Bool)
-> (WebGPUStatus -> WebGPUStatus -> Bool)
-> (WebGPUStatus -> WebGPUStatus -> Bool)
-> (WebGPUStatus -> WebGPUStatus -> Bool)
-> (WebGPUStatus -> WebGPUStatus -> WebGPUStatus)
-> (WebGPUStatus -> WebGPUStatus -> WebGPUStatus)
-> Ord WebGPUStatus
WebGPUStatus -> WebGPUStatus -> Bool
WebGPUStatus -> WebGPUStatus -> Ordering
WebGPUStatus -> WebGPUStatus -> WebGPUStatus
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: WebGPUStatus -> WebGPUStatus -> WebGPUStatus
$cmin :: WebGPUStatus -> WebGPUStatus -> WebGPUStatus
max :: WebGPUStatus -> WebGPUStatus -> WebGPUStatus
$cmax :: WebGPUStatus -> WebGPUStatus -> WebGPUStatus
>= :: WebGPUStatus -> WebGPUStatus -> Bool
$c>= :: WebGPUStatus -> WebGPUStatus -> Bool
> :: WebGPUStatus -> WebGPUStatus -> Bool
$c> :: WebGPUStatus -> WebGPUStatus -> Bool
<= :: WebGPUStatus -> WebGPUStatus -> Bool
$c<= :: WebGPUStatus -> WebGPUStatus -> Bool
< :: WebGPUStatus -> WebGPUStatus -> Bool
$c< :: WebGPUStatus -> WebGPUStatus -> Bool
compare :: WebGPUStatus -> WebGPUStatus -> Ordering
$ccompare :: WebGPUStatus -> WebGPUStatus -> Ordering
$cp1Ord :: Eq WebGPUStatus
Ord, Typeable)
 
instance ToJSVal WebGPUStatus where
        toJSVal :: WebGPUStatus -> JSM JSVal
toJSVal WebGPUStatus
WebGPUStatusNotenqueued
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUStatusNotenqueued
        toJSVal WebGPUStatus
WebGPUStatusEnqueued = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUStatusEnqueued
        toJSVal WebGPUStatus
WebGPUStatusCommitted = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUStatusCommitted
        toJSVal WebGPUStatus
WebGPUStatusScheduled = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUStatusScheduled
        toJSVal WebGPUStatus
WebGPUStatusCompleted = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUStatusCompleted
        toJSVal WebGPUStatus
WebGPUStatusError = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUStatusError
 
instance FromJSVal WebGPUStatus where
        fromJSVal :: JSVal -> JSM (Maybe WebGPUStatus)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_WebGPUStatusNotenqueued JSM Bool
-> (Bool -> JSM (Maybe WebGPUStatus)) -> JSM (Maybe WebGPUStatus)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe WebGPUStatus -> JSM (Maybe WebGPUStatus)
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPUStatus -> Maybe WebGPUStatus
forall a. a -> Maybe a
Just WebGPUStatus
WebGPUStatusNotenqueued)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_WebGPUStatusEnqueued JSM Bool
-> (Bool -> JSM (Maybe WebGPUStatus)) -> JSM (Maybe WebGPUStatus)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe WebGPUStatus -> JSM (Maybe WebGPUStatus)
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPUStatus -> Maybe WebGPUStatus
forall a. a -> Maybe a
Just WebGPUStatus
WebGPUStatusEnqueued)
                                 Bool
False
                                   -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_WebGPUStatusCommitted JSM Bool
-> (Bool -> JSM (Maybe WebGPUStatus)) -> JSM (Maybe WebGPUStatus)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                        \ Bool
r ->
                                          case Bool
r of
                                              Bool
True -> Maybe WebGPUStatus -> JSM (Maybe WebGPUStatus)
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPUStatus -> Maybe WebGPUStatus
forall a. a -> Maybe a
Just WebGPUStatus
WebGPUStatusCommitted)
                                              Bool
False
                                                -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_WebGPUStatusScheduled JSM Bool
-> (Bool -> JSM (Maybe WebGPUStatus)) -> JSM (Maybe WebGPUStatus)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                     \ Bool
r ->
                                                       case Bool
r of
                                                           Bool
True
                                                             -> Maybe WebGPUStatus -> JSM (Maybe WebGPUStatus)
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPUStatus -> Maybe WebGPUStatus
forall a. a -> Maybe a
Just WebGPUStatus
WebGPUStatusScheduled)
                                                           Bool
False
                                                             -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                                  String
js_WebGPUStatusCompleted
                                                                  JSM Bool
-> (Bool -> JSM (Maybe WebGPUStatus)) -> JSM (Maybe WebGPUStatus)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                  \ Bool
r ->
                                                                    case Bool
r of
                                                                        Bool
True
                                                                          -> Maybe WebGPUStatus -> JSM (Maybe WebGPUStatus)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                               (WebGPUStatus -> Maybe WebGPUStatus
forall a. a -> Maybe a
Just
                                                                                  WebGPUStatus
WebGPUStatusCompleted)
                                                                        Bool
False
                                                                          -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                                               String
js_WebGPUStatusError
                                                                               JSM Bool
-> (Bool -> JSM (Maybe WebGPUStatus)) -> JSM (Maybe WebGPUStatus)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                               \ Bool
r ->
                                                                                 case Bool
r of
                                                                                     Bool
True
                                                                                       -> Maybe WebGPUStatus -> JSM (Maybe WebGPUStatus)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                                            (WebGPUStatus -> Maybe WebGPUStatus
forall a. a -> Maybe a
Just
                                                                                               WebGPUStatus
WebGPUStatusError)
                                                                                     Bool
False
                                                                                       -> Maybe WebGPUStatus -> JSM (Maybe WebGPUStatus)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                                            Maybe WebGPUStatus
forall a. Maybe a
Nothing
js_WebGPUStatusNotenqueued :: String
js_WebGPUStatusNotenqueued = String
"notenqueued"
js_WebGPUStatusEnqueued :: String
js_WebGPUStatusEnqueued = String
"enqueued"
js_WebGPUStatusCommitted :: String
js_WebGPUStatusCommitted = String
"committed"
js_WebGPUStatusScheduled :: String
js_WebGPUStatusScheduled = String
"scheduled"
js_WebGPUStatusCompleted :: String
js_WebGPUStatusCompleted = String
"completed"
js_WebGPUStatusError :: String
js_WebGPUStatusError = String
"error"
 
data WebGPUSamplerAddressMode = WebGPUSamplerAddressModeClamptoedge
                              | WebGPUSamplerAddressModeMirrorclamptoedge
                              | WebGPUSamplerAddressModeRepeat
                              | WebGPUSamplerAddressModeMirrorrepeat
                              | WebGPUSamplerAddressModeClamptozero
                              deriving (Int -> WebGPUSamplerAddressMode -> ShowS
[WebGPUSamplerAddressMode] -> ShowS
WebGPUSamplerAddressMode -> String
(Int -> WebGPUSamplerAddressMode -> ShowS)
-> (WebGPUSamplerAddressMode -> String)
-> ([WebGPUSamplerAddressMode] -> ShowS)
-> Show WebGPUSamplerAddressMode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WebGPUSamplerAddressMode] -> ShowS
$cshowList :: [WebGPUSamplerAddressMode] -> ShowS
show :: WebGPUSamplerAddressMode -> String
$cshow :: WebGPUSamplerAddressMode -> String
showsPrec :: Int -> WebGPUSamplerAddressMode -> ShowS
$cshowsPrec :: Int -> WebGPUSamplerAddressMode -> ShowS
Show, ReadPrec [WebGPUSamplerAddressMode]
ReadPrec WebGPUSamplerAddressMode
Int -> ReadS WebGPUSamplerAddressMode
ReadS [WebGPUSamplerAddressMode]
(Int -> ReadS WebGPUSamplerAddressMode)
-> ReadS [WebGPUSamplerAddressMode]
-> ReadPrec WebGPUSamplerAddressMode
-> ReadPrec [WebGPUSamplerAddressMode]
-> Read WebGPUSamplerAddressMode
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [WebGPUSamplerAddressMode]
$creadListPrec :: ReadPrec [WebGPUSamplerAddressMode]
readPrec :: ReadPrec WebGPUSamplerAddressMode
$creadPrec :: ReadPrec WebGPUSamplerAddressMode
readList :: ReadS [WebGPUSamplerAddressMode]
$creadList :: ReadS [WebGPUSamplerAddressMode]
readsPrec :: Int -> ReadS WebGPUSamplerAddressMode
$creadsPrec :: Int -> ReadS WebGPUSamplerAddressMode
Read, WebGPUSamplerAddressMode -> WebGPUSamplerAddressMode -> Bool
(WebGPUSamplerAddressMode -> WebGPUSamplerAddressMode -> Bool)
-> (WebGPUSamplerAddressMode -> WebGPUSamplerAddressMode -> Bool)
-> Eq WebGPUSamplerAddressMode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WebGPUSamplerAddressMode -> WebGPUSamplerAddressMode -> Bool
$c/= :: WebGPUSamplerAddressMode -> WebGPUSamplerAddressMode -> Bool
== :: WebGPUSamplerAddressMode -> WebGPUSamplerAddressMode -> Bool
$c== :: WebGPUSamplerAddressMode -> WebGPUSamplerAddressMode -> Bool
Eq, Eq WebGPUSamplerAddressMode
Eq WebGPUSamplerAddressMode
-> (WebGPUSamplerAddressMode
    -> WebGPUSamplerAddressMode -> Ordering)
-> (WebGPUSamplerAddressMode -> WebGPUSamplerAddressMode -> Bool)
-> (WebGPUSamplerAddressMode -> WebGPUSamplerAddressMode -> Bool)
-> (WebGPUSamplerAddressMode -> WebGPUSamplerAddressMode -> Bool)
-> (WebGPUSamplerAddressMode -> WebGPUSamplerAddressMode -> Bool)
-> (WebGPUSamplerAddressMode
    -> WebGPUSamplerAddressMode -> WebGPUSamplerAddressMode)
-> (WebGPUSamplerAddressMode
    -> WebGPUSamplerAddressMode -> WebGPUSamplerAddressMode)
-> Ord WebGPUSamplerAddressMode
WebGPUSamplerAddressMode -> WebGPUSamplerAddressMode -> Bool
WebGPUSamplerAddressMode -> WebGPUSamplerAddressMode -> Ordering
WebGPUSamplerAddressMode
-> WebGPUSamplerAddressMode -> WebGPUSamplerAddressMode
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: WebGPUSamplerAddressMode
-> WebGPUSamplerAddressMode -> WebGPUSamplerAddressMode
$cmin :: WebGPUSamplerAddressMode
-> WebGPUSamplerAddressMode -> WebGPUSamplerAddressMode
max :: WebGPUSamplerAddressMode
-> WebGPUSamplerAddressMode -> WebGPUSamplerAddressMode
$cmax :: WebGPUSamplerAddressMode
-> WebGPUSamplerAddressMode -> WebGPUSamplerAddressMode
>= :: WebGPUSamplerAddressMode -> WebGPUSamplerAddressMode -> Bool
$c>= :: WebGPUSamplerAddressMode -> WebGPUSamplerAddressMode -> Bool
> :: WebGPUSamplerAddressMode -> WebGPUSamplerAddressMode -> Bool
$c> :: WebGPUSamplerAddressMode -> WebGPUSamplerAddressMode -> Bool
<= :: WebGPUSamplerAddressMode -> WebGPUSamplerAddressMode -> Bool
$c<= :: WebGPUSamplerAddressMode -> WebGPUSamplerAddressMode -> Bool
< :: WebGPUSamplerAddressMode -> WebGPUSamplerAddressMode -> Bool
$c< :: WebGPUSamplerAddressMode -> WebGPUSamplerAddressMode -> Bool
compare :: WebGPUSamplerAddressMode -> WebGPUSamplerAddressMode -> Ordering
$ccompare :: WebGPUSamplerAddressMode -> WebGPUSamplerAddressMode -> Ordering
$cp1Ord :: Eq WebGPUSamplerAddressMode
Ord, Typeable)
 
instance ToJSVal WebGPUSamplerAddressMode where
        toJSVal :: WebGPUSamplerAddressMode -> JSM JSVal
toJSVal WebGPUSamplerAddressMode
WebGPUSamplerAddressModeClamptoedge
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUSamplerAddressModeClamptoedge
        toJSVal WebGPUSamplerAddressMode
WebGPUSamplerAddressModeMirrorclamptoedge
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUSamplerAddressModeMirrorclamptoedge
        toJSVal WebGPUSamplerAddressMode
WebGPUSamplerAddressModeRepeat
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUSamplerAddressModeRepeat
        toJSVal WebGPUSamplerAddressMode
WebGPUSamplerAddressModeMirrorrepeat
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUSamplerAddressModeMirrorrepeat
        toJSVal WebGPUSamplerAddressMode
WebGPUSamplerAddressModeClamptozero
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUSamplerAddressModeClamptozero
 
instance FromJSVal WebGPUSamplerAddressMode where
        fromJSVal :: JSVal -> JSM (Maybe WebGPUSamplerAddressMode)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_WebGPUSamplerAddressModeClamptoedge JSM Bool
-> (Bool -> JSM (Maybe WebGPUSamplerAddressMode))
-> JSM (Maybe WebGPUSamplerAddressMode)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe WebGPUSamplerAddressMode
-> JSM (Maybe WebGPUSamplerAddressMode)
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPUSamplerAddressMode -> Maybe WebGPUSamplerAddressMode
forall a. a -> Maybe a
Just WebGPUSamplerAddressMode
WebGPUSamplerAddressModeClamptoedge)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_WebGPUSamplerAddressModeMirrorclamptoedge JSM Bool
-> (Bool -> JSM (Maybe WebGPUSamplerAddressMode))
-> JSM (Maybe WebGPUSamplerAddressMode)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe WebGPUSamplerAddressMode
-> JSM (Maybe WebGPUSamplerAddressMode)
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPUSamplerAddressMode -> Maybe WebGPUSamplerAddressMode
forall a. a -> Maybe a
Just WebGPUSamplerAddressMode
WebGPUSamplerAddressModeMirrorclamptoedge)
                                 Bool
False
                                   -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_WebGPUSamplerAddressModeRepeat JSM Bool
-> (Bool -> JSM (Maybe WebGPUSamplerAddressMode))
-> JSM (Maybe WebGPUSamplerAddressMode)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                        \ Bool
r ->
                                          case Bool
r of
                                              Bool
True -> Maybe WebGPUSamplerAddressMode
-> JSM (Maybe WebGPUSamplerAddressMode)
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPUSamplerAddressMode -> Maybe WebGPUSamplerAddressMode
forall a. a -> Maybe a
Just WebGPUSamplerAddressMode
WebGPUSamplerAddressModeRepeat)
                                              Bool
False
                                                -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                     String
js_WebGPUSamplerAddressModeMirrorrepeat
                                                     JSM Bool
-> (Bool -> JSM (Maybe WebGPUSamplerAddressMode))
-> JSM (Maybe WebGPUSamplerAddressMode)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                     \ Bool
r ->
                                                       case Bool
r of
                                                           Bool
True
                                                             -> Maybe WebGPUSamplerAddressMode
-> JSM (Maybe WebGPUSamplerAddressMode)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                  (WebGPUSamplerAddressMode -> Maybe WebGPUSamplerAddressMode
forall a. a -> Maybe a
Just
                                                                     WebGPUSamplerAddressMode
WebGPUSamplerAddressModeMirrorrepeat)
                                                           Bool
False
                                                             -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                                  String
js_WebGPUSamplerAddressModeClamptozero
                                                                  JSM Bool
-> (Bool -> JSM (Maybe WebGPUSamplerAddressMode))
-> JSM (Maybe WebGPUSamplerAddressMode)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                  \ Bool
r ->
                                                                    case Bool
r of
                                                                        Bool
True
                                                                          -> Maybe WebGPUSamplerAddressMode
-> JSM (Maybe WebGPUSamplerAddressMode)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                               (WebGPUSamplerAddressMode -> Maybe WebGPUSamplerAddressMode
forall a. a -> Maybe a
Just
                                                                                  WebGPUSamplerAddressMode
WebGPUSamplerAddressModeClamptozero)
                                                                        Bool
False -> Maybe WebGPUSamplerAddressMode
-> JSM (Maybe WebGPUSamplerAddressMode)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe WebGPUSamplerAddressMode
forall a. Maybe a
Nothing
js_WebGPUSamplerAddressModeClamptoedge :: String
js_WebGPUSamplerAddressModeClamptoedge = String
"clamptoedge"
js_WebGPUSamplerAddressModeMirrorclamptoedge :: String
js_WebGPUSamplerAddressModeMirrorclamptoedge = String
"mirrorclamptoedge"
js_WebGPUSamplerAddressModeRepeat :: String
js_WebGPUSamplerAddressModeRepeat = String
"repeat"
js_WebGPUSamplerAddressModeMirrorrepeat :: String
js_WebGPUSamplerAddressModeMirrorrepeat = String
"mirrorrepeat"
js_WebGPUSamplerAddressModeClamptozero :: String
js_WebGPUSamplerAddressModeClamptozero = String
"clamptozero"
 
data WebGPUSamplerMinMagFilter = WebGPUSamplerMinMagFilterNearest
                               | WebGPUSamplerMinMagFilterLinear
                               deriving (Int -> WebGPUSamplerMinMagFilter -> ShowS
[WebGPUSamplerMinMagFilter] -> ShowS
WebGPUSamplerMinMagFilter -> String
(Int -> WebGPUSamplerMinMagFilter -> ShowS)
-> (WebGPUSamplerMinMagFilter -> String)
-> ([WebGPUSamplerMinMagFilter] -> ShowS)
-> Show WebGPUSamplerMinMagFilter
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WebGPUSamplerMinMagFilter] -> ShowS
$cshowList :: [WebGPUSamplerMinMagFilter] -> ShowS
show :: WebGPUSamplerMinMagFilter -> String
$cshow :: WebGPUSamplerMinMagFilter -> String
showsPrec :: Int -> WebGPUSamplerMinMagFilter -> ShowS
$cshowsPrec :: Int -> WebGPUSamplerMinMagFilter -> ShowS
Show, ReadPrec [WebGPUSamplerMinMagFilter]
ReadPrec WebGPUSamplerMinMagFilter
Int -> ReadS WebGPUSamplerMinMagFilter
ReadS [WebGPUSamplerMinMagFilter]
(Int -> ReadS WebGPUSamplerMinMagFilter)
-> ReadS [WebGPUSamplerMinMagFilter]
-> ReadPrec WebGPUSamplerMinMagFilter
-> ReadPrec [WebGPUSamplerMinMagFilter]
-> Read WebGPUSamplerMinMagFilter
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [WebGPUSamplerMinMagFilter]
$creadListPrec :: ReadPrec [WebGPUSamplerMinMagFilter]
readPrec :: ReadPrec WebGPUSamplerMinMagFilter
$creadPrec :: ReadPrec WebGPUSamplerMinMagFilter
readList :: ReadS [WebGPUSamplerMinMagFilter]
$creadList :: ReadS [WebGPUSamplerMinMagFilter]
readsPrec :: Int -> ReadS WebGPUSamplerMinMagFilter
$creadsPrec :: Int -> ReadS WebGPUSamplerMinMagFilter
Read, WebGPUSamplerMinMagFilter -> WebGPUSamplerMinMagFilter -> Bool
(WebGPUSamplerMinMagFilter -> WebGPUSamplerMinMagFilter -> Bool)
-> (WebGPUSamplerMinMagFilter -> WebGPUSamplerMinMagFilter -> Bool)
-> Eq WebGPUSamplerMinMagFilter
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WebGPUSamplerMinMagFilter -> WebGPUSamplerMinMagFilter -> Bool
$c/= :: WebGPUSamplerMinMagFilter -> WebGPUSamplerMinMagFilter -> Bool
== :: WebGPUSamplerMinMagFilter -> WebGPUSamplerMinMagFilter -> Bool
$c== :: WebGPUSamplerMinMagFilter -> WebGPUSamplerMinMagFilter -> Bool
Eq, Eq WebGPUSamplerMinMagFilter
Eq WebGPUSamplerMinMagFilter
-> (WebGPUSamplerMinMagFilter
    -> WebGPUSamplerMinMagFilter -> Ordering)
-> (WebGPUSamplerMinMagFilter -> WebGPUSamplerMinMagFilter -> Bool)
-> (WebGPUSamplerMinMagFilter -> WebGPUSamplerMinMagFilter -> Bool)
-> (WebGPUSamplerMinMagFilter -> WebGPUSamplerMinMagFilter -> Bool)
-> (WebGPUSamplerMinMagFilter -> WebGPUSamplerMinMagFilter -> Bool)
-> (WebGPUSamplerMinMagFilter
    -> WebGPUSamplerMinMagFilter -> WebGPUSamplerMinMagFilter)
-> (WebGPUSamplerMinMagFilter
    -> WebGPUSamplerMinMagFilter -> WebGPUSamplerMinMagFilter)
-> Ord WebGPUSamplerMinMagFilter
WebGPUSamplerMinMagFilter -> WebGPUSamplerMinMagFilter -> Bool
WebGPUSamplerMinMagFilter -> WebGPUSamplerMinMagFilter -> Ordering
WebGPUSamplerMinMagFilter
-> WebGPUSamplerMinMagFilter -> WebGPUSamplerMinMagFilter
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: WebGPUSamplerMinMagFilter
-> WebGPUSamplerMinMagFilter -> WebGPUSamplerMinMagFilter
$cmin :: WebGPUSamplerMinMagFilter
-> WebGPUSamplerMinMagFilter -> WebGPUSamplerMinMagFilter
max :: WebGPUSamplerMinMagFilter
-> WebGPUSamplerMinMagFilter -> WebGPUSamplerMinMagFilter
$cmax :: WebGPUSamplerMinMagFilter
-> WebGPUSamplerMinMagFilter -> WebGPUSamplerMinMagFilter
>= :: WebGPUSamplerMinMagFilter -> WebGPUSamplerMinMagFilter -> Bool
$c>= :: WebGPUSamplerMinMagFilter -> WebGPUSamplerMinMagFilter -> Bool
> :: WebGPUSamplerMinMagFilter -> WebGPUSamplerMinMagFilter -> Bool
$c> :: WebGPUSamplerMinMagFilter -> WebGPUSamplerMinMagFilter -> Bool
<= :: WebGPUSamplerMinMagFilter -> WebGPUSamplerMinMagFilter -> Bool
$c<= :: WebGPUSamplerMinMagFilter -> WebGPUSamplerMinMagFilter -> Bool
< :: WebGPUSamplerMinMagFilter -> WebGPUSamplerMinMagFilter -> Bool
$c< :: WebGPUSamplerMinMagFilter -> WebGPUSamplerMinMagFilter -> Bool
compare :: WebGPUSamplerMinMagFilter -> WebGPUSamplerMinMagFilter -> Ordering
$ccompare :: WebGPUSamplerMinMagFilter -> WebGPUSamplerMinMagFilter -> Ordering
$cp1Ord :: Eq WebGPUSamplerMinMagFilter
Ord, Typeable)
 
instance ToJSVal WebGPUSamplerMinMagFilter where
        toJSVal :: WebGPUSamplerMinMagFilter -> JSM JSVal
toJSVal WebGPUSamplerMinMagFilter
WebGPUSamplerMinMagFilterNearest
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUSamplerMinMagFilterNearest
        toJSVal WebGPUSamplerMinMagFilter
WebGPUSamplerMinMagFilterLinear
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUSamplerMinMagFilterLinear
 
instance FromJSVal WebGPUSamplerMinMagFilter where
        fromJSVal :: JSVal -> JSM (Maybe WebGPUSamplerMinMagFilter)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_WebGPUSamplerMinMagFilterNearest JSM Bool
-> (Bool -> JSM (Maybe WebGPUSamplerMinMagFilter))
-> JSM (Maybe WebGPUSamplerMinMagFilter)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe WebGPUSamplerMinMagFilter
-> JSM (Maybe WebGPUSamplerMinMagFilter)
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPUSamplerMinMagFilter -> Maybe WebGPUSamplerMinMagFilter
forall a. a -> Maybe a
Just WebGPUSamplerMinMagFilter
WebGPUSamplerMinMagFilterNearest)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_WebGPUSamplerMinMagFilterLinear JSM Bool
-> (Bool -> JSM (Maybe WebGPUSamplerMinMagFilter))
-> JSM (Maybe WebGPUSamplerMinMagFilter)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe WebGPUSamplerMinMagFilter
-> JSM (Maybe WebGPUSamplerMinMagFilter)
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPUSamplerMinMagFilter -> Maybe WebGPUSamplerMinMagFilter
forall a. a -> Maybe a
Just WebGPUSamplerMinMagFilter
WebGPUSamplerMinMagFilterLinear)
                                 Bool
False -> Maybe WebGPUSamplerMinMagFilter
-> JSM (Maybe WebGPUSamplerMinMagFilter)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe WebGPUSamplerMinMagFilter
forall a. Maybe a
Nothing
js_WebGPUSamplerMinMagFilterNearest :: String
js_WebGPUSamplerMinMagFilterNearest = String
"nearest"
js_WebGPUSamplerMinMagFilterLinear :: String
js_WebGPUSamplerMinMagFilterLinear = String
"linear"
 
data WebGPUSamplerMipFilter = WebGPUSamplerMipFilterNotmipmapped
                            | WebGPUSamplerMipFilterNearest
                            | WebGPUSamplerMipFilterLinear
                            deriving (Int -> WebGPUSamplerMipFilter -> ShowS
[WebGPUSamplerMipFilter] -> ShowS
WebGPUSamplerMipFilter -> String
(Int -> WebGPUSamplerMipFilter -> ShowS)
-> (WebGPUSamplerMipFilter -> String)
-> ([WebGPUSamplerMipFilter] -> ShowS)
-> Show WebGPUSamplerMipFilter
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WebGPUSamplerMipFilter] -> ShowS
$cshowList :: [WebGPUSamplerMipFilter] -> ShowS
show :: WebGPUSamplerMipFilter -> String
$cshow :: WebGPUSamplerMipFilter -> String
showsPrec :: Int -> WebGPUSamplerMipFilter -> ShowS
$cshowsPrec :: Int -> WebGPUSamplerMipFilter -> ShowS
Show, ReadPrec [WebGPUSamplerMipFilter]
ReadPrec WebGPUSamplerMipFilter
Int -> ReadS WebGPUSamplerMipFilter
ReadS [WebGPUSamplerMipFilter]
(Int -> ReadS WebGPUSamplerMipFilter)
-> ReadS [WebGPUSamplerMipFilter]
-> ReadPrec WebGPUSamplerMipFilter
-> ReadPrec [WebGPUSamplerMipFilter]
-> Read WebGPUSamplerMipFilter
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [WebGPUSamplerMipFilter]
$creadListPrec :: ReadPrec [WebGPUSamplerMipFilter]
readPrec :: ReadPrec WebGPUSamplerMipFilter
$creadPrec :: ReadPrec WebGPUSamplerMipFilter
readList :: ReadS [WebGPUSamplerMipFilter]
$creadList :: ReadS [WebGPUSamplerMipFilter]
readsPrec :: Int -> ReadS WebGPUSamplerMipFilter
$creadsPrec :: Int -> ReadS WebGPUSamplerMipFilter
Read, WebGPUSamplerMipFilter -> WebGPUSamplerMipFilter -> Bool
(WebGPUSamplerMipFilter -> WebGPUSamplerMipFilter -> Bool)
-> (WebGPUSamplerMipFilter -> WebGPUSamplerMipFilter -> Bool)
-> Eq WebGPUSamplerMipFilter
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WebGPUSamplerMipFilter -> WebGPUSamplerMipFilter -> Bool
$c/= :: WebGPUSamplerMipFilter -> WebGPUSamplerMipFilter -> Bool
== :: WebGPUSamplerMipFilter -> WebGPUSamplerMipFilter -> Bool
$c== :: WebGPUSamplerMipFilter -> WebGPUSamplerMipFilter -> Bool
Eq, Eq WebGPUSamplerMipFilter
Eq WebGPUSamplerMipFilter
-> (WebGPUSamplerMipFilter -> WebGPUSamplerMipFilter -> Ordering)
-> (WebGPUSamplerMipFilter -> WebGPUSamplerMipFilter -> Bool)
-> (WebGPUSamplerMipFilter -> WebGPUSamplerMipFilter -> Bool)
-> (WebGPUSamplerMipFilter -> WebGPUSamplerMipFilter -> Bool)
-> (WebGPUSamplerMipFilter -> WebGPUSamplerMipFilter -> Bool)
-> (WebGPUSamplerMipFilter
    -> WebGPUSamplerMipFilter -> WebGPUSamplerMipFilter)
-> (WebGPUSamplerMipFilter
    -> WebGPUSamplerMipFilter -> WebGPUSamplerMipFilter)
-> Ord WebGPUSamplerMipFilter
WebGPUSamplerMipFilter -> WebGPUSamplerMipFilter -> Bool
WebGPUSamplerMipFilter -> WebGPUSamplerMipFilter -> Ordering
WebGPUSamplerMipFilter
-> WebGPUSamplerMipFilter -> WebGPUSamplerMipFilter
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: WebGPUSamplerMipFilter
-> WebGPUSamplerMipFilter -> WebGPUSamplerMipFilter
$cmin :: WebGPUSamplerMipFilter
-> WebGPUSamplerMipFilter -> WebGPUSamplerMipFilter
max :: WebGPUSamplerMipFilter
-> WebGPUSamplerMipFilter -> WebGPUSamplerMipFilter
$cmax :: WebGPUSamplerMipFilter
-> WebGPUSamplerMipFilter -> WebGPUSamplerMipFilter
>= :: WebGPUSamplerMipFilter -> WebGPUSamplerMipFilter -> Bool
$c>= :: WebGPUSamplerMipFilter -> WebGPUSamplerMipFilter -> Bool
> :: WebGPUSamplerMipFilter -> WebGPUSamplerMipFilter -> Bool
$c> :: WebGPUSamplerMipFilter -> WebGPUSamplerMipFilter -> Bool
<= :: WebGPUSamplerMipFilter -> WebGPUSamplerMipFilter -> Bool
$c<= :: WebGPUSamplerMipFilter -> WebGPUSamplerMipFilter -> Bool
< :: WebGPUSamplerMipFilter -> WebGPUSamplerMipFilter -> Bool
$c< :: WebGPUSamplerMipFilter -> WebGPUSamplerMipFilter -> Bool
compare :: WebGPUSamplerMipFilter -> WebGPUSamplerMipFilter -> Ordering
$ccompare :: WebGPUSamplerMipFilter -> WebGPUSamplerMipFilter -> Ordering
$cp1Ord :: Eq WebGPUSamplerMipFilter
Ord, Typeable)
 
instance ToJSVal WebGPUSamplerMipFilter where
        toJSVal :: WebGPUSamplerMipFilter -> JSM JSVal
toJSVal WebGPUSamplerMipFilter
WebGPUSamplerMipFilterNotmipmapped
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUSamplerMipFilterNotmipmapped
        toJSVal WebGPUSamplerMipFilter
WebGPUSamplerMipFilterNearest
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUSamplerMipFilterNearest
        toJSVal WebGPUSamplerMipFilter
WebGPUSamplerMipFilterLinear
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUSamplerMipFilterLinear
 
instance FromJSVal WebGPUSamplerMipFilter where
        fromJSVal :: JSVal -> JSM (Maybe WebGPUSamplerMipFilter)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_WebGPUSamplerMipFilterNotmipmapped JSM Bool
-> (Bool -> JSM (Maybe WebGPUSamplerMipFilter))
-> JSM (Maybe WebGPUSamplerMipFilter)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe WebGPUSamplerMipFilter -> JSM (Maybe WebGPUSamplerMipFilter)
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPUSamplerMipFilter -> Maybe WebGPUSamplerMipFilter
forall a. a -> Maybe a
Just WebGPUSamplerMipFilter
WebGPUSamplerMipFilterNotmipmapped)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_WebGPUSamplerMipFilterNearest JSM Bool
-> (Bool -> JSM (Maybe WebGPUSamplerMipFilter))
-> JSM (Maybe WebGPUSamplerMipFilter)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe WebGPUSamplerMipFilter -> JSM (Maybe WebGPUSamplerMipFilter)
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPUSamplerMipFilter -> Maybe WebGPUSamplerMipFilter
forall a. a -> Maybe a
Just WebGPUSamplerMipFilter
WebGPUSamplerMipFilterNearest)
                                 Bool
False
                                   -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_WebGPUSamplerMipFilterLinear JSM Bool
-> (Bool -> JSM (Maybe WebGPUSamplerMipFilter))
-> JSM (Maybe WebGPUSamplerMipFilter)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                        \ Bool
r ->
                                          case Bool
r of
                                              Bool
True -> Maybe WebGPUSamplerMipFilter -> JSM (Maybe WebGPUSamplerMipFilter)
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPUSamplerMipFilter -> Maybe WebGPUSamplerMipFilter
forall a. a -> Maybe a
Just WebGPUSamplerMipFilter
WebGPUSamplerMipFilterLinear)
                                              Bool
False -> Maybe WebGPUSamplerMipFilter -> JSM (Maybe WebGPUSamplerMipFilter)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe WebGPUSamplerMipFilter
forall a. Maybe a
Nothing
js_WebGPUSamplerMipFilterNotmipmapped :: String
js_WebGPUSamplerMipFilterNotmipmapped = String
"notmipmapped"
js_WebGPUSamplerMipFilterNearest :: String
js_WebGPUSamplerMipFilterNearest = String
"nearest"
js_WebGPUSamplerMipFilterLinear :: String
js_WebGPUSamplerMipFilterLinear = String
"linear"
 
data WebGPUCullMode = WebGPUCullModeNone
                    | WebGPUCullModeFront
                    | WebGPUCullModeBack
                    deriving (Int -> WebGPUCullMode -> ShowS
[WebGPUCullMode] -> ShowS
WebGPUCullMode -> String
(Int -> WebGPUCullMode -> ShowS)
-> (WebGPUCullMode -> String)
-> ([WebGPUCullMode] -> ShowS)
-> Show WebGPUCullMode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WebGPUCullMode] -> ShowS
$cshowList :: [WebGPUCullMode] -> ShowS
show :: WebGPUCullMode -> String
$cshow :: WebGPUCullMode -> String
showsPrec :: Int -> WebGPUCullMode -> ShowS
$cshowsPrec :: Int -> WebGPUCullMode -> ShowS
Show, ReadPrec [WebGPUCullMode]
ReadPrec WebGPUCullMode
Int -> ReadS WebGPUCullMode
ReadS [WebGPUCullMode]
(Int -> ReadS WebGPUCullMode)
-> ReadS [WebGPUCullMode]
-> ReadPrec WebGPUCullMode
-> ReadPrec [WebGPUCullMode]
-> Read WebGPUCullMode
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [WebGPUCullMode]
$creadListPrec :: ReadPrec [WebGPUCullMode]
readPrec :: ReadPrec WebGPUCullMode
$creadPrec :: ReadPrec WebGPUCullMode
readList :: ReadS [WebGPUCullMode]
$creadList :: ReadS [WebGPUCullMode]
readsPrec :: Int -> ReadS WebGPUCullMode
$creadsPrec :: Int -> ReadS WebGPUCullMode
Read, WebGPUCullMode -> WebGPUCullMode -> Bool
(WebGPUCullMode -> WebGPUCullMode -> Bool)
-> (WebGPUCullMode -> WebGPUCullMode -> Bool) -> Eq WebGPUCullMode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WebGPUCullMode -> WebGPUCullMode -> Bool
$c/= :: WebGPUCullMode -> WebGPUCullMode -> Bool
== :: WebGPUCullMode -> WebGPUCullMode -> Bool
$c== :: WebGPUCullMode -> WebGPUCullMode -> Bool
Eq, Eq WebGPUCullMode
Eq WebGPUCullMode
-> (WebGPUCullMode -> WebGPUCullMode -> Ordering)
-> (WebGPUCullMode -> WebGPUCullMode -> Bool)
-> (WebGPUCullMode -> WebGPUCullMode -> Bool)
-> (WebGPUCullMode -> WebGPUCullMode -> Bool)
-> (WebGPUCullMode -> WebGPUCullMode -> Bool)
-> (WebGPUCullMode -> WebGPUCullMode -> WebGPUCullMode)
-> (WebGPUCullMode -> WebGPUCullMode -> WebGPUCullMode)
-> Ord WebGPUCullMode
WebGPUCullMode -> WebGPUCullMode -> Bool
WebGPUCullMode -> WebGPUCullMode -> Ordering
WebGPUCullMode -> WebGPUCullMode -> WebGPUCullMode
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: WebGPUCullMode -> WebGPUCullMode -> WebGPUCullMode
$cmin :: WebGPUCullMode -> WebGPUCullMode -> WebGPUCullMode
max :: WebGPUCullMode -> WebGPUCullMode -> WebGPUCullMode
$cmax :: WebGPUCullMode -> WebGPUCullMode -> WebGPUCullMode
>= :: WebGPUCullMode -> WebGPUCullMode -> Bool
$c>= :: WebGPUCullMode -> WebGPUCullMode -> Bool
> :: WebGPUCullMode -> WebGPUCullMode -> Bool
$c> :: WebGPUCullMode -> WebGPUCullMode -> Bool
<= :: WebGPUCullMode -> WebGPUCullMode -> Bool
$c<= :: WebGPUCullMode -> WebGPUCullMode -> Bool
< :: WebGPUCullMode -> WebGPUCullMode -> Bool
$c< :: WebGPUCullMode -> WebGPUCullMode -> Bool
compare :: WebGPUCullMode -> WebGPUCullMode -> Ordering
$ccompare :: WebGPUCullMode -> WebGPUCullMode -> Ordering
$cp1Ord :: Eq WebGPUCullMode
Ord, Typeable)
 
instance ToJSVal WebGPUCullMode where
        toJSVal :: WebGPUCullMode -> JSM JSVal
toJSVal WebGPUCullMode
WebGPUCullModeNone = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUCullModeNone
        toJSVal WebGPUCullMode
WebGPUCullModeFront = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUCullModeFront
        toJSVal WebGPUCullMode
WebGPUCullModeBack = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUCullModeBack
 
instance FromJSVal WebGPUCullMode where
        fromJSVal :: JSVal -> JSM (Maybe WebGPUCullMode)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_WebGPUCullModeNone JSM Bool
-> (Bool -> JSM (Maybe WebGPUCullMode))
-> JSM (Maybe WebGPUCullMode)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe WebGPUCullMode -> JSM (Maybe WebGPUCullMode)
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPUCullMode -> Maybe WebGPUCullMode
forall a. a -> Maybe a
Just WebGPUCullMode
WebGPUCullModeNone)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_WebGPUCullModeFront JSM Bool
-> (Bool -> JSM (Maybe WebGPUCullMode))
-> JSM (Maybe WebGPUCullMode)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe WebGPUCullMode -> JSM (Maybe WebGPUCullMode)
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPUCullMode -> Maybe WebGPUCullMode
forall a. a -> Maybe a
Just WebGPUCullMode
WebGPUCullModeFront)
                                 Bool
False
                                   -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_WebGPUCullModeBack JSM Bool
-> (Bool -> JSM (Maybe WebGPUCullMode))
-> JSM (Maybe WebGPUCullMode)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                        \ Bool
r ->
                                          case Bool
r of
                                              Bool
True -> Maybe WebGPUCullMode -> JSM (Maybe WebGPUCullMode)
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPUCullMode -> Maybe WebGPUCullMode
forall a. a -> Maybe a
Just WebGPUCullMode
WebGPUCullModeBack)
                                              Bool
False -> Maybe WebGPUCullMode -> JSM (Maybe WebGPUCullMode)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe WebGPUCullMode
forall a. Maybe a
Nothing
js_WebGPUCullModeNone :: String
js_WebGPUCullModeNone = String
"none"
js_WebGPUCullModeFront :: String
js_WebGPUCullModeFront = String
"front"
js_WebGPUCullModeBack :: String
js_WebGPUCullModeBack = String
"back"
 
data WebGPUIndexType = WebGPUIndexTypeUint16
                     | WebGPUIndexTypeUint32
                     deriving (Int -> WebGPUIndexType -> ShowS
[WebGPUIndexType] -> ShowS
WebGPUIndexType -> String
(Int -> WebGPUIndexType -> ShowS)
-> (WebGPUIndexType -> String)
-> ([WebGPUIndexType] -> ShowS)
-> Show WebGPUIndexType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WebGPUIndexType] -> ShowS
$cshowList :: [WebGPUIndexType] -> ShowS
show :: WebGPUIndexType -> String
$cshow :: WebGPUIndexType -> String
showsPrec :: Int -> WebGPUIndexType -> ShowS
$cshowsPrec :: Int -> WebGPUIndexType -> ShowS
Show, ReadPrec [WebGPUIndexType]
ReadPrec WebGPUIndexType
Int -> ReadS WebGPUIndexType
ReadS [WebGPUIndexType]
(Int -> ReadS WebGPUIndexType)
-> ReadS [WebGPUIndexType]
-> ReadPrec WebGPUIndexType
-> ReadPrec [WebGPUIndexType]
-> Read WebGPUIndexType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [WebGPUIndexType]
$creadListPrec :: ReadPrec [WebGPUIndexType]
readPrec :: ReadPrec WebGPUIndexType
$creadPrec :: ReadPrec WebGPUIndexType
readList :: ReadS [WebGPUIndexType]
$creadList :: ReadS [WebGPUIndexType]
readsPrec :: Int -> ReadS WebGPUIndexType
$creadsPrec :: Int -> ReadS WebGPUIndexType
Read, WebGPUIndexType -> WebGPUIndexType -> Bool
(WebGPUIndexType -> WebGPUIndexType -> Bool)
-> (WebGPUIndexType -> WebGPUIndexType -> Bool)
-> Eq WebGPUIndexType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WebGPUIndexType -> WebGPUIndexType -> Bool
$c/= :: WebGPUIndexType -> WebGPUIndexType -> Bool
== :: WebGPUIndexType -> WebGPUIndexType -> Bool
$c== :: WebGPUIndexType -> WebGPUIndexType -> Bool
Eq, Eq WebGPUIndexType
Eq WebGPUIndexType
-> (WebGPUIndexType -> WebGPUIndexType -> Ordering)
-> (WebGPUIndexType -> WebGPUIndexType -> Bool)
-> (WebGPUIndexType -> WebGPUIndexType -> Bool)
-> (WebGPUIndexType -> WebGPUIndexType -> Bool)
-> (WebGPUIndexType -> WebGPUIndexType -> Bool)
-> (WebGPUIndexType -> WebGPUIndexType -> WebGPUIndexType)
-> (WebGPUIndexType -> WebGPUIndexType -> WebGPUIndexType)
-> Ord WebGPUIndexType
WebGPUIndexType -> WebGPUIndexType -> Bool
WebGPUIndexType -> WebGPUIndexType -> Ordering
WebGPUIndexType -> WebGPUIndexType -> WebGPUIndexType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: WebGPUIndexType -> WebGPUIndexType -> WebGPUIndexType
$cmin :: WebGPUIndexType -> WebGPUIndexType -> WebGPUIndexType
max :: WebGPUIndexType -> WebGPUIndexType -> WebGPUIndexType
$cmax :: WebGPUIndexType -> WebGPUIndexType -> WebGPUIndexType
>= :: WebGPUIndexType -> WebGPUIndexType -> Bool
$c>= :: WebGPUIndexType -> WebGPUIndexType -> Bool
> :: WebGPUIndexType -> WebGPUIndexType -> Bool
$c> :: WebGPUIndexType -> WebGPUIndexType -> Bool
<= :: WebGPUIndexType -> WebGPUIndexType -> Bool
$c<= :: WebGPUIndexType -> WebGPUIndexType -> Bool
< :: WebGPUIndexType -> WebGPUIndexType -> Bool
$c< :: WebGPUIndexType -> WebGPUIndexType -> Bool
compare :: WebGPUIndexType -> WebGPUIndexType -> Ordering
$ccompare :: WebGPUIndexType -> WebGPUIndexType -> Ordering
$cp1Ord :: Eq WebGPUIndexType
Ord, Typeable)
 
instance ToJSVal WebGPUIndexType where
        toJSVal :: WebGPUIndexType -> JSM JSVal
toJSVal WebGPUIndexType
WebGPUIndexTypeUint16 = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUIndexTypeUint16
        toJSVal WebGPUIndexType
WebGPUIndexTypeUint32 = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUIndexTypeUint32
 
instance FromJSVal WebGPUIndexType where
        fromJSVal :: JSVal -> JSM (Maybe WebGPUIndexType)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_WebGPUIndexTypeUint16 JSM Bool
-> (Bool -> JSM (Maybe WebGPUIndexType))
-> JSM (Maybe WebGPUIndexType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe WebGPUIndexType -> JSM (Maybe WebGPUIndexType)
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPUIndexType -> Maybe WebGPUIndexType
forall a. a -> Maybe a
Just WebGPUIndexType
WebGPUIndexTypeUint16)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_WebGPUIndexTypeUint32 JSM Bool
-> (Bool -> JSM (Maybe WebGPUIndexType))
-> JSM (Maybe WebGPUIndexType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe WebGPUIndexType -> JSM (Maybe WebGPUIndexType)
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPUIndexType -> Maybe WebGPUIndexType
forall a. a -> Maybe a
Just WebGPUIndexType
WebGPUIndexTypeUint32)
                                 Bool
False -> Maybe WebGPUIndexType -> JSM (Maybe WebGPUIndexType)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe WebGPUIndexType
forall a. Maybe a
Nothing
js_WebGPUIndexTypeUint16 :: String
js_WebGPUIndexTypeUint16 = String
"uint16"
js_WebGPUIndexTypeUint32 :: String
js_WebGPUIndexTypeUint32 = String
"uint32"
 
data WebGPUVisibilityResultMode = WebGPUVisibilityResultModeDisabled
                                | WebGPUVisibilityResultModeBoolean
                                | WebGPUVisibilityResultModeCounting
                                deriving (Int -> WebGPUVisibilityResultMode -> ShowS
[WebGPUVisibilityResultMode] -> ShowS
WebGPUVisibilityResultMode -> String
(Int -> WebGPUVisibilityResultMode -> ShowS)
-> (WebGPUVisibilityResultMode -> String)
-> ([WebGPUVisibilityResultMode] -> ShowS)
-> Show WebGPUVisibilityResultMode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WebGPUVisibilityResultMode] -> ShowS
$cshowList :: [WebGPUVisibilityResultMode] -> ShowS
show :: WebGPUVisibilityResultMode -> String
$cshow :: WebGPUVisibilityResultMode -> String
showsPrec :: Int -> WebGPUVisibilityResultMode -> ShowS
$cshowsPrec :: Int -> WebGPUVisibilityResultMode -> ShowS
Show, ReadPrec [WebGPUVisibilityResultMode]
ReadPrec WebGPUVisibilityResultMode
Int -> ReadS WebGPUVisibilityResultMode
ReadS [WebGPUVisibilityResultMode]
(Int -> ReadS WebGPUVisibilityResultMode)
-> ReadS [WebGPUVisibilityResultMode]
-> ReadPrec WebGPUVisibilityResultMode
-> ReadPrec [WebGPUVisibilityResultMode]
-> Read WebGPUVisibilityResultMode
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [WebGPUVisibilityResultMode]
$creadListPrec :: ReadPrec [WebGPUVisibilityResultMode]
readPrec :: ReadPrec WebGPUVisibilityResultMode
$creadPrec :: ReadPrec WebGPUVisibilityResultMode
readList :: ReadS [WebGPUVisibilityResultMode]
$creadList :: ReadS [WebGPUVisibilityResultMode]
readsPrec :: Int -> ReadS WebGPUVisibilityResultMode
$creadsPrec :: Int -> ReadS WebGPUVisibilityResultMode
Read, WebGPUVisibilityResultMode -> WebGPUVisibilityResultMode -> Bool
(WebGPUVisibilityResultMode -> WebGPUVisibilityResultMode -> Bool)
-> (WebGPUVisibilityResultMode
    -> WebGPUVisibilityResultMode -> Bool)
-> Eq WebGPUVisibilityResultMode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WebGPUVisibilityResultMode -> WebGPUVisibilityResultMode -> Bool
$c/= :: WebGPUVisibilityResultMode -> WebGPUVisibilityResultMode -> Bool
== :: WebGPUVisibilityResultMode -> WebGPUVisibilityResultMode -> Bool
$c== :: WebGPUVisibilityResultMode -> WebGPUVisibilityResultMode -> Bool
Eq, Eq WebGPUVisibilityResultMode
Eq WebGPUVisibilityResultMode
-> (WebGPUVisibilityResultMode
    -> WebGPUVisibilityResultMode -> Ordering)
-> (WebGPUVisibilityResultMode
    -> WebGPUVisibilityResultMode -> Bool)
-> (WebGPUVisibilityResultMode
    -> WebGPUVisibilityResultMode -> Bool)
-> (WebGPUVisibilityResultMode
    -> WebGPUVisibilityResultMode -> Bool)
-> (WebGPUVisibilityResultMode
    -> WebGPUVisibilityResultMode -> Bool)
-> (WebGPUVisibilityResultMode
    -> WebGPUVisibilityResultMode -> WebGPUVisibilityResultMode)
-> (WebGPUVisibilityResultMode
    -> WebGPUVisibilityResultMode -> WebGPUVisibilityResultMode)
-> Ord WebGPUVisibilityResultMode
WebGPUVisibilityResultMode -> WebGPUVisibilityResultMode -> Bool
WebGPUVisibilityResultMode
-> WebGPUVisibilityResultMode -> Ordering
WebGPUVisibilityResultMode
-> WebGPUVisibilityResultMode -> WebGPUVisibilityResultMode
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: WebGPUVisibilityResultMode
-> WebGPUVisibilityResultMode -> WebGPUVisibilityResultMode
$cmin :: WebGPUVisibilityResultMode
-> WebGPUVisibilityResultMode -> WebGPUVisibilityResultMode
max :: WebGPUVisibilityResultMode
-> WebGPUVisibilityResultMode -> WebGPUVisibilityResultMode
$cmax :: WebGPUVisibilityResultMode
-> WebGPUVisibilityResultMode -> WebGPUVisibilityResultMode
>= :: WebGPUVisibilityResultMode -> WebGPUVisibilityResultMode -> Bool
$c>= :: WebGPUVisibilityResultMode -> WebGPUVisibilityResultMode -> Bool
> :: WebGPUVisibilityResultMode -> WebGPUVisibilityResultMode -> Bool
$c> :: WebGPUVisibilityResultMode -> WebGPUVisibilityResultMode -> Bool
<= :: WebGPUVisibilityResultMode -> WebGPUVisibilityResultMode -> Bool
$c<= :: WebGPUVisibilityResultMode -> WebGPUVisibilityResultMode -> Bool
< :: WebGPUVisibilityResultMode -> WebGPUVisibilityResultMode -> Bool
$c< :: WebGPUVisibilityResultMode -> WebGPUVisibilityResultMode -> Bool
compare :: WebGPUVisibilityResultMode
-> WebGPUVisibilityResultMode -> Ordering
$ccompare :: WebGPUVisibilityResultMode
-> WebGPUVisibilityResultMode -> Ordering
$cp1Ord :: Eq WebGPUVisibilityResultMode
Ord, Typeable)
 
instance ToJSVal WebGPUVisibilityResultMode where
        toJSVal :: WebGPUVisibilityResultMode -> JSM JSVal
toJSVal WebGPUVisibilityResultMode
WebGPUVisibilityResultModeDisabled
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUVisibilityResultModeDisabled
        toJSVal WebGPUVisibilityResultMode
WebGPUVisibilityResultModeBoolean
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUVisibilityResultModeBoolean
        toJSVal WebGPUVisibilityResultMode
WebGPUVisibilityResultModeCounting
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUVisibilityResultModeCounting
 
instance FromJSVal WebGPUVisibilityResultMode where
        fromJSVal :: JSVal -> JSM (Maybe WebGPUVisibilityResultMode)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_WebGPUVisibilityResultModeDisabled JSM Bool
-> (Bool -> JSM (Maybe WebGPUVisibilityResultMode))
-> JSM (Maybe WebGPUVisibilityResultMode)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe WebGPUVisibilityResultMode
-> JSM (Maybe WebGPUVisibilityResultMode)
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPUVisibilityResultMode -> Maybe WebGPUVisibilityResultMode
forall a. a -> Maybe a
Just WebGPUVisibilityResultMode
WebGPUVisibilityResultModeDisabled)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_WebGPUVisibilityResultModeBoolean JSM Bool
-> (Bool -> JSM (Maybe WebGPUVisibilityResultMode))
-> JSM (Maybe WebGPUVisibilityResultMode)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe WebGPUVisibilityResultMode
-> JSM (Maybe WebGPUVisibilityResultMode)
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPUVisibilityResultMode -> Maybe WebGPUVisibilityResultMode
forall a. a -> Maybe a
Just WebGPUVisibilityResultMode
WebGPUVisibilityResultModeBoolean)
                                 Bool
False
                                   -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_WebGPUVisibilityResultModeCounting JSM Bool
-> (Bool -> JSM (Maybe WebGPUVisibilityResultMode))
-> JSM (Maybe WebGPUVisibilityResultMode)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                        \ Bool
r ->
                                          case Bool
r of
                                              Bool
True
                                                -> Maybe WebGPUVisibilityResultMode
-> JSM (Maybe WebGPUVisibilityResultMode)
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPUVisibilityResultMode -> Maybe WebGPUVisibilityResultMode
forall a. a -> Maybe a
Just WebGPUVisibilityResultMode
WebGPUVisibilityResultModeCounting)
                                              Bool
False -> Maybe WebGPUVisibilityResultMode
-> JSM (Maybe WebGPUVisibilityResultMode)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe WebGPUVisibilityResultMode
forall a. Maybe a
Nothing
js_WebGPUVisibilityResultModeDisabled :: String
js_WebGPUVisibilityResultModeDisabled = String
"disabled"
js_WebGPUVisibilityResultModeBoolean :: String
js_WebGPUVisibilityResultModeBoolean = String
"boolean"
js_WebGPUVisibilityResultModeCounting :: String
js_WebGPUVisibilityResultModeCounting = String
"counting"
 
data WebGPUWinding = WebGPUWindingClockwise
                   | WebGPUWindingCounterclockwise
                   deriving (Int -> WebGPUWinding -> ShowS
[WebGPUWinding] -> ShowS
WebGPUWinding -> String
(Int -> WebGPUWinding -> ShowS)
-> (WebGPUWinding -> String)
-> ([WebGPUWinding] -> ShowS)
-> Show WebGPUWinding
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WebGPUWinding] -> ShowS
$cshowList :: [WebGPUWinding] -> ShowS
show :: WebGPUWinding -> String
$cshow :: WebGPUWinding -> String
showsPrec :: Int -> WebGPUWinding -> ShowS
$cshowsPrec :: Int -> WebGPUWinding -> ShowS
Show, ReadPrec [WebGPUWinding]
ReadPrec WebGPUWinding
Int -> ReadS WebGPUWinding
ReadS [WebGPUWinding]
(Int -> ReadS WebGPUWinding)
-> ReadS [WebGPUWinding]
-> ReadPrec WebGPUWinding
-> ReadPrec [WebGPUWinding]
-> Read WebGPUWinding
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [WebGPUWinding]
$creadListPrec :: ReadPrec [WebGPUWinding]
readPrec :: ReadPrec WebGPUWinding
$creadPrec :: ReadPrec WebGPUWinding
readList :: ReadS [WebGPUWinding]
$creadList :: ReadS [WebGPUWinding]
readsPrec :: Int -> ReadS WebGPUWinding
$creadsPrec :: Int -> ReadS WebGPUWinding
Read, WebGPUWinding -> WebGPUWinding -> Bool
(WebGPUWinding -> WebGPUWinding -> Bool)
-> (WebGPUWinding -> WebGPUWinding -> Bool) -> Eq WebGPUWinding
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WebGPUWinding -> WebGPUWinding -> Bool
$c/= :: WebGPUWinding -> WebGPUWinding -> Bool
== :: WebGPUWinding -> WebGPUWinding -> Bool
$c== :: WebGPUWinding -> WebGPUWinding -> Bool
Eq, Eq WebGPUWinding
Eq WebGPUWinding
-> (WebGPUWinding -> WebGPUWinding -> Ordering)
-> (WebGPUWinding -> WebGPUWinding -> Bool)
-> (WebGPUWinding -> WebGPUWinding -> Bool)
-> (WebGPUWinding -> WebGPUWinding -> Bool)
-> (WebGPUWinding -> WebGPUWinding -> Bool)
-> (WebGPUWinding -> WebGPUWinding -> WebGPUWinding)
-> (WebGPUWinding -> WebGPUWinding -> WebGPUWinding)
-> Ord WebGPUWinding
WebGPUWinding -> WebGPUWinding -> Bool
WebGPUWinding -> WebGPUWinding -> Ordering
WebGPUWinding -> WebGPUWinding -> WebGPUWinding
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: WebGPUWinding -> WebGPUWinding -> WebGPUWinding
$cmin :: WebGPUWinding -> WebGPUWinding -> WebGPUWinding
max :: WebGPUWinding -> WebGPUWinding -> WebGPUWinding
$cmax :: WebGPUWinding -> WebGPUWinding -> WebGPUWinding
>= :: WebGPUWinding -> WebGPUWinding -> Bool
$c>= :: WebGPUWinding -> WebGPUWinding -> Bool
> :: WebGPUWinding -> WebGPUWinding -> Bool
$c> :: WebGPUWinding -> WebGPUWinding -> Bool
<= :: WebGPUWinding -> WebGPUWinding -> Bool
$c<= :: WebGPUWinding -> WebGPUWinding -> Bool
< :: WebGPUWinding -> WebGPUWinding -> Bool
$c< :: WebGPUWinding -> WebGPUWinding -> Bool
compare :: WebGPUWinding -> WebGPUWinding -> Ordering
$ccompare :: WebGPUWinding -> WebGPUWinding -> Ordering
$cp1Ord :: Eq WebGPUWinding
Ord, Typeable)
 
instance ToJSVal WebGPUWinding where
        toJSVal :: WebGPUWinding -> JSM JSVal
toJSVal WebGPUWinding
WebGPUWindingClockwise = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUWindingClockwise
        toJSVal WebGPUWinding
WebGPUWindingCounterclockwise
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUWindingCounterclockwise
 
instance FromJSVal WebGPUWinding where
        fromJSVal :: JSVal -> JSM (Maybe WebGPUWinding)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_WebGPUWindingClockwise JSM Bool
-> (Bool -> JSM (Maybe WebGPUWinding)) -> JSM (Maybe WebGPUWinding)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe WebGPUWinding -> JSM (Maybe WebGPUWinding)
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPUWinding -> Maybe WebGPUWinding
forall a. a -> Maybe a
Just WebGPUWinding
WebGPUWindingClockwise)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_WebGPUWindingCounterclockwise JSM Bool
-> (Bool -> JSM (Maybe WebGPUWinding)) -> JSM (Maybe WebGPUWinding)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe WebGPUWinding -> JSM (Maybe WebGPUWinding)
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPUWinding -> Maybe WebGPUWinding
forall a. a -> Maybe a
Just WebGPUWinding
WebGPUWindingCounterclockwise)
                                 Bool
False -> Maybe WebGPUWinding -> JSM (Maybe WebGPUWinding)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe WebGPUWinding
forall a. Maybe a
Nothing
js_WebGPUWindingClockwise :: String
js_WebGPUWindingClockwise = String
"clockwise"
js_WebGPUWindingCounterclockwise :: String
js_WebGPUWindingCounterclockwise = String
"counterclockwise"
 
data WebGPUDepthClipMode = WebGPUDepthClipModeClip
                         | WebGPUDepthClipModeClamp
                         deriving (Int -> WebGPUDepthClipMode -> ShowS
[WebGPUDepthClipMode] -> ShowS
WebGPUDepthClipMode -> String
(Int -> WebGPUDepthClipMode -> ShowS)
-> (WebGPUDepthClipMode -> String)
-> ([WebGPUDepthClipMode] -> ShowS)
-> Show WebGPUDepthClipMode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WebGPUDepthClipMode] -> ShowS
$cshowList :: [WebGPUDepthClipMode] -> ShowS
show :: WebGPUDepthClipMode -> String
$cshow :: WebGPUDepthClipMode -> String
showsPrec :: Int -> WebGPUDepthClipMode -> ShowS
$cshowsPrec :: Int -> WebGPUDepthClipMode -> ShowS
Show, ReadPrec [WebGPUDepthClipMode]
ReadPrec WebGPUDepthClipMode
Int -> ReadS WebGPUDepthClipMode
ReadS [WebGPUDepthClipMode]
(Int -> ReadS WebGPUDepthClipMode)
-> ReadS [WebGPUDepthClipMode]
-> ReadPrec WebGPUDepthClipMode
-> ReadPrec [WebGPUDepthClipMode]
-> Read WebGPUDepthClipMode
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [WebGPUDepthClipMode]
$creadListPrec :: ReadPrec [WebGPUDepthClipMode]
readPrec :: ReadPrec WebGPUDepthClipMode
$creadPrec :: ReadPrec WebGPUDepthClipMode
readList :: ReadS [WebGPUDepthClipMode]
$creadList :: ReadS [WebGPUDepthClipMode]
readsPrec :: Int -> ReadS WebGPUDepthClipMode
$creadsPrec :: Int -> ReadS WebGPUDepthClipMode
Read, WebGPUDepthClipMode -> WebGPUDepthClipMode -> Bool
(WebGPUDepthClipMode -> WebGPUDepthClipMode -> Bool)
-> (WebGPUDepthClipMode -> WebGPUDepthClipMode -> Bool)
-> Eq WebGPUDepthClipMode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WebGPUDepthClipMode -> WebGPUDepthClipMode -> Bool
$c/= :: WebGPUDepthClipMode -> WebGPUDepthClipMode -> Bool
== :: WebGPUDepthClipMode -> WebGPUDepthClipMode -> Bool
$c== :: WebGPUDepthClipMode -> WebGPUDepthClipMode -> Bool
Eq, Eq WebGPUDepthClipMode
Eq WebGPUDepthClipMode
-> (WebGPUDepthClipMode -> WebGPUDepthClipMode -> Ordering)
-> (WebGPUDepthClipMode -> WebGPUDepthClipMode -> Bool)
-> (WebGPUDepthClipMode -> WebGPUDepthClipMode -> Bool)
-> (WebGPUDepthClipMode -> WebGPUDepthClipMode -> Bool)
-> (WebGPUDepthClipMode -> WebGPUDepthClipMode -> Bool)
-> (WebGPUDepthClipMode
    -> WebGPUDepthClipMode -> WebGPUDepthClipMode)
-> (WebGPUDepthClipMode
    -> WebGPUDepthClipMode -> WebGPUDepthClipMode)
-> Ord WebGPUDepthClipMode
WebGPUDepthClipMode -> WebGPUDepthClipMode -> Bool
WebGPUDepthClipMode -> WebGPUDepthClipMode -> Ordering
WebGPUDepthClipMode -> WebGPUDepthClipMode -> WebGPUDepthClipMode
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: WebGPUDepthClipMode -> WebGPUDepthClipMode -> WebGPUDepthClipMode
$cmin :: WebGPUDepthClipMode -> WebGPUDepthClipMode -> WebGPUDepthClipMode
max :: WebGPUDepthClipMode -> WebGPUDepthClipMode -> WebGPUDepthClipMode
$cmax :: WebGPUDepthClipMode -> WebGPUDepthClipMode -> WebGPUDepthClipMode
>= :: WebGPUDepthClipMode -> WebGPUDepthClipMode -> Bool
$c>= :: WebGPUDepthClipMode -> WebGPUDepthClipMode -> Bool
> :: WebGPUDepthClipMode -> WebGPUDepthClipMode -> Bool
$c> :: WebGPUDepthClipMode -> WebGPUDepthClipMode -> Bool
<= :: WebGPUDepthClipMode -> WebGPUDepthClipMode -> Bool
$c<= :: WebGPUDepthClipMode -> WebGPUDepthClipMode -> Bool
< :: WebGPUDepthClipMode -> WebGPUDepthClipMode -> Bool
$c< :: WebGPUDepthClipMode -> WebGPUDepthClipMode -> Bool
compare :: WebGPUDepthClipMode -> WebGPUDepthClipMode -> Ordering
$ccompare :: WebGPUDepthClipMode -> WebGPUDepthClipMode -> Ordering
$cp1Ord :: Eq WebGPUDepthClipMode
Ord, Typeable)
 
instance ToJSVal WebGPUDepthClipMode where
        toJSVal :: WebGPUDepthClipMode -> JSM JSVal
toJSVal WebGPUDepthClipMode
WebGPUDepthClipModeClip
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUDepthClipModeClip
        toJSVal WebGPUDepthClipMode
WebGPUDepthClipModeClamp
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUDepthClipModeClamp
 
instance FromJSVal WebGPUDepthClipMode where
        fromJSVal :: JSVal -> JSM (Maybe WebGPUDepthClipMode)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_WebGPUDepthClipModeClip JSM Bool
-> (Bool -> JSM (Maybe WebGPUDepthClipMode))
-> JSM (Maybe WebGPUDepthClipMode)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe WebGPUDepthClipMode -> JSM (Maybe WebGPUDepthClipMode)
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPUDepthClipMode -> Maybe WebGPUDepthClipMode
forall a. a -> Maybe a
Just WebGPUDepthClipMode
WebGPUDepthClipModeClip)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_WebGPUDepthClipModeClamp JSM Bool
-> (Bool -> JSM (Maybe WebGPUDepthClipMode))
-> JSM (Maybe WebGPUDepthClipMode)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe WebGPUDepthClipMode -> JSM (Maybe WebGPUDepthClipMode)
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPUDepthClipMode -> Maybe WebGPUDepthClipMode
forall a. a -> Maybe a
Just WebGPUDepthClipMode
WebGPUDepthClipModeClamp)
                                 Bool
False -> Maybe WebGPUDepthClipMode -> JSM (Maybe WebGPUDepthClipMode)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe WebGPUDepthClipMode
forall a. Maybe a
Nothing
js_WebGPUDepthClipModeClip :: String
js_WebGPUDepthClipModeClip = String
"clip"
js_WebGPUDepthClipModeClamp :: String
js_WebGPUDepthClipModeClamp = String
"clamp"
 
data WebGPUTriangleFillMode = WebGPUTriangleFillModeFill
                            | WebGPUTriangleFillModeLines
                            deriving (Int -> WebGPUTriangleFillMode -> ShowS
[WebGPUTriangleFillMode] -> ShowS
WebGPUTriangleFillMode -> String
(Int -> WebGPUTriangleFillMode -> ShowS)
-> (WebGPUTriangleFillMode -> String)
-> ([WebGPUTriangleFillMode] -> ShowS)
-> Show WebGPUTriangleFillMode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WebGPUTriangleFillMode] -> ShowS
$cshowList :: [WebGPUTriangleFillMode] -> ShowS
show :: WebGPUTriangleFillMode -> String
$cshow :: WebGPUTriangleFillMode -> String
showsPrec :: Int -> WebGPUTriangleFillMode -> ShowS
$cshowsPrec :: Int -> WebGPUTriangleFillMode -> ShowS
Show, ReadPrec [WebGPUTriangleFillMode]
ReadPrec WebGPUTriangleFillMode
Int -> ReadS WebGPUTriangleFillMode
ReadS [WebGPUTriangleFillMode]
(Int -> ReadS WebGPUTriangleFillMode)
-> ReadS [WebGPUTriangleFillMode]
-> ReadPrec WebGPUTriangleFillMode
-> ReadPrec [WebGPUTriangleFillMode]
-> Read WebGPUTriangleFillMode
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [WebGPUTriangleFillMode]
$creadListPrec :: ReadPrec [WebGPUTriangleFillMode]
readPrec :: ReadPrec WebGPUTriangleFillMode
$creadPrec :: ReadPrec WebGPUTriangleFillMode
readList :: ReadS [WebGPUTriangleFillMode]
$creadList :: ReadS [WebGPUTriangleFillMode]
readsPrec :: Int -> ReadS WebGPUTriangleFillMode
$creadsPrec :: Int -> ReadS WebGPUTriangleFillMode
Read, WebGPUTriangleFillMode -> WebGPUTriangleFillMode -> Bool
(WebGPUTriangleFillMode -> WebGPUTriangleFillMode -> Bool)
-> (WebGPUTriangleFillMode -> WebGPUTriangleFillMode -> Bool)
-> Eq WebGPUTriangleFillMode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WebGPUTriangleFillMode -> WebGPUTriangleFillMode -> Bool
$c/= :: WebGPUTriangleFillMode -> WebGPUTriangleFillMode -> Bool
== :: WebGPUTriangleFillMode -> WebGPUTriangleFillMode -> Bool
$c== :: WebGPUTriangleFillMode -> WebGPUTriangleFillMode -> Bool
Eq, Eq WebGPUTriangleFillMode
Eq WebGPUTriangleFillMode
-> (WebGPUTriangleFillMode -> WebGPUTriangleFillMode -> Ordering)
-> (WebGPUTriangleFillMode -> WebGPUTriangleFillMode -> Bool)
-> (WebGPUTriangleFillMode -> WebGPUTriangleFillMode -> Bool)
-> (WebGPUTriangleFillMode -> WebGPUTriangleFillMode -> Bool)
-> (WebGPUTriangleFillMode -> WebGPUTriangleFillMode -> Bool)
-> (WebGPUTriangleFillMode
    -> WebGPUTriangleFillMode -> WebGPUTriangleFillMode)
-> (WebGPUTriangleFillMode
    -> WebGPUTriangleFillMode -> WebGPUTriangleFillMode)
-> Ord WebGPUTriangleFillMode
WebGPUTriangleFillMode -> WebGPUTriangleFillMode -> Bool
WebGPUTriangleFillMode -> WebGPUTriangleFillMode -> Ordering
WebGPUTriangleFillMode
-> WebGPUTriangleFillMode -> WebGPUTriangleFillMode
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: WebGPUTriangleFillMode
-> WebGPUTriangleFillMode -> WebGPUTriangleFillMode
$cmin :: WebGPUTriangleFillMode
-> WebGPUTriangleFillMode -> WebGPUTriangleFillMode
max :: WebGPUTriangleFillMode
-> WebGPUTriangleFillMode -> WebGPUTriangleFillMode
$cmax :: WebGPUTriangleFillMode
-> WebGPUTriangleFillMode -> WebGPUTriangleFillMode
>= :: WebGPUTriangleFillMode -> WebGPUTriangleFillMode -> Bool
$c>= :: WebGPUTriangleFillMode -> WebGPUTriangleFillMode -> Bool
> :: WebGPUTriangleFillMode -> WebGPUTriangleFillMode -> Bool
$c> :: WebGPUTriangleFillMode -> WebGPUTriangleFillMode -> Bool
<= :: WebGPUTriangleFillMode -> WebGPUTriangleFillMode -> Bool
$c<= :: WebGPUTriangleFillMode -> WebGPUTriangleFillMode -> Bool
< :: WebGPUTriangleFillMode -> WebGPUTriangleFillMode -> Bool
$c< :: WebGPUTriangleFillMode -> WebGPUTriangleFillMode -> Bool
compare :: WebGPUTriangleFillMode -> WebGPUTriangleFillMode -> Ordering
$ccompare :: WebGPUTriangleFillMode -> WebGPUTriangleFillMode -> Ordering
$cp1Ord :: Eq WebGPUTriangleFillMode
Ord, Typeable)
 
instance ToJSVal WebGPUTriangleFillMode where
        toJSVal :: WebGPUTriangleFillMode -> JSM JSVal
toJSVal WebGPUTriangleFillMode
WebGPUTriangleFillModeFill
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUTriangleFillModeFill
        toJSVal WebGPUTriangleFillMode
WebGPUTriangleFillModeLines
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUTriangleFillModeLines
 
instance FromJSVal WebGPUTriangleFillMode where
        fromJSVal :: JSVal -> JSM (Maybe WebGPUTriangleFillMode)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_WebGPUTriangleFillModeFill JSM Bool
-> (Bool -> JSM (Maybe WebGPUTriangleFillMode))
-> JSM (Maybe WebGPUTriangleFillMode)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe WebGPUTriangleFillMode -> JSM (Maybe WebGPUTriangleFillMode)
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPUTriangleFillMode -> Maybe WebGPUTriangleFillMode
forall a. a -> Maybe a
Just WebGPUTriangleFillMode
WebGPUTriangleFillModeFill)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_WebGPUTriangleFillModeLines JSM Bool
-> (Bool -> JSM (Maybe WebGPUTriangleFillMode))
-> JSM (Maybe WebGPUTriangleFillMode)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe WebGPUTriangleFillMode -> JSM (Maybe WebGPUTriangleFillMode)
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPUTriangleFillMode -> Maybe WebGPUTriangleFillMode
forall a. a -> Maybe a
Just WebGPUTriangleFillMode
WebGPUTriangleFillModeLines)
                                 Bool
False -> Maybe WebGPUTriangleFillMode -> JSM (Maybe WebGPUTriangleFillMode)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe WebGPUTriangleFillMode
forall a. Maybe a
Nothing
js_WebGPUTriangleFillModeFill :: String
js_WebGPUTriangleFillModeFill = String
"fill"
js_WebGPUTriangleFillModeLines :: String
js_WebGPUTriangleFillModeLines = String
"lines"
 
data WebGPUCPUCacheMode = WebGPUCPUCacheModeDefaultcache
                        | WebGPUCPUCacheModeWritecombined
                        deriving (Int -> WebGPUCPUCacheMode -> ShowS
[WebGPUCPUCacheMode] -> ShowS
WebGPUCPUCacheMode -> String
(Int -> WebGPUCPUCacheMode -> ShowS)
-> (WebGPUCPUCacheMode -> String)
-> ([WebGPUCPUCacheMode] -> ShowS)
-> Show WebGPUCPUCacheMode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WebGPUCPUCacheMode] -> ShowS
$cshowList :: [WebGPUCPUCacheMode] -> ShowS
show :: WebGPUCPUCacheMode -> String
$cshow :: WebGPUCPUCacheMode -> String
showsPrec :: Int -> WebGPUCPUCacheMode -> ShowS
$cshowsPrec :: Int -> WebGPUCPUCacheMode -> ShowS
Show, ReadPrec [WebGPUCPUCacheMode]
ReadPrec WebGPUCPUCacheMode
Int -> ReadS WebGPUCPUCacheMode
ReadS [WebGPUCPUCacheMode]
(Int -> ReadS WebGPUCPUCacheMode)
-> ReadS [WebGPUCPUCacheMode]
-> ReadPrec WebGPUCPUCacheMode
-> ReadPrec [WebGPUCPUCacheMode]
-> Read WebGPUCPUCacheMode
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [WebGPUCPUCacheMode]
$creadListPrec :: ReadPrec [WebGPUCPUCacheMode]
readPrec :: ReadPrec WebGPUCPUCacheMode
$creadPrec :: ReadPrec WebGPUCPUCacheMode
readList :: ReadS [WebGPUCPUCacheMode]
$creadList :: ReadS [WebGPUCPUCacheMode]
readsPrec :: Int -> ReadS WebGPUCPUCacheMode
$creadsPrec :: Int -> ReadS WebGPUCPUCacheMode
Read, WebGPUCPUCacheMode -> WebGPUCPUCacheMode -> Bool
(WebGPUCPUCacheMode -> WebGPUCPUCacheMode -> Bool)
-> (WebGPUCPUCacheMode -> WebGPUCPUCacheMode -> Bool)
-> Eq WebGPUCPUCacheMode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WebGPUCPUCacheMode -> WebGPUCPUCacheMode -> Bool
$c/= :: WebGPUCPUCacheMode -> WebGPUCPUCacheMode -> Bool
== :: WebGPUCPUCacheMode -> WebGPUCPUCacheMode -> Bool
$c== :: WebGPUCPUCacheMode -> WebGPUCPUCacheMode -> Bool
Eq, Eq WebGPUCPUCacheMode
Eq WebGPUCPUCacheMode
-> (WebGPUCPUCacheMode -> WebGPUCPUCacheMode -> Ordering)
-> (WebGPUCPUCacheMode -> WebGPUCPUCacheMode -> Bool)
-> (WebGPUCPUCacheMode -> WebGPUCPUCacheMode -> Bool)
-> (WebGPUCPUCacheMode -> WebGPUCPUCacheMode -> Bool)
-> (WebGPUCPUCacheMode -> WebGPUCPUCacheMode -> Bool)
-> (WebGPUCPUCacheMode -> WebGPUCPUCacheMode -> WebGPUCPUCacheMode)
-> (WebGPUCPUCacheMode -> WebGPUCPUCacheMode -> WebGPUCPUCacheMode)
-> Ord WebGPUCPUCacheMode
WebGPUCPUCacheMode -> WebGPUCPUCacheMode -> Bool
WebGPUCPUCacheMode -> WebGPUCPUCacheMode -> Ordering
WebGPUCPUCacheMode -> WebGPUCPUCacheMode -> WebGPUCPUCacheMode
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: WebGPUCPUCacheMode -> WebGPUCPUCacheMode -> WebGPUCPUCacheMode
$cmin :: WebGPUCPUCacheMode -> WebGPUCPUCacheMode -> WebGPUCPUCacheMode
max :: WebGPUCPUCacheMode -> WebGPUCPUCacheMode -> WebGPUCPUCacheMode
$cmax :: WebGPUCPUCacheMode -> WebGPUCPUCacheMode -> WebGPUCPUCacheMode
>= :: WebGPUCPUCacheMode -> WebGPUCPUCacheMode -> Bool
$c>= :: WebGPUCPUCacheMode -> WebGPUCPUCacheMode -> Bool
> :: WebGPUCPUCacheMode -> WebGPUCPUCacheMode -> Bool
$c> :: WebGPUCPUCacheMode -> WebGPUCPUCacheMode -> Bool
<= :: WebGPUCPUCacheMode -> WebGPUCPUCacheMode -> Bool
$c<= :: WebGPUCPUCacheMode -> WebGPUCPUCacheMode -> Bool
< :: WebGPUCPUCacheMode -> WebGPUCPUCacheMode -> Bool
$c< :: WebGPUCPUCacheMode -> WebGPUCPUCacheMode -> Bool
compare :: WebGPUCPUCacheMode -> WebGPUCPUCacheMode -> Ordering
$ccompare :: WebGPUCPUCacheMode -> WebGPUCPUCacheMode -> Ordering
$cp1Ord :: Eq WebGPUCPUCacheMode
Ord, Typeable)
 
instance ToJSVal WebGPUCPUCacheMode where
        toJSVal :: WebGPUCPUCacheMode -> JSM JSVal
toJSVal WebGPUCPUCacheMode
WebGPUCPUCacheModeDefaultcache
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUCPUCacheModeDefaultcache
        toJSVal WebGPUCPUCacheMode
WebGPUCPUCacheModeWritecombined
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUCPUCacheModeWritecombined
 
instance FromJSVal WebGPUCPUCacheMode where
        fromJSVal :: JSVal -> JSM (Maybe WebGPUCPUCacheMode)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_WebGPUCPUCacheModeDefaultcache JSM Bool
-> (Bool -> JSM (Maybe WebGPUCPUCacheMode))
-> JSM (Maybe WebGPUCPUCacheMode)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe WebGPUCPUCacheMode -> JSM (Maybe WebGPUCPUCacheMode)
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPUCPUCacheMode -> Maybe WebGPUCPUCacheMode
forall a. a -> Maybe a
Just WebGPUCPUCacheMode
WebGPUCPUCacheModeDefaultcache)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_WebGPUCPUCacheModeWritecombined JSM Bool
-> (Bool -> JSM (Maybe WebGPUCPUCacheMode))
-> JSM (Maybe WebGPUCPUCacheMode)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe WebGPUCPUCacheMode -> JSM (Maybe WebGPUCPUCacheMode)
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPUCPUCacheMode -> Maybe WebGPUCPUCacheMode
forall a. a -> Maybe a
Just WebGPUCPUCacheMode
WebGPUCPUCacheModeWritecombined)
                                 Bool
False -> Maybe WebGPUCPUCacheMode -> JSM (Maybe WebGPUCPUCacheMode)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe WebGPUCPUCacheMode
forall a. Maybe a
Nothing
js_WebGPUCPUCacheModeDefaultcache :: String
js_WebGPUCPUCacheModeDefaultcache = String
"defaultcache"
js_WebGPUCPUCacheModeWritecombined :: String
js_WebGPUCPUCacheModeWritecombined = String
"writecombined"
 
data WebGPUStorageMode = WebGPUStorageModeShared
                       | WebGPUStorageModeManaged
                       | WebGPUStorageModePrivate
                       deriving (Int -> WebGPUStorageMode -> ShowS
[WebGPUStorageMode] -> ShowS
WebGPUStorageMode -> String
(Int -> WebGPUStorageMode -> ShowS)
-> (WebGPUStorageMode -> String)
-> ([WebGPUStorageMode] -> ShowS)
-> Show WebGPUStorageMode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WebGPUStorageMode] -> ShowS
$cshowList :: [WebGPUStorageMode] -> ShowS
show :: WebGPUStorageMode -> String
$cshow :: WebGPUStorageMode -> String
showsPrec :: Int -> WebGPUStorageMode -> ShowS
$cshowsPrec :: Int -> WebGPUStorageMode -> ShowS
Show, ReadPrec [WebGPUStorageMode]
ReadPrec WebGPUStorageMode
Int -> ReadS WebGPUStorageMode
ReadS [WebGPUStorageMode]
(Int -> ReadS WebGPUStorageMode)
-> ReadS [WebGPUStorageMode]
-> ReadPrec WebGPUStorageMode
-> ReadPrec [WebGPUStorageMode]
-> Read WebGPUStorageMode
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [WebGPUStorageMode]
$creadListPrec :: ReadPrec [WebGPUStorageMode]
readPrec :: ReadPrec WebGPUStorageMode
$creadPrec :: ReadPrec WebGPUStorageMode
readList :: ReadS [WebGPUStorageMode]
$creadList :: ReadS [WebGPUStorageMode]
readsPrec :: Int -> ReadS WebGPUStorageMode
$creadsPrec :: Int -> ReadS WebGPUStorageMode
Read, WebGPUStorageMode -> WebGPUStorageMode -> Bool
(WebGPUStorageMode -> WebGPUStorageMode -> Bool)
-> (WebGPUStorageMode -> WebGPUStorageMode -> Bool)
-> Eq WebGPUStorageMode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WebGPUStorageMode -> WebGPUStorageMode -> Bool
$c/= :: WebGPUStorageMode -> WebGPUStorageMode -> Bool
== :: WebGPUStorageMode -> WebGPUStorageMode -> Bool
$c== :: WebGPUStorageMode -> WebGPUStorageMode -> Bool
Eq, Eq WebGPUStorageMode
Eq WebGPUStorageMode
-> (WebGPUStorageMode -> WebGPUStorageMode -> Ordering)
-> (WebGPUStorageMode -> WebGPUStorageMode -> Bool)
-> (WebGPUStorageMode -> WebGPUStorageMode -> Bool)
-> (WebGPUStorageMode -> WebGPUStorageMode -> Bool)
-> (WebGPUStorageMode -> WebGPUStorageMode -> Bool)
-> (WebGPUStorageMode -> WebGPUStorageMode -> WebGPUStorageMode)
-> (WebGPUStorageMode -> WebGPUStorageMode -> WebGPUStorageMode)
-> Ord WebGPUStorageMode
WebGPUStorageMode -> WebGPUStorageMode -> Bool
WebGPUStorageMode -> WebGPUStorageMode -> Ordering
WebGPUStorageMode -> WebGPUStorageMode -> WebGPUStorageMode
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: WebGPUStorageMode -> WebGPUStorageMode -> WebGPUStorageMode
$cmin :: WebGPUStorageMode -> WebGPUStorageMode -> WebGPUStorageMode
max :: WebGPUStorageMode -> WebGPUStorageMode -> WebGPUStorageMode
$cmax :: WebGPUStorageMode -> WebGPUStorageMode -> WebGPUStorageMode
>= :: WebGPUStorageMode -> WebGPUStorageMode -> Bool
$c>= :: WebGPUStorageMode -> WebGPUStorageMode -> Bool
> :: WebGPUStorageMode -> WebGPUStorageMode -> Bool
$c> :: WebGPUStorageMode -> WebGPUStorageMode -> Bool
<= :: WebGPUStorageMode -> WebGPUStorageMode -> Bool
$c<= :: WebGPUStorageMode -> WebGPUStorageMode -> Bool
< :: WebGPUStorageMode -> WebGPUStorageMode -> Bool
$c< :: WebGPUStorageMode -> WebGPUStorageMode -> Bool
compare :: WebGPUStorageMode -> WebGPUStorageMode -> Ordering
$ccompare :: WebGPUStorageMode -> WebGPUStorageMode -> Ordering
$cp1Ord :: Eq WebGPUStorageMode
Ord, Typeable)
 
instance ToJSVal WebGPUStorageMode where
        toJSVal :: WebGPUStorageMode -> JSM JSVal
toJSVal WebGPUStorageMode
WebGPUStorageModeShared
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUStorageModeShared
        toJSVal WebGPUStorageMode
WebGPUStorageModeManaged
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUStorageModeManaged
        toJSVal WebGPUStorageMode
WebGPUStorageModePrivate
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUStorageModePrivate
 
instance FromJSVal WebGPUStorageMode where
        fromJSVal :: JSVal -> JSM (Maybe WebGPUStorageMode)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_WebGPUStorageModeShared JSM Bool
-> (Bool -> JSM (Maybe WebGPUStorageMode))
-> JSM (Maybe WebGPUStorageMode)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe WebGPUStorageMode -> JSM (Maybe WebGPUStorageMode)
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPUStorageMode -> Maybe WebGPUStorageMode
forall a. a -> Maybe a
Just WebGPUStorageMode
WebGPUStorageModeShared)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_WebGPUStorageModeManaged JSM Bool
-> (Bool -> JSM (Maybe WebGPUStorageMode))
-> JSM (Maybe WebGPUStorageMode)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe WebGPUStorageMode -> JSM (Maybe WebGPUStorageMode)
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPUStorageMode -> Maybe WebGPUStorageMode
forall a. a -> Maybe a
Just WebGPUStorageMode
WebGPUStorageModeManaged)
                                 Bool
False
                                   -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_WebGPUStorageModePrivate JSM Bool
-> (Bool -> JSM (Maybe WebGPUStorageMode))
-> JSM (Maybe WebGPUStorageMode)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                        \ Bool
r ->
                                          case Bool
r of
                                              Bool
True -> Maybe WebGPUStorageMode -> JSM (Maybe WebGPUStorageMode)
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPUStorageMode -> Maybe WebGPUStorageMode
forall a. a -> Maybe a
Just WebGPUStorageMode
WebGPUStorageModePrivate)
                                              Bool
False -> Maybe WebGPUStorageMode -> JSM (Maybe WebGPUStorageMode)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe WebGPUStorageMode
forall a. Maybe a
Nothing
js_WebGPUStorageModeShared :: String
js_WebGPUStorageModeShared = String
"shared"
js_WebGPUStorageModeManaged :: String
js_WebGPUStorageModeManaged = String
"managed"
js_WebGPUStorageModePrivate :: String
js_WebGPUStorageModePrivate = String
"private"
 
data WebGPUResourceOptions = WebGPUResourceOptionsCpucachemodedefaultcache
                           | WebGPUResourceOptionsCpucachemodewritecombined
                           | WebGPUResourceOptionsStoragemodeshared
                           | WebGPUResourceOptionsStoragemodemanaged
                           | WebGPUResourceOptionsStoragemodeprivate
                           | WebGPUResourceOptionsOptioncpucachemodedefaultcache
                           | WebGPUResourceOptionsOptioncpucachemodewritecombined
                           deriving (Int -> WebGPUResourceOptions -> ShowS
[WebGPUResourceOptions] -> ShowS
WebGPUResourceOptions -> String
(Int -> WebGPUResourceOptions -> ShowS)
-> (WebGPUResourceOptions -> String)
-> ([WebGPUResourceOptions] -> ShowS)
-> Show WebGPUResourceOptions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WebGPUResourceOptions] -> ShowS
$cshowList :: [WebGPUResourceOptions] -> ShowS
show :: WebGPUResourceOptions -> String
$cshow :: WebGPUResourceOptions -> String
showsPrec :: Int -> WebGPUResourceOptions -> ShowS
$cshowsPrec :: Int -> WebGPUResourceOptions -> ShowS
Show, ReadPrec [WebGPUResourceOptions]
ReadPrec WebGPUResourceOptions
Int -> ReadS WebGPUResourceOptions
ReadS [WebGPUResourceOptions]
(Int -> ReadS WebGPUResourceOptions)
-> ReadS [WebGPUResourceOptions]
-> ReadPrec WebGPUResourceOptions
-> ReadPrec [WebGPUResourceOptions]
-> Read WebGPUResourceOptions
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [WebGPUResourceOptions]
$creadListPrec :: ReadPrec [WebGPUResourceOptions]
readPrec :: ReadPrec WebGPUResourceOptions
$creadPrec :: ReadPrec WebGPUResourceOptions
readList :: ReadS [WebGPUResourceOptions]
$creadList :: ReadS [WebGPUResourceOptions]
readsPrec :: Int -> ReadS WebGPUResourceOptions
$creadsPrec :: Int -> ReadS WebGPUResourceOptions
Read, WebGPUResourceOptions -> WebGPUResourceOptions -> Bool
(WebGPUResourceOptions -> WebGPUResourceOptions -> Bool)
-> (WebGPUResourceOptions -> WebGPUResourceOptions -> Bool)
-> Eq WebGPUResourceOptions
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WebGPUResourceOptions -> WebGPUResourceOptions -> Bool
$c/= :: WebGPUResourceOptions -> WebGPUResourceOptions -> Bool
== :: WebGPUResourceOptions -> WebGPUResourceOptions -> Bool
$c== :: WebGPUResourceOptions -> WebGPUResourceOptions -> Bool
Eq, Eq WebGPUResourceOptions
Eq WebGPUResourceOptions
-> (WebGPUResourceOptions -> WebGPUResourceOptions -> Ordering)
-> (WebGPUResourceOptions -> WebGPUResourceOptions -> Bool)
-> (WebGPUResourceOptions -> WebGPUResourceOptions -> Bool)
-> (WebGPUResourceOptions -> WebGPUResourceOptions -> Bool)
-> (WebGPUResourceOptions -> WebGPUResourceOptions -> Bool)
-> (WebGPUResourceOptions
    -> WebGPUResourceOptions -> WebGPUResourceOptions)
-> (WebGPUResourceOptions
    -> WebGPUResourceOptions -> WebGPUResourceOptions)
-> Ord WebGPUResourceOptions
WebGPUResourceOptions -> WebGPUResourceOptions -> Bool
WebGPUResourceOptions -> WebGPUResourceOptions -> Ordering
WebGPUResourceOptions
-> WebGPUResourceOptions -> WebGPUResourceOptions
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: WebGPUResourceOptions
-> WebGPUResourceOptions -> WebGPUResourceOptions
$cmin :: WebGPUResourceOptions
-> WebGPUResourceOptions -> WebGPUResourceOptions
max :: WebGPUResourceOptions
-> WebGPUResourceOptions -> WebGPUResourceOptions
$cmax :: WebGPUResourceOptions
-> WebGPUResourceOptions -> WebGPUResourceOptions
>= :: WebGPUResourceOptions -> WebGPUResourceOptions -> Bool
$c>= :: WebGPUResourceOptions -> WebGPUResourceOptions -> Bool
> :: WebGPUResourceOptions -> WebGPUResourceOptions -> Bool
$c> :: WebGPUResourceOptions -> WebGPUResourceOptions -> Bool
<= :: WebGPUResourceOptions -> WebGPUResourceOptions -> Bool
$c<= :: WebGPUResourceOptions -> WebGPUResourceOptions -> Bool
< :: WebGPUResourceOptions -> WebGPUResourceOptions -> Bool
$c< :: WebGPUResourceOptions -> WebGPUResourceOptions -> Bool
compare :: WebGPUResourceOptions -> WebGPUResourceOptions -> Ordering
$ccompare :: WebGPUResourceOptions -> WebGPUResourceOptions -> Ordering
$cp1Ord :: Eq WebGPUResourceOptions
Ord, Typeable)
 
instance ToJSVal WebGPUResourceOptions where
        toJSVal :: WebGPUResourceOptions -> JSM JSVal
toJSVal WebGPUResourceOptions
WebGPUResourceOptionsCpucachemodedefaultcache
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUResourceOptionsCpucachemodedefaultcache
        toJSVal WebGPUResourceOptions
WebGPUResourceOptionsCpucachemodewritecombined
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUResourceOptionsCpucachemodewritecombined
        toJSVal WebGPUResourceOptions
WebGPUResourceOptionsStoragemodeshared
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUResourceOptionsStoragemodeshared
        toJSVal WebGPUResourceOptions
WebGPUResourceOptionsStoragemodemanaged
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUResourceOptionsStoragemodemanaged
        toJSVal WebGPUResourceOptions
WebGPUResourceOptionsStoragemodeprivate
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUResourceOptionsStoragemodeprivate
        toJSVal WebGPUResourceOptions
WebGPUResourceOptionsOptioncpucachemodedefaultcache
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUResourceOptionsOptioncpucachemodedefaultcache
        toJSVal WebGPUResourceOptions
WebGPUResourceOptionsOptioncpucachemodewritecombined
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUResourceOptionsOptioncpucachemodewritecombined
 
instance FromJSVal WebGPUResourceOptions where
        fromJSVal :: JSVal -> JSM (Maybe WebGPUResourceOptions)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_WebGPUResourceOptionsCpucachemodedefaultcache
              JSM Bool
-> (Bool -> JSM (Maybe WebGPUResourceOptions))
-> JSM (Maybe WebGPUResourceOptions)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe WebGPUResourceOptions -> JSM (Maybe WebGPUResourceOptions)
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPUResourceOptions -> Maybe WebGPUResourceOptions
forall a. a -> Maybe a
Just WebGPUResourceOptions
WebGPUResourceOptionsCpucachemodedefaultcache)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                           String
js_WebGPUResourceOptionsCpucachemodewritecombined
                           JSM Bool
-> (Bool -> JSM (Maybe WebGPUResourceOptions))
-> JSM (Maybe WebGPUResourceOptions)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True
                                   -> Maybe WebGPUResourceOptions -> JSM (Maybe WebGPUResourceOptions)
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPUResourceOptions -> Maybe WebGPUResourceOptions
forall a. a -> Maybe a
Just WebGPUResourceOptions
WebGPUResourceOptionsCpucachemodewritecombined)
                                 Bool
False
                                   -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_WebGPUResourceOptionsStoragemodeshared JSM Bool
-> (Bool -> JSM (Maybe WebGPUResourceOptions))
-> JSM (Maybe WebGPUResourceOptions)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                        \ Bool
r ->
                                          case Bool
r of
                                              Bool
True
                                                -> Maybe WebGPUResourceOptions -> JSM (Maybe WebGPUResourceOptions)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                     (WebGPUResourceOptions -> Maybe WebGPUResourceOptions
forall a. a -> Maybe a
Just WebGPUResourceOptions
WebGPUResourceOptionsStoragemodeshared)
                                              Bool
False
                                                -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                     String
js_WebGPUResourceOptionsStoragemodemanaged
                                                     JSM Bool
-> (Bool -> JSM (Maybe WebGPUResourceOptions))
-> JSM (Maybe WebGPUResourceOptions)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                     \ Bool
r ->
                                                       case Bool
r of
                                                           Bool
True
                                                             -> Maybe WebGPUResourceOptions -> JSM (Maybe WebGPUResourceOptions)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                  (WebGPUResourceOptions -> Maybe WebGPUResourceOptions
forall a. a -> Maybe a
Just
                                                                     WebGPUResourceOptions
WebGPUResourceOptionsStoragemodemanaged)
                                                           Bool
False
                                                             -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                                  String
js_WebGPUResourceOptionsStoragemodeprivate
                                                                  JSM Bool
-> (Bool -> JSM (Maybe WebGPUResourceOptions))
-> JSM (Maybe WebGPUResourceOptions)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                  \ Bool
r ->
                                                                    case Bool
r of
                                                                        Bool
True
                                                                          -> Maybe WebGPUResourceOptions -> JSM (Maybe WebGPUResourceOptions)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                               (WebGPUResourceOptions -> Maybe WebGPUResourceOptions
forall a. a -> Maybe a
Just
                                                                                  WebGPUResourceOptions
WebGPUResourceOptionsStoragemodeprivate)
                                                                        Bool
False
                                                                          -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                                               String
js_WebGPUResourceOptionsOptioncpucachemodedefaultcache
                                                                               JSM Bool
-> (Bool -> JSM (Maybe WebGPUResourceOptions))
-> JSM (Maybe WebGPUResourceOptions)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                               \ Bool
r ->
                                                                                 case Bool
r of
                                                                                     Bool
True
                                                                                       -> Maybe WebGPUResourceOptions -> JSM (Maybe WebGPUResourceOptions)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                                            (WebGPUResourceOptions -> Maybe WebGPUResourceOptions
forall a. a -> Maybe a
Just
                                                                                               WebGPUResourceOptions
WebGPUResourceOptionsOptioncpucachemodedefaultcache)
                                                                                     Bool
False
                                                                                       -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                                                            String
js_WebGPUResourceOptionsOptioncpucachemodewritecombined
                                                                                            JSM Bool
-> (Bool -> JSM (Maybe WebGPUResourceOptions))
-> JSM (Maybe WebGPUResourceOptions)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                                            \ Bool
r ->
                                                                                              case Bool
r
                                                                                                of
                                                                                                  Bool
True
                                                                                                    -> Maybe WebGPUResourceOptions -> JSM (Maybe WebGPUResourceOptions)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                                                         (WebGPUResourceOptions -> Maybe WebGPUResourceOptions
forall a. a -> Maybe a
Just
                                                                                                            WebGPUResourceOptions
WebGPUResourceOptionsOptioncpucachemodewritecombined)
                                                                                                  Bool
False
                                                                                                    -> Maybe WebGPUResourceOptions -> JSM (Maybe WebGPUResourceOptions)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                                                         Maybe WebGPUResourceOptions
forall a. Maybe a
Nothing
js_WebGPUResourceOptionsCpucachemodedefaultcache :: String
js_WebGPUResourceOptionsCpucachemodedefaultcache
  = String
"cpucachemodedefaultcache"
js_WebGPUResourceOptionsCpucachemodewritecombined :: String
js_WebGPUResourceOptionsCpucachemodewritecombined
  = String
"cpucachemodewritecombined"
js_WebGPUResourceOptionsStoragemodeshared :: String
js_WebGPUResourceOptionsStoragemodeshared = String
"storagemodeshared"
js_WebGPUResourceOptionsStoragemodemanaged :: String
js_WebGPUResourceOptionsStoragemodemanaged = String
"storagemodemanaged"
js_WebGPUResourceOptionsStoragemodeprivate :: String
js_WebGPUResourceOptionsStoragemodeprivate = String
"storagemodeprivate"
js_WebGPUResourceOptionsOptioncpucachemodedefaultcache :: String
js_WebGPUResourceOptionsOptioncpucachemodedefaultcache
  = String
"optioncpucachemodedefaultcache"
js_WebGPUResourceOptionsOptioncpucachemodewritecombined :: String
js_WebGPUResourceOptionsOptioncpucachemodewritecombined
  = String
"optioncpucachemodewritecombined"
 
data WebGPUTextureUsage = WebGPUTextureUsageUnknown
                        | WebGPUTextureUsageShaderread
                        | WebGPUTextureUsageShaderwrite
                        | WebGPUTextureUsageRendertarget
                        | WebGPUTextureUsagePixelformatview
                        deriving (Int -> WebGPUTextureUsage -> ShowS
[WebGPUTextureUsage] -> ShowS
WebGPUTextureUsage -> String
(Int -> WebGPUTextureUsage -> ShowS)
-> (WebGPUTextureUsage -> String)
-> ([WebGPUTextureUsage] -> ShowS)
-> Show WebGPUTextureUsage
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WebGPUTextureUsage] -> ShowS
$cshowList :: [WebGPUTextureUsage] -> ShowS
show :: WebGPUTextureUsage -> String
$cshow :: WebGPUTextureUsage -> String
showsPrec :: Int -> WebGPUTextureUsage -> ShowS
$cshowsPrec :: Int -> WebGPUTextureUsage -> ShowS
Show, ReadPrec [WebGPUTextureUsage]
ReadPrec WebGPUTextureUsage
Int -> ReadS WebGPUTextureUsage
ReadS [WebGPUTextureUsage]
(Int -> ReadS WebGPUTextureUsage)
-> ReadS [WebGPUTextureUsage]
-> ReadPrec WebGPUTextureUsage
-> ReadPrec [WebGPUTextureUsage]
-> Read WebGPUTextureUsage
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [WebGPUTextureUsage]
$creadListPrec :: ReadPrec [WebGPUTextureUsage]
readPrec :: ReadPrec WebGPUTextureUsage
$creadPrec :: ReadPrec WebGPUTextureUsage
readList :: ReadS [WebGPUTextureUsage]
$creadList :: ReadS [WebGPUTextureUsage]
readsPrec :: Int -> ReadS WebGPUTextureUsage
$creadsPrec :: Int -> ReadS WebGPUTextureUsage
Read, WebGPUTextureUsage -> WebGPUTextureUsage -> Bool
(WebGPUTextureUsage -> WebGPUTextureUsage -> Bool)
-> (WebGPUTextureUsage -> WebGPUTextureUsage -> Bool)
-> Eq WebGPUTextureUsage
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WebGPUTextureUsage -> WebGPUTextureUsage -> Bool
$c/= :: WebGPUTextureUsage -> WebGPUTextureUsage -> Bool
== :: WebGPUTextureUsage -> WebGPUTextureUsage -> Bool
$c== :: WebGPUTextureUsage -> WebGPUTextureUsage -> Bool
Eq, Eq WebGPUTextureUsage
Eq WebGPUTextureUsage
-> (WebGPUTextureUsage -> WebGPUTextureUsage -> Ordering)
-> (WebGPUTextureUsage -> WebGPUTextureUsage -> Bool)
-> (WebGPUTextureUsage -> WebGPUTextureUsage -> Bool)
-> (WebGPUTextureUsage -> WebGPUTextureUsage -> Bool)
-> (WebGPUTextureUsage -> WebGPUTextureUsage -> Bool)
-> (WebGPUTextureUsage -> WebGPUTextureUsage -> WebGPUTextureUsage)
-> (WebGPUTextureUsage -> WebGPUTextureUsage -> WebGPUTextureUsage)
-> Ord WebGPUTextureUsage
WebGPUTextureUsage -> WebGPUTextureUsage -> Bool
WebGPUTextureUsage -> WebGPUTextureUsage -> Ordering
WebGPUTextureUsage -> WebGPUTextureUsage -> WebGPUTextureUsage
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: WebGPUTextureUsage -> WebGPUTextureUsage -> WebGPUTextureUsage
$cmin :: WebGPUTextureUsage -> WebGPUTextureUsage -> WebGPUTextureUsage
max :: WebGPUTextureUsage -> WebGPUTextureUsage -> WebGPUTextureUsage
$cmax :: WebGPUTextureUsage -> WebGPUTextureUsage -> WebGPUTextureUsage
>= :: WebGPUTextureUsage -> WebGPUTextureUsage -> Bool
$c>= :: WebGPUTextureUsage -> WebGPUTextureUsage -> Bool
> :: WebGPUTextureUsage -> WebGPUTextureUsage -> Bool
$c> :: WebGPUTextureUsage -> WebGPUTextureUsage -> Bool
<= :: WebGPUTextureUsage -> WebGPUTextureUsage -> Bool
$c<= :: WebGPUTextureUsage -> WebGPUTextureUsage -> Bool
< :: WebGPUTextureUsage -> WebGPUTextureUsage -> Bool
$c< :: WebGPUTextureUsage -> WebGPUTextureUsage -> Bool
compare :: WebGPUTextureUsage -> WebGPUTextureUsage -> Ordering
$ccompare :: WebGPUTextureUsage -> WebGPUTextureUsage -> Ordering
$cp1Ord :: Eq WebGPUTextureUsage
Ord, Typeable)
 
instance ToJSVal WebGPUTextureUsage where
        toJSVal :: WebGPUTextureUsage -> JSM JSVal
toJSVal WebGPUTextureUsage
WebGPUTextureUsageUnknown
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUTextureUsageUnknown
        toJSVal WebGPUTextureUsage
WebGPUTextureUsageShaderread
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUTextureUsageShaderread
        toJSVal WebGPUTextureUsage
WebGPUTextureUsageShaderwrite
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUTextureUsageShaderwrite
        toJSVal WebGPUTextureUsage
WebGPUTextureUsageRendertarget
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUTextureUsageRendertarget
        toJSVal WebGPUTextureUsage
WebGPUTextureUsagePixelformatview
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUTextureUsagePixelformatview
 
instance FromJSVal WebGPUTextureUsage where
        fromJSVal :: JSVal -> JSM (Maybe WebGPUTextureUsage)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_WebGPUTextureUsageUnknown JSM Bool
-> (Bool -> JSM (Maybe WebGPUTextureUsage))
-> JSM (Maybe WebGPUTextureUsage)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe WebGPUTextureUsage -> JSM (Maybe WebGPUTextureUsage)
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPUTextureUsage -> Maybe WebGPUTextureUsage
forall a. a -> Maybe a
Just WebGPUTextureUsage
WebGPUTextureUsageUnknown)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_WebGPUTextureUsageShaderread JSM Bool
-> (Bool -> JSM (Maybe WebGPUTextureUsage))
-> JSM (Maybe WebGPUTextureUsage)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe WebGPUTextureUsage -> JSM (Maybe WebGPUTextureUsage)
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPUTextureUsage -> Maybe WebGPUTextureUsage
forall a. a -> Maybe a
Just WebGPUTextureUsage
WebGPUTextureUsageShaderread)
                                 Bool
False
                                   -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_WebGPUTextureUsageShaderwrite JSM Bool
-> (Bool -> JSM (Maybe WebGPUTextureUsage))
-> JSM (Maybe WebGPUTextureUsage)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                        \ Bool
r ->
                                          case Bool
r of
                                              Bool
True -> Maybe WebGPUTextureUsage -> JSM (Maybe WebGPUTextureUsage)
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPUTextureUsage -> Maybe WebGPUTextureUsage
forall a. a -> Maybe a
Just WebGPUTextureUsage
WebGPUTextureUsageShaderwrite)
                                              Bool
False
                                                -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_WebGPUTextureUsageRendertarget
                                                     JSM Bool
-> (Bool -> JSM (Maybe WebGPUTextureUsage))
-> JSM (Maybe WebGPUTextureUsage)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                     \ Bool
r ->
                                                       case Bool
r of
                                                           Bool
True
                                                             -> Maybe WebGPUTextureUsage -> JSM (Maybe WebGPUTextureUsage)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                  (WebGPUTextureUsage -> Maybe WebGPUTextureUsage
forall a. a -> Maybe a
Just
                                                                     WebGPUTextureUsage
WebGPUTextureUsageRendertarget)
                                                           Bool
False
                                                             -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                                  String
js_WebGPUTextureUsagePixelformatview
                                                                  JSM Bool
-> (Bool -> JSM (Maybe WebGPUTextureUsage))
-> JSM (Maybe WebGPUTextureUsage)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                  \ Bool
r ->
                                                                    case Bool
r of
                                                                        Bool
True
                                                                          -> Maybe WebGPUTextureUsage -> JSM (Maybe WebGPUTextureUsage)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                               (WebGPUTextureUsage -> Maybe WebGPUTextureUsage
forall a. a -> Maybe a
Just
                                                                                  WebGPUTextureUsage
WebGPUTextureUsagePixelformatview)
                                                                        Bool
False -> Maybe WebGPUTextureUsage -> JSM (Maybe WebGPUTextureUsage)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe WebGPUTextureUsage
forall a. Maybe a
Nothing
js_WebGPUTextureUsageUnknown :: String
js_WebGPUTextureUsageUnknown = String
"unknown"
js_WebGPUTextureUsageShaderread :: String
js_WebGPUTextureUsageShaderread = String
"shaderread"
js_WebGPUTextureUsageShaderwrite :: String
js_WebGPUTextureUsageShaderwrite = String
"shaderwrite"
js_WebGPUTextureUsageRendertarget :: String
js_WebGPUTextureUsageRendertarget = String
"rendertarget"
js_WebGPUTextureUsagePixelformatview :: String
js_WebGPUTextureUsagePixelformatview = String
"pixelformatview"
 
data WebGPUBlendOperation = WebGPUBlendOperationAdd
                          | WebGPUBlendOperationSubtract
                          | WebGPUBlendOperationReversesubtract
                          | WebGPUBlendOperationMin
                          | WebGPUBlendOperationMax
                          deriving (Int -> WebGPUBlendOperation -> ShowS
[WebGPUBlendOperation] -> ShowS
WebGPUBlendOperation -> String
(Int -> WebGPUBlendOperation -> ShowS)
-> (WebGPUBlendOperation -> String)
-> ([WebGPUBlendOperation] -> ShowS)
-> Show WebGPUBlendOperation
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WebGPUBlendOperation] -> ShowS
$cshowList :: [WebGPUBlendOperation] -> ShowS
show :: WebGPUBlendOperation -> String
$cshow :: WebGPUBlendOperation -> String
showsPrec :: Int -> WebGPUBlendOperation -> ShowS
$cshowsPrec :: Int -> WebGPUBlendOperation -> ShowS
Show, ReadPrec [WebGPUBlendOperation]
ReadPrec WebGPUBlendOperation
Int -> ReadS WebGPUBlendOperation
ReadS [WebGPUBlendOperation]
(Int -> ReadS WebGPUBlendOperation)
-> ReadS [WebGPUBlendOperation]
-> ReadPrec WebGPUBlendOperation
-> ReadPrec [WebGPUBlendOperation]
-> Read WebGPUBlendOperation
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [WebGPUBlendOperation]
$creadListPrec :: ReadPrec [WebGPUBlendOperation]
readPrec :: ReadPrec WebGPUBlendOperation
$creadPrec :: ReadPrec WebGPUBlendOperation
readList :: ReadS [WebGPUBlendOperation]
$creadList :: ReadS [WebGPUBlendOperation]
readsPrec :: Int -> ReadS WebGPUBlendOperation
$creadsPrec :: Int -> ReadS WebGPUBlendOperation
Read, WebGPUBlendOperation -> WebGPUBlendOperation -> Bool
(WebGPUBlendOperation -> WebGPUBlendOperation -> Bool)
-> (WebGPUBlendOperation -> WebGPUBlendOperation -> Bool)
-> Eq WebGPUBlendOperation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WebGPUBlendOperation -> WebGPUBlendOperation -> Bool
$c/= :: WebGPUBlendOperation -> WebGPUBlendOperation -> Bool
== :: WebGPUBlendOperation -> WebGPUBlendOperation -> Bool
$c== :: WebGPUBlendOperation -> WebGPUBlendOperation -> Bool
Eq, Eq WebGPUBlendOperation
Eq WebGPUBlendOperation
-> (WebGPUBlendOperation -> WebGPUBlendOperation -> Ordering)
-> (WebGPUBlendOperation -> WebGPUBlendOperation -> Bool)
-> (WebGPUBlendOperation -> WebGPUBlendOperation -> Bool)
-> (WebGPUBlendOperation -> WebGPUBlendOperation -> Bool)
-> (WebGPUBlendOperation -> WebGPUBlendOperation -> Bool)
-> (WebGPUBlendOperation
    -> WebGPUBlendOperation -> WebGPUBlendOperation)
-> (WebGPUBlendOperation
    -> WebGPUBlendOperation -> WebGPUBlendOperation)
-> Ord WebGPUBlendOperation
WebGPUBlendOperation -> WebGPUBlendOperation -> Bool
WebGPUBlendOperation -> WebGPUBlendOperation -> Ordering
WebGPUBlendOperation
-> WebGPUBlendOperation -> WebGPUBlendOperation
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: WebGPUBlendOperation
-> WebGPUBlendOperation -> WebGPUBlendOperation
$cmin :: WebGPUBlendOperation
-> WebGPUBlendOperation -> WebGPUBlendOperation
max :: WebGPUBlendOperation
-> WebGPUBlendOperation -> WebGPUBlendOperation
$cmax :: WebGPUBlendOperation
-> WebGPUBlendOperation -> WebGPUBlendOperation
>= :: WebGPUBlendOperation -> WebGPUBlendOperation -> Bool
$c>= :: WebGPUBlendOperation -> WebGPUBlendOperation -> Bool
> :: WebGPUBlendOperation -> WebGPUBlendOperation -> Bool
$c> :: WebGPUBlendOperation -> WebGPUBlendOperation -> Bool
<= :: WebGPUBlendOperation -> WebGPUBlendOperation -> Bool
$c<= :: WebGPUBlendOperation -> WebGPUBlendOperation -> Bool
< :: WebGPUBlendOperation -> WebGPUBlendOperation -> Bool
$c< :: WebGPUBlendOperation -> WebGPUBlendOperation -> Bool
compare :: WebGPUBlendOperation -> WebGPUBlendOperation -> Ordering
$ccompare :: WebGPUBlendOperation -> WebGPUBlendOperation -> Ordering
$cp1Ord :: Eq WebGPUBlendOperation
Ord, Typeable)
 
instance ToJSVal WebGPUBlendOperation where
        toJSVal :: WebGPUBlendOperation -> JSM JSVal
toJSVal WebGPUBlendOperation
WebGPUBlendOperationAdd
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUBlendOperationAdd
        toJSVal WebGPUBlendOperation
WebGPUBlendOperationSubtract
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUBlendOperationSubtract
        toJSVal WebGPUBlendOperation
WebGPUBlendOperationReversesubtract
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUBlendOperationReversesubtract
        toJSVal WebGPUBlendOperation
WebGPUBlendOperationMin
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUBlendOperationMin
        toJSVal WebGPUBlendOperation
WebGPUBlendOperationMax
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUBlendOperationMax
 
instance FromJSVal WebGPUBlendOperation where
        fromJSVal :: JSVal -> JSM (Maybe WebGPUBlendOperation)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_WebGPUBlendOperationAdd JSM Bool
-> (Bool -> JSM (Maybe WebGPUBlendOperation))
-> JSM (Maybe WebGPUBlendOperation)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe WebGPUBlendOperation -> JSM (Maybe WebGPUBlendOperation)
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPUBlendOperation -> Maybe WebGPUBlendOperation
forall a. a -> Maybe a
Just WebGPUBlendOperation
WebGPUBlendOperationAdd)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_WebGPUBlendOperationSubtract JSM Bool
-> (Bool -> JSM (Maybe WebGPUBlendOperation))
-> JSM (Maybe WebGPUBlendOperation)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe WebGPUBlendOperation -> JSM (Maybe WebGPUBlendOperation)
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPUBlendOperation -> Maybe WebGPUBlendOperation
forall a. a -> Maybe a
Just WebGPUBlendOperation
WebGPUBlendOperationSubtract)
                                 Bool
False
                                   -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_WebGPUBlendOperationReversesubtract JSM Bool
-> (Bool -> JSM (Maybe WebGPUBlendOperation))
-> JSM (Maybe WebGPUBlendOperation)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                        \ Bool
r ->
                                          case Bool
r of
                                              Bool
True
                                                -> Maybe WebGPUBlendOperation -> JSM (Maybe WebGPUBlendOperation)
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPUBlendOperation -> Maybe WebGPUBlendOperation
forall a. a -> Maybe a
Just WebGPUBlendOperation
WebGPUBlendOperationReversesubtract)
                                              Bool
False
                                                -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_WebGPUBlendOperationMin JSM Bool
-> (Bool -> JSM (Maybe WebGPUBlendOperation))
-> JSM (Maybe WebGPUBlendOperation)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                     \ Bool
r ->
                                                       case Bool
r of
                                                           Bool
True
                                                             -> Maybe WebGPUBlendOperation -> JSM (Maybe WebGPUBlendOperation)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                  (WebGPUBlendOperation -> Maybe WebGPUBlendOperation
forall a. a -> Maybe a
Just WebGPUBlendOperation
WebGPUBlendOperationMin)
                                                           Bool
False
                                                             -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                                  String
js_WebGPUBlendOperationMax
                                                                  JSM Bool
-> (Bool -> JSM (Maybe WebGPUBlendOperation))
-> JSM (Maybe WebGPUBlendOperation)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                  \ Bool
r ->
                                                                    case Bool
r of
                                                                        Bool
True
                                                                          -> Maybe WebGPUBlendOperation -> JSM (Maybe WebGPUBlendOperation)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                               (WebGPUBlendOperation -> Maybe WebGPUBlendOperation
forall a. a -> Maybe a
Just
                                                                                  WebGPUBlendOperation
WebGPUBlendOperationMax)
                                                                        Bool
False -> Maybe WebGPUBlendOperation -> JSM (Maybe WebGPUBlendOperation)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe WebGPUBlendOperation
forall a. Maybe a
Nothing
js_WebGPUBlendOperationAdd :: String
js_WebGPUBlendOperationAdd = String
"add"
js_WebGPUBlendOperationSubtract :: String
js_WebGPUBlendOperationSubtract = String
"subtract"
js_WebGPUBlendOperationReversesubtract :: String
js_WebGPUBlendOperationReversesubtract = String
"reversesubtract"
js_WebGPUBlendOperationMin :: String
js_WebGPUBlendOperationMin = String
"min"
js_WebGPUBlendOperationMax :: String
js_WebGPUBlendOperationMax = String
"max"
 
data WebGPUBlendFactor = WebGPUBlendFactorZero
                       | WebGPUBlendFactorOne
                       | WebGPUBlendFactorSourcecolor
                       | WebGPUBlendFactorOneminussourcecolor
                       | WebGPUBlendFactorSourcealpha
                       | WebGPUBlendFactorOneminussourcealpha
                       | WebGPUBlendFactorDestinationcolor
                       | WebGPUBlendFactorOneminusdestinationcolor
                       | WebGPUBlendFactorDestinationalpha
                       | WebGPUBlendFactorOneminusdestinationalpha
                       | WebGPUBlendFactorSourcealphasaturated
                       | WebGPUBlendFactorBlendcolor
                       | WebGPUBlendFactorOneminusblendcolor
                       | WebGPUBlendFactorBlendalpha
                       | WebGPUBlendFactorOneminusblendalpha
                       deriving (Int -> WebGPUBlendFactor -> ShowS
[WebGPUBlendFactor] -> ShowS
WebGPUBlendFactor -> String
(Int -> WebGPUBlendFactor -> ShowS)
-> (WebGPUBlendFactor -> String)
-> ([WebGPUBlendFactor] -> ShowS)
-> Show WebGPUBlendFactor
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WebGPUBlendFactor] -> ShowS
$cshowList :: [WebGPUBlendFactor] -> ShowS
show :: WebGPUBlendFactor -> String
$cshow :: WebGPUBlendFactor -> String
showsPrec :: Int -> WebGPUBlendFactor -> ShowS
$cshowsPrec :: Int -> WebGPUBlendFactor -> ShowS
Show, ReadPrec [WebGPUBlendFactor]
ReadPrec WebGPUBlendFactor
Int -> ReadS WebGPUBlendFactor
ReadS [WebGPUBlendFactor]
(Int -> ReadS WebGPUBlendFactor)
-> ReadS [WebGPUBlendFactor]
-> ReadPrec WebGPUBlendFactor
-> ReadPrec [WebGPUBlendFactor]
-> Read WebGPUBlendFactor
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [WebGPUBlendFactor]
$creadListPrec :: ReadPrec [WebGPUBlendFactor]
readPrec :: ReadPrec WebGPUBlendFactor
$creadPrec :: ReadPrec WebGPUBlendFactor
readList :: ReadS [WebGPUBlendFactor]
$creadList :: ReadS [WebGPUBlendFactor]
readsPrec :: Int -> ReadS WebGPUBlendFactor
$creadsPrec :: Int -> ReadS WebGPUBlendFactor
Read, WebGPUBlendFactor -> WebGPUBlendFactor -> Bool
(WebGPUBlendFactor -> WebGPUBlendFactor -> Bool)
-> (WebGPUBlendFactor -> WebGPUBlendFactor -> Bool)
-> Eq WebGPUBlendFactor
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WebGPUBlendFactor -> WebGPUBlendFactor -> Bool
$c/= :: WebGPUBlendFactor -> WebGPUBlendFactor -> Bool
== :: WebGPUBlendFactor -> WebGPUBlendFactor -> Bool
$c== :: WebGPUBlendFactor -> WebGPUBlendFactor -> Bool
Eq, Eq WebGPUBlendFactor
Eq WebGPUBlendFactor
-> (WebGPUBlendFactor -> WebGPUBlendFactor -> Ordering)
-> (WebGPUBlendFactor -> WebGPUBlendFactor -> Bool)
-> (WebGPUBlendFactor -> WebGPUBlendFactor -> Bool)
-> (WebGPUBlendFactor -> WebGPUBlendFactor -> Bool)
-> (WebGPUBlendFactor -> WebGPUBlendFactor -> Bool)
-> (WebGPUBlendFactor -> WebGPUBlendFactor -> WebGPUBlendFactor)
-> (WebGPUBlendFactor -> WebGPUBlendFactor -> WebGPUBlendFactor)
-> Ord WebGPUBlendFactor
WebGPUBlendFactor -> WebGPUBlendFactor -> Bool
WebGPUBlendFactor -> WebGPUBlendFactor -> Ordering
WebGPUBlendFactor -> WebGPUBlendFactor -> WebGPUBlendFactor
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: WebGPUBlendFactor -> WebGPUBlendFactor -> WebGPUBlendFactor
$cmin :: WebGPUBlendFactor -> WebGPUBlendFactor -> WebGPUBlendFactor
max :: WebGPUBlendFactor -> WebGPUBlendFactor -> WebGPUBlendFactor
$cmax :: WebGPUBlendFactor -> WebGPUBlendFactor -> WebGPUBlendFactor
>= :: WebGPUBlendFactor -> WebGPUBlendFactor -> Bool
$c>= :: WebGPUBlendFactor -> WebGPUBlendFactor -> Bool
> :: WebGPUBlendFactor -> WebGPUBlendFactor -> Bool
$c> :: WebGPUBlendFactor -> WebGPUBlendFactor -> Bool
<= :: WebGPUBlendFactor -> WebGPUBlendFactor -> Bool
$c<= :: WebGPUBlendFactor -> WebGPUBlendFactor -> Bool
< :: WebGPUBlendFactor -> WebGPUBlendFactor -> Bool
$c< :: WebGPUBlendFactor -> WebGPUBlendFactor -> Bool
compare :: WebGPUBlendFactor -> WebGPUBlendFactor -> Ordering
$ccompare :: WebGPUBlendFactor -> WebGPUBlendFactor -> Ordering
$cp1Ord :: Eq WebGPUBlendFactor
Ord, Typeable)
 
instance ToJSVal WebGPUBlendFactor where
        toJSVal :: WebGPUBlendFactor -> JSM JSVal
toJSVal WebGPUBlendFactor
WebGPUBlendFactorZero = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUBlendFactorZero
        toJSVal WebGPUBlendFactor
WebGPUBlendFactorOne = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUBlendFactorOne
        toJSVal WebGPUBlendFactor
WebGPUBlendFactorSourcecolor
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUBlendFactorSourcecolor
        toJSVal WebGPUBlendFactor
WebGPUBlendFactorOneminussourcecolor
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUBlendFactorOneminussourcecolor
        toJSVal WebGPUBlendFactor
WebGPUBlendFactorSourcealpha
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUBlendFactorSourcealpha
        toJSVal WebGPUBlendFactor
WebGPUBlendFactorOneminussourcealpha
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUBlendFactorOneminussourcealpha
        toJSVal WebGPUBlendFactor
WebGPUBlendFactorDestinationcolor
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUBlendFactorDestinationcolor
        toJSVal WebGPUBlendFactor
WebGPUBlendFactorOneminusdestinationcolor
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUBlendFactorOneminusdestinationcolor
        toJSVal WebGPUBlendFactor
WebGPUBlendFactorDestinationalpha
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUBlendFactorDestinationalpha
        toJSVal WebGPUBlendFactor
WebGPUBlendFactorOneminusdestinationalpha
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUBlendFactorOneminusdestinationalpha
        toJSVal WebGPUBlendFactor
WebGPUBlendFactorSourcealphasaturated
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUBlendFactorSourcealphasaturated
        toJSVal WebGPUBlendFactor
WebGPUBlendFactorBlendcolor
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUBlendFactorBlendcolor
        toJSVal WebGPUBlendFactor
WebGPUBlendFactorOneminusblendcolor
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUBlendFactorOneminusblendcolor
        toJSVal WebGPUBlendFactor
WebGPUBlendFactorBlendalpha
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUBlendFactorBlendalpha
        toJSVal WebGPUBlendFactor
WebGPUBlendFactorOneminusblendalpha
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUBlendFactorOneminusblendalpha
 
instance FromJSVal WebGPUBlendFactor where
        fromJSVal :: JSVal -> JSM (Maybe WebGPUBlendFactor)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_WebGPUBlendFactorZero JSM Bool
-> (Bool -> JSM (Maybe WebGPUBlendFactor))
-> JSM (Maybe WebGPUBlendFactor)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe WebGPUBlendFactor -> JSM (Maybe WebGPUBlendFactor)
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPUBlendFactor -> Maybe WebGPUBlendFactor
forall a. a -> Maybe a
Just WebGPUBlendFactor
WebGPUBlendFactorZero)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_WebGPUBlendFactorOne JSM Bool
-> (Bool -> JSM (Maybe WebGPUBlendFactor))
-> JSM (Maybe WebGPUBlendFactor)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe WebGPUBlendFactor -> JSM (Maybe WebGPUBlendFactor)
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPUBlendFactor -> Maybe WebGPUBlendFactor
forall a. a -> Maybe a
Just WebGPUBlendFactor
WebGPUBlendFactorOne)
                                 Bool
False
                                   -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_WebGPUBlendFactorSourcecolor JSM Bool
-> (Bool -> JSM (Maybe WebGPUBlendFactor))
-> JSM (Maybe WebGPUBlendFactor)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                        \ Bool
r ->
                                          case Bool
r of
                                              Bool
True -> Maybe WebGPUBlendFactor -> JSM (Maybe WebGPUBlendFactor)
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPUBlendFactor -> Maybe WebGPUBlendFactor
forall a. a -> Maybe a
Just WebGPUBlendFactor
WebGPUBlendFactorSourcecolor)
                                              Bool
False
                                                -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                     String
js_WebGPUBlendFactorOneminussourcecolor
                                                     JSM Bool
-> (Bool -> JSM (Maybe WebGPUBlendFactor))
-> JSM (Maybe WebGPUBlendFactor)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                     \ Bool
r ->
                                                       case Bool
r of
                                                           Bool
True
                                                             -> Maybe WebGPUBlendFactor -> JSM (Maybe WebGPUBlendFactor)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                  (WebGPUBlendFactor -> Maybe WebGPUBlendFactor
forall a. a -> Maybe a
Just
                                                                     WebGPUBlendFactor
WebGPUBlendFactorOneminussourcecolor)
                                                           Bool
False
                                                             -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                                  String
js_WebGPUBlendFactorSourcealpha
                                                                  JSM Bool
-> (Bool -> JSM (Maybe WebGPUBlendFactor))
-> JSM (Maybe WebGPUBlendFactor)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                  \ Bool
r ->
                                                                    case Bool
r of
                                                                        Bool
True
                                                                          -> Maybe WebGPUBlendFactor -> JSM (Maybe WebGPUBlendFactor)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                               (WebGPUBlendFactor -> Maybe WebGPUBlendFactor
forall a. a -> Maybe a
Just
                                                                                  WebGPUBlendFactor
WebGPUBlendFactorSourcealpha)
                                                                        Bool
False
                                                                          -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                                               String
js_WebGPUBlendFactorOneminussourcealpha
                                                                               JSM Bool
-> (Bool -> JSM (Maybe WebGPUBlendFactor))
-> JSM (Maybe WebGPUBlendFactor)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                               \ Bool
r ->
                                                                                 case Bool
r of
                                                                                     Bool
True
                                                                                       -> Maybe WebGPUBlendFactor -> JSM (Maybe WebGPUBlendFactor)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                                            (WebGPUBlendFactor -> Maybe WebGPUBlendFactor
forall a. a -> Maybe a
Just
                                                                                               WebGPUBlendFactor
WebGPUBlendFactorOneminussourcealpha)
                                                                                     Bool
False
                                                                                       -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                                                            String
js_WebGPUBlendFactorDestinationcolor
                                                                                            JSM Bool
-> (Bool -> JSM (Maybe WebGPUBlendFactor))
-> JSM (Maybe WebGPUBlendFactor)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                                            \ Bool
r ->
                                                                                              case Bool
r
                                                                                                of
                                                                                                  Bool
True
                                                                                                    -> Maybe WebGPUBlendFactor -> JSM (Maybe WebGPUBlendFactor)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                                                         (WebGPUBlendFactor -> Maybe WebGPUBlendFactor
forall a. a -> Maybe a
Just
                                                                                                            WebGPUBlendFactor
WebGPUBlendFactorDestinationcolor)
                                                                                                  Bool
False
                                                                                                    -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                                                                         String
js_WebGPUBlendFactorOneminusdestinationcolor
                                                                                                         JSM Bool
-> (Bool -> JSM (Maybe WebGPUBlendFactor))
-> JSM (Maybe WebGPUBlendFactor)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                                                         \ Bool
r
                                                                                                           ->
                                                                                                           case
                                                                                                             Bool
r
                                                                                                             of
                                                                                                               Bool
True
                                                                                                                 -> Maybe WebGPUBlendFactor -> JSM (Maybe WebGPUBlendFactor)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                                                                      (WebGPUBlendFactor -> Maybe WebGPUBlendFactor
forall a. a -> Maybe a
Just
                                                                                                                         WebGPUBlendFactor
WebGPUBlendFactorOneminusdestinationcolor)
                                                                                                               Bool
False
                                                                                                                 -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                                                                                      String
js_WebGPUBlendFactorDestinationalpha
                                                                                                                      JSM Bool
-> (Bool -> JSM (Maybe WebGPUBlendFactor))
-> JSM (Maybe WebGPUBlendFactor)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                                                                      \ Bool
r
                                                                                                                        ->
                                                                                                                        case
                                                                                                                          Bool
r
                                                                                                                          of
                                                                                                                            Bool
True
                                                                                                                              -> Maybe WebGPUBlendFactor -> JSM (Maybe WebGPUBlendFactor)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                                                                                   (WebGPUBlendFactor -> Maybe WebGPUBlendFactor
forall a. a -> Maybe a
Just
                                                                                                                                      WebGPUBlendFactor
WebGPUBlendFactorDestinationalpha)
                                                                                                                            Bool
False
                                                                                                                              -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                                                                                                   String
js_WebGPUBlendFactorOneminusdestinationalpha
                                                                                                                                   JSM Bool
-> (Bool -> JSM (Maybe WebGPUBlendFactor))
-> JSM (Maybe WebGPUBlendFactor)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                                                                                   \ Bool
r
                                                                                                                                     ->
                                                                                                                                     case
                                                                                                                                       Bool
r
                                                                                                                                       of
                                                                                                                                         Bool
True
                                                                                                                                           -> Maybe WebGPUBlendFactor -> JSM (Maybe WebGPUBlendFactor)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                                                                                                (WebGPUBlendFactor -> Maybe WebGPUBlendFactor
forall a. a -> Maybe a
Just
                                                                                                                                                   WebGPUBlendFactor
WebGPUBlendFactorOneminusdestinationalpha)
                                                                                                                                         Bool
False
                                                                                                                                           -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                                                                                                                String
js_WebGPUBlendFactorSourcealphasaturated
                                                                                                                                                JSM Bool
-> (Bool -> JSM (Maybe WebGPUBlendFactor))
-> JSM (Maybe WebGPUBlendFactor)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                                                                                                \ Bool
r
                                                                                                                                                  ->
                                                                                                                                                  case
                                                                                                                                                    Bool
r
                                                                                                                                                    of
                                                                                                                                                      Bool
True
                                                                                                                                                        -> Maybe WebGPUBlendFactor -> JSM (Maybe WebGPUBlendFactor)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                                                                                                             (WebGPUBlendFactor -> Maybe WebGPUBlendFactor
forall a. a -> Maybe a
Just
                                                                                                                                                                WebGPUBlendFactor
WebGPUBlendFactorSourcealphasaturated)
                                                                                                                                                      Bool
False
                                                                                                                                                        -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                                                                                                                             String
js_WebGPUBlendFactorBlendcolor
                                                                                                                                                             JSM Bool
-> (Bool -> JSM (Maybe WebGPUBlendFactor))
-> JSM (Maybe WebGPUBlendFactor)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                                                                                                             \ Bool
r
                                                                                                                                                               ->
                                                                                                                                                               case
                                                                                                                                                                 Bool
r
                                                                                                                                                                 of
                                                                                                                                                                   Bool
True
                                                                                                                                                                     -> Maybe WebGPUBlendFactor -> JSM (Maybe WebGPUBlendFactor)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                                                                                                                          (WebGPUBlendFactor -> Maybe WebGPUBlendFactor
forall a. a -> Maybe a
Just
                                                                                                                                                                             WebGPUBlendFactor
WebGPUBlendFactorBlendcolor)
                                                                                                                                                                   Bool
False
                                                                                                                                                                     -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                                                                                                                                          String
js_WebGPUBlendFactorOneminusblendcolor
                                                                                                                                                                          JSM Bool
-> (Bool -> JSM (Maybe WebGPUBlendFactor))
-> JSM (Maybe WebGPUBlendFactor)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                                                                                                                          \ Bool
r
                                                                                                                                                                            ->
                                                                                                                                                                            case
                                                                                                                                                                              Bool
r
                                                                                                                                                                              of
                                                                                                                                                                                Bool
True
                                                                                                                                                                                  -> Maybe WebGPUBlendFactor -> JSM (Maybe WebGPUBlendFactor)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                                                                                                                                       (WebGPUBlendFactor -> Maybe WebGPUBlendFactor
forall a. a -> Maybe a
Just
                                                                                                                                                                                          WebGPUBlendFactor
WebGPUBlendFactorOneminusblendcolor)
                                                                                                                                                                                Bool
False
                                                                                                                                                                                  -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                                                                                                                                                       String
js_WebGPUBlendFactorBlendalpha
                                                                                                                                                                                       JSM Bool
-> (Bool -> JSM (Maybe WebGPUBlendFactor))
-> JSM (Maybe WebGPUBlendFactor)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                                                                                                                                       \ Bool
r
                                                                                                                                                                                         ->
                                                                                                                                                                                         case
                                                                                                                                                                                           Bool
r
                                                                                                                                                                                           of
                                                                                                                                                                                             Bool
True
                                                                                                                                                                                               -> Maybe WebGPUBlendFactor -> JSM (Maybe WebGPUBlendFactor)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                                                                                                                                                    (WebGPUBlendFactor -> Maybe WebGPUBlendFactor
forall a. a -> Maybe a
Just
                                                                                                                                                                                                       WebGPUBlendFactor
WebGPUBlendFactorBlendalpha)
                                                                                                                                                                                             Bool
False
                                                                                                                                                                                               -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                                                                                                                                                                    String
js_WebGPUBlendFactorOneminusblendalpha
                                                                                                                                                                                                    JSM Bool
-> (Bool -> JSM (Maybe WebGPUBlendFactor))
-> JSM (Maybe WebGPUBlendFactor)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                                                                                                                                                    \ Bool
r
                                                                                                                                                                                                      ->
                                                                                                                                                                                                      case
                                                                                                                                                                                                        Bool
r
                                                                                                                                                                                                        of
                                                                                                                                                                                                          Bool
True
                                                                                                                                                                                                            -> Maybe WebGPUBlendFactor -> JSM (Maybe WebGPUBlendFactor)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                                                                                                                                                                 (WebGPUBlendFactor -> Maybe WebGPUBlendFactor
forall a. a -> Maybe a
Just
                                                                                                                                                                                                                    WebGPUBlendFactor
WebGPUBlendFactorOneminusblendalpha)
                                                                                                                                                                                                          Bool
False
                                                                                                                                                                                                            -> Maybe WebGPUBlendFactor -> JSM (Maybe WebGPUBlendFactor)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                                                                                                                                                                 Maybe WebGPUBlendFactor
forall a. Maybe a
Nothing
js_WebGPUBlendFactorZero :: String
js_WebGPUBlendFactorZero = String
"zero"
js_WebGPUBlendFactorOne :: String
js_WebGPUBlendFactorOne = String
"one"
js_WebGPUBlendFactorSourcecolor :: String
js_WebGPUBlendFactorSourcecolor = String
"sourcecolor"
js_WebGPUBlendFactorOneminussourcecolor :: String
js_WebGPUBlendFactorOneminussourcecolor = String
"oneminussourcecolor"
js_WebGPUBlendFactorSourcealpha :: String
js_WebGPUBlendFactorSourcealpha = String
"sourcealpha"
js_WebGPUBlendFactorOneminussourcealpha :: String
js_WebGPUBlendFactorOneminussourcealpha = String
"oneminussourcealpha"
js_WebGPUBlendFactorDestinationcolor :: String
js_WebGPUBlendFactorDestinationcolor = String
"destinationcolor"
js_WebGPUBlendFactorOneminusdestinationcolor :: String
js_WebGPUBlendFactorOneminusdestinationcolor
  = String
"oneminusdestinationcolor"
js_WebGPUBlendFactorDestinationalpha :: String
js_WebGPUBlendFactorDestinationalpha = String
"destinationalpha"
js_WebGPUBlendFactorOneminusdestinationalpha :: String
js_WebGPUBlendFactorOneminusdestinationalpha
  = String
"oneminusdestinationalpha"
js_WebGPUBlendFactorSourcealphasaturated :: String
js_WebGPUBlendFactorSourcealphasaturated = String
"sourcealphasaturated"
js_WebGPUBlendFactorBlendcolor :: String
js_WebGPUBlendFactorBlendcolor = String
"blendcolor"
js_WebGPUBlendFactorOneminusblendcolor :: String
js_WebGPUBlendFactorOneminusblendcolor = String
"oneminusblendcolor"
js_WebGPUBlendFactorBlendalpha :: String
js_WebGPUBlendFactorBlendalpha = String
"blendalpha"
js_WebGPUBlendFactorOneminusblendalpha :: String
js_WebGPUBlendFactorOneminusblendalpha = String
"oneminusblendalpha"
 
data WebGPUColorWriteMask = WebGPUColorWriteMaskNone
                          | WebGPUColorWriteMaskRed
                          | WebGPUColorWriteMaskGreen
                          | WebGPUColorWriteMaskBlue
                          | WebGPUColorWriteMaskAlpha
                          | WebGPUColorWriteMaskAll
                          deriving (Int -> WebGPUColorWriteMask -> ShowS
[WebGPUColorWriteMask] -> ShowS
WebGPUColorWriteMask -> String
(Int -> WebGPUColorWriteMask -> ShowS)
-> (WebGPUColorWriteMask -> String)
-> ([WebGPUColorWriteMask] -> ShowS)
-> Show WebGPUColorWriteMask
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WebGPUColorWriteMask] -> ShowS
$cshowList :: [WebGPUColorWriteMask] -> ShowS
show :: WebGPUColorWriteMask -> String
$cshow :: WebGPUColorWriteMask -> String
showsPrec :: Int -> WebGPUColorWriteMask -> ShowS
$cshowsPrec :: Int -> WebGPUColorWriteMask -> ShowS
Show, ReadPrec [WebGPUColorWriteMask]
ReadPrec WebGPUColorWriteMask
Int -> ReadS WebGPUColorWriteMask
ReadS [WebGPUColorWriteMask]
(Int -> ReadS WebGPUColorWriteMask)
-> ReadS [WebGPUColorWriteMask]
-> ReadPrec WebGPUColorWriteMask
-> ReadPrec [WebGPUColorWriteMask]
-> Read WebGPUColorWriteMask
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [WebGPUColorWriteMask]
$creadListPrec :: ReadPrec [WebGPUColorWriteMask]
readPrec :: ReadPrec WebGPUColorWriteMask
$creadPrec :: ReadPrec WebGPUColorWriteMask
readList :: ReadS [WebGPUColorWriteMask]
$creadList :: ReadS [WebGPUColorWriteMask]
readsPrec :: Int -> ReadS WebGPUColorWriteMask
$creadsPrec :: Int -> ReadS WebGPUColorWriteMask
Read, WebGPUColorWriteMask -> WebGPUColorWriteMask -> Bool
(WebGPUColorWriteMask -> WebGPUColorWriteMask -> Bool)
-> (WebGPUColorWriteMask -> WebGPUColorWriteMask -> Bool)
-> Eq WebGPUColorWriteMask
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WebGPUColorWriteMask -> WebGPUColorWriteMask -> Bool
$c/= :: WebGPUColorWriteMask -> WebGPUColorWriteMask -> Bool
== :: WebGPUColorWriteMask -> WebGPUColorWriteMask -> Bool
$c== :: WebGPUColorWriteMask -> WebGPUColorWriteMask -> Bool
Eq, Eq WebGPUColorWriteMask
Eq WebGPUColorWriteMask
-> (WebGPUColorWriteMask -> WebGPUColorWriteMask -> Ordering)
-> (WebGPUColorWriteMask -> WebGPUColorWriteMask -> Bool)
-> (WebGPUColorWriteMask -> WebGPUColorWriteMask -> Bool)
-> (WebGPUColorWriteMask -> WebGPUColorWriteMask -> Bool)
-> (WebGPUColorWriteMask -> WebGPUColorWriteMask -> Bool)
-> (WebGPUColorWriteMask
    -> WebGPUColorWriteMask -> WebGPUColorWriteMask)
-> (WebGPUColorWriteMask
    -> WebGPUColorWriteMask -> WebGPUColorWriteMask)
-> Ord WebGPUColorWriteMask
WebGPUColorWriteMask -> WebGPUColorWriteMask -> Bool
WebGPUColorWriteMask -> WebGPUColorWriteMask -> Ordering
WebGPUColorWriteMask
-> WebGPUColorWriteMask -> WebGPUColorWriteMask
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: WebGPUColorWriteMask
-> WebGPUColorWriteMask -> WebGPUColorWriteMask
$cmin :: WebGPUColorWriteMask
-> WebGPUColorWriteMask -> WebGPUColorWriteMask
max :: WebGPUColorWriteMask
-> WebGPUColorWriteMask -> WebGPUColorWriteMask
$cmax :: WebGPUColorWriteMask
-> WebGPUColorWriteMask -> WebGPUColorWriteMask
>= :: WebGPUColorWriteMask -> WebGPUColorWriteMask -> Bool
$c>= :: WebGPUColorWriteMask -> WebGPUColorWriteMask -> Bool
> :: WebGPUColorWriteMask -> WebGPUColorWriteMask -> Bool
$c> :: WebGPUColorWriteMask -> WebGPUColorWriteMask -> Bool
<= :: WebGPUColorWriteMask -> WebGPUColorWriteMask -> Bool
$c<= :: WebGPUColorWriteMask -> WebGPUColorWriteMask -> Bool
< :: WebGPUColorWriteMask -> WebGPUColorWriteMask -> Bool
$c< :: WebGPUColorWriteMask -> WebGPUColorWriteMask -> Bool
compare :: WebGPUColorWriteMask -> WebGPUColorWriteMask -> Ordering
$ccompare :: WebGPUColorWriteMask -> WebGPUColorWriteMask -> Ordering
$cp1Ord :: Eq WebGPUColorWriteMask
Ord, Typeable)
 
instance ToJSVal WebGPUColorWriteMask where
        toJSVal :: WebGPUColorWriteMask -> JSM JSVal
toJSVal WebGPUColorWriteMask
WebGPUColorWriteMaskNone
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUColorWriteMaskNone
        toJSVal WebGPUColorWriteMask
WebGPUColorWriteMaskRed
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUColorWriteMaskRed
        toJSVal WebGPUColorWriteMask
WebGPUColorWriteMaskGreen
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUColorWriteMaskGreen
        toJSVal WebGPUColorWriteMask
WebGPUColorWriteMaskBlue
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUColorWriteMaskBlue
        toJSVal WebGPUColorWriteMask
WebGPUColorWriteMaskAlpha
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUColorWriteMaskAlpha
        toJSVal WebGPUColorWriteMask
WebGPUColorWriteMaskAll
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUColorWriteMaskAll
 
instance FromJSVal WebGPUColorWriteMask where
        fromJSVal :: JSVal -> JSM (Maybe WebGPUColorWriteMask)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_WebGPUColorWriteMaskNone JSM Bool
-> (Bool -> JSM (Maybe WebGPUColorWriteMask))
-> JSM (Maybe WebGPUColorWriteMask)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe WebGPUColorWriteMask -> JSM (Maybe WebGPUColorWriteMask)
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPUColorWriteMask -> Maybe WebGPUColorWriteMask
forall a. a -> Maybe a
Just WebGPUColorWriteMask
WebGPUColorWriteMaskNone)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_WebGPUColorWriteMaskRed JSM Bool
-> (Bool -> JSM (Maybe WebGPUColorWriteMask))
-> JSM (Maybe WebGPUColorWriteMask)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe WebGPUColorWriteMask -> JSM (Maybe WebGPUColorWriteMask)
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPUColorWriteMask -> Maybe WebGPUColorWriteMask
forall a. a -> Maybe a
Just WebGPUColorWriteMask
WebGPUColorWriteMaskRed)
                                 Bool
False
                                   -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_WebGPUColorWriteMaskGreen JSM Bool
-> (Bool -> JSM (Maybe WebGPUColorWriteMask))
-> JSM (Maybe WebGPUColorWriteMask)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                        \ Bool
r ->
                                          case Bool
r of
                                              Bool
True -> Maybe WebGPUColorWriteMask -> JSM (Maybe WebGPUColorWriteMask)
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPUColorWriteMask -> Maybe WebGPUColorWriteMask
forall a. a -> Maybe a
Just WebGPUColorWriteMask
WebGPUColorWriteMaskGreen)
                                              Bool
False
                                                -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_WebGPUColorWriteMaskBlue JSM Bool
-> (Bool -> JSM (Maybe WebGPUColorWriteMask))
-> JSM (Maybe WebGPUColorWriteMask)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                     \ Bool
r ->
                                                       case Bool
r of
                                                           Bool
True
                                                             -> Maybe WebGPUColorWriteMask -> JSM (Maybe WebGPUColorWriteMask)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                  (WebGPUColorWriteMask -> Maybe WebGPUColorWriteMask
forall a. a -> Maybe a
Just WebGPUColorWriteMask
WebGPUColorWriteMaskBlue)
                                                           Bool
False
                                                             -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                                  String
js_WebGPUColorWriteMaskAlpha
                                                                  JSM Bool
-> (Bool -> JSM (Maybe WebGPUColorWriteMask))
-> JSM (Maybe WebGPUColorWriteMask)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                  \ Bool
r ->
                                                                    case Bool
r of
                                                                        Bool
True
                                                                          -> Maybe WebGPUColorWriteMask -> JSM (Maybe WebGPUColorWriteMask)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                               (WebGPUColorWriteMask -> Maybe WebGPUColorWriteMask
forall a. a -> Maybe a
Just
                                                                                  WebGPUColorWriteMask
WebGPUColorWriteMaskAlpha)
                                                                        Bool
False
                                                                          -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                                               String
js_WebGPUColorWriteMaskAll
                                                                               JSM Bool
-> (Bool -> JSM (Maybe WebGPUColorWriteMask))
-> JSM (Maybe WebGPUColorWriteMask)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                               \ Bool
r ->
                                                                                 case Bool
r of
                                                                                     Bool
True
                                                                                       -> Maybe WebGPUColorWriteMask -> JSM (Maybe WebGPUColorWriteMask)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                                            (WebGPUColorWriteMask -> Maybe WebGPUColorWriteMask
forall a. a -> Maybe a
Just
                                                                                               WebGPUColorWriteMask
WebGPUColorWriteMaskAll)
                                                                                     Bool
False
                                                                                       -> Maybe WebGPUColorWriteMask -> JSM (Maybe WebGPUColorWriteMask)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                                            Maybe WebGPUColorWriteMask
forall a. Maybe a
Nothing
js_WebGPUColorWriteMaskNone :: String
js_WebGPUColorWriteMaskNone = String
"none"
js_WebGPUColorWriteMaskRed :: String
js_WebGPUColorWriteMaskRed = String
"red"
js_WebGPUColorWriteMaskGreen :: String
js_WebGPUColorWriteMaskGreen = String
"green"
js_WebGPUColorWriteMaskBlue :: String
js_WebGPUColorWriteMaskBlue = String
"blue"
js_WebGPUColorWriteMaskAlpha :: String
js_WebGPUColorWriteMaskAlpha = String
"alpha"
js_WebGPUColorWriteMaskAll :: String
js_WebGPUColorWriteMaskAll = String
"all"
 
data WebGPUMultisampleDepthResolveFilter = WebGPUMultisampleDepthResolveFilterSample0
                                         | WebGPUMultisampleDepthResolveFilterMin
                                         | WebGPUMultisampleDepthResolveFilterMax
                                         deriving (Int -> WebGPUMultisampleDepthResolveFilter -> ShowS
[WebGPUMultisampleDepthResolveFilter] -> ShowS
WebGPUMultisampleDepthResolveFilter -> String
(Int -> WebGPUMultisampleDepthResolveFilter -> ShowS)
-> (WebGPUMultisampleDepthResolveFilter -> String)
-> ([WebGPUMultisampleDepthResolveFilter] -> ShowS)
-> Show WebGPUMultisampleDepthResolveFilter
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WebGPUMultisampleDepthResolveFilter] -> ShowS
$cshowList :: [WebGPUMultisampleDepthResolveFilter] -> ShowS
show :: WebGPUMultisampleDepthResolveFilter -> String
$cshow :: WebGPUMultisampleDepthResolveFilter -> String
showsPrec :: Int -> WebGPUMultisampleDepthResolveFilter -> ShowS
$cshowsPrec :: Int -> WebGPUMultisampleDepthResolveFilter -> ShowS
Show, ReadPrec [WebGPUMultisampleDepthResolveFilter]
ReadPrec WebGPUMultisampleDepthResolveFilter
Int -> ReadS WebGPUMultisampleDepthResolveFilter
ReadS [WebGPUMultisampleDepthResolveFilter]
(Int -> ReadS WebGPUMultisampleDepthResolveFilter)
-> ReadS [WebGPUMultisampleDepthResolveFilter]
-> ReadPrec WebGPUMultisampleDepthResolveFilter
-> ReadPrec [WebGPUMultisampleDepthResolveFilter]
-> Read WebGPUMultisampleDepthResolveFilter
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [WebGPUMultisampleDepthResolveFilter]
$creadListPrec :: ReadPrec [WebGPUMultisampleDepthResolveFilter]
readPrec :: ReadPrec WebGPUMultisampleDepthResolveFilter
$creadPrec :: ReadPrec WebGPUMultisampleDepthResolveFilter
readList :: ReadS [WebGPUMultisampleDepthResolveFilter]
$creadList :: ReadS [WebGPUMultisampleDepthResolveFilter]
readsPrec :: Int -> ReadS WebGPUMultisampleDepthResolveFilter
$creadsPrec :: Int -> ReadS WebGPUMultisampleDepthResolveFilter
Read, WebGPUMultisampleDepthResolveFilter
-> WebGPUMultisampleDepthResolveFilter -> Bool
(WebGPUMultisampleDepthResolveFilter
 -> WebGPUMultisampleDepthResolveFilter -> Bool)
-> (WebGPUMultisampleDepthResolveFilter
    -> WebGPUMultisampleDepthResolveFilter -> Bool)
-> Eq WebGPUMultisampleDepthResolveFilter
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WebGPUMultisampleDepthResolveFilter
-> WebGPUMultisampleDepthResolveFilter -> Bool
$c/= :: WebGPUMultisampleDepthResolveFilter
-> WebGPUMultisampleDepthResolveFilter -> Bool
== :: WebGPUMultisampleDepthResolveFilter
-> WebGPUMultisampleDepthResolveFilter -> Bool
$c== :: WebGPUMultisampleDepthResolveFilter
-> WebGPUMultisampleDepthResolveFilter -> Bool
Eq, Eq WebGPUMultisampleDepthResolveFilter
Eq WebGPUMultisampleDepthResolveFilter
-> (WebGPUMultisampleDepthResolveFilter
    -> WebGPUMultisampleDepthResolveFilter -> Ordering)
-> (WebGPUMultisampleDepthResolveFilter
    -> WebGPUMultisampleDepthResolveFilter -> Bool)
-> (WebGPUMultisampleDepthResolveFilter
    -> WebGPUMultisampleDepthResolveFilter -> Bool)
-> (WebGPUMultisampleDepthResolveFilter
    -> WebGPUMultisampleDepthResolveFilter -> Bool)
-> (WebGPUMultisampleDepthResolveFilter
    -> WebGPUMultisampleDepthResolveFilter -> Bool)
-> (WebGPUMultisampleDepthResolveFilter
    -> WebGPUMultisampleDepthResolveFilter
    -> WebGPUMultisampleDepthResolveFilter)
-> (WebGPUMultisampleDepthResolveFilter
    -> WebGPUMultisampleDepthResolveFilter
    -> WebGPUMultisampleDepthResolveFilter)
-> Ord WebGPUMultisampleDepthResolveFilter
WebGPUMultisampleDepthResolveFilter
-> WebGPUMultisampleDepthResolveFilter -> Bool
WebGPUMultisampleDepthResolveFilter
-> WebGPUMultisampleDepthResolveFilter -> Ordering
WebGPUMultisampleDepthResolveFilter
-> WebGPUMultisampleDepthResolveFilter
-> WebGPUMultisampleDepthResolveFilter
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: WebGPUMultisampleDepthResolveFilter
-> WebGPUMultisampleDepthResolveFilter
-> WebGPUMultisampleDepthResolveFilter
$cmin :: WebGPUMultisampleDepthResolveFilter
-> WebGPUMultisampleDepthResolveFilter
-> WebGPUMultisampleDepthResolveFilter
max :: WebGPUMultisampleDepthResolveFilter
-> WebGPUMultisampleDepthResolveFilter
-> WebGPUMultisampleDepthResolveFilter
$cmax :: WebGPUMultisampleDepthResolveFilter
-> WebGPUMultisampleDepthResolveFilter
-> WebGPUMultisampleDepthResolveFilter
>= :: WebGPUMultisampleDepthResolveFilter
-> WebGPUMultisampleDepthResolveFilter -> Bool
$c>= :: WebGPUMultisampleDepthResolveFilter
-> WebGPUMultisampleDepthResolveFilter -> Bool
> :: WebGPUMultisampleDepthResolveFilter
-> WebGPUMultisampleDepthResolveFilter -> Bool
$c> :: WebGPUMultisampleDepthResolveFilter
-> WebGPUMultisampleDepthResolveFilter -> Bool
<= :: WebGPUMultisampleDepthResolveFilter
-> WebGPUMultisampleDepthResolveFilter -> Bool
$c<= :: WebGPUMultisampleDepthResolveFilter
-> WebGPUMultisampleDepthResolveFilter -> Bool
< :: WebGPUMultisampleDepthResolveFilter
-> WebGPUMultisampleDepthResolveFilter -> Bool
$c< :: WebGPUMultisampleDepthResolveFilter
-> WebGPUMultisampleDepthResolveFilter -> Bool
compare :: WebGPUMultisampleDepthResolveFilter
-> WebGPUMultisampleDepthResolveFilter -> Ordering
$ccompare :: WebGPUMultisampleDepthResolveFilter
-> WebGPUMultisampleDepthResolveFilter -> Ordering
$cp1Ord :: Eq WebGPUMultisampleDepthResolveFilter
Ord, Typeable)
 
instance ToJSVal WebGPUMultisampleDepthResolveFilter where
        toJSVal :: WebGPUMultisampleDepthResolveFilter -> JSM JSVal
toJSVal WebGPUMultisampleDepthResolveFilter
WebGPUMultisampleDepthResolveFilterSample0
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUMultisampleDepthResolveFilterSample0
        toJSVal WebGPUMultisampleDepthResolveFilter
WebGPUMultisampleDepthResolveFilterMin
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUMultisampleDepthResolveFilterMin
        toJSVal WebGPUMultisampleDepthResolveFilter
WebGPUMultisampleDepthResolveFilterMax
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUMultisampleDepthResolveFilterMax
 
instance FromJSVal WebGPUMultisampleDepthResolveFilter where
        fromJSVal :: JSVal -> JSM (Maybe WebGPUMultisampleDepthResolveFilter)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_WebGPUMultisampleDepthResolveFilterSample0 JSM Bool
-> (Bool -> JSM (Maybe WebGPUMultisampleDepthResolveFilter))
-> JSM (Maybe WebGPUMultisampleDepthResolveFilter)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe WebGPUMultisampleDepthResolveFilter
-> JSM (Maybe WebGPUMultisampleDepthResolveFilter)
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPUMultisampleDepthResolveFilter
-> Maybe WebGPUMultisampleDepthResolveFilter
forall a. a -> Maybe a
Just WebGPUMultisampleDepthResolveFilter
WebGPUMultisampleDepthResolveFilterSample0)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_WebGPUMultisampleDepthResolveFilterMin JSM Bool
-> (Bool -> JSM (Maybe WebGPUMultisampleDepthResolveFilter))
-> JSM (Maybe WebGPUMultisampleDepthResolveFilter)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe WebGPUMultisampleDepthResolveFilter
-> JSM (Maybe WebGPUMultisampleDepthResolveFilter)
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPUMultisampleDepthResolveFilter
-> Maybe WebGPUMultisampleDepthResolveFilter
forall a. a -> Maybe a
Just WebGPUMultisampleDepthResolveFilter
WebGPUMultisampleDepthResolveFilterMin)
                                 Bool
False
                                   -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_WebGPUMultisampleDepthResolveFilterMax JSM Bool
-> (Bool -> JSM (Maybe WebGPUMultisampleDepthResolveFilter))
-> JSM (Maybe WebGPUMultisampleDepthResolveFilter)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                        \ Bool
r ->
                                          case Bool
r of
                                              Bool
True
                                                -> Maybe WebGPUMultisampleDepthResolveFilter
-> JSM (Maybe WebGPUMultisampleDepthResolveFilter)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                     (WebGPUMultisampleDepthResolveFilter
-> Maybe WebGPUMultisampleDepthResolveFilter
forall a. a -> Maybe a
Just WebGPUMultisampleDepthResolveFilter
WebGPUMultisampleDepthResolveFilterMax)
                                              Bool
False -> Maybe WebGPUMultisampleDepthResolveFilter
-> JSM (Maybe WebGPUMultisampleDepthResolveFilter)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe WebGPUMultisampleDepthResolveFilter
forall a. Maybe a
Nothing
js_WebGPUMultisampleDepthResolveFilterSample0 :: String
js_WebGPUMultisampleDepthResolveFilterSample0 = String
"sample0"
js_WebGPUMultisampleDepthResolveFilterMin :: String
js_WebGPUMultisampleDepthResolveFilterMin = String
"min"
js_WebGPUMultisampleDepthResolveFilterMax :: String
js_WebGPUMultisampleDepthResolveFilterMax = String
"max"
 
data WebGPUFeatureSet = WebGPUFeatureSetLevel1
                      | WebGPUFeatureSetLevel2
                      deriving (Int -> WebGPUFeatureSet -> ShowS
[WebGPUFeatureSet] -> ShowS
WebGPUFeatureSet -> String
(Int -> WebGPUFeatureSet -> ShowS)
-> (WebGPUFeatureSet -> String)
-> ([WebGPUFeatureSet] -> ShowS)
-> Show WebGPUFeatureSet
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WebGPUFeatureSet] -> ShowS
$cshowList :: [WebGPUFeatureSet] -> ShowS
show :: WebGPUFeatureSet -> String
$cshow :: WebGPUFeatureSet -> String
showsPrec :: Int -> WebGPUFeatureSet -> ShowS
$cshowsPrec :: Int -> WebGPUFeatureSet -> ShowS
Show, ReadPrec [WebGPUFeatureSet]
ReadPrec WebGPUFeatureSet
Int -> ReadS WebGPUFeatureSet
ReadS [WebGPUFeatureSet]
(Int -> ReadS WebGPUFeatureSet)
-> ReadS [WebGPUFeatureSet]
-> ReadPrec WebGPUFeatureSet
-> ReadPrec [WebGPUFeatureSet]
-> Read WebGPUFeatureSet
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [WebGPUFeatureSet]
$creadListPrec :: ReadPrec [WebGPUFeatureSet]
readPrec :: ReadPrec WebGPUFeatureSet
$creadPrec :: ReadPrec WebGPUFeatureSet
readList :: ReadS [WebGPUFeatureSet]
$creadList :: ReadS [WebGPUFeatureSet]
readsPrec :: Int -> ReadS WebGPUFeatureSet
$creadsPrec :: Int -> ReadS WebGPUFeatureSet
Read, WebGPUFeatureSet -> WebGPUFeatureSet -> Bool
(WebGPUFeatureSet -> WebGPUFeatureSet -> Bool)
-> (WebGPUFeatureSet -> WebGPUFeatureSet -> Bool)
-> Eq WebGPUFeatureSet
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WebGPUFeatureSet -> WebGPUFeatureSet -> Bool
$c/= :: WebGPUFeatureSet -> WebGPUFeatureSet -> Bool
== :: WebGPUFeatureSet -> WebGPUFeatureSet -> Bool
$c== :: WebGPUFeatureSet -> WebGPUFeatureSet -> Bool
Eq, Eq WebGPUFeatureSet
Eq WebGPUFeatureSet
-> (WebGPUFeatureSet -> WebGPUFeatureSet -> Ordering)
-> (WebGPUFeatureSet -> WebGPUFeatureSet -> Bool)
-> (WebGPUFeatureSet -> WebGPUFeatureSet -> Bool)
-> (WebGPUFeatureSet -> WebGPUFeatureSet -> Bool)
-> (WebGPUFeatureSet -> WebGPUFeatureSet -> Bool)
-> (WebGPUFeatureSet -> WebGPUFeatureSet -> WebGPUFeatureSet)
-> (WebGPUFeatureSet -> WebGPUFeatureSet -> WebGPUFeatureSet)
-> Ord WebGPUFeatureSet
WebGPUFeatureSet -> WebGPUFeatureSet -> Bool
WebGPUFeatureSet -> WebGPUFeatureSet -> Ordering
WebGPUFeatureSet -> WebGPUFeatureSet -> WebGPUFeatureSet
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: WebGPUFeatureSet -> WebGPUFeatureSet -> WebGPUFeatureSet
$cmin :: WebGPUFeatureSet -> WebGPUFeatureSet -> WebGPUFeatureSet
max :: WebGPUFeatureSet -> WebGPUFeatureSet -> WebGPUFeatureSet
$cmax :: WebGPUFeatureSet -> WebGPUFeatureSet -> WebGPUFeatureSet
>= :: WebGPUFeatureSet -> WebGPUFeatureSet -> Bool
$c>= :: WebGPUFeatureSet -> WebGPUFeatureSet -> Bool
> :: WebGPUFeatureSet -> WebGPUFeatureSet -> Bool
$c> :: WebGPUFeatureSet -> WebGPUFeatureSet -> Bool
<= :: WebGPUFeatureSet -> WebGPUFeatureSet -> Bool
$c<= :: WebGPUFeatureSet -> WebGPUFeatureSet -> Bool
< :: WebGPUFeatureSet -> WebGPUFeatureSet -> Bool
$c< :: WebGPUFeatureSet -> WebGPUFeatureSet -> Bool
compare :: WebGPUFeatureSet -> WebGPUFeatureSet -> Ordering
$ccompare :: WebGPUFeatureSet -> WebGPUFeatureSet -> Ordering
$cp1Ord :: Eq WebGPUFeatureSet
Ord, Typeable)
 
instance ToJSVal WebGPUFeatureSet where
        toJSVal :: WebGPUFeatureSet -> JSM JSVal
toJSVal WebGPUFeatureSet
WebGPUFeatureSetLevel1 = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUFeatureSetLevel1
        toJSVal WebGPUFeatureSet
WebGPUFeatureSetLevel2 = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_WebGPUFeatureSetLevel2
 
instance FromJSVal WebGPUFeatureSet where
        fromJSVal :: JSVal -> JSM (Maybe WebGPUFeatureSet)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_WebGPUFeatureSetLevel1 JSM Bool
-> (Bool -> JSM (Maybe WebGPUFeatureSet))
-> JSM (Maybe WebGPUFeatureSet)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe WebGPUFeatureSet -> JSM (Maybe WebGPUFeatureSet)
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPUFeatureSet -> Maybe WebGPUFeatureSet
forall a. a -> Maybe a
Just WebGPUFeatureSet
WebGPUFeatureSetLevel1)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_WebGPUFeatureSetLevel2 JSM Bool
-> (Bool -> JSM (Maybe WebGPUFeatureSet))
-> JSM (Maybe WebGPUFeatureSet)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe WebGPUFeatureSet -> JSM (Maybe WebGPUFeatureSet)
forall (m :: * -> *) a. Monad m => a -> m a
return (WebGPUFeatureSet -> Maybe WebGPUFeatureSet
forall a. a -> Maybe a
Just WebGPUFeatureSet
WebGPUFeatureSetLevel2)
                                 Bool
False -> Maybe WebGPUFeatureSet -> JSM (Maybe WebGPUFeatureSet)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe WebGPUFeatureSet
forall a. Maybe a
Nothing
js_WebGPUFeatureSetLevel1 :: String
js_WebGPUFeatureSetLevel1 = String
"level1"
js_WebGPUFeatureSetLevel2 :: String
js_WebGPUFeatureSetLevel2 = String
"level2"
 
data VideoPresentationMode = VideoPresentationModeFullscreen
                           | VideoPresentationModePictureInPicture
                           | VideoPresentationModeInline
                           deriving (Int -> VideoPresentationMode -> ShowS
[VideoPresentationMode] -> ShowS
VideoPresentationMode -> String
(Int -> VideoPresentationMode -> ShowS)
-> (VideoPresentationMode -> String)
-> ([VideoPresentationMode] -> ShowS)
-> Show VideoPresentationMode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VideoPresentationMode] -> ShowS
$cshowList :: [VideoPresentationMode] -> ShowS
show :: VideoPresentationMode -> String
$cshow :: VideoPresentationMode -> String
showsPrec :: Int -> VideoPresentationMode -> ShowS
$cshowsPrec :: Int -> VideoPresentationMode -> ShowS
Show, ReadPrec [VideoPresentationMode]
ReadPrec VideoPresentationMode
Int -> ReadS VideoPresentationMode
ReadS [VideoPresentationMode]
(Int -> ReadS VideoPresentationMode)
-> ReadS [VideoPresentationMode]
-> ReadPrec VideoPresentationMode
-> ReadPrec [VideoPresentationMode]
-> Read VideoPresentationMode
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [VideoPresentationMode]
$creadListPrec :: ReadPrec [VideoPresentationMode]
readPrec :: ReadPrec VideoPresentationMode
$creadPrec :: ReadPrec VideoPresentationMode
readList :: ReadS [VideoPresentationMode]
$creadList :: ReadS [VideoPresentationMode]
readsPrec :: Int -> ReadS VideoPresentationMode
$creadsPrec :: Int -> ReadS VideoPresentationMode
Read, VideoPresentationMode -> VideoPresentationMode -> Bool
(VideoPresentationMode -> VideoPresentationMode -> Bool)
-> (VideoPresentationMode -> VideoPresentationMode -> Bool)
-> Eq VideoPresentationMode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VideoPresentationMode -> VideoPresentationMode -> Bool
$c/= :: VideoPresentationMode -> VideoPresentationMode -> Bool
== :: VideoPresentationMode -> VideoPresentationMode -> Bool
$c== :: VideoPresentationMode -> VideoPresentationMode -> Bool
Eq, Eq VideoPresentationMode
Eq VideoPresentationMode
-> (VideoPresentationMode -> VideoPresentationMode -> Ordering)
-> (VideoPresentationMode -> VideoPresentationMode -> Bool)
-> (VideoPresentationMode -> VideoPresentationMode -> Bool)
-> (VideoPresentationMode -> VideoPresentationMode -> Bool)
-> (VideoPresentationMode -> VideoPresentationMode -> Bool)
-> (VideoPresentationMode
    -> VideoPresentationMode -> VideoPresentationMode)
-> (VideoPresentationMode
    -> VideoPresentationMode -> VideoPresentationMode)
-> Ord VideoPresentationMode
VideoPresentationMode -> VideoPresentationMode -> Bool
VideoPresentationMode -> VideoPresentationMode -> Ordering
VideoPresentationMode
-> VideoPresentationMode -> VideoPresentationMode
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: VideoPresentationMode
-> VideoPresentationMode -> VideoPresentationMode
$cmin :: VideoPresentationMode
-> VideoPresentationMode -> VideoPresentationMode
max :: VideoPresentationMode
-> VideoPresentationMode -> VideoPresentationMode
$cmax :: VideoPresentationMode
-> VideoPresentationMode -> VideoPresentationMode
>= :: VideoPresentationMode -> VideoPresentationMode -> Bool
$c>= :: VideoPresentationMode -> VideoPresentationMode -> Bool
> :: VideoPresentationMode -> VideoPresentationMode -> Bool
$c> :: VideoPresentationMode -> VideoPresentationMode -> Bool
<= :: VideoPresentationMode -> VideoPresentationMode -> Bool
$c<= :: VideoPresentationMode -> VideoPresentationMode -> Bool
< :: VideoPresentationMode -> VideoPresentationMode -> Bool
$c< :: VideoPresentationMode -> VideoPresentationMode -> Bool
compare :: VideoPresentationMode -> VideoPresentationMode -> Ordering
$ccompare :: VideoPresentationMode -> VideoPresentationMode -> Ordering
$cp1Ord :: Eq VideoPresentationMode
Ord, Typeable)
 
instance ToJSVal VideoPresentationMode where
        toJSVal :: VideoPresentationMode -> JSM JSVal
toJSVal VideoPresentationMode
VideoPresentationModeFullscreen
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_VideoPresentationModeFullscreen
        toJSVal VideoPresentationMode
VideoPresentationModePictureInPicture
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_VideoPresentationModePictureInPicture
        toJSVal VideoPresentationMode
VideoPresentationModeInline
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_VideoPresentationModeInline
 
instance FromJSVal VideoPresentationMode where
        fromJSVal :: JSVal -> JSM (Maybe VideoPresentationMode)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_VideoPresentationModeFullscreen JSM Bool
-> (Bool -> JSM (Maybe VideoPresentationMode))
-> JSM (Maybe VideoPresentationMode)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe VideoPresentationMode -> JSM (Maybe VideoPresentationMode)
forall (m :: * -> *) a. Monad m => a -> m a
return (VideoPresentationMode -> Maybe VideoPresentationMode
forall a. a -> Maybe a
Just VideoPresentationMode
VideoPresentationModeFullscreen)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_VideoPresentationModePictureInPicture JSM Bool
-> (Bool -> JSM (Maybe VideoPresentationMode))
-> JSM (Maybe VideoPresentationMode)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe VideoPresentationMode -> JSM (Maybe VideoPresentationMode)
forall (m :: * -> *) a. Monad m => a -> m a
return (VideoPresentationMode -> Maybe VideoPresentationMode
forall a. a -> Maybe a
Just VideoPresentationMode
VideoPresentationModePictureInPicture)
                                 Bool
False
                                   -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_VideoPresentationModeInline JSM Bool
-> (Bool -> JSM (Maybe VideoPresentationMode))
-> JSM (Maybe VideoPresentationMode)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                        \ Bool
r ->
                                          case Bool
r of
                                              Bool
True -> Maybe VideoPresentationMode -> JSM (Maybe VideoPresentationMode)
forall (m :: * -> *) a. Monad m => a -> m a
return (VideoPresentationMode -> Maybe VideoPresentationMode
forall a. a -> Maybe a
Just VideoPresentationMode
VideoPresentationModeInline)
                                              Bool
False -> Maybe VideoPresentationMode -> JSM (Maybe VideoPresentationMode)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe VideoPresentationMode
forall a. Maybe a
Nothing
js_VideoPresentationModeFullscreen :: String
js_VideoPresentationModeFullscreen = String
"fullscreen"
js_VideoPresentationModePictureInPicture :: String
js_VideoPresentationModePictureInPicture = String
"picture-in-picture"
js_VideoPresentationModeInline :: String
js_VideoPresentationModeInline = String
"inline"
 
data TextTrackMode = TextTrackModeDisabled
                   | TextTrackModeHidden
                   | TextTrackModeShowing
                   deriving (Int -> TextTrackMode -> ShowS
[TextTrackMode] -> ShowS
TextTrackMode -> String
(Int -> TextTrackMode -> ShowS)
-> (TextTrackMode -> String)
-> ([TextTrackMode] -> ShowS)
-> Show TextTrackMode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TextTrackMode] -> ShowS
$cshowList :: [TextTrackMode] -> ShowS
show :: TextTrackMode -> String
$cshow :: TextTrackMode -> String
showsPrec :: Int -> TextTrackMode -> ShowS
$cshowsPrec :: Int -> TextTrackMode -> ShowS
Show, ReadPrec [TextTrackMode]
ReadPrec TextTrackMode
Int -> ReadS TextTrackMode
ReadS [TextTrackMode]
(Int -> ReadS TextTrackMode)
-> ReadS [TextTrackMode]
-> ReadPrec TextTrackMode
-> ReadPrec [TextTrackMode]
-> Read TextTrackMode
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TextTrackMode]
$creadListPrec :: ReadPrec [TextTrackMode]
readPrec :: ReadPrec TextTrackMode
$creadPrec :: ReadPrec TextTrackMode
readList :: ReadS [TextTrackMode]
$creadList :: ReadS [TextTrackMode]
readsPrec :: Int -> ReadS TextTrackMode
$creadsPrec :: Int -> ReadS TextTrackMode
Read, TextTrackMode -> TextTrackMode -> Bool
(TextTrackMode -> TextTrackMode -> Bool)
-> (TextTrackMode -> TextTrackMode -> Bool) -> Eq TextTrackMode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TextTrackMode -> TextTrackMode -> Bool
$c/= :: TextTrackMode -> TextTrackMode -> Bool
== :: TextTrackMode -> TextTrackMode -> Bool
$c== :: TextTrackMode -> TextTrackMode -> Bool
Eq, Eq TextTrackMode
Eq TextTrackMode
-> (TextTrackMode -> TextTrackMode -> Ordering)
-> (TextTrackMode -> TextTrackMode -> Bool)
-> (TextTrackMode -> TextTrackMode -> Bool)
-> (TextTrackMode -> TextTrackMode -> Bool)
-> (TextTrackMode -> TextTrackMode -> Bool)
-> (TextTrackMode -> TextTrackMode -> TextTrackMode)
-> (TextTrackMode -> TextTrackMode -> TextTrackMode)
-> Ord TextTrackMode
TextTrackMode -> TextTrackMode -> Bool
TextTrackMode -> TextTrackMode -> Ordering
TextTrackMode -> TextTrackMode -> TextTrackMode
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: TextTrackMode -> TextTrackMode -> TextTrackMode
$cmin :: TextTrackMode -> TextTrackMode -> TextTrackMode
max :: TextTrackMode -> TextTrackMode -> TextTrackMode
$cmax :: TextTrackMode -> TextTrackMode -> TextTrackMode
>= :: TextTrackMode -> TextTrackMode -> Bool
$c>= :: TextTrackMode -> TextTrackMode -> Bool
> :: TextTrackMode -> TextTrackMode -> Bool
$c> :: TextTrackMode -> TextTrackMode -> Bool
<= :: TextTrackMode -> TextTrackMode -> Bool
$c<= :: TextTrackMode -> TextTrackMode -> Bool
< :: TextTrackMode -> TextTrackMode -> Bool
$c< :: TextTrackMode -> TextTrackMode -> Bool
compare :: TextTrackMode -> TextTrackMode -> Ordering
$ccompare :: TextTrackMode -> TextTrackMode -> Ordering
$cp1Ord :: Eq TextTrackMode
Ord, Typeable)
 
instance ToJSVal TextTrackMode where
        toJSVal :: TextTrackMode -> JSM JSVal
toJSVal TextTrackMode
TextTrackModeDisabled = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_TextTrackModeDisabled
        toJSVal TextTrackMode
TextTrackModeHidden = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_TextTrackModeHidden
        toJSVal TextTrackMode
TextTrackModeShowing = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_TextTrackModeShowing
 
instance FromJSVal TextTrackMode where
        fromJSVal :: JSVal -> JSM (Maybe TextTrackMode)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_TextTrackModeDisabled JSM Bool
-> (Bool -> JSM (Maybe TextTrackMode)) -> JSM (Maybe TextTrackMode)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe TextTrackMode -> JSM (Maybe TextTrackMode)
forall (m :: * -> *) a. Monad m => a -> m a
return (TextTrackMode -> Maybe TextTrackMode
forall a. a -> Maybe a
Just TextTrackMode
TextTrackModeDisabled)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_TextTrackModeHidden JSM Bool
-> (Bool -> JSM (Maybe TextTrackMode)) -> JSM (Maybe TextTrackMode)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe TextTrackMode -> JSM (Maybe TextTrackMode)
forall (m :: * -> *) a. Monad m => a -> m a
return (TextTrackMode -> Maybe TextTrackMode
forall a. a -> Maybe a
Just TextTrackMode
TextTrackModeHidden)
                                 Bool
False
                                   -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_TextTrackModeShowing JSM Bool
-> (Bool -> JSM (Maybe TextTrackMode)) -> JSM (Maybe TextTrackMode)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                        \ Bool
r ->
                                          case Bool
r of
                                              Bool
True -> Maybe TextTrackMode -> JSM (Maybe TextTrackMode)
forall (m :: * -> *) a. Monad m => a -> m a
return (TextTrackMode -> Maybe TextTrackMode
forall a. a -> Maybe a
Just TextTrackMode
TextTrackModeShowing)
                                              Bool
False -> Maybe TextTrackMode -> JSM (Maybe TextTrackMode)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe TextTrackMode
forall a. Maybe a
Nothing
js_TextTrackModeDisabled :: String
js_TextTrackModeDisabled = String
"disabled"
js_TextTrackModeHidden :: String
js_TextTrackModeHidden = String
"hidden"
js_TextTrackModeShowing :: String
js_TextTrackModeShowing = String
"showing"
 
data TextTrackKind = TextTrackKindSubtitles
                   | TextTrackKindCaptions
                   | TextTrackKindDescriptions
                   | TextTrackKindChapters
                   | TextTrackKindMetadata
                   | TextTrackKindForced
                   deriving (Int -> TextTrackKind -> ShowS
[TextTrackKind] -> ShowS
TextTrackKind -> String
(Int -> TextTrackKind -> ShowS)
-> (TextTrackKind -> String)
-> ([TextTrackKind] -> ShowS)
-> Show TextTrackKind
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TextTrackKind] -> ShowS
$cshowList :: [TextTrackKind] -> ShowS
show :: TextTrackKind -> String
$cshow :: TextTrackKind -> String
showsPrec :: Int -> TextTrackKind -> ShowS
$cshowsPrec :: Int -> TextTrackKind -> ShowS
Show, ReadPrec [TextTrackKind]
ReadPrec TextTrackKind
Int -> ReadS TextTrackKind
ReadS [TextTrackKind]
(Int -> ReadS TextTrackKind)
-> ReadS [TextTrackKind]
-> ReadPrec TextTrackKind
-> ReadPrec [TextTrackKind]
-> Read TextTrackKind
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TextTrackKind]
$creadListPrec :: ReadPrec [TextTrackKind]
readPrec :: ReadPrec TextTrackKind
$creadPrec :: ReadPrec TextTrackKind
readList :: ReadS [TextTrackKind]
$creadList :: ReadS [TextTrackKind]
readsPrec :: Int -> ReadS TextTrackKind
$creadsPrec :: Int -> ReadS TextTrackKind
Read, TextTrackKind -> TextTrackKind -> Bool
(TextTrackKind -> TextTrackKind -> Bool)
-> (TextTrackKind -> TextTrackKind -> Bool) -> Eq TextTrackKind
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TextTrackKind -> TextTrackKind -> Bool
$c/= :: TextTrackKind -> TextTrackKind -> Bool
== :: TextTrackKind -> TextTrackKind -> Bool
$c== :: TextTrackKind -> TextTrackKind -> Bool
Eq, Eq TextTrackKind
Eq TextTrackKind
-> (TextTrackKind -> TextTrackKind -> Ordering)
-> (TextTrackKind -> TextTrackKind -> Bool)
-> (TextTrackKind -> TextTrackKind -> Bool)
-> (TextTrackKind -> TextTrackKind -> Bool)
-> (TextTrackKind -> TextTrackKind -> Bool)
-> (TextTrackKind -> TextTrackKind -> TextTrackKind)
-> (TextTrackKind -> TextTrackKind -> TextTrackKind)
-> Ord TextTrackKind
TextTrackKind -> TextTrackKind -> Bool
TextTrackKind -> TextTrackKind -> Ordering
TextTrackKind -> TextTrackKind -> TextTrackKind
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: TextTrackKind -> TextTrackKind -> TextTrackKind
$cmin :: TextTrackKind -> TextTrackKind -> TextTrackKind
max :: TextTrackKind -> TextTrackKind -> TextTrackKind
$cmax :: TextTrackKind -> TextTrackKind -> TextTrackKind
>= :: TextTrackKind -> TextTrackKind -> Bool
$c>= :: TextTrackKind -> TextTrackKind -> Bool
> :: TextTrackKind -> TextTrackKind -> Bool
$c> :: TextTrackKind -> TextTrackKind -> Bool
<= :: TextTrackKind -> TextTrackKind -> Bool
$c<= :: TextTrackKind -> TextTrackKind -> Bool
< :: TextTrackKind -> TextTrackKind -> Bool
$c< :: TextTrackKind -> TextTrackKind -> Bool
compare :: TextTrackKind -> TextTrackKind -> Ordering
$ccompare :: TextTrackKind -> TextTrackKind -> Ordering
$cp1Ord :: Eq TextTrackKind
Ord, Typeable)
 
instance ToJSVal TextTrackKind where
        toJSVal :: TextTrackKind -> JSM JSVal
toJSVal TextTrackKind
TextTrackKindSubtitles = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_TextTrackKindSubtitles
        toJSVal TextTrackKind
TextTrackKindCaptions = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_TextTrackKindCaptions
        toJSVal TextTrackKind
TextTrackKindDescriptions
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_TextTrackKindDescriptions
        toJSVal TextTrackKind
TextTrackKindChapters = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_TextTrackKindChapters
        toJSVal TextTrackKind
TextTrackKindMetadata = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_TextTrackKindMetadata
        toJSVal TextTrackKind
TextTrackKindForced = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_TextTrackKindForced
 
instance FromJSVal TextTrackKind where
        fromJSVal :: JSVal -> JSM (Maybe TextTrackKind)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_TextTrackKindSubtitles JSM Bool
-> (Bool -> JSM (Maybe TextTrackKind)) -> JSM (Maybe TextTrackKind)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe TextTrackKind -> JSM (Maybe TextTrackKind)
forall (m :: * -> *) a. Monad m => a -> m a
return (TextTrackKind -> Maybe TextTrackKind
forall a. a -> Maybe a
Just TextTrackKind
TextTrackKindSubtitles)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_TextTrackKindCaptions JSM Bool
-> (Bool -> JSM (Maybe TextTrackKind)) -> JSM (Maybe TextTrackKind)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe TextTrackKind -> JSM (Maybe TextTrackKind)
forall (m :: * -> *) a. Monad m => a -> m a
return (TextTrackKind -> Maybe TextTrackKind
forall a. a -> Maybe a
Just TextTrackKind
TextTrackKindCaptions)
                                 Bool
False
                                   -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_TextTrackKindDescriptions JSM Bool
-> (Bool -> JSM (Maybe TextTrackKind)) -> JSM (Maybe TextTrackKind)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                        \ Bool
r ->
                                          case Bool
r of
                                              Bool
True -> Maybe TextTrackKind -> JSM (Maybe TextTrackKind)
forall (m :: * -> *) a. Monad m => a -> m a
return (TextTrackKind -> Maybe TextTrackKind
forall a. a -> Maybe a
Just TextTrackKind
TextTrackKindDescriptions)
                                              Bool
False
                                                -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_TextTrackKindChapters JSM Bool
-> (Bool -> JSM (Maybe TextTrackKind)) -> JSM (Maybe TextTrackKind)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                     \ Bool
r ->
                                                       case Bool
r of
                                                           Bool
True
                                                             -> Maybe TextTrackKind -> JSM (Maybe TextTrackKind)
forall (m :: * -> *) a. Monad m => a -> m a
return (TextTrackKind -> Maybe TextTrackKind
forall a. a -> Maybe a
Just TextTrackKind
TextTrackKindChapters)
                                                           Bool
False
                                                             -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                                  String
js_TextTrackKindMetadata
                                                                  JSM Bool
-> (Bool -> JSM (Maybe TextTrackKind)) -> JSM (Maybe TextTrackKind)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                  \ Bool
r ->
                                                                    case Bool
r of
                                                                        Bool
True
                                                                          -> Maybe TextTrackKind -> JSM (Maybe TextTrackKind)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                               (TextTrackKind -> Maybe TextTrackKind
forall a. a -> Maybe a
Just
                                                                                  TextTrackKind
TextTrackKindMetadata)
                                                                        Bool
False
                                                                          -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                                               String
js_TextTrackKindForced
                                                                               JSM Bool
-> (Bool -> JSM (Maybe TextTrackKind)) -> JSM (Maybe TextTrackKind)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                               \ Bool
r ->
                                                                                 case Bool
r of
                                                                                     Bool
True
                                                                                       -> Maybe TextTrackKind -> JSM (Maybe TextTrackKind)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                                            (TextTrackKind -> Maybe TextTrackKind
forall a. a -> Maybe a
Just
                                                                                               TextTrackKind
TextTrackKindForced)
                                                                                     Bool
False
                                                                                       -> Maybe TextTrackKind -> JSM (Maybe TextTrackKind)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                                            Maybe TextTrackKind
forall a. Maybe a
Nothing
js_TextTrackKindSubtitles :: String
js_TextTrackKindSubtitles = String
"subtitles"
js_TextTrackKindCaptions :: String
js_TextTrackKindCaptions = String
"captions"
js_TextTrackKindDescriptions :: String
js_TextTrackKindDescriptions = String
"descriptions"
js_TextTrackKindChapters :: String
js_TextTrackKindChapters = String
"chapters"
js_TextTrackKindMetadata :: String
js_TextTrackKindMetadata = String
"metadata"
js_TextTrackKindForced :: String
js_TextTrackKindForced = String
"forced"
 
data ApplePayErrorCode = ApplePayErrorCodeUnknown
                       | ApplePayErrorCodeShippingContactInvalid
                       | ApplePayErrorCodeBillingContactInvalid
                       | ApplePayErrorCodeAddressUnservicable
                       deriving (Int -> ApplePayErrorCode -> ShowS
[ApplePayErrorCode] -> ShowS
ApplePayErrorCode -> String
(Int -> ApplePayErrorCode -> ShowS)
-> (ApplePayErrorCode -> String)
-> ([ApplePayErrorCode] -> ShowS)
-> Show ApplePayErrorCode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ApplePayErrorCode] -> ShowS
$cshowList :: [ApplePayErrorCode] -> ShowS
show :: ApplePayErrorCode -> String
$cshow :: ApplePayErrorCode -> String
showsPrec :: Int -> ApplePayErrorCode -> ShowS
$cshowsPrec :: Int -> ApplePayErrorCode -> ShowS
Show, ReadPrec [ApplePayErrorCode]
ReadPrec ApplePayErrorCode
Int -> ReadS ApplePayErrorCode
ReadS [ApplePayErrorCode]
(Int -> ReadS ApplePayErrorCode)
-> ReadS [ApplePayErrorCode]
-> ReadPrec ApplePayErrorCode
-> ReadPrec [ApplePayErrorCode]
-> Read ApplePayErrorCode
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ApplePayErrorCode]
$creadListPrec :: ReadPrec [ApplePayErrorCode]
readPrec :: ReadPrec ApplePayErrorCode
$creadPrec :: ReadPrec ApplePayErrorCode
readList :: ReadS [ApplePayErrorCode]
$creadList :: ReadS [ApplePayErrorCode]
readsPrec :: Int -> ReadS ApplePayErrorCode
$creadsPrec :: Int -> ReadS ApplePayErrorCode
Read, ApplePayErrorCode -> ApplePayErrorCode -> Bool
(ApplePayErrorCode -> ApplePayErrorCode -> Bool)
-> (ApplePayErrorCode -> ApplePayErrorCode -> Bool)
-> Eq ApplePayErrorCode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ApplePayErrorCode -> ApplePayErrorCode -> Bool
$c/= :: ApplePayErrorCode -> ApplePayErrorCode -> Bool
== :: ApplePayErrorCode -> ApplePayErrorCode -> Bool
$c== :: ApplePayErrorCode -> ApplePayErrorCode -> Bool
Eq, Eq ApplePayErrorCode
Eq ApplePayErrorCode
-> (ApplePayErrorCode -> ApplePayErrorCode -> Ordering)
-> (ApplePayErrorCode -> ApplePayErrorCode -> Bool)
-> (ApplePayErrorCode -> ApplePayErrorCode -> Bool)
-> (ApplePayErrorCode -> ApplePayErrorCode -> Bool)
-> (ApplePayErrorCode -> ApplePayErrorCode -> Bool)
-> (ApplePayErrorCode -> ApplePayErrorCode -> ApplePayErrorCode)
-> (ApplePayErrorCode -> ApplePayErrorCode -> ApplePayErrorCode)
-> Ord ApplePayErrorCode
ApplePayErrorCode -> ApplePayErrorCode -> Bool
ApplePayErrorCode -> ApplePayErrorCode -> Ordering
ApplePayErrorCode -> ApplePayErrorCode -> ApplePayErrorCode
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ApplePayErrorCode -> ApplePayErrorCode -> ApplePayErrorCode
$cmin :: ApplePayErrorCode -> ApplePayErrorCode -> ApplePayErrorCode
max :: ApplePayErrorCode -> ApplePayErrorCode -> ApplePayErrorCode
$cmax :: ApplePayErrorCode -> ApplePayErrorCode -> ApplePayErrorCode
>= :: ApplePayErrorCode -> ApplePayErrorCode -> Bool
$c>= :: ApplePayErrorCode -> ApplePayErrorCode -> Bool
> :: ApplePayErrorCode -> ApplePayErrorCode -> Bool
$c> :: ApplePayErrorCode -> ApplePayErrorCode -> Bool
<= :: ApplePayErrorCode -> ApplePayErrorCode -> Bool
$c<= :: ApplePayErrorCode -> ApplePayErrorCode -> Bool
< :: ApplePayErrorCode -> ApplePayErrorCode -> Bool
$c< :: ApplePayErrorCode -> ApplePayErrorCode -> Bool
compare :: ApplePayErrorCode -> ApplePayErrorCode -> Ordering
$ccompare :: ApplePayErrorCode -> ApplePayErrorCode -> Ordering
$cp1Ord :: Eq ApplePayErrorCode
Ord, Typeable)
 
instance ToJSVal ApplePayErrorCode where
        toJSVal :: ApplePayErrorCode -> JSM JSVal
toJSVal ApplePayErrorCode
ApplePayErrorCodeUnknown
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_ApplePayErrorCodeUnknown
        toJSVal ApplePayErrorCode
ApplePayErrorCodeShippingContactInvalid
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_ApplePayErrorCodeShippingContactInvalid
        toJSVal ApplePayErrorCode
ApplePayErrorCodeBillingContactInvalid
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_ApplePayErrorCodeBillingContactInvalid
        toJSVal ApplePayErrorCode
ApplePayErrorCodeAddressUnservicable
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_ApplePayErrorCodeAddressUnservicable
 
instance FromJSVal ApplePayErrorCode where
        fromJSVal :: JSVal -> JSM (Maybe ApplePayErrorCode)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_ApplePayErrorCodeUnknown JSM Bool
-> (Bool -> JSM (Maybe ApplePayErrorCode))
-> JSM (Maybe ApplePayErrorCode)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe ApplePayErrorCode -> JSM (Maybe ApplePayErrorCode)
forall (m :: * -> *) a. Monad m => a -> m a
return (ApplePayErrorCode -> Maybe ApplePayErrorCode
forall a. a -> Maybe a
Just ApplePayErrorCode
ApplePayErrorCodeUnknown)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_ApplePayErrorCodeShippingContactInvalid JSM Bool
-> (Bool -> JSM (Maybe ApplePayErrorCode))
-> JSM (Maybe ApplePayErrorCode)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe ApplePayErrorCode -> JSM (Maybe ApplePayErrorCode)
forall (m :: * -> *) a. Monad m => a -> m a
return (ApplePayErrorCode -> Maybe ApplePayErrorCode
forall a. a -> Maybe a
Just ApplePayErrorCode
ApplePayErrorCodeShippingContactInvalid)
                                 Bool
False
                                   -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_ApplePayErrorCodeBillingContactInvalid JSM Bool
-> (Bool -> JSM (Maybe ApplePayErrorCode))
-> JSM (Maybe ApplePayErrorCode)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                        \ Bool
r ->
                                          case Bool
r of
                                              Bool
True
                                                -> Maybe ApplePayErrorCode -> JSM (Maybe ApplePayErrorCode)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                     (ApplePayErrorCode -> Maybe ApplePayErrorCode
forall a. a -> Maybe a
Just ApplePayErrorCode
ApplePayErrorCodeBillingContactInvalid)
                                              Bool
False
                                                -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                     String
js_ApplePayErrorCodeAddressUnservicable
                                                     JSM Bool
-> (Bool -> JSM (Maybe ApplePayErrorCode))
-> JSM (Maybe ApplePayErrorCode)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                     \ Bool
r ->
                                                       case Bool
r of
                                                           Bool
True
                                                             -> Maybe ApplePayErrorCode -> JSM (Maybe ApplePayErrorCode)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                  (ApplePayErrorCode -> Maybe ApplePayErrorCode
forall a. a -> Maybe a
Just
                                                                     ApplePayErrorCode
ApplePayErrorCodeAddressUnservicable)
                                                           Bool
False -> Maybe ApplePayErrorCode -> JSM (Maybe ApplePayErrorCode)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ApplePayErrorCode
forall a. Maybe a
Nothing
js_ApplePayErrorCodeUnknown :: String
js_ApplePayErrorCodeUnknown = String
"unknown"
js_ApplePayErrorCodeShippingContactInvalid :: String
js_ApplePayErrorCodeShippingContactInvalid
  = String
"shippingContactInvalid"
js_ApplePayErrorCodeBillingContactInvalid :: String
js_ApplePayErrorCodeBillingContactInvalid = String
"billingContactInvalid"
js_ApplePayErrorCodeAddressUnservicable :: String
js_ApplePayErrorCodeAddressUnservicable = String
"addressUnservicable"
 
data ApplePayErrorContactField = ApplePayErrorContactFieldPhoneNumber
                               | ApplePayErrorContactFieldEmailAddress
                               | ApplePayErrorContactFieldName
                               | ApplePayErrorContactFieldPostalAddress
                               | ApplePayErrorContactFieldAddressLines
                               | ApplePayErrorContactFieldLocality
                               | ApplePayErrorContactFieldPostalCode
                               | ApplePayErrorContactFieldAdministrativeArea
                               | ApplePayErrorContactFieldCountry
                               deriving (Int -> ApplePayErrorContactField -> ShowS
[ApplePayErrorContactField] -> ShowS
ApplePayErrorContactField -> String
(Int -> ApplePayErrorContactField -> ShowS)
-> (ApplePayErrorContactField -> String)
-> ([ApplePayErrorContactField] -> ShowS)
-> Show ApplePayErrorContactField
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ApplePayErrorContactField] -> ShowS
$cshowList :: [ApplePayErrorContactField] -> ShowS
show :: ApplePayErrorContactField -> String
$cshow :: ApplePayErrorContactField -> String
showsPrec :: Int -> ApplePayErrorContactField -> ShowS
$cshowsPrec :: Int -> ApplePayErrorContactField -> ShowS
Show, ReadPrec [ApplePayErrorContactField]
ReadPrec ApplePayErrorContactField
Int -> ReadS ApplePayErrorContactField
ReadS [ApplePayErrorContactField]
(Int -> ReadS ApplePayErrorContactField)
-> ReadS [ApplePayErrorContactField]
-> ReadPrec ApplePayErrorContactField
-> ReadPrec [ApplePayErrorContactField]
-> Read ApplePayErrorContactField
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ApplePayErrorContactField]
$creadListPrec :: ReadPrec [ApplePayErrorContactField]
readPrec :: ReadPrec ApplePayErrorContactField
$creadPrec :: ReadPrec ApplePayErrorContactField
readList :: ReadS [ApplePayErrorContactField]
$creadList :: ReadS [ApplePayErrorContactField]
readsPrec :: Int -> ReadS ApplePayErrorContactField
$creadsPrec :: Int -> ReadS ApplePayErrorContactField
Read, ApplePayErrorContactField -> ApplePayErrorContactField -> Bool
(ApplePayErrorContactField -> ApplePayErrorContactField -> Bool)
-> (ApplePayErrorContactField -> ApplePayErrorContactField -> Bool)
-> Eq ApplePayErrorContactField
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ApplePayErrorContactField -> ApplePayErrorContactField -> Bool
$c/= :: ApplePayErrorContactField -> ApplePayErrorContactField -> Bool
== :: ApplePayErrorContactField -> ApplePayErrorContactField -> Bool
$c== :: ApplePayErrorContactField -> ApplePayErrorContactField -> Bool
Eq, Eq ApplePayErrorContactField
Eq ApplePayErrorContactField
-> (ApplePayErrorContactField
    -> ApplePayErrorContactField -> Ordering)
-> (ApplePayErrorContactField -> ApplePayErrorContactField -> Bool)
-> (ApplePayErrorContactField -> ApplePayErrorContactField -> Bool)
-> (ApplePayErrorContactField -> ApplePayErrorContactField -> Bool)
-> (ApplePayErrorContactField -> ApplePayErrorContactField -> Bool)
-> (ApplePayErrorContactField
    -> ApplePayErrorContactField -> ApplePayErrorContactField)
-> (ApplePayErrorContactField
    -> ApplePayErrorContactField -> ApplePayErrorContactField)
-> Ord ApplePayErrorContactField
ApplePayErrorContactField -> ApplePayErrorContactField -> Bool
ApplePayErrorContactField -> ApplePayErrorContactField -> Ordering
ApplePayErrorContactField
-> ApplePayErrorContactField -> ApplePayErrorContactField
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ApplePayErrorContactField
-> ApplePayErrorContactField -> ApplePayErrorContactField
$cmin :: ApplePayErrorContactField
-> ApplePayErrorContactField -> ApplePayErrorContactField
max :: ApplePayErrorContactField
-> ApplePayErrorContactField -> ApplePayErrorContactField
$cmax :: ApplePayErrorContactField
-> ApplePayErrorContactField -> ApplePayErrorContactField
>= :: ApplePayErrorContactField -> ApplePayErrorContactField -> Bool
$c>= :: ApplePayErrorContactField -> ApplePayErrorContactField -> Bool
> :: ApplePayErrorContactField -> ApplePayErrorContactField -> Bool
$c> :: ApplePayErrorContactField -> ApplePayErrorContactField -> Bool
<= :: ApplePayErrorContactField -> ApplePayErrorContactField -> Bool
$c<= :: ApplePayErrorContactField -> ApplePayErrorContactField -> Bool
< :: ApplePayErrorContactField -> ApplePayErrorContactField -> Bool
$c< :: ApplePayErrorContactField -> ApplePayErrorContactField -> Bool
compare :: ApplePayErrorContactField -> ApplePayErrorContactField -> Ordering
$ccompare :: ApplePayErrorContactField -> ApplePayErrorContactField -> Ordering
$cp1Ord :: Eq ApplePayErrorContactField
Ord, Typeable)
 
instance ToJSVal ApplePayErrorContactField where
        toJSVal :: ApplePayErrorContactField -> JSM JSVal
toJSVal ApplePayErrorContactField
ApplePayErrorContactFieldPhoneNumber
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_ApplePayErrorContactFieldPhoneNumber
        toJSVal ApplePayErrorContactField
ApplePayErrorContactFieldEmailAddress
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_ApplePayErrorContactFieldEmailAddress
        toJSVal ApplePayErrorContactField
ApplePayErrorContactFieldName
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_ApplePayErrorContactFieldName
        toJSVal ApplePayErrorContactField
ApplePayErrorContactFieldPostalAddress
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_ApplePayErrorContactFieldPostalAddress
        toJSVal ApplePayErrorContactField
ApplePayErrorContactFieldAddressLines
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_ApplePayErrorContactFieldAddressLines
        toJSVal ApplePayErrorContactField
ApplePayErrorContactFieldLocality
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_ApplePayErrorContactFieldLocality
        toJSVal ApplePayErrorContactField
ApplePayErrorContactFieldPostalCode
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_ApplePayErrorContactFieldPostalCode
        toJSVal ApplePayErrorContactField
ApplePayErrorContactFieldAdministrativeArea
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_ApplePayErrorContactFieldAdministrativeArea
        toJSVal ApplePayErrorContactField
ApplePayErrorContactFieldCountry
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_ApplePayErrorContactFieldCountry
 
instance FromJSVal ApplePayErrorContactField where
        fromJSVal :: JSVal -> JSM (Maybe ApplePayErrorContactField)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_ApplePayErrorContactFieldPhoneNumber JSM Bool
-> (Bool -> JSM (Maybe ApplePayErrorContactField))
-> JSM (Maybe ApplePayErrorContactField)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe ApplePayErrorContactField
-> JSM (Maybe ApplePayErrorContactField)
forall (m :: * -> *) a. Monad m => a -> m a
return (ApplePayErrorContactField -> Maybe ApplePayErrorContactField
forall a. a -> Maybe a
Just ApplePayErrorContactField
ApplePayErrorContactFieldPhoneNumber)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_ApplePayErrorContactFieldEmailAddress JSM Bool
-> (Bool -> JSM (Maybe ApplePayErrorContactField))
-> JSM (Maybe ApplePayErrorContactField)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe ApplePayErrorContactField
-> JSM (Maybe ApplePayErrorContactField)
forall (m :: * -> *) a. Monad m => a -> m a
return (ApplePayErrorContactField -> Maybe ApplePayErrorContactField
forall a. a -> Maybe a
Just ApplePayErrorContactField
ApplePayErrorContactFieldEmailAddress)
                                 Bool
False
                                   -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_ApplePayErrorContactFieldName JSM Bool
-> (Bool -> JSM (Maybe ApplePayErrorContactField))
-> JSM (Maybe ApplePayErrorContactField)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                        \ Bool
r ->
                                          case Bool
r of
                                              Bool
True -> Maybe ApplePayErrorContactField
-> JSM (Maybe ApplePayErrorContactField)
forall (m :: * -> *) a. Monad m => a -> m a
return (ApplePayErrorContactField -> Maybe ApplePayErrorContactField
forall a. a -> Maybe a
Just ApplePayErrorContactField
ApplePayErrorContactFieldName)
                                              Bool
False
                                                -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                     String
js_ApplePayErrorContactFieldPostalAddress
                                                     JSM Bool
-> (Bool -> JSM (Maybe ApplePayErrorContactField))
-> JSM (Maybe ApplePayErrorContactField)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                     \ Bool
r ->
                                                       case Bool
r of
                                                           Bool
True
                                                             -> Maybe ApplePayErrorContactField
-> JSM (Maybe ApplePayErrorContactField)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                  (ApplePayErrorContactField -> Maybe ApplePayErrorContactField
forall a. a -> Maybe a
Just
                                                                     ApplePayErrorContactField
ApplePayErrorContactFieldPostalAddress)
                                                           Bool
False
                                                             -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                                  String
js_ApplePayErrorContactFieldAddressLines
                                                                  JSM Bool
-> (Bool -> JSM (Maybe ApplePayErrorContactField))
-> JSM (Maybe ApplePayErrorContactField)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                  \ Bool
r ->
                                                                    case Bool
r of
                                                                        Bool
True
                                                                          -> Maybe ApplePayErrorContactField
-> JSM (Maybe ApplePayErrorContactField)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                               (ApplePayErrorContactField -> Maybe ApplePayErrorContactField
forall a. a -> Maybe a
Just
                                                                                  ApplePayErrorContactField
ApplePayErrorContactFieldAddressLines)
                                                                        Bool
False
                                                                          -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                                               String
js_ApplePayErrorContactFieldLocality
                                                                               JSM Bool
-> (Bool -> JSM (Maybe ApplePayErrorContactField))
-> JSM (Maybe ApplePayErrorContactField)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                               \ Bool
r ->
                                                                                 case Bool
r of
                                                                                     Bool
True
                                                                                       -> Maybe ApplePayErrorContactField
-> JSM (Maybe ApplePayErrorContactField)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                                            (ApplePayErrorContactField -> Maybe ApplePayErrorContactField
forall a. a -> Maybe a
Just
                                                                                               ApplePayErrorContactField
ApplePayErrorContactFieldLocality)
                                                                                     Bool
False
                                                                                       -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                                                            String
js_ApplePayErrorContactFieldPostalCode
                                                                                            JSM Bool
-> (Bool -> JSM (Maybe ApplePayErrorContactField))
-> JSM (Maybe ApplePayErrorContactField)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                                            \ Bool
r ->
                                                                                              case Bool
r
                                                                                                of
                                                                                                  Bool
True
                                                                                                    -> Maybe ApplePayErrorContactField
-> JSM (Maybe ApplePayErrorContactField)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                                                         (ApplePayErrorContactField -> Maybe ApplePayErrorContactField
forall a. a -> Maybe a
Just
                                                                                                            ApplePayErrorContactField
ApplePayErrorContactFieldPostalCode)
                                                                                                  Bool
False
                                                                                                    -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                                                                         String
js_ApplePayErrorContactFieldAdministrativeArea
                                                                                                         JSM Bool
-> (Bool -> JSM (Maybe ApplePayErrorContactField))
-> JSM (Maybe ApplePayErrorContactField)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                                                         \ Bool
r
                                                                                                           ->
                                                                                                           case
                                                                                                             Bool
r
                                                                                                             of
                                                                                                               Bool
True
                                                                                                                 -> Maybe ApplePayErrorContactField
-> JSM (Maybe ApplePayErrorContactField)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                                                                      (ApplePayErrorContactField -> Maybe ApplePayErrorContactField
forall a. a -> Maybe a
Just
                                                                                                                         ApplePayErrorContactField
ApplePayErrorContactFieldAdministrativeArea)
                                                                                                               Bool
False
                                                                                                                 -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                                                                                      String
js_ApplePayErrorContactFieldCountry
                                                                                                                      JSM Bool
-> (Bool -> JSM (Maybe ApplePayErrorContactField))
-> JSM (Maybe ApplePayErrorContactField)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                                                                      \ Bool
r
                                                                                                                        ->
                                                                                                                        case
                                                                                                                          Bool
r
                                                                                                                          of
                                                                                                                            Bool
True
                                                                                                                              -> Maybe ApplePayErrorContactField
-> JSM (Maybe ApplePayErrorContactField)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                                                                                   (ApplePayErrorContactField -> Maybe ApplePayErrorContactField
forall a. a -> Maybe a
Just
                                                                                                                                      ApplePayErrorContactField
ApplePayErrorContactFieldCountry)
                                                                                                                            Bool
False
                                                                                                                              -> Maybe ApplePayErrorContactField
-> JSM (Maybe ApplePayErrorContactField)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                                                                                   Maybe ApplePayErrorContactField
forall a. Maybe a
Nothing
js_ApplePayErrorContactFieldPhoneNumber :: String
js_ApplePayErrorContactFieldPhoneNumber = String
"phoneNumber"
js_ApplePayErrorContactFieldEmailAddress :: String
js_ApplePayErrorContactFieldEmailAddress = String
"emailAddress"
js_ApplePayErrorContactFieldName :: String
js_ApplePayErrorContactFieldName = String
"name"
js_ApplePayErrorContactFieldPostalAddress :: String
js_ApplePayErrorContactFieldPostalAddress = String
"postalAddress"
js_ApplePayErrorContactFieldAddressLines :: String
js_ApplePayErrorContactFieldAddressLines = String
"addressLines"
js_ApplePayErrorContactFieldLocality :: String
js_ApplePayErrorContactFieldLocality = String
"locality"
js_ApplePayErrorContactFieldPostalCode :: String
js_ApplePayErrorContactFieldPostalCode = String
"postalCode"
js_ApplePayErrorContactFieldAdministrativeArea :: String
js_ApplePayErrorContactFieldAdministrativeArea
  = String
"administrativeArea"
js_ApplePayErrorContactFieldCountry :: String
js_ApplePayErrorContactFieldCountry = String
"country"
 
data ApplePayLineItemType = ApplePayLineItemTypePending
                          | ApplePayLineItemTypeFinal
                          deriving (Int -> ApplePayLineItemType -> ShowS
[ApplePayLineItemType] -> ShowS
ApplePayLineItemType -> String
(Int -> ApplePayLineItemType -> ShowS)
-> (ApplePayLineItemType -> String)
-> ([ApplePayLineItemType] -> ShowS)
-> Show ApplePayLineItemType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ApplePayLineItemType] -> ShowS
$cshowList :: [ApplePayLineItemType] -> ShowS
show :: ApplePayLineItemType -> String
$cshow :: ApplePayLineItemType -> String
showsPrec :: Int -> ApplePayLineItemType -> ShowS
$cshowsPrec :: Int -> ApplePayLineItemType -> ShowS
Show, ReadPrec [ApplePayLineItemType]
ReadPrec ApplePayLineItemType
Int -> ReadS ApplePayLineItemType
ReadS [ApplePayLineItemType]
(Int -> ReadS ApplePayLineItemType)
-> ReadS [ApplePayLineItemType]
-> ReadPrec ApplePayLineItemType
-> ReadPrec [ApplePayLineItemType]
-> Read ApplePayLineItemType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ApplePayLineItemType]
$creadListPrec :: ReadPrec [ApplePayLineItemType]
readPrec :: ReadPrec ApplePayLineItemType
$creadPrec :: ReadPrec ApplePayLineItemType
readList :: ReadS [ApplePayLineItemType]
$creadList :: ReadS [ApplePayLineItemType]
readsPrec :: Int -> ReadS ApplePayLineItemType
$creadsPrec :: Int -> ReadS ApplePayLineItemType
Read, ApplePayLineItemType -> ApplePayLineItemType -> Bool
(ApplePayLineItemType -> ApplePayLineItemType -> Bool)
-> (ApplePayLineItemType -> ApplePayLineItemType -> Bool)
-> Eq ApplePayLineItemType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ApplePayLineItemType -> ApplePayLineItemType -> Bool
$c/= :: ApplePayLineItemType -> ApplePayLineItemType -> Bool
== :: ApplePayLineItemType -> ApplePayLineItemType -> Bool
$c== :: ApplePayLineItemType -> ApplePayLineItemType -> Bool
Eq, Eq ApplePayLineItemType
Eq ApplePayLineItemType
-> (ApplePayLineItemType -> ApplePayLineItemType -> Ordering)
-> (ApplePayLineItemType -> ApplePayLineItemType -> Bool)
-> (ApplePayLineItemType -> ApplePayLineItemType -> Bool)
-> (ApplePayLineItemType -> ApplePayLineItemType -> Bool)
-> (ApplePayLineItemType -> ApplePayLineItemType -> Bool)
-> (ApplePayLineItemType
    -> ApplePayLineItemType -> ApplePayLineItemType)
-> (ApplePayLineItemType
    -> ApplePayLineItemType -> ApplePayLineItemType)
-> Ord ApplePayLineItemType
ApplePayLineItemType -> ApplePayLineItemType -> Bool
ApplePayLineItemType -> ApplePayLineItemType -> Ordering
ApplePayLineItemType
-> ApplePayLineItemType -> ApplePayLineItemType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ApplePayLineItemType
-> ApplePayLineItemType -> ApplePayLineItemType
$cmin :: ApplePayLineItemType
-> ApplePayLineItemType -> ApplePayLineItemType
max :: ApplePayLineItemType
-> ApplePayLineItemType -> ApplePayLineItemType
$cmax :: ApplePayLineItemType
-> ApplePayLineItemType -> ApplePayLineItemType
>= :: ApplePayLineItemType -> ApplePayLineItemType -> Bool
$c>= :: ApplePayLineItemType -> ApplePayLineItemType -> Bool
> :: ApplePayLineItemType -> ApplePayLineItemType -> Bool
$c> :: ApplePayLineItemType -> ApplePayLineItemType -> Bool
<= :: ApplePayLineItemType -> ApplePayLineItemType -> Bool
$c<= :: ApplePayLineItemType -> ApplePayLineItemType -> Bool
< :: ApplePayLineItemType -> ApplePayLineItemType -> Bool
$c< :: ApplePayLineItemType -> ApplePayLineItemType -> Bool
compare :: ApplePayLineItemType -> ApplePayLineItemType -> Ordering
$ccompare :: ApplePayLineItemType -> ApplePayLineItemType -> Ordering
$cp1Ord :: Eq ApplePayLineItemType
Ord, Typeable)
 
instance ToJSVal ApplePayLineItemType where
        toJSVal :: ApplePayLineItemType -> JSM JSVal
toJSVal ApplePayLineItemType
ApplePayLineItemTypePending
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_ApplePayLineItemTypePending
        toJSVal ApplePayLineItemType
ApplePayLineItemTypeFinal
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_ApplePayLineItemTypeFinal
 
instance FromJSVal ApplePayLineItemType where
        fromJSVal :: JSVal -> JSM (Maybe ApplePayLineItemType)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_ApplePayLineItemTypePending JSM Bool
-> (Bool -> JSM (Maybe ApplePayLineItemType))
-> JSM (Maybe ApplePayLineItemType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe ApplePayLineItemType -> JSM (Maybe ApplePayLineItemType)
forall (m :: * -> *) a. Monad m => a -> m a
return (ApplePayLineItemType -> Maybe ApplePayLineItemType
forall a. a -> Maybe a
Just ApplePayLineItemType
ApplePayLineItemTypePending)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_ApplePayLineItemTypeFinal JSM Bool
-> (Bool -> JSM (Maybe ApplePayLineItemType))
-> JSM (Maybe ApplePayLineItemType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe ApplePayLineItemType -> JSM (Maybe ApplePayLineItemType)
forall (m :: * -> *) a. Monad m => a -> m a
return (ApplePayLineItemType -> Maybe ApplePayLineItemType
forall a. a -> Maybe a
Just ApplePayLineItemType
ApplePayLineItemTypeFinal)
                                 Bool
False -> Maybe ApplePayLineItemType -> JSM (Maybe ApplePayLineItemType)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ApplePayLineItemType
forall a. Maybe a
Nothing
js_ApplePayLineItemTypePending :: String
js_ApplePayLineItemTypePending = String
"pending"
js_ApplePayLineItemTypeFinal :: String
js_ApplePayLineItemTypeFinal = String
"final"
 
data ApplePayPaymentMethodType = ApplePayPaymentMethodTypeDebit
                               | ApplePayPaymentMethodTypeCredit
                               | ApplePayPaymentMethodTypePrepaid
                               | ApplePayPaymentMethodTypeStore
                               deriving (Int -> ApplePayPaymentMethodType -> ShowS
[ApplePayPaymentMethodType] -> ShowS
ApplePayPaymentMethodType -> String
(Int -> ApplePayPaymentMethodType -> ShowS)
-> (ApplePayPaymentMethodType -> String)
-> ([ApplePayPaymentMethodType] -> ShowS)
-> Show ApplePayPaymentMethodType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ApplePayPaymentMethodType] -> ShowS
$cshowList :: [ApplePayPaymentMethodType] -> ShowS
show :: ApplePayPaymentMethodType -> String
$cshow :: ApplePayPaymentMethodType -> String
showsPrec :: Int -> ApplePayPaymentMethodType -> ShowS
$cshowsPrec :: Int -> ApplePayPaymentMethodType -> ShowS
Show, ReadPrec [ApplePayPaymentMethodType]
ReadPrec ApplePayPaymentMethodType
Int -> ReadS ApplePayPaymentMethodType
ReadS [ApplePayPaymentMethodType]
(Int -> ReadS ApplePayPaymentMethodType)
-> ReadS [ApplePayPaymentMethodType]
-> ReadPrec ApplePayPaymentMethodType
-> ReadPrec [ApplePayPaymentMethodType]
-> Read ApplePayPaymentMethodType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ApplePayPaymentMethodType]
$creadListPrec :: ReadPrec [ApplePayPaymentMethodType]
readPrec :: ReadPrec ApplePayPaymentMethodType
$creadPrec :: ReadPrec ApplePayPaymentMethodType
readList :: ReadS [ApplePayPaymentMethodType]
$creadList :: ReadS [ApplePayPaymentMethodType]
readsPrec :: Int -> ReadS ApplePayPaymentMethodType
$creadsPrec :: Int -> ReadS ApplePayPaymentMethodType
Read, ApplePayPaymentMethodType -> ApplePayPaymentMethodType -> Bool
(ApplePayPaymentMethodType -> ApplePayPaymentMethodType -> Bool)
-> (ApplePayPaymentMethodType -> ApplePayPaymentMethodType -> Bool)
-> Eq ApplePayPaymentMethodType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ApplePayPaymentMethodType -> ApplePayPaymentMethodType -> Bool
$c/= :: ApplePayPaymentMethodType -> ApplePayPaymentMethodType -> Bool
== :: ApplePayPaymentMethodType -> ApplePayPaymentMethodType -> Bool
$c== :: ApplePayPaymentMethodType -> ApplePayPaymentMethodType -> Bool
Eq, Eq ApplePayPaymentMethodType
Eq ApplePayPaymentMethodType
-> (ApplePayPaymentMethodType
    -> ApplePayPaymentMethodType -> Ordering)
-> (ApplePayPaymentMethodType -> ApplePayPaymentMethodType -> Bool)
-> (ApplePayPaymentMethodType -> ApplePayPaymentMethodType -> Bool)
-> (ApplePayPaymentMethodType -> ApplePayPaymentMethodType -> Bool)
-> (ApplePayPaymentMethodType -> ApplePayPaymentMethodType -> Bool)
-> (ApplePayPaymentMethodType
    -> ApplePayPaymentMethodType -> ApplePayPaymentMethodType)
-> (ApplePayPaymentMethodType
    -> ApplePayPaymentMethodType -> ApplePayPaymentMethodType)
-> Ord ApplePayPaymentMethodType
ApplePayPaymentMethodType -> ApplePayPaymentMethodType -> Bool
ApplePayPaymentMethodType -> ApplePayPaymentMethodType -> Ordering
ApplePayPaymentMethodType
-> ApplePayPaymentMethodType -> ApplePayPaymentMethodType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ApplePayPaymentMethodType
-> ApplePayPaymentMethodType -> ApplePayPaymentMethodType
$cmin :: ApplePayPaymentMethodType
-> ApplePayPaymentMethodType -> ApplePayPaymentMethodType
max :: ApplePayPaymentMethodType
-> ApplePayPaymentMethodType -> ApplePayPaymentMethodType
$cmax :: ApplePayPaymentMethodType
-> ApplePayPaymentMethodType -> ApplePayPaymentMethodType
>= :: ApplePayPaymentMethodType -> ApplePayPaymentMethodType -> Bool
$c>= :: ApplePayPaymentMethodType -> ApplePayPaymentMethodType -> Bool
> :: ApplePayPaymentMethodType -> ApplePayPaymentMethodType -> Bool
$c> :: ApplePayPaymentMethodType -> ApplePayPaymentMethodType -> Bool
<= :: ApplePayPaymentMethodType -> ApplePayPaymentMethodType -> Bool
$c<= :: ApplePayPaymentMethodType -> ApplePayPaymentMethodType -> Bool
< :: ApplePayPaymentMethodType -> ApplePayPaymentMethodType -> Bool
$c< :: ApplePayPaymentMethodType -> ApplePayPaymentMethodType -> Bool
compare :: ApplePayPaymentMethodType -> ApplePayPaymentMethodType -> Ordering
$ccompare :: ApplePayPaymentMethodType -> ApplePayPaymentMethodType -> Ordering
$cp1Ord :: Eq ApplePayPaymentMethodType
Ord, Typeable)
 
instance ToJSVal ApplePayPaymentMethodType where
        toJSVal :: ApplePayPaymentMethodType -> JSM JSVal
toJSVal ApplePayPaymentMethodType
ApplePayPaymentMethodTypeDebit
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_ApplePayPaymentMethodTypeDebit
        toJSVal ApplePayPaymentMethodType
ApplePayPaymentMethodTypeCredit
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_ApplePayPaymentMethodTypeCredit
        toJSVal ApplePayPaymentMethodType
ApplePayPaymentMethodTypePrepaid
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_ApplePayPaymentMethodTypePrepaid
        toJSVal ApplePayPaymentMethodType
ApplePayPaymentMethodTypeStore
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_ApplePayPaymentMethodTypeStore
 
instance FromJSVal ApplePayPaymentMethodType where
        fromJSVal :: JSVal -> JSM (Maybe ApplePayPaymentMethodType)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_ApplePayPaymentMethodTypeDebit JSM Bool
-> (Bool -> JSM (Maybe ApplePayPaymentMethodType))
-> JSM (Maybe ApplePayPaymentMethodType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe ApplePayPaymentMethodType
-> JSM (Maybe ApplePayPaymentMethodType)
forall (m :: * -> *) a. Monad m => a -> m a
return (ApplePayPaymentMethodType -> Maybe ApplePayPaymentMethodType
forall a. a -> Maybe a
Just ApplePayPaymentMethodType
ApplePayPaymentMethodTypeDebit)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_ApplePayPaymentMethodTypeCredit JSM Bool
-> (Bool -> JSM (Maybe ApplePayPaymentMethodType))
-> JSM (Maybe ApplePayPaymentMethodType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe ApplePayPaymentMethodType
-> JSM (Maybe ApplePayPaymentMethodType)
forall (m :: * -> *) a. Monad m => a -> m a
return (ApplePayPaymentMethodType -> Maybe ApplePayPaymentMethodType
forall a. a -> Maybe a
Just ApplePayPaymentMethodType
ApplePayPaymentMethodTypeCredit)
                                 Bool
False
                                   -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_ApplePayPaymentMethodTypePrepaid JSM Bool
-> (Bool -> JSM (Maybe ApplePayPaymentMethodType))
-> JSM (Maybe ApplePayPaymentMethodType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                        \ Bool
r ->
                                          case Bool
r of
                                              Bool
True -> Maybe ApplePayPaymentMethodType
-> JSM (Maybe ApplePayPaymentMethodType)
forall (m :: * -> *) a. Monad m => a -> m a
return (ApplePayPaymentMethodType -> Maybe ApplePayPaymentMethodType
forall a. a -> Maybe a
Just ApplePayPaymentMethodType
ApplePayPaymentMethodTypePrepaid)
                                              Bool
False
                                                -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_ApplePayPaymentMethodTypeStore
                                                     JSM Bool
-> (Bool -> JSM (Maybe ApplePayPaymentMethodType))
-> JSM (Maybe ApplePayPaymentMethodType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                     \ Bool
r ->
                                                       case Bool
r of
                                                           Bool
True
                                                             -> Maybe ApplePayPaymentMethodType
-> JSM (Maybe ApplePayPaymentMethodType)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                  (ApplePayPaymentMethodType -> Maybe ApplePayPaymentMethodType
forall a. a -> Maybe a
Just
                                                                     ApplePayPaymentMethodType
ApplePayPaymentMethodTypeStore)
                                                           Bool
False -> Maybe ApplePayPaymentMethodType
-> JSM (Maybe ApplePayPaymentMethodType)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ApplePayPaymentMethodType
forall a. Maybe a
Nothing
js_ApplePayPaymentMethodTypeDebit :: String
js_ApplePayPaymentMethodTypeDebit = String
"debit"
js_ApplePayPaymentMethodTypeCredit :: String
js_ApplePayPaymentMethodTypeCredit = String
"credit"
js_ApplePayPaymentMethodTypePrepaid :: String
js_ApplePayPaymentMethodTypePrepaid = String
"prepaid"
js_ApplePayPaymentMethodTypeStore :: String
js_ApplePayPaymentMethodTypeStore = String
"store"
 
data ApplePayPaymentPassActivationState = ApplePayPaymentPassActivationStateActivated
                                        | ApplePayPaymentPassActivationStateRequiresActivation
                                        | ApplePayPaymentPassActivationStateActivating
                                        | ApplePayPaymentPassActivationStateSuspended
                                        | ApplePayPaymentPassActivationStateDeactivated
                                        deriving (Int -> ApplePayPaymentPassActivationState -> ShowS
[ApplePayPaymentPassActivationState] -> ShowS
ApplePayPaymentPassActivationState -> String
(Int -> ApplePayPaymentPassActivationState -> ShowS)
-> (ApplePayPaymentPassActivationState -> String)
-> ([ApplePayPaymentPassActivationState] -> ShowS)
-> Show ApplePayPaymentPassActivationState
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ApplePayPaymentPassActivationState] -> ShowS
$cshowList :: [ApplePayPaymentPassActivationState] -> ShowS
show :: ApplePayPaymentPassActivationState -> String
$cshow :: ApplePayPaymentPassActivationState -> String
showsPrec :: Int -> ApplePayPaymentPassActivationState -> ShowS
$cshowsPrec :: Int -> ApplePayPaymentPassActivationState -> ShowS
Show, ReadPrec [ApplePayPaymentPassActivationState]
ReadPrec ApplePayPaymentPassActivationState
Int -> ReadS ApplePayPaymentPassActivationState
ReadS [ApplePayPaymentPassActivationState]
(Int -> ReadS ApplePayPaymentPassActivationState)
-> ReadS [ApplePayPaymentPassActivationState]
-> ReadPrec ApplePayPaymentPassActivationState
-> ReadPrec [ApplePayPaymentPassActivationState]
-> Read ApplePayPaymentPassActivationState
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ApplePayPaymentPassActivationState]
$creadListPrec :: ReadPrec [ApplePayPaymentPassActivationState]
readPrec :: ReadPrec ApplePayPaymentPassActivationState
$creadPrec :: ReadPrec ApplePayPaymentPassActivationState
readList :: ReadS [ApplePayPaymentPassActivationState]
$creadList :: ReadS [ApplePayPaymentPassActivationState]
readsPrec :: Int -> ReadS ApplePayPaymentPassActivationState
$creadsPrec :: Int -> ReadS ApplePayPaymentPassActivationState
Read, ApplePayPaymentPassActivationState
-> ApplePayPaymentPassActivationState -> Bool
(ApplePayPaymentPassActivationState
 -> ApplePayPaymentPassActivationState -> Bool)
-> (ApplePayPaymentPassActivationState
    -> ApplePayPaymentPassActivationState -> Bool)
-> Eq ApplePayPaymentPassActivationState
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ApplePayPaymentPassActivationState
-> ApplePayPaymentPassActivationState -> Bool
$c/= :: ApplePayPaymentPassActivationState
-> ApplePayPaymentPassActivationState -> Bool
== :: ApplePayPaymentPassActivationState
-> ApplePayPaymentPassActivationState -> Bool
$c== :: ApplePayPaymentPassActivationState
-> ApplePayPaymentPassActivationState -> Bool
Eq, Eq ApplePayPaymentPassActivationState
Eq ApplePayPaymentPassActivationState
-> (ApplePayPaymentPassActivationState
    -> ApplePayPaymentPassActivationState -> Ordering)
-> (ApplePayPaymentPassActivationState
    -> ApplePayPaymentPassActivationState -> Bool)
-> (ApplePayPaymentPassActivationState
    -> ApplePayPaymentPassActivationState -> Bool)
-> (ApplePayPaymentPassActivationState
    -> ApplePayPaymentPassActivationState -> Bool)
-> (ApplePayPaymentPassActivationState
    -> ApplePayPaymentPassActivationState -> Bool)
-> (ApplePayPaymentPassActivationState
    -> ApplePayPaymentPassActivationState
    -> ApplePayPaymentPassActivationState)
-> (ApplePayPaymentPassActivationState
    -> ApplePayPaymentPassActivationState
    -> ApplePayPaymentPassActivationState)
-> Ord ApplePayPaymentPassActivationState
ApplePayPaymentPassActivationState
-> ApplePayPaymentPassActivationState -> Bool
ApplePayPaymentPassActivationState
-> ApplePayPaymentPassActivationState -> Ordering
ApplePayPaymentPassActivationState
-> ApplePayPaymentPassActivationState
-> ApplePayPaymentPassActivationState
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ApplePayPaymentPassActivationState
-> ApplePayPaymentPassActivationState
-> ApplePayPaymentPassActivationState
$cmin :: ApplePayPaymentPassActivationState
-> ApplePayPaymentPassActivationState
-> ApplePayPaymentPassActivationState
max :: ApplePayPaymentPassActivationState
-> ApplePayPaymentPassActivationState
-> ApplePayPaymentPassActivationState
$cmax :: ApplePayPaymentPassActivationState
-> ApplePayPaymentPassActivationState
-> ApplePayPaymentPassActivationState
>= :: ApplePayPaymentPassActivationState
-> ApplePayPaymentPassActivationState -> Bool
$c>= :: ApplePayPaymentPassActivationState
-> ApplePayPaymentPassActivationState -> Bool
> :: ApplePayPaymentPassActivationState
-> ApplePayPaymentPassActivationState -> Bool
$c> :: ApplePayPaymentPassActivationState
-> ApplePayPaymentPassActivationState -> Bool
<= :: ApplePayPaymentPassActivationState
-> ApplePayPaymentPassActivationState -> Bool
$c<= :: ApplePayPaymentPassActivationState
-> ApplePayPaymentPassActivationState -> Bool
< :: ApplePayPaymentPassActivationState
-> ApplePayPaymentPassActivationState -> Bool
$c< :: ApplePayPaymentPassActivationState
-> ApplePayPaymentPassActivationState -> Bool
compare :: ApplePayPaymentPassActivationState
-> ApplePayPaymentPassActivationState -> Ordering
$ccompare :: ApplePayPaymentPassActivationState
-> ApplePayPaymentPassActivationState -> Ordering
$cp1Ord :: Eq ApplePayPaymentPassActivationState
Ord, Typeable)
 
instance ToJSVal ApplePayPaymentPassActivationState where
        toJSVal :: ApplePayPaymentPassActivationState -> JSM JSVal
toJSVal ApplePayPaymentPassActivationState
ApplePayPaymentPassActivationStateActivated
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_ApplePayPaymentPassActivationStateActivated
        toJSVal ApplePayPaymentPassActivationState
ApplePayPaymentPassActivationStateRequiresActivation
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_ApplePayPaymentPassActivationStateRequiresActivation
        toJSVal ApplePayPaymentPassActivationState
ApplePayPaymentPassActivationStateActivating
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_ApplePayPaymentPassActivationStateActivating
        toJSVal ApplePayPaymentPassActivationState
ApplePayPaymentPassActivationStateSuspended
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_ApplePayPaymentPassActivationStateSuspended
        toJSVal ApplePayPaymentPassActivationState
ApplePayPaymentPassActivationStateDeactivated
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_ApplePayPaymentPassActivationStateDeactivated
 
instance FromJSVal ApplePayPaymentPassActivationState where
        fromJSVal :: JSVal -> JSM (Maybe ApplePayPaymentPassActivationState)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_ApplePayPaymentPassActivationStateActivated
              JSM Bool
-> (Bool -> JSM (Maybe ApplePayPaymentPassActivationState))
-> JSM (Maybe ApplePayPaymentPassActivationState)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe ApplePayPaymentPassActivationState
-> JSM (Maybe ApplePayPaymentPassActivationState)
forall (m :: * -> *) a. Monad m => a -> m a
return (ApplePayPaymentPassActivationState
-> Maybe ApplePayPaymentPassActivationState
forall a. a -> Maybe a
Just ApplePayPaymentPassActivationState
ApplePayPaymentPassActivationStateActivated)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                           String
js_ApplePayPaymentPassActivationStateRequiresActivation
                           JSM Bool
-> (Bool -> JSM (Maybe ApplePayPaymentPassActivationState))
-> JSM (Maybe ApplePayPaymentPassActivationState)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True
                                   -> Maybe ApplePayPaymentPassActivationState
-> JSM (Maybe ApplePayPaymentPassActivationState)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                        (ApplePayPaymentPassActivationState
-> Maybe ApplePayPaymentPassActivationState
forall a. a -> Maybe a
Just ApplePayPaymentPassActivationState
ApplePayPaymentPassActivationStateRequiresActivation)
                                 Bool
False
                                   -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                        String
js_ApplePayPaymentPassActivationStateActivating
                                        JSM Bool
-> (Bool -> JSM (Maybe ApplePayPaymentPassActivationState))
-> JSM (Maybe ApplePayPaymentPassActivationState)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                        \ Bool
r ->
                                          case Bool
r of
                                              Bool
True
                                                -> Maybe ApplePayPaymentPassActivationState
-> JSM (Maybe ApplePayPaymentPassActivationState)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                     (ApplePayPaymentPassActivationState
-> Maybe ApplePayPaymentPassActivationState
forall a. a -> Maybe a
Just
                                                        ApplePayPaymentPassActivationState
ApplePayPaymentPassActivationStateActivating)
                                              Bool
False
                                                -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                     String
js_ApplePayPaymentPassActivationStateSuspended
                                                     JSM Bool
-> (Bool -> JSM (Maybe ApplePayPaymentPassActivationState))
-> JSM (Maybe ApplePayPaymentPassActivationState)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                     \ Bool
r ->
                                                       case Bool
r of
                                                           Bool
True
                                                             -> Maybe ApplePayPaymentPassActivationState
-> JSM (Maybe ApplePayPaymentPassActivationState)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                  (ApplePayPaymentPassActivationState
-> Maybe ApplePayPaymentPassActivationState
forall a. a -> Maybe a
Just
                                                                     ApplePayPaymentPassActivationState
ApplePayPaymentPassActivationStateSuspended)
                                                           Bool
False
                                                             -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                                  String
js_ApplePayPaymentPassActivationStateDeactivated
                                                                  JSM Bool
-> (Bool -> JSM (Maybe ApplePayPaymentPassActivationState))
-> JSM (Maybe ApplePayPaymentPassActivationState)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                  \ Bool
r ->
                                                                    case Bool
r of
                                                                        Bool
True
                                                                          -> Maybe ApplePayPaymentPassActivationState
-> JSM (Maybe ApplePayPaymentPassActivationState)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                               (ApplePayPaymentPassActivationState
-> Maybe ApplePayPaymentPassActivationState
forall a. a -> Maybe a
Just
                                                                                  ApplePayPaymentPassActivationState
ApplePayPaymentPassActivationStateDeactivated)
                                                                        Bool
False -> Maybe ApplePayPaymentPassActivationState
-> JSM (Maybe ApplePayPaymentPassActivationState)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ApplePayPaymentPassActivationState
forall a. Maybe a
Nothing
js_ApplePayPaymentPassActivationStateActivated :: String
js_ApplePayPaymentPassActivationStateActivated = String
"activated"
js_ApplePayPaymentPassActivationStateRequiresActivation :: String
js_ApplePayPaymentPassActivationStateRequiresActivation
  = String
"requiresActivation"
js_ApplePayPaymentPassActivationStateActivating :: String
js_ApplePayPaymentPassActivationStateActivating = String
"activating"
js_ApplePayPaymentPassActivationStateSuspended :: String
js_ApplePayPaymentPassActivationStateSuspended = String
"suspended"
js_ApplePayPaymentPassActivationStateDeactivated :: String
js_ApplePayPaymentPassActivationStateDeactivated = String
"deactivated"
 
data ApplePayMerchantCapability = ApplePayMerchantCapabilitySupports3DS
                                | ApplePayMerchantCapabilitySupportsEMV
                                | ApplePayMerchantCapabilitySupportsCredit
                                | ApplePayMerchantCapabilitySupportsDebit
                                deriving (Int -> ApplePayMerchantCapability -> ShowS
[ApplePayMerchantCapability] -> ShowS
ApplePayMerchantCapability -> String
(Int -> ApplePayMerchantCapability -> ShowS)
-> (ApplePayMerchantCapability -> String)
-> ([ApplePayMerchantCapability] -> ShowS)
-> Show ApplePayMerchantCapability
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ApplePayMerchantCapability] -> ShowS
$cshowList :: [ApplePayMerchantCapability] -> ShowS
show :: ApplePayMerchantCapability -> String
$cshow :: ApplePayMerchantCapability -> String
showsPrec :: Int -> ApplePayMerchantCapability -> ShowS
$cshowsPrec :: Int -> ApplePayMerchantCapability -> ShowS
Show, ReadPrec [ApplePayMerchantCapability]
ReadPrec ApplePayMerchantCapability
Int -> ReadS ApplePayMerchantCapability
ReadS [ApplePayMerchantCapability]
(Int -> ReadS ApplePayMerchantCapability)
-> ReadS [ApplePayMerchantCapability]
-> ReadPrec ApplePayMerchantCapability
-> ReadPrec [ApplePayMerchantCapability]
-> Read ApplePayMerchantCapability
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ApplePayMerchantCapability]
$creadListPrec :: ReadPrec [ApplePayMerchantCapability]
readPrec :: ReadPrec ApplePayMerchantCapability
$creadPrec :: ReadPrec ApplePayMerchantCapability
readList :: ReadS [ApplePayMerchantCapability]
$creadList :: ReadS [ApplePayMerchantCapability]
readsPrec :: Int -> ReadS ApplePayMerchantCapability
$creadsPrec :: Int -> ReadS ApplePayMerchantCapability
Read, ApplePayMerchantCapability -> ApplePayMerchantCapability -> Bool
(ApplePayMerchantCapability -> ApplePayMerchantCapability -> Bool)
-> (ApplePayMerchantCapability
    -> ApplePayMerchantCapability -> Bool)
-> Eq ApplePayMerchantCapability
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ApplePayMerchantCapability -> ApplePayMerchantCapability -> Bool
$c/= :: ApplePayMerchantCapability -> ApplePayMerchantCapability -> Bool
== :: ApplePayMerchantCapability -> ApplePayMerchantCapability -> Bool
$c== :: ApplePayMerchantCapability -> ApplePayMerchantCapability -> Bool
Eq, Eq ApplePayMerchantCapability
Eq ApplePayMerchantCapability
-> (ApplePayMerchantCapability
    -> ApplePayMerchantCapability -> Ordering)
-> (ApplePayMerchantCapability
    -> ApplePayMerchantCapability -> Bool)
-> (ApplePayMerchantCapability
    -> ApplePayMerchantCapability -> Bool)
-> (ApplePayMerchantCapability
    -> ApplePayMerchantCapability -> Bool)
-> (ApplePayMerchantCapability
    -> ApplePayMerchantCapability -> Bool)
-> (ApplePayMerchantCapability
    -> ApplePayMerchantCapability -> ApplePayMerchantCapability)
-> (ApplePayMerchantCapability
    -> ApplePayMerchantCapability -> ApplePayMerchantCapability)
-> Ord ApplePayMerchantCapability
ApplePayMerchantCapability -> ApplePayMerchantCapability -> Bool
ApplePayMerchantCapability
-> ApplePayMerchantCapability -> Ordering
ApplePayMerchantCapability
-> ApplePayMerchantCapability -> ApplePayMerchantCapability
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ApplePayMerchantCapability
-> ApplePayMerchantCapability -> ApplePayMerchantCapability
$cmin :: ApplePayMerchantCapability
-> ApplePayMerchantCapability -> ApplePayMerchantCapability
max :: ApplePayMerchantCapability
-> ApplePayMerchantCapability -> ApplePayMerchantCapability
$cmax :: ApplePayMerchantCapability
-> ApplePayMerchantCapability -> ApplePayMerchantCapability
>= :: ApplePayMerchantCapability -> ApplePayMerchantCapability -> Bool
$c>= :: ApplePayMerchantCapability -> ApplePayMerchantCapability -> Bool
> :: ApplePayMerchantCapability -> ApplePayMerchantCapability -> Bool
$c> :: ApplePayMerchantCapability -> ApplePayMerchantCapability -> Bool
<= :: ApplePayMerchantCapability -> ApplePayMerchantCapability -> Bool
$c<= :: ApplePayMerchantCapability -> ApplePayMerchantCapability -> Bool
< :: ApplePayMerchantCapability -> ApplePayMerchantCapability -> Bool
$c< :: ApplePayMerchantCapability -> ApplePayMerchantCapability -> Bool
compare :: ApplePayMerchantCapability
-> ApplePayMerchantCapability -> Ordering
$ccompare :: ApplePayMerchantCapability
-> ApplePayMerchantCapability -> Ordering
$cp1Ord :: Eq ApplePayMerchantCapability
Ord, Typeable)
 
instance ToJSVal ApplePayMerchantCapability where
        toJSVal :: ApplePayMerchantCapability -> JSM JSVal
toJSVal ApplePayMerchantCapability
ApplePayMerchantCapabilitySupports3DS
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_ApplePayMerchantCapabilitySupports3DS
        toJSVal ApplePayMerchantCapability
ApplePayMerchantCapabilitySupportsEMV
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_ApplePayMerchantCapabilitySupportsEMV
        toJSVal ApplePayMerchantCapability
ApplePayMerchantCapabilitySupportsCredit
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_ApplePayMerchantCapabilitySupportsCredit
        toJSVal ApplePayMerchantCapability
ApplePayMerchantCapabilitySupportsDebit
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_ApplePayMerchantCapabilitySupportsDebit
 
instance FromJSVal ApplePayMerchantCapability where
        fromJSVal :: JSVal -> JSM (Maybe ApplePayMerchantCapability)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_ApplePayMerchantCapabilitySupports3DS JSM Bool
-> (Bool -> JSM (Maybe ApplePayMerchantCapability))
-> JSM (Maybe ApplePayMerchantCapability)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe ApplePayMerchantCapability
-> JSM (Maybe ApplePayMerchantCapability)
forall (m :: * -> *) a. Monad m => a -> m a
return (ApplePayMerchantCapability -> Maybe ApplePayMerchantCapability
forall a. a -> Maybe a
Just ApplePayMerchantCapability
ApplePayMerchantCapabilitySupports3DS)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_ApplePayMerchantCapabilitySupportsEMV JSM Bool
-> (Bool -> JSM (Maybe ApplePayMerchantCapability))
-> JSM (Maybe ApplePayMerchantCapability)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe ApplePayMerchantCapability
-> JSM (Maybe ApplePayMerchantCapability)
forall (m :: * -> *) a. Monad m => a -> m a
return (ApplePayMerchantCapability -> Maybe ApplePayMerchantCapability
forall a. a -> Maybe a
Just ApplePayMerchantCapability
ApplePayMerchantCapabilitySupportsEMV)
                                 Bool
False
                                   -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_ApplePayMerchantCapabilitySupportsCredit
                                        JSM Bool
-> (Bool -> JSM (Maybe ApplePayMerchantCapability))
-> JSM (Maybe ApplePayMerchantCapability)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                        \ Bool
r ->
                                          case Bool
r of
                                              Bool
True
                                                -> Maybe ApplePayMerchantCapability
-> JSM (Maybe ApplePayMerchantCapability)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                     (ApplePayMerchantCapability -> Maybe ApplePayMerchantCapability
forall a. a -> Maybe a
Just ApplePayMerchantCapability
ApplePayMerchantCapabilitySupportsCredit)
                                              Bool
False
                                                -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                     String
js_ApplePayMerchantCapabilitySupportsDebit
                                                     JSM Bool
-> (Bool -> JSM (Maybe ApplePayMerchantCapability))
-> JSM (Maybe ApplePayMerchantCapability)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                     \ Bool
r ->
                                                       case Bool
r of
                                                           Bool
True
                                                             -> Maybe ApplePayMerchantCapability
-> JSM (Maybe ApplePayMerchantCapability)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                  (ApplePayMerchantCapability -> Maybe ApplePayMerchantCapability
forall a. a -> Maybe a
Just
                                                                     ApplePayMerchantCapability
ApplePayMerchantCapabilitySupportsDebit)
                                                           Bool
False -> Maybe ApplePayMerchantCapability
-> JSM (Maybe ApplePayMerchantCapability)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ApplePayMerchantCapability
forall a. Maybe a
Nothing
js_ApplePayMerchantCapabilitySupports3DS :: String
js_ApplePayMerchantCapabilitySupports3DS = String
"supports3DS"
js_ApplePayMerchantCapabilitySupportsEMV :: String
js_ApplePayMerchantCapabilitySupportsEMV = String
"supportsEMV"
js_ApplePayMerchantCapabilitySupportsCredit :: String
js_ApplePayMerchantCapabilitySupportsCredit = String
"supportsCredit"
js_ApplePayMerchantCapabilitySupportsDebit :: String
js_ApplePayMerchantCapabilitySupportsDebit = String
"supportsDebit"
 
data ApplePayContactField = ApplePayContactFieldEmail
                          | ApplePayContactFieldName
                          | ApplePayContactFieldPhone
                          | ApplePayContactFieldPostalAddress
                          deriving (Int -> ApplePayContactField -> ShowS
[ApplePayContactField] -> ShowS
ApplePayContactField -> String
(Int -> ApplePayContactField -> ShowS)
-> (ApplePayContactField -> String)
-> ([ApplePayContactField] -> ShowS)
-> Show ApplePayContactField
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ApplePayContactField] -> ShowS
$cshowList :: [ApplePayContactField] -> ShowS
show :: ApplePayContactField -> String
$cshow :: ApplePayContactField -> String
showsPrec :: Int -> ApplePayContactField -> ShowS
$cshowsPrec :: Int -> ApplePayContactField -> ShowS
Show, ReadPrec [ApplePayContactField]
ReadPrec ApplePayContactField
Int -> ReadS ApplePayContactField
ReadS [ApplePayContactField]
(Int -> ReadS ApplePayContactField)
-> ReadS [ApplePayContactField]
-> ReadPrec ApplePayContactField
-> ReadPrec [ApplePayContactField]
-> Read ApplePayContactField
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ApplePayContactField]
$creadListPrec :: ReadPrec [ApplePayContactField]
readPrec :: ReadPrec ApplePayContactField
$creadPrec :: ReadPrec ApplePayContactField
readList :: ReadS [ApplePayContactField]
$creadList :: ReadS [ApplePayContactField]
readsPrec :: Int -> ReadS ApplePayContactField
$creadsPrec :: Int -> ReadS ApplePayContactField
Read, ApplePayContactField -> ApplePayContactField -> Bool
(ApplePayContactField -> ApplePayContactField -> Bool)
-> (ApplePayContactField -> ApplePayContactField -> Bool)
-> Eq ApplePayContactField
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ApplePayContactField -> ApplePayContactField -> Bool
$c/= :: ApplePayContactField -> ApplePayContactField -> Bool
== :: ApplePayContactField -> ApplePayContactField -> Bool
$c== :: ApplePayContactField -> ApplePayContactField -> Bool
Eq, Eq ApplePayContactField
Eq ApplePayContactField
-> (ApplePayContactField -> ApplePayContactField -> Ordering)
-> (ApplePayContactField -> ApplePayContactField -> Bool)
-> (ApplePayContactField -> ApplePayContactField -> Bool)
-> (ApplePayContactField -> ApplePayContactField -> Bool)
-> (ApplePayContactField -> ApplePayContactField -> Bool)
-> (ApplePayContactField
    -> ApplePayContactField -> ApplePayContactField)
-> (ApplePayContactField
    -> ApplePayContactField -> ApplePayContactField)
-> Ord ApplePayContactField
ApplePayContactField -> ApplePayContactField -> Bool
ApplePayContactField -> ApplePayContactField -> Ordering
ApplePayContactField
-> ApplePayContactField -> ApplePayContactField
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ApplePayContactField
-> ApplePayContactField -> ApplePayContactField
$cmin :: ApplePayContactField
-> ApplePayContactField -> ApplePayContactField
max :: ApplePayContactField
-> ApplePayContactField -> ApplePayContactField
$cmax :: ApplePayContactField
-> ApplePayContactField -> ApplePayContactField
>= :: ApplePayContactField -> ApplePayContactField -> Bool
$c>= :: ApplePayContactField -> ApplePayContactField -> Bool
> :: ApplePayContactField -> ApplePayContactField -> Bool
$c> :: ApplePayContactField -> ApplePayContactField -> Bool
<= :: ApplePayContactField -> ApplePayContactField -> Bool
$c<= :: ApplePayContactField -> ApplePayContactField -> Bool
< :: ApplePayContactField -> ApplePayContactField -> Bool
$c< :: ApplePayContactField -> ApplePayContactField -> Bool
compare :: ApplePayContactField -> ApplePayContactField -> Ordering
$ccompare :: ApplePayContactField -> ApplePayContactField -> Ordering
$cp1Ord :: Eq ApplePayContactField
Ord, Typeable)
 
instance ToJSVal ApplePayContactField where
        toJSVal :: ApplePayContactField -> JSM JSVal
toJSVal ApplePayContactField
ApplePayContactFieldEmail
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_ApplePayContactFieldEmail
        toJSVal ApplePayContactField
ApplePayContactFieldName
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_ApplePayContactFieldName
        toJSVal ApplePayContactField
ApplePayContactFieldPhone
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_ApplePayContactFieldPhone
        toJSVal ApplePayContactField
ApplePayContactFieldPostalAddress
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_ApplePayContactFieldPostalAddress
 
instance FromJSVal ApplePayContactField where
        fromJSVal :: JSVal -> JSM (Maybe ApplePayContactField)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_ApplePayContactFieldEmail JSM Bool
-> (Bool -> JSM (Maybe ApplePayContactField))
-> JSM (Maybe ApplePayContactField)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe ApplePayContactField -> JSM (Maybe ApplePayContactField)
forall (m :: * -> *) a. Monad m => a -> m a
return (ApplePayContactField -> Maybe ApplePayContactField
forall a. a -> Maybe a
Just ApplePayContactField
ApplePayContactFieldEmail)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_ApplePayContactFieldName JSM Bool
-> (Bool -> JSM (Maybe ApplePayContactField))
-> JSM (Maybe ApplePayContactField)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe ApplePayContactField -> JSM (Maybe ApplePayContactField)
forall (m :: * -> *) a. Monad m => a -> m a
return (ApplePayContactField -> Maybe ApplePayContactField
forall a. a -> Maybe a
Just ApplePayContactField
ApplePayContactFieldName)
                                 Bool
False
                                   -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_ApplePayContactFieldPhone JSM Bool
-> (Bool -> JSM (Maybe ApplePayContactField))
-> JSM (Maybe ApplePayContactField)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                        \ Bool
r ->
                                          case Bool
r of
                                              Bool
True -> Maybe ApplePayContactField -> JSM (Maybe ApplePayContactField)
forall (m :: * -> *) a. Monad m => a -> m a
return (ApplePayContactField -> Maybe ApplePayContactField
forall a. a -> Maybe a
Just ApplePayContactField
ApplePayContactFieldPhone)
                                              Bool
False
                                                -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                     String
js_ApplePayContactFieldPostalAddress
                                                     JSM Bool
-> (Bool -> JSM (Maybe ApplePayContactField))
-> JSM (Maybe ApplePayContactField)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                     \ Bool
r ->
                                                       case Bool
r of
                                                           Bool
True
                                                             -> Maybe ApplePayContactField -> JSM (Maybe ApplePayContactField)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                  (ApplePayContactField -> Maybe ApplePayContactField
forall a. a -> Maybe a
Just
                                                                     ApplePayContactField
ApplePayContactFieldPostalAddress)
                                                           Bool
False -> Maybe ApplePayContactField -> JSM (Maybe ApplePayContactField)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ApplePayContactField
forall a. Maybe a
Nothing
js_ApplePayContactFieldEmail :: String
js_ApplePayContactFieldEmail = String
"email"
js_ApplePayContactFieldName :: String
js_ApplePayContactFieldName = String
"name"
js_ApplePayContactFieldPhone :: String
js_ApplePayContactFieldPhone = String
"phone"
js_ApplePayContactFieldPostalAddress :: String
js_ApplePayContactFieldPostalAddress = String
"postalAddress"
 
data ApplePayShippingType = ApplePayShippingTypeShipping
                          | ApplePayShippingTypeDelivery
                          | ApplePayShippingTypeStorePickup
                          | ApplePayShippingTypeServicePickup
                          deriving (Int -> ApplePayShippingType -> ShowS
[ApplePayShippingType] -> ShowS
ApplePayShippingType -> String
(Int -> ApplePayShippingType -> ShowS)
-> (ApplePayShippingType -> String)
-> ([ApplePayShippingType] -> ShowS)
-> Show ApplePayShippingType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ApplePayShippingType] -> ShowS
$cshowList :: [ApplePayShippingType] -> ShowS
show :: ApplePayShippingType -> String
$cshow :: ApplePayShippingType -> String
showsPrec :: Int -> ApplePayShippingType -> ShowS
$cshowsPrec :: Int -> ApplePayShippingType -> ShowS
Show, ReadPrec [ApplePayShippingType]
ReadPrec ApplePayShippingType
Int -> ReadS ApplePayShippingType
ReadS [ApplePayShippingType]
(Int -> ReadS ApplePayShippingType)
-> ReadS [ApplePayShippingType]
-> ReadPrec ApplePayShippingType
-> ReadPrec [ApplePayShippingType]
-> Read ApplePayShippingType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ApplePayShippingType]
$creadListPrec :: ReadPrec [ApplePayShippingType]
readPrec :: ReadPrec ApplePayShippingType
$creadPrec :: ReadPrec ApplePayShippingType
readList :: ReadS [ApplePayShippingType]
$creadList :: ReadS [ApplePayShippingType]
readsPrec :: Int -> ReadS ApplePayShippingType
$creadsPrec :: Int -> ReadS ApplePayShippingType
Read, ApplePayShippingType -> ApplePayShippingType -> Bool
(ApplePayShippingType -> ApplePayShippingType -> Bool)
-> (ApplePayShippingType -> ApplePayShippingType -> Bool)
-> Eq ApplePayShippingType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ApplePayShippingType -> ApplePayShippingType -> Bool
$c/= :: ApplePayShippingType -> ApplePayShippingType -> Bool
== :: ApplePayShippingType -> ApplePayShippingType -> Bool
$c== :: ApplePayShippingType -> ApplePayShippingType -> Bool
Eq, Eq ApplePayShippingType
Eq ApplePayShippingType
-> (ApplePayShippingType -> ApplePayShippingType -> Ordering)
-> (ApplePayShippingType -> ApplePayShippingType -> Bool)
-> (ApplePayShippingType -> ApplePayShippingType -> Bool)
-> (ApplePayShippingType -> ApplePayShippingType -> Bool)
-> (ApplePayShippingType -> ApplePayShippingType -> Bool)
-> (ApplePayShippingType
    -> ApplePayShippingType -> ApplePayShippingType)
-> (ApplePayShippingType
    -> ApplePayShippingType -> ApplePayShippingType)
-> Ord ApplePayShippingType
ApplePayShippingType -> ApplePayShippingType -> Bool
ApplePayShippingType -> ApplePayShippingType -> Ordering
ApplePayShippingType
-> ApplePayShippingType -> ApplePayShippingType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ApplePayShippingType
-> ApplePayShippingType -> ApplePayShippingType
$cmin :: ApplePayShippingType
-> ApplePayShippingType -> ApplePayShippingType
max :: ApplePayShippingType
-> ApplePayShippingType -> ApplePayShippingType
$cmax :: ApplePayShippingType
-> ApplePayShippingType -> ApplePayShippingType
>= :: ApplePayShippingType -> ApplePayShippingType -> Bool
$c>= :: ApplePayShippingType -> ApplePayShippingType -> Bool
> :: ApplePayShippingType -> ApplePayShippingType -> Bool
$c> :: ApplePayShippingType -> ApplePayShippingType -> Bool
<= :: ApplePayShippingType -> ApplePayShippingType -> Bool
$c<= :: ApplePayShippingType -> ApplePayShippingType -> Bool
< :: ApplePayShippingType -> ApplePayShippingType -> Bool
$c< :: ApplePayShippingType -> ApplePayShippingType -> Bool
compare :: ApplePayShippingType -> ApplePayShippingType -> Ordering
$ccompare :: ApplePayShippingType -> ApplePayShippingType -> Ordering
$cp1Ord :: Eq ApplePayShippingType
Ord, Typeable)
 
instance ToJSVal ApplePayShippingType where
        toJSVal :: ApplePayShippingType -> JSM JSVal
toJSVal ApplePayShippingType
ApplePayShippingTypeShipping
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_ApplePayShippingTypeShipping
        toJSVal ApplePayShippingType
ApplePayShippingTypeDelivery
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_ApplePayShippingTypeDelivery
        toJSVal ApplePayShippingType
ApplePayShippingTypeStorePickup
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_ApplePayShippingTypeStorePickup
        toJSVal ApplePayShippingType
ApplePayShippingTypeServicePickup
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_ApplePayShippingTypeServicePickup
 
instance FromJSVal ApplePayShippingType where
        fromJSVal :: JSVal -> JSM (Maybe ApplePayShippingType)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_ApplePayShippingTypeShipping JSM Bool
-> (Bool -> JSM (Maybe ApplePayShippingType))
-> JSM (Maybe ApplePayShippingType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe ApplePayShippingType -> JSM (Maybe ApplePayShippingType)
forall (m :: * -> *) a. Monad m => a -> m a
return (ApplePayShippingType -> Maybe ApplePayShippingType
forall a. a -> Maybe a
Just ApplePayShippingType
ApplePayShippingTypeShipping)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_ApplePayShippingTypeDelivery JSM Bool
-> (Bool -> JSM (Maybe ApplePayShippingType))
-> JSM (Maybe ApplePayShippingType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe ApplePayShippingType -> JSM (Maybe ApplePayShippingType)
forall (m :: * -> *) a. Monad m => a -> m a
return (ApplePayShippingType -> Maybe ApplePayShippingType
forall a. a -> Maybe a
Just ApplePayShippingType
ApplePayShippingTypeDelivery)
                                 Bool
False
                                   -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_ApplePayShippingTypeStorePickup JSM Bool
-> (Bool -> JSM (Maybe ApplePayShippingType))
-> JSM (Maybe ApplePayShippingType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                        \ Bool
r ->
                                          case Bool
r of
                                              Bool
True -> Maybe ApplePayShippingType -> JSM (Maybe ApplePayShippingType)
forall (m :: * -> *) a. Monad m => a -> m a
return (ApplePayShippingType -> Maybe ApplePayShippingType
forall a. a -> Maybe a
Just ApplePayShippingType
ApplePayShippingTypeStorePickup)
                                              Bool
False
                                                -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                     String
js_ApplePayShippingTypeServicePickup
                                                     JSM Bool
-> (Bool -> JSM (Maybe ApplePayShippingType))
-> JSM (Maybe ApplePayShippingType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                     \ Bool
r ->
                                                       case Bool
r of
                                                           Bool
True
                                                             -> Maybe ApplePayShippingType -> JSM (Maybe ApplePayShippingType)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                  (ApplePayShippingType -> Maybe ApplePayShippingType
forall a. a -> Maybe a
Just
                                                                     ApplePayShippingType
ApplePayShippingTypeServicePickup)
                                                           Bool
False -> Maybe ApplePayShippingType -> JSM (Maybe ApplePayShippingType)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ApplePayShippingType
forall a. Maybe a
Nothing
js_ApplePayShippingTypeShipping :: String
js_ApplePayShippingTypeShipping = String
"shipping"
js_ApplePayShippingTypeDelivery :: String
js_ApplePayShippingTypeDelivery = String
"delivery"
js_ApplePayShippingTypeStorePickup :: String
js_ApplePayShippingTypeStorePickup = String
"storePickup"
js_ApplePayShippingTypeServicePickup :: String
js_ApplePayShippingTypeServicePickup = String
"servicePickup"
 
data MediaKeyMessageType = MediaKeyMessageTypeLicenseRequest
                         | MediaKeyMessageTypeLicenseRenewal
                         | MediaKeyMessageTypeLicenseRelease
                         | MediaKeyMessageTypeIndividualizationRequest
                         deriving (Int -> MediaKeyMessageType -> ShowS
[MediaKeyMessageType] -> ShowS
MediaKeyMessageType -> String
(Int -> MediaKeyMessageType -> ShowS)
-> (MediaKeyMessageType -> String)
-> ([MediaKeyMessageType] -> ShowS)
-> Show MediaKeyMessageType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MediaKeyMessageType] -> ShowS
$cshowList :: [MediaKeyMessageType] -> ShowS
show :: MediaKeyMessageType -> String
$cshow :: MediaKeyMessageType -> String
showsPrec :: Int -> MediaKeyMessageType -> ShowS
$cshowsPrec :: Int -> MediaKeyMessageType -> ShowS
Show, ReadPrec [MediaKeyMessageType]
ReadPrec MediaKeyMessageType
Int -> ReadS MediaKeyMessageType
ReadS [MediaKeyMessageType]
(Int -> ReadS MediaKeyMessageType)
-> ReadS [MediaKeyMessageType]
-> ReadPrec MediaKeyMessageType
-> ReadPrec [MediaKeyMessageType]
-> Read MediaKeyMessageType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [MediaKeyMessageType]
$creadListPrec :: ReadPrec [MediaKeyMessageType]
readPrec :: ReadPrec MediaKeyMessageType
$creadPrec :: ReadPrec MediaKeyMessageType
readList :: ReadS [MediaKeyMessageType]
$creadList :: ReadS [MediaKeyMessageType]
readsPrec :: Int -> ReadS MediaKeyMessageType
$creadsPrec :: Int -> ReadS MediaKeyMessageType
Read, MediaKeyMessageType -> MediaKeyMessageType -> Bool
(MediaKeyMessageType -> MediaKeyMessageType -> Bool)
-> (MediaKeyMessageType -> MediaKeyMessageType -> Bool)
-> Eq MediaKeyMessageType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MediaKeyMessageType -> MediaKeyMessageType -> Bool
$c/= :: MediaKeyMessageType -> MediaKeyMessageType -> Bool
== :: MediaKeyMessageType -> MediaKeyMessageType -> Bool
$c== :: MediaKeyMessageType -> MediaKeyMessageType -> Bool
Eq, Eq MediaKeyMessageType
Eq MediaKeyMessageType
-> (MediaKeyMessageType -> MediaKeyMessageType -> Ordering)
-> (MediaKeyMessageType -> MediaKeyMessageType -> Bool)
-> (MediaKeyMessageType -> MediaKeyMessageType -> Bool)
-> (MediaKeyMessageType -> MediaKeyMessageType -> Bool)
-> (MediaKeyMessageType -> MediaKeyMessageType -> Bool)
-> (MediaKeyMessageType
    -> MediaKeyMessageType -> MediaKeyMessageType)
-> (MediaKeyMessageType
    -> MediaKeyMessageType -> MediaKeyMessageType)
-> Ord MediaKeyMessageType
MediaKeyMessageType -> MediaKeyMessageType -> Bool
MediaKeyMessageType -> MediaKeyMessageType -> Ordering
MediaKeyMessageType -> MediaKeyMessageType -> MediaKeyMessageType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: MediaKeyMessageType -> MediaKeyMessageType -> MediaKeyMessageType
$cmin :: MediaKeyMessageType -> MediaKeyMessageType -> MediaKeyMessageType
max :: MediaKeyMessageType -> MediaKeyMessageType -> MediaKeyMessageType
$cmax :: MediaKeyMessageType -> MediaKeyMessageType -> MediaKeyMessageType
>= :: MediaKeyMessageType -> MediaKeyMessageType -> Bool
$c>= :: MediaKeyMessageType -> MediaKeyMessageType -> Bool
> :: MediaKeyMessageType -> MediaKeyMessageType -> Bool
$c> :: MediaKeyMessageType -> MediaKeyMessageType -> Bool
<= :: MediaKeyMessageType -> MediaKeyMessageType -> Bool
$c<= :: MediaKeyMessageType -> MediaKeyMessageType -> Bool
< :: MediaKeyMessageType -> MediaKeyMessageType -> Bool
$c< :: MediaKeyMessageType -> MediaKeyMessageType -> Bool
compare :: MediaKeyMessageType -> MediaKeyMessageType -> Ordering
$ccompare :: MediaKeyMessageType -> MediaKeyMessageType -> Ordering
$cp1Ord :: Eq MediaKeyMessageType
Ord, Typeable)
 
instance ToJSVal MediaKeyMessageType where
        toJSVal :: MediaKeyMessageType -> JSM JSVal
toJSVal MediaKeyMessageType
MediaKeyMessageTypeLicenseRequest
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_MediaKeyMessageTypeLicenseRequest
        toJSVal MediaKeyMessageType
MediaKeyMessageTypeLicenseRenewal
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_MediaKeyMessageTypeLicenseRenewal
        toJSVal MediaKeyMessageType
MediaKeyMessageTypeLicenseRelease
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_MediaKeyMessageTypeLicenseRelease
        toJSVal MediaKeyMessageType
MediaKeyMessageTypeIndividualizationRequest
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_MediaKeyMessageTypeIndividualizationRequest
 
instance FromJSVal MediaKeyMessageType where
        fromJSVal :: JSVal -> JSM (Maybe MediaKeyMessageType)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_MediaKeyMessageTypeLicenseRequest JSM Bool
-> (Bool -> JSM (Maybe MediaKeyMessageType))
-> JSM (Maybe MediaKeyMessageType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe MediaKeyMessageType -> JSM (Maybe MediaKeyMessageType)
forall (m :: * -> *) a. Monad m => a -> m a
return (MediaKeyMessageType -> Maybe MediaKeyMessageType
forall a. a -> Maybe a
Just MediaKeyMessageType
MediaKeyMessageTypeLicenseRequest)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_MediaKeyMessageTypeLicenseRenewal JSM Bool
-> (Bool -> JSM (Maybe MediaKeyMessageType))
-> JSM (Maybe MediaKeyMessageType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe MediaKeyMessageType -> JSM (Maybe MediaKeyMessageType)
forall (m :: * -> *) a. Monad m => a -> m a
return (MediaKeyMessageType -> Maybe MediaKeyMessageType
forall a. a -> Maybe a
Just MediaKeyMessageType
MediaKeyMessageTypeLicenseRenewal)
                                 Bool
False
                                   -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_MediaKeyMessageTypeLicenseRelease JSM Bool
-> (Bool -> JSM (Maybe MediaKeyMessageType))
-> JSM (Maybe MediaKeyMessageType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                        \ Bool
r ->
                                          case Bool
r of
                                              Bool
True
                                                -> Maybe MediaKeyMessageType -> JSM (Maybe MediaKeyMessageType)
forall (m :: * -> *) a. Monad m => a -> m a
return (MediaKeyMessageType -> Maybe MediaKeyMessageType
forall a. a -> Maybe a
Just MediaKeyMessageType
MediaKeyMessageTypeLicenseRelease)
                                              Bool
False
                                                -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                     String
js_MediaKeyMessageTypeIndividualizationRequest
                                                     JSM Bool
-> (Bool -> JSM (Maybe MediaKeyMessageType))
-> JSM (Maybe MediaKeyMessageType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                     \ Bool
r ->
                                                       case Bool
r of
                                                           Bool
True
                                                             -> Maybe MediaKeyMessageType -> JSM (Maybe MediaKeyMessageType)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                  (MediaKeyMessageType -> Maybe MediaKeyMessageType
forall a. a -> Maybe a
Just
                                                                     MediaKeyMessageType
MediaKeyMessageTypeIndividualizationRequest)
                                                           Bool
False -> Maybe MediaKeyMessageType -> JSM (Maybe MediaKeyMessageType)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe MediaKeyMessageType
forall a. Maybe a
Nothing
js_MediaKeyMessageTypeLicenseRequest :: String
js_MediaKeyMessageTypeLicenseRequest = String
"license-request"
js_MediaKeyMessageTypeLicenseRenewal :: String
js_MediaKeyMessageTypeLicenseRenewal = String
"license-renewal"
js_MediaKeyMessageTypeLicenseRelease :: String
js_MediaKeyMessageTypeLicenseRelease = String
"license-release"
js_MediaKeyMessageTypeIndividualizationRequest :: String
js_MediaKeyMessageTypeIndividualizationRequest
  = String
"individualization-request"
 
data MediaKeySessionType = MediaKeySessionTypeTemporary
                         | MediaKeySessionTypePersistentUsageRecord
                         | MediaKeySessionTypePersistentLicense
                         deriving (Int -> MediaKeySessionType -> ShowS
[MediaKeySessionType] -> ShowS
MediaKeySessionType -> String
(Int -> MediaKeySessionType -> ShowS)
-> (MediaKeySessionType -> String)
-> ([MediaKeySessionType] -> ShowS)
-> Show MediaKeySessionType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MediaKeySessionType] -> ShowS
$cshowList :: [MediaKeySessionType] -> ShowS
show :: MediaKeySessionType -> String
$cshow :: MediaKeySessionType -> String
showsPrec :: Int -> MediaKeySessionType -> ShowS
$cshowsPrec :: Int -> MediaKeySessionType -> ShowS
Show, ReadPrec [MediaKeySessionType]
ReadPrec MediaKeySessionType
Int -> ReadS MediaKeySessionType
ReadS [MediaKeySessionType]
(Int -> ReadS MediaKeySessionType)
-> ReadS [MediaKeySessionType]
-> ReadPrec MediaKeySessionType
-> ReadPrec [MediaKeySessionType]
-> Read MediaKeySessionType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [MediaKeySessionType]
$creadListPrec :: ReadPrec [MediaKeySessionType]
readPrec :: ReadPrec MediaKeySessionType
$creadPrec :: ReadPrec MediaKeySessionType
readList :: ReadS [MediaKeySessionType]
$creadList :: ReadS [MediaKeySessionType]
readsPrec :: Int -> ReadS MediaKeySessionType
$creadsPrec :: Int -> ReadS MediaKeySessionType
Read, MediaKeySessionType -> MediaKeySessionType -> Bool
(MediaKeySessionType -> MediaKeySessionType -> Bool)
-> (MediaKeySessionType -> MediaKeySessionType -> Bool)
-> Eq MediaKeySessionType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MediaKeySessionType -> MediaKeySessionType -> Bool
$c/= :: MediaKeySessionType -> MediaKeySessionType -> Bool
== :: MediaKeySessionType -> MediaKeySessionType -> Bool
$c== :: MediaKeySessionType -> MediaKeySessionType -> Bool
Eq, Eq MediaKeySessionType
Eq MediaKeySessionType
-> (MediaKeySessionType -> MediaKeySessionType -> Ordering)
-> (MediaKeySessionType -> MediaKeySessionType -> Bool)
-> (MediaKeySessionType -> MediaKeySessionType -> Bool)
-> (MediaKeySessionType -> MediaKeySessionType -> Bool)
-> (MediaKeySessionType -> MediaKeySessionType -> Bool)
-> (MediaKeySessionType
    -> MediaKeySessionType -> MediaKeySessionType)
-> (MediaKeySessionType
    -> MediaKeySessionType -> MediaKeySessionType)
-> Ord MediaKeySessionType
MediaKeySessionType -> MediaKeySessionType -> Bool
MediaKeySessionType -> MediaKeySessionType -> Ordering
MediaKeySessionType -> MediaKeySessionType -> MediaKeySessionType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: MediaKeySessionType -> MediaKeySessionType -> MediaKeySessionType
$cmin :: MediaKeySessionType -> MediaKeySessionType -> MediaKeySessionType
max :: MediaKeySessionType -> MediaKeySessionType -> MediaKeySessionType
$cmax :: MediaKeySessionType -> MediaKeySessionType -> MediaKeySessionType
>= :: MediaKeySessionType -> MediaKeySessionType -> Bool
$c>= :: MediaKeySessionType -> MediaKeySessionType -> Bool
> :: MediaKeySessionType -> MediaKeySessionType -> Bool
$c> :: MediaKeySessionType -> MediaKeySessionType -> Bool
<= :: MediaKeySessionType -> MediaKeySessionType -> Bool
$c<= :: MediaKeySessionType -> MediaKeySessionType -> Bool
< :: MediaKeySessionType -> MediaKeySessionType -> Bool
$c< :: MediaKeySessionType -> MediaKeySessionType -> Bool
compare :: MediaKeySessionType -> MediaKeySessionType -> Ordering
$ccompare :: MediaKeySessionType -> MediaKeySessionType -> Ordering
$cp1Ord :: Eq MediaKeySessionType
Ord, Typeable)
 
instance ToJSVal MediaKeySessionType where
        toJSVal :: MediaKeySessionType -> JSM JSVal
toJSVal MediaKeySessionType
MediaKeySessionTypeTemporary
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_MediaKeySessionTypeTemporary
        toJSVal MediaKeySessionType
MediaKeySessionTypePersistentUsageRecord
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_MediaKeySessionTypePersistentUsageRecord
        toJSVal MediaKeySessionType
MediaKeySessionTypePersistentLicense
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_MediaKeySessionTypePersistentLicense
 
instance FromJSVal MediaKeySessionType where
        fromJSVal :: JSVal -> JSM (Maybe MediaKeySessionType)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_MediaKeySessionTypeTemporary JSM Bool
-> (Bool -> JSM (Maybe MediaKeySessionType))
-> JSM (Maybe MediaKeySessionType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe MediaKeySessionType -> JSM (Maybe MediaKeySessionType)
forall (m :: * -> *) a. Monad m => a -> m a
return (MediaKeySessionType -> Maybe MediaKeySessionType
forall a. a -> Maybe a
Just MediaKeySessionType
MediaKeySessionTypeTemporary)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_MediaKeySessionTypePersistentUsageRecord JSM Bool
-> (Bool -> JSM (Maybe MediaKeySessionType))
-> JSM (Maybe MediaKeySessionType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe MediaKeySessionType -> JSM (Maybe MediaKeySessionType)
forall (m :: * -> *) a. Monad m => a -> m a
return (MediaKeySessionType -> Maybe MediaKeySessionType
forall a. a -> Maybe a
Just MediaKeySessionType
MediaKeySessionTypePersistentUsageRecord)
                                 Bool
False
                                   -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_MediaKeySessionTypePersistentLicense JSM Bool
-> (Bool -> JSM (Maybe MediaKeySessionType))
-> JSM (Maybe MediaKeySessionType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                        \ Bool
r ->
                                          case Bool
r of
                                              Bool
True
                                                -> Maybe MediaKeySessionType -> JSM (Maybe MediaKeySessionType)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                     (MediaKeySessionType -> Maybe MediaKeySessionType
forall a. a -> Maybe a
Just MediaKeySessionType
MediaKeySessionTypePersistentLicense)
                                              Bool
False -> Maybe MediaKeySessionType -> JSM (Maybe MediaKeySessionType)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe MediaKeySessionType
forall a. Maybe a
Nothing
js_MediaKeySessionTypeTemporary :: String
js_MediaKeySessionTypeTemporary = String
"temporary"
js_MediaKeySessionTypePersistentUsageRecord :: String
js_MediaKeySessionTypePersistentUsageRecord
  = String
"persistent-usage-record"
js_MediaKeySessionTypePersistentLicense :: String
js_MediaKeySessionTypePersistentLicense = String
"persistent-license"
 
data MediaKeysRequirement = MediaKeysRequirementRequired
                          | MediaKeysRequirementOptional
                          | MediaKeysRequirementNotAllowed
                          deriving (Int -> MediaKeysRequirement -> ShowS
[MediaKeysRequirement] -> ShowS
MediaKeysRequirement -> String
(Int -> MediaKeysRequirement -> ShowS)
-> (MediaKeysRequirement -> String)
-> ([MediaKeysRequirement] -> ShowS)
-> Show MediaKeysRequirement
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MediaKeysRequirement] -> ShowS
$cshowList :: [MediaKeysRequirement] -> ShowS
show :: MediaKeysRequirement -> String
$cshow :: MediaKeysRequirement -> String
showsPrec :: Int -> MediaKeysRequirement -> ShowS
$cshowsPrec :: Int -> MediaKeysRequirement -> ShowS
Show, ReadPrec [MediaKeysRequirement]
ReadPrec MediaKeysRequirement
Int -> ReadS MediaKeysRequirement
ReadS [MediaKeysRequirement]
(Int -> ReadS MediaKeysRequirement)
-> ReadS [MediaKeysRequirement]
-> ReadPrec MediaKeysRequirement
-> ReadPrec [MediaKeysRequirement]
-> Read MediaKeysRequirement
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [MediaKeysRequirement]
$creadListPrec :: ReadPrec [MediaKeysRequirement]
readPrec :: ReadPrec MediaKeysRequirement
$creadPrec :: ReadPrec MediaKeysRequirement
readList :: ReadS [MediaKeysRequirement]
$creadList :: ReadS [MediaKeysRequirement]
readsPrec :: Int -> ReadS MediaKeysRequirement
$creadsPrec :: Int -> ReadS MediaKeysRequirement
Read, MediaKeysRequirement -> MediaKeysRequirement -> Bool
(MediaKeysRequirement -> MediaKeysRequirement -> Bool)
-> (MediaKeysRequirement -> MediaKeysRequirement -> Bool)
-> Eq MediaKeysRequirement
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MediaKeysRequirement -> MediaKeysRequirement -> Bool
$c/= :: MediaKeysRequirement -> MediaKeysRequirement -> Bool
== :: MediaKeysRequirement -> MediaKeysRequirement -> Bool
$c== :: MediaKeysRequirement -> MediaKeysRequirement -> Bool
Eq, Eq MediaKeysRequirement
Eq MediaKeysRequirement
-> (MediaKeysRequirement -> MediaKeysRequirement -> Ordering)
-> (MediaKeysRequirement -> MediaKeysRequirement -> Bool)
-> (MediaKeysRequirement -> MediaKeysRequirement -> Bool)
-> (MediaKeysRequirement -> MediaKeysRequirement -> Bool)
-> (MediaKeysRequirement -> MediaKeysRequirement -> Bool)
-> (MediaKeysRequirement
    -> MediaKeysRequirement -> MediaKeysRequirement)
-> (MediaKeysRequirement
    -> MediaKeysRequirement -> MediaKeysRequirement)
-> Ord MediaKeysRequirement
MediaKeysRequirement -> MediaKeysRequirement -> Bool
MediaKeysRequirement -> MediaKeysRequirement -> Ordering
MediaKeysRequirement
-> MediaKeysRequirement -> MediaKeysRequirement
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: MediaKeysRequirement
-> MediaKeysRequirement -> MediaKeysRequirement
$cmin :: MediaKeysRequirement
-> MediaKeysRequirement -> MediaKeysRequirement
max :: MediaKeysRequirement
-> MediaKeysRequirement -> MediaKeysRequirement
$cmax :: MediaKeysRequirement
-> MediaKeysRequirement -> MediaKeysRequirement
>= :: MediaKeysRequirement -> MediaKeysRequirement -> Bool
$c>= :: MediaKeysRequirement -> MediaKeysRequirement -> Bool
> :: MediaKeysRequirement -> MediaKeysRequirement -> Bool
$c> :: MediaKeysRequirement -> MediaKeysRequirement -> Bool
<= :: MediaKeysRequirement -> MediaKeysRequirement -> Bool
$c<= :: MediaKeysRequirement -> MediaKeysRequirement -> Bool
< :: MediaKeysRequirement -> MediaKeysRequirement -> Bool
$c< :: MediaKeysRequirement -> MediaKeysRequirement -> Bool
compare :: MediaKeysRequirement -> MediaKeysRequirement -> Ordering
$ccompare :: MediaKeysRequirement -> MediaKeysRequirement -> Ordering
$cp1Ord :: Eq MediaKeysRequirement
Ord, Typeable)
 
instance ToJSVal MediaKeysRequirement where
        toJSVal :: MediaKeysRequirement -> JSM JSVal
toJSVal MediaKeysRequirement
MediaKeysRequirementRequired
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_MediaKeysRequirementRequired
        toJSVal MediaKeysRequirement
MediaKeysRequirementOptional
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_MediaKeysRequirementOptional
        toJSVal MediaKeysRequirement
MediaKeysRequirementNotAllowed
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_MediaKeysRequirementNotAllowed
 
instance FromJSVal MediaKeysRequirement where
        fromJSVal :: JSVal -> JSM (Maybe MediaKeysRequirement)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_MediaKeysRequirementRequired JSM Bool
-> (Bool -> JSM (Maybe MediaKeysRequirement))
-> JSM (Maybe MediaKeysRequirement)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe MediaKeysRequirement -> JSM (Maybe MediaKeysRequirement)
forall (m :: * -> *) a. Monad m => a -> m a
return (MediaKeysRequirement -> Maybe MediaKeysRequirement
forall a. a -> Maybe a
Just MediaKeysRequirement
MediaKeysRequirementRequired)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_MediaKeysRequirementOptional JSM Bool
-> (Bool -> JSM (Maybe MediaKeysRequirement))
-> JSM (Maybe MediaKeysRequirement)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe MediaKeysRequirement -> JSM (Maybe MediaKeysRequirement)
forall (m :: * -> *) a. Monad m => a -> m a
return (MediaKeysRequirement -> Maybe MediaKeysRequirement
forall a. a -> Maybe a
Just MediaKeysRequirement
MediaKeysRequirementOptional)
                                 Bool
False
                                   -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_MediaKeysRequirementNotAllowed JSM Bool
-> (Bool -> JSM (Maybe MediaKeysRequirement))
-> JSM (Maybe MediaKeysRequirement)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                        \ Bool
r ->
                                          case Bool
r of
                                              Bool
True -> Maybe MediaKeysRequirement -> JSM (Maybe MediaKeysRequirement)
forall (m :: * -> *) a. Monad m => a -> m a
return (MediaKeysRequirement -> Maybe MediaKeysRequirement
forall a. a -> Maybe a
Just MediaKeysRequirement
MediaKeysRequirementNotAllowed)
                                              Bool
False -> Maybe MediaKeysRequirement -> JSM (Maybe MediaKeysRequirement)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe MediaKeysRequirement
forall a. Maybe a
Nothing
js_MediaKeysRequirementRequired :: String
js_MediaKeysRequirementRequired = String
"required"
js_MediaKeysRequirementOptional :: String
js_MediaKeysRequirementOptional = String
"optional"
js_MediaKeysRequirementNotAllowed :: String
js_MediaKeysRequirementNotAllowed = String
"not-allowed"
 
data MediaKeyStatus = MediaKeyStatusUsable
                    | MediaKeyStatusExpired
                    | MediaKeyStatusReleased
                    | MediaKeyStatusOutputRestricted
                    | MediaKeyStatusOutputDownscaled
                    | MediaKeyStatusStatusPending
                    | MediaKeyStatusInternalError
                    deriving (Int -> MediaKeyStatus -> ShowS
[MediaKeyStatus] -> ShowS
MediaKeyStatus -> String
(Int -> MediaKeyStatus -> ShowS)
-> (MediaKeyStatus -> String)
-> ([MediaKeyStatus] -> ShowS)
-> Show MediaKeyStatus
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MediaKeyStatus] -> ShowS
$cshowList :: [MediaKeyStatus] -> ShowS
show :: MediaKeyStatus -> String
$cshow :: MediaKeyStatus -> String
showsPrec :: Int -> MediaKeyStatus -> ShowS
$cshowsPrec :: Int -> MediaKeyStatus -> ShowS
Show, ReadPrec [MediaKeyStatus]
ReadPrec MediaKeyStatus
Int -> ReadS MediaKeyStatus
ReadS [MediaKeyStatus]
(Int -> ReadS MediaKeyStatus)
-> ReadS [MediaKeyStatus]
-> ReadPrec MediaKeyStatus
-> ReadPrec [MediaKeyStatus]
-> Read MediaKeyStatus
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [MediaKeyStatus]
$creadListPrec :: ReadPrec [MediaKeyStatus]
readPrec :: ReadPrec MediaKeyStatus
$creadPrec :: ReadPrec MediaKeyStatus
readList :: ReadS [MediaKeyStatus]
$creadList :: ReadS [MediaKeyStatus]
readsPrec :: Int -> ReadS MediaKeyStatus
$creadsPrec :: Int -> ReadS MediaKeyStatus
Read, MediaKeyStatus -> MediaKeyStatus -> Bool
(MediaKeyStatus -> MediaKeyStatus -> Bool)
-> (MediaKeyStatus -> MediaKeyStatus -> Bool) -> Eq MediaKeyStatus
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MediaKeyStatus -> MediaKeyStatus -> Bool
$c/= :: MediaKeyStatus -> MediaKeyStatus -> Bool
== :: MediaKeyStatus -> MediaKeyStatus -> Bool
$c== :: MediaKeyStatus -> MediaKeyStatus -> Bool
Eq, Eq MediaKeyStatus
Eq MediaKeyStatus
-> (MediaKeyStatus -> MediaKeyStatus -> Ordering)
-> (MediaKeyStatus -> MediaKeyStatus -> Bool)
-> (MediaKeyStatus -> MediaKeyStatus -> Bool)
-> (MediaKeyStatus -> MediaKeyStatus -> Bool)
-> (MediaKeyStatus -> MediaKeyStatus -> Bool)
-> (MediaKeyStatus -> MediaKeyStatus -> MediaKeyStatus)
-> (MediaKeyStatus -> MediaKeyStatus -> MediaKeyStatus)
-> Ord MediaKeyStatus
MediaKeyStatus -> MediaKeyStatus -> Bool
MediaKeyStatus -> MediaKeyStatus -> Ordering
MediaKeyStatus -> MediaKeyStatus -> MediaKeyStatus
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: MediaKeyStatus -> MediaKeyStatus -> MediaKeyStatus
$cmin :: MediaKeyStatus -> MediaKeyStatus -> MediaKeyStatus
max :: MediaKeyStatus -> MediaKeyStatus -> MediaKeyStatus
$cmax :: MediaKeyStatus -> MediaKeyStatus -> MediaKeyStatus
>= :: MediaKeyStatus -> MediaKeyStatus -> Bool
$c>= :: MediaKeyStatus -> MediaKeyStatus -> Bool
> :: MediaKeyStatus -> MediaKeyStatus -> Bool
$c> :: MediaKeyStatus -> MediaKeyStatus -> Bool
<= :: MediaKeyStatus -> MediaKeyStatus -> Bool
$c<= :: MediaKeyStatus -> MediaKeyStatus -> Bool
< :: MediaKeyStatus -> MediaKeyStatus -> Bool
$c< :: MediaKeyStatus -> MediaKeyStatus -> Bool
compare :: MediaKeyStatus -> MediaKeyStatus -> Ordering
$ccompare :: MediaKeyStatus -> MediaKeyStatus -> Ordering
$cp1Ord :: Eq MediaKeyStatus
Ord, Typeable)
 
instance ToJSVal MediaKeyStatus where
        toJSVal :: MediaKeyStatus -> JSM JSVal
toJSVal MediaKeyStatus
MediaKeyStatusUsable = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_MediaKeyStatusUsable
        toJSVal MediaKeyStatus
MediaKeyStatusExpired = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_MediaKeyStatusExpired
        toJSVal MediaKeyStatus
MediaKeyStatusReleased = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_MediaKeyStatusReleased
        toJSVal MediaKeyStatus
MediaKeyStatusOutputRestricted
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_MediaKeyStatusOutputRestricted
        toJSVal MediaKeyStatus
MediaKeyStatusOutputDownscaled
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_MediaKeyStatusOutputDownscaled
        toJSVal MediaKeyStatus
MediaKeyStatusStatusPending
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_MediaKeyStatusStatusPending
        toJSVal MediaKeyStatus
MediaKeyStatusInternalError
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_MediaKeyStatusInternalError
 
instance FromJSVal MediaKeyStatus where
        fromJSVal :: JSVal -> JSM (Maybe MediaKeyStatus)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_MediaKeyStatusUsable JSM Bool
-> (Bool -> JSM (Maybe MediaKeyStatus))
-> JSM (Maybe MediaKeyStatus)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe MediaKeyStatus -> JSM (Maybe MediaKeyStatus)
forall (m :: * -> *) a. Monad m => a -> m a
return (MediaKeyStatus -> Maybe MediaKeyStatus
forall a. a -> Maybe a
Just MediaKeyStatus
MediaKeyStatusUsable)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_MediaKeyStatusExpired JSM Bool
-> (Bool -> JSM (Maybe MediaKeyStatus))
-> JSM (Maybe MediaKeyStatus)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe MediaKeyStatus -> JSM (Maybe MediaKeyStatus)
forall (m :: * -> *) a. Monad m => a -> m a
return (MediaKeyStatus -> Maybe MediaKeyStatus
forall a. a -> Maybe a
Just MediaKeyStatus
MediaKeyStatusExpired)
                                 Bool
False
                                   -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_MediaKeyStatusReleased JSM Bool
-> (Bool -> JSM (Maybe MediaKeyStatus))
-> JSM (Maybe MediaKeyStatus)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                        \ Bool
r ->
                                          case Bool
r of
                                              Bool
True -> Maybe MediaKeyStatus -> JSM (Maybe MediaKeyStatus)
forall (m :: * -> *) a. Monad m => a -> m a
return (MediaKeyStatus -> Maybe MediaKeyStatus
forall a. a -> Maybe a
Just MediaKeyStatus
MediaKeyStatusReleased)
                                              Bool
False
                                                -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_MediaKeyStatusOutputRestricted
                                                     JSM Bool
-> (Bool -> JSM (Maybe MediaKeyStatus))
-> JSM (Maybe MediaKeyStatus)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                     \ Bool
r ->
                                                       case Bool
r of
                                                           Bool
True
                                                             -> Maybe MediaKeyStatus -> JSM (Maybe MediaKeyStatus)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                  (MediaKeyStatus -> Maybe MediaKeyStatus
forall a. a -> Maybe a
Just
                                                                     MediaKeyStatus
MediaKeyStatusOutputRestricted)
                                                           Bool
False
                                                             -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                                  String
js_MediaKeyStatusOutputDownscaled
                                                                  JSM Bool
-> (Bool -> JSM (Maybe MediaKeyStatus))
-> JSM (Maybe MediaKeyStatus)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                  \ Bool
r ->
                                                                    case Bool
r of
                                                                        Bool
True
                                                                          -> Maybe MediaKeyStatus -> JSM (Maybe MediaKeyStatus)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                               (MediaKeyStatus -> Maybe MediaKeyStatus
forall a. a -> Maybe a
Just
                                                                                  MediaKeyStatus
MediaKeyStatusOutputDownscaled)
                                                                        Bool
False
                                                                          -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                                               String
js_MediaKeyStatusStatusPending
                                                                               JSM Bool
-> (Bool -> JSM (Maybe MediaKeyStatus))
-> JSM (Maybe MediaKeyStatus)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                               \ Bool
r ->
                                                                                 case Bool
r of
                                                                                     Bool
True
                                                                                       -> Maybe MediaKeyStatus -> JSM (Maybe MediaKeyStatus)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                                            (MediaKeyStatus -> Maybe MediaKeyStatus
forall a. a -> Maybe a
Just
                                                                                               MediaKeyStatus
MediaKeyStatusStatusPending)
                                                                                     Bool
False
                                                                                       -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                                                            String
js_MediaKeyStatusInternalError
                                                                                            JSM Bool
-> (Bool -> JSM (Maybe MediaKeyStatus))
-> JSM (Maybe MediaKeyStatus)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                                            \ Bool
r ->
                                                                                              case Bool
r
                                                                                                of
                                                                                                  Bool
True
                                                                                                    -> Maybe MediaKeyStatus -> JSM (Maybe MediaKeyStatus)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                                                         (MediaKeyStatus -> Maybe MediaKeyStatus
forall a. a -> Maybe a
Just
                                                                                                            MediaKeyStatus
MediaKeyStatusInternalError)
                                                                                                  Bool
False
                                                                                                    -> Maybe MediaKeyStatus -> JSM (Maybe MediaKeyStatus)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                                                         Maybe MediaKeyStatus
forall a. Maybe a
Nothing
js_MediaKeyStatusUsable :: String
js_MediaKeyStatusUsable = String
"usable"
js_MediaKeyStatusExpired :: String
js_MediaKeyStatusExpired = String
"expired"
js_MediaKeyStatusReleased :: String
js_MediaKeyStatusReleased = String
"released"
js_MediaKeyStatusOutputRestricted :: String
js_MediaKeyStatusOutputRestricted = String
"output-restricted"
js_MediaKeyStatusOutputDownscaled :: String
js_MediaKeyStatusOutputDownscaled = String
"output-downscaled"
js_MediaKeyStatusStatusPending :: String
js_MediaKeyStatusStatusPending = String
"status-pending"
js_MediaKeyStatusInternalError :: String
js_MediaKeyStatusInternalError = String
"internal-error"
 
data RequestType = RequestType
                 | RequestTypeAudio
                 | RequestTypeFont
                 | RequestTypeImage
                 | RequestTypeScript
                 | RequestTypeStyle
                 | RequestTypeTrack
                 | RequestTypeVideo
                 deriving (Int -> RequestType -> ShowS
[RequestType] -> ShowS
RequestType -> String
(Int -> RequestType -> ShowS)
-> (RequestType -> String)
-> ([RequestType] -> ShowS)
-> Show RequestType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RequestType] -> ShowS
$cshowList :: [RequestType] -> ShowS
show :: RequestType -> String
$cshow :: RequestType -> String
showsPrec :: Int -> RequestType -> ShowS
$cshowsPrec :: Int -> RequestType -> ShowS
Show, ReadPrec [RequestType]
ReadPrec RequestType
Int -> ReadS RequestType
ReadS [RequestType]
(Int -> ReadS RequestType)
-> ReadS [RequestType]
-> ReadPrec RequestType
-> ReadPrec [RequestType]
-> Read RequestType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RequestType]
$creadListPrec :: ReadPrec [RequestType]
readPrec :: ReadPrec RequestType
$creadPrec :: ReadPrec RequestType
readList :: ReadS [RequestType]
$creadList :: ReadS [RequestType]
readsPrec :: Int -> ReadS RequestType
$creadsPrec :: Int -> ReadS RequestType
Read, RequestType -> RequestType -> Bool
(RequestType -> RequestType -> Bool)
-> (RequestType -> RequestType -> Bool) -> Eq RequestType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RequestType -> RequestType -> Bool
$c/= :: RequestType -> RequestType -> Bool
== :: RequestType -> RequestType -> Bool
$c== :: RequestType -> RequestType -> Bool
Eq, Eq RequestType
Eq RequestType
-> (RequestType -> RequestType -> Ordering)
-> (RequestType -> RequestType -> Bool)
-> (RequestType -> RequestType -> Bool)
-> (RequestType -> RequestType -> Bool)
-> (RequestType -> RequestType -> Bool)
-> (RequestType -> RequestType -> RequestType)
-> (RequestType -> RequestType -> RequestType)
-> Ord RequestType
RequestType -> RequestType -> Bool
RequestType -> RequestType -> Ordering
RequestType -> RequestType -> RequestType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: RequestType -> RequestType -> RequestType
$cmin :: RequestType -> RequestType -> RequestType
max :: RequestType -> RequestType -> RequestType
$cmax :: RequestType -> RequestType -> RequestType
>= :: RequestType -> RequestType -> Bool
$c>= :: RequestType -> RequestType -> Bool
> :: RequestType -> RequestType -> Bool
$c> :: RequestType -> RequestType -> Bool
<= :: RequestType -> RequestType -> Bool
$c<= :: RequestType -> RequestType -> Bool
< :: RequestType -> RequestType -> Bool
$c< :: RequestType -> RequestType -> Bool
compare :: RequestType -> RequestType -> Ordering
$ccompare :: RequestType -> RequestType -> Ordering
$cp1Ord :: Eq RequestType
Ord, Typeable)
 
instance ToJSVal RequestType where
        toJSVal :: RequestType -> JSM JSVal
toJSVal RequestType
RequestType = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RequestType
        toJSVal RequestType
RequestTypeAudio = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RequestTypeAudio
        toJSVal RequestType
RequestTypeFont = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RequestTypeFont
        toJSVal RequestType
RequestTypeImage = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RequestTypeImage
        toJSVal RequestType
RequestTypeScript = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RequestTypeScript
        toJSVal RequestType
RequestTypeStyle = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RequestTypeStyle
        toJSVal RequestType
RequestTypeTrack = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RequestTypeTrack
        toJSVal RequestType
RequestTypeVideo = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RequestTypeVideo
 
instance FromJSVal RequestType where
        fromJSVal :: JSVal -> JSM (Maybe RequestType)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_RequestType JSM Bool
-> (Bool -> JSM (Maybe RequestType)) -> JSM (Maybe RequestType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe RequestType -> JSM (Maybe RequestType)
forall (m :: * -> *) a. Monad m => a -> m a
return (RequestType -> Maybe RequestType
forall a. a -> Maybe a
Just RequestType
RequestType)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_RequestTypeAudio JSM Bool
-> (Bool -> JSM (Maybe RequestType)) -> JSM (Maybe RequestType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe RequestType -> JSM (Maybe RequestType)
forall (m :: * -> *) a. Monad m => a -> m a
return (RequestType -> Maybe RequestType
forall a. a -> Maybe a
Just RequestType
RequestTypeAudio)
                                 Bool
False
                                   -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_RequestTypeFont JSM Bool
-> (Bool -> JSM (Maybe RequestType)) -> JSM (Maybe RequestType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                        \ Bool
r ->
                                          case Bool
r of
                                              Bool
True -> Maybe RequestType -> JSM (Maybe RequestType)
forall (m :: * -> *) a. Monad m => a -> m a
return (RequestType -> Maybe RequestType
forall a. a -> Maybe a
Just RequestType
RequestTypeFont)
                                              Bool
False
                                                -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_RequestTypeImage JSM Bool
-> (Bool -> JSM (Maybe RequestType)) -> JSM (Maybe RequestType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                     \ Bool
r ->
                                                       case Bool
r of
                                                           Bool
True -> Maybe RequestType -> JSM (Maybe RequestType)
forall (m :: * -> *) a. Monad m => a -> m a
return (RequestType -> Maybe RequestType
forall a. a -> Maybe a
Just RequestType
RequestTypeImage)
                                                           Bool
False
                                                             -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_RequestTypeScript
                                                                  JSM Bool
-> (Bool -> JSM (Maybe RequestType)) -> JSM (Maybe RequestType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                  \ Bool
r ->
                                                                    case Bool
r of
                                                                        Bool
True
                                                                          -> Maybe RequestType -> JSM (Maybe RequestType)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                               (RequestType -> Maybe RequestType
forall a. a -> Maybe a
Just
                                                                                  RequestType
RequestTypeScript)
                                                                        Bool
False
                                                                          -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                                               String
js_RequestTypeStyle
                                                                               JSM Bool
-> (Bool -> JSM (Maybe RequestType)) -> JSM (Maybe RequestType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                               \ Bool
r ->
                                                                                 case Bool
r of
                                                                                     Bool
True
                                                                                       -> Maybe RequestType -> JSM (Maybe RequestType)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                                            (RequestType -> Maybe RequestType
forall a. a -> Maybe a
Just
                                                                                               RequestType
RequestTypeStyle)
                                                                                     Bool
False
                                                                                       -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                                                            String
js_RequestTypeTrack
                                                                                            JSM Bool
-> (Bool -> JSM (Maybe RequestType)) -> JSM (Maybe RequestType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                                            \ Bool
r ->
                                                                                              case Bool
r
                                                                                                of
                                                                                                  Bool
True
                                                                                                    -> Maybe RequestType -> JSM (Maybe RequestType)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                                                         (RequestType -> Maybe RequestType
forall a. a -> Maybe a
Just
                                                                                                            RequestType
RequestTypeTrack)
                                                                                                  Bool
False
                                                                                                    -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                                                                         String
js_RequestTypeVideo
                                                                                                         JSM Bool
-> (Bool -> JSM (Maybe RequestType)) -> JSM (Maybe RequestType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                                                         \ Bool
r
                                                                                                           ->
                                                                                                           case
                                                                                                             Bool
r
                                                                                                             of
                                                                                                               Bool
True
                                                                                                                 -> Maybe RequestType -> JSM (Maybe RequestType)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                                                                      (RequestType -> Maybe RequestType
forall a. a -> Maybe a
Just
                                                                                                                         RequestType
RequestTypeVideo)
                                                                                                               Bool
False
                                                                                                                 -> Maybe RequestType -> JSM (Maybe RequestType)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                                                                      Maybe RequestType
forall a. Maybe a
Nothing
js_RequestType :: String
js_RequestType = String
""
js_RequestTypeAudio :: String
js_RequestTypeAudio = String
"audio"
js_RequestTypeFont :: String
js_RequestTypeFont = String
"font"
js_RequestTypeImage :: String
js_RequestTypeImage = String
"image"
js_RequestTypeScript :: String
js_RequestTypeScript = String
"script"
js_RequestTypeStyle :: String
js_RequestTypeStyle = String
"style"
js_RequestTypeTrack :: String
js_RequestTypeTrack = String
"track"
js_RequestTypeVideo :: String
js_RequestTypeVideo = String
"video"
 
data RequestDestination = RequestDestination
                        | RequestDestinationDocument
                        | RequestDestinationSharedworker
                        | RequestDestinationSubresource
                        | RequestDestinationUnknown
                        | RequestDestinationWorker
                        deriving (Int -> RequestDestination -> ShowS
[RequestDestination] -> ShowS
RequestDestination -> String
(Int -> RequestDestination -> ShowS)
-> (RequestDestination -> String)
-> ([RequestDestination] -> ShowS)
-> Show RequestDestination
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RequestDestination] -> ShowS
$cshowList :: [RequestDestination] -> ShowS
show :: RequestDestination -> String
$cshow :: RequestDestination -> String
showsPrec :: Int -> RequestDestination -> ShowS
$cshowsPrec :: Int -> RequestDestination -> ShowS
Show, ReadPrec [RequestDestination]
ReadPrec RequestDestination
Int -> ReadS RequestDestination
ReadS [RequestDestination]
(Int -> ReadS RequestDestination)
-> ReadS [RequestDestination]
-> ReadPrec RequestDestination
-> ReadPrec [RequestDestination]
-> Read RequestDestination
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RequestDestination]
$creadListPrec :: ReadPrec [RequestDestination]
readPrec :: ReadPrec RequestDestination
$creadPrec :: ReadPrec RequestDestination
readList :: ReadS [RequestDestination]
$creadList :: ReadS [RequestDestination]
readsPrec :: Int -> ReadS RequestDestination
$creadsPrec :: Int -> ReadS RequestDestination
Read, RequestDestination -> RequestDestination -> Bool
(RequestDestination -> RequestDestination -> Bool)
-> (RequestDestination -> RequestDestination -> Bool)
-> Eq RequestDestination
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RequestDestination -> RequestDestination -> Bool
$c/= :: RequestDestination -> RequestDestination -> Bool
== :: RequestDestination -> RequestDestination -> Bool
$c== :: RequestDestination -> RequestDestination -> Bool
Eq, Eq RequestDestination
Eq RequestDestination
-> (RequestDestination -> RequestDestination -> Ordering)
-> (RequestDestination -> RequestDestination -> Bool)
-> (RequestDestination -> RequestDestination -> Bool)
-> (RequestDestination -> RequestDestination -> Bool)
-> (RequestDestination -> RequestDestination -> Bool)
-> (RequestDestination -> RequestDestination -> RequestDestination)
-> (RequestDestination -> RequestDestination -> RequestDestination)
-> Ord RequestDestination
RequestDestination -> RequestDestination -> Bool
RequestDestination -> RequestDestination -> Ordering
RequestDestination -> RequestDestination -> RequestDestination
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: RequestDestination -> RequestDestination -> RequestDestination
$cmin :: RequestDestination -> RequestDestination -> RequestDestination
max :: RequestDestination -> RequestDestination -> RequestDestination
$cmax :: RequestDestination -> RequestDestination -> RequestDestination
>= :: RequestDestination -> RequestDestination -> Bool
$c>= :: RequestDestination -> RequestDestination -> Bool
> :: RequestDestination -> RequestDestination -> Bool
$c> :: RequestDestination -> RequestDestination -> Bool
<= :: RequestDestination -> RequestDestination -> Bool
$c<= :: RequestDestination -> RequestDestination -> Bool
< :: RequestDestination -> RequestDestination -> Bool
$c< :: RequestDestination -> RequestDestination -> Bool
compare :: RequestDestination -> RequestDestination -> Ordering
$ccompare :: RequestDestination -> RequestDestination -> Ordering
$cp1Ord :: Eq RequestDestination
Ord, Typeable)
 
instance ToJSVal RequestDestination where
        toJSVal :: RequestDestination -> JSM JSVal
toJSVal RequestDestination
RequestDestination = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RequestDestination
        toJSVal RequestDestination
RequestDestinationDocument
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RequestDestinationDocument
        toJSVal RequestDestination
RequestDestinationSharedworker
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RequestDestinationSharedworker
        toJSVal RequestDestination
RequestDestinationSubresource
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RequestDestinationSubresource
        toJSVal RequestDestination
RequestDestinationUnknown
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RequestDestinationUnknown
        toJSVal RequestDestination
RequestDestinationWorker
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RequestDestinationWorker
 
instance FromJSVal RequestDestination where
        fromJSVal :: JSVal -> JSM (Maybe RequestDestination)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_RequestDestination JSM Bool
-> (Bool -> JSM (Maybe RequestDestination))
-> JSM (Maybe RequestDestination)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe RequestDestination -> JSM (Maybe RequestDestination)
forall (m :: * -> *) a. Monad m => a -> m a
return (RequestDestination -> Maybe RequestDestination
forall a. a -> Maybe a
Just RequestDestination
RequestDestination)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_RequestDestinationDocument JSM Bool
-> (Bool -> JSM (Maybe RequestDestination))
-> JSM (Maybe RequestDestination)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe RequestDestination -> JSM (Maybe RequestDestination)
forall (m :: * -> *) a. Monad m => a -> m a
return (RequestDestination -> Maybe RequestDestination
forall a. a -> Maybe a
Just RequestDestination
RequestDestinationDocument)
                                 Bool
False
                                   -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_RequestDestinationSharedworker JSM Bool
-> (Bool -> JSM (Maybe RequestDestination))
-> JSM (Maybe RequestDestination)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                        \ Bool
r ->
                                          case Bool
r of
                                              Bool
True -> Maybe RequestDestination -> JSM (Maybe RequestDestination)
forall (m :: * -> *) a. Monad m => a -> m a
return (RequestDestination -> Maybe RequestDestination
forall a. a -> Maybe a
Just RequestDestination
RequestDestinationSharedworker)
                                              Bool
False
                                                -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_RequestDestinationSubresource
                                                     JSM Bool
-> (Bool -> JSM (Maybe RequestDestination))
-> JSM (Maybe RequestDestination)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                     \ Bool
r ->
                                                       case Bool
r of
                                                           Bool
True
                                                             -> Maybe RequestDestination -> JSM (Maybe RequestDestination)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                  (RequestDestination -> Maybe RequestDestination
forall a. a -> Maybe a
Just
                                                                     RequestDestination
RequestDestinationSubresource)
                                                           Bool
False
                                                             -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                                  String
js_RequestDestinationUnknown
                                                                  JSM Bool
-> (Bool -> JSM (Maybe RequestDestination))
-> JSM (Maybe RequestDestination)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                  \ Bool
r ->
                                                                    case Bool
r of
                                                                        Bool
True
                                                                          -> Maybe RequestDestination -> JSM (Maybe RequestDestination)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                               (RequestDestination -> Maybe RequestDestination
forall a. a -> Maybe a
Just
                                                                                  RequestDestination
RequestDestinationUnknown)
                                                                        Bool
False
                                                                          -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                                               String
js_RequestDestinationWorker
                                                                               JSM Bool
-> (Bool -> JSM (Maybe RequestDestination))
-> JSM (Maybe RequestDestination)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                               \ Bool
r ->
                                                                                 case Bool
r of
                                                                                     Bool
True
                                                                                       -> Maybe RequestDestination -> JSM (Maybe RequestDestination)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                                            (RequestDestination -> Maybe RequestDestination
forall a. a -> Maybe a
Just
                                                                                               RequestDestination
RequestDestinationWorker)
                                                                                     Bool
False
                                                                                       -> Maybe RequestDestination -> JSM (Maybe RequestDestination)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                                            Maybe RequestDestination
forall a. Maybe a
Nothing
js_RequestDestination :: String
js_RequestDestination = String
""
js_RequestDestinationDocument :: String
js_RequestDestinationDocument = String
"document"
js_RequestDestinationSharedworker :: String
js_RequestDestinationSharedworker = String
"sharedworker"
js_RequestDestinationSubresource :: String
js_RequestDestinationSubresource = String
"subresource"
js_RequestDestinationUnknown :: String
js_RequestDestinationUnknown = String
"unknown"
js_RequestDestinationWorker :: String
js_RequestDestinationWorker = String
"worker"
 
data RequestMode = RequestModeNavigate
                 | RequestModeSameOrigin
                 | RequestModeNoCors
                 | RequestModeCors
                 deriving (Int -> RequestMode -> ShowS
[RequestMode] -> ShowS
RequestMode -> String
(Int -> RequestMode -> ShowS)
-> (RequestMode -> String)
-> ([RequestMode] -> ShowS)
-> Show RequestMode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RequestMode] -> ShowS
$cshowList :: [RequestMode] -> ShowS
show :: RequestMode -> String
$cshow :: RequestMode -> String
showsPrec :: Int -> RequestMode -> ShowS
$cshowsPrec :: Int -> RequestMode -> ShowS
Show, ReadPrec [RequestMode]
ReadPrec RequestMode
Int -> ReadS RequestMode
ReadS [RequestMode]
(Int -> ReadS RequestMode)
-> ReadS [RequestMode]
-> ReadPrec RequestMode
-> ReadPrec [RequestMode]
-> Read RequestMode
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RequestMode]
$creadListPrec :: ReadPrec [RequestMode]
readPrec :: ReadPrec RequestMode
$creadPrec :: ReadPrec RequestMode
readList :: ReadS [RequestMode]
$creadList :: ReadS [RequestMode]
readsPrec :: Int -> ReadS RequestMode
$creadsPrec :: Int -> ReadS RequestMode
Read, RequestMode -> RequestMode -> Bool
(RequestMode -> RequestMode -> Bool)
-> (RequestMode -> RequestMode -> Bool) -> Eq RequestMode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RequestMode -> RequestMode -> Bool
$c/= :: RequestMode -> RequestMode -> Bool
== :: RequestMode -> RequestMode -> Bool
$c== :: RequestMode -> RequestMode -> Bool
Eq, Eq RequestMode
Eq RequestMode
-> (RequestMode -> RequestMode -> Ordering)
-> (RequestMode -> RequestMode -> Bool)
-> (RequestMode -> RequestMode -> Bool)
-> (RequestMode -> RequestMode -> Bool)
-> (RequestMode -> RequestMode -> Bool)
-> (RequestMode -> RequestMode -> RequestMode)
-> (RequestMode -> RequestMode -> RequestMode)
-> Ord RequestMode
RequestMode -> RequestMode -> Bool
RequestMode -> RequestMode -> Ordering
RequestMode -> RequestMode -> RequestMode
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: RequestMode -> RequestMode -> RequestMode
$cmin :: RequestMode -> RequestMode -> RequestMode
max :: RequestMode -> RequestMode -> RequestMode
$cmax :: RequestMode -> RequestMode -> RequestMode
>= :: RequestMode -> RequestMode -> Bool
$c>= :: RequestMode -> RequestMode -> Bool
> :: RequestMode -> RequestMode -> Bool
$c> :: RequestMode -> RequestMode -> Bool
<= :: RequestMode -> RequestMode -> Bool
$c<= :: RequestMode -> RequestMode -> Bool
< :: RequestMode -> RequestMode -> Bool
$c< :: RequestMode -> RequestMode -> Bool
compare :: RequestMode -> RequestMode -> Ordering
$ccompare :: RequestMode -> RequestMode -> Ordering
$cp1Ord :: Eq RequestMode
Ord, Typeable)
 
instance ToJSVal RequestMode where
        toJSVal :: RequestMode -> JSM JSVal
toJSVal RequestMode
RequestModeNavigate = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RequestModeNavigate
        toJSVal RequestMode
RequestModeSameOrigin = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RequestModeSameOrigin
        toJSVal RequestMode
RequestModeNoCors = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RequestModeNoCors
        toJSVal RequestMode
RequestModeCors = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RequestModeCors
 
instance FromJSVal RequestMode where
        fromJSVal :: JSVal -> JSM (Maybe RequestMode)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_RequestModeNavigate JSM Bool
-> (Bool -> JSM (Maybe RequestMode)) -> JSM (Maybe RequestMode)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe RequestMode -> JSM (Maybe RequestMode)
forall (m :: * -> *) a. Monad m => a -> m a
return (RequestMode -> Maybe RequestMode
forall a. a -> Maybe a
Just RequestMode
RequestModeNavigate)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_RequestModeSameOrigin JSM Bool
-> (Bool -> JSM (Maybe RequestMode)) -> JSM (Maybe RequestMode)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe RequestMode -> JSM (Maybe RequestMode)
forall (m :: * -> *) a. Monad m => a -> m a
return (RequestMode -> Maybe RequestMode
forall a. a -> Maybe a
Just RequestMode
RequestModeSameOrigin)
                                 Bool
False
                                   -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_RequestModeNoCors JSM Bool
-> (Bool -> JSM (Maybe RequestMode)) -> JSM (Maybe RequestMode)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                        \ Bool
r ->
                                          case Bool
r of
                                              Bool
True -> Maybe RequestMode -> JSM (Maybe RequestMode)
forall (m :: * -> *) a. Monad m => a -> m a
return (RequestMode -> Maybe RequestMode
forall a. a -> Maybe a
Just RequestMode
RequestModeNoCors)
                                              Bool
False
                                                -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_RequestModeCors JSM Bool
-> (Bool -> JSM (Maybe RequestMode)) -> JSM (Maybe RequestMode)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                     \ Bool
r ->
                                                       case Bool
r of
                                                           Bool
True -> Maybe RequestMode -> JSM (Maybe RequestMode)
forall (m :: * -> *) a. Monad m => a -> m a
return (RequestMode -> Maybe RequestMode
forall a. a -> Maybe a
Just RequestMode
RequestModeCors)
                                                           Bool
False -> Maybe RequestMode -> JSM (Maybe RequestMode)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe RequestMode
forall a. Maybe a
Nothing
js_RequestModeNavigate :: String
js_RequestModeNavigate = String
"navigate"
js_RequestModeSameOrigin :: String
js_RequestModeSameOrigin = String
"same-origin"
js_RequestModeNoCors :: String
js_RequestModeNoCors = String
"no-cors"
js_RequestModeCors :: String
js_RequestModeCors = String
"cors"
 
data RequestCredentials = RequestCredentialsOmit
                        | RequestCredentialsSameOrigin
                        | RequestCredentialsInclude
                        deriving (Int -> RequestCredentials -> ShowS
[RequestCredentials] -> ShowS
RequestCredentials -> String
(Int -> RequestCredentials -> ShowS)
-> (RequestCredentials -> String)
-> ([RequestCredentials] -> ShowS)
-> Show RequestCredentials
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RequestCredentials] -> ShowS
$cshowList :: [RequestCredentials] -> ShowS
show :: RequestCredentials -> String
$cshow :: RequestCredentials -> String
showsPrec :: Int -> RequestCredentials -> ShowS
$cshowsPrec :: Int -> RequestCredentials -> ShowS
Show, ReadPrec [RequestCredentials]
ReadPrec RequestCredentials
Int -> ReadS RequestCredentials
ReadS [RequestCredentials]
(Int -> ReadS RequestCredentials)
-> ReadS [RequestCredentials]
-> ReadPrec RequestCredentials
-> ReadPrec [RequestCredentials]
-> Read RequestCredentials
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RequestCredentials]
$creadListPrec :: ReadPrec [RequestCredentials]
readPrec :: ReadPrec RequestCredentials
$creadPrec :: ReadPrec RequestCredentials
readList :: ReadS [RequestCredentials]
$creadList :: ReadS [RequestCredentials]
readsPrec :: Int -> ReadS RequestCredentials
$creadsPrec :: Int -> ReadS RequestCredentials
Read, RequestCredentials -> RequestCredentials -> Bool
(RequestCredentials -> RequestCredentials -> Bool)
-> (RequestCredentials -> RequestCredentials -> Bool)
-> Eq RequestCredentials
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RequestCredentials -> RequestCredentials -> Bool
$c/= :: RequestCredentials -> RequestCredentials -> Bool
== :: RequestCredentials -> RequestCredentials -> Bool
$c== :: RequestCredentials -> RequestCredentials -> Bool
Eq, Eq RequestCredentials
Eq RequestCredentials
-> (RequestCredentials -> RequestCredentials -> Ordering)
-> (RequestCredentials -> RequestCredentials -> Bool)
-> (RequestCredentials -> RequestCredentials -> Bool)
-> (RequestCredentials -> RequestCredentials -> Bool)
-> (RequestCredentials -> RequestCredentials -> Bool)
-> (RequestCredentials -> RequestCredentials -> RequestCredentials)
-> (RequestCredentials -> RequestCredentials -> RequestCredentials)
-> Ord RequestCredentials
RequestCredentials -> RequestCredentials -> Bool
RequestCredentials -> RequestCredentials -> Ordering
RequestCredentials -> RequestCredentials -> RequestCredentials
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: RequestCredentials -> RequestCredentials -> RequestCredentials
$cmin :: RequestCredentials -> RequestCredentials -> RequestCredentials
max :: RequestCredentials -> RequestCredentials -> RequestCredentials
$cmax :: RequestCredentials -> RequestCredentials -> RequestCredentials
>= :: RequestCredentials -> RequestCredentials -> Bool
$c>= :: RequestCredentials -> RequestCredentials -> Bool
> :: RequestCredentials -> RequestCredentials -> Bool
$c> :: RequestCredentials -> RequestCredentials -> Bool
<= :: RequestCredentials -> RequestCredentials -> Bool
$c<= :: RequestCredentials -> RequestCredentials -> Bool
< :: RequestCredentials -> RequestCredentials -> Bool
$c< :: RequestCredentials -> RequestCredentials -> Bool
compare :: RequestCredentials -> RequestCredentials -> Ordering
$ccompare :: RequestCredentials -> RequestCredentials -> Ordering
$cp1Ord :: Eq RequestCredentials
Ord, Typeable)
 
instance ToJSVal RequestCredentials where
        toJSVal :: RequestCredentials -> JSM JSVal
toJSVal RequestCredentials
RequestCredentialsOmit = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RequestCredentialsOmit
        toJSVal RequestCredentials
RequestCredentialsSameOrigin
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RequestCredentialsSameOrigin
        toJSVal RequestCredentials
RequestCredentialsInclude
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RequestCredentialsInclude
 
instance FromJSVal RequestCredentials where
        fromJSVal :: JSVal -> JSM (Maybe RequestCredentials)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_RequestCredentialsOmit JSM Bool
-> (Bool -> JSM (Maybe RequestCredentials))
-> JSM (Maybe RequestCredentials)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe RequestCredentials -> JSM (Maybe RequestCredentials)
forall (m :: * -> *) a. Monad m => a -> m a
return (RequestCredentials -> Maybe RequestCredentials
forall a. a -> Maybe a
Just RequestCredentials
RequestCredentialsOmit)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_RequestCredentialsSameOrigin JSM Bool
-> (Bool -> JSM (Maybe RequestCredentials))
-> JSM (Maybe RequestCredentials)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe RequestCredentials -> JSM (Maybe RequestCredentials)
forall (m :: * -> *) a. Monad m => a -> m a
return (RequestCredentials -> Maybe RequestCredentials
forall a. a -> Maybe a
Just RequestCredentials
RequestCredentialsSameOrigin)
                                 Bool
False
                                   -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_RequestCredentialsInclude JSM Bool
-> (Bool -> JSM (Maybe RequestCredentials))
-> JSM (Maybe RequestCredentials)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                        \ Bool
r ->
                                          case Bool
r of
                                              Bool
True -> Maybe RequestCredentials -> JSM (Maybe RequestCredentials)
forall (m :: * -> *) a. Monad m => a -> m a
return (RequestCredentials -> Maybe RequestCredentials
forall a. a -> Maybe a
Just RequestCredentials
RequestCredentialsInclude)
                                              Bool
False -> Maybe RequestCredentials -> JSM (Maybe RequestCredentials)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe RequestCredentials
forall a. Maybe a
Nothing
js_RequestCredentialsOmit :: String
js_RequestCredentialsOmit = String
"omit"
js_RequestCredentialsSameOrigin :: String
js_RequestCredentialsSameOrigin = String
"same-origin"
js_RequestCredentialsInclude :: String
js_RequestCredentialsInclude = String
"include"
 
data RequestCache = RequestCacheDefault
                  | RequestCacheNoStore
                  | RequestCacheReload
                  | RequestCacheNoCache
                  | RequestCacheForceCache
                  | RequestCacheOnlyIfCached
                  deriving (Int -> RequestCache -> ShowS
[RequestCache] -> ShowS
RequestCache -> String
(Int -> RequestCache -> ShowS)
-> (RequestCache -> String)
-> ([RequestCache] -> ShowS)
-> Show RequestCache
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RequestCache] -> ShowS
$cshowList :: [RequestCache] -> ShowS
show :: RequestCache -> String
$cshow :: RequestCache -> String
showsPrec :: Int -> RequestCache -> ShowS
$cshowsPrec :: Int -> RequestCache -> ShowS
Show, ReadPrec [RequestCache]
ReadPrec RequestCache
Int -> ReadS RequestCache
ReadS [RequestCache]
(Int -> ReadS RequestCache)
-> ReadS [RequestCache]
-> ReadPrec RequestCache
-> ReadPrec [RequestCache]
-> Read RequestCache
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RequestCache]
$creadListPrec :: ReadPrec [RequestCache]
readPrec :: ReadPrec RequestCache
$creadPrec :: ReadPrec RequestCache
readList :: ReadS [RequestCache]
$creadList :: ReadS [RequestCache]
readsPrec :: Int -> ReadS RequestCache
$creadsPrec :: Int -> ReadS RequestCache
Read, RequestCache -> RequestCache -> Bool
(RequestCache -> RequestCache -> Bool)
-> (RequestCache -> RequestCache -> Bool) -> Eq RequestCache
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RequestCache -> RequestCache -> Bool
$c/= :: RequestCache -> RequestCache -> Bool
== :: RequestCache -> RequestCache -> Bool
$c== :: RequestCache -> RequestCache -> Bool
Eq, Eq RequestCache
Eq RequestCache
-> (RequestCache -> RequestCache -> Ordering)
-> (RequestCache -> RequestCache -> Bool)
-> (RequestCache -> RequestCache -> Bool)
-> (RequestCache -> RequestCache -> Bool)
-> (RequestCache -> RequestCache -> Bool)
-> (RequestCache -> RequestCache -> RequestCache)
-> (RequestCache -> RequestCache -> RequestCache)
-> Ord RequestCache
RequestCache -> RequestCache -> Bool
RequestCache -> RequestCache -> Ordering
RequestCache -> RequestCache -> RequestCache
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: RequestCache -> RequestCache -> RequestCache
$cmin :: RequestCache -> RequestCache -> RequestCache
max :: RequestCache -> RequestCache -> RequestCache
$cmax :: RequestCache -> RequestCache -> RequestCache
>= :: RequestCache -> RequestCache -> Bool
$c>= :: RequestCache -> RequestCache -> Bool
> :: RequestCache -> RequestCache -> Bool
$c> :: RequestCache -> RequestCache -> Bool
<= :: RequestCache -> RequestCache -> Bool
$c<= :: RequestCache -> RequestCache -> Bool
< :: RequestCache -> RequestCache -> Bool
$c< :: RequestCache -> RequestCache -> Bool
compare :: RequestCache -> RequestCache -> Ordering
$ccompare :: RequestCache -> RequestCache -> Ordering
$cp1Ord :: Eq RequestCache
Ord, Typeable)
 
instance ToJSVal RequestCache where
        toJSVal :: RequestCache -> JSM JSVal
toJSVal RequestCache
RequestCacheDefault = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RequestCacheDefault
        toJSVal RequestCache
RequestCacheNoStore = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RequestCacheNoStore
        toJSVal RequestCache
RequestCacheReload = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RequestCacheReload
        toJSVal RequestCache
RequestCacheNoCache = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RequestCacheNoCache
        toJSVal RequestCache
RequestCacheForceCache = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RequestCacheForceCache
        toJSVal RequestCache
RequestCacheOnlyIfCached
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RequestCacheOnlyIfCached
 
instance FromJSVal RequestCache where
        fromJSVal :: JSVal -> JSM (Maybe RequestCache)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_RequestCacheDefault JSM Bool
-> (Bool -> JSM (Maybe RequestCache)) -> JSM (Maybe RequestCache)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe RequestCache -> JSM (Maybe RequestCache)
forall (m :: * -> *) a. Monad m => a -> m a
return (RequestCache -> Maybe RequestCache
forall a. a -> Maybe a
Just RequestCache
RequestCacheDefault)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_RequestCacheNoStore JSM Bool
-> (Bool -> JSM (Maybe RequestCache)) -> JSM (Maybe RequestCache)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe RequestCache -> JSM (Maybe RequestCache)
forall (m :: * -> *) a. Monad m => a -> m a
return (RequestCache -> Maybe RequestCache
forall a. a -> Maybe a
Just RequestCache
RequestCacheNoStore)
                                 Bool
False
                                   -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_RequestCacheReload JSM Bool
-> (Bool -> JSM (Maybe RequestCache)) -> JSM (Maybe RequestCache)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                        \ Bool
r ->
                                          case Bool
r of
                                              Bool
True -> Maybe RequestCache -> JSM (Maybe RequestCache)
forall (m :: * -> *) a. Monad m => a -> m a
return (RequestCache -> Maybe RequestCache
forall a. a -> Maybe a
Just RequestCache
RequestCacheReload)
                                              Bool
False
                                                -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_RequestCacheNoCache JSM Bool
-> (Bool -> JSM (Maybe RequestCache)) -> JSM (Maybe RequestCache)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                     \ Bool
r ->
                                                       case Bool
r of
                                                           Bool
True -> Maybe RequestCache -> JSM (Maybe RequestCache)
forall (m :: * -> *) a. Monad m => a -> m a
return (RequestCache -> Maybe RequestCache
forall a. a -> Maybe a
Just RequestCache
RequestCacheNoCache)
                                                           Bool
False
                                                             -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                                  String
js_RequestCacheForceCache
                                                                  JSM Bool
-> (Bool -> JSM (Maybe RequestCache)) -> JSM (Maybe RequestCache)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                  \ Bool
r ->
                                                                    case Bool
r of
                                                                        Bool
True
                                                                          -> Maybe RequestCache -> JSM (Maybe RequestCache)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                               (RequestCache -> Maybe RequestCache
forall a. a -> Maybe a
Just
                                                                                  RequestCache
RequestCacheForceCache)
                                                                        Bool
False
                                                                          -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                                               String
js_RequestCacheOnlyIfCached
                                                                               JSM Bool
-> (Bool -> JSM (Maybe RequestCache)) -> JSM (Maybe RequestCache)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                               \ Bool
r ->
                                                                                 case Bool
r of
                                                                                     Bool
True
                                                                                       -> Maybe RequestCache -> JSM (Maybe RequestCache)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                                            (RequestCache -> Maybe RequestCache
forall a. a -> Maybe a
Just
                                                                                               RequestCache
RequestCacheOnlyIfCached)
                                                                                     Bool
False
                                                                                       -> Maybe RequestCache -> JSM (Maybe RequestCache)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                                            Maybe RequestCache
forall a. Maybe a
Nothing
js_RequestCacheDefault :: String
js_RequestCacheDefault = String
"default"
js_RequestCacheNoStore :: String
js_RequestCacheNoStore = String
"no-store"
js_RequestCacheReload :: String
js_RequestCacheReload = String
"reload"
js_RequestCacheNoCache :: String
js_RequestCacheNoCache = String
"no-cache"
js_RequestCacheForceCache :: String
js_RequestCacheForceCache = String
"force-cache"
js_RequestCacheOnlyIfCached :: String
js_RequestCacheOnlyIfCached = String
"only-if-cached"
 
data RequestRedirect = RequestRedirectFollow
                     | RequestRedirectError
                     | RequestRedirectManual
                     deriving (Int -> RequestRedirect -> ShowS
[RequestRedirect] -> ShowS
RequestRedirect -> String
(Int -> RequestRedirect -> ShowS)
-> (RequestRedirect -> String)
-> ([RequestRedirect] -> ShowS)
-> Show RequestRedirect
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RequestRedirect] -> ShowS
$cshowList :: [RequestRedirect] -> ShowS
show :: RequestRedirect -> String
$cshow :: RequestRedirect -> String
showsPrec :: Int -> RequestRedirect -> ShowS
$cshowsPrec :: Int -> RequestRedirect -> ShowS
Show, ReadPrec [RequestRedirect]
ReadPrec RequestRedirect
Int -> ReadS RequestRedirect
ReadS [RequestRedirect]
(Int -> ReadS RequestRedirect)
-> ReadS [RequestRedirect]
-> ReadPrec RequestRedirect
-> ReadPrec [RequestRedirect]
-> Read RequestRedirect
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RequestRedirect]
$creadListPrec :: ReadPrec [RequestRedirect]
readPrec :: ReadPrec RequestRedirect
$creadPrec :: ReadPrec RequestRedirect
readList :: ReadS [RequestRedirect]
$creadList :: ReadS [RequestRedirect]
readsPrec :: Int -> ReadS RequestRedirect
$creadsPrec :: Int -> ReadS RequestRedirect
Read, RequestRedirect -> RequestRedirect -> Bool
(RequestRedirect -> RequestRedirect -> Bool)
-> (RequestRedirect -> RequestRedirect -> Bool)
-> Eq RequestRedirect
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RequestRedirect -> RequestRedirect -> Bool
$c/= :: RequestRedirect -> RequestRedirect -> Bool
== :: RequestRedirect -> RequestRedirect -> Bool
$c== :: RequestRedirect -> RequestRedirect -> Bool
Eq, Eq RequestRedirect
Eq RequestRedirect
-> (RequestRedirect -> RequestRedirect -> Ordering)
-> (RequestRedirect -> RequestRedirect -> Bool)
-> (RequestRedirect -> RequestRedirect -> Bool)
-> (RequestRedirect -> RequestRedirect -> Bool)
-> (RequestRedirect -> RequestRedirect -> Bool)
-> (RequestRedirect -> RequestRedirect -> RequestRedirect)
-> (RequestRedirect -> RequestRedirect -> RequestRedirect)
-> Ord RequestRedirect
RequestRedirect -> RequestRedirect -> Bool
RequestRedirect -> RequestRedirect -> Ordering
RequestRedirect -> RequestRedirect -> RequestRedirect
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: RequestRedirect -> RequestRedirect -> RequestRedirect
$cmin :: RequestRedirect -> RequestRedirect -> RequestRedirect
max :: RequestRedirect -> RequestRedirect -> RequestRedirect
$cmax :: RequestRedirect -> RequestRedirect -> RequestRedirect
>= :: RequestRedirect -> RequestRedirect -> Bool
$c>= :: RequestRedirect -> RequestRedirect -> Bool
> :: RequestRedirect -> RequestRedirect -> Bool
$c> :: RequestRedirect -> RequestRedirect -> Bool
<= :: RequestRedirect -> RequestRedirect -> Bool
$c<= :: RequestRedirect -> RequestRedirect -> Bool
< :: RequestRedirect -> RequestRedirect -> Bool
$c< :: RequestRedirect -> RequestRedirect -> Bool
compare :: RequestRedirect -> RequestRedirect -> Ordering
$ccompare :: RequestRedirect -> RequestRedirect -> Ordering
$cp1Ord :: Eq RequestRedirect
Ord, Typeable)
 
instance ToJSVal RequestRedirect where
        toJSVal :: RequestRedirect -> JSM JSVal
toJSVal RequestRedirect
RequestRedirectFollow = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RequestRedirectFollow
        toJSVal RequestRedirect
RequestRedirectError = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RequestRedirectError
        toJSVal RequestRedirect
RequestRedirectManual = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RequestRedirectManual
 
instance FromJSVal RequestRedirect where
        fromJSVal :: JSVal -> JSM (Maybe RequestRedirect)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_RequestRedirectFollow JSM Bool
-> (Bool -> JSM (Maybe RequestRedirect))
-> JSM (Maybe RequestRedirect)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe RequestRedirect -> JSM (Maybe RequestRedirect)
forall (m :: * -> *) a. Monad m => a -> m a
return (RequestRedirect -> Maybe RequestRedirect
forall a. a -> Maybe a
Just RequestRedirect
RequestRedirectFollow)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_RequestRedirectError JSM Bool
-> (Bool -> JSM (Maybe RequestRedirect))
-> JSM (Maybe RequestRedirect)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe RequestRedirect -> JSM (Maybe RequestRedirect)
forall (m :: * -> *) a. Monad m => a -> m a
return (RequestRedirect -> Maybe RequestRedirect
forall a. a -> Maybe a
Just RequestRedirect
RequestRedirectError)
                                 Bool
False
                                   -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_RequestRedirectManual JSM Bool
-> (Bool -> JSM (Maybe RequestRedirect))
-> JSM (Maybe RequestRedirect)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                        \ Bool
r ->
                                          case Bool
r of
                                              Bool
True -> Maybe RequestRedirect -> JSM (Maybe RequestRedirect)
forall (m :: * -> *) a. Monad m => a -> m a
return (RequestRedirect -> Maybe RequestRedirect
forall a. a -> Maybe a
Just RequestRedirect
RequestRedirectManual)
                                              Bool
False -> Maybe RequestRedirect -> JSM (Maybe RequestRedirect)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe RequestRedirect
forall a. Maybe a
Nothing
js_RequestRedirectFollow :: String
js_RequestRedirectFollow = String
"follow"
js_RequestRedirectError :: String
js_RequestRedirectError = String
"error"
js_RequestRedirectManual :: String
js_RequestRedirectManual = String
"manual"
 
data ReferrerPolicy = ReferrerPolicy
                    | ReferrerPolicyNoReferrer
                    | ReferrerPolicyNoReferrerWhenDowngrade
                    | ReferrerPolicyOrigin
                    | ReferrerPolicyOriginWhenCrossOrigin
                    | ReferrerPolicyUnsafeUrl
                    deriving (Int -> ReferrerPolicy -> ShowS
[ReferrerPolicy] -> ShowS
ReferrerPolicy -> String
(Int -> ReferrerPolicy -> ShowS)
-> (ReferrerPolicy -> String)
-> ([ReferrerPolicy] -> ShowS)
-> Show ReferrerPolicy
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ReferrerPolicy] -> ShowS
$cshowList :: [ReferrerPolicy] -> ShowS
show :: ReferrerPolicy -> String
$cshow :: ReferrerPolicy -> String
showsPrec :: Int -> ReferrerPolicy -> ShowS
$cshowsPrec :: Int -> ReferrerPolicy -> ShowS
Show, ReadPrec [ReferrerPolicy]
ReadPrec ReferrerPolicy
Int -> ReadS ReferrerPolicy
ReadS [ReferrerPolicy]
(Int -> ReadS ReferrerPolicy)
-> ReadS [ReferrerPolicy]
-> ReadPrec ReferrerPolicy
-> ReadPrec [ReferrerPolicy]
-> Read ReferrerPolicy
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ReferrerPolicy]
$creadListPrec :: ReadPrec [ReferrerPolicy]
readPrec :: ReadPrec ReferrerPolicy
$creadPrec :: ReadPrec ReferrerPolicy
readList :: ReadS [ReferrerPolicy]
$creadList :: ReadS [ReferrerPolicy]
readsPrec :: Int -> ReadS ReferrerPolicy
$creadsPrec :: Int -> ReadS ReferrerPolicy
Read, ReferrerPolicy -> ReferrerPolicy -> Bool
(ReferrerPolicy -> ReferrerPolicy -> Bool)
-> (ReferrerPolicy -> ReferrerPolicy -> Bool) -> Eq ReferrerPolicy
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ReferrerPolicy -> ReferrerPolicy -> Bool
$c/= :: ReferrerPolicy -> ReferrerPolicy -> Bool
== :: ReferrerPolicy -> ReferrerPolicy -> Bool
$c== :: ReferrerPolicy -> ReferrerPolicy -> Bool
Eq, Eq ReferrerPolicy
Eq ReferrerPolicy
-> (ReferrerPolicy -> ReferrerPolicy -> Ordering)
-> (ReferrerPolicy -> ReferrerPolicy -> Bool)
-> (ReferrerPolicy -> ReferrerPolicy -> Bool)
-> (ReferrerPolicy -> ReferrerPolicy -> Bool)
-> (ReferrerPolicy -> ReferrerPolicy -> Bool)
-> (ReferrerPolicy -> ReferrerPolicy -> ReferrerPolicy)
-> (ReferrerPolicy -> ReferrerPolicy -> ReferrerPolicy)
-> Ord ReferrerPolicy
ReferrerPolicy -> ReferrerPolicy -> Bool
ReferrerPolicy -> ReferrerPolicy -> Ordering
ReferrerPolicy -> ReferrerPolicy -> ReferrerPolicy
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ReferrerPolicy -> ReferrerPolicy -> ReferrerPolicy
$cmin :: ReferrerPolicy -> ReferrerPolicy -> ReferrerPolicy
max :: ReferrerPolicy -> ReferrerPolicy -> ReferrerPolicy
$cmax :: ReferrerPolicy -> ReferrerPolicy -> ReferrerPolicy
>= :: ReferrerPolicy -> ReferrerPolicy -> Bool
$c>= :: ReferrerPolicy -> ReferrerPolicy -> Bool
> :: ReferrerPolicy -> ReferrerPolicy -> Bool
$c> :: ReferrerPolicy -> ReferrerPolicy -> Bool
<= :: ReferrerPolicy -> ReferrerPolicy -> Bool
$c<= :: ReferrerPolicy -> ReferrerPolicy -> Bool
< :: ReferrerPolicy -> ReferrerPolicy -> Bool
$c< :: ReferrerPolicy -> ReferrerPolicy -> Bool
compare :: ReferrerPolicy -> ReferrerPolicy -> Ordering
$ccompare :: ReferrerPolicy -> ReferrerPolicy -> Ordering
$cp1Ord :: Eq ReferrerPolicy
Ord, Typeable)
 
instance ToJSVal ReferrerPolicy where
        toJSVal :: ReferrerPolicy -> JSM JSVal
toJSVal ReferrerPolicy
ReferrerPolicy = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_ReferrerPolicy
        toJSVal ReferrerPolicy
ReferrerPolicyNoReferrer
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_ReferrerPolicyNoReferrer
        toJSVal ReferrerPolicy
ReferrerPolicyNoReferrerWhenDowngrade
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_ReferrerPolicyNoReferrerWhenDowngrade
        toJSVal ReferrerPolicy
ReferrerPolicyOrigin = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_ReferrerPolicyOrigin
        toJSVal ReferrerPolicy
ReferrerPolicyOriginWhenCrossOrigin
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_ReferrerPolicyOriginWhenCrossOrigin
        toJSVal ReferrerPolicy
ReferrerPolicyUnsafeUrl
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_ReferrerPolicyUnsafeUrl
 
instance FromJSVal ReferrerPolicy where
        fromJSVal :: JSVal -> JSM (Maybe ReferrerPolicy)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_ReferrerPolicy JSM Bool
-> (Bool -> JSM (Maybe ReferrerPolicy))
-> JSM (Maybe ReferrerPolicy)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe ReferrerPolicy -> JSM (Maybe ReferrerPolicy)
forall (m :: * -> *) a. Monad m => a -> m a
return (ReferrerPolicy -> Maybe ReferrerPolicy
forall a. a -> Maybe a
Just ReferrerPolicy
ReferrerPolicy)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_ReferrerPolicyNoReferrer JSM Bool
-> (Bool -> JSM (Maybe ReferrerPolicy))
-> JSM (Maybe ReferrerPolicy)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe ReferrerPolicy -> JSM (Maybe ReferrerPolicy)
forall (m :: * -> *) a. Monad m => a -> m a
return (ReferrerPolicy -> Maybe ReferrerPolicy
forall a. a -> Maybe a
Just ReferrerPolicy
ReferrerPolicyNoReferrer)
                                 Bool
False
                                   -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_ReferrerPolicyNoReferrerWhenDowngrade JSM Bool
-> (Bool -> JSM (Maybe ReferrerPolicy))
-> JSM (Maybe ReferrerPolicy)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                        \ Bool
r ->
                                          case Bool
r of
                                              Bool
True
                                                -> Maybe ReferrerPolicy -> JSM (Maybe ReferrerPolicy)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                     (ReferrerPolicy -> Maybe ReferrerPolicy
forall a. a -> Maybe a
Just ReferrerPolicy
ReferrerPolicyNoReferrerWhenDowngrade)
                                              Bool
False
                                                -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_ReferrerPolicyOrigin JSM Bool
-> (Bool -> JSM (Maybe ReferrerPolicy))
-> JSM (Maybe ReferrerPolicy)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                     \ Bool
r ->
                                                       case Bool
r of
                                                           Bool
True
                                                             -> Maybe ReferrerPolicy -> JSM (Maybe ReferrerPolicy)
forall (m :: * -> *) a. Monad m => a -> m a
return (ReferrerPolicy -> Maybe ReferrerPolicy
forall a. a -> Maybe a
Just ReferrerPolicy
ReferrerPolicyOrigin)
                                                           Bool
False
                                                             -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                                  String
js_ReferrerPolicyOriginWhenCrossOrigin
                                                                  JSM Bool
-> (Bool -> JSM (Maybe ReferrerPolicy))
-> JSM (Maybe ReferrerPolicy)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                  \ Bool
r ->
                                                                    case Bool
r of
                                                                        Bool
True
                                                                          -> Maybe ReferrerPolicy -> JSM (Maybe ReferrerPolicy)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                               (ReferrerPolicy -> Maybe ReferrerPolicy
forall a. a -> Maybe a
Just
                                                                                  ReferrerPolicy
ReferrerPolicyOriginWhenCrossOrigin)
                                                                        Bool
False
                                                                          -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                                               String
js_ReferrerPolicyUnsafeUrl
                                                                               JSM Bool
-> (Bool -> JSM (Maybe ReferrerPolicy))
-> JSM (Maybe ReferrerPolicy)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                               \ Bool
r ->
                                                                                 case Bool
r of
                                                                                     Bool
True
                                                                                       -> Maybe ReferrerPolicy -> JSM (Maybe ReferrerPolicy)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                                            (ReferrerPolicy -> Maybe ReferrerPolicy
forall a. a -> Maybe a
Just
                                                                                               ReferrerPolicy
ReferrerPolicyUnsafeUrl)
                                                                                     Bool
False
                                                                                       -> Maybe ReferrerPolicy -> JSM (Maybe ReferrerPolicy)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                                            Maybe ReferrerPolicy
forall a. Maybe a
Nothing
js_ReferrerPolicy :: String
js_ReferrerPolicy = String
""
js_ReferrerPolicyNoReferrer :: String
js_ReferrerPolicyNoReferrer = String
"no-referrer"
js_ReferrerPolicyNoReferrerWhenDowngrade :: String
js_ReferrerPolicyNoReferrerWhenDowngrade
  = String
"no-referrer-when-downgrade"
js_ReferrerPolicyOrigin :: String
js_ReferrerPolicyOrigin = String
"origin"
js_ReferrerPolicyOriginWhenCrossOrigin :: String
js_ReferrerPolicyOriginWhenCrossOrigin = String
"origin-when-cross-origin"
js_ReferrerPolicyUnsafeUrl :: String
js_ReferrerPolicyUnsafeUrl = String
"unsafe-url"
 
data ResponseType = ResponseTypeBasic
                  | ResponseTypeCors
                  | ResponseTypeDefault
                  | ResponseTypeError
                  | ResponseTypeOpaque
                  | ResponseTypeOpaqueredirect
                  deriving (Int -> ResponseType -> ShowS
[ResponseType] -> ShowS
ResponseType -> String
(Int -> ResponseType -> ShowS)
-> (ResponseType -> String)
-> ([ResponseType] -> ShowS)
-> Show ResponseType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ResponseType] -> ShowS
$cshowList :: [ResponseType] -> ShowS
show :: ResponseType -> String
$cshow :: ResponseType -> String
showsPrec :: Int -> ResponseType -> ShowS
$cshowsPrec :: Int -> ResponseType -> ShowS
Show, ReadPrec [ResponseType]
ReadPrec ResponseType
Int -> ReadS ResponseType
ReadS [ResponseType]
(Int -> ReadS ResponseType)
-> ReadS [ResponseType]
-> ReadPrec ResponseType
-> ReadPrec [ResponseType]
-> Read ResponseType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ResponseType]
$creadListPrec :: ReadPrec [ResponseType]
readPrec :: ReadPrec ResponseType
$creadPrec :: ReadPrec ResponseType
readList :: ReadS [ResponseType]
$creadList :: ReadS [ResponseType]
readsPrec :: Int -> ReadS ResponseType
$creadsPrec :: Int -> ReadS ResponseType
Read, ResponseType -> ResponseType -> Bool
(ResponseType -> ResponseType -> Bool)
-> (ResponseType -> ResponseType -> Bool) -> Eq ResponseType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ResponseType -> ResponseType -> Bool
$c/= :: ResponseType -> ResponseType -> Bool
== :: ResponseType -> ResponseType -> Bool
$c== :: ResponseType -> ResponseType -> Bool
Eq, Eq ResponseType
Eq ResponseType
-> (ResponseType -> ResponseType -> Ordering)
-> (ResponseType -> ResponseType -> Bool)
-> (ResponseType -> ResponseType -> Bool)
-> (ResponseType -> ResponseType -> Bool)
-> (ResponseType -> ResponseType -> Bool)
-> (ResponseType -> ResponseType -> ResponseType)
-> (ResponseType -> ResponseType -> ResponseType)
-> Ord ResponseType
ResponseType -> ResponseType -> Bool
ResponseType -> ResponseType -> Ordering
ResponseType -> ResponseType -> ResponseType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ResponseType -> ResponseType -> ResponseType
$cmin :: ResponseType -> ResponseType -> ResponseType
max :: ResponseType -> ResponseType -> ResponseType
$cmax :: ResponseType -> ResponseType -> ResponseType
>= :: ResponseType -> ResponseType -> Bool
$c>= :: ResponseType -> ResponseType -> Bool
> :: ResponseType -> ResponseType -> Bool
$c> :: ResponseType -> ResponseType -> Bool
<= :: ResponseType -> ResponseType -> Bool
$c<= :: ResponseType -> ResponseType -> Bool
< :: ResponseType -> ResponseType -> Bool
$c< :: ResponseType -> ResponseType -> Bool
compare :: ResponseType -> ResponseType -> Ordering
$ccompare :: ResponseType -> ResponseType -> Ordering
$cp1Ord :: Eq ResponseType
Ord, Typeable)
 
instance ToJSVal ResponseType where
        toJSVal :: ResponseType -> JSM JSVal
toJSVal ResponseType
ResponseTypeBasic = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_ResponseTypeBasic
        toJSVal ResponseType
ResponseTypeCors = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_ResponseTypeCors
        toJSVal ResponseType
ResponseTypeDefault = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_ResponseTypeDefault
        toJSVal ResponseType
ResponseTypeError = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_ResponseTypeError
        toJSVal ResponseType
ResponseTypeOpaque = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_ResponseTypeOpaque
        toJSVal ResponseType
ResponseTypeOpaqueredirect
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_ResponseTypeOpaqueredirect
 
instance FromJSVal ResponseType where
        fromJSVal :: JSVal -> JSM (Maybe ResponseType)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_ResponseTypeBasic JSM Bool
-> (Bool -> JSM (Maybe ResponseType)) -> JSM (Maybe ResponseType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe ResponseType -> JSM (Maybe ResponseType)
forall (m :: * -> *) a. Monad m => a -> m a
return (ResponseType -> Maybe ResponseType
forall a. a -> Maybe a
Just ResponseType
ResponseTypeBasic)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_ResponseTypeCors JSM Bool
-> (Bool -> JSM (Maybe ResponseType)) -> JSM (Maybe ResponseType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe ResponseType -> JSM (Maybe ResponseType)
forall (m :: * -> *) a. Monad m => a -> m a
return (ResponseType -> Maybe ResponseType
forall a. a -> Maybe a
Just ResponseType
ResponseTypeCors)
                                 Bool
False
                                   -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_ResponseTypeDefault JSM Bool
-> (Bool -> JSM (Maybe ResponseType)) -> JSM (Maybe ResponseType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                        \ Bool
r ->
                                          case Bool
r of
                                              Bool
True -> Maybe ResponseType -> JSM (Maybe ResponseType)
forall (m :: * -> *) a. Monad m => a -> m a
return (ResponseType -> Maybe ResponseType
forall a. a -> Maybe a
Just ResponseType
ResponseTypeDefault)
                                              Bool
False
                                                -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_ResponseTypeError JSM Bool
-> (Bool -> JSM (Maybe ResponseType)) -> JSM (Maybe ResponseType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                     \ Bool
r ->
                                                       case Bool
r of
                                                           Bool
True -> Maybe ResponseType -> JSM (Maybe ResponseType)
forall (m :: * -> *) a. Monad m => a -> m a
return (ResponseType -> Maybe ResponseType
forall a. a -> Maybe a
Just ResponseType
ResponseTypeError)
                                                           Bool
False
                                                             -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                                  String
js_ResponseTypeOpaque
                                                                  JSM Bool
-> (Bool -> JSM (Maybe ResponseType)) -> JSM (Maybe ResponseType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                  \ Bool
r ->
                                                                    case Bool
r of
                                                                        Bool
True
                                                                          -> Maybe ResponseType -> JSM (Maybe ResponseType)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                               (ResponseType -> Maybe ResponseType
forall a. a -> Maybe a
Just
                                                                                  ResponseType
ResponseTypeOpaque)
                                                                        Bool
False
                                                                          -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                                               String
js_ResponseTypeOpaqueredirect
                                                                               JSM Bool
-> (Bool -> JSM (Maybe ResponseType)) -> JSM (Maybe ResponseType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                               \ Bool
r ->
                                                                                 case Bool
r of
                                                                                     Bool
True
                                                                                       -> Maybe ResponseType -> JSM (Maybe ResponseType)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                                            (ResponseType -> Maybe ResponseType
forall a. a -> Maybe a
Just
                                                                                               ResponseType
ResponseTypeOpaqueredirect)
                                                                                     Bool
False
                                                                                       -> Maybe ResponseType -> JSM (Maybe ResponseType)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                                            Maybe ResponseType
forall a. Maybe a
Nothing
js_ResponseTypeBasic :: String
js_ResponseTypeBasic = String
"basic"
js_ResponseTypeCors :: String
js_ResponseTypeCors = String
"cors"
js_ResponseTypeDefault :: String
js_ResponseTypeDefault = String
"default"
js_ResponseTypeError :: String
js_ResponseTypeError = String
"error"
js_ResponseTypeOpaque :: String
js_ResponseTypeOpaque = String
"opaque"
js_ResponseTypeOpaqueredirect :: String
js_ResponseTypeOpaqueredirect = String
"opaqueredirect"
 
data IDBCursorDirection = IDBCursorDirectionNext
                        | IDBCursorDirectionNextunique
                        | IDBCursorDirectionPrev
                        | IDBCursorDirectionPrevunique
                        deriving (Int -> IDBCursorDirection -> ShowS
[IDBCursorDirection] -> ShowS
IDBCursorDirection -> String
(Int -> IDBCursorDirection -> ShowS)
-> (IDBCursorDirection -> String)
-> ([IDBCursorDirection] -> ShowS)
-> Show IDBCursorDirection
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [IDBCursorDirection] -> ShowS
$cshowList :: [IDBCursorDirection] -> ShowS
show :: IDBCursorDirection -> String
$cshow :: IDBCursorDirection -> String
showsPrec :: Int -> IDBCursorDirection -> ShowS
$cshowsPrec :: Int -> IDBCursorDirection -> ShowS
Show, ReadPrec [IDBCursorDirection]
ReadPrec IDBCursorDirection
Int -> ReadS IDBCursorDirection
ReadS [IDBCursorDirection]
(Int -> ReadS IDBCursorDirection)
-> ReadS [IDBCursorDirection]
-> ReadPrec IDBCursorDirection
-> ReadPrec [IDBCursorDirection]
-> Read IDBCursorDirection
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [IDBCursorDirection]
$creadListPrec :: ReadPrec [IDBCursorDirection]
readPrec :: ReadPrec IDBCursorDirection
$creadPrec :: ReadPrec IDBCursorDirection
readList :: ReadS [IDBCursorDirection]
$creadList :: ReadS [IDBCursorDirection]
readsPrec :: Int -> ReadS IDBCursorDirection
$creadsPrec :: Int -> ReadS IDBCursorDirection
Read, IDBCursorDirection -> IDBCursorDirection -> Bool
(IDBCursorDirection -> IDBCursorDirection -> Bool)
-> (IDBCursorDirection -> IDBCursorDirection -> Bool)
-> Eq IDBCursorDirection
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IDBCursorDirection -> IDBCursorDirection -> Bool
$c/= :: IDBCursorDirection -> IDBCursorDirection -> Bool
== :: IDBCursorDirection -> IDBCursorDirection -> Bool
$c== :: IDBCursorDirection -> IDBCursorDirection -> Bool
Eq, Eq IDBCursorDirection
Eq IDBCursorDirection
-> (IDBCursorDirection -> IDBCursorDirection -> Ordering)
-> (IDBCursorDirection -> IDBCursorDirection -> Bool)
-> (IDBCursorDirection -> IDBCursorDirection -> Bool)
-> (IDBCursorDirection -> IDBCursorDirection -> Bool)
-> (IDBCursorDirection -> IDBCursorDirection -> Bool)
-> (IDBCursorDirection -> IDBCursorDirection -> IDBCursorDirection)
-> (IDBCursorDirection -> IDBCursorDirection -> IDBCursorDirection)
-> Ord IDBCursorDirection
IDBCursorDirection -> IDBCursorDirection -> Bool
IDBCursorDirection -> IDBCursorDirection -> Ordering
IDBCursorDirection -> IDBCursorDirection -> IDBCursorDirection
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: IDBCursorDirection -> IDBCursorDirection -> IDBCursorDirection
$cmin :: IDBCursorDirection -> IDBCursorDirection -> IDBCursorDirection
max :: IDBCursorDirection -> IDBCursorDirection -> IDBCursorDirection
$cmax :: IDBCursorDirection -> IDBCursorDirection -> IDBCursorDirection
>= :: IDBCursorDirection -> IDBCursorDirection -> Bool
$c>= :: IDBCursorDirection -> IDBCursorDirection -> Bool
> :: IDBCursorDirection -> IDBCursorDirection -> Bool
$c> :: IDBCursorDirection -> IDBCursorDirection -> Bool
<= :: IDBCursorDirection -> IDBCursorDirection -> Bool
$c<= :: IDBCursorDirection -> IDBCursorDirection -> Bool
< :: IDBCursorDirection -> IDBCursorDirection -> Bool
$c< :: IDBCursorDirection -> IDBCursorDirection -> Bool
compare :: IDBCursorDirection -> IDBCursorDirection -> Ordering
$ccompare :: IDBCursorDirection -> IDBCursorDirection -> Ordering
$cp1Ord :: Eq IDBCursorDirection
Ord, Typeable)
 
instance ToJSVal IDBCursorDirection where
        toJSVal :: IDBCursorDirection -> JSM JSVal
toJSVal IDBCursorDirection
IDBCursorDirectionNext = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_IDBCursorDirectionNext
        toJSVal IDBCursorDirection
IDBCursorDirectionNextunique
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_IDBCursorDirectionNextunique
        toJSVal IDBCursorDirection
IDBCursorDirectionPrev = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_IDBCursorDirectionPrev
        toJSVal IDBCursorDirection
IDBCursorDirectionPrevunique
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_IDBCursorDirectionPrevunique
 
instance FromJSVal IDBCursorDirection where
        fromJSVal :: JSVal -> JSM (Maybe IDBCursorDirection)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_IDBCursorDirectionNext JSM Bool
-> (Bool -> JSM (Maybe IDBCursorDirection))
-> JSM (Maybe IDBCursorDirection)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe IDBCursorDirection -> JSM (Maybe IDBCursorDirection)
forall (m :: * -> *) a. Monad m => a -> m a
return (IDBCursorDirection -> Maybe IDBCursorDirection
forall a. a -> Maybe a
Just IDBCursorDirection
IDBCursorDirectionNext)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_IDBCursorDirectionNextunique JSM Bool
-> (Bool -> JSM (Maybe IDBCursorDirection))
-> JSM (Maybe IDBCursorDirection)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe IDBCursorDirection -> JSM (Maybe IDBCursorDirection)
forall (m :: * -> *) a. Monad m => a -> m a
return (IDBCursorDirection -> Maybe IDBCursorDirection
forall a. a -> Maybe a
Just IDBCursorDirection
IDBCursorDirectionNextunique)
                                 Bool
False
                                   -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_IDBCursorDirectionPrev JSM Bool
-> (Bool -> JSM (Maybe IDBCursorDirection))
-> JSM (Maybe IDBCursorDirection)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                        \ Bool
r ->
                                          case Bool
r of
                                              Bool
True -> Maybe IDBCursorDirection -> JSM (Maybe IDBCursorDirection)
forall (m :: * -> *) a. Monad m => a -> m a
return (IDBCursorDirection -> Maybe IDBCursorDirection
forall a. a -> Maybe a
Just IDBCursorDirection
IDBCursorDirectionPrev)
                                              Bool
False
                                                -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_IDBCursorDirectionPrevunique
                                                     JSM Bool
-> (Bool -> JSM (Maybe IDBCursorDirection))
-> JSM (Maybe IDBCursorDirection)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                     \ Bool
r ->
                                                       case Bool
r of
                                                           Bool
True
                                                             -> Maybe IDBCursorDirection -> JSM (Maybe IDBCursorDirection)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                  (IDBCursorDirection -> Maybe IDBCursorDirection
forall a. a -> Maybe a
Just
                                                                     IDBCursorDirection
IDBCursorDirectionPrevunique)
                                                           Bool
False -> Maybe IDBCursorDirection -> JSM (Maybe IDBCursorDirection)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe IDBCursorDirection
forall a. Maybe a
Nothing
js_IDBCursorDirectionNext :: String
js_IDBCursorDirectionNext = String
"next"
js_IDBCursorDirectionNextunique :: String
js_IDBCursorDirectionNextunique = String
"nextunique"
js_IDBCursorDirectionPrev :: String
js_IDBCursorDirectionPrev = String
"prev"
js_IDBCursorDirectionPrevunique :: String
js_IDBCursorDirectionPrevunique = String
"prevunique"
 
data IDBRequestReadyState = IDBRequestReadyStatePending
                          | IDBRequestReadyStateDone
                          deriving (Int -> IDBRequestReadyState -> ShowS
[IDBRequestReadyState] -> ShowS
IDBRequestReadyState -> String
(Int -> IDBRequestReadyState -> ShowS)
-> (IDBRequestReadyState -> String)
-> ([IDBRequestReadyState] -> ShowS)
-> Show IDBRequestReadyState
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [IDBRequestReadyState] -> ShowS
$cshowList :: [IDBRequestReadyState] -> ShowS
show :: IDBRequestReadyState -> String
$cshow :: IDBRequestReadyState -> String
showsPrec :: Int -> IDBRequestReadyState -> ShowS
$cshowsPrec :: Int -> IDBRequestReadyState -> ShowS
Show, ReadPrec [IDBRequestReadyState]
ReadPrec IDBRequestReadyState
Int -> ReadS IDBRequestReadyState
ReadS [IDBRequestReadyState]
(Int -> ReadS IDBRequestReadyState)
-> ReadS [IDBRequestReadyState]
-> ReadPrec IDBRequestReadyState
-> ReadPrec [IDBRequestReadyState]
-> Read IDBRequestReadyState
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [IDBRequestReadyState]
$creadListPrec :: ReadPrec [IDBRequestReadyState]
readPrec :: ReadPrec IDBRequestReadyState
$creadPrec :: ReadPrec IDBRequestReadyState
readList :: ReadS [IDBRequestReadyState]
$creadList :: ReadS [IDBRequestReadyState]
readsPrec :: Int -> ReadS IDBRequestReadyState
$creadsPrec :: Int -> ReadS IDBRequestReadyState
Read, IDBRequestReadyState -> IDBRequestReadyState -> Bool
(IDBRequestReadyState -> IDBRequestReadyState -> Bool)
-> (IDBRequestReadyState -> IDBRequestReadyState -> Bool)
-> Eq IDBRequestReadyState
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IDBRequestReadyState -> IDBRequestReadyState -> Bool
$c/= :: IDBRequestReadyState -> IDBRequestReadyState -> Bool
== :: IDBRequestReadyState -> IDBRequestReadyState -> Bool
$c== :: IDBRequestReadyState -> IDBRequestReadyState -> Bool
Eq, Eq IDBRequestReadyState
Eq IDBRequestReadyState
-> (IDBRequestReadyState -> IDBRequestReadyState -> Ordering)
-> (IDBRequestReadyState -> IDBRequestReadyState -> Bool)
-> (IDBRequestReadyState -> IDBRequestReadyState -> Bool)
-> (IDBRequestReadyState -> IDBRequestReadyState -> Bool)
-> (IDBRequestReadyState -> IDBRequestReadyState -> Bool)
-> (IDBRequestReadyState
    -> IDBRequestReadyState -> IDBRequestReadyState)
-> (IDBRequestReadyState
    -> IDBRequestReadyState -> IDBRequestReadyState)
-> Ord IDBRequestReadyState
IDBRequestReadyState -> IDBRequestReadyState -> Bool
IDBRequestReadyState -> IDBRequestReadyState -> Ordering
IDBRequestReadyState
-> IDBRequestReadyState -> IDBRequestReadyState
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: IDBRequestReadyState
-> IDBRequestReadyState -> IDBRequestReadyState
$cmin :: IDBRequestReadyState
-> IDBRequestReadyState -> IDBRequestReadyState
max :: IDBRequestReadyState
-> IDBRequestReadyState -> IDBRequestReadyState
$cmax :: IDBRequestReadyState
-> IDBRequestReadyState -> IDBRequestReadyState
>= :: IDBRequestReadyState -> IDBRequestReadyState -> Bool
$c>= :: IDBRequestReadyState -> IDBRequestReadyState -> Bool
> :: IDBRequestReadyState -> IDBRequestReadyState -> Bool
$c> :: IDBRequestReadyState -> IDBRequestReadyState -> Bool
<= :: IDBRequestReadyState -> IDBRequestReadyState -> Bool
$c<= :: IDBRequestReadyState -> IDBRequestReadyState -> Bool
< :: IDBRequestReadyState -> IDBRequestReadyState -> Bool
$c< :: IDBRequestReadyState -> IDBRequestReadyState -> Bool
compare :: IDBRequestReadyState -> IDBRequestReadyState -> Ordering
$ccompare :: IDBRequestReadyState -> IDBRequestReadyState -> Ordering
$cp1Ord :: Eq IDBRequestReadyState
Ord, Typeable)
 
instance ToJSVal IDBRequestReadyState where
        toJSVal :: IDBRequestReadyState -> JSM JSVal
toJSVal IDBRequestReadyState
IDBRequestReadyStatePending
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_IDBRequestReadyStatePending
        toJSVal IDBRequestReadyState
IDBRequestReadyStateDone
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_IDBRequestReadyStateDone
 
instance FromJSVal IDBRequestReadyState where
        fromJSVal :: JSVal -> JSM (Maybe IDBRequestReadyState)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_IDBRequestReadyStatePending JSM Bool
-> (Bool -> JSM (Maybe IDBRequestReadyState))
-> JSM (Maybe IDBRequestReadyState)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe IDBRequestReadyState -> JSM (Maybe IDBRequestReadyState)
forall (m :: * -> *) a. Monad m => a -> m a
return (IDBRequestReadyState -> Maybe IDBRequestReadyState
forall a. a -> Maybe a
Just IDBRequestReadyState
IDBRequestReadyStatePending)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_IDBRequestReadyStateDone JSM Bool
-> (Bool -> JSM (Maybe IDBRequestReadyState))
-> JSM (Maybe IDBRequestReadyState)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe IDBRequestReadyState -> JSM (Maybe IDBRequestReadyState)
forall (m :: * -> *) a. Monad m => a -> m a
return (IDBRequestReadyState -> Maybe IDBRequestReadyState
forall a. a -> Maybe a
Just IDBRequestReadyState
IDBRequestReadyStateDone)
                                 Bool
False -> Maybe IDBRequestReadyState -> JSM (Maybe IDBRequestReadyState)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe IDBRequestReadyState
forall a. Maybe a
Nothing
js_IDBRequestReadyStatePending :: String
js_IDBRequestReadyStatePending = String
"pending"
js_IDBRequestReadyStateDone :: String
js_IDBRequestReadyStateDone = String
"done"
 
data IDBTransactionMode = IDBTransactionModeReadonly
                        | IDBTransactionModeReadwrite
                        | IDBTransactionModeVersionchange
                        deriving (Int -> IDBTransactionMode -> ShowS
[IDBTransactionMode] -> ShowS
IDBTransactionMode -> String
(Int -> IDBTransactionMode -> ShowS)
-> (IDBTransactionMode -> String)
-> ([IDBTransactionMode] -> ShowS)
-> Show IDBTransactionMode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [IDBTransactionMode] -> ShowS
$cshowList :: [IDBTransactionMode] -> ShowS
show :: IDBTransactionMode -> String
$cshow :: IDBTransactionMode -> String
showsPrec :: Int -> IDBTransactionMode -> ShowS
$cshowsPrec :: Int -> IDBTransactionMode -> ShowS
Show, ReadPrec [IDBTransactionMode]
ReadPrec IDBTransactionMode
Int -> ReadS IDBTransactionMode
ReadS [IDBTransactionMode]
(Int -> ReadS IDBTransactionMode)
-> ReadS [IDBTransactionMode]
-> ReadPrec IDBTransactionMode
-> ReadPrec [IDBTransactionMode]
-> Read IDBTransactionMode
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [IDBTransactionMode]
$creadListPrec :: ReadPrec [IDBTransactionMode]
readPrec :: ReadPrec IDBTransactionMode
$creadPrec :: ReadPrec IDBTransactionMode
readList :: ReadS [IDBTransactionMode]
$creadList :: ReadS [IDBTransactionMode]
readsPrec :: Int -> ReadS IDBTransactionMode
$creadsPrec :: Int -> ReadS IDBTransactionMode
Read, IDBTransactionMode -> IDBTransactionMode -> Bool
(IDBTransactionMode -> IDBTransactionMode -> Bool)
-> (IDBTransactionMode -> IDBTransactionMode -> Bool)
-> Eq IDBTransactionMode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IDBTransactionMode -> IDBTransactionMode -> Bool
$c/= :: IDBTransactionMode -> IDBTransactionMode -> Bool
== :: IDBTransactionMode -> IDBTransactionMode -> Bool
$c== :: IDBTransactionMode -> IDBTransactionMode -> Bool
Eq, Eq IDBTransactionMode
Eq IDBTransactionMode
-> (IDBTransactionMode -> IDBTransactionMode -> Ordering)
-> (IDBTransactionMode -> IDBTransactionMode -> Bool)
-> (IDBTransactionMode -> IDBTransactionMode -> Bool)
-> (IDBTransactionMode -> IDBTransactionMode -> Bool)
-> (IDBTransactionMode -> IDBTransactionMode -> Bool)
-> (IDBTransactionMode -> IDBTransactionMode -> IDBTransactionMode)
-> (IDBTransactionMode -> IDBTransactionMode -> IDBTransactionMode)
-> Ord IDBTransactionMode
IDBTransactionMode -> IDBTransactionMode -> Bool
IDBTransactionMode -> IDBTransactionMode -> Ordering
IDBTransactionMode -> IDBTransactionMode -> IDBTransactionMode
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: IDBTransactionMode -> IDBTransactionMode -> IDBTransactionMode
$cmin :: IDBTransactionMode -> IDBTransactionMode -> IDBTransactionMode
max :: IDBTransactionMode -> IDBTransactionMode -> IDBTransactionMode
$cmax :: IDBTransactionMode -> IDBTransactionMode -> IDBTransactionMode
>= :: IDBTransactionMode -> IDBTransactionMode -> Bool
$c>= :: IDBTransactionMode -> IDBTransactionMode -> Bool
> :: IDBTransactionMode -> IDBTransactionMode -> Bool
$c> :: IDBTransactionMode -> IDBTransactionMode -> Bool
<= :: IDBTransactionMode -> IDBTransactionMode -> Bool
$c<= :: IDBTransactionMode -> IDBTransactionMode -> Bool
< :: IDBTransactionMode -> IDBTransactionMode -> Bool
$c< :: IDBTransactionMode -> IDBTransactionMode -> Bool
compare :: IDBTransactionMode -> IDBTransactionMode -> Ordering
$ccompare :: IDBTransactionMode -> IDBTransactionMode -> Ordering
$cp1Ord :: Eq IDBTransactionMode
Ord, Typeable)
 
instance ToJSVal IDBTransactionMode where
        toJSVal :: IDBTransactionMode -> JSM JSVal
toJSVal IDBTransactionMode
IDBTransactionModeReadonly
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_IDBTransactionModeReadonly
        toJSVal IDBTransactionMode
IDBTransactionModeReadwrite
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_IDBTransactionModeReadwrite
        toJSVal IDBTransactionMode
IDBTransactionModeVersionchange
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_IDBTransactionModeVersionchange
 
instance FromJSVal IDBTransactionMode where
        fromJSVal :: JSVal -> JSM (Maybe IDBTransactionMode)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_IDBTransactionModeReadonly JSM Bool
-> (Bool -> JSM (Maybe IDBTransactionMode))
-> JSM (Maybe IDBTransactionMode)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe IDBTransactionMode -> JSM (Maybe IDBTransactionMode)
forall (m :: * -> *) a. Monad m => a -> m a
return (IDBTransactionMode -> Maybe IDBTransactionMode
forall a. a -> Maybe a
Just IDBTransactionMode
IDBTransactionModeReadonly)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_IDBTransactionModeReadwrite JSM Bool
-> (Bool -> JSM (Maybe IDBTransactionMode))
-> JSM (Maybe IDBTransactionMode)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe IDBTransactionMode -> JSM (Maybe IDBTransactionMode)
forall (m :: * -> *) a. Monad m => a -> m a
return (IDBTransactionMode -> Maybe IDBTransactionMode
forall a. a -> Maybe a
Just IDBTransactionMode
IDBTransactionModeReadwrite)
                                 Bool
False
                                   -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_IDBTransactionModeVersionchange JSM Bool
-> (Bool -> JSM (Maybe IDBTransactionMode))
-> JSM (Maybe IDBTransactionMode)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                        \ Bool
r ->
                                          case Bool
r of
                                              Bool
True -> Maybe IDBTransactionMode -> JSM (Maybe IDBTransactionMode)
forall (m :: * -> *) a. Monad m => a -> m a
return (IDBTransactionMode -> Maybe IDBTransactionMode
forall a. a -> Maybe a
Just IDBTransactionMode
IDBTransactionModeVersionchange)
                                              Bool
False -> Maybe IDBTransactionMode -> JSM (Maybe IDBTransactionMode)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe IDBTransactionMode
forall a. Maybe a
Nothing
js_IDBTransactionModeReadonly :: String
js_IDBTransactionModeReadonly = String
"readonly"
js_IDBTransactionModeReadwrite :: String
js_IDBTransactionModeReadwrite = String
"readwrite"
js_IDBTransactionModeVersionchange :: String
js_IDBTransactionModeVersionchange = String
"versionchange"
 
data DeviceType = DeviceTypeNone
                | DeviceTypeAirplay
                | DeviceTypeTvout
                deriving (Int -> DeviceType -> ShowS
[DeviceType] -> ShowS
DeviceType -> String
(Int -> DeviceType -> ShowS)
-> (DeviceType -> String)
-> ([DeviceType] -> ShowS)
-> Show DeviceType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeviceType] -> ShowS
$cshowList :: [DeviceType] -> ShowS
show :: DeviceType -> String
$cshow :: DeviceType -> String
showsPrec :: Int -> DeviceType -> ShowS
$cshowsPrec :: Int -> DeviceType -> ShowS
Show, ReadPrec [DeviceType]
ReadPrec DeviceType
Int -> ReadS DeviceType
ReadS [DeviceType]
(Int -> ReadS DeviceType)
-> ReadS [DeviceType]
-> ReadPrec DeviceType
-> ReadPrec [DeviceType]
-> Read DeviceType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeviceType]
$creadListPrec :: ReadPrec [DeviceType]
readPrec :: ReadPrec DeviceType
$creadPrec :: ReadPrec DeviceType
readList :: ReadS [DeviceType]
$creadList :: ReadS [DeviceType]
readsPrec :: Int -> ReadS DeviceType
$creadsPrec :: Int -> ReadS DeviceType
Read, DeviceType -> DeviceType -> Bool
(DeviceType -> DeviceType -> Bool)
-> (DeviceType -> DeviceType -> Bool) -> Eq DeviceType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeviceType -> DeviceType -> Bool
$c/= :: DeviceType -> DeviceType -> Bool
== :: DeviceType -> DeviceType -> Bool
$c== :: DeviceType -> DeviceType -> Bool
Eq, Eq DeviceType
Eq DeviceType
-> (DeviceType -> DeviceType -> Ordering)
-> (DeviceType -> DeviceType -> Bool)
-> (DeviceType -> DeviceType -> Bool)
-> (DeviceType -> DeviceType -> Bool)
-> (DeviceType -> DeviceType -> Bool)
-> (DeviceType -> DeviceType -> DeviceType)
-> (DeviceType -> DeviceType -> DeviceType)
-> Ord DeviceType
DeviceType -> DeviceType -> Bool
DeviceType -> DeviceType -> Ordering
DeviceType -> DeviceType -> DeviceType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: DeviceType -> DeviceType -> DeviceType
$cmin :: DeviceType -> DeviceType -> DeviceType
max :: DeviceType -> DeviceType -> DeviceType
$cmax :: DeviceType -> DeviceType -> DeviceType
>= :: DeviceType -> DeviceType -> Bool
$c>= :: DeviceType -> DeviceType -> Bool
> :: DeviceType -> DeviceType -> Bool
$c> :: DeviceType -> DeviceType -> Bool
<= :: DeviceType -> DeviceType -> Bool
$c<= :: DeviceType -> DeviceType -> Bool
< :: DeviceType -> DeviceType -> Bool
$c< :: DeviceType -> DeviceType -> Bool
compare :: DeviceType -> DeviceType -> Ordering
$ccompare :: DeviceType -> DeviceType -> Ordering
$cp1Ord :: Eq DeviceType
Ord, Typeable)
 
instance ToJSVal DeviceType where
        toJSVal :: DeviceType -> JSM JSVal
toJSVal DeviceType
DeviceTypeNone = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_DeviceTypeNone
        toJSVal DeviceType
DeviceTypeAirplay = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_DeviceTypeAirplay
        toJSVal DeviceType
DeviceTypeTvout = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_DeviceTypeTvout
 
instance FromJSVal DeviceType where
        fromJSVal :: JSVal -> JSM (Maybe DeviceType)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_DeviceTypeNone JSM Bool
-> (Bool -> JSM (Maybe DeviceType)) -> JSM (Maybe DeviceType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe DeviceType -> JSM (Maybe DeviceType)
forall (m :: * -> *) a. Monad m => a -> m a
return (DeviceType -> Maybe DeviceType
forall a. a -> Maybe a
Just DeviceType
DeviceTypeNone)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_DeviceTypeAirplay JSM Bool
-> (Bool -> JSM (Maybe DeviceType)) -> JSM (Maybe DeviceType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe DeviceType -> JSM (Maybe DeviceType)
forall (m :: * -> *) a. Monad m => a -> m a
return (DeviceType -> Maybe DeviceType
forall a. a -> Maybe a
Just DeviceType
DeviceTypeAirplay)
                                 Bool
False
                                   -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_DeviceTypeTvout JSM Bool
-> (Bool -> JSM (Maybe DeviceType)) -> JSM (Maybe DeviceType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                        \ Bool
r ->
                                          case Bool
r of
                                              Bool
True -> Maybe DeviceType -> JSM (Maybe DeviceType)
forall (m :: * -> *) a. Monad m => a -> m a
return (DeviceType -> Maybe DeviceType
forall a. a -> Maybe a
Just DeviceType
DeviceTypeTvout)
                                              Bool
False -> Maybe DeviceType -> JSM (Maybe DeviceType)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe DeviceType
forall a. Maybe a
Nothing
js_DeviceTypeNone :: String
js_DeviceTypeNone = String
"none"
js_DeviceTypeAirplay :: String
js_DeviceTypeAirplay = String
"airplay"
js_DeviceTypeTvout :: String
js_DeviceTypeTvout = String
"tvout"
 
data MediaSessionKind = MediaSessionKindContent
                      | MediaSessionKindTransient
                      | MediaSessionKindTransientSolo
                      | MediaSessionKindAmbient
                      deriving (Int -> MediaSessionKind -> ShowS
[MediaSessionKind] -> ShowS
MediaSessionKind -> String
(Int -> MediaSessionKind -> ShowS)
-> (MediaSessionKind -> String)
-> ([MediaSessionKind] -> ShowS)
-> Show MediaSessionKind
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MediaSessionKind] -> ShowS
$cshowList :: [MediaSessionKind] -> ShowS
show :: MediaSessionKind -> String
$cshow :: MediaSessionKind -> String
showsPrec :: Int -> MediaSessionKind -> ShowS
$cshowsPrec :: Int -> MediaSessionKind -> ShowS
Show, ReadPrec [MediaSessionKind]
ReadPrec MediaSessionKind
Int -> ReadS MediaSessionKind
ReadS [MediaSessionKind]
(Int -> ReadS MediaSessionKind)
-> ReadS [MediaSessionKind]
-> ReadPrec MediaSessionKind
-> ReadPrec [MediaSessionKind]
-> Read MediaSessionKind
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [MediaSessionKind]
$creadListPrec :: ReadPrec [MediaSessionKind]
readPrec :: ReadPrec MediaSessionKind
$creadPrec :: ReadPrec MediaSessionKind
readList :: ReadS [MediaSessionKind]
$creadList :: ReadS [MediaSessionKind]
readsPrec :: Int -> ReadS MediaSessionKind
$creadsPrec :: Int -> ReadS MediaSessionKind
Read, MediaSessionKind -> MediaSessionKind -> Bool
(MediaSessionKind -> MediaSessionKind -> Bool)
-> (MediaSessionKind -> MediaSessionKind -> Bool)
-> Eq MediaSessionKind
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MediaSessionKind -> MediaSessionKind -> Bool
$c/= :: MediaSessionKind -> MediaSessionKind -> Bool
== :: MediaSessionKind -> MediaSessionKind -> Bool
$c== :: MediaSessionKind -> MediaSessionKind -> Bool
Eq, Eq MediaSessionKind
Eq MediaSessionKind
-> (MediaSessionKind -> MediaSessionKind -> Ordering)
-> (MediaSessionKind -> MediaSessionKind -> Bool)
-> (MediaSessionKind -> MediaSessionKind -> Bool)
-> (MediaSessionKind -> MediaSessionKind -> Bool)
-> (MediaSessionKind -> MediaSessionKind -> Bool)
-> (MediaSessionKind -> MediaSessionKind -> MediaSessionKind)
-> (MediaSessionKind -> MediaSessionKind -> MediaSessionKind)
-> Ord MediaSessionKind
MediaSessionKind -> MediaSessionKind -> Bool
MediaSessionKind -> MediaSessionKind -> Ordering
MediaSessionKind -> MediaSessionKind -> MediaSessionKind
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: MediaSessionKind -> MediaSessionKind -> MediaSessionKind
$cmin :: MediaSessionKind -> MediaSessionKind -> MediaSessionKind
max :: MediaSessionKind -> MediaSessionKind -> MediaSessionKind
$cmax :: MediaSessionKind -> MediaSessionKind -> MediaSessionKind
>= :: MediaSessionKind -> MediaSessionKind -> Bool
$c>= :: MediaSessionKind -> MediaSessionKind -> Bool
> :: MediaSessionKind -> MediaSessionKind -> Bool
$c> :: MediaSessionKind -> MediaSessionKind -> Bool
<= :: MediaSessionKind -> MediaSessionKind -> Bool
$c<= :: MediaSessionKind -> MediaSessionKind -> Bool
< :: MediaSessionKind -> MediaSessionKind -> Bool
$c< :: MediaSessionKind -> MediaSessionKind -> Bool
compare :: MediaSessionKind -> MediaSessionKind -> Ordering
$ccompare :: MediaSessionKind -> MediaSessionKind -> Ordering
$cp1Ord :: Eq MediaSessionKind
Ord, Typeable)
 
instance ToJSVal MediaSessionKind where
        toJSVal :: MediaSessionKind -> JSM JSVal
toJSVal MediaSessionKind
MediaSessionKindContent
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_MediaSessionKindContent
        toJSVal MediaSessionKind
MediaSessionKindTransient
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_MediaSessionKindTransient
        toJSVal MediaSessionKind
MediaSessionKindTransientSolo
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_MediaSessionKindTransientSolo
        toJSVal MediaSessionKind
MediaSessionKindAmbient
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_MediaSessionKindAmbient
 
instance FromJSVal MediaSessionKind where
        fromJSVal :: JSVal -> JSM (Maybe MediaSessionKind)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_MediaSessionKindContent JSM Bool
-> (Bool -> JSM (Maybe MediaSessionKind))
-> JSM (Maybe MediaSessionKind)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe MediaSessionKind -> JSM (Maybe MediaSessionKind)
forall (m :: * -> *) a. Monad m => a -> m a
return (MediaSessionKind -> Maybe MediaSessionKind
forall a. a -> Maybe a
Just MediaSessionKind
MediaSessionKindContent)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_MediaSessionKindTransient JSM Bool
-> (Bool -> JSM (Maybe MediaSessionKind))
-> JSM (Maybe MediaSessionKind)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe MediaSessionKind -> JSM (Maybe MediaSessionKind)
forall (m :: * -> *) a. Monad m => a -> m a
return (MediaSessionKind -> Maybe MediaSessionKind
forall a. a -> Maybe a
Just MediaSessionKind
MediaSessionKindTransient)
                                 Bool
False
                                   -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_MediaSessionKindTransientSolo JSM Bool
-> (Bool -> JSM (Maybe MediaSessionKind))
-> JSM (Maybe MediaSessionKind)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                        \ Bool
r ->
                                          case Bool
r of
                                              Bool
True -> Maybe MediaSessionKind -> JSM (Maybe MediaSessionKind)
forall (m :: * -> *) a. Monad m => a -> m a
return (MediaSessionKind -> Maybe MediaSessionKind
forall a. a -> Maybe a
Just MediaSessionKind
MediaSessionKindTransientSolo)
                                              Bool
False
                                                -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_MediaSessionKindAmbient JSM Bool
-> (Bool -> JSM (Maybe MediaSessionKind))
-> JSM (Maybe MediaSessionKind)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                     \ Bool
r ->
                                                       case Bool
r of
                                                           Bool
True
                                                             -> Maybe MediaSessionKind -> JSM (Maybe MediaSessionKind)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                  (MediaSessionKind -> Maybe MediaSessionKind
forall a. a -> Maybe a
Just MediaSessionKind
MediaSessionKindAmbient)
                                                           Bool
False -> Maybe MediaSessionKind -> JSM (Maybe MediaSessionKind)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe MediaSessionKind
forall a. Maybe a
Nothing
js_MediaSessionKindContent :: String
js_MediaSessionKindContent = String
"content"
js_MediaSessionKindTransient :: String
js_MediaSessionKindTransient = String
"transient"
js_MediaSessionKindTransientSolo :: String
js_MediaSessionKindTransientSolo = String
"transient-solo"
js_MediaSessionKindAmbient :: String
js_MediaSessionKindAmbient = String
"ambient"
 
data EndOfStreamError = EndOfStreamErrorNetwork
                      | EndOfStreamErrorDecode
                      deriving (Int -> EndOfStreamError -> ShowS
[EndOfStreamError] -> ShowS
EndOfStreamError -> String
(Int -> EndOfStreamError -> ShowS)
-> (EndOfStreamError -> String)
-> ([EndOfStreamError] -> ShowS)
-> Show EndOfStreamError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EndOfStreamError] -> ShowS
$cshowList :: [EndOfStreamError] -> ShowS
show :: EndOfStreamError -> String
$cshow :: EndOfStreamError -> String
showsPrec :: Int -> EndOfStreamError -> ShowS
$cshowsPrec :: Int -> EndOfStreamError -> ShowS
Show, ReadPrec [EndOfStreamError]
ReadPrec EndOfStreamError
Int -> ReadS EndOfStreamError
ReadS [EndOfStreamError]
(Int -> ReadS EndOfStreamError)
-> ReadS [EndOfStreamError]
-> ReadPrec EndOfStreamError
-> ReadPrec [EndOfStreamError]
-> Read EndOfStreamError
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [EndOfStreamError]
$creadListPrec :: ReadPrec [EndOfStreamError]
readPrec :: ReadPrec EndOfStreamError
$creadPrec :: ReadPrec EndOfStreamError
readList :: ReadS [EndOfStreamError]
$creadList :: ReadS [EndOfStreamError]
readsPrec :: Int -> ReadS EndOfStreamError
$creadsPrec :: Int -> ReadS EndOfStreamError
Read, EndOfStreamError -> EndOfStreamError -> Bool
(EndOfStreamError -> EndOfStreamError -> Bool)
-> (EndOfStreamError -> EndOfStreamError -> Bool)
-> Eq EndOfStreamError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EndOfStreamError -> EndOfStreamError -> Bool
$c/= :: EndOfStreamError -> EndOfStreamError -> Bool
== :: EndOfStreamError -> EndOfStreamError -> Bool
$c== :: EndOfStreamError -> EndOfStreamError -> Bool
Eq, Eq EndOfStreamError
Eq EndOfStreamError
-> (EndOfStreamError -> EndOfStreamError -> Ordering)
-> (EndOfStreamError -> EndOfStreamError -> Bool)
-> (EndOfStreamError -> EndOfStreamError -> Bool)
-> (EndOfStreamError -> EndOfStreamError -> Bool)
-> (EndOfStreamError -> EndOfStreamError -> Bool)
-> (EndOfStreamError -> EndOfStreamError -> EndOfStreamError)
-> (EndOfStreamError -> EndOfStreamError -> EndOfStreamError)
-> Ord EndOfStreamError
EndOfStreamError -> EndOfStreamError -> Bool
EndOfStreamError -> EndOfStreamError -> Ordering
EndOfStreamError -> EndOfStreamError -> EndOfStreamError
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: EndOfStreamError -> EndOfStreamError -> EndOfStreamError
$cmin :: EndOfStreamError -> EndOfStreamError -> EndOfStreamError
max :: EndOfStreamError -> EndOfStreamError -> EndOfStreamError
$cmax :: EndOfStreamError -> EndOfStreamError -> EndOfStreamError
>= :: EndOfStreamError -> EndOfStreamError -> Bool
$c>= :: EndOfStreamError -> EndOfStreamError -> Bool
> :: EndOfStreamError -> EndOfStreamError -> Bool
$c> :: EndOfStreamError -> EndOfStreamError -> Bool
<= :: EndOfStreamError -> EndOfStreamError -> Bool
$c<= :: EndOfStreamError -> EndOfStreamError -> Bool
< :: EndOfStreamError -> EndOfStreamError -> Bool
$c< :: EndOfStreamError -> EndOfStreamError -> Bool
compare :: EndOfStreamError -> EndOfStreamError -> Ordering
$ccompare :: EndOfStreamError -> EndOfStreamError -> Ordering
$cp1Ord :: Eq EndOfStreamError
Ord, Typeable)
 
instance ToJSVal EndOfStreamError where
        toJSVal :: EndOfStreamError -> JSM JSVal
toJSVal EndOfStreamError
EndOfStreamErrorNetwork
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_EndOfStreamErrorNetwork
        toJSVal EndOfStreamError
EndOfStreamErrorDecode = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_EndOfStreamErrorDecode
 
instance FromJSVal EndOfStreamError where
        fromJSVal :: JSVal -> JSM (Maybe EndOfStreamError)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_EndOfStreamErrorNetwork JSM Bool
-> (Bool -> JSM (Maybe EndOfStreamError))
-> JSM (Maybe EndOfStreamError)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe EndOfStreamError -> JSM (Maybe EndOfStreamError)
forall (m :: * -> *) a. Monad m => a -> m a
return (EndOfStreamError -> Maybe EndOfStreamError
forall a. a -> Maybe a
Just EndOfStreamError
EndOfStreamErrorNetwork)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_EndOfStreamErrorDecode JSM Bool
-> (Bool -> JSM (Maybe EndOfStreamError))
-> JSM (Maybe EndOfStreamError)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe EndOfStreamError -> JSM (Maybe EndOfStreamError)
forall (m :: * -> *) a. Monad m => a -> m a
return (EndOfStreamError -> Maybe EndOfStreamError
forall a. a -> Maybe a
Just EndOfStreamError
EndOfStreamErrorDecode)
                                 Bool
False -> Maybe EndOfStreamError -> JSM (Maybe EndOfStreamError)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe EndOfStreamError
forall a. Maybe a
Nothing
js_EndOfStreamErrorNetwork :: String
js_EndOfStreamErrorNetwork = String
"network"
js_EndOfStreamErrorDecode :: String
js_EndOfStreamErrorDecode = String
"decode"
 
data ReadyState = ReadyStateClosed
                | ReadyStateOpen
                | ReadyStateEnded
                deriving (Int -> ReadyState -> ShowS
[ReadyState] -> ShowS
ReadyState -> String
(Int -> ReadyState -> ShowS)
-> (ReadyState -> String)
-> ([ReadyState] -> ShowS)
-> Show ReadyState
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ReadyState] -> ShowS
$cshowList :: [ReadyState] -> ShowS
show :: ReadyState -> String
$cshow :: ReadyState -> String
showsPrec :: Int -> ReadyState -> ShowS
$cshowsPrec :: Int -> ReadyState -> ShowS
Show, ReadPrec [ReadyState]
ReadPrec ReadyState
Int -> ReadS ReadyState
ReadS [ReadyState]
(Int -> ReadS ReadyState)
-> ReadS [ReadyState]
-> ReadPrec ReadyState
-> ReadPrec [ReadyState]
-> Read ReadyState
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ReadyState]
$creadListPrec :: ReadPrec [ReadyState]
readPrec :: ReadPrec ReadyState
$creadPrec :: ReadPrec ReadyState
readList :: ReadS [ReadyState]
$creadList :: ReadS [ReadyState]
readsPrec :: Int -> ReadS ReadyState
$creadsPrec :: Int -> ReadS ReadyState
Read, ReadyState -> ReadyState -> Bool
(ReadyState -> ReadyState -> Bool)
-> (ReadyState -> ReadyState -> Bool) -> Eq ReadyState
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ReadyState -> ReadyState -> Bool
$c/= :: ReadyState -> ReadyState -> Bool
== :: ReadyState -> ReadyState -> Bool
$c== :: ReadyState -> ReadyState -> Bool
Eq, Eq ReadyState
Eq ReadyState
-> (ReadyState -> ReadyState -> Ordering)
-> (ReadyState -> ReadyState -> Bool)
-> (ReadyState -> ReadyState -> Bool)
-> (ReadyState -> ReadyState -> Bool)
-> (ReadyState -> ReadyState -> Bool)
-> (ReadyState -> ReadyState -> ReadyState)
-> (ReadyState -> ReadyState -> ReadyState)
-> Ord ReadyState
ReadyState -> ReadyState -> Bool
ReadyState -> ReadyState -> Ordering
ReadyState -> ReadyState -> ReadyState
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ReadyState -> ReadyState -> ReadyState
$cmin :: ReadyState -> ReadyState -> ReadyState
max :: ReadyState -> ReadyState -> ReadyState
$cmax :: ReadyState -> ReadyState -> ReadyState
>= :: ReadyState -> ReadyState -> Bool
$c>= :: ReadyState -> ReadyState -> Bool
> :: ReadyState -> ReadyState -> Bool
$c> :: ReadyState -> ReadyState -> Bool
<= :: ReadyState -> ReadyState -> Bool
$c<= :: ReadyState -> ReadyState -> Bool
< :: ReadyState -> ReadyState -> Bool
$c< :: ReadyState -> ReadyState -> Bool
compare :: ReadyState -> ReadyState -> Ordering
$ccompare :: ReadyState -> ReadyState -> Ordering
$cp1Ord :: Eq ReadyState
Ord, Typeable)
 
instance ToJSVal ReadyState where
        toJSVal :: ReadyState -> JSM JSVal
toJSVal ReadyState
ReadyStateClosed = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_ReadyStateClosed
        toJSVal ReadyState
ReadyStateOpen = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_ReadyStateOpen
        toJSVal ReadyState
ReadyStateEnded = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_ReadyStateEnded
 
instance FromJSVal ReadyState where
        fromJSVal :: JSVal -> JSM (Maybe ReadyState)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_ReadyStateClosed JSM Bool
-> (Bool -> JSM (Maybe ReadyState)) -> JSM (Maybe ReadyState)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe ReadyState -> JSM (Maybe ReadyState)
forall (m :: * -> *) a. Monad m => a -> m a
return (ReadyState -> Maybe ReadyState
forall a. a -> Maybe a
Just ReadyState
ReadyStateClosed)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_ReadyStateOpen JSM Bool
-> (Bool -> JSM (Maybe ReadyState)) -> JSM (Maybe ReadyState)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe ReadyState -> JSM (Maybe ReadyState)
forall (m :: * -> *) a. Monad m => a -> m a
return (ReadyState -> Maybe ReadyState
forall a. a -> Maybe a
Just ReadyState
ReadyStateOpen)
                                 Bool
False
                                   -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_ReadyStateEnded JSM Bool
-> (Bool -> JSM (Maybe ReadyState)) -> JSM (Maybe ReadyState)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                        \ Bool
r ->
                                          case Bool
r of
                                              Bool
True -> Maybe ReadyState -> JSM (Maybe ReadyState)
forall (m :: * -> *) a. Monad m => a -> m a
return (ReadyState -> Maybe ReadyState
forall a. a -> Maybe a
Just ReadyState
ReadyStateEnded)
                                              Bool
False -> Maybe ReadyState -> JSM (Maybe ReadyState)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ReadyState
forall a. Maybe a
Nothing
js_ReadyStateClosed :: String
js_ReadyStateClosed = String
"closed"
js_ReadyStateOpen :: String
js_ReadyStateOpen = String
"open"
js_ReadyStateEnded :: String
js_ReadyStateEnded = String
"ended"
 
data AppendMode = AppendModeSegments
                | AppendModeSequence
                deriving (Int -> AppendMode -> ShowS
[AppendMode] -> ShowS
AppendMode -> String
(Int -> AppendMode -> ShowS)
-> (AppendMode -> String)
-> ([AppendMode] -> ShowS)
-> Show AppendMode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AppendMode] -> ShowS
$cshowList :: [AppendMode] -> ShowS
show :: AppendMode -> String
$cshow :: AppendMode -> String
showsPrec :: Int -> AppendMode -> ShowS
$cshowsPrec :: Int -> AppendMode -> ShowS
Show, ReadPrec [AppendMode]
ReadPrec AppendMode
Int -> ReadS AppendMode
ReadS [AppendMode]
(Int -> ReadS AppendMode)
-> ReadS [AppendMode]
-> ReadPrec AppendMode
-> ReadPrec [AppendMode]
-> Read AppendMode
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AppendMode]
$creadListPrec :: ReadPrec [AppendMode]
readPrec :: ReadPrec AppendMode
$creadPrec :: ReadPrec AppendMode
readList :: ReadS [AppendMode]
$creadList :: ReadS [AppendMode]
readsPrec :: Int -> ReadS AppendMode
$creadsPrec :: Int -> ReadS AppendMode
Read, AppendMode -> AppendMode -> Bool
(AppendMode -> AppendMode -> Bool)
-> (AppendMode -> AppendMode -> Bool) -> Eq AppendMode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AppendMode -> AppendMode -> Bool
$c/= :: AppendMode -> AppendMode -> Bool
== :: AppendMode -> AppendMode -> Bool
$c== :: AppendMode -> AppendMode -> Bool
Eq, Eq AppendMode
Eq AppendMode
-> (AppendMode -> AppendMode -> Ordering)
-> (AppendMode -> AppendMode -> Bool)
-> (AppendMode -> AppendMode -> Bool)
-> (AppendMode -> AppendMode -> Bool)
-> (AppendMode -> AppendMode -> Bool)
-> (AppendMode -> AppendMode -> AppendMode)
-> (AppendMode -> AppendMode -> AppendMode)
-> Ord AppendMode
AppendMode -> AppendMode -> Bool
AppendMode -> AppendMode -> Ordering
AppendMode -> AppendMode -> AppendMode
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: AppendMode -> AppendMode -> AppendMode
$cmin :: AppendMode -> AppendMode -> AppendMode
max :: AppendMode -> AppendMode -> AppendMode
$cmax :: AppendMode -> AppendMode -> AppendMode
>= :: AppendMode -> AppendMode -> Bool
$c>= :: AppendMode -> AppendMode -> Bool
> :: AppendMode -> AppendMode -> Bool
$c> :: AppendMode -> AppendMode -> Bool
<= :: AppendMode -> AppendMode -> Bool
$c<= :: AppendMode -> AppendMode -> Bool
< :: AppendMode -> AppendMode -> Bool
$c< :: AppendMode -> AppendMode -> Bool
compare :: AppendMode -> AppendMode -> Ordering
$ccompare :: AppendMode -> AppendMode -> Ordering
$cp1Ord :: Eq AppendMode
Ord, Typeable)
 
instance ToJSVal AppendMode where
        toJSVal :: AppendMode -> JSM JSVal
toJSVal AppendMode
AppendModeSegments = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_AppendModeSegments
        toJSVal AppendMode
AppendModeSequence = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_AppendModeSequence
 
instance FromJSVal AppendMode where
        fromJSVal :: JSVal -> JSM (Maybe AppendMode)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_AppendModeSegments JSM Bool
-> (Bool -> JSM (Maybe AppendMode)) -> JSM (Maybe AppendMode)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe AppendMode -> JSM (Maybe AppendMode)
forall (m :: * -> *) a. Monad m => a -> m a
return (AppendMode -> Maybe AppendMode
forall a. a -> Maybe a
Just AppendMode
AppendModeSegments)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_AppendModeSequence JSM Bool
-> (Bool -> JSM (Maybe AppendMode)) -> JSM (Maybe AppendMode)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe AppendMode -> JSM (Maybe AppendMode)
forall (m :: * -> *) a. Monad m => a -> m a
return (AppendMode -> Maybe AppendMode
forall a. a -> Maybe a
Just AppendMode
AppendModeSequence)
                                 Bool
False -> Maybe AppendMode -> JSM (Maybe AppendMode)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe AppendMode
forall a. Maybe a
Nothing
js_AppendModeSegments :: String
js_AppendModeSegments = String
"segments"
js_AppendModeSequence :: String
js_AppendModeSequence = String
"sequence"
 
data MediaDeviceKind = MediaDeviceKindAudioinput
                     | MediaDeviceKindAudiooutput
                     | MediaDeviceKindVideoinput
                     deriving (Int -> MediaDeviceKind -> ShowS
[MediaDeviceKind] -> ShowS
MediaDeviceKind -> String
(Int -> MediaDeviceKind -> ShowS)
-> (MediaDeviceKind -> String)
-> ([MediaDeviceKind] -> ShowS)
-> Show MediaDeviceKind
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MediaDeviceKind] -> ShowS
$cshowList :: [MediaDeviceKind] -> ShowS
show :: MediaDeviceKind -> String
$cshow :: MediaDeviceKind -> String
showsPrec :: Int -> MediaDeviceKind -> ShowS
$cshowsPrec :: Int -> MediaDeviceKind -> ShowS
Show, ReadPrec [MediaDeviceKind]
ReadPrec MediaDeviceKind
Int -> ReadS MediaDeviceKind
ReadS [MediaDeviceKind]
(Int -> ReadS MediaDeviceKind)
-> ReadS [MediaDeviceKind]
-> ReadPrec MediaDeviceKind
-> ReadPrec [MediaDeviceKind]
-> Read MediaDeviceKind
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [MediaDeviceKind]
$creadListPrec :: ReadPrec [MediaDeviceKind]
readPrec :: ReadPrec MediaDeviceKind
$creadPrec :: ReadPrec MediaDeviceKind
readList :: ReadS [MediaDeviceKind]
$creadList :: ReadS [MediaDeviceKind]
readsPrec :: Int -> ReadS MediaDeviceKind
$creadsPrec :: Int -> ReadS MediaDeviceKind
Read, MediaDeviceKind -> MediaDeviceKind -> Bool
(MediaDeviceKind -> MediaDeviceKind -> Bool)
-> (MediaDeviceKind -> MediaDeviceKind -> Bool)
-> Eq MediaDeviceKind
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MediaDeviceKind -> MediaDeviceKind -> Bool
$c/= :: MediaDeviceKind -> MediaDeviceKind -> Bool
== :: MediaDeviceKind -> MediaDeviceKind -> Bool
$c== :: MediaDeviceKind -> MediaDeviceKind -> Bool
Eq, Eq MediaDeviceKind
Eq MediaDeviceKind
-> (MediaDeviceKind -> MediaDeviceKind -> Ordering)
-> (MediaDeviceKind -> MediaDeviceKind -> Bool)
-> (MediaDeviceKind -> MediaDeviceKind -> Bool)
-> (MediaDeviceKind -> MediaDeviceKind -> Bool)
-> (MediaDeviceKind -> MediaDeviceKind -> Bool)
-> (MediaDeviceKind -> MediaDeviceKind -> MediaDeviceKind)
-> (MediaDeviceKind -> MediaDeviceKind -> MediaDeviceKind)
-> Ord MediaDeviceKind
MediaDeviceKind -> MediaDeviceKind -> Bool
MediaDeviceKind -> MediaDeviceKind -> Ordering
MediaDeviceKind -> MediaDeviceKind -> MediaDeviceKind
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: MediaDeviceKind -> MediaDeviceKind -> MediaDeviceKind
$cmin :: MediaDeviceKind -> MediaDeviceKind -> MediaDeviceKind
max :: MediaDeviceKind -> MediaDeviceKind -> MediaDeviceKind
$cmax :: MediaDeviceKind -> MediaDeviceKind -> MediaDeviceKind
>= :: MediaDeviceKind -> MediaDeviceKind -> Bool
$c>= :: MediaDeviceKind -> MediaDeviceKind -> Bool
> :: MediaDeviceKind -> MediaDeviceKind -> Bool
$c> :: MediaDeviceKind -> MediaDeviceKind -> Bool
<= :: MediaDeviceKind -> MediaDeviceKind -> Bool
$c<= :: MediaDeviceKind -> MediaDeviceKind -> Bool
< :: MediaDeviceKind -> MediaDeviceKind -> Bool
$c< :: MediaDeviceKind -> MediaDeviceKind -> Bool
compare :: MediaDeviceKind -> MediaDeviceKind -> Ordering
$ccompare :: MediaDeviceKind -> MediaDeviceKind -> Ordering
$cp1Ord :: Eq MediaDeviceKind
Ord, Typeable)
 
instance ToJSVal MediaDeviceKind where
        toJSVal :: MediaDeviceKind -> JSM JSVal
toJSVal MediaDeviceKind
MediaDeviceKindAudioinput
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_MediaDeviceKindAudioinput
        toJSVal MediaDeviceKind
MediaDeviceKindAudiooutput
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_MediaDeviceKindAudiooutput
        toJSVal MediaDeviceKind
MediaDeviceKindVideoinput
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_MediaDeviceKindVideoinput
 
instance FromJSVal MediaDeviceKind where
        fromJSVal :: JSVal -> JSM (Maybe MediaDeviceKind)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_MediaDeviceKindAudioinput JSM Bool
-> (Bool -> JSM (Maybe MediaDeviceKind))
-> JSM (Maybe MediaDeviceKind)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe MediaDeviceKind -> JSM (Maybe MediaDeviceKind)
forall (m :: * -> *) a. Monad m => a -> m a
return (MediaDeviceKind -> Maybe MediaDeviceKind
forall a. a -> Maybe a
Just MediaDeviceKind
MediaDeviceKindAudioinput)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_MediaDeviceKindAudiooutput JSM Bool
-> (Bool -> JSM (Maybe MediaDeviceKind))
-> JSM (Maybe MediaDeviceKind)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe MediaDeviceKind -> JSM (Maybe MediaDeviceKind)
forall (m :: * -> *) a. Monad m => a -> m a
return (MediaDeviceKind -> Maybe MediaDeviceKind
forall a. a -> Maybe a
Just MediaDeviceKind
MediaDeviceKindAudiooutput)
                                 Bool
False
                                   -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_MediaDeviceKindVideoinput JSM Bool
-> (Bool -> JSM (Maybe MediaDeviceKind))
-> JSM (Maybe MediaDeviceKind)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                        \ Bool
r ->
                                          case Bool
r of
                                              Bool
True -> Maybe MediaDeviceKind -> JSM (Maybe MediaDeviceKind)
forall (m :: * -> *) a. Monad m => a -> m a
return (MediaDeviceKind -> Maybe MediaDeviceKind
forall a. a -> Maybe a
Just MediaDeviceKind
MediaDeviceKindVideoinput)
                                              Bool
False -> Maybe MediaDeviceKind -> JSM (Maybe MediaDeviceKind)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe MediaDeviceKind
forall a. Maybe a
Nothing
js_MediaDeviceKindAudioinput :: String
js_MediaDeviceKindAudioinput = String
"audioinput"
js_MediaDeviceKindAudiooutput :: String
js_MediaDeviceKindAudiooutput = String
"audiooutput"
js_MediaDeviceKindVideoinput :: String
js_MediaDeviceKindVideoinput = String
"videoinput"
 
data MediaStreamTrackState = MediaStreamTrackStateLive
                           | MediaStreamTrackStateEnded
                           deriving (Int -> MediaStreamTrackState -> ShowS
[MediaStreamTrackState] -> ShowS
MediaStreamTrackState -> String
(Int -> MediaStreamTrackState -> ShowS)
-> (MediaStreamTrackState -> String)
-> ([MediaStreamTrackState] -> ShowS)
-> Show MediaStreamTrackState
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MediaStreamTrackState] -> ShowS
$cshowList :: [MediaStreamTrackState] -> ShowS
show :: MediaStreamTrackState -> String
$cshow :: MediaStreamTrackState -> String
showsPrec :: Int -> MediaStreamTrackState -> ShowS
$cshowsPrec :: Int -> MediaStreamTrackState -> ShowS
Show, ReadPrec [MediaStreamTrackState]
ReadPrec MediaStreamTrackState
Int -> ReadS MediaStreamTrackState
ReadS [MediaStreamTrackState]
(Int -> ReadS MediaStreamTrackState)
-> ReadS [MediaStreamTrackState]
-> ReadPrec MediaStreamTrackState
-> ReadPrec [MediaStreamTrackState]
-> Read MediaStreamTrackState
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [MediaStreamTrackState]
$creadListPrec :: ReadPrec [MediaStreamTrackState]
readPrec :: ReadPrec MediaStreamTrackState
$creadPrec :: ReadPrec MediaStreamTrackState
readList :: ReadS [MediaStreamTrackState]
$creadList :: ReadS [MediaStreamTrackState]
readsPrec :: Int -> ReadS MediaStreamTrackState
$creadsPrec :: Int -> ReadS MediaStreamTrackState
Read, MediaStreamTrackState -> MediaStreamTrackState -> Bool
(MediaStreamTrackState -> MediaStreamTrackState -> Bool)
-> (MediaStreamTrackState -> MediaStreamTrackState -> Bool)
-> Eq MediaStreamTrackState
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MediaStreamTrackState -> MediaStreamTrackState -> Bool
$c/= :: MediaStreamTrackState -> MediaStreamTrackState -> Bool
== :: MediaStreamTrackState -> MediaStreamTrackState -> Bool
$c== :: MediaStreamTrackState -> MediaStreamTrackState -> Bool
Eq, Eq MediaStreamTrackState
Eq MediaStreamTrackState
-> (MediaStreamTrackState -> MediaStreamTrackState -> Ordering)
-> (MediaStreamTrackState -> MediaStreamTrackState -> Bool)
-> (MediaStreamTrackState -> MediaStreamTrackState -> Bool)
-> (MediaStreamTrackState -> MediaStreamTrackState -> Bool)
-> (MediaStreamTrackState -> MediaStreamTrackState -> Bool)
-> (MediaStreamTrackState
    -> MediaStreamTrackState -> MediaStreamTrackState)
-> (MediaStreamTrackState
    -> MediaStreamTrackState -> MediaStreamTrackState)
-> Ord MediaStreamTrackState
MediaStreamTrackState -> MediaStreamTrackState -> Bool
MediaStreamTrackState -> MediaStreamTrackState -> Ordering
MediaStreamTrackState
-> MediaStreamTrackState -> MediaStreamTrackState
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: MediaStreamTrackState
-> MediaStreamTrackState -> MediaStreamTrackState
$cmin :: MediaStreamTrackState
-> MediaStreamTrackState -> MediaStreamTrackState
max :: MediaStreamTrackState
-> MediaStreamTrackState -> MediaStreamTrackState
$cmax :: MediaStreamTrackState
-> MediaStreamTrackState -> MediaStreamTrackState
>= :: MediaStreamTrackState -> MediaStreamTrackState -> Bool
$c>= :: MediaStreamTrackState -> MediaStreamTrackState -> Bool
> :: MediaStreamTrackState -> MediaStreamTrackState -> Bool
$c> :: MediaStreamTrackState -> MediaStreamTrackState -> Bool
<= :: MediaStreamTrackState -> MediaStreamTrackState -> Bool
$c<= :: MediaStreamTrackState -> MediaStreamTrackState -> Bool
< :: MediaStreamTrackState -> MediaStreamTrackState -> Bool
$c< :: MediaStreamTrackState -> MediaStreamTrackState -> Bool
compare :: MediaStreamTrackState -> MediaStreamTrackState -> Ordering
$ccompare :: MediaStreamTrackState -> MediaStreamTrackState -> Ordering
$cp1Ord :: Eq MediaStreamTrackState
Ord, Typeable)
 
instance ToJSVal MediaStreamTrackState where
        toJSVal :: MediaStreamTrackState -> JSM JSVal
toJSVal MediaStreamTrackState
MediaStreamTrackStateLive
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_MediaStreamTrackStateLive
        toJSVal MediaStreamTrackState
MediaStreamTrackStateEnded
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_MediaStreamTrackStateEnded
 
instance FromJSVal MediaStreamTrackState where
        fromJSVal :: JSVal -> JSM (Maybe MediaStreamTrackState)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_MediaStreamTrackStateLive JSM Bool
-> (Bool -> JSM (Maybe MediaStreamTrackState))
-> JSM (Maybe MediaStreamTrackState)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe MediaStreamTrackState -> JSM (Maybe MediaStreamTrackState)
forall (m :: * -> *) a. Monad m => a -> m a
return (MediaStreamTrackState -> Maybe MediaStreamTrackState
forall a. a -> Maybe a
Just MediaStreamTrackState
MediaStreamTrackStateLive)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_MediaStreamTrackStateEnded JSM Bool
-> (Bool -> JSM (Maybe MediaStreamTrackState))
-> JSM (Maybe MediaStreamTrackState)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe MediaStreamTrackState -> JSM (Maybe MediaStreamTrackState)
forall (m :: * -> *) a. Monad m => a -> m a
return (MediaStreamTrackState -> Maybe MediaStreamTrackState
forall a. a -> Maybe a
Just MediaStreamTrackState
MediaStreamTrackStateEnded)
                                 Bool
False -> Maybe MediaStreamTrackState -> JSM (Maybe MediaStreamTrackState)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe MediaStreamTrackState
forall a. Maybe a
Nothing
js_MediaStreamTrackStateLive :: String
js_MediaStreamTrackStateLive = String
"live"
js_MediaStreamTrackStateEnded :: String
js_MediaStreamTrackStateEnded = String
"ended"
 
data RTCIceTransportPolicy = RTCIceTransportPolicyRelay
                           | RTCIceTransportPolicyAll
                           deriving (Int -> RTCIceTransportPolicy -> ShowS
[RTCIceTransportPolicy] -> ShowS
RTCIceTransportPolicy -> String
(Int -> RTCIceTransportPolicy -> ShowS)
-> (RTCIceTransportPolicy -> String)
-> ([RTCIceTransportPolicy] -> ShowS)
-> Show RTCIceTransportPolicy
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RTCIceTransportPolicy] -> ShowS
$cshowList :: [RTCIceTransportPolicy] -> ShowS
show :: RTCIceTransportPolicy -> String
$cshow :: RTCIceTransportPolicy -> String
showsPrec :: Int -> RTCIceTransportPolicy -> ShowS
$cshowsPrec :: Int -> RTCIceTransportPolicy -> ShowS
Show, ReadPrec [RTCIceTransportPolicy]
ReadPrec RTCIceTransportPolicy
Int -> ReadS RTCIceTransportPolicy
ReadS [RTCIceTransportPolicy]
(Int -> ReadS RTCIceTransportPolicy)
-> ReadS [RTCIceTransportPolicy]
-> ReadPrec RTCIceTransportPolicy
-> ReadPrec [RTCIceTransportPolicy]
-> Read RTCIceTransportPolicy
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RTCIceTransportPolicy]
$creadListPrec :: ReadPrec [RTCIceTransportPolicy]
readPrec :: ReadPrec RTCIceTransportPolicy
$creadPrec :: ReadPrec RTCIceTransportPolicy
readList :: ReadS [RTCIceTransportPolicy]
$creadList :: ReadS [RTCIceTransportPolicy]
readsPrec :: Int -> ReadS RTCIceTransportPolicy
$creadsPrec :: Int -> ReadS RTCIceTransportPolicy
Read, RTCIceTransportPolicy -> RTCIceTransportPolicy -> Bool
(RTCIceTransportPolicy -> RTCIceTransportPolicy -> Bool)
-> (RTCIceTransportPolicy -> RTCIceTransportPolicy -> Bool)
-> Eq RTCIceTransportPolicy
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RTCIceTransportPolicy -> RTCIceTransportPolicy -> Bool
$c/= :: RTCIceTransportPolicy -> RTCIceTransportPolicy -> Bool
== :: RTCIceTransportPolicy -> RTCIceTransportPolicy -> Bool
$c== :: RTCIceTransportPolicy -> RTCIceTransportPolicy -> Bool
Eq, Eq RTCIceTransportPolicy
Eq RTCIceTransportPolicy
-> (RTCIceTransportPolicy -> RTCIceTransportPolicy -> Ordering)
-> (RTCIceTransportPolicy -> RTCIceTransportPolicy -> Bool)
-> (RTCIceTransportPolicy -> RTCIceTransportPolicy -> Bool)
-> (RTCIceTransportPolicy -> RTCIceTransportPolicy -> Bool)
-> (RTCIceTransportPolicy -> RTCIceTransportPolicy -> Bool)
-> (RTCIceTransportPolicy
    -> RTCIceTransportPolicy -> RTCIceTransportPolicy)
-> (RTCIceTransportPolicy
    -> RTCIceTransportPolicy -> RTCIceTransportPolicy)
-> Ord RTCIceTransportPolicy
RTCIceTransportPolicy -> RTCIceTransportPolicy -> Bool
RTCIceTransportPolicy -> RTCIceTransportPolicy -> Ordering
RTCIceTransportPolicy
-> RTCIceTransportPolicy -> RTCIceTransportPolicy
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: RTCIceTransportPolicy
-> RTCIceTransportPolicy -> RTCIceTransportPolicy
$cmin :: RTCIceTransportPolicy
-> RTCIceTransportPolicy -> RTCIceTransportPolicy
max :: RTCIceTransportPolicy
-> RTCIceTransportPolicy -> RTCIceTransportPolicy
$cmax :: RTCIceTransportPolicy
-> RTCIceTransportPolicy -> RTCIceTransportPolicy
>= :: RTCIceTransportPolicy -> RTCIceTransportPolicy -> Bool
$c>= :: RTCIceTransportPolicy -> RTCIceTransportPolicy -> Bool
> :: RTCIceTransportPolicy -> RTCIceTransportPolicy -> Bool
$c> :: RTCIceTransportPolicy -> RTCIceTransportPolicy -> Bool
<= :: RTCIceTransportPolicy -> RTCIceTransportPolicy -> Bool
$c<= :: RTCIceTransportPolicy -> RTCIceTransportPolicy -> Bool
< :: RTCIceTransportPolicy -> RTCIceTransportPolicy -> Bool
$c< :: RTCIceTransportPolicy -> RTCIceTransportPolicy -> Bool
compare :: RTCIceTransportPolicy -> RTCIceTransportPolicy -> Ordering
$ccompare :: RTCIceTransportPolicy -> RTCIceTransportPolicy -> Ordering
$cp1Ord :: Eq RTCIceTransportPolicy
Ord, Typeable)
 
instance ToJSVal RTCIceTransportPolicy where
        toJSVal :: RTCIceTransportPolicy -> JSM JSVal
toJSVal RTCIceTransportPolicy
RTCIceTransportPolicyRelay
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RTCIceTransportPolicyRelay
        toJSVal RTCIceTransportPolicy
RTCIceTransportPolicyAll
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RTCIceTransportPolicyAll
 
instance FromJSVal RTCIceTransportPolicy where
        fromJSVal :: JSVal -> JSM (Maybe RTCIceTransportPolicy)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_RTCIceTransportPolicyRelay JSM Bool
-> (Bool -> JSM (Maybe RTCIceTransportPolicy))
-> JSM (Maybe RTCIceTransportPolicy)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe RTCIceTransportPolicy -> JSM (Maybe RTCIceTransportPolicy)
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCIceTransportPolicy -> Maybe RTCIceTransportPolicy
forall a. a -> Maybe a
Just RTCIceTransportPolicy
RTCIceTransportPolicyRelay)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_RTCIceTransportPolicyAll JSM Bool
-> (Bool -> JSM (Maybe RTCIceTransportPolicy))
-> JSM (Maybe RTCIceTransportPolicy)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe RTCIceTransportPolicy -> JSM (Maybe RTCIceTransportPolicy)
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCIceTransportPolicy -> Maybe RTCIceTransportPolicy
forall a. a -> Maybe a
Just RTCIceTransportPolicy
RTCIceTransportPolicyAll)
                                 Bool
False -> Maybe RTCIceTransportPolicy -> JSM (Maybe RTCIceTransportPolicy)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe RTCIceTransportPolicy
forall a. Maybe a
Nothing
js_RTCIceTransportPolicyRelay :: String
js_RTCIceTransportPolicyRelay = String
"relay"
js_RTCIceTransportPolicyAll :: String
js_RTCIceTransportPolicyAll = String
"all"
 
data RTCBundlePolicy = RTCBundlePolicyBalanced
                     | RTCBundlePolicyMaxCompat
                     | RTCBundlePolicyMaxBundle
                     deriving (Int -> RTCBundlePolicy -> ShowS
[RTCBundlePolicy] -> ShowS
RTCBundlePolicy -> String
(Int -> RTCBundlePolicy -> ShowS)
-> (RTCBundlePolicy -> String)
-> ([RTCBundlePolicy] -> ShowS)
-> Show RTCBundlePolicy
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RTCBundlePolicy] -> ShowS
$cshowList :: [RTCBundlePolicy] -> ShowS
show :: RTCBundlePolicy -> String
$cshow :: RTCBundlePolicy -> String
showsPrec :: Int -> RTCBundlePolicy -> ShowS
$cshowsPrec :: Int -> RTCBundlePolicy -> ShowS
Show, ReadPrec [RTCBundlePolicy]
ReadPrec RTCBundlePolicy
Int -> ReadS RTCBundlePolicy
ReadS [RTCBundlePolicy]
(Int -> ReadS RTCBundlePolicy)
-> ReadS [RTCBundlePolicy]
-> ReadPrec RTCBundlePolicy
-> ReadPrec [RTCBundlePolicy]
-> Read RTCBundlePolicy
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RTCBundlePolicy]
$creadListPrec :: ReadPrec [RTCBundlePolicy]
readPrec :: ReadPrec RTCBundlePolicy
$creadPrec :: ReadPrec RTCBundlePolicy
readList :: ReadS [RTCBundlePolicy]
$creadList :: ReadS [RTCBundlePolicy]
readsPrec :: Int -> ReadS RTCBundlePolicy
$creadsPrec :: Int -> ReadS RTCBundlePolicy
Read, RTCBundlePolicy -> RTCBundlePolicy -> Bool
(RTCBundlePolicy -> RTCBundlePolicy -> Bool)
-> (RTCBundlePolicy -> RTCBundlePolicy -> Bool)
-> Eq RTCBundlePolicy
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RTCBundlePolicy -> RTCBundlePolicy -> Bool
$c/= :: RTCBundlePolicy -> RTCBundlePolicy -> Bool
== :: RTCBundlePolicy -> RTCBundlePolicy -> Bool
$c== :: RTCBundlePolicy -> RTCBundlePolicy -> Bool
Eq, Eq RTCBundlePolicy
Eq RTCBundlePolicy
-> (RTCBundlePolicy -> RTCBundlePolicy -> Ordering)
-> (RTCBundlePolicy -> RTCBundlePolicy -> Bool)
-> (RTCBundlePolicy -> RTCBundlePolicy -> Bool)
-> (RTCBundlePolicy -> RTCBundlePolicy -> Bool)
-> (RTCBundlePolicy -> RTCBundlePolicy -> Bool)
-> (RTCBundlePolicy -> RTCBundlePolicy -> RTCBundlePolicy)
-> (RTCBundlePolicy -> RTCBundlePolicy -> RTCBundlePolicy)
-> Ord RTCBundlePolicy
RTCBundlePolicy -> RTCBundlePolicy -> Bool
RTCBundlePolicy -> RTCBundlePolicy -> Ordering
RTCBundlePolicy -> RTCBundlePolicy -> RTCBundlePolicy
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: RTCBundlePolicy -> RTCBundlePolicy -> RTCBundlePolicy
$cmin :: RTCBundlePolicy -> RTCBundlePolicy -> RTCBundlePolicy
max :: RTCBundlePolicy -> RTCBundlePolicy -> RTCBundlePolicy
$cmax :: RTCBundlePolicy -> RTCBundlePolicy -> RTCBundlePolicy
>= :: RTCBundlePolicy -> RTCBundlePolicy -> Bool
$c>= :: RTCBundlePolicy -> RTCBundlePolicy -> Bool
> :: RTCBundlePolicy -> RTCBundlePolicy -> Bool
$c> :: RTCBundlePolicy -> RTCBundlePolicy -> Bool
<= :: RTCBundlePolicy -> RTCBundlePolicy -> Bool
$c<= :: RTCBundlePolicy -> RTCBundlePolicy -> Bool
< :: RTCBundlePolicy -> RTCBundlePolicy -> Bool
$c< :: RTCBundlePolicy -> RTCBundlePolicy -> Bool
compare :: RTCBundlePolicy -> RTCBundlePolicy -> Ordering
$ccompare :: RTCBundlePolicy -> RTCBundlePolicy -> Ordering
$cp1Ord :: Eq RTCBundlePolicy
Ord, Typeable)
 
instance ToJSVal RTCBundlePolicy where
        toJSVal :: RTCBundlePolicy -> JSM JSVal
toJSVal RTCBundlePolicy
RTCBundlePolicyBalanced
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RTCBundlePolicyBalanced
        toJSVal RTCBundlePolicy
RTCBundlePolicyMaxCompat
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RTCBundlePolicyMaxCompat
        toJSVal RTCBundlePolicy
RTCBundlePolicyMaxBundle
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RTCBundlePolicyMaxBundle
 
instance FromJSVal RTCBundlePolicy where
        fromJSVal :: JSVal -> JSM (Maybe RTCBundlePolicy)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_RTCBundlePolicyBalanced JSM Bool
-> (Bool -> JSM (Maybe RTCBundlePolicy))
-> JSM (Maybe RTCBundlePolicy)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe RTCBundlePolicy -> JSM (Maybe RTCBundlePolicy)
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCBundlePolicy -> Maybe RTCBundlePolicy
forall a. a -> Maybe a
Just RTCBundlePolicy
RTCBundlePolicyBalanced)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_RTCBundlePolicyMaxCompat JSM Bool
-> (Bool -> JSM (Maybe RTCBundlePolicy))
-> JSM (Maybe RTCBundlePolicy)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe RTCBundlePolicy -> JSM (Maybe RTCBundlePolicy)
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCBundlePolicy -> Maybe RTCBundlePolicy
forall a. a -> Maybe a
Just RTCBundlePolicy
RTCBundlePolicyMaxCompat)
                                 Bool
False
                                   -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_RTCBundlePolicyMaxBundle JSM Bool
-> (Bool -> JSM (Maybe RTCBundlePolicy))
-> JSM (Maybe RTCBundlePolicy)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                        \ Bool
r ->
                                          case Bool
r of
                                              Bool
True -> Maybe RTCBundlePolicy -> JSM (Maybe RTCBundlePolicy)
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCBundlePolicy -> Maybe RTCBundlePolicy
forall a. a -> Maybe a
Just RTCBundlePolicy
RTCBundlePolicyMaxBundle)
                                              Bool
False -> Maybe RTCBundlePolicy -> JSM (Maybe RTCBundlePolicy)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe RTCBundlePolicy
forall a. Maybe a
Nothing
js_RTCBundlePolicyBalanced :: String
js_RTCBundlePolicyBalanced = String
"balanced"
js_RTCBundlePolicyMaxCompat :: String
js_RTCBundlePolicyMaxCompat = String
"max-compat"
js_RTCBundlePolicyMaxBundle :: String
js_RTCBundlePolicyMaxBundle = String
"max-bundle"
 
data RTCDataChannelState = RTCDataChannelStateConnecting
                         | RTCDataChannelStateOpen
                         | RTCDataChannelStateClosing
                         | RTCDataChannelStateClosed
                         deriving (Int -> RTCDataChannelState -> ShowS
[RTCDataChannelState] -> ShowS
RTCDataChannelState -> String
(Int -> RTCDataChannelState -> ShowS)
-> (RTCDataChannelState -> String)
-> ([RTCDataChannelState] -> ShowS)
-> Show RTCDataChannelState
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RTCDataChannelState] -> ShowS
$cshowList :: [RTCDataChannelState] -> ShowS
show :: RTCDataChannelState -> String
$cshow :: RTCDataChannelState -> String
showsPrec :: Int -> RTCDataChannelState -> ShowS
$cshowsPrec :: Int -> RTCDataChannelState -> ShowS
Show, ReadPrec [RTCDataChannelState]
ReadPrec RTCDataChannelState
Int -> ReadS RTCDataChannelState
ReadS [RTCDataChannelState]
(Int -> ReadS RTCDataChannelState)
-> ReadS [RTCDataChannelState]
-> ReadPrec RTCDataChannelState
-> ReadPrec [RTCDataChannelState]
-> Read RTCDataChannelState
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RTCDataChannelState]
$creadListPrec :: ReadPrec [RTCDataChannelState]
readPrec :: ReadPrec RTCDataChannelState
$creadPrec :: ReadPrec RTCDataChannelState
readList :: ReadS [RTCDataChannelState]
$creadList :: ReadS [RTCDataChannelState]
readsPrec :: Int -> ReadS RTCDataChannelState
$creadsPrec :: Int -> ReadS RTCDataChannelState
Read, RTCDataChannelState -> RTCDataChannelState -> Bool
(RTCDataChannelState -> RTCDataChannelState -> Bool)
-> (RTCDataChannelState -> RTCDataChannelState -> Bool)
-> Eq RTCDataChannelState
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RTCDataChannelState -> RTCDataChannelState -> Bool
$c/= :: RTCDataChannelState -> RTCDataChannelState -> Bool
== :: RTCDataChannelState -> RTCDataChannelState -> Bool
$c== :: RTCDataChannelState -> RTCDataChannelState -> Bool
Eq, Eq RTCDataChannelState
Eq RTCDataChannelState
-> (RTCDataChannelState -> RTCDataChannelState -> Ordering)
-> (RTCDataChannelState -> RTCDataChannelState -> Bool)
-> (RTCDataChannelState -> RTCDataChannelState -> Bool)
-> (RTCDataChannelState -> RTCDataChannelState -> Bool)
-> (RTCDataChannelState -> RTCDataChannelState -> Bool)
-> (RTCDataChannelState
    -> RTCDataChannelState -> RTCDataChannelState)
-> (RTCDataChannelState
    -> RTCDataChannelState -> RTCDataChannelState)
-> Ord RTCDataChannelState
RTCDataChannelState -> RTCDataChannelState -> Bool
RTCDataChannelState -> RTCDataChannelState -> Ordering
RTCDataChannelState -> RTCDataChannelState -> RTCDataChannelState
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: RTCDataChannelState -> RTCDataChannelState -> RTCDataChannelState
$cmin :: RTCDataChannelState -> RTCDataChannelState -> RTCDataChannelState
max :: RTCDataChannelState -> RTCDataChannelState -> RTCDataChannelState
$cmax :: RTCDataChannelState -> RTCDataChannelState -> RTCDataChannelState
>= :: RTCDataChannelState -> RTCDataChannelState -> Bool
$c>= :: RTCDataChannelState -> RTCDataChannelState -> Bool
> :: RTCDataChannelState -> RTCDataChannelState -> Bool
$c> :: RTCDataChannelState -> RTCDataChannelState -> Bool
<= :: RTCDataChannelState -> RTCDataChannelState -> Bool
$c<= :: RTCDataChannelState -> RTCDataChannelState -> Bool
< :: RTCDataChannelState -> RTCDataChannelState -> Bool
$c< :: RTCDataChannelState -> RTCDataChannelState -> Bool
compare :: RTCDataChannelState -> RTCDataChannelState -> Ordering
$ccompare :: RTCDataChannelState -> RTCDataChannelState -> Ordering
$cp1Ord :: Eq RTCDataChannelState
Ord, Typeable)
 
instance ToJSVal RTCDataChannelState where
        toJSVal :: RTCDataChannelState -> JSM JSVal
toJSVal RTCDataChannelState
RTCDataChannelStateConnecting
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RTCDataChannelStateConnecting
        toJSVal RTCDataChannelState
RTCDataChannelStateOpen
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RTCDataChannelStateOpen
        toJSVal RTCDataChannelState
RTCDataChannelStateClosing
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RTCDataChannelStateClosing
        toJSVal RTCDataChannelState
RTCDataChannelStateClosed
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RTCDataChannelStateClosed
 
instance FromJSVal RTCDataChannelState where
        fromJSVal :: JSVal -> JSM (Maybe RTCDataChannelState)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_RTCDataChannelStateConnecting JSM Bool
-> (Bool -> JSM (Maybe RTCDataChannelState))
-> JSM (Maybe RTCDataChannelState)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe RTCDataChannelState -> JSM (Maybe RTCDataChannelState)
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCDataChannelState -> Maybe RTCDataChannelState
forall a. a -> Maybe a
Just RTCDataChannelState
RTCDataChannelStateConnecting)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_RTCDataChannelStateOpen JSM Bool
-> (Bool -> JSM (Maybe RTCDataChannelState))
-> JSM (Maybe RTCDataChannelState)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe RTCDataChannelState -> JSM (Maybe RTCDataChannelState)
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCDataChannelState -> Maybe RTCDataChannelState
forall a. a -> Maybe a
Just RTCDataChannelState
RTCDataChannelStateOpen)
                                 Bool
False
                                   -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_RTCDataChannelStateClosing JSM Bool
-> (Bool -> JSM (Maybe RTCDataChannelState))
-> JSM (Maybe RTCDataChannelState)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                        \ Bool
r ->
                                          case Bool
r of
                                              Bool
True -> Maybe RTCDataChannelState -> JSM (Maybe RTCDataChannelState)
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCDataChannelState -> Maybe RTCDataChannelState
forall a. a -> Maybe a
Just RTCDataChannelState
RTCDataChannelStateClosing)
                                              Bool
False
                                                -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_RTCDataChannelStateClosed JSM Bool
-> (Bool -> JSM (Maybe RTCDataChannelState))
-> JSM (Maybe RTCDataChannelState)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                     \ Bool
r ->
                                                       case Bool
r of
                                                           Bool
True
                                                             -> Maybe RTCDataChannelState -> JSM (Maybe RTCDataChannelState)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                  (RTCDataChannelState -> Maybe RTCDataChannelState
forall a. a -> Maybe a
Just RTCDataChannelState
RTCDataChannelStateClosed)
                                                           Bool
False -> Maybe RTCDataChannelState -> JSM (Maybe RTCDataChannelState)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe RTCDataChannelState
forall a. Maybe a
Nothing
js_RTCDataChannelStateConnecting :: String
js_RTCDataChannelStateConnecting = String
"connecting"
js_RTCDataChannelStateOpen :: String
js_RTCDataChannelStateOpen = String
"open"
js_RTCDataChannelStateClosing :: String
js_RTCDataChannelStateClosing = String
"closing"
js_RTCDataChannelStateClosed :: String
js_RTCDataChannelStateClosed = String
"closed"
 
data RTCIceConnectionState = RTCIceConnectionStateNew
                           | RTCIceConnectionStateChecking
                           | RTCIceConnectionStateConnected
                           | RTCIceConnectionStateCompleted
                           | RTCIceConnectionStateFailed
                           | RTCIceConnectionStateDisconnected
                           | RTCIceConnectionStateClosed
                           deriving (Int -> RTCIceConnectionState -> ShowS
[RTCIceConnectionState] -> ShowS
RTCIceConnectionState -> String
(Int -> RTCIceConnectionState -> ShowS)
-> (RTCIceConnectionState -> String)
-> ([RTCIceConnectionState] -> ShowS)
-> Show RTCIceConnectionState
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RTCIceConnectionState] -> ShowS
$cshowList :: [RTCIceConnectionState] -> ShowS
show :: RTCIceConnectionState -> String
$cshow :: RTCIceConnectionState -> String
showsPrec :: Int -> RTCIceConnectionState -> ShowS
$cshowsPrec :: Int -> RTCIceConnectionState -> ShowS
Show, ReadPrec [RTCIceConnectionState]
ReadPrec RTCIceConnectionState
Int -> ReadS RTCIceConnectionState
ReadS [RTCIceConnectionState]
(Int -> ReadS RTCIceConnectionState)
-> ReadS [RTCIceConnectionState]
-> ReadPrec RTCIceConnectionState
-> ReadPrec [RTCIceConnectionState]
-> Read RTCIceConnectionState
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RTCIceConnectionState]
$creadListPrec :: ReadPrec [RTCIceConnectionState]
readPrec :: ReadPrec RTCIceConnectionState
$creadPrec :: ReadPrec RTCIceConnectionState
readList :: ReadS [RTCIceConnectionState]
$creadList :: ReadS [RTCIceConnectionState]
readsPrec :: Int -> ReadS RTCIceConnectionState
$creadsPrec :: Int -> ReadS RTCIceConnectionState
Read, RTCIceConnectionState -> RTCIceConnectionState -> Bool
(RTCIceConnectionState -> RTCIceConnectionState -> Bool)
-> (RTCIceConnectionState -> RTCIceConnectionState -> Bool)
-> Eq RTCIceConnectionState
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RTCIceConnectionState -> RTCIceConnectionState -> Bool
$c/= :: RTCIceConnectionState -> RTCIceConnectionState -> Bool
== :: RTCIceConnectionState -> RTCIceConnectionState -> Bool
$c== :: RTCIceConnectionState -> RTCIceConnectionState -> Bool
Eq, Eq RTCIceConnectionState
Eq RTCIceConnectionState
-> (RTCIceConnectionState -> RTCIceConnectionState -> Ordering)
-> (RTCIceConnectionState -> RTCIceConnectionState -> Bool)
-> (RTCIceConnectionState -> RTCIceConnectionState -> Bool)
-> (RTCIceConnectionState -> RTCIceConnectionState -> Bool)
-> (RTCIceConnectionState -> RTCIceConnectionState -> Bool)
-> (RTCIceConnectionState
    -> RTCIceConnectionState -> RTCIceConnectionState)
-> (RTCIceConnectionState
    -> RTCIceConnectionState -> RTCIceConnectionState)
-> Ord RTCIceConnectionState
RTCIceConnectionState -> RTCIceConnectionState -> Bool
RTCIceConnectionState -> RTCIceConnectionState -> Ordering
RTCIceConnectionState
-> RTCIceConnectionState -> RTCIceConnectionState
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: RTCIceConnectionState
-> RTCIceConnectionState -> RTCIceConnectionState
$cmin :: RTCIceConnectionState
-> RTCIceConnectionState -> RTCIceConnectionState
max :: RTCIceConnectionState
-> RTCIceConnectionState -> RTCIceConnectionState
$cmax :: RTCIceConnectionState
-> RTCIceConnectionState -> RTCIceConnectionState
>= :: RTCIceConnectionState -> RTCIceConnectionState -> Bool
$c>= :: RTCIceConnectionState -> RTCIceConnectionState -> Bool
> :: RTCIceConnectionState -> RTCIceConnectionState -> Bool
$c> :: RTCIceConnectionState -> RTCIceConnectionState -> Bool
<= :: RTCIceConnectionState -> RTCIceConnectionState -> Bool
$c<= :: RTCIceConnectionState -> RTCIceConnectionState -> Bool
< :: RTCIceConnectionState -> RTCIceConnectionState -> Bool
$c< :: RTCIceConnectionState -> RTCIceConnectionState -> Bool
compare :: RTCIceConnectionState -> RTCIceConnectionState -> Ordering
$ccompare :: RTCIceConnectionState -> RTCIceConnectionState -> Ordering
$cp1Ord :: Eq RTCIceConnectionState
Ord, Typeable)
 
instance ToJSVal RTCIceConnectionState where
        toJSVal :: RTCIceConnectionState -> JSM JSVal
toJSVal RTCIceConnectionState
RTCIceConnectionStateNew
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RTCIceConnectionStateNew
        toJSVal RTCIceConnectionState
RTCIceConnectionStateChecking
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RTCIceConnectionStateChecking
        toJSVal RTCIceConnectionState
RTCIceConnectionStateConnected
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RTCIceConnectionStateConnected
        toJSVal RTCIceConnectionState
RTCIceConnectionStateCompleted
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RTCIceConnectionStateCompleted
        toJSVal RTCIceConnectionState
RTCIceConnectionStateFailed
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RTCIceConnectionStateFailed
        toJSVal RTCIceConnectionState
RTCIceConnectionStateDisconnected
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RTCIceConnectionStateDisconnected
        toJSVal RTCIceConnectionState
RTCIceConnectionStateClosed
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RTCIceConnectionStateClosed
 
instance FromJSVal RTCIceConnectionState where
        fromJSVal :: JSVal -> JSM (Maybe RTCIceConnectionState)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_RTCIceConnectionStateNew JSM Bool
-> (Bool -> JSM (Maybe RTCIceConnectionState))
-> JSM (Maybe RTCIceConnectionState)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe RTCIceConnectionState -> JSM (Maybe RTCIceConnectionState)
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCIceConnectionState -> Maybe RTCIceConnectionState
forall a. a -> Maybe a
Just RTCIceConnectionState
RTCIceConnectionStateNew)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_RTCIceConnectionStateChecking JSM Bool
-> (Bool -> JSM (Maybe RTCIceConnectionState))
-> JSM (Maybe RTCIceConnectionState)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe RTCIceConnectionState -> JSM (Maybe RTCIceConnectionState)
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCIceConnectionState -> Maybe RTCIceConnectionState
forall a. a -> Maybe a
Just RTCIceConnectionState
RTCIceConnectionStateChecking)
                                 Bool
False
                                   -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_RTCIceConnectionStateConnected JSM Bool
-> (Bool -> JSM (Maybe RTCIceConnectionState))
-> JSM (Maybe RTCIceConnectionState)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                        \ Bool
r ->
                                          case Bool
r of
                                              Bool
True -> Maybe RTCIceConnectionState -> JSM (Maybe RTCIceConnectionState)
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCIceConnectionState -> Maybe RTCIceConnectionState
forall a. a -> Maybe a
Just RTCIceConnectionState
RTCIceConnectionStateConnected)
                                              Bool
False
                                                -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_RTCIceConnectionStateCompleted
                                                     JSM Bool
-> (Bool -> JSM (Maybe RTCIceConnectionState))
-> JSM (Maybe RTCIceConnectionState)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                     \ Bool
r ->
                                                       case Bool
r of
                                                           Bool
True
                                                             -> Maybe RTCIceConnectionState -> JSM (Maybe RTCIceConnectionState)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                  (RTCIceConnectionState -> Maybe RTCIceConnectionState
forall a. a -> Maybe a
Just
                                                                     RTCIceConnectionState
RTCIceConnectionStateCompleted)
                                                           Bool
False
                                                             -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                                  String
js_RTCIceConnectionStateFailed
                                                                  JSM Bool
-> (Bool -> JSM (Maybe RTCIceConnectionState))
-> JSM (Maybe RTCIceConnectionState)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                  \ Bool
r ->
                                                                    case Bool
r of
                                                                        Bool
True
                                                                          -> Maybe RTCIceConnectionState -> JSM (Maybe RTCIceConnectionState)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                               (RTCIceConnectionState -> Maybe RTCIceConnectionState
forall a. a -> Maybe a
Just
                                                                                  RTCIceConnectionState
RTCIceConnectionStateFailed)
                                                                        Bool
False
                                                                          -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                                               String
js_RTCIceConnectionStateDisconnected
                                                                               JSM Bool
-> (Bool -> JSM (Maybe RTCIceConnectionState))
-> JSM (Maybe RTCIceConnectionState)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                               \ Bool
r ->
                                                                                 case Bool
r of
                                                                                     Bool
True
                                                                                       -> Maybe RTCIceConnectionState -> JSM (Maybe RTCIceConnectionState)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                                            (RTCIceConnectionState -> Maybe RTCIceConnectionState
forall a. a -> Maybe a
Just
                                                                                               RTCIceConnectionState
RTCIceConnectionStateDisconnected)
                                                                                     Bool
False
                                                                                       -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                                                            String
js_RTCIceConnectionStateClosed
                                                                                            JSM Bool
-> (Bool -> JSM (Maybe RTCIceConnectionState))
-> JSM (Maybe RTCIceConnectionState)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                                            \ Bool
r ->
                                                                                              case Bool
r
                                                                                                of
                                                                                                  Bool
True
                                                                                                    -> Maybe RTCIceConnectionState -> JSM (Maybe RTCIceConnectionState)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                                                         (RTCIceConnectionState -> Maybe RTCIceConnectionState
forall a. a -> Maybe a
Just
                                                                                                            RTCIceConnectionState
RTCIceConnectionStateClosed)
                                                                                                  Bool
False
                                                                                                    -> Maybe RTCIceConnectionState -> JSM (Maybe RTCIceConnectionState)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                                                         Maybe RTCIceConnectionState
forall a. Maybe a
Nothing
js_RTCIceConnectionStateNew :: String
js_RTCIceConnectionStateNew = String
"new"
js_RTCIceConnectionStateChecking :: String
js_RTCIceConnectionStateChecking = String
"checking"
js_RTCIceConnectionStateConnected :: String
js_RTCIceConnectionStateConnected = String
"connected"
js_RTCIceConnectionStateCompleted :: String
js_RTCIceConnectionStateCompleted = String
"completed"
js_RTCIceConnectionStateFailed :: String
js_RTCIceConnectionStateFailed = String
"failed"
js_RTCIceConnectionStateDisconnected :: String
js_RTCIceConnectionStateDisconnected = String
"disconnected"
js_RTCIceConnectionStateClosed :: String
js_RTCIceConnectionStateClosed = String
"closed"
 
data RTCIceGatheringState = RTCIceGatheringStateNew
                          | RTCIceGatheringStateGathering
                          | RTCIceGatheringStateComplete
                          deriving (Int -> RTCIceGatheringState -> ShowS
[RTCIceGatheringState] -> ShowS
RTCIceGatheringState -> String
(Int -> RTCIceGatheringState -> ShowS)
-> (RTCIceGatheringState -> String)
-> ([RTCIceGatheringState] -> ShowS)
-> Show RTCIceGatheringState
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RTCIceGatheringState] -> ShowS
$cshowList :: [RTCIceGatheringState] -> ShowS
show :: RTCIceGatheringState -> String
$cshow :: RTCIceGatheringState -> String
showsPrec :: Int -> RTCIceGatheringState -> ShowS
$cshowsPrec :: Int -> RTCIceGatheringState -> ShowS
Show, ReadPrec [RTCIceGatheringState]
ReadPrec RTCIceGatheringState
Int -> ReadS RTCIceGatheringState
ReadS [RTCIceGatheringState]
(Int -> ReadS RTCIceGatheringState)
-> ReadS [RTCIceGatheringState]
-> ReadPrec RTCIceGatheringState
-> ReadPrec [RTCIceGatheringState]
-> Read RTCIceGatheringState
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RTCIceGatheringState]
$creadListPrec :: ReadPrec [RTCIceGatheringState]
readPrec :: ReadPrec RTCIceGatheringState
$creadPrec :: ReadPrec RTCIceGatheringState
readList :: ReadS [RTCIceGatheringState]
$creadList :: ReadS [RTCIceGatheringState]
readsPrec :: Int -> ReadS RTCIceGatheringState
$creadsPrec :: Int -> ReadS RTCIceGatheringState
Read, RTCIceGatheringState -> RTCIceGatheringState -> Bool
(RTCIceGatheringState -> RTCIceGatheringState -> Bool)
-> (RTCIceGatheringState -> RTCIceGatheringState -> Bool)
-> Eq RTCIceGatheringState
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RTCIceGatheringState -> RTCIceGatheringState -> Bool
$c/= :: RTCIceGatheringState -> RTCIceGatheringState -> Bool
== :: RTCIceGatheringState -> RTCIceGatheringState -> Bool
$c== :: RTCIceGatheringState -> RTCIceGatheringState -> Bool
Eq, Eq RTCIceGatheringState
Eq RTCIceGatheringState
-> (RTCIceGatheringState -> RTCIceGatheringState -> Ordering)
-> (RTCIceGatheringState -> RTCIceGatheringState -> Bool)
-> (RTCIceGatheringState -> RTCIceGatheringState -> Bool)
-> (RTCIceGatheringState -> RTCIceGatheringState -> Bool)
-> (RTCIceGatheringState -> RTCIceGatheringState -> Bool)
-> (RTCIceGatheringState
    -> RTCIceGatheringState -> RTCIceGatheringState)
-> (RTCIceGatheringState
    -> RTCIceGatheringState -> RTCIceGatheringState)
-> Ord RTCIceGatheringState
RTCIceGatheringState -> RTCIceGatheringState -> Bool
RTCIceGatheringState -> RTCIceGatheringState -> Ordering
RTCIceGatheringState
-> RTCIceGatheringState -> RTCIceGatheringState
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: RTCIceGatheringState
-> RTCIceGatheringState -> RTCIceGatheringState
$cmin :: RTCIceGatheringState
-> RTCIceGatheringState -> RTCIceGatheringState
max :: RTCIceGatheringState
-> RTCIceGatheringState -> RTCIceGatheringState
$cmax :: RTCIceGatheringState
-> RTCIceGatheringState -> RTCIceGatheringState
>= :: RTCIceGatheringState -> RTCIceGatheringState -> Bool
$c>= :: RTCIceGatheringState -> RTCIceGatheringState -> Bool
> :: RTCIceGatheringState -> RTCIceGatheringState -> Bool
$c> :: RTCIceGatheringState -> RTCIceGatheringState -> Bool
<= :: RTCIceGatheringState -> RTCIceGatheringState -> Bool
$c<= :: RTCIceGatheringState -> RTCIceGatheringState -> Bool
< :: RTCIceGatheringState -> RTCIceGatheringState -> Bool
$c< :: RTCIceGatheringState -> RTCIceGatheringState -> Bool
compare :: RTCIceGatheringState -> RTCIceGatheringState -> Ordering
$ccompare :: RTCIceGatheringState -> RTCIceGatheringState -> Ordering
$cp1Ord :: Eq RTCIceGatheringState
Ord, Typeable)
 
instance ToJSVal RTCIceGatheringState where
        toJSVal :: RTCIceGatheringState -> JSM JSVal
toJSVal RTCIceGatheringState
RTCIceGatheringStateNew
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RTCIceGatheringStateNew
        toJSVal RTCIceGatheringState
RTCIceGatheringStateGathering
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RTCIceGatheringStateGathering
        toJSVal RTCIceGatheringState
RTCIceGatheringStateComplete
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RTCIceGatheringStateComplete
 
instance FromJSVal RTCIceGatheringState where
        fromJSVal :: JSVal -> JSM (Maybe RTCIceGatheringState)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_RTCIceGatheringStateNew JSM Bool
-> (Bool -> JSM (Maybe RTCIceGatheringState))
-> JSM (Maybe RTCIceGatheringState)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe RTCIceGatheringState -> JSM (Maybe RTCIceGatheringState)
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCIceGatheringState -> Maybe RTCIceGatheringState
forall a. a -> Maybe a
Just RTCIceGatheringState
RTCIceGatheringStateNew)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_RTCIceGatheringStateGathering JSM Bool
-> (Bool -> JSM (Maybe RTCIceGatheringState))
-> JSM (Maybe RTCIceGatheringState)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe RTCIceGatheringState -> JSM (Maybe RTCIceGatheringState)
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCIceGatheringState -> Maybe RTCIceGatheringState
forall a. a -> Maybe a
Just RTCIceGatheringState
RTCIceGatheringStateGathering)
                                 Bool
False
                                   -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_RTCIceGatheringStateComplete JSM Bool
-> (Bool -> JSM (Maybe RTCIceGatheringState))
-> JSM (Maybe RTCIceGatheringState)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                        \ Bool
r ->
                                          case Bool
r of
                                              Bool
True -> Maybe RTCIceGatheringState -> JSM (Maybe RTCIceGatheringState)
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCIceGatheringState -> Maybe RTCIceGatheringState
forall a. a -> Maybe a
Just RTCIceGatheringState
RTCIceGatheringStateComplete)
                                              Bool
False -> Maybe RTCIceGatheringState -> JSM (Maybe RTCIceGatheringState)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe RTCIceGatheringState
forall a. Maybe a
Nothing
js_RTCIceGatheringStateNew :: String
js_RTCIceGatheringStateNew = String
"new"
js_RTCIceGatheringStateGathering :: String
js_RTCIceGatheringStateGathering = String
"gathering"
js_RTCIceGatheringStateComplete :: String
js_RTCIceGatheringStateComplete = String
"complete"
 
data RTCIceTransportState = RTCIceTransportStateNew
                          | RTCIceTransportStateChecking
                          | RTCIceTransportStateConnected
                          | RTCIceTransportStateCompleted
                          | RTCIceTransportStateFailed
                          | RTCIceTransportStateDisconnected
                          | RTCIceTransportStateClosed
                          deriving (Int -> RTCIceTransportState -> ShowS
[RTCIceTransportState] -> ShowS
RTCIceTransportState -> String
(Int -> RTCIceTransportState -> ShowS)
-> (RTCIceTransportState -> String)
-> ([RTCIceTransportState] -> ShowS)
-> Show RTCIceTransportState
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RTCIceTransportState] -> ShowS
$cshowList :: [RTCIceTransportState] -> ShowS
show :: RTCIceTransportState -> String
$cshow :: RTCIceTransportState -> String
showsPrec :: Int -> RTCIceTransportState -> ShowS
$cshowsPrec :: Int -> RTCIceTransportState -> ShowS
Show, ReadPrec [RTCIceTransportState]
ReadPrec RTCIceTransportState
Int -> ReadS RTCIceTransportState
ReadS [RTCIceTransportState]
(Int -> ReadS RTCIceTransportState)
-> ReadS [RTCIceTransportState]
-> ReadPrec RTCIceTransportState
-> ReadPrec [RTCIceTransportState]
-> Read RTCIceTransportState
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RTCIceTransportState]
$creadListPrec :: ReadPrec [RTCIceTransportState]
readPrec :: ReadPrec RTCIceTransportState
$creadPrec :: ReadPrec RTCIceTransportState
readList :: ReadS [RTCIceTransportState]
$creadList :: ReadS [RTCIceTransportState]
readsPrec :: Int -> ReadS RTCIceTransportState
$creadsPrec :: Int -> ReadS RTCIceTransportState
Read, RTCIceTransportState -> RTCIceTransportState -> Bool
(RTCIceTransportState -> RTCIceTransportState -> Bool)
-> (RTCIceTransportState -> RTCIceTransportState -> Bool)
-> Eq RTCIceTransportState
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RTCIceTransportState -> RTCIceTransportState -> Bool
$c/= :: RTCIceTransportState -> RTCIceTransportState -> Bool
== :: RTCIceTransportState -> RTCIceTransportState -> Bool
$c== :: RTCIceTransportState -> RTCIceTransportState -> Bool
Eq, Eq RTCIceTransportState
Eq RTCIceTransportState
-> (RTCIceTransportState -> RTCIceTransportState -> Ordering)
-> (RTCIceTransportState -> RTCIceTransportState -> Bool)
-> (RTCIceTransportState -> RTCIceTransportState -> Bool)
-> (RTCIceTransportState -> RTCIceTransportState -> Bool)
-> (RTCIceTransportState -> RTCIceTransportState -> Bool)
-> (RTCIceTransportState
    -> RTCIceTransportState -> RTCIceTransportState)
-> (RTCIceTransportState
    -> RTCIceTransportState -> RTCIceTransportState)
-> Ord RTCIceTransportState
RTCIceTransportState -> RTCIceTransportState -> Bool
RTCIceTransportState -> RTCIceTransportState -> Ordering
RTCIceTransportState
-> RTCIceTransportState -> RTCIceTransportState
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: RTCIceTransportState
-> RTCIceTransportState -> RTCIceTransportState
$cmin :: RTCIceTransportState
-> RTCIceTransportState -> RTCIceTransportState
max :: RTCIceTransportState
-> RTCIceTransportState -> RTCIceTransportState
$cmax :: RTCIceTransportState
-> RTCIceTransportState -> RTCIceTransportState
>= :: RTCIceTransportState -> RTCIceTransportState -> Bool
$c>= :: RTCIceTransportState -> RTCIceTransportState -> Bool
> :: RTCIceTransportState -> RTCIceTransportState -> Bool
$c> :: RTCIceTransportState -> RTCIceTransportState -> Bool
<= :: RTCIceTransportState -> RTCIceTransportState -> Bool
$c<= :: RTCIceTransportState -> RTCIceTransportState -> Bool
< :: RTCIceTransportState -> RTCIceTransportState -> Bool
$c< :: RTCIceTransportState -> RTCIceTransportState -> Bool
compare :: RTCIceTransportState -> RTCIceTransportState -> Ordering
$ccompare :: RTCIceTransportState -> RTCIceTransportState -> Ordering
$cp1Ord :: Eq RTCIceTransportState
Ord, Typeable)
 
instance ToJSVal RTCIceTransportState where
        toJSVal :: RTCIceTransportState -> JSM JSVal
toJSVal RTCIceTransportState
RTCIceTransportStateNew
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RTCIceTransportStateNew
        toJSVal RTCIceTransportState
RTCIceTransportStateChecking
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RTCIceTransportStateChecking
        toJSVal RTCIceTransportState
RTCIceTransportStateConnected
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RTCIceTransportStateConnected
        toJSVal RTCIceTransportState
RTCIceTransportStateCompleted
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RTCIceTransportStateCompleted
        toJSVal RTCIceTransportState
RTCIceTransportStateFailed
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RTCIceTransportStateFailed
        toJSVal RTCIceTransportState
RTCIceTransportStateDisconnected
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RTCIceTransportStateDisconnected
        toJSVal RTCIceTransportState
RTCIceTransportStateClosed
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RTCIceTransportStateClosed
 
instance FromJSVal RTCIceTransportState where
        fromJSVal :: JSVal -> JSM (Maybe RTCIceTransportState)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_RTCIceTransportStateNew JSM Bool
-> (Bool -> JSM (Maybe RTCIceTransportState))
-> JSM (Maybe RTCIceTransportState)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe RTCIceTransportState -> JSM (Maybe RTCIceTransportState)
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCIceTransportState -> Maybe RTCIceTransportState
forall a. a -> Maybe a
Just RTCIceTransportState
RTCIceTransportStateNew)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_RTCIceTransportStateChecking JSM Bool
-> (Bool -> JSM (Maybe RTCIceTransportState))
-> JSM (Maybe RTCIceTransportState)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe RTCIceTransportState -> JSM (Maybe RTCIceTransportState)
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCIceTransportState -> Maybe RTCIceTransportState
forall a. a -> Maybe a
Just RTCIceTransportState
RTCIceTransportStateChecking)
                                 Bool
False
                                   -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_RTCIceTransportStateConnected JSM Bool
-> (Bool -> JSM (Maybe RTCIceTransportState))
-> JSM (Maybe RTCIceTransportState)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                        \ Bool
r ->
                                          case Bool
r of
                                              Bool
True -> Maybe RTCIceTransportState -> JSM (Maybe RTCIceTransportState)
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCIceTransportState -> Maybe RTCIceTransportState
forall a. a -> Maybe a
Just RTCIceTransportState
RTCIceTransportStateConnected)
                                              Bool
False
                                                -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_RTCIceTransportStateCompleted
                                                     JSM Bool
-> (Bool -> JSM (Maybe RTCIceTransportState))
-> JSM (Maybe RTCIceTransportState)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                     \ Bool
r ->
                                                       case Bool
r of
                                                           Bool
True
                                                             -> Maybe RTCIceTransportState -> JSM (Maybe RTCIceTransportState)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                  (RTCIceTransportState -> Maybe RTCIceTransportState
forall a. a -> Maybe a
Just
                                                                     RTCIceTransportState
RTCIceTransportStateCompleted)
                                                           Bool
False
                                                             -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                                  String
js_RTCIceTransportStateFailed
                                                                  JSM Bool
-> (Bool -> JSM (Maybe RTCIceTransportState))
-> JSM (Maybe RTCIceTransportState)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                  \ Bool
r ->
                                                                    case Bool
r of
                                                                        Bool
True
                                                                          -> Maybe RTCIceTransportState -> JSM (Maybe RTCIceTransportState)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                               (RTCIceTransportState -> Maybe RTCIceTransportState
forall a. a -> Maybe a
Just
                                                                                  RTCIceTransportState
RTCIceTransportStateFailed)
                                                                        Bool
False
                                                                          -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                                               String
js_RTCIceTransportStateDisconnected
                                                                               JSM Bool
-> (Bool -> JSM (Maybe RTCIceTransportState))
-> JSM (Maybe RTCIceTransportState)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                               \ Bool
r ->
                                                                                 case Bool
r of
                                                                                     Bool
True
                                                                                       -> Maybe RTCIceTransportState -> JSM (Maybe RTCIceTransportState)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                                            (RTCIceTransportState -> Maybe RTCIceTransportState
forall a. a -> Maybe a
Just
                                                                                               RTCIceTransportState
RTCIceTransportStateDisconnected)
                                                                                     Bool
False
                                                                                       -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                                                            String
js_RTCIceTransportStateClosed
                                                                                            JSM Bool
-> (Bool -> JSM (Maybe RTCIceTransportState))
-> JSM (Maybe RTCIceTransportState)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                                            \ Bool
r ->
                                                                                              case Bool
r
                                                                                                of
                                                                                                  Bool
True
                                                                                                    -> Maybe RTCIceTransportState -> JSM (Maybe RTCIceTransportState)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                                                         (RTCIceTransportState -> Maybe RTCIceTransportState
forall a. a -> Maybe a
Just
                                                                                                            RTCIceTransportState
RTCIceTransportStateClosed)
                                                                                                  Bool
False
                                                                                                    -> Maybe RTCIceTransportState -> JSM (Maybe RTCIceTransportState)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                                                         Maybe RTCIceTransportState
forall a. Maybe a
Nothing
js_RTCIceTransportStateNew :: String
js_RTCIceTransportStateNew = String
"new"
js_RTCIceTransportStateChecking :: String
js_RTCIceTransportStateChecking = String
"checking"
js_RTCIceTransportStateConnected :: String
js_RTCIceTransportStateConnected = String
"connected"
js_RTCIceTransportStateCompleted :: String
js_RTCIceTransportStateCompleted = String
"completed"
js_RTCIceTransportStateFailed :: String
js_RTCIceTransportStateFailed = String
"failed"
js_RTCIceTransportStateDisconnected :: String
js_RTCIceTransportStateDisconnected = String
"disconnected"
js_RTCIceTransportStateClosed :: String
js_RTCIceTransportStateClosed = String
"closed"
 
data RTCPeerConnectionState = RTCPeerConnectionStateNew
                            | RTCPeerConnectionStateConnecting
                            | RTCPeerConnectionStateConnected
                            | RTCPeerConnectionStateDisconnected
                            | RTCPeerConnectionStateFailed
                            | RTCPeerConnectionStateClosed
                            deriving (Int -> RTCPeerConnectionState -> ShowS
[RTCPeerConnectionState] -> ShowS
RTCPeerConnectionState -> String
(Int -> RTCPeerConnectionState -> ShowS)
-> (RTCPeerConnectionState -> String)
-> ([RTCPeerConnectionState] -> ShowS)
-> Show RTCPeerConnectionState
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RTCPeerConnectionState] -> ShowS
$cshowList :: [RTCPeerConnectionState] -> ShowS
show :: RTCPeerConnectionState -> String
$cshow :: RTCPeerConnectionState -> String
showsPrec :: Int -> RTCPeerConnectionState -> ShowS
$cshowsPrec :: Int -> RTCPeerConnectionState -> ShowS
Show, ReadPrec [RTCPeerConnectionState]
ReadPrec RTCPeerConnectionState
Int -> ReadS RTCPeerConnectionState
ReadS [RTCPeerConnectionState]
(Int -> ReadS RTCPeerConnectionState)
-> ReadS [RTCPeerConnectionState]
-> ReadPrec RTCPeerConnectionState
-> ReadPrec [RTCPeerConnectionState]
-> Read RTCPeerConnectionState
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RTCPeerConnectionState]
$creadListPrec :: ReadPrec [RTCPeerConnectionState]
readPrec :: ReadPrec RTCPeerConnectionState
$creadPrec :: ReadPrec RTCPeerConnectionState
readList :: ReadS [RTCPeerConnectionState]
$creadList :: ReadS [RTCPeerConnectionState]
readsPrec :: Int -> ReadS RTCPeerConnectionState
$creadsPrec :: Int -> ReadS RTCPeerConnectionState
Read, RTCPeerConnectionState -> RTCPeerConnectionState -> Bool
(RTCPeerConnectionState -> RTCPeerConnectionState -> Bool)
-> (RTCPeerConnectionState -> RTCPeerConnectionState -> Bool)
-> Eq RTCPeerConnectionState
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RTCPeerConnectionState -> RTCPeerConnectionState -> Bool
$c/= :: RTCPeerConnectionState -> RTCPeerConnectionState -> Bool
== :: RTCPeerConnectionState -> RTCPeerConnectionState -> Bool
$c== :: RTCPeerConnectionState -> RTCPeerConnectionState -> Bool
Eq, Eq RTCPeerConnectionState
Eq RTCPeerConnectionState
-> (RTCPeerConnectionState -> RTCPeerConnectionState -> Ordering)
-> (RTCPeerConnectionState -> RTCPeerConnectionState -> Bool)
-> (RTCPeerConnectionState -> RTCPeerConnectionState -> Bool)
-> (RTCPeerConnectionState -> RTCPeerConnectionState -> Bool)
-> (RTCPeerConnectionState -> RTCPeerConnectionState -> Bool)
-> (RTCPeerConnectionState
    -> RTCPeerConnectionState -> RTCPeerConnectionState)
-> (RTCPeerConnectionState
    -> RTCPeerConnectionState -> RTCPeerConnectionState)
-> Ord RTCPeerConnectionState
RTCPeerConnectionState -> RTCPeerConnectionState -> Bool
RTCPeerConnectionState -> RTCPeerConnectionState -> Ordering
RTCPeerConnectionState
-> RTCPeerConnectionState -> RTCPeerConnectionState
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: RTCPeerConnectionState
-> RTCPeerConnectionState -> RTCPeerConnectionState
$cmin :: RTCPeerConnectionState
-> RTCPeerConnectionState -> RTCPeerConnectionState
max :: RTCPeerConnectionState
-> RTCPeerConnectionState -> RTCPeerConnectionState
$cmax :: RTCPeerConnectionState
-> RTCPeerConnectionState -> RTCPeerConnectionState
>= :: RTCPeerConnectionState -> RTCPeerConnectionState -> Bool
$c>= :: RTCPeerConnectionState -> RTCPeerConnectionState -> Bool
> :: RTCPeerConnectionState -> RTCPeerConnectionState -> Bool
$c> :: RTCPeerConnectionState -> RTCPeerConnectionState -> Bool
<= :: RTCPeerConnectionState -> RTCPeerConnectionState -> Bool
$c<= :: RTCPeerConnectionState -> RTCPeerConnectionState -> Bool
< :: RTCPeerConnectionState -> RTCPeerConnectionState -> Bool
$c< :: RTCPeerConnectionState -> RTCPeerConnectionState -> Bool
compare :: RTCPeerConnectionState -> RTCPeerConnectionState -> Ordering
$ccompare :: RTCPeerConnectionState -> RTCPeerConnectionState -> Ordering
$cp1Ord :: Eq RTCPeerConnectionState
Ord, Typeable)
 
instance ToJSVal RTCPeerConnectionState where
        toJSVal :: RTCPeerConnectionState -> JSM JSVal
toJSVal RTCPeerConnectionState
RTCPeerConnectionStateNew
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RTCPeerConnectionStateNew
        toJSVal RTCPeerConnectionState
RTCPeerConnectionStateConnecting
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RTCPeerConnectionStateConnecting
        toJSVal RTCPeerConnectionState
RTCPeerConnectionStateConnected
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RTCPeerConnectionStateConnected
        toJSVal RTCPeerConnectionState
RTCPeerConnectionStateDisconnected
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RTCPeerConnectionStateDisconnected
        toJSVal RTCPeerConnectionState
RTCPeerConnectionStateFailed
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RTCPeerConnectionStateFailed
        toJSVal RTCPeerConnectionState
RTCPeerConnectionStateClosed
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RTCPeerConnectionStateClosed
 
instance FromJSVal RTCPeerConnectionState where
        fromJSVal :: JSVal -> JSM (Maybe RTCPeerConnectionState)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_RTCPeerConnectionStateNew JSM Bool
-> (Bool -> JSM (Maybe RTCPeerConnectionState))
-> JSM (Maybe RTCPeerConnectionState)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe RTCPeerConnectionState -> JSM (Maybe RTCPeerConnectionState)
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCPeerConnectionState -> Maybe RTCPeerConnectionState
forall a. a -> Maybe a
Just RTCPeerConnectionState
RTCPeerConnectionStateNew)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_RTCPeerConnectionStateConnecting JSM Bool
-> (Bool -> JSM (Maybe RTCPeerConnectionState))
-> JSM (Maybe RTCPeerConnectionState)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe RTCPeerConnectionState -> JSM (Maybe RTCPeerConnectionState)
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCPeerConnectionState -> Maybe RTCPeerConnectionState
forall a. a -> Maybe a
Just RTCPeerConnectionState
RTCPeerConnectionStateConnecting)
                                 Bool
False
                                   -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_RTCPeerConnectionStateConnected JSM Bool
-> (Bool -> JSM (Maybe RTCPeerConnectionState))
-> JSM (Maybe RTCPeerConnectionState)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                        \ Bool
r ->
                                          case Bool
r of
                                              Bool
True -> Maybe RTCPeerConnectionState -> JSM (Maybe RTCPeerConnectionState)
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCPeerConnectionState -> Maybe RTCPeerConnectionState
forall a. a -> Maybe a
Just RTCPeerConnectionState
RTCPeerConnectionStateConnected)
                                              Bool
False
                                                -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                     String
js_RTCPeerConnectionStateDisconnected
                                                     JSM Bool
-> (Bool -> JSM (Maybe RTCPeerConnectionState))
-> JSM (Maybe RTCPeerConnectionState)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                     \ Bool
r ->
                                                       case Bool
r of
                                                           Bool
True
                                                             -> Maybe RTCPeerConnectionState -> JSM (Maybe RTCPeerConnectionState)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                  (RTCPeerConnectionState -> Maybe RTCPeerConnectionState
forall a. a -> Maybe a
Just
                                                                     RTCPeerConnectionState
RTCPeerConnectionStateDisconnected)
                                                           Bool
False
                                                             -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                                  String
js_RTCPeerConnectionStateFailed
                                                                  JSM Bool
-> (Bool -> JSM (Maybe RTCPeerConnectionState))
-> JSM (Maybe RTCPeerConnectionState)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                  \ Bool
r ->
                                                                    case Bool
r of
                                                                        Bool
True
                                                                          -> Maybe RTCPeerConnectionState -> JSM (Maybe RTCPeerConnectionState)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                               (RTCPeerConnectionState -> Maybe RTCPeerConnectionState
forall a. a -> Maybe a
Just
                                                                                  RTCPeerConnectionState
RTCPeerConnectionStateFailed)
                                                                        Bool
False
                                                                          -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                                               String
js_RTCPeerConnectionStateClosed
                                                                               JSM Bool
-> (Bool -> JSM (Maybe RTCPeerConnectionState))
-> JSM (Maybe RTCPeerConnectionState)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                               \ Bool
r ->
                                                                                 case Bool
r of
                                                                                     Bool
True
                                                                                       -> Maybe RTCPeerConnectionState -> JSM (Maybe RTCPeerConnectionState)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                                            (RTCPeerConnectionState -> Maybe RTCPeerConnectionState
forall a. a -> Maybe a
Just
                                                                                               RTCPeerConnectionState
RTCPeerConnectionStateClosed)
                                                                                     Bool
False
                                                                                       -> Maybe RTCPeerConnectionState -> JSM (Maybe RTCPeerConnectionState)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                                            Maybe RTCPeerConnectionState
forall a. Maybe a
Nothing
js_RTCPeerConnectionStateNew :: String
js_RTCPeerConnectionStateNew = String
"new"
js_RTCPeerConnectionStateConnecting :: String
js_RTCPeerConnectionStateConnecting = String
"connecting"
js_RTCPeerConnectionStateConnected :: String
js_RTCPeerConnectionStateConnected = String
"connected"
js_RTCPeerConnectionStateDisconnected :: String
js_RTCPeerConnectionStateDisconnected = String
"disconnected"
js_RTCPeerConnectionStateFailed :: String
js_RTCPeerConnectionStateFailed = String
"failed"
js_RTCPeerConnectionStateClosed :: String
js_RTCPeerConnectionStateClosed = String
"closed"
 
data RTCDegradationPreference = RTCDegradationPreferenceMaintainFramerate
                              | RTCDegradationPreferenceMaintainResolution
                              | RTCDegradationPreferenceBalanced
                              deriving (Int -> RTCDegradationPreference -> ShowS
[RTCDegradationPreference] -> ShowS
RTCDegradationPreference -> String
(Int -> RTCDegradationPreference -> ShowS)
-> (RTCDegradationPreference -> String)
-> ([RTCDegradationPreference] -> ShowS)
-> Show RTCDegradationPreference
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RTCDegradationPreference] -> ShowS
$cshowList :: [RTCDegradationPreference] -> ShowS
show :: RTCDegradationPreference -> String
$cshow :: RTCDegradationPreference -> String
showsPrec :: Int -> RTCDegradationPreference -> ShowS
$cshowsPrec :: Int -> RTCDegradationPreference -> ShowS
Show, ReadPrec [RTCDegradationPreference]
ReadPrec RTCDegradationPreference
Int -> ReadS RTCDegradationPreference
ReadS [RTCDegradationPreference]
(Int -> ReadS RTCDegradationPreference)
-> ReadS [RTCDegradationPreference]
-> ReadPrec RTCDegradationPreference
-> ReadPrec [RTCDegradationPreference]
-> Read RTCDegradationPreference
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RTCDegradationPreference]
$creadListPrec :: ReadPrec [RTCDegradationPreference]
readPrec :: ReadPrec RTCDegradationPreference
$creadPrec :: ReadPrec RTCDegradationPreference
readList :: ReadS [RTCDegradationPreference]
$creadList :: ReadS [RTCDegradationPreference]
readsPrec :: Int -> ReadS RTCDegradationPreference
$creadsPrec :: Int -> ReadS RTCDegradationPreference
Read, RTCDegradationPreference -> RTCDegradationPreference -> Bool
(RTCDegradationPreference -> RTCDegradationPreference -> Bool)
-> (RTCDegradationPreference -> RTCDegradationPreference -> Bool)
-> Eq RTCDegradationPreference
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RTCDegradationPreference -> RTCDegradationPreference -> Bool
$c/= :: RTCDegradationPreference -> RTCDegradationPreference -> Bool
== :: RTCDegradationPreference -> RTCDegradationPreference -> Bool
$c== :: RTCDegradationPreference -> RTCDegradationPreference -> Bool
Eq, Eq RTCDegradationPreference
Eq RTCDegradationPreference
-> (RTCDegradationPreference
    -> RTCDegradationPreference -> Ordering)
-> (RTCDegradationPreference -> RTCDegradationPreference -> Bool)
-> (RTCDegradationPreference -> RTCDegradationPreference -> Bool)
-> (RTCDegradationPreference -> RTCDegradationPreference -> Bool)
-> (RTCDegradationPreference -> RTCDegradationPreference -> Bool)
-> (RTCDegradationPreference
    -> RTCDegradationPreference -> RTCDegradationPreference)
-> (RTCDegradationPreference
    -> RTCDegradationPreference -> RTCDegradationPreference)
-> Ord RTCDegradationPreference
RTCDegradationPreference -> RTCDegradationPreference -> Bool
RTCDegradationPreference -> RTCDegradationPreference -> Ordering
RTCDegradationPreference
-> RTCDegradationPreference -> RTCDegradationPreference
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: RTCDegradationPreference
-> RTCDegradationPreference -> RTCDegradationPreference
$cmin :: RTCDegradationPreference
-> RTCDegradationPreference -> RTCDegradationPreference
max :: RTCDegradationPreference
-> RTCDegradationPreference -> RTCDegradationPreference
$cmax :: RTCDegradationPreference
-> RTCDegradationPreference -> RTCDegradationPreference
>= :: RTCDegradationPreference -> RTCDegradationPreference -> Bool
$c>= :: RTCDegradationPreference -> RTCDegradationPreference -> Bool
> :: RTCDegradationPreference -> RTCDegradationPreference -> Bool
$c> :: RTCDegradationPreference -> RTCDegradationPreference -> Bool
<= :: RTCDegradationPreference -> RTCDegradationPreference -> Bool
$c<= :: RTCDegradationPreference -> RTCDegradationPreference -> Bool
< :: RTCDegradationPreference -> RTCDegradationPreference -> Bool
$c< :: RTCDegradationPreference -> RTCDegradationPreference -> Bool
compare :: RTCDegradationPreference -> RTCDegradationPreference -> Ordering
$ccompare :: RTCDegradationPreference -> RTCDegradationPreference -> Ordering
$cp1Ord :: Eq RTCDegradationPreference
Ord, Typeable)
 
instance ToJSVal RTCDegradationPreference where
        toJSVal :: RTCDegradationPreference -> JSM JSVal
toJSVal RTCDegradationPreference
RTCDegradationPreferenceMaintainFramerate
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RTCDegradationPreferenceMaintainFramerate
        toJSVal RTCDegradationPreference
RTCDegradationPreferenceMaintainResolution
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RTCDegradationPreferenceMaintainResolution
        toJSVal RTCDegradationPreference
RTCDegradationPreferenceBalanced
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RTCDegradationPreferenceBalanced
 
instance FromJSVal RTCDegradationPreference where
        fromJSVal :: JSVal -> JSM (Maybe RTCDegradationPreference)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_RTCDegradationPreferenceMaintainFramerate JSM Bool
-> (Bool -> JSM (Maybe RTCDegradationPreference))
-> JSM (Maybe RTCDegradationPreference)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe RTCDegradationPreference
-> JSM (Maybe RTCDegradationPreference)
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCDegradationPreference -> Maybe RTCDegradationPreference
forall a. a -> Maybe a
Just RTCDegradationPreference
RTCDegradationPreferenceMaintainFramerate)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_RTCDegradationPreferenceMaintainResolution
                           JSM Bool
-> (Bool -> JSM (Maybe RTCDegradationPreference))
-> JSM (Maybe RTCDegradationPreference)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe RTCDegradationPreference
-> JSM (Maybe RTCDegradationPreference)
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCDegradationPreference -> Maybe RTCDegradationPreference
forall a. a -> Maybe a
Just RTCDegradationPreference
RTCDegradationPreferenceMaintainResolution)
                                 Bool
False
                                   -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_RTCDegradationPreferenceBalanced JSM Bool
-> (Bool -> JSM (Maybe RTCDegradationPreference))
-> JSM (Maybe RTCDegradationPreference)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                        \ Bool
r ->
                                          case Bool
r of
                                              Bool
True -> Maybe RTCDegradationPreference
-> JSM (Maybe RTCDegradationPreference)
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCDegradationPreference -> Maybe RTCDegradationPreference
forall a. a -> Maybe a
Just RTCDegradationPreference
RTCDegradationPreferenceBalanced)
                                              Bool
False -> Maybe RTCDegradationPreference
-> JSM (Maybe RTCDegradationPreference)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe RTCDegradationPreference
forall a. Maybe a
Nothing
js_RTCDegradationPreferenceMaintainFramerate :: String
js_RTCDegradationPreferenceMaintainFramerate = String
"maintain-framerate"
js_RTCDegradationPreferenceMaintainResolution :: String
js_RTCDegradationPreferenceMaintainResolution
  = String
"maintain-resolution"
js_RTCDegradationPreferenceBalanced :: String
js_RTCDegradationPreferenceBalanced = String
"balanced"
 
data RTCDtxStatus = RTCDtxStatusDisabled
                  | RTCDtxStatusEnabled
                  deriving (Int -> RTCDtxStatus -> ShowS
[RTCDtxStatus] -> ShowS
RTCDtxStatus -> String
(Int -> RTCDtxStatus -> ShowS)
-> (RTCDtxStatus -> String)
-> ([RTCDtxStatus] -> ShowS)
-> Show RTCDtxStatus
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RTCDtxStatus] -> ShowS
$cshowList :: [RTCDtxStatus] -> ShowS
show :: RTCDtxStatus -> String
$cshow :: RTCDtxStatus -> String
showsPrec :: Int -> RTCDtxStatus -> ShowS
$cshowsPrec :: Int -> RTCDtxStatus -> ShowS
Show, ReadPrec [RTCDtxStatus]
ReadPrec RTCDtxStatus
Int -> ReadS RTCDtxStatus
ReadS [RTCDtxStatus]
(Int -> ReadS RTCDtxStatus)
-> ReadS [RTCDtxStatus]
-> ReadPrec RTCDtxStatus
-> ReadPrec [RTCDtxStatus]
-> Read RTCDtxStatus
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RTCDtxStatus]
$creadListPrec :: ReadPrec [RTCDtxStatus]
readPrec :: ReadPrec RTCDtxStatus
$creadPrec :: ReadPrec RTCDtxStatus
readList :: ReadS [RTCDtxStatus]
$creadList :: ReadS [RTCDtxStatus]
readsPrec :: Int -> ReadS RTCDtxStatus
$creadsPrec :: Int -> ReadS RTCDtxStatus
Read, RTCDtxStatus -> RTCDtxStatus -> Bool
(RTCDtxStatus -> RTCDtxStatus -> Bool)
-> (RTCDtxStatus -> RTCDtxStatus -> Bool) -> Eq RTCDtxStatus
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RTCDtxStatus -> RTCDtxStatus -> Bool
$c/= :: RTCDtxStatus -> RTCDtxStatus -> Bool
== :: RTCDtxStatus -> RTCDtxStatus -> Bool
$c== :: RTCDtxStatus -> RTCDtxStatus -> Bool
Eq, Eq RTCDtxStatus
Eq RTCDtxStatus
-> (RTCDtxStatus -> RTCDtxStatus -> Ordering)
-> (RTCDtxStatus -> RTCDtxStatus -> Bool)
-> (RTCDtxStatus -> RTCDtxStatus -> Bool)
-> (RTCDtxStatus -> RTCDtxStatus -> Bool)
-> (RTCDtxStatus -> RTCDtxStatus -> Bool)
-> (RTCDtxStatus -> RTCDtxStatus -> RTCDtxStatus)
-> (RTCDtxStatus -> RTCDtxStatus -> RTCDtxStatus)
-> Ord RTCDtxStatus
RTCDtxStatus -> RTCDtxStatus -> Bool
RTCDtxStatus -> RTCDtxStatus -> Ordering
RTCDtxStatus -> RTCDtxStatus -> RTCDtxStatus
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: RTCDtxStatus -> RTCDtxStatus -> RTCDtxStatus
$cmin :: RTCDtxStatus -> RTCDtxStatus -> RTCDtxStatus
max :: RTCDtxStatus -> RTCDtxStatus -> RTCDtxStatus
$cmax :: RTCDtxStatus -> RTCDtxStatus -> RTCDtxStatus
>= :: RTCDtxStatus -> RTCDtxStatus -> Bool
$c>= :: RTCDtxStatus -> RTCDtxStatus -> Bool
> :: RTCDtxStatus -> RTCDtxStatus -> Bool
$c> :: RTCDtxStatus -> RTCDtxStatus -> Bool
<= :: RTCDtxStatus -> RTCDtxStatus -> Bool
$c<= :: RTCDtxStatus -> RTCDtxStatus -> Bool
< :: RTCDtxStatus -> RTCDtxStatus -> Bool
$c< :: RTCDtxStatus -> RTCDtxStatus -> Bool
compare :: RTCDtxStatus -> RTCDtxStatus -> Ordering
$ccompare :: RTCDtxStatus -> RTCDtxStatus -> Ordering
$cp1Ord :: Eq RTCDtxStatus
Ord, Typeable)
 
instance ToJSVal RTCDtxStatus where
        toJSVal :: RTCDtxStatus -> JSM JSVal
toJSVal RTCDtxStatus
RTCDtxStatusDisabled = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RTCDtxStatusDisabled
        toJSVal RTCDtxStatus
RTCDtxStatusEnabled = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RTCDtxStatusEnabled
 
instance FromJSVal RTCDtxStatus where
        fromJSVal :: JSVal -> JSM (Maybe RTCDtxStatus)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_RTCDtxStatusDisabled JSM Bool
-> (Bool -> JSM (Maybe RTCDtxStatus)) -> JSM (Maybe RTCDtxStatus)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe RTCDtxStatus -> JSM (Maybe RTCDtxStatus)
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCDtxStatus -> Maybe RTCDtxStatus
forall a. a -> Maybe a
Just RTCDtxStatus
RTCDtxStatusDisabled)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_RTCDtxStatusEnabled JSM Bool
-> (Bool -> JSM (Maybe RTCDtxStatus)) -> JSM (Maybe RTCDtxStatus)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe RTCDtxStatus -> JSM (Maybe RTCDtxStatus)
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCDtxStatus -> Maybe RTCDtxStatus
forall a. a -> Maybe a
Just RTCDtxStatus
RTCDtxStatusEnabled)
                                 Bool
False -> Maybe RTCDtxStatus -> JSM (Maybe RTCDtxStatus)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe RTCDtxStatus
forall a. Maybe a
Nothing
js_RTCDtxStatusDisabled :: String
js_RTCDtxStatusDisabled = String
"disabled"
js_RTCDtxStatusEnabled :: String
js_RTCDtxStatusEnabled = String
"enabled"
 
data RTCPriorityType = RTCPriorityTypeVeryLow
                     | RTCPriorityTypeLow
                     | RTCPriorityTypeMedium
                     | RTCPriorityTypeHigh
                     deriving (Int -> RTCPriorityType -> ShowS
[RTCPriorityType] -> ShowS
RTCPriorityType -> String
(Int -> RTCPriorityType -> ShowS)
-> (RTCPriorityType -> String)
-> ([RTCPriorityType] -> ShowS)
-> Show RTCPriorityType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RTCPriorityType] -> ShowS
$cshowList :: [RTCPriorityType] -> ShowS
show :: RTCPriorityType -> String
$cshow :: RTCPriorityType -> String
showsPrec :: Int -> RTCPriorityType -> ShowS
$cshowsPrec :: Int -> RTCPriorityType -> ShowS
Show, ReadPrec [RTCPriorityType]
ReadPrec RTCPriorityType
Int -> ReadS RTCPriorityType
ReadS [RTCPriorityType]
(Int -> ReadS RTCPriorityType)
-> ReadS [RTCPriorityType]
-> ReadPrec RTCPriorityType
-> ReadPrec [RTCPriorityType]
-> Read RTCPriorityType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RTCPriorityType]
$creadListPrec :: ReadPrec [RTCPriorityType]
readPrec :: ReadPrec RTCPriorityType
$creadPrec :: ReadPrec RTCPriorityType
readList :: ReadS [RTCPriorityType]
$creadList :: ReadS [RTCPriorityType]
readsPrec :: Int -> ReadS RTCPriorityType
$creadsPrec :: Int -> ReadS RTCPriorityType
Read, RTCPriorityType -> RTCPriorityType -> Bool
(RTCPriorityType -> RTCPriorityType -> Bool)
-> (RTCPriorityType -> RTCPriorityType -> Bool)
-> Eq RTCPriorityType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RTCPriorityType -> RTCPriorityType -> Bool
$c/= :: RTCPriorityType -> RTCPriorityType -> Bool
== :: RTCPriorityType -> RTCPriorityType -> Bool
$c== :: RTCPriorityType -> RTCPriorityType -> Bool
Eq, Eq RTCPriorityType
Eq RTCPriorityType
-> (RTCPriorityType -> RTCPriorityType -> Ordering)
-> (RTCPriorityType -> RTCPriorityType -> Bool)
-> (RTCPriorityType -> RTCPriorityType -> Bool)
-> (RTCPriorityType -> RTCPriorityType -> Bool)
-> (RTCPriorityType -> RTCPriorityType -> Bool)
-> (RTCPriorityType -> RTCPriorityType -> RTCPriorityType)
-> (RTCPriorityType -> RTCPriorityType -> RTCPriorityType)
-> Ord RTCPriorityType
RTCPriorityType -> RTCPriorityType -> Bool
RTCPriorityType -> RTCPriorityType -> Ordering
RTCPriorityType -> RTCPriorityType -> RTCPriorityType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: RTCPriorityType -> RTCPriorityType -> RTCPriorityType
$cmin :: RTCPriorityType -> RTCPriorityType -> RTCPriorityType
max :: RTCPriorityType -> RTCPriorityType -> RTCPriorityType
$cmax :: RTCPriorityType -> RTCPriorityType -> RTCPriorityType
>= :: RTCPriorityType -> RTCPriorityType -> Bool
$c>= :: RTCPriorityType -> RTCPriorityType -> Bool
> :: RTCPriorityType -> RTCPriorityType -> Bool
$c> :: RTCPriorityType -> RTCPriorityType -> Bool
<= :: RTCPriorityType -> RTCPriorityType -> Bool
$c<= :: RTCPriorityType -> RTCPriorityType -> Bool
< :: RTCPriorityType -> RTCPriorityType -> Bool
$c< :: RTCPriorityType -> RTCPriorityType -> Bool
compare :: RTCPriorityType -> RTCPriorityType -> Ordering
$ccompare :: RTCPriorityType -> RTCPriorityType -> Ordering
$cp1Ord :: Eq RTCPriorityType
Ord, Typeable)
 
instance ToJSVal RTCPriorityType where
        toJSVal :: RTCPriorityType -> JSM JSVal
toJSVal RTCPriorityType
RTCPriorityTypeVeryLow = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RTCPriorityTypeVeryLow
        toJSVal RTCPriorityType
RTCPriorityTypeLow = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RTCPriorityTypeLow
        toJSVal RTCPriorityType
RTCPriorityTypeMedium = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RTCPriorityTypeMedium
        toJSVal RTCPriorityType
RTCPriorityTypeHigh = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RTCPriorityTypeHigh
 
instance FromJSVal RTCPriorityType where
        fromJSVal :: JSVal -> JSM (Maybe RTCPriorityType)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_RTCPriorityTypeVeryLow JSM Bool
-> (Bool -> JSM (Maybe RTCPriorityType))
-> JSM (Maybe RTCPriorityType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe RTCPriorityType -> JSM (Maybe RTCPriorityType)
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCPriorityType -> Maybe RTCPriorityType
forall a. a -> Maybe a
Just RTCPriorityType
RTCPriorityTypeVeryLow)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_RTCPriorityTypeLow JSM Bool
-> (Bool -> JSM (Maybe RTCPriorityType))
-> JSM (Maybe RTCPriorityType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe RTCPriorityType -> JSM (Maybe RTCPriorityType)
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCPriorityType -> Maybe RTCPriorityType
forall a. a -> Maybe a
Just RTCPriorityType
RTCPriorityTypeLow)
                                 Bool
False
                                   -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_RTCPriorityTypeMedium JSM Bool
-> (Bool -> JSM (Maybe RTCPriorityType))
-> JSM (Maybe RTCPriorityType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                        \ Bool
r ->
                                          case Bool
r of
                                              Bool
True -> Maybe RTCPriorityType -> JSM (Maybe RTCPriorityType)
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCPriorityType -> Maybe RTCPriorityType
forall a. a -> Maybe a
Just RTCPriorityType
RTCPriorityTypeMedium)
                                              Bool
False
                                                -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_RTCPriorityTypeHigh JSM Bool
-> (Bool -> JSM (Maybe RTCPriorityType))
-> JSM (Maybe RTCPriorityType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                     \ Bool
r ->
                                                       case Bool
r of
                                                           Bool
True -> Maybe RTCPriorityType -> JSM (Maybe RTCPriorityType)
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCPriorityType -> Maybe RTCPriorityType
forall a. a -> Maybe a
Just RTCPriorityType
RTCPriorityTypeHigh)
                                                           Bool
False -> Maybe RTCPriorityType -> JSM (Maybe RTCPriorityType)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe RTCPriorityType
forall a. Maybe a
Nothing
js_RTCPriorityTypeVeryLow :: String
js_RTCPriorityTypeVeryLow = String
"very-low"
js_RTCPriorityTypeLow :: String
js_RTCPriorityTypeLow = String
"low"
js_RTCPriorityTypeMedium :: String
js_RTCPriorityTypeMedium = String
"medium"
js_RTCPriorityTypeHigh :: String
js_RTCPriorityTypeHigh = String
"high"
 
data RTCRtpTransceiverDirection = RTCRtpTransceiverDirectionSendrecv
                                | RTCRtpTransceiverDirectionSendonly
                                | RTCRtpTransceiverDirectionRecvonly
                                | RTCRtpTransceiverDirectionInactive
                                deriving (Int -> RTCRtpTransceiverDirection -> ShowS
[RTCRtpTransceiverDirection] -> ShowS
RTCRtpTransceiverDirection -> String
(Int -> RTCRtpTransceiverDirection -> ShowS)
-> (RTCRtpTransceiverDirection -> String)
-> ([RTCRtpTransceiverDirection] -> ShowS)
-> Show RTCRtpTransceiverDirection
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RTCRtpTransceiverDirection] -> ShowS
$cshowList :: [RTCRtpTransceiverDirection] -> ShowS
show :: RTCRtpTransceiverDirection -> String
$cshow :: RTCRtpTransceiverDirection -> String
showsPrec :: Int -> RTCRtpTransceiverDirection -> ShowS
$cshowsPrec :: Int -> RTCRtpTransceiverDirection -> ShowS
Show, ReadPrec [RTCRtpTransceiverDirection]
ReadPrec RTCRtpTransceiverDirection
Int -> ReadS RTCRtpTransceiverDirection
ReadS [RTCRtpTransceiverDirection]
(Int -> ReadS RTCRtpTransceiverDirection)
-> ReadS [RTCRtpTransceiverDirection]
-> ReadPrec RTCRtpTransceiverDirection
-> ReadPrec [RTCRtpTransceiverDirection]
-> Read RTCRtpTransceiverDirection
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RTCRtpTransceiverDirection]
$creadListPrec :: ReadPrec [RTCRtpTransceiverDirection]
readPrec :: ReadPrec RTCRtpTransceiverDirection
$creadPrec :: ReadPrec RTCRtpTransceiverDirection
readList :: ReadS [RTCRtpTransceiverDirection]
$creadList :: ReadS [RTCRtpTransceiverDirection]
readsPrec :: Int -> ReadS RTCRtpTransceiverDirection
$creadsPrec :: Int -> ReadS RTCRtpTransceiverDirection
Read, RTCRtpTransceiverDirection -> RTCRtpTransceiverDirection -> Bool
(RTCRtpTransceiverDirection -> RTCRtpTransceiverDirection -> Bool)
-> (RTCRtpTransceiverDirection
    -> RTCRtpTransceiverDirection -> Bool)
-> Eq RTCRtpTransceiverDirection
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RTCRtpTransceiverDirection -> RTCRtpTransceiverDirection -> Bool
$c/= :: RTCRtpTransceiverDirection -> RTCRtpTransceiverDirection -> Bool
== :: RTCRtpTransceiverDirection -> RTCRtpTransceiverDirection -> Bool
$c== :: RTCRtpTransceiverDirection -> RTCRtpTransceiverDirection -> Bool
Eq, Eq RTCRtpTransceiverDirection
Eq RTCRtpTransceiverDirection
-> (RTCRtpTransceiverDirection
    -> RTCRtpTransceiverDirection -> Ordering)
-> (RTCRtpTransceiverDirection
    -> RTCRtpTransceiverDirection -> Bool)
-> (RTCRtpTransceiverDirection
    -> RTCRtpTransceiverDirection -> Bool)
-> (RTCRtpTransceiverDirection
    -> RTCRtpTransceiverDirection -> Bool)
-> (RTCRtpTransceiverDirection
    -> RTCRtpTransceiverDirection -> Bool)
-> (RTCRtpTransceiverDirection
    -> RTCRtpTransceiverDirection -> RTCRtpTransceiverDirection)
-> (RTCRtpTransceiverDirection
    -> RTCRtpTransceiverDirection -> RTCRtpTransceiverDirection)
-> Ord RTCRtpTransceiverDirection
RTCRtpTransceiverDirection -> RTCRtpTransceiverDirection -> Bool
RTCRtpTransceiverDirection
-> RTCRtpTransceiverDirection -> Ordering
RTCRtpTransceiverDirection
-> RTCRtpTransceiverDirection -> RTCRtpTransceiverDirection
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: RTCRtpTransceiverDirection
-> RTCRtpTransceiverDirection -> RTCRtpTransceiverDirection
$cmin :: RTCRtpTransceiverDirection
-> RTCRtpTransceiverDirection -> RTCRtpTransceiverDirection
max :: RTCRtpTransceiverDirection
-> RTCRtpTransceiverDirection -> RTCRtpTransceiverDirection
$cmax :: RTCRtpTransceiverDirection
-> RTCRtpTransceiverDirection -> RTCRtpTransceiverDirection
>= :: RTCRtpTransceiverDirection -> RTCRtpTransceiverDirection -> Bool
$c>= :: RTCRtpTransceiverDirection -> RTCRtpTransceiverDirection -> Bool
> :: RTCRtpTransceiverDirection -> RTCRtpTransceiverDirection -> Bool
$c> :: RTCRtpTransceiverDirection -> RTCRtpTransceiverDirection -> Bool
<= :: RTCRtpTransceiverDirection -> RTCRtpTransceiverDirection -> Bool
$c<= :: RTCRtpTransceiverDirection -> RTCRtpTransceiverDirection -> Bool
< :: RTCRtpTransceiverDirection -> RTCRtpTransceiverDirection -> Bool
$c< :: RTCRtpTransceiverDirection -> RTCRtpTransceiverDirection -> Bool
compare :: RTCRtpTransceiverDirection
-> RTCRtpTransceiverDirection -> Ordering
$ccompare :: RTCRtpTransceiverDirection
-> RTCRtpTransceiverDirection -> Ordering
$cp1Ord :: Eq RTCRtpTransceiverDirection
Ord, Typeable)
 
instance ToJSVal RTCRtpTransceiverDirection where
        toJSVal :: RTCRtpTransceiverDirection -> JSM JSVal
toJSVal RTCRtpTransceiverDirection
RTCRtpTransceiverDirectionSendrecv
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RTCRtpTransceiverDirectionSendrecv
        toJSVal RTCRtpTransceiverDirection
RTCRtpTransceiverDirectionSendonly
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RTCRtpTransceiverDirectionSendonly
        toJSVal RTCRtpTransceiverDirection
RTCRtpTransceiverDirectionRecvonly
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RTCRtpTransceiverDirectionRecvonly
        toJSVal RTCRtpTransceiverDirection
RTCRtpTransceiverDirectionInactive
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RTCRtpTransceiverDirectionInactive
 
instance FromJSVal RTCRtpTransceiverDirection where
        fromJSVal :: JSVal -> JSM (Maybe RTCRtpTransceiverDirection)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_RTCRtpTransceiverDirectionSendrecv JSM Bool
-> (Bool -> JSM (Maybe RTCRtpTransceiverDirection))
-> JSM (Maybe RTCRtpTransceiverDirection)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe RTCRtpTransceiverDirection
-> JSM (Maybe RTCRtpTransceiverDirection)
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCRtpTransceiverDirection -> Maybe RTCRtpTransceiverDirection
forall a. a -> Maybe a
Just RTCRtpTransceiverDirection
RTCRtpTransceiverDirectionSendrecv)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_RTCRtpTransceiverDirectionSendonly JSM Bool
-> (Bool -> JSM (Maybe RTCRtpTransceiverDirection))
-> JSM (Maybe RTCRtpTransceiverDirection)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe RTCRtpTransceiverDirection
-> JSM (Maybe RTCRtpTransceiverDirection)
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCRtpTransceiverDirection -> Maybe RTCRtpTransceiverDirection
forall a. a -> Maybe a
Just RTCRtpTransceiverDirection
RTCRtpTransceiverDirectionSendonly)
                                 Bool
False
                                   -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_RTCRtpTransceiverDirectionRecvonly JSM Bool
-> (Bool -> JSM (Maybe RTCRtpTransceiverDirection))
-> JSM (Maybe RTCRtpTransceiverDirection)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                        \ Bool
r ->
                                          case Bool
r of
                                              Bool
True
                                                -> Maybe RTCRtpTransceiverDirection
-> JSM (Maybe RTCRtpTransceiverDirection)
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCRtpTransceiverDirection -> Maybe RTCRtpTransceiverDirection
forall a. a -> Maybe a
Just RTCRtpTransceiverDirection
RTCRtpTransceiverDirectionRecvonly)
                                              Bool
False
                                                -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                     String
js_RTCRtpTransceiverDirectionInactive
                                                     JSM Bool
-> (Bool -> JSM (Maybe RTCRtpTransceiverDirection))
-> JSM (Maybe RTCRtpTransceiverDirection)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                     \ Bool
r ->
                                                       case Bool
r of
                                                           Bool
True
                                                             -> Maybe RTCRtpTransceiverDirection
-> JSM (Maybe RTCRtpTransceiverDirection)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                  (RTCRtpTransceiverDirection -> Maybe RTCRtpTransceiverDirection
forall a. a -> Maybe a
Just
                                                                     RTCRtpTransceiverDirection
RTCRtpTransceiverDirectionInactive)
                                                           Bool
False -> Maybe RTCRtpTransceiverDirection
-> JSM (Maybe RTCRtpTransceiverDirection)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe RTCRtpTransceiverDirection
forall a. Maybe a
Nothing
js_RTCRtpTransceiverDirectionSendrecv :: String
js_RTCRtpTransceiverDirectionSendrecv = String
"sendrecv"
js_RTCRtpTransceiverDirectionSendonly :: String
js_RTCRtpTransceiverDirectionSendonly = String
"sendonly"
js_RTCRtpTransceiverDirectionRecvonly :: String
js_RTCRtpTransceiverDirectionRecvonly = String
"recvonly"
js_RTCRtpTransceiverDirectionInactive :: String
js_RTCRtpTransceiverDirectionInactive = String
"inactive"
 
data RTCSdpType = RTCSdpTypeOffer
                | RTCSdpTypePranswer
                | RTCSdpTypeAnswer
                | RTCSdpTypeRollback
                deriving (Int -> RTCSdpType -> ShowS
[RTCSdpType] -> ShowS
RTCSdpType -> String
(Int -> RTCSdpType -> ShowS)
-> (RTCSdpType -> String)
-> ([RTCSdpType] -> ShowS)
-> Show RTCSdpType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RTCSdpType] -> ShowS
$cshowList :: [RTCSdpType] -> ShowS
show :: RTCSdpType -> String
$cshow :: RTCSdpType -> String
showsPrec :: Int -> RTCSdpType -> ShowS
$cshowsPrec :: Int -> RTCSdpType -> ShowS
Show, ReadPrec [RTCSdpType]
ReadPrec RTCSdpType
Int -> ReadS RTCSdpType
ReadS [RTCSdpType]
(Int -> ReadS RTCSdpType)
-> ReadS [RTCSdpType]
-> ReadPrec RTCSdpType
-> ReadPrec [RTCSdpType]
-> Read RTCSdpType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RTCSdpType]
$creadListPrec :: ReadPrec [RTCSdpType]
readPrec :: ReadPrec RTCSdpType
$creadPrec :: ReadPrec RTCSdpType
readList :: ReadS [RTCSdpType]
$creadList :: ReadS [RTCSdpType]
readsPrec :: Int -> ReadS RTCSdpType
$creadsPrec :: Int -> ReadS RTCSdpType
Read, RTCSdpType -> RTCSdpType -> Bool
(RTCSdpType -> RTCSdpType -> Bool)
-> (RTCSdpType -> RTCSdpType -> Bool) -> Eq RTCSdpType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RTCSdpType -> RTCSdpType -> Bool
$c/= :: RTCSdpType -> RTCSdpType -> Bool
== :: RTCSdpType -> RTCSdpType -> Bool
$c== :: RTCSdpType -> RTCSdpType -> Bool
Eq, Eq RTCSdpType
Eq RTCSdpType
-> (RTCSdpType -> RTCSdpType -> Ordering)
-> (RTCSdpType -> RTCSdpType -> Bool)
-> (RTCSdpType -> RTCSdpType -> Bool)
-> (RTCSdpType -> RTCSdpType -> Bool)
-> (RTCSdpType -> RTCSdpType -> Bool)
-> (RTCSdpType -> RTCSdpType -> RTCSdpType)
-> (RTCSdpType -> RTCSdpType -> RTCSdpType)
-> Ord RTCSdpType
RTCSdpType -> RTCSdpType -> Bool
RTCSdpType -> RTCSdpType -> Ordering
RTCSdpType -> RTCSdpType -> RTCSdpType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: RTCSdpType -> RTCSdpType -> RTCSdpType
$cmin :: RTCSdpType -> RTCSdpType -> RTCSdpType
max :: RTCSdpType -> RTCSdpType -> RTCSdpType
$cmax :: RTCSdpType -> RTCSdpType -> RTCSdpType
>= :: RTCSdpType -> RTCSdpType -> Bool
$c>= :: RTCSdpType -> RTCSdpType -> Bool
> :: RTCSdpType -> RTCSdpType -> Bool
$c> :: RTCSdpType -> RTCSdpType -> Bool
<= :: RTCSdpType -> RTCSdpType -> Bool
$c<= :: RTCSdpType -> RTCSdpType -> Bool
< :: RTCSdpType -> RTCSdpType -> Bool
$c< :: RTCSdpType -> RTCSdpType -> Bool
compare :: RTCSdpType -> RTCSdpType -> Ordering
$ccompare :: RTCSdpType -> RTCSdpType -> Ordering
$cp1Ord :: Eq RTCSdpType
Ord, Typeable)
 
instance ToJSVal RTCSdpType where
        toJSVal :: RTCSdpType -> JSM JSVal
toJSVal RTCSdpType
RTCSdpTypeOffer = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RTCSdpTypeOffer
        toJSVal RTCSdpType
RTCSdpTypePranswer = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RTCSdpTypePranswer
        toJSVal RTCSdpType
RTCSdpTypeAnswer = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RTCSdpTypeAnswer
        toJSVal RTCSdpType
RTCSdpTypeRollback = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RTCSdpTypeRollback
 
instance FromJSVal RTCSdpType where
        fromJSVal :: JSVal -> JSM (Maybe RTCSdpType)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_RTCSdpTypeOffer JSM Bool
-> (Bool -> JSM (Maybe RTCSdpType)) -> JSM (Maybe RTCSdpType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe RTCSdpType -> JSM (Maybe RTCSdpType)
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCSdpType -> Maybe RTCSdpType
forall a. a -> Maybe a
Just RTCSdpType
RTCSdpTypeOffer)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_RTCSdpTypePranswer JSM Bool
-> (Bool -> JSM (Maybe RTCSdpType)) -> JSM (Maybe RTCSdpType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe RTCSdpType -> JSM (Maybe RTCSdpType)
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCSdpType -> Maybe RTCSdpType
forall a. a -> Maybe a
Just RTCSdpType
RTCSdpTypePranswer)
                                 Bool
False
                                   -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_RTCSdpTypeAnswer JSM Bool
-> (Bool -> JSM (Maybe RTCSdpType)) -> JSM (Maybe RTCSdpType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                        \ Bool
r ->
                                          case Bool
r of
                                              Bool
True -> Maybe RTCSdpType -> JSM (Maybe RTCSdpType)
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCSdpType -> Maybe RTCSdpType
forall a. a -> Maybe a
Just RTCSdpType
RTCSdpTypeAnswer)
                                              Bool
False
                                                -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_RTCSdpTypeRollback JSM Bool
-> (Bool -> JSM (Maybe RTCSdpType)) -> JSM (Maybe RTCSdpType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                     \ Bool
r ->
                                                       case Bool
r of
                                                           Bool
True -> Maybe RTCSdpType -> JSM (Maybe RTCSdpType)
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCSdpType -> Maybe RTCSdpType
forall a. a -> Maybe a
Just RTCSdpType
RTCSdpTypeRollback)
                                                           Bool
False -> Maybe RTCSdpType -> JSM (Maybe RTCSdpType)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe RTCSdpType
forall a. Maybe a
Nothing
js_RTCSdpTypeOffer :: String
js_RTCSdpTypeOffer = String
"offer"
js_RTCSdpTypePranswer :: String
js_RTCSdpTypePranswer = String
"pranswer"
js_RTCSdpTypeAnswer :: String
js_RTCSdpTypeAnswer = String
"answer"
js_RTCSdpTypeRollback :: String
js_RTCSdpTypeRollback = String
"rollback"
 
data RTCSignalingState = RTCSignalingStateStable
                       | RTCSignalingStateHaveLocalOffer
                       | RTCSignalingStateHaveRemoteOffer
                       | RTCSignalingStateHaveLocalPranswer
                       | RTCSignalingStateHaveRemotePranswer
                       deriving (Int -> RTCSignalingState -> ShowS
[RTCSignalingState] -> ShowS
RTCSignalingState -> String
(Int -> RTCSignalingState -> ShowS)
-> (RTCSignalingState -> String)
-> ([RTCSignalingState] -> ShowS)
-> Show RTCSignalingState
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RTCSignalingState] -> ShowS
$cshowList :: [RTCSignalingState] -> ShowS
show :: RTCSignalingState -> String
$cshow :: RTCSignalingState -> String
showsPrec :: Int -> RTCSignalingState -> ShowS
$cshowsPrec :: Int -> RTCSignalingState -> ShowS
Show, ReadPrec [RTCSignalingState]
ReadPrec RTCSignalingState
Int -> ReadS RTCSignalingState
ReadS [RTCSignalingState]
(Int -> ReadS RTCSignalingState)
-> ReadS [RTCSignalingState]
-> ReadPrec RTCSignalingState
-> ReadPrec [RTCSignalingState]
-> Read RTCSignalingState
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RTCSignalingState]
$creadListPrec :: ReadPrec [RTCSignalingState]
readPrec :: ReadPrec RTCSignalingState
$creadPrec :: ReadPrec RTCSignalingState
readList :: ReadS [RTCSignalingState]
$creadList :: ReadS [RTCSignalingState]
readsPrec :: Int -> ReadS RTCSignalingState
$creadsPrec :: Int -> ReadS RTCSignalingState
Read, RTCSignalingState -> RTCSignalingState -> Bool
(RTCSignalingState -> RTCSignalingState -> Bool)
-> (RTCSignalingState -> RTCSignalingState -> Bool)
-> Eq RTCSignalingState
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RTCSignalingState -> RTCSignalingState -> Bool
$c/= :: RTCSignalingState -> RTCSignalingState -> Bool
== :: RTCSignalingState -> RTCSignalingState -> Bool
$c== :: RTCSignalingState -> RTCSignalingState -> Bool
Eq, Eq RTCSignalingState
Eq RTCSignalingState
-> (RTCSignalingState -> RTCSignalingState -> Ordering)
-> (RTCSignalingState -> RTCSignalingState -> Bool)
-> (RTCSignalingState -> RTCSignalingState -> Bool)
-> (RTCSignalingState -> RTCSignalingState -> Bool)
-> (RTCSignalingState -> RTCSignalingState -> Bool)
-> (RTCSignalingState -> RTCSignalingState -> RTCSignalingState)
-> (RTCSignalingState -> RTCSignalingState -> RTCSignalingState)
-> Ord RTCSignalingState
RTCSignalingState -> RTCSignalingState -> Bool
RTCSignalingState -> RTCSignalingState -> Ordering
RTCSignalingState -> RTCSignalingState -> RTCSignalingState
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: RTCSignalingState -> RTCSignalingState -> RTCSignalingState
$cmin :: RTCSignalingState -> RTCSignalingState -> RTCSignalingState
max :: RTCSignalingState -> RTCSignalingState -> RTCSignalingState
$cmax :: RTCSignalingState -> RTCSignalingState -> RTCSignalingState
>= :: RTCSignalingState -> RTCSignalingState -> Bool
$c>= :: RTCSignalingState -> RTCSignalingState -> Bool
> :: RTCSignalingState -> RTCSignalingState -> Bool
$c> :: RTCSignalingState -> RTCSignalingState -> Bool
<= :: RTCSignalingState -> RTCSignalingState -> Bool
$c<= :: RTCSignalingState -> RTCSignalingState -> Bool
< :: RTCSignalingState -> RTCSignalingState -> Bool
$c< :: RTCSignalingState -> RTCSignalingState -> Bool
compare :: RTCSignalingState -> RTCSignalingState -> Ordering
$ccompare :: RTCSignalingState -> RTCSignalingState -> Ordering
$cp1Ord :: Eq RTCSignalingState
Ord, Typeable)
 
instance ToJSVal RTCSignalingState where
        toJSVal :: RTCSignalingState -> JSM JSVal
toJSVal RTCSignalingState
RTCSignalingStateStable
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RTCSignalingStateStable
        toJSVal RTCSignalingState
RTCSignalingStateHaveLocalOffer
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RTCSignalingStateHaveLocalOffer
        toJSVal RTCSignalingState
RTCSignalingStateHaveRemoteOffer
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RTCSignalingStateHaveRemoteOffer
        toJSVal RTCSignalingState
RTCSignalingStateHaveLocalPranswer
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RTCSignalingStateHaveLocalPranswer
        toJSVal RTCSignalingState
RTCSignalingStateHaveRemotePranswer
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RTCSignalingStateHaveRemotePranswer
 
instance FromJSVal RTCSignalingState where
        fromJSVal :: JSVal -> JSM (Maybe RTCSignalingState)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_RTCSignalingStateStable JSM Bool
-> (Bool -> JSM (Maybe RTCSignalingState))
-> JSM (Maybe RTCSignalingState)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe RTCSignalingState -> JSM (Maybe RTCSignalingState)
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCSignalingState -> Maybe RTCSignalingState
forall a. a -> Maybe a
Just RTCSignalingState
RTCSignalingStateStable)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_RTCSignalingStateHaveLocalOffer JSM Bool
-> (Bool -> JSM (Maybe RTCSignalingState))
-> JSM (Maybe RTCSignalingState)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe RTCSignalingState -> JSM (Maybe RTCSignalingState)
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCSignalingState -> Maybe RTCSignalingState
forall a. a -> Maybe a
Just RTCSignalingState
RTCSignalingStateHaveLocalOffer)
                                 Bool
False
                                   -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_RTCSignalingStateHaveRemoteOffer JSM Bool
-> (Bool -> JSM (Maybe RTCSignalingState))
-> JSM (Maybe RTCSignalingState)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                        \ Bool
r ->
                                          case Bool
r of
                                              Bool
True -> Maybe RTCSignalingState -> JSM (Maybe RTCSignalingState)
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCSignalingState -> Maybe RTCSignalingState
forall a. a -> Maybe a
Just RTCSignalingState
RTCSignalingStateHaveRemoteOffer)
                                              Bool
False
                                                -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                     String
js_RTCSignalingStateHaveLocalPranswer
                                                     JSM Bool
-> (Bool -> JSM (Maybe RTCSignalingState))
-> JSM (Maybe RTCSignalingState)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                     \ Bool
r ->
                                                       case Bool
r of
                                                           Bool
True
                                                             -> Maybe RTCSignalingState -> JSM (Maybe RTCSignalingState)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                  (RTCSignalingState -> Maybe RTCSignalingState
forall a. a -> Maybe a
Just
                                                                     RTCSignalingState
RTCSignalingStateHaveLocalPranswer)
                                                           Bool
False
                                                             -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                                  String
js_RTCSignalingStateHaveRemotePranswer
                                                                  JSM Bool
-> (Bool -> JSM (Maybe RTCSignalingState))
-> JSM (Maybe RTCSignalingState)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                  \ Bool
r ->
                                                                    case Bool
r of
                                                                        Bool
True
                                                                          -> Maybe RTCSignalingState -> JSM (Maybe RTCSignalingState)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                               (RTCSignalingState -> Maybe RTCSignalingState
forall a. a -> Maybe a
Just
                                                                                  RTCSignalingState
RTCSignalingStateHaveRemotePranswer)
                                                                        Bool
False -> Maybe RTCSignalingState -> JSM (Maybe RTCSignalingState)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe RTCSignalingState
forall a. Maybe a
Nothing
js_RTCSignalingStateStable :: String
js_RTCSignalingStateStable = String
"stable"
js_RTCSignalingStateHaveLocalOffer :: String
js_RTCSignalingStateHaveLocalOffer = String
"have-local-offer"
js_RTCSignalingStateHaveRemoteOffer :: String
js_RTCSignalingStateHaveRemoteOffer = String
"have-remote-offer"
js_RTCSignalingStateHaveLocalPranswer :: String
js_RTCSignalingStateHaveLocalPranswer = String
"have-local-pranswer"
js_RTCSignalingStateHaveRemotePranswer :: String
js_RTCSignalingStateHaveRemotePranswer = String
"have-remote-pranswer"
 
data RTCStatsType = RTCStatsTypeCodec
                  | RTCStatsTypeInboundRtp
                  | RTCStatsTypeOutboundRtp
                  | RTCStatsTypePeerConnection
                  | RTCStatsTypeDataChannel
                  | RTCStatsTypeTrack
                  | RTCStatsTypeTransport
                  | RTCStatsTypeCandidatePair
                  | RTCStatsTypeLocalCandidate
                  | RTCStatsTypeRemoteCandidate
                  | RTCStatsTypeCertificate
                  deriving (Int -> RTCStatsType -> ShowS
[RTCStatsType] -> ShowS
RTCStatsType -> String
(Int -> RTCStatsType -> ShowS)
-> (RTCStatsType -> String)
-> ([RTCStatsType] -> ShowS)
-> Show RTCStatsType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RTCStatsType] -> ShowS
$cshowList :: [RTCStatsType] -> ShowS
show :: RTCStatsType -> String
$cshow :: RTCStatsType -> String
showsPrec :: Int -> RTCStatsType -> ShowS
$cshowsPrec :: Int -> RTCStatsType -> ShowS
Show, ReadPrec [RTCStatsType]
ReadPrec RTCStatsType
Int -> ReadS RTCStatsType
ReadS [RTCStatsType]
(Int -> ReadS RTCStatsType)
-> ReadS [RTCStatsType]
-> ReadPrec RTCStatsType
-> ReadPrec [RTCStatsType]
-> Read RTCStatsType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RTCStatsType]
$creadListPrec :: ReadPrec [RTCStatsType]
readPrec :: ReadPrec RTCStatsType
$creadPrec :: ReadPrec RTCStatsType
readList :: ReadS [RTCStatsType]
$creadList :: ReadS [RTCStatsType]
readsPrec :: Int -> ReadS RTCStatsType
$creadsPrec :: Int -> ReadS RTCStatsType
Read, RTCStatsType -> RTCStatsType -> Bool
(RTCStatsType -> RTCStatsType -> Bool)
-> (RTCStatsType -> RTCStatsType -> Bool) -> Eq RTCStatsType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RTCStatsType -> RTCStatsType -> Bool
$c/= :: RTCStatsType -> RTCStatsType -> Bool
== :: RTCStatsType -> RTCStatsType -> Bool
$c== :: RTCStatsType -> RTCStatsType -> Bool
Eq, Eq RTCStatsType
Eq RTCStatsType
-> (RTCStatsType -> RTCStatsType -> Ordering)
-> (RTCStatsType -> RTCStatsType -> Bool)
-> (RTCStatsType -> RTCStatsType -> Bool)
-> (RTCStatsType -> RTCStatsType -> Bool)
-> (RTCStatsType -> RTCStatsType -> Bool)
-> (RTCStatsType -> RTCStatsType -> RTCStatsType)
-> (RTCStatsType -> RTCStatsType -> RTCStatsType)
-> Ord RTCStatsType
RTCStatsType -> RTCStatsType -> Bool
RTCStatsType -> RTCStatsType -> Ordering
RTCStatsType -> RTCStatsType -> RTCStatsType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: RTCStatsType -> RTCStatsType -> RTCStatsType
$cmin :: RTCStatsType -> RTCStatsType -> RTCStatsType
max :: RTCStatsType -> RTCStatsType -> RTCStatsType
$cmax :: RTCStatsType -> RTCStatsType -> RTCStatsType
>= :: RTCStatsType -> RTCStatsType -> Bool
$c>= :: RTCStatsType -> RTCStatsType -> Bool
> :: RTCStatsType -> RTCStatsType -> Bool
$c> :: RTCStatsType -> RTCStatsType -> Bool
<= :: RTCStatsType -> RTCStatsType -> Bool
$c<= :: RTCStatsType -> RTCStatsType -> Bool
< :: RTCStatsType -> RTCStatsType -> Bool
$c< :: RTCStatsType -> RTCStatsType -> Bool
compare :: RTCStatsType -> RTCStatsType -> Ordering
$ccompare :: RTCStatsType -> RTCStatsType -> Ordering
$cp1Ord :: Eq RTCStatsType
Ord, Typeable)
 
instance ToJSVal RTCStatsType where
        toJSVal :: RTCStatsType -> JSM JSVal
toJSVal RTCStatsType
RTCStatsTypeCodec = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RTCStatsTypeCodec
        toJSVal RTCStatsType
RTCStatsTypeInboundRtp = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RTCStatsTypeInboundRtp
        toJSVal RTCStatsType
RTCStatsTypeOutboundRtp
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RTCStatsTypeOutboundRtp
        toJSVal RTCStatsType
RTCStatsTypePeerConnection
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RTCStatsTypePeerConnection
        toJSVal RTCStatsType
RTCStatsTypeDataChannel
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RTCStatsTypeDataChannel
        toJSVal RTCStatsType
RTCStatsTypeTrack = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RTCStatsTypeTrack
        toJSVal RTCStatsType
RTCStatsTypeTransport = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RTCStatsTypeTransport
        toJSVal RTCStatsType
RTCStatsTypeCandidatePair
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RTCStatsTypeCandidatePair
        toJSVal RTCStatsType
RTCStatsTypeLocalCandidate
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RTCStatsTypeLocalCandidate
        toJSVal RTCStatsType
RTCStatsTypeRemoteCandidate
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RTCStatsTypeRemoteCandidate
        toJSVal RTCStatsType
RTCStatsTypeCertificate
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_RTCStatsTypeCertificate
 
instance FromJSVal RTCStatsType where
        fromJSVal :: JSVal -> JSM (Maybe RTCStatsType)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_RTCStatsTypeCodec JSM Bool
-> (Bool -> JSM (Maybe RTCStatsType)) -> JSM (Maybe RTCStatsType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe RTCStatsType -> JSM (Maybe RTCStatsType)
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCStatsType -> Maybe RTCStatsType
forall a. a -> Maybe a
Just RTCStatsType
RTCStatsTypeCodec)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_RTCStatsTypeInboundRtp JSM Bool
-> (Bool -> JSM (Maybe RTCStatsType)) -> JSM (Maybe RTCStatsType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe RTCStatsType -> JSM (Maybe RTCStatsType)
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCStatsType -> Maybe RTCStatsType
forall a. a -> Maybe a
Just RTCStatsType
RTCStatsTypeInboundRtp)
                                 Bool
False
                                   -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_RTCStatsTypeOutboundRtp JSM Bool
-> (Bool -> JSM (Maybe RTCStatsType)) -> JSM (Maybe RTCStatsType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                        \ Bool
r ->
                                          case Bool
r of
                                              Bool
True -> Maybe RTCStatsType -> JSM (Maybe RTCStatsType)
forall (m :: * -> *) a. Monad m => a -> m a
return (RTCStatsType -> Maybe RTCStatsType
forall a. a -> Maybe a
Just RTCStatsType
RTCStatsTypeOutboundRtp)
                                              Bool
False
                                                -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_RTCStatsTypePeerConnection JSM Bool
-> (Bool -> JSM (Maybe RTCStatsType)) -> JSM (Maybe RTCStatsType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                     \ Bool
r ->
                                                       case Bool
r of
                                                           Bool
True
                                                             -> Maybe RTCStatsType -> JSM (Maybe RTCStatsType)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                  (RTCStatsType -> Maybe RTCStatsType
forall a. a -> Maybe a
Just RTCStatsType
RTCStatsTypePeerConnection)
                                                           Bool
False
                                                             -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                                  String
js_RTCStatsTypeDataChannel
                                                                  JSM Bool
-> (Bool -> JSM (Maybe RTCStatsType)) -> JSM (Maybe RTCStatsType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                  \ Bool
r ->
                                                                    case Bool
r of
                                                                        Bool
True
                                                                          -> Maybe RTCStatsType -> JSM (Maybe RTCStatsType)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                               (RTCStatsType -> Maybe RTCStatsType
forall a. a -> Maybe a
Just
                                                                                  RTCStatsType
RTCStatsTypeDataChannel)
                                                                        Bool
False
                                                                          -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                                               String
js_RTCStatsTypeTrack
                                                                               JSM Bool
-> (Bool -> JSM (Maybe RTCStatsType)) -> JSM (Maybe RTCStatsType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                               \ Bool
r ->
                                                                                 case Bool
r of
                                                                                     Bool
True
                                                                                       -> Maybe RTCStatsType -> JSM (Maybe RTCStatsType)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                                            (RTCStatsType -> Maybe RTCStatsType
forall a. a -> Maybe a
Just
                                                                                               RTCStatsType
RTCStatsTypeTrack)
                                                                                     Bool
False
                                                                                       -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                                                            String
js_RTCStatsTypeTransport
                                                                                            JSM Bool
-> (Bool -> JSM (Maybe RTCStatsType)) -> JSM (Maybe RTCStatsType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                                            \ Bool
r ->
                                                                                              case Bool
r
                                                                                                of
                                                                                                  Bool
True
                                                                                                    -> Maybe RTCStatsType -> JSM (Maybe RTCStatsType)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                                                         (RTCStatsType -> Maybe RTCStatsType
forall a. a -> Maybe a
Just
                                                                                                            RTCStatsType
RTCStatsTypeTransport)
                                                                                                  Bool
False
                                                                                                    -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                                                                         String
js_RTCStatsTypeCandidatePair
                                                                                                         JSM Bool
-> (Bool -> JSM (Maybe RTCStatsType)) -> JSM (Maybe RTCStatsType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                                                         \ Bool
r
                                                                                                           ->
                                                                                                           case
                                                                                                             Bool
r
                                                                                                             of
                                                                                                               Bool
True
                                                                                                                 -> Maybe RTCStatsType -> JSM (Maybe RTCStatsType)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                                                                      (RTCStatsType -> Maybe RTCStatsType
forall a. a -> Maybe a
Just
                                                                                                                         RTCStatsType
RTCStatsTypeCandidatePair)
                                                                                                               Bool
False
                                                                                                                 -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                                                                                      String
js_RTCStatsTypeLocalCandidate
                                                                                                                      JSM Bool
-> (Bool -> JSM (Maybe RTCStatsType)) -> JSM (Maybe RTCStatsType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                                                                      \ Bool
r
                                                                                                                        ->
                                                                                                                        case
                                                                                                                          Bool
r
                                                                                                                          of
                                                                                                                            Bool
True
                                                                                                                              -> Maybe RTCStatsType -> JSM (Maybe RTCStatsType)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                                                                                   (RTCStatsType -> Maybe RTCStatsType
forall a. a -> Maybe a
Just
                                                                                                                                      RTCStatsType
RTCStatsTypeLocalCandidate)
                                                                                                                            Bool
False
                                                                                                                              -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                                                                                                   String
js_RTCStatsTypeRemoteCandidate
                                                                                                                                   JSM Bool
-> (Bool -> JSM (Maybe RTCStatsType)) -> JSM (Maybe RTCStatsType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                                                                                   \ Bool
r
                                                                                                                                     ->
                                                                                                                                     case
                                                                                                                                       Bool
r
                                                                                                                                       of
                                                                                                                                         Bool
True
                                                                                                                                           -> Maybe RTCStatsType -> JSM (Maybe RTCStatsType)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                                                                                                (RTCStatsType -> Maybe RTCStatsType
forall a. a -> Maybe a
Just
                                                                                                                                                   RTCStatsType
RTCStatsTypeRemoteCandidate)
                                                                                                                                         Bool
False
                                                                                                                                           -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                                                                                                                String
js_RTCStatsTypeCertificate
                                                                                                                                                JSM Bool
-> (Bool -> JSM (Maybe RTCStatsType)) -> JSM (Maybe RTCStatsType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                                                                                                \ Bool
r
                                                                                                                                                  ->
                                                                                                                                                  case
                                                                                                                                                    Bool
r
                                                                                                                                                    of
                                                                                                                                                      Bool
True
                                                                                                                                                        -> Maybe RTCStatsType -> JSM (Maybe RTCStatsType)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                                                                                                             (RTCStatsType -> Maybe RTCStatsType
forall a. a -> Maybe a
Just
                                                                                                                                                                RTCStatsType
RTCStatsTypeCertificate)
                                                                                                                                                      Bool
False
                                                                                                                                                        -> Maybe RTCStatsType -> JSM (Maybe RTCStatsType)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                                                                                                             Maybe RTCStatsType
forall a. Maybe a
Nothing
js_RTCStatsTypeCodec :: String
js_RTCStatsTypeCodec = String
"codec"
js_RTCStatsTypeInboundRtp :: String
js_RTCStatsTypeInboundRtp = String
"inbound-rtp"
js_RTCStatsTypeOutboundRtp :: String
js_RTCStatsTypeOutboundRtp = String
"outbound-rtp"
js_RTCStatsTypePeerConnection :: String
js_RTCStatsTypePeerConnection = String
"peer-connection"
js_RTCStatsTypeDataChannel :: String
js_RTCStatsTypeDataChannel = String
"data-channel"
js_RTCStatsTypeTrack :: String
js_RTCStatsTypeTrack = String
"track"
js_RTCStatsTypeTransport :: String
js_RTCStatsTypeTransport = String
"transport"
js_RTCStatsTypeCandidatePair :: String
js_RTCStatsTypeCandidatePair = String
"candidate-pair"
js_RTCStatsTypeLocalCandidate :: String
js_RTCStatsTypeLocalCandidate = String
"local-candidate"
js_RTCStatsTypeRemoteCandidate :: String
js_RTCStatsTypeRemoteCandidate = String
"remote-candidate"
js_RTCStatsTypeCertificate :: String
js_RTCStatsTypeCertificate = String
"certificate"
 
data NotificationDirection = NotificationDirectionAuto
                           | NotificationDirectionLtr
                           | NotificationDirectionRtl
                           deriving (Int -> NotificationDirection -> ShowS
[NotificationDirection] -> ShowS
NotificationDirection -> String
(Int -> NotificationDirection -> ShowS)
-> (NotificationDirection -> String)
-> ([NotificationDirection] -> ShowS)
-> Show NotificationDirection
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NotificationDirection] -> ShowS
$cshowList :: [NotificationDirection] -> ShowS
show :: NotificationDirection -> String
$cshow :: NotificationDirection -> String
showsPrec :: Int -> NotificationDirection -> ShowS
$cshowsPrec :: Int -> NotificationDirection -> ShowS
Show, ReadPrec [NotificationDirection]
ReadPrec NotificationDirection
Int -> ReadS NotificationDirection
ReadS [NotificationDirection]
(Int -> ReadS NotificationDirection)
-> ReadS [NotificationDirection]
-> ReadPrec NotificationDirection
-> ReadPrec [NotificationDirection]
-> Read NotificationDirection
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [NotificationDirection]
$creadListPrec :: ReadPrec [NotificationDirection]
readPrec :: ReadPrec NotificationDirection
$creadPrec :: ReadPrec NotificationDirection
readList :: ReadS [NotificationDirection]
$creadList :: ReadS [NotificationDirection]
readsPrec :: Int -> ReadS NotificationDirection
$creadsPrec :: Int -> ReadS NotificationDirection
Read, NotificationDirection -> NotificationDirection -> Bool
(NotificationDirection -> NotificationDirection -> Bool)
-> (NotificationDirection -> NotificationDirection -> Bool)
-> Eq NotificationDirection
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NotificationDirection -> NotificationDirection -> Bool
$c/= :: NotificationDirection -> NotificationDirection -> Bool
== :: NotificationDirection -> NotificationDirection -> Bool
$c== :: NotificationDirection -> NotificationDirection -> Bool
Eq, Eq NotificationDirection
Eq NotificationDirection
-> (NotificationDirection -> NotificationDirection -> Ordering)
-> (NotificationDirection -> NotificationDirection -> Bool)
-> (NotificationDirection -> NotificationDirection -> Bool)
-> (NotificationDirection -> NotificationDirection -> Bool)
-> (NotificationDirection -> NotificationDirection -> Bool)
-> (NotificationDirection
    -> NotificationDirection -> NotificationDirection)
-> (NotificationDirection
    -> NotificationDirection -> NotificationDirection)
-> Ord NotificationDirection
NotificationDirection -> NotificationDirection -> Bool
NotificationDirection -> NotificationDirection -> Ordering
NotificationDirection
-> NotificationDirection -> NotificationDirection
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: NotificationDirection
-> NotificationDirection -> NotificationDirection
$cmin :: NotificationDirection
-> NotificationDirection -> NotificationDirection
max :: NotificationDirection
-> NotificationDirection -> NotificationDirection
$cmax :: NotificationDirection
-> NotificationDirection -> NotificationDirection
>= :: NotificationDirection -> NotificationDirection -> Bool
$c>= :: NotificationDirection -> NotificationDirection -> Bool
> :: NotificationDirection -> NotificationDirection -> Bool
$c> :: NotificationDirection -> NotificationDirection -> Bool
<= :: NotificationDirection -> NotificationDirection -> Bool
$c<= :: NotificationDirection -> NotificationDirection -> Bool
< :: NotificationDirection -> NotificationDirection -> Bool
$c< :: NotificationDirection -> NotificationDirection -> Bool
compare :: NotificationDirection -> NotificationDirection -> Ordering
$ccompare :: NotificationDirection -> NotificationDirection -> Ordering
$cp1Ord :: Eq NotificationDirection
Ord, Typeable)
 
instance ToJSVal NotificationDirection where
        toJSVal :: NotificationDirection -> JSM JSVal
toJSVal NotificationDirection
NotificationDirectionAuto
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_NotificationDirectionAuto
        toJSVal NotificationDirection
NotificationDirectionLtr
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_NotificationDirectionLtr
        toJSVal NotificationDirection
NotificationDirectionRtl
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_NotificationDirectionRtl
 
instance FromJSVal NotificationDirection where
        fromJSVal :: JSVal -> JSM (Maybe NotificationDirection)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_NotificationDirectionAuto JSM Bool
-> (Bool -> JSM (Maybe NotificationDirection))
-> JSM (Maybe NotificationDirection)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe NotificationDirection -> JSM (Maybe NotificationDirection)
forall (m :: * -> *) a. Monad m => a -> m a
return (NotificationDirection -> Maybe NotificationDirection
forall a. a -> Maybe a
Just NotificationDirection
NotificationDirectionAuto)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_NotificationDirectionLtr JSM Bool
-> (Bool -> JSM (Maybe NotificationDirection))
-> JSM (Maybe NotificationDirection)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe NotificationDirection -> JSM (Maybe NotificationDirection)
forall (m :: * -> *) a. Monad m => a -> m a
return (NotificationDirection -> Maybe NotificationDirection
forall a. a -> Maybe a
Just NotificationDirection
NotificationDirectionLtr)
                                 Bool
False
                                   -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_NotificationDirectionRtl JSM Bool
-> (Bool -> JSM (Maybe NotificationDirection))
-> JSM (Maybe NotificationDirection)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                        \ Bool
r ->
                                          case Bool
r of
                                              Bool
True -> Maybe NotificationDirection -> JSM (Maybe NotificationDirection)
forall (m :: * -> *) a. Monad m => a -> m a
return (NotificationDirection -> Maybe NotificationDirection
forall a. a -> Maybe a
Just NotificationDirection
NotificationDirectionRtl)
                                              Bool
False -> Maybe NotificationDirection -> JSM (Maybe NotificationDirection)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe NotificationDirection
forall a. Maybe a
Nothing
js_NotificationDirectionAuto :: String
js_NotificationDirectionAuto = String
"auto"
js_NotificationDirectionLtr :: String
js_NotificationDirectionLtr = String
"ltr"
js_NotificationDirectionRtl :: String
js_NotificationDirectionRtl = String
"rtl"
 
data AudioContextState = AudioContextStateSuspended
                       | AudioContextStateRunning
                       | AudioContextStateInterrupted
                       | AudioContextStateClosed
                       deriving (Int -> AudioContextState -> ShowS
[AudioContextState] -> ShowS
AudioContextState -> String
(Int -> AudioContextState -> ShowS)
-> (AudioContextState -> String)
-> ([AudioContextState] -> ShowS)
-> Show AudioContextState
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AudioContextState] -> ShowS
$cshowList :: [AudioContextState] -> ShowS
show :: AudioContextState -> String
$cshow :: AudioContextState -> String
showsPrec :: Int -> AudioContextState -> ShowS
$cshowsPrec :: Int -> AudioContextState -> ShowS
Show, ReadPrec [AudioContextState]
ReadPrec AudioContextState
Int -> ReadS AudioContextState
ReadS [AudioContextState]
(Int -> ReadS AudioContextState)
-> ReadS [AudioContextState]
-> ReadPrec AudioContextState
-> ReadPrec [AudioContextState]
-> Read AudioContextState
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AudioContextState]
$creadListPrec :: ReadPrec [AudioContextState]
readPrec :: ReadPrec AudioContextState
$creadPrec :: ReadPrec AudioContextState
readList :: ReadS [AudioContextState]
$creadList :: ReadS [AudioContextState]
readsPrec :: Int -> ReadS AudioContextState
$creadsPrec :: Int -> ReadS AudioContextState
Read, AudioContextState -> AudioContextState -> Bool
(AudioContextState -> AudioContextState -> Bool)
-> (AudioContextState -> AudioContextState -> Bool)
-> Eq AudioContextState
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AudioContextState -> AudioContextState -> Bool
$c/= :: AudioContextState -> AudioContextState -> Bool
== :: AudioContextState -> AudioContextState -> Bool
$c== :: AudioContextState -> AudioContextState -> Bool
Eq, Eq AudioContextState
Eq AudioContextState
-> (AudioContextState -> AudioContextState -> Ordering)
-> (AudioContextState -> AudioContextState -> Bool)
-> (AudioContextState -> AudioContextState -> Bool)
-> (AudioContextState -> AudioContextState -> Bool)
-> (AudioContextState -> AudioContextState -> Bool)
-> (AudioContextState -> AudioContextState -> AudioContextState)
-> (AudioContextState -> AudioContextState -> AudioContextState)
-> Ord AudioContextState
AudioContextState -> AudioContextState -> Bool
AudioContextState -> AudioContextState -> Ordering
AudioContextState -> AudioContextState -> AudioContextState
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: AudioContextState -> AudioContextState -> AudioContextState
$cmin :: AudioContextState -> AudioContextState -> AudioContextState
max :: AudioContextState -> AudioContextState -> AudioContextState
$cmax :: AudioContextState -> AudioContextState -> AudioContextState
>= :: AudioContextState -> AudioContextState -> Bool
$c>= :: AudioContextState -> AudioContextState -> Bool
> :: AudioContextState -> AudioContextState -> Bool
$c> :: AudioContextState -> AudioContextState -> Bool
<= :: AudioContextState -> AudioContextState -> Bool
$c<= :: AudioContextState -> AudioContextState -> Bool
< :: AudioContextState -> AudioContextState -> Bool
$c< :: AudioContextState -> AudioContextState -> Bool
compare :: AudioContextState -> AudioContextState -> Ordering
$ccompare :: AudioContextState -> AudioContextState -> Ordering
$cp1Ord :: Eq AudioContextState
Ord, Typeable)
 
instance ToJSVal AudioContextState where
        toJSVal :: AudioContextState -> JSM JSVal
toJSVal AudioContextState
AudioContextStateSuspended
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_AudioContextStateSuspended
        toJSVal AudioContextState
AudioContextStateRunning
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_AudioContextStateRunning
        toJSVal AudioContextState
AudioContextStateInterrupted
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_AudioContextStateInterrupted
        toJSVal AudioContextState
AudioContextStateClosed
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_AudioContextStateClosed
 
instance FromJSVal AudioContextState where
        fromJSVal :: JSVal -> JSM (Maybe AudioContextState)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_AudioContextStateSuspended JSM Bool
-> (Bool -> JSM (Maybe AudioContextState))
-> JSM (Maybe AudioContextState)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe AudioContextState -> JSM (Maybe AudioContextState)
forall (m :: * -> *) a. Monad m => a -> m a
return (AudioContextState -> Maybe AudioContextState
forall a. a -> Maybe a
Just AudioContextState
AudioContextStateSuspended)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_AudioContextStateRunning JSM Bool
-> (Bool -> JSM (Maybe AudioContextState))
-> JSM (Maybe AudioContextState)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe AudioContextState -> JSM (Maybe AudioContextState)
forall (m :: * -> *) a. Monad m => a -> m a
return (AudioContextState -> Maybe AudioContextState
forall a. a -> Maybe a
Just AudioContextState
AudioContextStateRunning)
                                 Bool
False
                                   -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_AudioContextStateInterrupted JSM Bool
-> (Bool -> JSM (Maybe AudioContextState))
-> JSM (Maybe AudioContextState)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                        \ Bool
r ->
                                          case Bool
r of
                                              Bool
True -> Maybe AudioContextState -> JSM (Maybe AudioContextState)
forall (m :: * -> *) a. Monad m => a -> m a
return (AudioContextState -> Maybe AudioContextState
forall a. a -> Maybe a
Just AudioContextState
AudioContextStateInterrupted)
                                              Bool
False
                                                -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_AudioContextStateClosed JSM Bool
-> (Bool -> JSM (Maybe AudioContextState))
-> JSM (Maybe AudioContextState)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                     \ Bool
r ->
                                                       case Bool
r of
                                                           Bool
True
                                                             -> Maybe AudioContextState -> JSM (Maybe AudioContextState)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                  (AudioContextState -> Maybe AudioContextState
forall a. a -> Maybe a
Just AudioContextState
AudioContextStateClosed)
                                                           Bool
False -> Maybe AudioContextState -> JSM (Maybe AudioContextState)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe AudioContextState
forall a. Maybe a
Nothing
js_AudioContextStateSuspended :: String
js_AudioContextStateSuspended = String
"suspended"
js_AudioContextStateRunning :: String
js_AudioContextStateRunning = String
"running"
js_AudioContextStateInterrupted :: String
js_AudioContextStateInterrupted = String
"interrupted"
js_AudioContextStateClosed :: String
js_AudioContextStateClosed = String
"closed"
 
data BiquadFilterType = BiquadFilterTypeLowpass
                      | BiquadFilterTypeHighpass
                      | BiquadFilterTypeBandpass
                      | BiquadFilterTypeLowshelf
                      | BiquadFilterTypeHighshelf
                      | BiquadFilterTypePeaking
                      | BiquadFilterTypeNotch
                      | BiquadFilterTypeAllpass
                      deriving (Int -> BiquadFilterType -> ShowS
[BiquadFilterType] -> ShowS
BiquadFilterType -> String
(Int -> BiquadFilterType -> ShowS)
-> (BiquadFilterType -> String)
-> ([BiquadFilterType] -> ShowS)
-> Show BiquadFilterType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BiquadFilterType] -> ShowS
$cshowList :: [BiquadFilterType] -> ShowS
show :: BiquadFilterType -> String
$cshow :: BiquadFilterType -> String
showsPrec :: Int -> BiquadFilterType -> ShowS
$cshowsPrec :: Int -> BiquadFilterType -> ShowS
Show, ReadPrec [BiquadFilterType]
ReadPrec BiquadFilterType
Int -> ReadS BiquadFilterType
ReadS [BiquadFilterType]
(Int -> ReadS BiquadFilterType)
-> ReadS [BiquadFilterType]
-> ReadPrec BiquadFilterType
-> ReadPrec [BiquadFilterType]
-> Read BiquadFilterType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [BiquadFilterType]
$creadListPrec :: ReadPrec [BiquadFilterType]
readPrec :: ReadPrec BiquadFilterType
$creadPrec :: ReadPrec BiquadFilterType
readList :: ReadS [BiquadFilterType]
$creadList :: ReadS [BiquadFilterType]
readsPrec :: Int -> ReadS BiquadFilterType
$creadsPrec :: Int -> ReadS BiquadFilterType
Read, BiquadFilterType -> BiquadFilterType -> Bool
(BiquadFilterType -> BiquadFilterType -> Bool)
-> (BiquadFilterType -> BiquadFilterType -> Bool)
-> Eq BiquadFilterType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BiquadFilterType -> BiquadFilterType -> Bool
$c/= :: BiquadFilterType -> BiquadFilterType -> Bool
== :: BiquadFilterType -> BiquadFilterType -> Bool
$c== :: BiquadFilterType -> BiquadFilterType -> Bool
Eq, Eq BiquadFilterType
Eq BiquadFilterType
-> (BiquadFilterType -> BiquadFilterType -> Ordering)
-> (BiquadFilterType -> BiquadFilterType -> Bool)
-> (BiquadFilterType -> BiquadFilterType -> Bool)
-> (BiquadFilterType -> BiquadFilterType -> Bool)
-> (BiquadFilterType -> BiquadFilterType -> Bool)
-> (BiquadFilterType -> BiquadFilterType -> BiquadFilterType)
-> (BiquadFilterType -> BiquadFilterType -> BiquadFilterType)
-> Ord BiquadFilterType
BiquadFilterType -> BiquadFilterType -> Bool
BiquadFilterType -> BiquadFilterType -> Ordering
BiquadFilterType -> BiquadFilterType -> BiquadFilterType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: BiquadFilterType -> BiquadFilterType -> BiquadFilterType
$cmin :: BiquadFilterType -> BiquadFilterType -> BiquadFilterType
max :: BiquadFilterType -> BiquadFilterType -> BiquadFilterType
$cmax :: BiquadFilterType -> BiquadFilterType -> BiquadFilterType
>= :: BiquadFilterType -> BiquadFilterType -> Bool
$c>= :: BiquadFilterType -> BiquadFilterType -> Bool
> :: BiquadFilterType -> BiquadFilterType -> Bool
$c> :: BiquadFilterType -> BiquadFilterType -> Bool
<= :: BiquadFilterType -> BiquadFilterType -> Bool
$c<= :: BiquadFilterType -> BiquadFilterType -> Bool
< :: BiquadFilterType -> BiquadFilterType -> Bool
$c< :: BiquadFilterType -> BiquadFilterType -> Bool
compare :: BiquadFilterType -> BiquadFilterType -> Ordering
$ccompare :: BiquadFilterType -> BiquadFilterType -> Ordering
$cp1Ord :: Eq BiquadFilterType
Ord, Typeable)
 
instance ToJSVal BiquadFilterType where
        toJSVal :: BiquadFilterType -> JSM JSVal
toJSVal BiquadFilterType
BiquadFilterTypeLowpass
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_BiquadFilterTypeLowpass
        toJSVal BiquadFilterType
BiquadFilterTypeHighpass
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_BiquadFilterTypeHighpass
        toJSVal BiquadFilterType
BiquadFilterTypeBandpass
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_BiquadFilterTypeBandpass
        toJSVal BiquadFilterType
BiquadFilterTypeLowshelf
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_BiquadFilterTypeLowshelf
        toJSVal BiquadFilterType
BiquadFilterTypeHighshelf
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_BiquadFilterTypeHighshelf
        toJSVal BiquadFilterType
BiquadFilterTypePeaking
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_BiquadFilterTypePeaking
        toJSVal BiquadFilterType
BiquadFilterTypeNotch = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_BiquadFilterTypeNotch
        toJSVal BiquadFilterType
BiquadFilterTypeAllpass
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_BiquadFilterTypeAllpass
 
instance FromJSVal BiquadFilterType where
        fromJSVal :: JSVal -> JSM (Maybe BiquadFilterType)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_BiquadFilterTypeLowpass JSM Bool
-> (Bool -> JSM (Maybe BiquadFilterType))
-> JSM (Maybe BiquadFilterType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe BiquadFilterType -> JSM (Maybe BiquadFilterType)
forall (m :: * -> *) a. Monad m => a -> m a
return (BiquadFilterType -> Maybe BiquadFilterType
forall a. a -> Maybe a
Just BiquadFilterType
BiquadFilterTypeLowpass)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_BiquadFilterTypeHighpass JSM Bool
-> (Bool -> JSM (Maybe BiquadFilterType))
-> JSM (Maybe BiquadFilterType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe BiquadFilterType -> JSM (Maybe BiquadFilterType)
forall (m :: * -> *) a. Monad m => a -> m a
return (BiquadFilterType -> Maybe BiquadFilterType
forall a. a -> Maybe a
Just BiquadFilterType
BiquadFilterTypeHighpass)
                                 Bool
False
                                   -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_BiquadFilterTypeBandpass JSM Bool
-> (Bool -> JSM (Maybe BiquadFilterType))
-> JSM (Maybe BiquadFilterType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                        \ Bool
r ->
                                          case Bool
r of
                                              Bool
True -> Maybe BiquadFilterType -> JSM (Maybe BiquadFilterType)
forall (m :: * -> *) a. Monad m => a -> m a
return (BiquadFilterType -> Maybe BiquadFilterType
forall a. a -> Maybe a
Just BiquadFilterType
BiquadFilterTypeBandpass)
                                              Bool
False
                                                -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_BiquadFilterTypeLowshelf JSM Bool
-> (Bool -> JSM (Maybe BiquadFilterType))
-> JSM (Maybe BiquadFilterType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                     \ Bool
r ->
                                                       case Bool
r of
                                                           Bool
True
                                                             -> Maybe BiquadFilterType -> JSM (Maybe BiquadFilterType)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                  (BiquadFilterType -> Maybe BiquadFilterType
forall a. a -> Maybe a
Just BiquadFilterType
BiquadFilterTypeLowshelf)
                                                           Bool
False
                                                             -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                                  String
js_BiquadFilterTypeHighshelf
                                                                  JSM Bool
-> (Bool -> JSM (Maybe BiquadFilterType))
-> JSM (Maybe BiquadFilterType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                  \ Bool
r ->
                                                                    case Bool
r of
                                                                        Bool
True
                                                                          -> Maybe BiquadFilterType -> JSM (Maybe BiquadFilterType)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                               (BiquadFilterType -> Maybe BiquadFilterType
forall a. a -> Maybe a
Just
                                                                                  BiquadFilterType
BiquadFilterTypeHighshelf)
                                                                        Bool
False
                                                                          -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                                               String
js_BiquadFilterTypePeaking
                                                                               JSM Bool
-> (Bool -> JSM (Maybe BiquadFilterType))
-> JSM (Maybe BiquadFilterType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                               \ Bool
r ->
                                                                                 case Bool
r of
                                                                                     Bool
True
                                                                                       -> Maybe BiquadFilterType -> JSM (Maybe BiquadFilterType)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                                            (BiquadFilterType -> Maybe BiquadFilterType
forall a. a -> Maybe a
Just
                                                                                               BiquadFilterType
BiquadFilterTypePeaking)
                                                                                     Bool
False
                                                                                       -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                                                            String
js_BiquadFilterTypeNotch
                                                                                            JSM Bool
-> (Bool -> JSM (Maybe BiquadFilterType))
-> JSM (Maybe BiquadFilterType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                                            \ Bool
r ->
                                                                                              case Bool
r
                                                                                                of
                                                                                                  Bool
True
                                                                                                    -> Maybe BiquadFilterType -> JSM (Maybe BiquadFilterType)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                                                         (BiquadFilterType -> Maybe BiquadFilterType
forall a. a -> Maybe a
Just
                                                                                                            BiquadFilterType
BiquadFilterTypeNotch)
                                                                                                  Bool
False
                                                                                                    -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                                                                         String
js_BiquadFilterTypeAllpass
                                                                                                         JSM Bool
-> (Bool -> JSM (Maybe BiquadFilterType))
-> JSM (Maybe BiquadFilterType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                                                         \ Bool
r
                                                                                                           ->
                                                                                                           case
                                                                                                             Bool
r
                                                                                                             of
                                                                                                               Bool
True
                                                                                                                 -> Maybe BiquadFilterType -> JSM (Maybe BiquadFilterType)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                                                                      (BiquadFilterType -> Maybe BiquadFilterType
forall a. a -> Maybe a
Just
                                                                                                                         BiquadFilterType
BiquadFilterTypeAllpass)
                                                                                                               Bool
False
                                                                                                                 -> Maybe BiquadFilterType -> JSM (Maybe BiquadFilterType)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                                                                      Maybe BiquadFilterType
forall a. Maybe a
Nothing
js_BiquadFilterTypeLowpass :: String
js_BiquadFilterTypeLowpass = String
"lowpass"
js_BiquadFilterTypeHighpass :: String
js_BiquadFilterTypeHighpass = String
"highpass"
js_BiquadFilterTypeBandpass :: String
js_BiquadFilterTypeBandpass = String
"bandpass"
js_BiquadFilterTypeLowshelf :: String
js_BiquadFilterTypeLowshelf = String
"lowshelf"
js_BiquadFilterTypeHighshelf :: String
js_BiquadFilterTypeHighshelf = String
"highshelf"
js_BiquadFilterTypePeaking :: String
js_BiquadFilterTypePeaking = String
"peaking"
js_BiquadFilterTypeNotch :: String
js_BiquadFilterTypeNotch = String
"notch"
js_BiquadFilterTypeAllpass :: String
js_BiquadFilterTypeAllpass = String
"allpass"
 
data OscillatorType = OscillatorTypeSine
                    | OscillatorTypeSquare
                    | OscillatorTypeSawtooth
                    | OscillatorTypeTriangle
                    | OscillatorTypeCustom
                    deriving (Int -> OscillatorType -> ShowS
[OscillatorType] -> ShowS
OscillatorType -> String
(Int -> OscillatorType -> ShowS)
-> (OscillatorType -> String)
-> ([OscillatorType] -> ShowS)
-> Show OscillatorType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [OscillatorType] -> ShowS
$cshowList :: [OscillatorType] -> ShowS
show :: OscillatorType -> String
$cshow :: OscillatorType -> String
showsPrec :: Int -> OscillatorType -> ShowS
$cshowsPrec :: Int -> OscillatorType -> ShowS
Show, ReadPrec [OscillatorType]
ReadPrec OscillatorType
Int -> ReadS OscillatorType
ReadS [OscillatorType]
(Int -> ReadS OscillatorType)
-> ReadS [OscillatorType]
-> ReadPrec OscillatorType
-> ReadPrec [OscillatorType]
-> Read OscillatorType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [OscillatorType]
$creadListPrec :: ReadPrec [OscillatorType]
readPrec :: ReadPrec OscillatorType
$creadPrec :: ReadPrec OscillatorType
readList :: ReadS [OscillatorType]
$creadList :: ReadS [OscillatorType]
readsPrec :: Int -> ReadS OscillatorType
$creadsPrec :: Int -> ReadS OscillatorType
Read, OscillatorType -> OscillatorType -> Bool
(OscillatorType -> OscillatorType -> Bool)
-> (OscillatorType -> OscillatorType -> Bool) -> Eq OscillatorType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OscillatorType -> OscillatorType -> Bool
$c/= :: OscillatorType -> OscillatorType -> Bool
== :: OscillatorType -> OscillatorType -> Bool
$c== :: OscillatorType -> OscillatorType -> Bool
Eq, Eq OscillatorType
Eq OscillatorType
-> (OscillatorType -> OscillatorType -> Ordering)
-> (OscillatorType -> OscillatorType -> Bool)
-> (OscillatorType -> OscillatorType -> Bool)
-> (OscillatorType -> OscillatorType -> Bool)
-> (OscillatorType -> OscillatorType -> Bool)
-> (OscillatorType -> OscillatorType -> OscillatorType)
-> (OscillatorType -> OscillatorType -> OscillatorType)
-> Ord OscillatorType
OscillatorType -> OscillatorType -> Bool
OscillatorType -> OscillatorType -> Ordering
OscillatorType -> OscillatorType -> OscillatorType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: OscillatorType -> OscillatorType -> OscillatorType
$cmin :: OscillatorType -> OscillatorType -> OscillatorType
max :: OscillatorType -> OscillatorType -> OscillatorType
$cmax :: OscillatorType -> OscillatorType -> OscillatorType
>= :: OscillatorType -> OscillatorType -> Bool
$c>= :: OscillatorType -> OscillatorType -> Bool
> :: OscillatorType -> OscillatorType -> Bool
$c> :: OscillatorType -> OscillatorType -> Bool
<= :: OscillatorType -> OscillatorType -> Bool
$c<= :: OscillatorType -> OscillatorType -> Bool
< :: OscillatorType -> OscillatorType -> Bool
$c< :: OscillatorType -> OscillatorType -> Bool
compare :: OscillatorType -> OscillatorType -> Ordering
$ccompare :: OscillatorType -> OscillatorType -> Ordering
$cp1Ord :: Eq OscillatorType
Ord, Typeable)
 
instance ToJSVal OscillatorType where
        toJSVal :: OscillatorType -> JSM JSVal
toJSVal OscillatorType
OscillatorTypeSine = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_OscillatorTypeSine
        toJSVal OscillatorType
OscillatorTypeSquare = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_OscillatorTypeSquare
        toJSVal OscillatorType
OscillatorTypeSawtooth = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_OscillatorTypeSawtooth
        toJSVal OscillatorType
OscillatorTypeTriangle = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_OscillatorTypeTriangle
        toJSVal OscillatorType
OscillatorTypeCustom = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_OscillatorTypeCustom
 
instance FromJSVal OscillatorType where
        fromJSVal :: JSVal -> JSM (Maybe OscillatorType)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_OscillatorTypeSine JSM Bool
-> (Bool -> JSM (Maybe OscillatorType))
-> JSM (Maybe OscillatorType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe OscillatorType -> JSM (Maybe OscillatorType)
forall (m :: * -> *) a. Monad m => a -> m a
return (OscillatorType -> Maybe OscillatorType
forall a. a -> Maybe a
Just OscillatorType
OscillatorTypeSine)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_OscillatorTypeSquare JSM Bool
-> (Bool -> JSM (Maybe OscillatorType))
-> JSM (Maybe OscillatorType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe OscillatorType -> JSM (Maybe OscillatorType)
forall (m :: * -> *) a. Monad m => a -> m a
return (OscillatorType -> Maybe OscillatorType
forall a. a -> Maybe a
Just OscillatorType
OscillatorTypeSquare)
                                 Bool
False
                                   -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_OscillatorTypeSawtooth JSM Bool
-> (Bool -> JSM (Maybe OscillatorType))
-> JSM (Maybe OscillatorType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                        \ Bool
r ->
                                          case Bool
r of
                                              Bool
True -> Maybe OscillatorType -> JSM (Maybe OscillatorType)
forall (m :: * -> *) a. Monad m => a -> m a
return (OscillatorType -> Maybe OscillatorType
forall a. a -> Maybe a
Just OscillatorType
OscillatorTypeSawtooth)
                                              Bool
False
                                                -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_OscillatorTypeTriangle JSM Bool
-> (Bool -> JSM (Maybe OscillatorType))
-> JSM (Maybe OscillatorType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                     \ Bool
r ->
                                                       case Bool
r of
                                                           Bool
True
                                                             -> Maybe OscillatorType -> JSM (Maybe OscillatorType)
forall (m :: * -> *) a. Monad m => a -> m a
return (OscillatorType -> Maybe OscillatorType
forall a. a -> Maybe a
Just OscillatorType
OscillatorTypeTriangle)
                                                           Bool
False
                                                             -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                                  String
js_OscillatorTypeCustom
                                                                  JSM Bool
-> (Bool -> JSM (Maybe OscillatorType))
-> JSM (Maybe OscillatorType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                  \ Bool
r ->
                                                                    case Bool
r of
                                                                        Bool
True
                                                                          -> Maybe OscillatorType -> JSM (Maybe OscillatorType)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                               (OscillatorType -> Maybe OscillatorType
forall a. a -> Maybe a
Just
                                                                                  OscillatorType
OscillatorTypeCustom)
                                                                        Bool
False -> Maybe OscillatorType -> JSM (Maybe OscillatorType)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe OscillatorType
forall a. Maybe a
Nothing
js_OscillatorTypeSine :: String
js_OscillatorTypeSine = String
"sine"
js_OscillatorTypeSquare :: String
js_OscillatorTypeSquare = String
"square"
js_OscillatorTypeSawtooth :: String
js_OscillatorTypeSawtooth = String
"sawtooth"
js_OscillatorTypeTriangle :: String
js_OscillatorTypeTriangle = String
"triangle"
js_OscillatorTypeCustom :: String
js_OscillatorTypeCustom = String
"custom"
 
data PanningModelType = PanningModelTypeEqualpower
                      | PanningModelTypeHRTF
                      deriving (Int -> PanningModelType -> ShowS
[PanningModelType] -> ShowS
PanningModelType -> String
(Int -> PanningModelType -> ShowS)
-> (PanningModelType -> String)
-> ([PanningModelType] -> ShowS)
-> Show PanningModelType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PanningModelType] -> ShowS
$cshowList :: [PanningModelType] -> ShowS
show :: PanningModelType -> String
$cshow :: PanningModelType -> String
showsPrec :: Int -> PanningModelType -> ShowS
$cshowsPrec :: Int -> PanningModelType -> ShowS
Show, ReadPrec [PanningModelType]
ReadPrec PanningModelType
Int -> ReadS PanningModelType
ReadS [PanningModelType]
(Int -> ReadS PanningModelType)
-> ReadS [PanningModelType]
-> ReadPrec PanningModelType
-> ReadPrec [PanningModelType]
-> Read PanningModelType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PanningModelType]
$creadListPrec :: ReadPrec [PanningModelType]
readPrec :: ReadPrec PanningModelType
$creadPrec :: ReadPrec PanningModelType
readList :: ReadS [PanningModelType]
$creadList :: ReadS [PanningModelType]
readsPrec :: Int -> ReadS PanningModelType
$creadsPrec :: Int -> ReadS PanningModelType
Read, PanningModelType -> PanningModelType -> Bool
(PanningModelType -> PanningModelType -> Bool)
-> (PanningModelType -> PanningModelType -> Bool)
-> Eq PanningModelType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PanningModelType -> PanningModelType -> Bool
$c/= :: PanningModelType -> PanningModelType -> Bool
== :: PanningModelType -> PanningModelType -> Bool
$c== :: PanningModelType -> PanningModelType -> Bool
Eq, Eq PanningModelType
Eq PanningModelType
-> (PanningModelType -> PanningModelType -> Ordering)
-> (PanningModelType -> PanningModelType -> Bool)
-> (PanningModelType -> PanningModelType -> Bool)
-> (PanningModelType -> PanningModelType -> Bool)
-> (PanningModelType -> PanningModelType -> Bool)
-> (PanningModelType -> PanningModelType -> PanningModelType)
-> (PanningModelType -> PanningModelType -> PanningModelType)
-> Ord PanningModelType
PanningModelType -> PanningModelType -> Bool
PanningModelType -> PanningModelType -> Ordering
PanningModelType -> PanningModelType -> PanningModelType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: PanningModelType -> PanningModelType -> PanningModelType
$cmin :: PanningModelType -> PanningModelType -> PanningModelType
max :: PanningModelType -> PanningModelType -> PanningModelType
$cmax :: PanningModelType -> PanningModelType -> PanningModelType
>= :: PanningModelType -> PanningModelType -> Bool
$c>= :: PanningModelType -> PanningModelType -> Bool
> :: PanningModelType -> PanningModelType -> Bool
$c> :: PanningModelType -> PanningModelType -> Bool
<= :: PanningModelType -> PanningModelType -> Bool
$c<= :: PanningModelType -> PanningModelType -> Bool
< :: PanningModelType -> PanningModelType -> Bool
$c< :: PanningModelType -> PanningModelType -> Bool
compare :: PanningModelType -> PanningModelType -> Ordering
$ccompare :: PanningModelType -> PanningModelType -> Ordering
$cp1Ord :: Eq PanningModelType
Ord, Typeable)
 
instance ToJSVal PanningModelType where
        toJSVal :: PanningModelType -> JSM JSVal
toJSVal PanningModelType
PanningModelTypeEqualpower
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_PanningModelTypeEqualpower
        toJSVal PanningModelType
PanningModelTypeHRTF = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_PanningModelTypeHRTF
 
instance FromJSVal PanningModelType where
        fromJSVal :: JSVal -> JSM (Maybe PanningModelType)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_PanningModelTypeEqualpower JSM Bool
-> (Bool -> JSM (Maybe PanningModelType))
-> JSM (Maybe PanningModelType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe PanningModelType -> JSM (Maybe PanningModelType)
forall (m :: * -> *) a. Monad m => a -> m a
return (PanningModelType -> Maybe PanningModelType
forall a. a -> Maybe a
Just PanningModelType
PanningModelTypeEqualpower)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_PanningModelTypeHRTF JSM Bool
-> (Bool -> JSM (Maybe PanningModelType))
-> JSM (Maybe PanningModelType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe PanningModelType -> JSM (Maybe PanningModelType)
forall (m :: * -> *) a. Monad m => a -> m a
return (PanningModelType -> Maybe PanningModelType
forall a. a -> Maybe a
Just PanningModelType
PanningModelTypeHRTF)
                                 Bool
False -> Maybe PanningModelType -> JSM (Maybe PanningModelType)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe PanningModelType
forall a. Maybe a
Nothing
js_PanningModelTypeEqualpower :: String
js_PanningModelTypeEqualpower = String
"equalpower"
js_PanningModelTypeHRTF :: String
js_PanningModelTypeHRTF = String
"HRTF"
 
data DistanceModelType = DistanceModelTypeLinear
                       | DistanceModelTypeInverse
                       | DistanceModelTypeExponential
                       deriving (Int -> DistanceModelType -> ShowS
[DistanceModelType] -> ShowS
DistanceModelType -> String
(Int -> DistanceModelType -> ShowS)
-> (DistanceModelType -> String)
-> ([DistanceModelType] -> ShowS)
-> Show DistanceModelType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DistanceModelType] -> ShowS
$cshowList :: [DistanceModelType] -> ShowS
show :: DistanceModelType -> String
$cshow :: DistanceModelType -> String
showsPrec :: Int -> DistanceModelType -> ShowS
$cshowsPrec :: Int -> DistanceModelType -> ShowS
Show, ReadPrec [DistanceModelType]
ReadPrec DistanceModelType
Int -> ReadS DistanceModelType
ReadS [DistanceModelType]
(Int -> ReadS DistanceModelType)
-> ReadS [DistanceModelType]
-> ReadPrec DistanceModelType
-> ReadPrec [DistanceModelType]
-> Read DistanceModelType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DistanceModelType]
$creadListPrec :: ReadPrec [DistanceModelType]
readPrec :: ReadPrec DistanceModelType
$creadPrec :: ReadPrec DistanceModelType
readList :: ReadS [DistanceModelType]
$creadList :: ReadS [DistanceModelType]
readsPrec :: Int -> ReadS DistanceModelType
$creadsPrec :: Int -> ReadS DistanceModelType
Read, DistanceModelType -> DistanceModelType -> Bool
(DistanceModelType -> DistanceModelType -> Bool)
-> (DistanceModelType -> DistanceModelType -> Bool)
-> Eq DistanceModelType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DistanceModelType -> DistanceModelType -> Bool
$c/= :: DistanceModelType -> DistanceModelType -> Bool
== :: DistanceModelType -> DistanceModelType -> Bool
$c== :: DistanceModelType -> DistanceModelType -> Bool
Eq, Eq DistanceModelType
Eq DistanceModelType
-> (DistanceModelType -> DistanceModelType -> Ordering)
-> (DistanceModelType -> DistanceModelType -> Bool)
-> (DistanceModelType -> DistanceModelType -> Bool)
-> (DistanceModelType -> DistanceModelType -> Bool)
-> (DistanceModelType -> DistanceModelType -> Bool)
-> (DistanceModelType -> DistanceModelType -> DistanceModelType)
-> (DistanceModelType -> DistanceModelType -> DistanceModelType)
-> Ord DistanceModelType
DistanceModelType -> DistanceModelType -> Bool
DistanceModelType -> DistanceModelType -> Ordering
DistanceModelType -> DistanceModelType -> DistanceModelType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: DistanceModelType -> DistanceModelType -> DistanceModelType
$cmin :: DistanceModelType -> DistanceModelType -> DistanceModelType
max :: DistanceModelType -> DistanceModelType -> DistanceModelType
$cmax :: DistanceModelType -> DistanceModelType -> DistanceModelType
>= :: DistanceModelType -> DistanceModelType -> Bool
$c>= :: DistanceModelType -> DistanceModelType -> Bool
> :: DistanceModelType -> DistanceModelType -> Bool
$c> :: DistanceModelType -> DistanceModelType -> Bool
<= :: DistanceModelType -> DistanceModelType -> Bool
$c<= :: DistanceModelType -> DistanceModelType -> Bool
< :: DistanceModelType -> DistanceModelType -> Bool
$c< :: DistanceModelType -> DistanceModelType -> Bool
compare :: DistanceModelType -> DistanceModelType -> Ordering
$ccompare :: DistanceModelType -> DistanceModelType -> Ordering
$cp1Ord :: Eq DistanceModelType
Ord, Typeable)
 
instance ToJSVal DistanceModelType where
        toJSVal :: DistanceModelType -> JSM JSVal
toJSVal DistanceModelType
DistanceModelTypeLinear
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_DistanceModelTypeLinear
        toJSVal DistanceModelType
DistanceModelTypeInverse
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_DistanceModelTypeInverse
        toJSVal DistanceModelType
DistanceModelTypeExponential
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_DistanceModelTypeExponential
 
instance FromJSVal DistanceModelType where
        fromJSVal :: JSVal -> JSM (Maybe DistanceModelType)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_DistanceModelTypeLinear JSM Bool
-> (Bool -> JSM (Maybe DistanceModelType))
-> JSM (Maybe DistanceModelType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe DistanceModelType -> JSM (Maybe DistanceModelType)
forall (m :: * -> *) a. Monad m => a -> m a
return (DistanceModelType -> Maybe DistanceModelType
forall a. a -> Maybe a
Just DistanceModelType
DistanceModelTypeLinear)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_DistanceModelTypeInverse JSM Bool
-> (Bool -> JSM (Maybe DistanceModelType))
-> JSM (Maybe DistanceModelType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe DistanceModelType -> JSM (Maybe DistanceModelType)
forall (m :: * -> *) a. Monad m => a -> m a
return (DistanceModelType -> Maybe DistanceModelType
forall a. a -> Maybe a
Just DistanceModelType
DistanceModelTypeInverse)
                                 Bool
False
                                   -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_DistanceModelTypeExponential JSM Bool
-> (Bool -> JSM (Maybe DistanceModelType))
-> JSM (Maybe DistanceModelType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                        \ Bool
r ->
                                          case Bool
r of
                                              Bool
True -> Maybe DistanceModelType -> JSM (Maybe DistanceModelType)
forall (m :: * -> *) a. Monad m => a -> m a
return (DistanceModelType -> Maybe DistanceModelType
forall a. a -> Maybe a
Just DistanceModelType
DistanceModelTypeExponential)
                                              Bool
False -> Maybe DistanceModelType -> JSM (Maybe DistanceModelType)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe DistanceModelType
forall a. Maybe a
Nothing
js_DistanceModelTypeLinear :: String
js_DistanceModelTypeLinear = String
"linear"
js_DistanceModelTypeInverse :: String
js_DistanceModelTypeInverse = String
"inverse"
js_DistanceModelTypeExponential :: String
js_DistanceModelTypeExponential = String
"exponential"
 
data OverSampleType = OverSampleTypeNone
                    | OverSampleType2x
                    | OverSampleType4x
                    deriving (Int -> OverSampleType -> ShowS
[OverSampleType] -> ShowS
OverSampleType -> String
(Int -> OverSampleType -> ShowS)
-> (OverSampleType -> String)
-> ([OverSampleType] -> ShowS)
-> Show OverSampleType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [OverSampleType] -> ShowS
$cshowList :: [OverSampleType] -> ShowS
show :: OverSampleType -> String
$cshow :: OverSampleType -> String
showsPrec :: Int -> OverSampleType -> ShowS
$cshowsPrec :: Int -> OverSampleType -> ShowS
Show, ReadPrec [OverSampleType]
ReadPrec OverSampleType
Int -> ReadS OverSampleType
ReadS [OverSampleType]
(Int -> ReadS OverSampleType)
-> ReadS [OverSampleType]
-> ReadPrec OverSampleType
-> ReadPrec [OverSampleType]
-> Read OverSampleType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [OverSampleType]
$creadListPrec :: ReadPrec [OverSampleType]
readPrec :: ReadPrec OverSampleType
$creadPrec :: ReadPrec OverSampleType
readList :: ReadS [OverSampleType]
$creadList :: ReadS [OverSampleType]
readsPrec :: Int -> ReadS OverSampleType
$creadsPrec :: Int -> ReadS OverSampleType
Read, OverSampleType -> OverSampleType -> Bool
(OverSampleType -> OverSampleType -> Bool)
-> (OverSampleType -> OverSampleType -> Bool) -> Eq OverSampleType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OverSampleType -> OverSampleType -> Bool
$c/= :: OverSampleType -> OverSampleType -> Bool
== :: OverSampleType -> OverSampleType -> Bool
$c== :: OverSampleType -> OverSampleType -> Bool
Eq, Eq OverSampleType
Eq OverSampleType
-> (OverSampleType -> OverSampleType -> Ordering)
-> (OverSampleType -> OverSampleType -> Bool)
-> (OverSampleType -> OverSampleType -> Bool)
-> (OverSampleType -> OverSampleType -> Bool)
-> (OverSampleType -> OverSampleType -> Bool)
-> (OverSampleType -> OverSampleType -> OverSampleType)
-> (OverSampleType -> OverSampleType -> OverSampleType)
-> Ord OverSampleType
OverSampleType -> OverSampleType -> Bool
OverSampleType -> OverSampleType -> Ordering
OverSampleType -> OverSampleType -> OverSampleType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: OverSampleType -> OverSampleType -> OverSampleType
$cmin :: OverSampleType -> OverSampleType -> OverSampleType
max :: OverSampleType -> OverSampleType -> OverSampleType
$cmax :: OverSampleType -> OverSampleType -> OverSampleType
>= :: OverSampleType -> OverSampleType -> Bool
$c>= :: OverSampleType -> OverSampleType -> Bool
> :: OverSampleType -> OverSampleType -> Bool
$c> :: OverSampleType -> OverSampleType -> Bool
<= :: OverSampleType -> OverSampleType -> Bool
$c<= :: OverSampleType -> OverSampleType -> Bool
< :: OverSampleType -> OverSampleType -> Bool
$c< :: OverSampleType -> OverSampleType -> Bool
compare :: OverSampleType -> OverSampleType -> Ordering
$ccompare :: OverSampleType -> OverSampleType -> Ordering
$cp1Ord :: Eq OverSampleType
Ord, Typeable)
 
instance ToJSVal OverSampleType where
        toJSVal :: OverSampleType -> JSM JSVal
toJSVal OverSampleType
OverSampleTypeNone = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_OverSampleTypeNone
        toJSVal OverSampleType
OverSampleType2x = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_OverSampleType2x
        toJSVal OverSampleType
OverSampleType4x = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_OverSampleType4x
 
instance FromJSVal OverSampleType where
        fromJSVal :: JSVal -> JSM (Maybe OverSampleType)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_OverSampleTypeNone JSM Bool
-> (Bool -> JSM (Maybe OverSampleType))
-> JSM (Maybe OverSampleType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe OverSampleType -> JSM (Maybe OverSampleType)
forall (m :: * -> *) a. Monad m => a -> m a
return (OverSampleType -> Maybe OverSampleType
forall a. a -> Maybe a
Just OverSampleType
OverSampleTypeNone)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_OverSampleType2x JSM Bool
-> (Bool -> JSM (Maybe OverSampleType))
-> JSM (Maybe OverSampleType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe OverSampleType -> JSM (Maybe OverSampleType)
forall (m :: * -> *) a. Monad m => a -> m a
return (OverSampleType -> Maybe OverSampleType
forall a. a -> Maybe a
Just OverSampleType
OverSampleType2x)
                                 Bool
False
                                   -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_OverSampleType4x JSM Bool
-> (Bool -> JSM (Maybe OverSampleType))
-> JSM (Maybe OverSampleType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                        \ Bool
r ->
                                          case Bool
r of
                                              Bool
True -> Maybe OverSampleType -> JSM (Maybe OverSampleType)
forall (m :: * -> *) a. Monad m => a -> m a
return (OverSampleType -> Maybe OverSampleType
forall a. a -> Maybe a
Just OverSampleType
OverSampleType4x)
                                              Bool
False -> Maybe OverSampleType -> JSM (Maybe OverSampleType)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe OverSampleType
forall a. Maybe a
Nothing
js_OverSampleTypeNone :: String
js_OverSampleTypeNone = String
"none"
js_OverSampleType2x :: String
js_OverSampleType2x = String
"2x"
js_OverSampleType4x :: String
js_OverSampleType4x = String
"4x"
 
data ScrollRestoration = ScrollRestorationAuto
                       | ScrollRestorationManual
                       deriving (Int -> ScrollRestoration -> ShowS
[ScrollRestoration] -> ShowS
ScrollRestoration -> String
(Int -> ScrollRestoration -> ShowS)
-> (ScrollRestoration -> String)
-> ([ScrollRestoration] -> ShowS)
-> Show ScrollRestoration
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ScrollRestoration] -> ShowS
$cshowList :: [ScrollRestoration] -> ShowS
show :: ScrollRestoration -> String
$cshow :: ScrollRestoration -> String
showsPrec :: Int -> ScrollRestoration -> ShowS
$cshowsPrec :: Int -> ScrollRestoration -> ShowS
Show, ReadPrec [ScrollRestoration]
ReadPrec ScrollRestoration
Int -> ReadS ScrollRestoration
ReadS [ScrollRestoration]
(Int -> ReadS ScrollRestoration)
-> ReadS [ScrollRestoration]
-> ReadPrec ScrollRestoration
-> ReadPrec [ScrollRestoration]
-> Read ScrollRestoration
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ScrollRestoration]
$creadListPrec :: ReadPrec [ScrollRestoration]
readPrec :: ReadPrec ScrollRestoration
$creadPrec :: ReadPrec ScrollRestoration
readList :: ReadS [ScrollRestoration]
$creadList :: ReadS [ScrollRestoration]
readsPrec :: Int -> ReadS ScrollRestoration
$creadsPrec :: Int -> ReadS ScrollRestoration
Read, ScrollRestoration -> ScrollRestoration -> Bool
(ScrollRestoration -> ScrollRestoration -> Bool)
-> (ScrollRestoration -> ScrollRestoration -> Bool)
-> Eq ScrollRestoration
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ScrollRestoration -> ScrollRestoration -> Bool
$c/= :: ScrollRestoration -> ScrollRestoration -> Bool
== :: ScrollRestoration -> ScrollRestoration -> Bool
$c== :: ScrollRestoration -> ScrollRestoration -> Bool
Eq, Eq ScrollRestoration
Eq ScrollRestoration
-> (ScrollRestoration -> ScrollRestoration -> Ordering)
-> (ScrollRestoration -> ScrollRestoration -> Bool)
-> (ScrollRestoration -> ScrollRestoration -> Bool)
-> (ScrollRestoration -> ScrollRestoration -> Bool)
-> (ScrollRestoration -> ScrollRestoration -> Bool)
-> (ScrollRestoration -> ScrollRestoration -> ScrollRestoration)
-> (ScrollRestoration -> ScrollRestoration -> ScrollRestoration)
-> Ord ScrollRestoration
ScrollRestoration -> ScrollRestoration -> Bool
ScrollRestoration -> ScrollRestoration -> Ordering
ScrollRestoration -> ScrollRestoration -> ScrollRestoration
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ScrollRestoration -> ScrollRestoration -> ScrollRestoration
$cmin :: ScrollRestoration -> ScrollRestoration -> ScrollRestoration
max :: ScrollRestoration -> ScrollRestoration -> ScrollRestoration
$cmax :: ScrollRestoration -> ScrollRestoration -> ScrollRestoration
>= :: ScrollRestoration -> ScrollRestoration -> Bool
$c>= :: ScrollRestoration -> ScrollRestoration -> Bool
> :: ScrollRestoration -> ScrollRestoration -> Bool
$c> :: ScrollRestoration -> ScrollRestoration -> Bool
<= :: ScrollRestoration -> ScrollRestoration -> Bool
$c<= :: ScrollRestoration -> ScrollRestoration -> Bool
< :: ScrollRestoration -> ScrollRestoration -> Bool
$c< :: ScrollRestoration -> ScrollRestoration -> Bool
compare :: ScrollRestoration -> ScrollRestoration -> Ordering
$ccompare :: ScrollRestoration -> ScrollRestoration -> Ordering
$cp1Ord :: Eq ScrollRestoration
Ord, Typeable)
 
instance ToJSVal ScrollRestoration where
        toJSVal :: ScrollRestoration -> JSM JSVal
toJSVal ScrollRestoration
ScrollRestorationAuto = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_ScrollRestorationAuto
        toJSVal ScrollRestoration
ScrollRestorationManual
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_ScrollRestorationManual
 
instance FromJSVal ScrollRestoration where
        fromJSVal :: JSVal -> JSM (Maybe ScrollRestoration)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_ScrollRestorationAuto JSM Bool
-> (Bool -> JSM (Maybe ScrollRestoration))
-> JSM (Maybe ScrollRestoration)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe ScrollRestoration -> JSM (Maybe ScrollRestoration)
forall (m :: * -> *) a. Monad m => a -> m a
return (ScrollRestoration -> Maybe ScrollRestoration
forall a. a -> Maybe a
Just ScrollRestoration
ScrollRestorationAuto)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_ScrollRestorationManual JSM Bool
-> (Bool -> JSM (Maybe ScrollRestoration))
-> JSM (Maybe ScrollRestoration)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe ScrollRestoration -> JSM (Maybe ScrollRestoration)
forall (m :: * -> *) a. Monad m => a -> m a
return (ScrollRestoration -> Maybe ScrollRestoration
forall a. a -> Maybe a
Just ScrollRestoration
ScrollRestorationManual)
                                 Bool
False -> Maybe ScrollRestoration -> JSM (Maybe ScrollRestoration)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ScrollRestoration
forall a. Maybe a
Nothing
js_ScrollRestorationAuto :: String
js_ScrollRestorationAuto = String
"auto"
js_ScrollRestorationManual :: String
js_ScrollRestorationManual = String
"manual"
 
data XMLHttpRequestResponseType = XMLHttpRequestResponseType
                                | XMLHttpRequestResponseTypeArraybuffer
                                | XMLHttpRequestResponseTypeBlob
                                | XMLHttpRequestResponseTypeDocument
                                | XMLHttpRequestResponseTypeJson
                                | XMLHttpRequestResponseTypeText
                                deriving (Int -> XMLHttpRequestResponseType -> ShowS
[XMLHttpRequestResponseType] -> ShowS
XMLHttpRequestResponseType -> String
(Int -> XMLHttpRequestResponseType -> ShowS)
-> (XMLHttpRequestResponseType -> String)
-> ([XMLHttpRequestResponseType] -> ShowS)
-> Show XMLHttpRequestResponseType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [XMLHttpRequestResponseType] -> ShowS
$cshowList :: [XMLHttpRequestResponseType] -> ShowS
show :: XMLHttpRequestResponseType -> String
$cshow :: XMLHttpRequestResponseType -> String
showsPrec :: Int -> XMLHttpRequestResponseType -> ShowS
$cshowsPrec :: Int -> XMLHttpRequestResponseType -> ShowS
Show, ReadPrec [XMLHttpRequestResponseType]
ReadPrec XMLHttpRequestResponseType
Int -> ReadS XMLHttpRequestResponseType
ReadS [XMLHttpRequestResponseType]
(Int -> ReadS XMLHttpRequestResponseType)
-> ReadS [XMLHttpRequestResponseType]
-> ReadPrec XMLHttpRequestResponseType
-> ReadPrec [XMLHttpRequestResponseType]
-> Read XMLHttpRequestResponseType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [XMLHttpRequestResponseType]
$creadListPrec :: ReadPrec [XMLHttpRequestResponseType]
readPrec :: ReadPrec XMLHttpRequestResponseType
$creadPrec :: ReadPrec XMLHttpRequestResponseType
readList :: ReadS [XMLHttpRequestResponseType]
$creadList :: ReadS [XMLHttpRequestResponseType]
readsPrec :: Int -> ReadS XMLHttpRequestResponseType
$creadsPrec :: Int -> ReadS XMLHttpRequestResponseType
Read, XMLHttpRequestResponseType -> XMLHttpRequestResponseType -> Bool
(XMLHttpRequestResponseType -> XMLHttpRequestResponseType -> Bool)
-> (XMLHttpRequestResponseType
    -> XMLHttpRequestResponseType -> Bool)
-> Eq XMLHttpRequestResponseType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: XMLHttpRequestResponseType -> XMLHttpRequestResponseType -> Bool
$c/= :: XMLHttpRequestResponseType -> XMLHttpRequestResponseType -> Bool
== :: XMLHttpRequestResponseType -> XMLHttpRequestResponseType -> Bool
$c== :: XMLHttpRequestResponseType -> XMLHttpRequestResponseType -> Bool
Eq, Eq XMLHttpRequestResponseType
Eq XMLHttpRequestResponseType
-> (XMLHttpRequestResponseType
    -> XMLHttpRequestResponseType -> Ordering)
-> (XMLHttpRequestResponseType
    -> XMLHttpRequestResponseType -> Bool)
-> (XMLHttpRequestResponseType
    -> XMLHttpRequestResponseType -> Bool)
-> (XMLHttpRequestResponseType
    -> XMLHttpRequestResponseType -> Bool)
-> (XMLHttpRequestResponseType
    -> XMLHttpRequestResponseType -> Bool)
-> (XMLHttpRequestResponseType
    -> XMLHttpRequestResponseType -> XMLHttpRequestResponseType)
-> (XMLHttpRequestResponseType
    -> XMLHttpRequestResponseType -> XMLHttpRequestResponseType)
-> Ord XMLHttpRequestResponseType
XMLHttpRequestResponseType -> XMLHttpRequestResponseType -> Bool
XMLHttpRequestResponseType
-> XMLHttpRequestResponseType -> Ordering
XMLHttpRequestResponseType
-> XMLHttpRequestResponseType -> XMLHttpRequestResponseType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: XMLHttpRequestResponseType
-> XMLHttpRequestResponseType -> XMLHttpRequestResponseType
$cmin :: XMLHttpRequestResponseType
-> XMLHttpRequestResponseType -> XMLHttpRequestResponseType
max :: XMLHttpRequestResponseType
-> XMLHttpRequestResponseType -> XMLHttpRequestResponseType
$cmax :: XMLHttpRequestResponseType
-> XMLHttpRequestResponseType -> XMLHttpRequestResponseType
>= :: XMLHttpRequestResponseType -> XMLHttpRequestResponseType -> Bool
$c>= :: XMLHttpRequestResponseType -> XMLHttpRequestResponseType -> Bool
> :: XMLHttpRequestResponseType -> XMLHttpRequestResponseType -> Bool
$c> :: XMLHttpRequestResponseType -> XMLHttpRequestResponseType -> Bool
<= :: XMLHttpRequestResponseType -> XMLHttpRequestResponseType -> Bool
$c<= :: XMLHttpRequestResponseType -> XMLHttpRequestResponseType -> Bool
< :: XMLHttpRequestResponseType -> XMLHttpRequestResponseType -> Bool
$c< :: XMLHttpRequestResponseType -> XMLHttpRequestResponseType -> Bool
compare :: XMLHttpRequestResponseType
-> XMLHttpRequestResponseType -> Ordering
$ccompare :: XMLHttpRequestResponseType
-> XMLHttpRequestResponseType -> Ordering
$cp1Ord :: Eq XMLHttpRequestResponseType
Ord, Typeable)
 
instance ToJSVal XMLHttpRequestResponseType where
        toJSVal :: XMLHttpRequestResponseType -> JSM JSVal
toJSVal XMLHttpRequestResponseType
XMLHttpRequestResponseType
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_XMLHttpRequestResponseType
        toJSVal XMLHttpRequestResponseType
XMLHttpRequestResponseTypeArraybuffer
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_XMLHttpRequestResponseTypeArraybuffer
        toJSVal XMLHttpRequestResponseType
XMLHttpRequestResponseTypeBlob
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_XMLHttpRequestResponseTypeBlob
        toJSVal XMLHttpRequestResponseType
XMLHttpRequestResponseTypeDocument
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_XMLHttpRequestResponseTypeDocument
        toJSVal XMLHttpRequestResponseType
XMLHttpRequestResponseTypeJson
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_XMLHttpRequestResponseTypeJson
        toJSVal XMLHttpRequestResponseType
XMLHttpRequestResponseTypeText
          = String -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal String
js_XMLHttpRequestResponseTypeText
 
instance FromJSVal XMLHttpRequestResponseType where
        fromJSVal :: JSVal -> JSM (Maybe XMLHttpRequestResponseType)
fromJSVal JSVal
x
          = JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_XMLHttpRequestResponseType JSM Bool
-> (Bool -> JSM (Maybe XMLHttpRequestResponseType))
-> JSM (Maybe XMLHttpRequestResponseType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
              \ Bool
r ->
                case Bool
r of
                    Bool
True -> Maybe XMLHttpRequestResponseType
-> JSM (Maybe XMLHttpRequestResponseType)
forall (m :: * -> *) a. Monad m => a -> m a
return (XMLHttpRequestResponseType -> Maybe XMLHttpRequestResponseType
forall a. a -> Maybe a
Just XMLHttpRequestResponseType
XMLHttpRequestResponseType)
                    Bool
False
                      -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_XMLHttpRequestResponseTypeArraybuffer JSM Bool
-> (Bool -> JSM (Maybe XMLHttpRequestResponseType))
-> JSM (Maybe XMLHttpRequestResponseType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           \ Bool
r ->
                             case Bool
r of
                                 Bool
True -> Maybe XMLHttpRequestResponseType
-> JSM (Maybe XMLHttpRequestResponseType)
forall (m :: * -> *) a. Monad m => a -> m a
return (XMLHttpRequestResponseType -> Maybe XMLHttpRequestResponseType
forall a. a -> Maybe a
Just XMLHttpRequestResponseType
XMLHttpRequestResponseTypeArraybuffer)
                                 Bool
False
                                   -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual` String
js_XMLHttpRequestResponseTypeBlob JSM Bool
-> (Bool -> JSM (Maybe XMLHttpRequestResponseType))
-> JSM (Maybe XMLHttpRequestResponseType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                        \ Bool
r ->
                                          case Bool
r of
                                              Bool
True -> Maybe XMLHttpRequestResponseType
-> JSM (Maybe XMLHttpRequestResponseType)
forall (m :: * -> *) a. Monad m => a -> m a
return (XMLHttpRequestResponseType -> Maybe XMLHttpRequestResponseType
forall a. a -> Maybe a
Just XMLHttpRequestResponseType
XMLHttpRequestResponseTypeBlob)
                                              Bool
False
                                                -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                     String
js_XMLHttpRequestResponseTypeDocument
                                                     JSM Bool
-> (Bool -> JSM (Maybe XMLHttpRequestResponseType))
-> JSM (Maybe XMLHttpRequestResponseType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                     \ Bool
r ->
                                                       case Bool
r of
                                                           Bool
True
                                                             -> Maybe XMLHttpRequestResponseType
-> JSM (Maybe XMLHttpRequestResponseType)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                  (XMLHttpRequestResponseType -> Maybe XMLHttpRequestResponseType
forall a. a -> Maybe a
Just
                                                                     XMLHttpRequestResponseType
XMLHttpRequestResponseTypeDocument)
                                                           Bool
False
                                                             -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                                  String
js_XMLHttpRequestResponseTypeJson
                                                                  JSM Bool
-> (Bool -> JSM (Maybe XMLHttpRequestResponseType))
-> JSM (Maybe XMLHttpRequestResponseType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                  \ Bool
r ->
                                                                    case Bool
r of
                                                                        Bool
True
                                                                          -> Maybe XMLHttpRequestResponseType
-> JSM (Maybe XMLHttpRequestResponseType)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                               (XMLHttpRequestResponseType -> Maybe XMLHttpRequestResponseType
forall a. a -> Maybe a
Just
                                                                                  XMLHttpRequestResponseType
XMLHttpRequestResponseTypeJson)
                                                                        Bool
False
                                                                          -> JSVal
x JSVal -> String -> JSM Bool
forall a b. (ToJSVal a, ToJSVal b) => a -> b -> JSM Bool
`strictEqual`
                                                                               String
js_XMLHttpRequestResponseTypeText
                                                                               JSM Bool
-> (Bool -> JSM (Maybe XMLHttpRequestResponseType))
-> JSM (Maybe XMLHttpRequestResponseType)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                                                               \ Bool
r ->
                                                                                 case Bool
r of
                                                                                     Bool
True
                                                                                       -> Maybe XMLHttpRequestResponseType
-> JSM (Maybe XMLHttpRequestResponseType)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                                            (XMLHttpRequestResponseType -> Maybe XMLHttpRequestResponseType
forall a. a -> Maybe a
Just
                                                                                               XMLHttpRequestResponseType
XMLHttpRequestResponseTypeText)
                                                                                     Bool
False
                                                                                       -> Maybe XMLHttpRequestResponseType
-> JSM (Maybe XMLHttpRequestResponseType)
forall (m :: * -> *) a. Monad m => a -> m a
return
                                                                                            Maybe XMLHttpRequestResponseType
forall a. Maybe a
Nothing
js_XMLHttpRequestResponseType :: String
js_XMLHttpRequestResponseType = String
""
js_XMLHttpRequestResponseTypeArraybuffer :: String
js_XMLHttpRequestResponseTypeArraybuffer = String
"arraybuffer"
js_XMLHttpRequestResponseTypeBlob :: String
js_XMLHttpRequestResponseTypeBlob = String
"blob"
js_XMLHttpRequestResponseTypeDocument :: String
js_XMLHttpRequestResponseTypeDocument = String
"document"
js_XMLHttpRequestResponseTypeJson :: String
js_XMLHttpRequestResponseTypeJson = String
"json"
js_XMLHttpRequestResponseTypeText :: String
js_XMLHttpRequestResponseTypeText = String
"text"