{-# OPTIONS_GHC -Wno-orphans #-}

-- | Some common errors.
--
-- Such registry makes sense, as soon as errors are declared globally.
module Lorentz.Errors.Common () where

import Fmt (Buildable(..))

import Lorentz.Errors

----------------------------------------------------------------------------
-- Authorization
----------------------------------------------------------------------------

-- | Contract initiator should be contract admin in order to perform this
-- operation.
type instance ErrorArg "senderIsNotAdmin" = ()

instance Buildable (CustomError "senderIsNotAdmin") where
  build (CustomError _ ()) =
    "This operation can be executed only by admin, but is invoked by \
    \someone else"

instance CustomErrorHasDoc "senderIsNotAdmin" where
  customErrClass = ErrClassActionException
  customErrDocMdCause =
    "Entrypoint executed not by its administrator."