{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# OPTIONS_GHC -fno-warn-unticked-promoted-constructors #-}
module Simplex.Messaging.Agent.Store where
import Control.Exception (Exception)
import Data.ByteString.Char8 (ByteString)
import Data.Int (Int64)
import Data.Kind (Type)
import Data.Time (UTCTime)
import Data.Type.Equality
import Simplex.Messaging.Agent.Protocol
import Simplex.Messaging.Protocol
( MsgBody,
MsgId,
RecipientPrivateKey,
SenderPrivateKey,
SenderPublicKey,
)
import qualified Simplex.Messaging.Protocol as SMP
class Monad m => MonadAgentStore s m where
createRcvConn :: s -> RcvQueue -> m ()
createSndConn :: s -> SndQueue -> m ()
getConn :: s -> ConnAlias -> m SomeConn
getAllConnAliases :: s -> m [ConnAlias]
getRcvConn :: s -> SMPServer -> SMP.RecipientId -> m SomeConn
deleteConn :: s -> ConnAlias -> m ()
upgradeRcvConnToDuplex :: s -> ConnAlias -> SndQueue -> m ()
upgradeSndConnToDuplex :: s -> ConnAlias -> RcvQueue -> m ()
setRcvQueueStatus :: s -> RcvQueue -> QueueStatus -> m ()
setRcvQueueActive :: s -> RcvQueue -> VerificationKey -> m ()
setSndQueueStatus :: s -> SndQueue -> QueueStatus -> m ()
updateRcvIds :: s -> RcvQueue -> m (InternalId, InternalRcvId, PrevExternalSndId, PrevRcvMsgHash)
createRcvMsg :: s -> RcvQueue -> RcvMsgData -> m ()
updateSndIds :: s -> SndQueue -> m (InternalId, InternalSndId, PrevSndMsgHash)
createSndMsg :: s -> SndQueue -> SndMsgData -> m ()
getMsg :: s -> ConnAlias -> InternalId -> m Msg
data RcvQueue = RcvQueue
{ RcvQueue -> SMPServer
server :: SMPServer,
RcvQueue -> RecipientId
rcvId :: SMP.RecipientId,
RcvQueue -> RecipientId
connAlias :: ConnAlias,
RcvQueue -> RecipientPrivateKey
rcvPrivateKey :: RecipientPrivateKey,
RcvQueue -> Maybe RecipientId
sndId :: Maybe SMP.SenderId,
RcvQueue -> Maybe SenderPublicKey
sndKey :: Maybe SenderPublicKey,
RcvQueue -> RecipientPrivateKey
decryptKey :: DecryptionKey,
RcvQueue -> Maybe SenderPublicKey
verifyKey :: Maybe VerificationKey,
RcvQueue -> QueueStatus
status :: QueueStatus
}
deriving (RcvQueue -> RcvQueue -> Bool
(RcvQueue -> RcvQueue -> Bool)
-> (RcvQueue -> RcvQueue -> Bool) -> Eq RcvQueue
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RcvQueue -> RcvQueue -> Bool
$c/= :: RcvQueue -> RcvQueue -> Bool
== :: RcvQueue -> RcvQueue -> Bool
$c== :: RcvQueue -> RcvQueue -> Bool
Eq, Int -> RcvQueue -> ShowS
[RcvQueue] -> ShowS
RcvQueue -> String
(Int -> RcvQueue -> ShowS)
-> (RcvQueue -> String) -> ([RcvQueue] -> ShowS) -> Show RcvQueue
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RcvQueue] -> ShowS
$cshowList :: [RcvQueue] -> ShowS
show :: RcvQueue -> String
$cshow :: RcvQueue -> String
showsPrec :: Int -> RcvQueue -> ShowS
$cshowsPrec :: Int -> RcvQueue -> ShowS
Show)
data SndQueue = SndQueue
{ SndQueue -> SMPServer
server :: SMPServer,
SndQueue -> RecipientId
sndId :: SMP.SenderId,
SndQueue -> RecipientId
connAlias :: ConnAlias,
SndQueue -> RecipientPrivateKey
sndPrivateKey :: SenderPrivateKey,
SndQueue -> SenderPublicKey
encryptKey :: EncryptionKey,
SndQueue -> RecipientPrivateKey
signKey :: SignatureKey,
SndQueue -> QueueStatus
status :: QueueStatus
}
deriving (SndQueue -> SndQueue -> Bool
(SndQueue -> SndQueue -> Bool)
-> (SndQueue -> SndQueue -> Bool) -> Eq SndQueue
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SndQueue -> SndQueue -> Bool
$c/= :: SndQueue -> SndQueue -> Bool
== :: SndQueue -> SndQueue -> Bool
$c== :: SndQueue -> SndQueue -> Bool
Eq, Int -> SndQueue -> ShowS
[SndQueue] -> ShowS
SndQueue -> String
(Int -> SndQueue -> ShowS)
-> (SndQueue -> String) -> ([SndQueue] -> ShowS) -> Show SndQueue
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SndQueue] -> ShowS
$cshowList :: [SndQueue] -> ShowS
show :: SndQueue -> String
$cshow :: SndQueue -> String
showsPrec :: Int -> SndQueue -> ShowS
$cshowsPrec :: Int -> SndQueue -> ShowS
Show)
data ConnType = CRcv | CSnd | CDuplex deriving (ConnType -> ConnType -> Bool
(ConnType -> ConnType -> Bool)
-> (ConnType -> ConnType -> Bool) -> Eq ConnType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ConnType -> ConnType -> Bool
$c/= :: ConnType -> ConnType -> Bool
== :: ConnType -> ConnType -> Bool
$c== :: ConnType -> ConnType -> Bool
Eq, Int -> ConnType -> ShowS
[ConnType] -> ShowS
ConnType -> String
(Int -> ConnType -> ShowS)
-> (ConnType -> String) -> ([ConnType] -> ShowS) -> Show ConnType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ConnType] -> ShowS
$cshowList :: [ConnType] -> ShowS
show :: ConnType -> String
$cshow :: ConnType -> String
showsPrec :: Int -> ConnType -> ShowS
$cshowsPrec :: Int -> ConnType -> ShowS
Show)
data Connection (d :: ConnType) where
RcvConnection :: ConnAlias -> RcvQueue -> Connection CRcv
SndConnection :: ConnAlias -> SndQueue -> Connection CSnd
DuplexConnection :: ConnAlias -> RcvQueue -> SndQueue -> Connection CDuplex
deriving instance Eq (Connection d)
deriving instance Show (Connection d)
data SConnType :: ConnType -> Type where
SCRcv :: SConnType CRcv
SCSnd :: SConnType CSnd
SCDuplex :: SConnType CDuplex
connType :: SConnType c -> ConnType
connType :: SConnType c -> ConnType
connType SCRcv = ConnType
CRcv
connType SCSnd = ConnType
CSnd
connType SCDuplex = ConnType
CDuplex
deriving instance Eq (SConnType d)
deriving instance Show (SConnType d)
instance TestEquality SConnType where
testEquality :: SConnType a -> SConnType b -> Maybe (a :~: b)
testEquality SCRcv SCRcv = (a :~: a) -> Maybe (a :~: a)
forall a. a -> Maybe a
Just a :~: a
forall k (a :: k). a :~: a
Refl
testEquality SCSnd SCSnd = (a :~: a) -> Maybe (a :~: a)
forall a. a -> Maybe a
Just a :~: a
forall k (a :: k). a :~: a
Refl
testEquality SCDuplex SCDuplex = (a :~: a) -> Maybe (a :~: a)
forall a. a -> Maybe a
Just a :~: a
forall k (a :: k). a :~: a
Refl
testEquality _ _ = Maybe (a :~: b)
forall a. Maybe a
Nothing
data SomeConn = forall d. SomeConn (SConnType d) (Connection d)
instance Eq SomeConn where
SomeConn d :: SConnType d
d c :: Connection d
c == :: SomeConn -> SomeConn -> Bool
== SomeConn d' :: SConnType d
d' c' :: Connection d
c' = case SConnType d -> SConnType d -> Maybe (d :~: d)
forall k (f :: k -> *) (a :: k) (b :: k).
TestEquality f =>
f a -> f b -> Maybe (a :~: b)
testEquality SConnType d
d SConnType d
d' of
Just Refl -> Connection d
c Connection d -> Connection d -> Bool
forall a. Eq a => a -> a -> Bool
== Connection d
Connection d
c'
_ -> Bool
False
deriving instance Show SomeConn
type MsgHash = ByteString
type PrevExternalSndId = Int64
type PrevRcvMsgHash = MsgHash
type PrevSndMsgHash = MsgHash
data RcvMsgData = RcvMsgData
{ RcvMsgData -> InternalId
internalId :: InternalId,
RcvMsgData -> InternalRcvId
internalRcvId :: InternalRcvId,
RcvMsgData -> InternalTs
internalTs :: InternalTs,
RcvMsgData -> (ExternalSndId, InternalTs)
senderMeta :: (ExternalSndId, ExternalSndTs),
RcvMsgData -> (RecipientId, InternalTs)
brokerMeta :: (BrokerId, BrokerTs),
RcvMsgData -> RecipientId
msgBody :: MsgBody,
RcvMsgData -> RecipientId
internalHash :: MsgHash,
RcvMsgData -> RecipientId
externalPrevSndHash :: MsgHash,
RcvMsgData -> MsgIntegrity
msgIntegrity :: MsgIntegrity
}
data SndMsgData = SndMsgData
{ SndMsgData -> InternalId
internalId :: InternalId,
SndMsgData -> InternalSndId
internalSndId :: InternalSndId,
SndMsgData -> InternalTs
internalTs :: InternalTs,
SndMsgData -> RecipientId
msgBody :: MsgBody,
SndMsgData -> RecipientId
internalHash :: MsgHash
}
data Msg = MRcv RcvMsg | MSnd SndMsg
deriving (Msg -> Msg -> Bool
(Msg -> Msg -> Bool) -> (Msg -> Msg -> Bool) -> Eq Msg
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Msg -> Msg -> Bool
$c/= :: Msg -> Msg -> Bool
== :: Msg -> Msg -> Bool
$c== :: Msg -> Msg -> Bool
Eq, Int -> Msg -> ShowS
[Msg] -> ShowS
Msg -> String
(Int -> Msg -> ShowS)
-> (Msg -> String) -> ([Msg] -> ShowS) -> Show Msg
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Msg] -> ShowS
$cshowList :: [Msg] -> ShowS
show :: Msg -> String
$cshow :: Msg -> String
showsPrec :: Int -> Msg -> ShowS
$cshowsPrec :: Int -> Msg -> ShowS
Show)
data RcvMsg = RcvMsg
{ RcvMsg -> MsgBase
msgBase :: MsgBase,
RcvMsg -> InternalRcvId
internalRcvId :: InternalRcvId,
RcvMsg -> ExternalSndId
externalSndId :: ExternalSndId,
RcvMsg -> InternalTs
externalSndTs :: ExternalSndTs,
RcvMsg -> RecipientId
brokerId :: BrokerId,
RcvMsg -> InternalTs
brokerTs :: BrokerTs,
RcvMsg -> RcvMsgStatus
rcvMsgStatus :: RcvMsgStatus,
RcvMsg -> InternalTs
ackBrokerTs :: AckBrokerTs,
RcvMsg -> InternalTs
ackSenderTs :: AckSenderTs,
RcvMsg -> RecipientId
externalPrevSndHash :: MsgHash,
RcvMsg -> MsgIntegrity
msgIntegrity :: MsgIntegrity
}
deriving (RcvMsg -> RcvMsg -> Bool
(RcvMsg -> RcvMsg -> Bool)
-> (RcvMsg -> RcvMsg -> Bool) -> Eq RcvMsg
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RcvMsg -> RcvMsg -> Bool
$c/= :: RcvMsg -> RcvMsg -> Bool
== :: RcvMsg -> RcvMsg -> Bool
$c== :: RcvMsg -> RcvMsg -> Bool
Eq, Int -> RcvMsg -> ShowS
[RcvMsg] -> ShowS
RcvMsg -> String
(Int -> RcvMsg -> ShowS)
-> (RcvMsg -> String) -> ([RcvMsg] -> ShowS) -> Show RcvMsg
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RcvMsg] -> ShowS
$cshowList :: [RcvMsg] -> ShowS
show :: RcvMsg -> String
$cshow :: RcvMsg -> String
showsPrec :: Int -> RcvMsg -> ShowS
$cshowsPrec :: Int -> RcvMsg -> ShowS
Show)
newtype InternalRcvId = InternalRcvId {InternalRcvId -> ExternalSndId
unRcvId :: Int64} deriving (InternalRcvId -> InternalRcvId -> Bool
(InternalRcvId -> InternalRcvId -> Bool)
-> (InternalRcvId -> InternalRcvId -> Bool) -> Eq InternalRcvId
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InternalRcvId -> InternalRcvId -> Bool
$c/= :: InternalRcvId -> InternalRcvId -> Bool
== :: InternalRcvId -> InternalRcvId -> Bool
$c== :: InternalRcvId -> InternalRcvId -> Bool
Eq, Int -> InternalRcvId -> ShowS
[InternalRcvId] -> ShowS
InternalRcvId -> String
(Int -> InternalRcvId -> ShowS)
-> (InternalRcvId -> String)
-> ([InternalRcvId] -> ShowS)
-> Show InternalRcvId
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InternalRcvId] -> ShowS
$cshowList :: [InternalRcvId] -> ShowS
show :: InternalRcvId -> String
$cshow :: InternalRcvId -> String
showsPrec :: Int -> InternalRcvId -> ShowS
$cshowsPrec :: Int -> InternalRcvId -> ShowS
Show)
type ExternalSndId = Int64
type ExternalSndTs = UTCTime
type BrokerId = MsgId
type BrokerTs = UTCTime
data RcvMsgStatus
= Received
| AcknowledgedToBroker
| AcknowledgedToSender
deriving (RcvMsgStatus -> RcvMsgStatus -> Bool
(RcvMsgStatus -> RcvMsgStatus -> Bool)
-> (RcvMsgStatus -> RcvMsgStatus -> Bool) -> Eq RcvMsgStatus
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RcvMsgStatus -> RcvMsgStatus -> Bool
$c/= :: RcvMsgStatus -> RcvMsgStatus -> Bool
== :: RcvMsgStatus -> RcvMsgStatus -> Bool
$c== :: RcvMsgStatus -> RcvMsgStatus -> Bool
Eq, Int -> RcvMsgStatus -> ShowS
[RcvMsgStatus] -> ShowS
RcvMsgStatus -> String
(Int -> RcvMsgStatus -> ShowS)
-> (RcvMsgStatus -> String)
-> ([RcvMsgStatus] -> ShowS)
-> Show RcvMsgStatus
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RcvMsgStatus] -> ShowS
$cshowList :: [RcvMsgStatus] -> ShowS
show :: RcvMsgStatus -> String
$cshow :: RcvMsgStatus -> String
showsPrec :: Int -> RcvMsgStatus -> ShowS
$cshowsPrec :: Int -> RcvMsgStatus -> ShowS
Show)
type AckBrokerTs = UTCTime
type AckSenderTs = UTCTime
data SndMsg = SndMsg
{ SndMsg -> MsgBase
msgBase :: MsgBase,
SndMsg -> InternalSndId
internalSndId :: InternalSndId,
SndMsg -> SndMsgStatus
sndMsgStatus :: SndMsgStatus,
SndMsg -> InternalTs
sentTs :: SentTs,
SndMsg -> InternalTs
deliveredTs :: DeliveredTs
}
deriving (SndMsg -> SndMsg -> Bool
(SndMsg -> SndMsg -> Bool)
-> (SndMsg -> SndMsg -> Bool) -> Eq SndMsg
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SndMsg -> SndMsg -> Bool
$c/= :: SndMsg -> SndMsg -> Bool
== :: SndMsg -> SndMsg -> Bool
$c== :: SndMsg -> SndMsg -> Bool
Eq, Int -> SndMsg -> ShowS
[SndMsg] -> ShowS
SndMsg -> String
(Int -> SndMsg -> ShowS)
-> (SndMsg -> String) -> ([SndMsg] -> ShowS) -> Show SndMsg
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SndMsg] -> ShowS
$cshowList :: [SndMsg] -> ShowS
show :: SndMsg -> String
$cshow :: SndMsg -> String
showsPrec :: Int -> SndMsg -> ShowS
$cshowsPrec :: Int -> SndMsg -> ShowS
Show)
newtype InternalSndId = InternalSndId {InternalSndId -> ExternalSndId
unSndId :: Int64} deriving (InternalSndId -> InternalSndId -> Bool
(InternalSndId -> InternalSndId -> Bool)
-> (InternalSndId -> InternalSndId -> Bool) -> Eq InternalSndId
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InternalSndId -> InternalSndId -> Bool
$c/= :: InternalSndId -> InternalSndId -> Bool
== :: InternalSndId -> InternalSndId -> Bool
$c== :: InternalSndId -> InternalSndId -> Bool
Eq, Int -> InternalSndId -> ShowS
[InternalSndId] -> ShowS
InternalSndId -> String
(Int -> InternalSndId -> ShowS)
-> (InternalSndId -> String)
-> ([InternalSndId] -> ShowS)
-> Show InternalSndId
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InternalSndId] -> ShowS
$cshowList :: [InternalSndId] -> ShowS
show :: InternalSndId -> String
$cshow :: InternalSndId -> String
showsPrec :: Int -> InternalSndId -> ShowS
$cshowsPrec :: Int -> InternalSndId -> ShowS
Show)
data SndMsgStatus
= Created
| Sent
| Delivered
deriving (SndMsgStatus -> SndMsgStatus -> Bool
(SndMsgStatus -> SndMsgStatus -> Bool)
-> (SndMsgStatus -> SndMsgStatus -> Bool) -> Eq SndMsgStatus
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SndMsgStatus -> SndMsgStatus -> Bool
$c/= :: SndMsgStatus -> SndMsgStatus -> Bool
== :: SndMsgStatus -> SndMsgStatus -> Bool
$c== :: SndMsgStatus -> SndMsgStatus -> Bool
Eq, Int -> SndMsgStatus -> ShowS
[SndMsgStatus] -> ShowS
SndMsgStatus -> String
(Int -> SndMsgStatus -> ShowS)
-> (SndMsgStatus -> String)
-> ([SndMsgStatus] -> ShowS)
-> Show SndMsgStatus
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SndMsgStatus] -> ShowS
$cshowList :: [SndMsgStatus] -> ShowS
show :: SndMsgStatus -> String
$cshow :: SndMsgStatus -> String
showsPrec :: Int -> SndMsgStatus -> ShowS
$cshowsPrec :: Int -> SndMsgStatus -> ShowS
Show)
type SentTs = UTCTime
type DeliveredTs = UTCTime
data MsgBase = MsgBase
{ MsgBase -> RecipientId
connAlias :: ConnAlias,
MsgBase -> InternalId
internalId :: InternalId,
MsgBase -> InternalTs
internalTs :: InternalTs,
MsgBase -> RecipientId
msgBody :: MsgBody,
MsgBase -> RecipientId
internalHash :: MsgHash
}
deriving (MsgBase -> MsgBase -> Bool
(MsgBase -> MsgBase -> Bool)
-> (MsgBase -> MsgBase -> Bool) -> Eq MsgBase
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MsgBase -> MsgBase -> Bool
$c/= :: MsgBase -> MsgBase -> Bool
== :: MsgBase -> MsgBase -> Bool
$c== :: MsgBase -> MsgBase -> Bool
Eq, Int -> MsgBase -> ShowS
[MsgBase] -> ShowS
MsgBase -> String
(Int -> MsgBase -> ShowS)
-> (MsgBase -> String) -> ([MsgBase] -> ShowS) -> Show MsgBase
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MsgBase] -> ShowS
$cshowList :: [MsgBase] -> ShowS
show :: MsgBase -> String
$cshow :: MsgBase -> String
showsPrec :: Int -> MsgBase -> ShowS
$cshowsPrec :: Int -> MsgBase -> ShowS
Show)
newtype InternalId = InternalId {InternalId -> ExternalSndId
unId :: Int64} deriving (InternalId -> InternalId -> Bool
(InternalId -> InternalId -> Bool)
-> (InternalId -> InternalId -> Bool) -> Eq InternalId
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InternalId -> InternalId -> Bool
$c/= :: InternalId -> InternalId -> Bool
== :: InternalId -> InternalId -> Bool
$c== :: InternalId -> InternalId -> Bool
Eq, Int -> InternalId -> ShowS
[InternalId] -> ShowS
InternalId -> String
(Int -> InternalId -> ShowS)
-> (InternalId -> String)
-> ([InternalId] -> ShowS)
-> Show InternalId
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InternalId] -> ShowS
$cshowList :: [InternalId] -> ShowS
show :: InternalId -> String
$cshow :: InternalId -> String
showsPrec :: Int -> InternalId -> ShowS
$cshowsPrec :: Int -> InternalId -> ShowS
Show)
type InternalTs = UTCTime
data StoreError
=
SEInternal ByteString
|
SEConnNotFound
|
SEConnDuplicate
|
SEBadConnType ConnType
|
SEBadQueueStatus
|
SENotImplemented
deriving (StoreError -> StoreError -> Bool
(StoreError -> StoreError -> Bool)
-> (StoreError -> StoreError -> Bool) -> Eq StoreError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StoreError -> StoreError -> Bool
$c/= :: StoreError -> StoreError -> Bool
== :: StoreError -> StoreError -> Bool
$c== :: StoreError -> StoreError -> Bool
Eq, Int -> StoreError -> ShowS
[StoreError] -> ShowS
StoreError -> String
(Int -> StoreError -> ShowS)
-> (StoreError -> String)
-> ([StoreError] -> ShowS)
-> Show StoreError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StoreError] -> ShowS
$cshowList :: [StoreError] -> ShowS
show :: StoreError -> String
$cshow :: StoreError -> String
showsPrec :: Int -> StoreError -> ShowS
$cshowsPrec :: Int -> StoreError -> ShowS
Show, Show StoreError
Typeable StoreError
(Typeable StoreError, Show StoreError) =>
(StoreError -> SomeException)
-> (SomeException -> Maybe StoreError)
-> (StoreError -> String)
-> Exception StoreError
SomeException -> Maybe StoreError
StoreError -> String
StoreError -> SomeException
forall e.
(Typeable e, Show e) =>
(e -> SomeException)
-> (SomeException -> Maybe e) -> (e -> String) -> Exception e
displayException :: StoreError -> String
$cdisplayException :: StoreError -> String
fromException :: SomeException -> Maybe StoreError
$cfromException :: SomeException -> Maybe StoreError
toException :: StoreError -> SomeException
$ctoException :: StoreError -> SomeException
$cp2Exception :: Show StoreError
$cp1Exception :: Typeable StoreError
Exception)