{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE StrictData #-}
module OTel.API.Trace.Core.TraceState.Errors
  ( TraceStateErrors(..)
  , TraceStateError(..)
  , TraceStateSimpleKeyIsEmptyError(..)
  , TraceStateSimpleKeyContainsInvalidCharsError(..)
  , TraceStateTenantIdIsEmptyError(..)
  , TraceStateTenantIdContainsInvalidCharsError(..)
  , TraceStateSystemIdIsEmptyError(..)
  , TraceStateSystemIdContainsInvalidCharsError(..)
  , TraceStateSimpleKeyTooLongError(..)
  , TraceStateTenantIdTooLongError(..)
  , TraceStateSystemIdTooLongError(..)
  , TraceStateKeyTypeUnknownError(..)
  , TraceStateValueIsEmptyError(..)
  , TraceStateValueContainsInvalidCharsError(..)
  , TraceStateValueTooLongError(..)
  ) where

import Control.Monad.Catch (Exception)
import Data.Text (Text)
import OTel.API.Common (Key)
import Prelude

newtype TraceStateErrors = TraceStateErrors
  { TraceStateErrors -> [TraceStateError]
unTraceStateErrors :: [TraceStateError]
  } deriving stock (TraceStateErrors -> TraceStateErrors -> Bool
(TraceStateErrors -> TraceStateErrors -> Bool)
-> (TraceStateErrors -> TraceStateErrors -> Bool)
-> Eq TraceStateErrors
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TraceStateErrors -> TraceStateErrors -> Bool
== :: TraceStateErrors -> TraceStateErrors -> Bool
$c/= :: TraceStateErrors -> TraceStateErrors -> Bool
/= :: TraceStateErrors -> TraceStateErrors -> Bool
Eq, Int -> TraceStateErrors -> ShowS
[TraceStateErrors] -> ShowS
TraceStateErrors -> String
(Int -> TraceStateErrors -> ShowS)
-> (TraceStateErrors -> String)
-> ([TraceStateErrors] -> ShowS)
-> Show TraceStateErrors
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TraceStateErrors -> ShowS
showsPrec :: Int -> TraceStateErrors -> ShowS
$cshow :: TraceStateErrors -> String
show :: TraceStateErrors -> String
$cshowList :: [TraceStateErrors] -> ShowS
showList :: [TraceStateErrors] -> ShowS
Show)
    deriving anyclass (Show TraceStateErrors
Typeable TraceStateErrors
(Typeable TraceStateErrors, Show TraceStateErrors) =>
(TraceStateErrors -> SomeException)
-> (SomeException -> Maybe TraceStateErrors)
-> (TraceStateErrors -> String)
-> Exception TraceStateErrors
SomeException -> Maybe TraceStateErrors
TraceStateErrors -> String
TraceStateErrors -> SomeException
forall e.
(Typeable e, Show e) =>
(e -> SomeException)
-> (SomeException -> Maybe e) -> (e -> String) -> Exception e
$ctoException :: TraceStateErrors -> SomeException
toException :: TraceStateErrors -> SomeException
$cfromException :: SomeException -> Maybe TraceStateErrors
fromException :: SomeException -> Maybe TraceStateErrors
$cdisplayException :: TraceStateErrors -> String
displayException :: TraceStateErrors -> String
Exception)

data TraceStateError
  = TraceStateSimpleKeyIsEmpty TraceStateSimpleKeyIsEmptyError
  | TraceStateSimpleKeyContainsInvalidChars TraceStateSimpleKeyContainsInvalidCharsError
  | TraceStateTenantIdIsEmpty TraceStateTenantIdIsEmptyError
  | TraceStateTenantIdContainsInvalidChars TraceStateTenantIdContainsInvalidCharsError
  | TraceStateSystemIdIsEmpty TraceStateSystemIdIsEmptyError
  | TraceStateSystemIdContainsInvalidChars TraceStateSystemIdContainsInvalidCharsError
  | TraceStateSimpleKeyTooLong TraceStateSimpleKeyTooLongError
  | TraceStateTenantIdTooLong TraceStateTenantIdTooLongError
  | TraceStateSystemIdTooLong TraceStateSystemIdTooLongError
  | TraceStateKeyTypeUnknown TraceStateKeyTypeUnknownError
  | TraceStateValueIsEmpty TraceStateValueIsEmptyError
  | TraceStateValueContainsInvalidChars TraceStateValueContainsInvalidCharsError
  | TraceStateValueTooLong TraceStateValueTooLongError
  deriving stock (TraceStateError -> TraceStateError -> Bool
(TraceStateError -> TraceStateError -> Bool)
-> (TraceStateError -> TraceStateError -> Bool)
-> Eq TraceStateError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TraceStateError -> TraceStateError -> Bool
== :: TraceStateError -> TraceStateError -> Bool
$c/= :: TraceStateError -> TraceStateError -> Bool
/= :: TraceStateError -> TraceStateError -> Bool
Eq, Int -> TraceStateError -> ShowS
[TraceStateError] -> ShowS
TraceStateError -> String
(Int -> TraceStateError -> ShowS)
-> (TraceStateError -> String)
-> ([TraceStateError] -> ShowS)
-> Show TraceStateError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TraceStateError -> ShowS
showsPrec :: Int -> TraceStateError -> ShowS
$cshow :: TraceStateError -> String
show :: TraceStateError -> String
$cshowList :: [TraceStateError] -> ShowS
showList :: [TraceStateError] -> ShowS
Show)

newtype TraceStateSimpleKeyIsEmptyError = TraceStateSimpleKeyIsEmptyError
  { TraceStateSimpleKeyIsEmptyError -> Text
rawValue :: Text
  } deriving stock (TraceStateSimpleKeyIsEmptyError
-> TraceStateSimpleKeyIsEmptyError -> Bool
(TraceStateSimpleKeyIsEmptyError
 -> TraceStateSimpleKeyIsEmptyError -> Bool)
-> (TraceStateSimpleKeyIsEmptyError
    -> TraceStateSimpleKeyIsEmptyError -> Bool)
-> Eq TraceStateSimpleKeyIsEmptyError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TraceStateSimpleKeyIsEmptyError
-> TraceStateSimpleKeyIsEmptyError -> Bool
== :: TraceStateSimpleKeyIsEmptyError
-> TraceStateSimpleKeyIsEmptyError -> Bool
$c/= :: TraceStateSimpleKeyIsEmptyError
-> TraceStateSimpleKeyIsEmptyError -> Bool
/= :: TraceStateSimpleKeyIsEmptyError
-> TraceStateSimpleKeyIsEmptyError -> Bool
Eq, Int -> TraceStateSimpleKeyIsEmptyError -> ShowS
[TraceStateSimpleKeyIsEmptyError] -> ShowS
TraceStateSimpleKeyIsEmptyError -> String
(Int -> TraceStateSimpleKeyIsEmptyError -> ShowS)
-> (TraceStateSimpleKeyIsEmptyError -> String)
-> ([TraceStateSimpleKeyIsEmptyError] -> ShowS)
-> Show TraceStateSimpleKeyIsEmptyError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TraceStateSimpleKeyIsEmptyError -> ShowS
showsPrec :: Int -> TraceStateSimpleKeyIsEmptyError -> ShowS
$cshow :: TraceStateSimpleKeyIsEmptyError -> String
show :: TraceStateSimpleKeyIsEmptyError -> String
$cshowList :: [TraceStateSimpleKeyIsEmptyError] -> ShowS
showList :: [TraceStateSimpleKeyIsEmptyError] -> ShowS
Show)

data TraceStateSimpleKeyContainsInvalidCharsError = TraceStateSimpleKeyContainsInvalidCharsError
  { TraceStateSimpleKeyContainsInvalidCharsError -> Key Text
rawKey :: Key Text
  , TraceStateSimpleKeyContainsInvalidCharsError -> Text
rawValue :: Text
  , TraceStateSimpleKeyContainsInvalidCharsError -> Text
invalidChars :: Text
  } deriving stock (TraceStateSimpleKeyContainsInvalidCharsError
-> TraceStateSimpleKeyContainsInvalidCharsError -> Bool
(TraceStateSimpleKeyContainsInvalidCharsError
 -> TraceStateSimpleKeyContainsInvalidCharsError -> Bool)
-> (TraceStateSimpleKeyContainsInvalidCharsError
    -> TraceStateSimpleKeyContainsInvalidCharsError -> Bool)
-> Eq TraceStateSimpleKeyContainsInvalidCharsError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TraceStateSimpleKeyContainsInvalidCharsError
-> TraceStateSimpleKeyContainsInvalidCharsError -> Bool
== :: TraceStateSimpleKeyContainsInvalidCharsError
-> TraceStateSimpleKeyContainsInvalidCharsError -> Bool
$c/= :: TraceStateSimpleKeyContainsInvalidCharsError
-> TraceStateSimpleKeyContainsInvalidCharsError -> Bool
/= :: TraceStateSimpleKeyContainsInvalidCharsError
-> TraceStateSimpleKeyContainsInvalidCharsError -> Bool
Eq, Int -> TraceStateSimpleKeyContainsInvalidCharsError -> ShowS
[TraceStateSimpleKeyContainsInvalidCharsError] -> ShowS
TraceStateSimpleKeyContainsInvalidCharsError -> String
(Int -> TraceStateSimpleKeyContainsInvalidCharsError -> ShowS)
-> (TraceStateSimpleKeyContainsInvalidCharsError -> String)
-> ([TraceStateSimpleKeyContainsInvalidCharsError] -> ShowS)
-> Show TraceStateSimpleKeyContainsInvalidCharsError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TraceStateSimpleKeyContainsInvalidCharsError -> ShowS
showsPrec :: Int -> TraceStateSimpleKeyContainsInvalidCharsError -> ShowS
$cshow :: TraceStateSimpleKeyContainsInvalidCharsError -> String
show :: TraceStateSimpleKeyContainsInvalidCharsError -> String
$cshowList :: [TraceStateSimpleKeyContainsInvalidCharsError] -> ShowS
showList :: [TraceStateSimpleKeyContainsInvalidCharsError] -> ShowS
Show)

data TraceStateTenantIdIsEmptyError = TraceStateTenantIdIsEmptyError
  { TraceStateTenantIdIsEmptyError -> Text
rawSystemId :: Text
  , TraceStateTenantIdIsEmptyError -> Text
rawValue :: Text
  } deriving stock (TraceStateTenantIdIsEmptyError
-> TraceStateTenantIdIsEmptyError -> Bool
(TraceStateTenantIdIsEmptyError
 -> TraceStateTenantIdIsEmptyError -> Bool)
-> (TraceStateTenantIdIsEmptyError
    -> TraceStateTenantIdIsEmptyError -> Bool)
-> Eq TraceStateTenantIdIsEmptyError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TraceStateTenantIdIsEmptyError
-> TraceStateTenantIdIsEmptyError -> Bool
== :: TraceStateTenantIdIsEmptyError
-> TraceStateTenantIdIsEmptyError -> Bool
$c/= :: TraceStateTenantIdIsEmptyError
-> TraceStateTenantIdIsEmptyError -> Bool
/= :: TraceStateTenantIdIsEmptyError
-> TraceStateTenantIdIsEmptyError -> Bool
Eq, Int -> TraceStateTenantIdIsEmptyError -> ShowS
[TraceStateTenantIdIsEmptyError] -> ShowS
TraceStateTenantIdIsEmptyError -> String
(Int -> TraceStateTenantIdIsEmptyError -> ShowS)
-> (TraceStateTenantIdIsEmptyError -> String)
-> ([TraceStateTenantIdIsEmptyError] -> ShowS)
-> Show TraceStateTenantIdIsEmptyError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TraceStateTenantIdIsEmptyError -> ShowS
showsPrec :: Int -> TraceStateTenantIdIsEmptyError -> ShowS
$cshow :: TraceStateTenantIdIsEmptyError -> String
show :: TraceStateTenantIdIsEmptyError -> String
$cshowList :: [TraceStateTenantIdIsEmptyError] -> ShowS
showList :: [TraceStateTenantIdIsEmptyError] -> ShowS
Show)

data TraceStateTenantIdContainsInvalidCharsError = TraceStateTenantIdContainsInvalidCharsError
  { TraceStateTenantIdContainsInvalidCharsError -> Text
rawTenantId :: Text
  , TraceStateTenantIdContainsInvalidCharsError -> Text
rawSystemId :: Text
  , TraceStateTenantIdContainsInvalidCharsError -> Text
rawValue :: Text
  , TraceStateTenantIdContainsInvalidCharsError -> Text
invalidChars :: Text
  } deriving stock (TraceStateTenantIdContainsInvalidCharsError
-> TraceStateTenantIdContainsInvalidCharsError -> Bool
(TraceStateTenantIdContainsInvalidCharsError
 -> TraceStateTenantIdContainsInvalidCharsError -> Bool)
-> (TraceStateTenantIdContainsInvalidCharsError
    -> TraceStateTenantIdContainsInvalidCharsError -> Bool)
-> Eq TraceStateTenantIdContainsInvalidCharsError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TraceStateTenantIdContainsInvalidCharsError
-> TraceStateTenantIdContainsInvalidCharsError -> Bool
== :: TraceStateTenantIdContainsInvalidCharsError
-> TraceStateTenantIdContainsInvalidCharsError -> Bool
$c/= :: TraceStateTenantIdContainsInvalidCharsError
-> TraceStateTenantIdContainsInvalidCharsError -> Bool
/= :: TraceStateTenantIdContainsInvalidCharsError
-> TraceStateTenantIdContainsInvalidCharsError -> Bool
Eq, Int -> TraceStateTenantIdContainsInvalidCharsError -> ShowS
[TraceStateTenantIdContainsInvalidCharsError] -> ShowS
TraceStateTenantIdContainsInvalidCharsError -> String
(Int -> TraceStateTenantIdContainsInvalidCharsError -> ShowS)
-> (TraceStateTenantIdContainsInvalidCharsError -> String)
-> ([TraceStateTenantIdContainsInvalidCharsError] -> ShowS)
-> Show TraceStateTenantIdContainsInvalidCharsError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TraceStateTenantIdContainsInvalidCharsError -> ShowS
showsPrec :: Int -> TraceStateTenantIdContainsInvalidCharsError -> ShowS
$cshow :: TraceStateTenantIdContainsInvalidCharsError -> String
show :: TraceStateTenantIdContainsInvalidCharsError -> String
$cshowList :: [TraceStateTenantIdContainsInvalidCharsError] -> ShowS
showList :: [TraceStateTenantIdContainsInvalidCharsError] -> ShowS
Show)

data TraceStateSystemIdIsEmptyError = TraceStateSystemIdIsEmptyError
  { TraceStateSystemIdIsEmptyError -> Text
rawSystemId :: Text
  , TraceStateSystemIdIsEmptyError -> Text
rawValue :: Text
  } deriving stock (TraceStateSystemIdIsEmptyError
-> TraceStateSystemIdIsEmptyError -> Bool
(TraceStateSystemIdIsEmptyError
 -> TraceStateSystemIdIsEmptyError -> Bool)
-> (TraceStateSystemIdIsEmptyError
    -> TraceStateSystemIdIsEmptyError -> Bool)
-> Eq TraceStateSystemIdIsEmptyError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TraceStateSystemIdIsEmptyError
-> TraceStateSystemIdIsEmptyError -> Bool
== :: TraceStateSystemIdIsEmptyError
-> TraceStateSystemIdIsEmptyError -> Bool
$c/= :: TraceStateSystemIdIsEmptyError
-> TraceStateSystemIdIsEmptyError -> Bool
/= :: TraceStateSystemIdIsEmptyError
-> TraceStateSystemIdIsEmptyError -> Bool
Eq, Int -> TraceStateSystemIdIsEmptyError -> ShowS
[TraceStateSystemIdIsEmptyError] -> ShowS
TraceStateSystemIdIsEmptyError -> String
(Int -> TraceStateSystemIdIsEmptyError -> ShowS)
-> (TraceStateSystemIdIsEmptyError -> String)
-> ([TraceStateSystemIdIsEmptyError] -> ShowS)
-> Show TraceStateSystemIdIsEmptyError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TraceStateSystemIdIsEmptyError -> ShowS
showsPrec :: Int -> TraceStateSystemIdIsEmptyError -> ShowS
$cshow :: TraceStateSystemIdIsEmptyError -> String
show :: TraceStateSystemIdIsEmptyError -> String
$cshowList :: [TraceStateSystemIdIsEmptyError] -> ShowS
showList :: [TraceStateSystemIdIsEmptyError] -> ShowS
Show)

data TraceStateSystemIdContainsInvalidCharsError = TraceStateSystemIdContainsInvalidCharsError
  { TraceStateSystemIdContainsInvalidCharsError -> Text
rawTenantId :: Text
  , TraceStateSystemIdContainsInvalidCharsError -> Text
rawSystemId :: Text
  , TraceStateSystemIdContainsInvalidCharsError -> Text
rawValue :: Text
  , TraceStateSystemIdContainsInvalidCharsError -> Text
invalidChars :: Text
  } deriving stock (TraceStateSystemIdContainsInvalidCharsError
-> TraceStateSystemIdContainsInvalidCharsError -> Bool
(TraceStateSystemIdContainsInvalidCharsError
 -> TraceStateSystemIdContainsInvalidCharsError -> Bool)
-> (TraceStateSystemIdContainsInvalidCharsError
    -> TraceStateSystemIdContainsInvalidCharsError -> Bool)
-> Eq TraceStateSystemIdContainsInvalidCharsError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TraceStateSystemIdContainsInvalidCharsError
-> TraceStateSystemIdContainsInvalidCharsError -> Bool
== :: TraceStateSystemIdContainsInvalidCharsError
-> TraceStateSystemIdContainsInvalidCharsError -> Bool
$c/= :: TraceStateSystemIdContainsInvalidCharsError
-> TraceStateSystemIdContainsInvalidCharsError -> Bool
/= :: TraceStateSystemIdContainsInvalidCharsError
-> TraceStateSystemIdContainsInvalidCharsError -> Bool
Eq, Int -> TraceStateSystemIdContainsInvalidCharsError -> ShowS
[TraceStateSystemIdContainsInvalidCharsError] -> ShowS
TraceStateSystemIdContainsInvalidCharsError -> String
(Int -> TraceStateSystemIdContainsInvalidCharsError -> ShowS)
-> (TraceStateSystemIdContainsInvalidCharsError -> String)
-> ([TraceStateSystemIdContainsInvalidCharsError] -> ShowS)
-> Show TraceStateSystemIdContainsInvalidCharsError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TraceStateSystemIdContainsInvalidCharsError -> ShowS
showsPrec :: Int -> TraceStateSystemIdContainsInvalidCharsError -> ShowS
$cshow :: TraceStateSystemIdContainsInvalidCharsError -> String
show :: TraceStateSystemIdContainsInvalidCharsError -> String
$cshowList :: [TraceStateSystemIdContainsInvalidCharsError] -> ShowS
showList :: [TraceStateSystemIdContainsInvalidCharsError] -> ShowS
Show)

data TraceStateSimpleKeyTooLongError = TraceStateSimpleKeyTooLongError
  { TraceStateSimpleKeyTooLongError -> Key Text
rawKey :: Key Text
  , TraceStateSimpleKeyTooLongError -> Text
rawValue :: Text
  } deriving stock (TraceStateSimpleKeyTooLongError
-> TraceStateSimpleKeyTooLongError -> Bool
(TraceStateSimpleKeyTooLongError
 -> TraceStateSimpleKeyTooLongError -> Bool)
-> (TraceStateSimpleKeyTooLongError
    -> TraceStateSimpleKeyTooLongError -> Bool)
-> Eq TraceStateSimpleKeyTooLongError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TraceStateSimpleKeyTooLongError
-> TraceStateSimpleKeyTooLongError -> Bool
== :: TraceStateSimpleKeyTooLongError
-> TraceStateSimpleKeyTooLongError -> Bool
$c/= :: TraceStateSimpleKeyTooLongError
-> TraceStateSimpleKeyTooLongError -> Bool
/= :: TraceStateSimpleKeyTooLongError
-> TraceStateSimpleKeyTooLongError -> Bool
Eq, Int -> TraceStateSimpleKeyTooLongError -> ShowS
[TraceStateSimpleKeyTooLongError] -> ShowS
TraceStateSimpleKeyTooLongError -> String
(Int -> TraceStateSimpleKeyTooLongError -> ShowS)
-> (TraceStateSimpleKeyTooLongError -> String)
-> ([TraceStateSimpleKeyTooLongError] -> ShowS)
-> Show TraceStateSimpleKeyTooLongError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TraceStateSimpleKeyTooLongError -> ShowS
showsPrec :: Int -> TraceStateSimpleKeyTooLongError -> ShowS
$cshow :: TraceStateSimpleKeyTooLongError -> String
show :: TraceStateSimpleKeyTooLongError -> String
$cshowList :: [TraceStateSimpleKeyTooLongError] -> ShowS
showList :: [TraceStateSimpleKeyTooLongError] -> ShowS
Show)

data TraceStateTenantIdTooLongError = TraceStateTenantIdTooLongError
  { TraceStateTenantIdTooLongError -> Text
rawTenantId :: Text
  , TraceStateTenantIdTooLongError -> Text
rawSystemId :: Text
  , TraceStateTenantIdTooLongError -> Text
rawValue :: Text
  } deriving stock (TraceStateTenantIdTooLongError
-> TraceStateTenantIdTooLongError -> Bool
(TraceStateTenantIdTooLongError
 -> TraceStateTenantIdTooLongError -> Bool)
-> (TraceStateTenantIdTooLongError
    -> TraceStateTenantIdTooLongError -> Bool)
-> Eq TraceStateTenantIdTooLongError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TraceStateTenantIdTooLongError
-> TraceStateTenantIdTooLongError -> Bool
== :: TraceStateTenantIdTooLongError
-> TraceStateTenantIdTooLongError -> Bool
$c/= :: TraceStateTenantIdTooLongError
-> TraceStateTenantIdTooLongError -> Bool
/= :: TraceStateTenantIdTooLongError
-> TraceStateTenantIdTooLongError -> Bool
Eq, Int -> TraceStateTenantIdTooLongError -> ShowS
[TraceStateTenantIdTooLongError] -> ShowS
TraceStateTenantIdTooLongError -> String
(Int -> TraceStateTenantIdTooLongError -> ShowS)
-> (TraceStateTenantIdTooLongError -> String)
-> ([TraceStateTenantIdTooLongError] -> ShowS)
-> Show TraceStateTenantIdTooLongError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TraceStateTenantIdTooLongError -> ShowS
showsPrec :: Int -> TraceStateTenantIdTooLongError -> ShowS
$cshow :: TraceStateTenantIdTooLongError -> String
show :: TraceStateTenantIdTooLongError -> String
$cshowList :: [TraceStateTenantIdTooLongError] -> ShowS
showList :: [TraceStateTenantIdTooLongError] -> ShowS
Show)

data TraceStateSystemIdTooLongError = TraceStateSystemIdTooLongError
  { TraceStateSystemIdTooLongError -> Text
rawTenantId :: Text
  , TraceStateSystemIdTooLongError -> Text
rawSystemId :: Text
  , TraceStateSystemIdTooLongError -> Text
rawValue :: Text
  } deriving stock (TraceStateSystemIdTooLongError
-> TraceStateSystemIdTooLongError -> Bool
(TraceStateSystemIdTooLongError
 -> TraceStateSystemIdTooLongError -> Bool)
-> (TraceStateSystemIdTooLongError
    -> TraceStateSystemIdTooLongError -> Bool)
-> Eq TraceStateSystemIdTooLongError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TraceStateSystemIdTooLongError
-> TraceStateSystemIdTooLongError -> Bool
== :: TraceStateSystemIdTooLongError
-> TraceStateSystemIdTooLongError -> Bool
$c/= :: TraceStateSystemIdTooLongError
-> TraceStateSystemIdTooLongError -> Bool
/= :: TraceStateSystemIdTooLongError
-> TraceStateSystemIdTooLongError -> Bool
Eq, Int -> TraceStateSystemIdTooLongError -> ShowS
[TraceStateSystemIdTooLongError] -> ShowS
TraceStateSystemIdTooLongError -> String
(Int -> TraceStateSystemIdTooLongError -> ShowS)
-> (TraceStateSystemIdTooLongError -> String)
-> ([TraceStateSystemIdTooLongError] -> ShowS)
-> Show TraceStateSystemIdTooLongError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TraceStateSystemIdTooLongError -> ShowS
showsPrec :: Int -> TraceStateSystemIdTooLongError -> ShowS
$cshow :: TraceStateSystemIdTooLongError -> String
show :: TraceStateSystemIdTooLongError -> String
$cshowList :: [TraceStateSystemIdTooLongError] -> ShowS
showList :: [TraceStateSystemIdTooLongError] -> ShowS
Show)

data TraceStateKeyTypeUnknownError = TraceStateKeyTypeUnknownError
  { TraceStateKeyTypeUnknownError -> Key Text
rawKey :: Key Text
  , TraceStateKeyTypeUnknownError -> Text
rawValue :: Text
  } deriving stock (TraceStateKeyTypeUnknownError
-> TraceStateKeyTypeUnknownError -> Bool
(TraceStateKeyTypeUnknownError
 -> TraceStateKeyTypeUnknownError -> Bool)
-> (TraceStateKeyTypeUnknownError
    -> TraceStateKeyTypeUnknownError -> Bool)
-> Eq TraceStateKeyTypeUnknownError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TraceStateKeyTypeUnknownError
-> TraceStateKeyTypeUnknownError -> Bool
== :: TraceStateKeyTypeUnknownError
-> TraceStateKeyTypeUnknownError -> Bool
$c/= :: TraceStateKeyTypeUnknownError
-> TraceStateKeyTypeUnknownError -> Bool
/= :: TraceStateKeyTypeUnknownError
-> TraceStateKeyTypeUnknownError -> Bool
Eq, Int -> TraceStateKeyTypeUnknownError -> ShowS
[TraceStateKeyTypeUnknownError] -> ShowS
TraceStateKeyTypeUnknownError -> String
(Int -> TraceStateKeyTypeUnknownError -> ShowS)
-> (TraceStateKeyTypeUnknownError -> String)
-> ([TraceStateKeyTypeUnknownError] -> ShowS)
-> Show TraceStateKeyTypeUnknownError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TraceStateKeyTypeUnknownError -> ShowS
showsPrec :: Int -> TraceStateKeyTypeUnknownError -> ShowS
$cshow :: TraceStateKeyTypeUnknownError -> String
show :: TraceStateKeyTypeUnknownError -> String
$cshowList :: [TraceStateKeyTypeUnknownError] -> ShowS
showList :: [TraceStateKeyTypeUnknownError] -> ShowS
Show)

newtype TraceStateValueIsEmptyError = TraceStateValueIsEmptyError
  { TraceStateValueIsEmptyError -> Key Text
rawKey :: Key Text
  } deriving stock (TraceStateValueIsEmptyError -> TraceStateValueIsEmptyError -> Bool
(TraceStateValueIsEmptyError
 -> TraceStateValueIsEmptyError -> Bool)
-> (TraceStateValueIsEmptyError
    -> TraceStateValueIsEmptyError -> Bool)
-> Eq TraceStateValueIsEmptyError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TraceStateValueIsEmptyError -> TraceStateValueIsEmptyError -> Bool
== :: TraceStateValueIsEmptyError -> TraceStateValueIsEmptyError -> Bool
$c/= :: TraceStateValueIsEmptyError -> TraceStateValueIsEmptyError -> Bool
/= :: TraceStateValueIsEmptyError -> TraceStateValueIsEmptyError -> Bool
Eq, Int -> TraceStateValueIsEmptyError -> ShowS
[TraceStateValueIsEmptyError] -> ShowS
TraceStateValueIsEmptyError -> String
(Int -> TraceStateValueIsEmptyError -> ShowS)
-> (TraceStateValueIsEmptyError -> String)
-> ([TraceStateValueIsEmptyError] -> ShowS)
-> Show TraceStateValueIsEmptyError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TraceStateValueIsEmptyError -> ShowS
showsPrec :: Int -> TraceStateValueIsEmptyError -> ShowS
$cshow :: TraceStateValueIsEmptyError -> String
show :: TraceStateValueIsEmptyError -> String
$cshowList :: [TraceStateValueIsEmptyError] -> ShowS
showList :: [TraceStateValueIsEmptyError] -> ShowS
Show)

data TraceStateValueContainsInvalidCharsError = TraceStateValueContainsInvalidCharsError
  { TraceStateValueContainsInvalidCharsError -> Key Text
rawKey :: Key Text
  , TraceStateValueContainsInvalidCharsError -> Text
rawValue :: Text
  , TraceStateValueContainsInvalidCharsError -> Text
invalidChars :: Text
  } deriving stock (TraceStateValueContainsInvalidCharsError
-> TraceStateValueContainsInvalidCharsError -> Bool
(TraceStateValueContainsInvalidCharsError
 -> TraceStateValueContainsInvalidCharsError -> Bool)
-> (TraceStateValueContainsInvalidCharsError
    -> TraceStateValueContainsInvalidCharsError -> Bool)
-> Eq TraceStateValueContainsInvalidCharsError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TraceStateValueContainsInvalidCharsError
-> TraceStateValueContainsInvalidCharsError -> Bool
== :: TraceStateValueContainsInvalidCharsError
-> TraceStateValueContainsInvalidCharsError -> Bool
$c/= :: TraceStateValueContainsInvalidCharsError
-> TraceStateValueContainsInvalidCharsError -> Bool
/= :: TraceStateValueContainsInvalidCharsError
-> TraceStateValueContainsInvalidCharsError -> Bool
Eq, Int -> TraceStateValueContainsInvalidCharsError -> ShowS
[TraceStateValueContainsInvalidCharsError] -> ShowS
TraceStateValueContainsInvalidCharsError -> String
(Int -> TraceStateValueContainsInvalidCharsError -> ShowS)
-> (TraceStateValueContainsInvalidCharsError -> String)
-> ([TraceStateValueContainsInvalidCharsError] -> ShowS)
-> Show TraceStateValueContainsInvalidCharsError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TraceStateValueContainsInvalidCharsError -> ShowS
showsPrec :: Int -> TraceStateValueContainsInvalidCharsError -> ShowS
$cshow :: TraceStateValueContainsInvalidCharsError -> String
show :: TraceStateValueContainsInvalidCharsError -> String
$cshowList :: [TraceStateValueContainsInvalidCharsError] -> ShowS
showList :: [TraceStateValueContainsInvalidCharsError] -> ShowS
Show)

data TraceStateValueTooLongError = TraceStateValueTooLongError
  { TraceStateValueTooLongError -> Key Text
rawKey :: Key Text
  , TraceStateValueTooLongError -> Text
rawValue :: Text
  } deriving stock (TraceStateValueTooLongError -> TraceStateValueTooLongError -> Bool
(TraceStateValueTooLongError
 -> TraceStateValueTooLongError -> Bool)
-> (TraceStateValueTooLongError
    -> TraceStateValueTooLongError -> Bool)
-> Eq TraceStateValueTooLongError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TraceStateValueTooLongError -> TraceStateValueTooLongError -> Bool
== :: TraceStateValueTooLongError -> TraceStateValueTooLongError -> Bool
$c/= :: TraceStateValueTooLongError -> TraceStateValueTooLongError -> Bool
/= :: TraceStateValueTooLongError -> TraceStateValueTooLongError -> Bool
Eq, Int -> TraceStateValueTooLongError -> ShowS
[TraceStateValueTooLongError] -> ShowS
TraceStateValueTooLongError -> String
(Int -> TraceStateValueTooLongError -> ShowS)
-> (TraceStateValueTooLongError -> String)
-> ([TraceStateValueTooLongError] -> ShowS)
-> Show TraceStateValueTooLongError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TraceStateValueTooLongError -> ShowS
showsPrec :: Int -> TraceStateValueTooLongError -> ShowS
$cshow :: TraceStateValueTooLongError -> String
show :: TraceStateValueTooLongError -> String
$cshowList :: [TraceStateValueTooLongError] -> ShowS
showList :: [TraceStateValueTooLongError] -> ShowS
Show)