Safe Haskell | None |
---|---|
Language | Haskell2010 |
Quickjs.Error
Contents
Documentation
data SomeJSRuntimeException Source #
Constructors
Exception e => SomeJSRuntimeException e |
Instances
Show SomeJSRuntimeException Source # | |
Defined in Quickjs.Error Methods showsPrec :: Int -> SomeJSRuntimeException -> ShowS # show :: SomeJSRuntimeException -> String # showList :: [SomeJSRuntimeException] -> ShowS # | |
Exception SomeJSRuntimeException Source # | |
Defined in Quickjs.Error |
jsRuntimeExceptionToException :: Exception e => e -> SomeException Source #
jsRuntimeExceptionFromException :: Exception e => SomeException -> Maybe e Source #
data UnknownJSTag Source #
Constructors
UnknownJSTag | |
Instances
Show UnknownJSTag Source # | |
Defined in Quickjs.Error Methods showsPrec :: Int -> UnknownJSTag -> ShowS # show :: UnknownJSTag -> String # showList :: [UnknownJSTag] -> ShowS # | |
Generic UnknownJSTag Source # | |
Defined in Quickjs.Error Associated Types type Rep UnknownJSTag :: Type -> Type # | |
Exception UnknownJSTag Source # | |
Defined in Quickjs.Error Methods toException :: UnknownJSTag -> SomeException # fromException :: SomeException -> Maybe UnknownJSTag # displayException :: UnknownJSTag -> String # | |
type Rep UnknownJSTag Source # | |
Defined in Quickjs.Error type Rep UnknownJSTag = D1 (MetaData "UnknownJSTag" "Quickjs.Error" "quickjs-hs-0.1.2.1-DC3kFhrKF8pDeXbNbDFYn7" False) (C1 (MetaCons "UnknownJSTag" PrefixI True) (S1 (MetaSel (Just "raw_tag") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 CLong))) |
data UnsupportedTypeTag Source #
Constructors
UnsupportedTypeTag | |
Instances
Show UnsupportedTypeTag Source # | |
Defined in Quickjs.Error Methods showsPrec :: Int -> UnsupportedTypeTag -> ShowS # show :: UnsupportedTypeTag -> String # showList :: [UnsupportedTypeTag] -> ShowS # | |
Generic UnsupportedTypeTag Source # | |
Defined in Quickjs.Error Associated Types type Rep UnsupportedTypeTag :: Type -> Type # Methods from :: UnsupportedTypeTag -> Rep UnsupportedTypeTag x # to :: Rep UnsupportedTypeTag x -> UnsupportedTypeTag # | |
Exception UnsupportedTypeTag Source # | |
Defined in Quickjs.Error Methods toException :: UnsupportedTypeTag -> SomeException # fromException :: SomeException -> Maybe UnsupportedTypeTag # | |
type Rep UnsupportedTypeTag Source # | |
Defined in Quickjs.Error type Rep UnsupportedTypeTag = D1 (MetaData "UnsupportedTypeTag" "Quickjs.Error" "quickjs-hs-0.1.2.1-DC3kFhrKF8pDeXbNbDFYn7" False) (C1 (MetaCons "UnsupportedTypeTag" PrefixI True) (S1 (MetaSel (Just "_tag") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 JSTagEnum))) |
data JSException Source #
Constructors
JSException | |
Instances
Show JSException Source # | |
Defined in Quickjs.Error Methods showsPrec :: Int -> JSException -> ShowS # show :: JSException -> String # showList :: [JSException] -> ShowS # | |
Generic JSException Source # | |
Defined in Quickjs.Error Associated Types type Rep JSException :: Type -> Type # | |
Exception JSException Source # | |
Defined in Quickjs.Error Methods toException :: JSException -> SomeException # fromException :: SomeException -> Maybe JSException # displayException :: JSException -> String # | |
type Rep JSException Source # | |
Defined in Quickjs.Error type Rep JSException = D1 (MetaData "JSException" "Quickjs.Error" "quickjs-hs-0.1.2.1-DC3kFhrKF8pDeXbNbDFYn7" False) (C1 (MetaCons "JSException" PrefixI True) (S1 (MetaSel (Just "location") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text) :*: S1 (MetaSel (Just "message") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text))) |
data JSValueUndefined Source #
Constructors
JSValueUndefined | |
Instances
Show JSValueUndefined Source # | |
Defined in Quickjs.Error Methods showsPrec :: Int -> JSValueUndefined -> ShowS # show :: JSValueUndefined -> String # showList :: [JSValueUndefined] -> ShowS # | |
Generic JSValueUndefined Source # | |
Defined in Quickjs.Error Associated Types type Rep JSValueUndefined :: Type -> Type # Methods from :: JSValueUndefined -> Rep JSValueUndefined x # to :: Rep JSValueUndefined x -> JSValueUndefined # | |
Exception JSValueUndefined Source # | |
Defined in Quickjs.Error Methods toException :: JSValueUndefined -> SomeException # | |
type Rep JSValueUndefined Source # | |
Defined in Quickjs.Error type Rep JSValueUndefined = D1 (MetaData "JSValueUndefined" "Quickjs.Error" "quickjs-hs-0.1.2.1-DC3kFhrKF8pDeXbNbDFYn7" False) (C1 (MetaCons "JSValueUndefined" PrefixI True) (S1 (MetaSel (Just "value") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text))) |
data JSValueIncorrectType Source #
Constructors
JSValueIncorrectType | |
Fields
|
Instances
data InternalError Source #
Constructors
InternalError | |
Instances
Show InternalError Source # | |
Defined in Quickjs.Error Methods showsPrec :: Int -> InternalError -> ShowS # show :: InternalError -> String # showList :: [InternalError] -> ShowS # | |
Generic InternalError Source # | |
Defined in Quickjs.Error Associated Types type Rep InternalError :: Type -> Type # | |
Exception InternalError Source # | |
Defined in Quickjs.Error Methods toException :: InternalError -> SomeException # fromException :: SomeException -> Maybe InternalError # displayException :: InternalError -> String # | |
type Rep InternalError Source # | |
Defined in Quickjs.Error type Rep InternalError = D1 (MetaData "InternalError" "Quickjs.Error" "quickjs-hs-0.1.2.1-DC3kFhrKF8pDeXbNbDFYn7" False) (C1 (MetaCons "InternalError" PrefixI True) (S1 (MetaSel (Just "message") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text))) |