lorentz-0.1.0: EDSL for the Michelson Language

Safe HaskellNone
LanguageHaskell2010

Lorentz.Errors

Contents

Synopsis

Haskell to Value conversion

class (Typeable e, ErrorHasDoc e) => IsError e where Source #

Haskell type representing error.

Methods

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 # 
Instance details

Defined in Lorentz.Errors

Methods

errorToVal :: () -> (forall (t :: T). ErrorScope t => Value t -> r) -> r Source #

errorFromVal :: (Typeable t, SingI t) => Value t -> Either Text () Source #

IsError MText Source #

Use this for internal errors only.

Normal error scenarios should use the mechanism of custom errors, see below.

Instance details

Defined in Lorentz.Errors

Methods

errorToVal :: MText -> (forall (t :: T). ErrorScope t => Value t -> r) -> r Source #

errorFromVal :: (Typeable t, SingI t) => Value t -> Either Text MText Source #

IsError UnspecifiedError Source # 
Instance details

Defined in Lorentz.Errors

Methods

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 # 
Instance details

Defined in Lorentz.Errors

Methods

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 # 
Instance details

Defined in Lorentz.Macro

Methods

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 CustomError constructor is not provided its argument, we assume that this is no-arg error and interpret the passed value as complete.

Instance details

Defined in Lorentz.Errors

Methods

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 #

Methods

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 # 
Instance details

Defined in Lorentz.Errors

ErrorHasDoc MText Source # 
Instance details

Defined in Lorentz.Errors

ErrorHasDoc UnspecifiedError Source # 
Instance details

Defined in Lorentz.Errors

(CustomErrorHasDoc tag, SingI (ToT (ErrorArg tag))) => ErrorHasDoc (CustomError tag :: Type) Source # 
Instance details

Defined in Lorentz.Errors

TypeHasDoc r => ErrorHasDoc (VoidResult r :: Type) Source # 
Instance details

Defined in Lorentz.Macro

ErrorHasDoc (CustomError tag) => ErrorHasDoc (arg -> CustomError tag :: Type) Source # 
Instance details

Defined in Lorentz.Errors

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.

Constructors

UnspecifiedError 
Instances
Generic UnspecifiedError Source # 
Instance details

Defined in Lorentz.Errors

Associated Types

type Rep UnspecifiedError :: Type -> Type #

IsoValue UnspecifiedError Source # 
Instance details

Defined in Lorentz.Errors

Associated Types

type ToT UnspecifiedError :: T #

IsError UnspecifiedError Source # 
Instance details

Defined in Lorentz.Errors

Methods

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 # 
Instance details

Defined in Lorentz.Errors

type Rep UnspecifiedError Source # 
Instance details

Defined in Lorentz.Errors

type Rep UnspecifiedError = D1 (MetaData "UnspecifiedError" "Lorentz.Errors" "lorentz-0.1.0-1IijY81BuYC4to9wXiBP3G" False) (C1 (MetaCons "UnspecifiedError" PrefixI False) (U1 :: Type -> Type))
type ToT UnspecifiedError Source # 
Instance details

Defined in Lorentz.Errors

General instructions

failUsing :: forall e s t. IsError e => e -> s :-> t Source #

Fail with the given Haskell value.

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 Empty type.

Instance details

Defined in Lorentz.Empty

type ErrorArg "emptySupplied" = ()
type ErrorArg "senderIsNotAdmin" Source #

Contract initiator should be contract admin in order to perform this operation.

Instance details

Defined in Lorentz.Errors.Common

type ErrorArg "senderIsNotAdmin" = ()
type ErrorArg "uparamArgumentUnpackFailed" Source # 
Instance details

Defined in Lorentz.UParam

type ErrorArg "uparamArgumentUnpackFailed" = ()
type ErrorArg "uparamNoSuchEntryPoint" Source # 
Instance details

Defined in Lorentz.UParam

type ErrorArg "uparamNoSuchEntryPoint" = MText

data CustomError (tag :: Symbol) Source #

Material custom error.

Use this in pattern matches against error (e.g. in tests).

Constructors

CustomError 

Fields

Instances
Eq (ErrorArg tag) => Eq (CustomError tag) Source # 
Instance details

Defined in Lorentz.Errors

Methods

(==) :: CustomError tag -> CustomError tag -> Bool #

(/=) :: CustomError tag -> CustomError tag -> Bool #

Show (ErrorArg tag) => Show (CustomError tag) Source # 
Instance details

Defined in Lorentz.Errors

Methods

showsPrec :: Int -> CustomError tag -> ShowS #

show :: CustomError tag -> String #

showList :: [CustomError tag] -> ShowS #

Buildable (CustomError "emptySupplied") Source # 
Instance details

Defined in Lorentz.Empty

Methods

build :: CustomError "emptySupplied" -> Builder #

Buildable (CustomError "senderIsNotAdmin") Source # 
Instance details

Defined in Lorentz.Errors.Common

Methods

build :: CustomError "senderIsNotAdmin" -> Builder #

Buildable (CustomError "uparamArgumentUnpackFailed") Source # 
Instance details

Defined in Lorentz.UParam

Methods

build :: CustomError "uparamArgumentUnpackFailed" -> Builder #

Buildable (CustomError "uparamNoSuchEntryPoint") Source # 
Instance details

Defined in Lorentz.UParam

Methods

build :: CustomError "uparamNoSuchEntryPoint" -> Builder #

(TypeError (Text "CustomError has no IsoValue instance") :: Constraint) => IsoValue (CustomError tag) Source #

This instance cannot be implemented, use IsError instance instead.

Instance details

Defined in Lorentz.Errors

Associated Types

type ToT (CustomError tag) :: T #

Methods

toVal :: CustomError tag -> Value (ToT (CustomError tag)) #

fromVal :: Value (ToT (CustomError tag)) -> CustomError tag #

(CustomErrorHasDoc tag, KnownError (ErrorArg tag), IsoValue (ErrorArg tag)) => IsError (CustomError tag) Source # 
Instance details

Defined in Lorentz.Errors

Methods

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 # 
Instance details

Defined in Lorentz.Errors

ErrorHasDoc (CustomError tag) => ErrorHasDoc (arg -> CustomError tag :: Type) Source # 
Instance details

Defined in Lorentz.Errors

Eq (ErrorArg tag) => Eq (() -> CustomError tag) Source # 
Instance details

Defined in Lorentz.Errors

Methods

(==) :: (() -> CustomError tag) -> (() -> CustomError tag) -> Bool #

(/=) :: (() -> CustomError tag) -> (() -> CustomError tag) -> Bool #

Show (ErrorArg tag) => Show (() -> CustomError tag) Source # 
Instance details

Defined in Lorentz.Errors

Methods

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 CustomError constructor is not provided its argument, we assume that this is no-arg error and interpret the passed value as complete.

Instance details

Defined in Lorentz.Errors

Methods

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 # 
Instance details

Defined in Lorentz.Errors

type ToT (CustomError tag) = (TypeError (Text "CustomError has no IsoValue instance") :: T)

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.

Constructors

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 nat, and unknown value is provided. This includes more complex cases which involve multiple entrypoints. E.g. API provides iterator interface, middleware should care about using it hiding complex details and exposing a simpler API to user; then an attempt to request non-existing element would also correspond to an error from this class.

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 # 
Instance details

Defined in Lorentz.Errors

Methods

build :: ErrorClass -> Builder #

class (KnownSymbol tag, TypeHasDoc (ErrorArg tag), IsError (CustomError tag)) => CustomErrorHasDoc tag where Source #

Minimal complete definition

customErrDocMdCause, customErrClass

Methods

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

data DError where Source #

Mentions that contract uses given error.

Constructors

DError :: IsError e => Proxy e -> DError 

data DThrows where Source #

Documentation for custom errors.

Mentions that entrypoint throws given error.

Constructors

DThrows :: IsError e => Proxy e -> DThrows 

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.

Equations

CustomErrorNoIsoValue a = TypeError ((Text "No IsoValue instance for " :<>: ShowType a) :$$: Text "It has custom error representation") 

deriveCustomError :: Name -> Q [Dec] Source #

Deprecated: Datatype error declarations has been deprecated

Derive IsError instance for given type.

This will also forbid deriving IsoValue instance for that type to avoid having multiple different Michelson representations.

errorsDocumentation :: Markdown Source #

This is to be included on top of Errors section of the generated documentation.