Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- class (Typeable e, ErrorHasDoc e) => IsError e where
- errorToVal :: e -> (forall t. ErrorScope t => Value t -> r) -> r
- errorFromVal :: (Typeable t, SingI t) => Value t -> Either Text e
- isoErrorToVal :: (KnownError e, IsoValue e) => e -> (forall t. ErrorScope t => Value t -> r) -> r
- isoErrorFromVal :: (Typeable t, Typeable (ToT e), IsoValue e) => Value t -> Either Text e
- class ErrorHasDoc e where
- typeDocMdDescriptionReferToError :: forall e. IsError e => Markdown
- data UnspecifiedError = UnspecifiedError
- failUsing :: forall e s t. IsError e => e -> s :-> t
- failUnexpected :: MText -> s :-> t
- type family ErrorArg (tag :: Symbol) :: Type
- data CustomError (tag :: Symbol) = CustomError {}
- failCustom :: forall tag err s any. (err ~ ErrorArg tag, CustomErrorHasDoc tag, KnownError err) => Label tag -> (err ': s) :-> any
- type RequireNoArgError tag msg = (TypeErrorUnless (ErrorArg tag == ()) msg, msg ~ (Text "Expected no-arg error, but given error requires argument of type " :<>: ShowType (ErrorArg tag)))
- failCustom_ :: forall tag s any notVoidErrorMsg. (RequireNoArgError tag notVoidErrorMsg, CustomErrorHasDoc tag) => Label tag -> s :-> any
- data ErrorClass
- class (KnownSymbol tag, TypeHasDoc (ErrorArg tag), IsError (CustomError tag)) => CustomErrorHasDoc tag where
- data DError where
- data DThrows where
- customErrorToVal :: (LooseSumC e, HasCallStack) => e -> (forall t. ErrorScope t => Value t -> r) -> r
- customErrorFromVal :: forall t e. (SingI t, LooseSumC e) => Value t -> Either Text e
- failUsingArg :: forall err name fieldTy s s'. FailUsingArg err name fieldTy s s'
- type FailUsingArg e name fieldTy s s' = (KnownSymbol name, IsError e, IsoValue fieldTy, CtorHasOnlyField name e fieldTy, Each [Typeable, SingI] '[ToT fieldTy], HasCallStack) => Label name -> (fieldTy ': s) :-> s'
- type family CustomErrorNoIsoValue a where ...
- deriveCustomError :: Name -> Q [Dec]
- errorsDocumentation :: Markdown
Haskell to Value
conversion
class (Typeable e, ErrorHasDoc e) => IsError e where Source #
Haskell type representing error.
errorToVal :: e -> (forall t. ErrorScope t => Value t -> r) -> r Source #
Converts a Haskell error into Value
representation.
errorFromVal :: (Typeable t, SingI t) => Value t -> Either Text e Source #
Converts a Value
into Haskell error.
Instances
(TypeError (Text "Use representative error messages") :: Constraint) => IsError () Source # | |
Defined in Lorentz.Errors | |
IsError MText Source # | Use this for internal errors only. Normal error scenarios should use the mechanism of custom errors, see below. |
IsError UnspecifiedError Source # | |
Defined in Lorentz.Errors errorToVal :: UnspecifiedError -> (forall (t :: T). ErrorScope t => Value t -> r) -> r Source # errorFromVal :: (Typeable t, SingI t) => Value t -> Either Text UnspecifiedError Source # | |
(CustomErrorHasDoc tag, KnownError (ErrorArg tag), IsoValue (ErrorArg tag)) => IsError (CustomError tag) Source # | |
Defined in Lorentz.Errors errorToVal :: CustomError tag -> (forall (t :: T). ErrorScope t => Value t -> r) -> r Source # errorFromVal :: (Typeable t, SingI t) => Value t -> Either Text (CustomError tag) Source # | |
(Typeable r, NiceConstant r, ErrorHasDoc (VoidResult r)) => IsError (VoidResult r) Source # | |
Defined in Lorentz.Macro errorToVal :: VoidResult r -> (forall (t :: T). ErrorScope t => Value t -> r0) -> r0 Source # errorFromVal :: (Typeable t, SingI t) => Value t -> Either Text (VoidResult r) Source # | |
(Typeable arg, IsError (CustomError tag), TypeErrorUnless (arg == ()) notVoidError, arg ~ ErrorArg tag, notVoidError ~ (Text "This error requires argument of type " :<>: ShowType (ErrorArg tag))) => IsError (arg -> CustomError tag) Source # | If |
Defined in Lorentz.Errors errorToVal :: (arg -> CustomError tag) -> (forall (t :: T). ErrorScope t => Value t -> r) -> r Source # errorFromVal :: (Typeable t, SingI t) => Value t -> Either Text (arg -> CustomError tag) Source # |
isoErrorToVal :: (KnownError e, IsoValue e) => e -> (forall t. ErrorScope t => Value t -> r) -> r Source #
Implementation of errorToVal
via IsoValue
.
isoErrorFromVal :: (Typeable t, Typeable (ToT e), IsoValue e) => Value t -> Either Text e Source #
Implementation of errorFromVal
via IsoValue
.
class ErrorHasDoc e where Source #
errorDocName :: Text Source #
Name of error as it appears in the corresponding section title.
errorDocMdCause :: Markdown Source #
What should happen for this error to be raised.
errorDocMdCauseInEntrypoint :: Markdown Source #
Brief version of errorDocMdCause
.
This will appear along with the error when mentioned in entrypoint description. By default, the first sentence of the full description is used.
errorDocHaskellRep :: Markdown Source #
How this error is represented in Haskell.
errorDocClass :: ErrorClass Source #
Error class.
errorDocDependencies :: [SomeDocDefinitionItem] Source #
Which definitions documentation for this error mentions.
Instances
(TypeError (Text "Use representative error messages") :: Constraint) => ErrorHasDoc () Source # | |
ErrorHasDoc MText Source # | |
ErrorHasDoc UnspecifiedError Source # | |
(CustomErrorHasDoc tag, SingI (ToT (ErrorArg tag))) => ErrorHasDoc (CustomError tag :: Type) Source # | |
TypeHasDoc r => ErrorHasDoc (VoidResult r :: Type) Source # | |
ErrorHasDoc (CustomError tag) => ErrorHasDoc (arg -> CustomError tag :: Type) Source # | |
typeDocMdDescriptionReferToError :: forall e. IsError e => Markdown Source #
Implementation of typeDocMdDescription
(of TypeHasDoc
typeclass)
for Haskell types which sole purpose is to be error.
data UnspecifiedError Source #
Use this type as replacement for ()
when you really want to leave
error cause unspecified.
Instances
Generic UnspecifiedError Source # | |
Defined in Lorentz.Errors type Rep UnspecifiedError :: Type -> Type # from :: UnspecifiedError -> Rep UnspecifiedError x # to :: Rep UnspecifiedError x -> UnspecifiedError # | |
IsoValue UnspecifiedError Source # | |
Defined in Lorentz.Errors type ToT UnspecifiedError :: T Source # toVal :: UnspecifiedError -> Value (ToT UnspecifiedError) Source # fromVal :: Value (ToT UnspecifiedError) -> UnspecifiedError Source # | |
IsError UnspecifiedError Source # | |
Defined in Lorentz.Errors errorToVal :: UnspecifiedError -> (forall (t :: T). ErrorScope t => Value t -> r) -> r Source # errorFromVal :: (Typeable t, SingI t) => Value t -> Either Text UnspecifiedError Source # | |
ErrorHasDoc UnspecifiedError Source # | |
type Rep UnspecifiedError Source # | |
type ToT UnspecifiedError Source # | |
Defined in Lorentz.Errors |
General instructions
failUnexpected :: MText -> s :-> t Source #
Fail, providing a reference to the place in the code where this function is called.
Like error
in Haskell code, this instruction is for internal errors only.
Custom errors
type family ErrorArg (tag :: Symbol) :: Type Source #
Declares a custom error, defining error name - error argument
relation.
If your error is supposed to carry no argument, then provide ()
.
Note that this relation is defined globally rather than on per-contract basis, so define errors accordingly. If your error has argument specific to your contract, call it such that error name reflects its belonging to this contract.
Instances
type ErrorArg "emptySupplied" Source # | Someone constructed |
Defined in Lorentz.Empty type ErrorArg "emptySupplied" = () | |
type ErrorArg "senderIsNotAdmin" Source # | Contract initiator should be contract admin in order to perform this operation. |
Defined in Lorentz.Errors.Common type ErrorArg "senderIsNotAdmin" = () | |
type ErrorArg "uparamArgumentUnpackFailed" Source # | |
Defined in Lorentz.UParam type ErrorArg "uparamArgumentUnpackFailed" = () | |
type ErrorArg "uparamNoSuchEntryPoint" Source # | |
Defined in Lorentz.UParam |
data CustomError (tag :: Symbol) Source #
Material custom error.
Use this in pattern matches against error (e.g. in tests).
Instances
Eq (ErrorArg tag) => Eq (CustomError tag) Source # | |
Defined in Lorentz.Errors (==) :: CustomError tag -> CustomError tag -> Bool # (/=) :: CustomError tag -> CustomError tag -> Bool # | |
Show (ErrorArg tag) => Show (CustomError tag) Source # | |
Defined in Lorentz.Errors showsPrec :: Int -> CustomError tag -> ShowS # show :: CustomError tag -> String # showList :: [CustomError tag] -> ShowS # | |
Buildable (CustomError "emptySupplied") Source # | |
Defined in Lorentz.Empty build :: CustomError "emptySupplied" -> Builder # | |
Buildable (CustomError "senderIsNotAdmin") Source # | |
Defined in Lorentz.Errors.Common build :: CustomError "senderIsNotAdmin" -> Builder # | |
Buildable (CustomError "uparamArgumentUnpackFailed") Source # | |
Defined in Lorentz.UParam build :: CustomError "uparamArgumentUnpackFailed" -> Builder # | |
Buildable (CustomError "uparamNoSuchEntryPoint") Source # | |
Defined in Lorentz.UParam build :: CustomError "uparamNoSuchEntryPoint" -> Builder # | |
(TypeError (Text "CustomError has no IsoValue instance") :: Constraint) => IsoValue (CustomError tag) Source # | This instance cannot be implemented, use |
Defined in Lorentz.Errors type ToT (CustomError tag) :: T Source # toVal :: CustomError tag -> Value (ToT (CustomError tag)) Source # fromVal :: Value (ToT (CustomError tag)) -> CustomError tag Source # | |
(CustomErrorHasDoc tag, KnownError (ErrorArg tag), IsoValue (ErrorArg tag)) => IsError (CustomError tag) Source # | |
Defined in Lorentz.Errors errorToVal :: CustomError tag -> (forall (t :: T). ErrorScope t => Value t -> r) -> r Source # errorFromVal :: (Typeable t, SingI t) => Value t -> Either Text (CustomError tag) Source # | |
(CustomErrorHasDoc tag, SingI (ToT (ErrorArg tag))) => ErrorHasDoc (CustomError tag :: Type) Source # | |
ErrorHasDoc (CustomError tag) => ErrorHasDoc (arg -> CustomError tag :: Type) Source # | |
Eq (ErrorArg tag) => Eq (() -> CustomError tag) Source # | |
Defined in Lorentz.Errors (==) :: (() -> CustomError tag) -> (() -> CustomError tag) -> Bool # (/=) :: (() -> CustomError tag) -> (() -> CustomError tag) -> Bool # | |
Show (ErrorArg tag) => Show (() -> CustomError tag) Source # | |
Defined in Lorentz.Errors showsPrec :: Int -> (() -> CustomError tag) -> ShowS # show :: (() -> CustomError tag) -> String # showList :: [() -> CustomError tag] -> ShowS # | |
(Typeable arg, IsError (CustomError tag), TypeErrorUnless (arg == ()) notVoidError, arg ~ ErrorArg tag, notVoidError ~ (Text "This error requires argument of type " :<>: ShowType (ErrorArg tag))) => IsError (arg -> CustomError tag) Source # | If |
Defined in Lorentz.Errors errorToVal :: (arg -> CustomError tag) -> (forall (t :: T). ErrorScope t => Value t -> r) -> r Source # errorFromVal :: (Typeable t, SingI t) => Value t -> Either Text (arg -> CustomError tag) Source # | |
type ToT (CustomError tag) Source # | |
Defined in Lorentz.Errors |
failCustom :: forall tag err s any. (err ~ ErrorArg tag, CustomErrorHasDoc tag, KnownError err) => Label tag -> (err ': s) :-> any Source #
Fail with given custom error.
type RequireNoArgError tag msg = (TypeErrorUnless (ErrorArg tag == ()) msg, msg ~ (Text "Expected no-arg error, but given error requires argument of type " :<>: ShowType (ErrorArg tag))) Source #
failCustom_ :: forall tag s any notVoidErrorMsg. (RequireNoArgError tag notVoidErrorMsg, CustomErrorHasDoc tag) => Label tag -> s :-> any Source #
Specialization of failCustom
for no-arg errors.
Documentation
data ErrorClass Source #
Error class on how the error should be handled by the client.
ErrClassActionException | Normal expected error. Examples: "insufficient balance", "wallet does not exist". |
ErrClassBadArgument | Invalid argument passed to entrypoint.
Examples: your entrypoint accepts an enum represented as |
ErrClassContractInternal | Unexpected error. Most likely it means that there is a bug in the contract or the contract has been deployed incorrectly. |
ErrClassUnknown | It's possible to leave error class unspecified. |
Instances
Buildable ErrorClass Source # | |
Defined in Lorentz.Errors build :: ErrorClass -> Builder # |
class (KnownSymbol tag, TypeHasDoc (ErrorArg tag), IsError (CustomError tag)) => CustomErrorHasDoc tag where Source #
customErrDocMdCause :: Markdown Source #
What should happen for this error to be raised.
customErrDocMdCauseInEntrypoint :: Markdown Source #
Brief version of customErrDocMdCause
.
This will appear along with the error when mentioned in entrypoint description.
By default, the first sentence of the full description is used.
customErrClass :: ErrorClass Source #
Error class.
By default this returns "unknown error" class; though you should provide explicit implementation in order to avoid a warning.
customErrArgumentSemantics :: Maybe Markdown Source #
Clarification of error argument meaning.
Provide when it's not obvious, e.g. argument is not named with :!
.
NOTE: This should not be an entire sentence, rather just the semantic backbone.
Bad:
* Error argument stands for the previous value of approval.
Good:
* the previous value of approval
* pair, first argument of which is one thing, and the second is another
Instances
CustomErrorHasDoc "emptySupplied" Source # | |
CustomErrorHasDoc "senderIsNotAdmin" Source # | |
CustomErrorHasDoc "uparamArgumentUnpackFailed" Source # | |
CustomErrorHasDoc "uparamNoSuchEntryPoint" Source # | |
Mentions that contract uses given error.
Instances
Eq DError Source # | |
Ord DError Source # | |
DocItem DError Source # | |
Defined in Lorentz.Errors type DocItemPosition DError = (pos :: Nat) Source # type DocItemPlacement DError :: DocItemPlacementKind Source # docItemSectionName :: Maybe Text Source # docItemSectionDescription :: Maybe Markdown Source # docItemSectionNameStyle :: DocSectionNameStyle Source # docItemRef :: DError -> DocItemRef (DocItemPlacement DError) Source # docItemToMarkdown :: HeaderLevel -> DError -> Markdown Source # docItemDependencies :: DError -> [SomeDocDefinitionItem] Source # docItemsOrder :: [DError] -> [DError] Source # | |
type DocItemPosition DError Source # | |
Defined in Lorentz.Errors | |
type DocItemPlacement DError Source # | |
Defined in Lorentz.Errors |
Documentation for custom errors.
Mentions that entrypoint throws given error.
Instances
Eq DThrows Source # | |
DocItem DThrows Source # | |
Defined in Lorentz.Errors type DocItemPosition DThrows = (pos :: Nat) Source # type DocItemPlacement DThrows :: DocItemPlacementKind Source # docItemSectionName :: Maybe Text Source # docItemSectionDescription :: Maybe Markdown Source # docItemSectionNameStyle :: DocSectionNameStyle Source # docItemRef :: DThrows -> DocItemRef (DocItemPlacement DThrows) Source # docItemToMarkdown :: HeaderLevel -> DThrows -> Markdown Source # docItemDependencies :: DThrows -> [SomeDocDefinitionItem] Source # docItemsOrder :: [DThrows] -> [DThrows] Source # | |
type DocItemPosition DThrows Source # | |
Defined in Lorentz.Errors | |
type DocItemPlacement DThrows Source # | |
Defined in Lorentz.Errors |
Old interface (DEPRECATED)
customErrorToVal :: (LooseSumC e, HasCallStack) => e -> (forall t. ErrorScope t => Value t -> r) -> r Source #
Deprecated: Datatype error declarations has been deprecated
Implementation of errorToVal
for custom errors.
customErrorFromVal :: forall t e. (SingI t, LooseSumC e) => Value t -> Either Text e Source #
Deprecated: Datatype error declarations has been deprecated
Implementation of errorFromVal
for custom errors.
This function is deprecated.
failUsingArg :: forall err name fieldTy s s'. FailUsingArg err name fieldTy s s' Source #
Deprecated: Datatype error declarations has been deprecated
Fail with given error, picking argument for error from the top of the stack.
If your error constructor does not carry an argument, use failUsing
function instead.
Consider the following practice: once error datatype for your contract
is defined, create a specialization of this function to the error type.
This function is deprecated.
type FailUsingArg e name fieldTy s s' = (KnownSymbol name, IsError e, IsoValue fieldTy, CtorHasOnlyField name e fieldTy, Each [Typeable, SingI] '[ToT fieldTy], HasCallStack) => Label name -> (fieldTy ': s) :-> s' Source #
Signature of userFailWith
.
type family CustomErrorNoIsoValue a where ... Source #
Prompt an error message saying that IsoValue
is not applicable for this type.
errorsDocumentation :: Markdown Source #
This is to be included on top of Errors
section of the generated
documentation.