{-# OPTIONS_GHC -Wno-orphans #-}
module Lorentz.Empty
( Empty
, absurd_
) where
import Fmt (Buildable(..))
import Lorentz.Base
import Lorentz.Doc
import Lorentz.Errors
import Lorentz.Value
import Michelson.Typed.Haskell.Doc
newtype Empty = Empty ()
deriving stock Generic
deriving anyclass IsoValue
instance TypeHasDoc Empty where
typeDocMdDescription =
"Type which should never be constructed.\n\n\
\If appears as part of entrypoint argument, this means that the entrypoint \
\should never be called."
type instance ErrorArg "emptySupplied" = ()
instance Buildable (CustomError "emptySupplied") where
build (CustomError _ ()) =
"'Empty' value was passed to the contract."
instance CustomErrorHasDoc "emptySupplied" where
customErrClass = ErrClassBadArgument
customErrDocMdCause =
"Value of type " <> typeDocMdReference (Proxy @Empty) (WithinParens False)
<> " has been supplied."
absurd_ :: Empty : s :-> s'
absurd_ =
failCustom_ #emptySupplied #
doc (DDescription "Should never be called")