hs-abci-sdk-0.1.0.0

Safe HaskellNone
LanguageHaskell2010

Tendermint.SDK.BaseApp

Contents

Synopsis

BaseApp

type BaseAppEffs = [RawStore, Metrics, Logger, Resource, Error AppError] Source #

Concrete row of effects for the BaseApp. Note that because there does | not exist an interpreter for an untagged RawStore, you must scope | these effects before they can be interpreted.

type family (as :: [a]) :& (bs :: [a]) :: [a] where ... infixr 5 Source #

This type family gives a nice syntax for combining multiple lists of effects.

Equations

'[] :& bs = bs 
(a ': as) :& bs = a ': (as :& bs) 

compileToCoreEffs :: AuthTreeGetter s => forall a. Sem (ScopedBaseApp s CoreEffs) a -> Sem CoreEffs a Source #

An intermediary interpeter, bringing BaseApp down to CoreEff.

CoreEff

type CoreEffs = '[MergeScopes, Reader LogConfig, Reader (Maybe PrometheusEnv), Reader AuthTreeState, Embed IO] Source #

CoreEffs is one level below BaseAppEffs, and provides one possible | interpretation for its effects to IO.

runCoreEffs :: Context -> forall a. Sem CoreEffs a -> IO a Source #

The standard interpeter for CoreEffs.

Store

data RawStore m a Source #

Instances
type DefiningModule (RawStore :: k -> Type -> Type) Source # 
Instance details

Defined in Tendermint.SDK.BaseApp.Store.RawStore

type DefiningModule (RawStore :: k -> Type -> Type) = "Tendermint.SDK.BaseApp.Store.RawStore"

class RawKey k where Source #

Methods

rawKey :: Iso' k ByteString Source #

Instances
RawKey Address Source # 
Instance details

Defined in Tendermint.SDK.BaseApp.Store.RawStore

class RawKey k => IsKey k ns where Source #

Minimal complete definition

Nothing

Associated Types

type Value k ns = a | a -> ns k Source #

Instances
IsKey Address AuthModule Source # 
Instance details

Defined in Tendermint.SDK.Modules.Auth.Types

Associated Types

type Value Address AuthModule = (a :: Type) Source #

newtype StoreKey n Source #

Constructors

StoreKey ByteString 

put :: forall k r ns. IsKey k ns => HasCodec (Value k ns) => Member RawStore r => StoreKey ns -> k -> Value k ns -> Sem r () Source #

get :: forall k r ns. IsKey k ns => HasCodec (Value k ns) => Members [RawStore, Error AppError] r => StoreKey ns -> k -> Sem r (Maybe (Value k ns)) Source #

delete :: forall k ns r. IsKey k ns => Member RawStore r => StoreKey ns -> k -> Sem r () Source #

Query Routes

data Leaf (a :: *) Source #

Instances
HasCodec a => HasQueryRouter (Leaf a :: Type) r Source # 
Instance details

Defined in Tendermint.SDK.BaseApp.Query.Router

Associated Types

type RouteQ (Leaf a) r :: Type Source #

Methods

routeQ :: Proxy (Leaf a) -> Proxy r -> Delayed (Sem r) env QueryRequest (RouteQ (Leaf a) r) -> Router env r QueryRequest Query Source #

type RouteQ (Leaf a :: Type) r Source # 
Instance details

Defined in Tendermint.SDK.BaseApp.Query.Router

type RouteQ (Leaf a :: Type) r = Sem r (QueryResult a)

data QA (a :: *) Source #

Instances
(FromQueryData a, HasQueryRouter sublayout r) => HasQueryRouter (QA a :> sublayout :: Type) r Source # 
Instance details

Defined in Tendermint.SDK.BaseApp.Query.Router

Associated Types

type RouteQ (QA a :> sublayout) r :: Type Source #

Methods

routeQ :: Proxy (QA a :> sublayout) -> Proxy r -> Delayed (Sem r) env QueryRequest (RouteQ (QA a :> sublayout) r) -> Router env r QueryRequest Query Source #

type RouteQ (QA a :> sublayout :: Type) r Source # 
Instance details

Defined in Tendermint.SDK.BaseApp.Query.Router

type RouteQ (QA a :> sublayout :: Type) r = QueryArgs a -> RouteQ sublayout r

Scope

data ConnectionScope Source #

Constructors

Query 
Mempool 
Consensus 
Instances
(Members CoreEffs r, AuthTreeGetter s) => ResolveScope (s :: ConnectionScope) r Source # 
Instance details

Defined in Tendermint.SDK.BaseApp.CoreEff

Methods

resolveScope :: Sem (Tagged s RawStore ': r) a -> Sem r a Source #

applyScope :: forall s r. forall a. Sem (RawStore ': r) a -> Sem (Tagged s RawStore ': r) a Source #

Errors

data AppError Source #

This type represents a common error response for the query, checkTx, | and deliver tx abci-messages.

Constructors

AppError 

class IsAppError e where Source #

Allows for custom application error types to be coerced into the standard error resposne.

Methods

makeAppError :: e -> AppError Source #

data SDKError Source #

These errors originate from the SDK itself. The "sdk" namespace is reserved | for this error type and should not be used in modules or applications.

Constructors

InternalError

Something went wrong and we have no idea what.

ParseError Text

Parsing errors for SDK specific types, e.g. RawTransaction or Msg, etc.

UnmatchedRoute Text

The name of the route that failed to match.

OutOfGasException 
MessageValidation [Text] 
SignatureRecoveryError Text 
NonceException Word64 Word64 
Instances
IsAppError SDKError Source # 
Instance details

Defined in Tendermint.SDK.BaseApp.Errors

throwSDKError :: Member (Error AppError) r => SDKError -> Sem r a Source #

As of right now it's not expected that one can recover from an SDKError, | so we are throwing them as AppErrors directly.

Events

data Event #

Constructors

Event 

Fields

Instances
Eq Event 
Instance details

Defined in Network.ABCI.Types.Messages.FieldTypes

Methods

(==) :: Event -> Event -> Bool #

(/=) :: Event -> Event -> Bool #

Show Event 
Instance details

Defined in Network.ABCI.Types.Messages.FieldTypes

Methods

showsPrec :: Int -> Event -> ShowS #

show :: Event -> String #

showList :: [Event] -> ShowS #

Generic Event 
Instance details

Defined in Network.ABCI.Types.Messages.FieldTypes

Associated Types

type Rep Event :: Type -> Type #

Methods

from :: Event -> Rep Event x #

to :: Rep Event x -> Event #

FromJSON Event 
Instance details

Defined in Network.ABCI.Types.Messages.FieldTypes

Methods

parseJSON :: Value -> Parser Event

parseJSONList :: Value -> Parser [Event]

ToJSON Event 
Instance details

Defined in Network.ABCI.Types.Messages.FieldTypes

Methods

toJSON :: Event -> Value

toEncoding :: Event -> Encoding

toJSONList :: [Event] -> Value

toEncodingList :: [Event] -> Encoding

Wrapped Event 
Instance details

Defined in Network.ABCI.Types.Messages.FieldTypes

Associated Types

type Unwrapped Event :: Type

Methods

_Wrapped' :: Iso' Event (Unwrapped Event)

type Rep Event 
Instance details

Defined in Network.ABCI.Types.Messages.FieldTypes

type Rep Event = D1 (MetaData "Event" "Network.ABCI.Types.Messages.FieldTypes" "hs-abci-types-0.1.0.0-CSbCBfElGIr9n2xrkSCrY5" False) (C1 (MetaCons "Event" PrefixI True) (S1 (MetaSel (Just "eventType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text) :*: S1 (MetaSel (Just "eventAttributes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [KVPair])))
type Unwrapped Event 
Instance details

Defined in Network.ABCI.Types.Messages.FieldTypes

type Unwrapped Event = Event

class ToEvent e where Source #

A class representing a type that can be emitted as an event in the | event logs for the deliverTx response.

Minimal complete definition

makeEventType

newtype ContextEvent t Source #

Special event wrapper to add contextual event_type info

Constructors

ContextEvent t 
Instances
(ToJSON a, ToEvent a) => ToJSON (ContextEvent a) Source # 
Instance details

Defined in Tendermint.SDK.BaseApp.Events

Methods

toJSON :: ContextEvent a -> Value

toEncoding :: ContextEvent a -> Encoding

toJSONList :: [ContextEvent a] -> Value

toEncodingList :: [ContextEvent a] -> Encoding

Select a => Select (ContextEvent a) Source # 
Instance details

Defined in Tendermint.SDK.BaseApp.Events

emit :: ToEvent e => Member (Output Event) r => e -> Sem r () Source #

logEvent :: forall e r. (ToJSON e, ToEvent e, Select e) => Member Logger r => e -> Sem r () Source #

Gas

data GasMeter m a Source #

Instances
type DefiningModule (GasMeter :: (k -> Type) -> k -> Type) Source # 
Instance details

Defined in Tendermint.SDK.BaseApp.Gas

type DefiningModule (GasMeter :: (k -> Type) -> k -> Type) = "Tendermint.SDK.BaseApp.Gas"

Logger

data Logger m a Source #

Effect allowing for console logging.

Instances
type DefiningModule Logger Source # 
Instance details

Defined in Tendermint.SDK.BaseApp.Logger

type DefiningModule Logger = "Tendermint.SDK.BaseApp.Logger"

log :: forall r. MemberWithError Logger r => Severity -> Text -> Sem r () Source #

addContext :: forall r x a. (MemberWithError Logger r, Select x, ToJSON x) => x -> Sem r a -> Sem r a Source #

data LogSelect Source #

Constructors

All 
Some [Text] 

class Select a where Source #

Class for selecting object keys for contextual logging

Minimal complete definition

Nothing

Instances
Select a => Select (ContextEvent a) Source # 
Instance details

Defined in Tendermint.SDK.BaseApp.Events

data Verbosity Source #

Constructors

V0 
V1 
V2 
V3 

Metrics

data Metrics m a Source #

Instances
type DefiningModule Metrics Source # 
Instance details

Defined in Tendermint.SDK.BaseApp.Metrics

type DefiningModule Metrics = "Tendermint.SDK.BaseApp.Metrics"

incCount :: forall r. MemberWithError Metrics r => CountName -> Sem r () Source #

withTimer :: forall r a. MemberWithError Metrics r => HistogramName -> Sem r a -> Sem r a Source #

Transaction

data RoutingTx msg where Source #

Constructors

RoutingTx :: Tx alg msg -> RoutingTx msg 
Instances
Functor RoutingTx Source # 
Instance details

Defined in Tendermint.SDK.BaseApp.Transaction.Types

Methods

fmap :: (a -> b) -> RoutingTx a -> RoutingTx b #

(<$) :: a -> RoutingTx b -> RoutingTx a #

HasPath (RoutingTx msg) Source # 
Instance details

Defined in Tendermint.SDK.BaseApp.Transaction.Types

Methods

path :: Lens' (RoutingTx msg) Text Source #

type family RouteTx layout r c :: * Source #

Instances
type RouteTx EmptyTxServer r c Source # 
Instance details

Defined in Tendermint.SDK.BaseApp.Transaction.Router

type RouteTx (a :<|> b :: Type) r c Source # 
Instance details

Defined in Tendermint.SDK.BaseApp.Transaction.Router

type RouteTx (a :<|> b :: Type) r c = RouteTx a r c :<|> RouteTx b r c
type RouteTx (path :> sublayout :: Type) r c Source # 
Instance details

Defined in Tendermint.SDK.BaseApp.Transaction.Router

type RouteTx (path :> sublayout :: Type) r c = RouteTx sublayout r c
type RouteTx (TypedMessage msg :~> Return' oc a :: Type) r c Source # 
Instance details

Defined in Tendermint.SDK.BaseApp.Transaction.Router

type RouteTx (TypedMessage msg :~> Return' oc a :: Type) r c = RoutingTx msg -> Sem (TxEffs :& r) (OnCheckReturn c oc a)

data msg :~> a Source #

Instances
(Member (Error AppError :: (Type -> Type) -> Type -> Type) r, ValidateMessage msg) => DefaultCheckTx (TypedMessage msg :~> Return a :: Type) r Source # 
Instance details

Defined in Tendermint.SDK.BaseApp.Transaction.Checker

Associated Types

type DefaultCheckTxT (TypedMessage msg :~> Return a) r :: Type Source #

(HasMessageType msg, HasCodec msg, HasCodec (OnCheckReturn c oc a), Member (Embed IO) r) => HasTxRouter (TypedMessage msg :~> Return' oc a :: Type) r c Source # 
Instance details

Defined in Tendermint.SDK.BaseApp.Transaction.Router

Associated Types

type RouteTx (TypedMessage msg :~> Return' oc a) r c :: Type Source #

Methods

routeTx :: Proxy (TypedMessage msg :~> Return' oc a) -> Proxy r -> Proxy c -> Delayed (Sem r) env (RoutingTx ByteString) (RouteTx (TypedMessage msg :~> Return' oc a) r c) -> Router env r (RoutingTx ByteString) TxResult Source #

type DefaultCheckTxT (TypedMessage msg :~> Return a :: Type) r Source # 
Instance details

Defined in Tendermint.SDK.BaseApp.Transaction.Checker

type DefaultCheckTxT (TypedMessage msg :~> Return a :: Type) r = RoutingTx msg -> Sem r ()
type RouteTx (TypedMessage msg :~> Return' oc a :: Type) r c Source # 
Instance details

Defined in Tendermint.SDK.BaseApp.Transaction.Router

type RouteTx (TypedMessage msg :~> Return' oc a :: Type) r c = RoutingTx msg -> Sem (TxEffs :& r) (OnCheckReturn c oc a)

data TypedMessage msg Source #

Instances
(Member (Error AppError :: (Type -> Type) -> Type -> Type) r, ValidateMessage msg) => DefaultCheckTx (TypedMessage msg :~> Return a :: Type) r Source # 
Instance details

Defined in Tendermint.SDK.BaseApp.Transaction.Checker

Associated Types

type DefaultCheckTxT (TypedMessage msg :~> Return a) r :: Type Source #

(HasMessageType msg, HasCodec msg, HasCodec (OnCheckReturn c oc a), Member (Embed IO) r) => HasTxRouter (TypedMessage msg :~> Return' oc a :: Type) r c Source # 
Instance details

Defined in Tendermint.SDK.BaseApp.Transaction.Router

Associated Types

type RouteTx (TypedMessage msg :~> Return' oc a) r c :: Type Source #

Methods

routeTx :: Proxy (TypedMessage msg :~> Return' oc a) -> Proxy r -> Proxy c -> Delayed (Sem r) env (RoutingTx ByteString) (RouteTx (TypedMessage msg :~> Return' oc a) r c) -> Router env r (RoutingTx ByteString) TxResult Source #

type DefaultCheckTxT (TypedMessage msg :~> Return a :: Type) r Source # 
Instance details

Defined in Tendermint.SDK.BaseApp.Transaction.Checker

type DefaultCheckTxT (TypedMessage msg :~> Return a :: Type) r = RoutingTx msg -> Sem r ()
type RouteTx (TypedMessage msg :~> Return' oc a :: Type) r c Source # 
Instance details

Defined in Tendermint.SDK.BaseApp.Transaction.Router

type RouteTx (TypedMessage msg :~> Return' oc a :: Type) r c = RoutingTx msg -> Sem (TxEffs :& r) (OnCheckReturn c oc a)

type TxEffs = [Output Event, GasMeter, Error AppError] Source #

serveTxApplication :: HasTxRouter layout r c => Proxy layout -> Proxy r -> Proxy (c :: RouteContext) -> RouteTx layout r c -> TransactionApplication (Sem r) Source #

class DefaultCheckTx api (r :: EffectRow) where Source #

Associated Types

type DefaultCheckTxT api r :: * Source #

Methods

defaultCheckTx :: Proxy api -> Proxy r -> DefaultCheckTxT api r Source #

Instances
DefaultCheckTx EmptyTxServer r Source # 
Instance details

Defined in Tendermint.SDK.BaseApp.Transaction.Checker

Associated Types

type DefaultCheckTxT EmptyTxServer r :: Type Source #

(DefaultCheckTx a r, DefaultCheckTx b r) => DefaultCheckTx (a :<|> b :: Type) r Source # 
Instance details

Defined in Tendermint.SDK.BaseApp.Transaction.Checker

Associated Types

type DefaultCheckTxT (a :<|> b) r :: Type Source #

Methods

defaultCheckTx :: Proxy (a :<|> b) -> Proxy r -> DefaultCheckTxT (a :<|> b) r Source #

DefaultCheckTx rest r => DefaultCheckTx (path :> rest :: Type) r Source # 
Instance details

Defined in Tendermint.SDK.BaseApp.Transaction.Checker

Associated Types

type DefaultCheckTxT (path :> rest) r :: Type Source #

Methods

defaultCheckTx :: Proxy (path :> rest) -> Proxy r -> DefaultCheckTxT (path :> rest) r Source #

(Member (Error AppError :: (Type -> Type) -> Type -> Type) r, ValidateMessage msg) => DefaultCheckTx (TypedMessage msg :~> Return a :: Type) r Source # 
Instance details

Defined in Tendermint.SDK.BaseApp.Transaction.Checker

Associated Types

type DefaultCheckTxT (TypedMessage msg :~> Return a) r :: Type Source #

Query

class HasCodec a => Queryable a Source #

class representing objects which can be queried via the hs-abci query message. | Here the Name is the leaf of the query url, e.g. if you can access a token | balance of type Balance at "token/balance", then 'Name Balance ~ "balance"'.

Associated Types

type Name a :: Symbol Source #

Instances
Queryable Account Source # 
Instance details

Defined in Tendermint.SDK.Modules.Auth.Types

Associated Types

type Name Account :: Symbol Source #

class FromQueryData a where Source #

This class is used to parse the 'data' field of the query request message. | The default method assumes that the 'data' is simply the key for the | value being queried.

Minimal complete definition

Nothing

type family QueryApi kvs :: * Source #

Instances
type QueryApi ((k, a) ': ((k', a') ': as)) Source # 
Instance details

Defined in Tendermint.SDK.BaseApp.Query.Store

type QueryApi ((k, a) ': ((k', a') ': as)) = (QA k :> Leaf a) :<|> QueryApi ((k', a') ': as)
type QueryApi ((k, a) ': ([] :: [Type])) Source # 
Instance details

Defined in Tendermint.SDK.BaseApp.Query.Store

type QueryApi ((k, a) ': ([] :: [Type])) = QA k :> StoreLeaf a

type family RouteQ layout r :: * Source #

A routeQ handler.

Instances
type RouteQ EmptyQueryServer r Source # 
Instance details

Defined in Tendermint.SDK.BaseApp.Query.Router

type RouteQ (Leaf a :: Type) r Source # 
Instance details

Defined in Tendermint.SDK.BaseApp.Query.Router

type RouteQ (Leaf a :: Type) r = Sem r (QueryResult a)
type RouteQ (a :<|> b :: Type) r Source # 
Instance details

Defined in Tendermint.SDK.BaseApp.Query.Router

type RouteQ (a :<|> b :: Type) r = RouteQ a r :<|> RouteQ b r
type RouteQ (StoreLeaf a :: Type) r Source # 
Instance details

Defined in Tendermint.SDK.BaseApp.Query.Store

type RouteQ (StoreLeaf a :: Type) r = Sem r (QueryResult a)
type RouteQ (Capture' mods capture a :> sublayout :: Type) r Source # 
Instance details

Defined in Tendermint.SDK.BaseApp.Query.Router

type RouteQ (Capture' mods capture a :> sublayout :: Type) r = a -> RouteQ sublayout r
type RouteQ (QueryParam' mods sym a :> sublayout :: Type) r Source # 
Instance details

Defined in Tendermint.SDK.BaseApp.Query.Router

type RouteQ (QueryParam' mods sym a :> sublayout :: Type) r = RequestArgument mods a -> RouteQ sublayout r
type RouteQ (QA a :> sublayout :: Type) r Source # 
Instance details

Defined in Tendermint.SDK.BaseApp.Query.Router

type RouteQ (QA a :> sublayout :: Type) r = QueryArgs a -> RouteQ sublayout r
type RouteQ (path :> sublayout :: Type) r Source # 
Instance details

Defined in Tendermint.SDK.BaseApp.Query.Router

type RouteQ (path :> sublayout :: Type) r = RouteQ sublayout r

data QueryResult a Source #

Instances
Functor QueryResult Source # 
Instance details

Defined in Tendermint.SDK.BaseApp.Query.Types

Methods

fmap :: (a -> b) -> QueryResult a -> QueryResult b #

(<$) :: a -> QueryResult b -> QueryResult a #

Eq a => Eq (QueryResult a) Source # 
Instance details

Defined in Tendermint.SDK.BaseApp.Query.Types

Show a => Show (QueryResult a) Source # 
Instance details

Defined in Tendermint.SDK.BaseApp.Query.Types

(IsKey k ns, a ~ Value k ns, HasCodec a, Members ((RawStore :: (Type -> Type) -> Type -> Type) ': ((Error AppError :: (Type -> Type) -> Type -> Type) ': ([] :: [(Type -> Type) -> Type -> Type]))) r) => StoreQueryHandler (a :: Type) ns (QueryArgs k -> Sem r (QueryResult a)) Source # 
Instance details

Defined in Tendermint.SDK.BaseApp.Query.Store

Methods

storeQueryHandler :: Proxy a -> StoreKey ns -> QueryArgs k -> Sem r (QueryResult a) Source #

serveQueryApplication :: HasQueryRouter layout r => Proxy layout -> Proxy r -> RouteQ layout r -> QueryApplication (Sem r) Source #