plutus-chain-index-core-1.1.0.0
Safe HaskellNone
LanguageHaskell2010

Plutus.ChainIndex

Synopsis

Documentation

handleChainIndexEffects :: (LastMember IO effs, Member (LogMsg ChainIndexLog) effs) => RunRequirements -> Eff (ChainIndexQueryEffect ': (ChainIndexControlEffect ': (BeamEffect Sqlite ': effs))) a -> Eff effs (Either ChainIndexError a) Source #

Handle the chain index effects from the set of all effects.

data RunRequirements Source #

The required arguments to run the chain index effects.

newtype Value Source #

A cryptocurrency value. This is a map from CurrencySymbols to a quantity of that currency.

Operations on currencies are usually implemented pointwise. That is, we apply the operation to the quantities for each currency in turn. So when we add two Values the resulting Value has, for each currency, the sum of the quantities of that particular currency in the argument Value. The effect of this is that the currencies in the Value are "independent", and are operated on separately.

Whenever we need to get the quantity of a currency in a Value where there is no explicit quantity of that currency in the Value, then the quantity is taken to be zero.

See note [Currencies] for more details.

Instances

Instances details
Eq Value 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

(==) :: Value -> Value -> Bool Source #

(/=) :: Value -> Value -> Bool Source #

Data Value 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Value -> c Value Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Value Source #

toConstr :: Value -> Constr Source #

dataTypeOf :: Value -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Value) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Value) Source #

gmapT :: (forall b. Data b => b -> b) -> Value -> Value Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Value -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Value -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Value -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Value -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Value -> m Value Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Value -> m Value Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Value -> m Value Source #

Show Value 
Instance details

Defined in Plutus.V1.Ledger.Value

Generic Value 
Instance details

Defined in Plutus.V1.Ledger.Value

Associated Types

type Rep Value :: Type -> Type Source #

Methods

from :: Value -> Rep Value x Source #

to :: Rep Value x -> Value Source #

Semigroup Value 
Instance details

Defined in Plutus.V1.Ledger.Value

Monoid Value 
Instance details

Defined in Plutus.V1.Ledger.Value

NFData Value 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

rnf :: Value -> () Source #

Pretty Value 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

pretty :: Value -> Doc ann Source #

prettyList :: [Value] -> Doc ann Source #

UnsafeFromData Value 
Instance details

Defined in Plutus.V1.Ledger.Value

FromData Value 
Instance details

Defined in Plutus.V1.Ledger.Value

ToData Value 
Instance details

Defined in Plutus.V1.Ledger.Value

JoinSemiLattice Value 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

(\/) :: Value -> Value -> Value Source #

MeetSemiLattice Value 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

(/\) :: Value -> Value -> Value Source #

AdditiveSemigroup Value 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

(+) :: Value -> Value -> Value Source #

AdditiveMonoid Value 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

zero :: Value Source #

AdditiveGroup Value 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

(-) :: Value -> Value -> Value Source #

Monoid Value 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

mempty :: Value Source #

Group Value 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

inv :: Value -> Value Source #

Semigroup Value 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

(<>) :: Value -> Value -> Value Source #

Eq Value 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

(==) :: Value -> Value -> Bool Source #

Module Integer Value 
Instance details

Defined in Plutus.V1.Ledger.Value

Methods

scale :: Integer -> Value -> Value Source #

Lift DefaultUni Value 
Instance details

Defined in Plutus.V1.Ledger.Value

Typeable DefaultUni Value 
Instance details

Defined in Plutus.V1.Ledger.Value

type Rep Value 
Instance details

Defined in Plutus.V1.Ledger.Value

type Rep Value = D1 ('MetaData "Value" "Plutus.V1.Ledger.Value" "plutus-ledger-api-1.0.0.1-EUjexvcAhXiGIaLon6olWb" 'True) (C1 ('MetaCons "Value" 'PrefixI 'True) (S1 ('MetaSel ('Just "getValue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map CurrencySymbol (Map TokenName Integer)))))

pageOf Source #

Arguments

:: Eq a 
=> PageQuery a

Pagination query parameters.

-> Set a 
-> Page a 

Given a Set, request the Page with the given PageQuery.

data PageQuery a Source #

Query parameters for pagination.

Constructors

PageQuery 

Fields

Instances

Instances details
Functor PageQuery 
Instance details

Defined in Control.Monad.Freer.Extras.Pagination

Methods

fmap :: (a -> b) -> PageQuery a -> PageQuery b Source #

(<$) :: a -> PageQuery b -> PageQuery a Source #

Eq a => Eq (PageQuery a) 
Instance details

Defined in Control.Monad.Freer.Extras.Pagination

Ord a => Ord (PageQuery a) 
Instance details

Defined in Control.Monad.Freer.Extras.Pagination

Show a => Show (PageQuery a) 
Instance details

Defined in Control.Monad.Freer.Extras.Pagination

Generic (PageQuery a) 
Instance details

Defined in Control.Monad.Freer.Extras.Pagination

Associated Types

type Rep (PageQuery a) :: Type -> Type Source #

Methods

from :: PageQuery a -> Rep (PageQuery a) x Source #

to :: Rep (PageQuery a) x -> PageQuery a Source #

ToJSON a => ToJSON (PageQuery a) 
Instance details

Defined in Control.Monad.Freer.Extras.Pagination

FromJSON a => FromJSON (PageQuery a) 
Instance details

Defined in Control.Monad.Freer.Extras.Pagination

Default (PageQuery a) 
Instance details

Defined in Control.Monad.Freer.Extras.Pagination

Methods

def :: PageQuery a Source #

ToSchema a => ToSchema (PageQuery a) 
Instance details

Defined in Control.Monad.Freer.Extras.Pagination

type Rep (PageQuery a) 
Instance details

Defined in Control.Monad.Freer.Extras.Pagination

type Rep (PageQuery a) = D1 ('MetaData "PageQuery" "Control.Monad.Freer.Extras.Pagination" "freer-extras-1.1.0.0-EyJCycsLf6M9CsqRdBgpX0" 'False) (C1 ('MetaCons "PageQuery" 'PrefixI 'True) (S1 ('MetaSel ('Just "pageQuerySize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PageSize) :*: S1 ('MetaSel ('Just "pageQueryLastItem") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe a))))

newtype PageSize Source #

Constructors

PageSize 

Fields

Instances

Instances details
Eq PageSize 
Instance details

Defined in Control.Monad.Freer.Extras.Pagination

Num PageSize 
Instance details

Defined in Control.Monad.Freer.Extras.Pagination

Ord PageSize 
Instance details

Defined in Control.Monad.Freer.Extras.Pagination

Show PageSize 
Instance details

Defined in Control.Monad.Freer.Extras.Pagination

Generic PageSize 
Instance details

Defined in Control.Monad.Freer.Extras.Pagination

Associated Types

type Rep PageSize :: Type -> Type Source #

ToJSON PageSize 
Instance details

Defined in Control.Monad.Freer.Extras.Pagination

FromJSON PageSize 
Instance details

Defined in Control.Monad.Freer.Extras.Pagination

Default PageSize 
Instance details

Defined in Control.Monad.Freer.Extras.Pagination

Methods

def :: PageSize Source #

ToSchema PageSize 
Instance details

Defined in Control.Monad.Freer.Extras.Pagination

type Rep PageSize 
Instance details

Defined in Control.Monad.Freer.Extras.Pagination

type Rep PageSize = D1 ('MetaData "PageSize" "Control.Monad.Freer.Extras.Pagination" "freer-extras-1.1.0.0-EyJCycsLf6M9CsqRdBgpX0" 'True) (C1 ('MetaCons "PageSize" 'PrefixI 'True) (S1 ('MetaSel ('Just "getPageSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Natural)))

data Page a Source #

Part of a collection.

Constructors

Page 

Fields

Instances

Instances details
Functor Page 
Instance details

Defined in Control.Monad.Freer.Extras.Pagination

Methods

fmap :: (a -> b) -> Page a -> Page b Source #

(<$) :: a -> Page b -> Page a Source #

Eq a => Eq (Page a) 
Instance details

Defined in Control.Monad.Freer.Extras.Pagination

Methods

(==) :: Page a -> Page a -> Bool Source #

(/=) :: Page a -> Page a -> Bool Source #

Ord a => Ord (Page a) 
Instance details

Defined in Control.Monad.Freer.Extras.Pagination

Methods

compare :: Page a -> Page a -> Ordering Source #

(<) :: Page a -> Page a -> Bool Source #

(<=) :: Page a -> Page a -> Bool Source #

(>) :: Page a -> Page a -> Bool Source #

(>=) :: Page a -> Page a -> Bool Source #

max :: Page a -> Page a -> Page a Source #

min :: Page a -> Page a -> Page a Source #

Show a => Show (Page a) 
Instance details

Defined in Control.Monad.Freer.Extras.Pagination

Methods

showsPrec :: Int -> Page a -> ShowS Source #

show :: Page a -> String Source #

showList :: [Page a] -> ShowS Source #

Generic (Page a) 
Instance details

Defined in Control.Monad.Freer.Extras.Pagination

Associated Types

type Rep (Page a) :: Type -> Type Source #

Methods

from :: Page a -> Rep (Page a) x Source #

to :: Rep (Page a) x -> Page a Source #

ToJSON a => ToJSON (Page a) 
Instance details

Defined in Control.Monad.Freer.Extras.Pagination

FromJSON a => FromJSON (Page a) 
Instance details

Defined in Control.Monad.Freer.Extras.Pagination

ToSchema a => ToSchema (Page a) 
Instance details

Defined in Control.Monad.Freer.Extras.Pagination

type Rep (Page a) 
Instance details

Defined in Control.Monad.Freer.Extras.Pagination

type Rep (Page a) = D1 ('MetaData "Page" "Control.Monad.Freer.Extras.Pagination" "freer-extras-1.1.0.0-EyJCycsLf6M9CsqRdBgpX0" 'False) (C1 ('MetaCons "Page" 'PrefixI 'True) (S1 ('MetaSel ('Just "currentPageQuery") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PageQuery a)) :*: (S1 ('MetaSel ('Just "nextPageQuery") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (PageQuery a))) :*: S1 ('MetaSel ('Just "pageItems") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [a]))))

newtype BlockId Source #

Block identifier (usually a hash)

Constructors

BlockId 

Instances

Instances details
Eq BlockId 
Instance details

Defined in Ledger.Blockchain

Ord BlockId 
Instance details

Defined in Ledger.Blockchain

Show BlockId 
Instance details

Defined in Ledger.Blockchain

Generic BlockId 
Instance details

Defined in Ledger.Blockchain

Associated Types

type Rep BlockId :: Type -> Type Source #

ToJSON BlockId 
Instance details

Defined in Ledger.Blockchain

FromJSON BlockId 
Instance details

Defined in Ledger.Blockchain

ToSchema BlockId 
Instance details

Defined in Ledger.Blockchain

Pretty BlockId 
Instance details

Defined in Ledger.Blockchain

Methods

pretty :: BlockId -> Doc ann Source #

prettyList :: [BlockId] -> Doc ann Source #

HasDbType BlockId Source # 
Instance details

Defined in Plutus.ChainIndex.DbSchema

Associated Types

type DbType BlockId Source #

type Rep BlockId 
Instance details

Defined in Ledger.Blockchain

type Rep BlockId = D1 ('MetaData "BlockId" "Ledger.Blockchain" "plutus-ledger-1.1.0.0-JskZbcPMCdRJVHaAZ0to82" 'True) (C1 ('MetaCons "BlockId" 'PrefixI 'True) (S1 ('MetaSel ('Just "getBlockId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)))
type DbType BlockId Source # 
Instance details

Defined in Plutus.ChainIndex.DbSchema

data Address Source #

Address with two kinds of credentials, normal and staking.

Instances

Instances details
Eq Address 
Instance details

Defined in Plutus.V1.Ledger.Address

Ord Address 
Instance details

Defined in Plutus.V1.Ledger.Address

Show Address 
Instance details

Defined in Plutus.V1.Ledger.Address

Generic Address 
Instance details

Defined in Plutus.V1.Ledger.Address

Associated Types

type Rep Address :: Type -> Type Source #

NFData Address 
Instance details

Defined in Plutus.V1.Ledger.Address

Methods

rnf :: Address -> () Source #

Pretty Address 
Instance details

Defined in Plutus.V1.Ledger.Address

Methods

pretty :: Address -> Doc ann Source #

prettyList :: [Address] -> Doc ann Source #

UnsafeFromData Address 
Instance details

Defined in Plutus.V1.Ledger.Address

FromData Address 
Instance details

Defined in Plutus.V1.Ledger.Address

ToData Address 
Instance details

Defined in Plutus.V1.Ledger.Address

Eq Address 
Instance details

Defined in Plutus.V1.Ledger.Address

Methods

(==) :: Address -> Address -> Bool Source #

Lift DefaultUni Address 
Instance details

Defined in Plutus.V1.Ledger.Address

Typeable DefaultUni Address 
Instance details

Defined in Plutus.V1.Ledger.Address

type Rep Address 
Instance details

Defined in Plutus.V1.Ledger.Address

type Rep Address = D1 ('MetaData "Address" "Plutus.V1.Ledger.Address" "plutus-ledger-api-1.0.0.1-EUjexvcAhXiGIaLon6olWb" 'False) (C1 ('MetaCons "Address" 'PrefixI 'True) (S1 ('MetaSel ('Just "addressCredential") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Credential) :*: S1 ('MetaSel ('Just "addressStakingCredential") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe StakingCredential))))

data OutputDatum Source #

The datum attached to an output: either nothing; a datum hash; or the datum itself (an "inline datum").

Instances

Instances details
Eq OutputDatum 
Instance details

Defined in Plutus.V2.Ledger.Tx

Show OutputDatum 
Instance details

Defined in Plutus.V2.Ledger.Tx

Generic OutputDatum 
Instance details

Defined in Plutus.V2.Ledger.Tx

Associated Types

type Rep OutputDatum :: Type -> Type Source #

NFData OutputDatum 
Instance details

Defined in Plutus.V2.Ledger.Tx

Methods

rnf :: OutputDatum -> () Source #

Pretty OutputDatum 
Instance details

Defined in Plutus.V2.Ledger.Tx

UnsafeFromData OutputDatum 
Instance details

Defined in Plutus.V2.Ledger.Tx

FromData OutputDatum 
Instance details

Defined in Plutus.V2.Ledger.Tx

ToData OutputDatum 
Instance details

Defined in Plutus.V2.Ledger.Tx

Eq OutputDatum 
Instance details

Defined in Plutus.V2.Ledger.Tx

Lift DefaultUni OutputDatum 
Instance details

Defined in Plutus.V2.Ledger.Tx

Typeable DefaultUni OutputDatum 
Instance details

Defined in Plutus.V2.Ledger.Tx

type Rep OutputDatum 
Instance details

Defined in Plutus.V2.Ledger.Tx

type Rep OutputDatum = D1 ('MetaData "OutputDatum" "Plutus.V2.Ledger.Tx" "plutus-ledger-api-1.0.0.1-EUjexvcAhXiGIaLon6olWb" 'False) (C1 ('MetaCons "NoOutputDatum" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "OutputDatumHash" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DatumHash)) :+: C1 ('MetaCons "OutputDatum" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Datum))))

data ChainIndexTxOutputs Source #

List of outputs of a transaction. There is only an optional collateral output if the transaction is invalid.

Constructors

InvalidTx (Maybe ChainIndexTxOut)

The transaction is invalid so there is maybe a collateral output.

ValidTx [ChainIndexTxOut] 

Instances

Instances details
Eq ChainIndexTxOutputs Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Show ChainIndexTxOutputs Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Generic ChainIndexTxOutputs Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Associated Types

type Rep ChainIndexTxOutputs :: Type -> Type Source #

ToJSON ChainIndexTxOutputs Source # 
Instance details

Defined in Plutus.ChainIndex.Types

FromJSON ChainIndexTxOutputs Source # 
Instance details

Defined in Plutus.ChainIndex.Types

ToSchema ChainIndexTxOutputs Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Serialise ChainIndexTxOutputs Source # 
Instance details

Defined in Plutus.ChainIndex.Types

type Rep ChainIndexTxOutputs Source # 
Instance details

Defined in Plutus.ChainIndex.Types

type Rep ChainIndexTxOutputs = D1 ('MetaData "ChainIndexTxOutputs" "Plutus.ChainIndex.Types" "plutus-chain-index-core-1.1.0.0-K7whjMLv5AnJVt0avXcbFn" 'False) (C1 ('MetaCons "InvalidTx" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe ChainIndexTxOut))) :+: C1 ('MetaCons "ValidTx" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [ChainIndexTxOut])))

data ChainIndexTxOut Source #

Constructors

ChainIndexTxOut 

Fields

Instances

Instances details
Eq ChainIndexTxOut Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Show ChainIndexTxOut Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Generic ChainIndexTxOut Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Associated Types

type Rep ChainIndexTxOut :: Type -> Type Source #

ToJSON ChainIndexTxOut Source # 
Instance details

Defined in Plutus.ChainIndex.Types

FromJSON ChainIndexTxOut Source # 
Instance details

Defined in Plutus.ChainIndex.Types

ToSchema ChainIndexTxOut Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Pretty ChainIndexTxOut Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Serialise ChainIndexTxOut Source # 
Instance details

Defined in Plutus.ChainIndex.Types

HasDbType ChainIndexTxOut Source # 
Instance details

Defined in Plutus.ChainIndex.DbSchema

Associated Types

type DbType ChainIndexTxOut Source #

type Rep ChainIndexTxOut Source # 
Instance details

Defined in Plutus.ChainIndex.Types

type Rep ChainIndexTxOut = D1 ('MetaData "ChainIndexTxOut" "Plutus.ChainIndex.Types" "plutus-chain-index-core-1.1.0.0-K7whjMLv5AnJVt0avXcbFn" 'False) (C1 ('MetaCons "ChainIndexTxOut" 'PrefixI 'True) ((S1 ('MetaSel ('Just "citoAddress") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 CardanoAddress) :*: S1 ('MetaSel ('Just "citoValue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Value)) :*: (S1 ('MetaSel ('Just "citoDatum") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 OutputDatum) :*: S1 ('MetaSel ('Just "citoRefScript") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ReferenceScript))))
type DbType ChainIndexTxOut Source # 
Instance details

Defined in Plutus.ChainIndex.DbSchema

data ReferenceScript Source #

Instances

Instances details
Eq ReferenceScript Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Show ReferenceScript Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Generic ReferenceScript Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Associated Types

type Rep ReferenceScript :: Type -> Type Source #

ToJSON ReferenceScript Source # 
Instance details

Defined in Plutus.ChainIndex.Types

FromJSON ReferenceScript Source # 
Instance details

Defined in Plutus.ChainIndex.Types

ToSchema ReferenceScript Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Serialise ReferenceScript Source # 
Instance details

Defined in Plutus.ChainIndex.Types

type Rep ReferenceScript Source # 
Instance details

Defined in Plutus.ChainIndex.Types

type Rep ReferenceScript = D1 ('MetaData "ReferenceScript" "Plutus.ChainIndex.Types" "plutus-chain-index-core-1.1.0.0-K7whjMLv5AnJVt0avXcbFn" 'False) (C1 ('MetaCons "ReferenceScriptNone" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ReferenceScriptInAnyLang" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ScriptInAnyLang)))

data ChainIndexTx Source #

Constructors

ChainIndexTx 

Fields

Instances

Instances details
Eq ChainIndexTx Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Show ChainIndexTx Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Generic ChainIndexTx Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Associated Types

type Rep ChainIndexTx :: Type -> Type Source #

ToJSON ChainIndexTx Source # 
Instance details

Defined in Plutus.ChainIndex.Types

FromJSON ChainIndexTx Source # 
Instance details

Defined in Plutus.ChainIndex.Types

ToSchema ChainIndexTx Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Pretty ChainIndexTx Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Serialise ChainIndexTx Source # 
Instance details

Defined in Plutus.ChainIndex.Types

HasDbType ChainIndexTx Source # 
Instance details

Defined in Plutus.ChainIndex.DbSchema

Associated Types

type DbType ChainIndexTx Source #

HasDbType (TxId, ChainIndexTx) Source # 
Instance details

Defined in Plutus.ChainIndex.DbSchema

Associated Types

type DbType (TxId, ChainIndexTx) Source #

type Rep ChainIndexTx Source # 
Instance details

Defined in Plutus.ChainIndex.Types

type DbType ChainIndexTx Source # 
Instance details

Defined in Plutus.ChainIndex.DbSchema

type DbType (TxId, ChainIndexTx) Source # 
Instance details

Defined in Plutus.ChainIndex.DbSchema

data Tip Source #

The tip of the chain index.

Constructors

TipAtGenesis 
Tip 

Fields

Instances

Instances details
Eq Tip Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Methods

(==) :: Tip -> Tip -> Bool Source #

(/=) :: Tip -> Tip -> Bool Source #

Ord Tip Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Methods

compare :: Tip -> Tip -> Ordering Source #

(<) :: Tip -> Tip -> Bool Source #

(<=) :: Tip -> Tip -> Bool Source #

(>) :: Tip -> Tip -> Bool Source #

(>=) :: Tip -> Tip -> Bool Source #

max :: Tip -> Tip -> Tip Source #

min :: Tip -> Tip -> Tip Source #

Show Tip Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Generic Tip Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Associated Types

type Rep Tip :: Type -> Type Source #

Methods

from :: Tip -> Rep Tip x Source #

to :: Rep Tip x -> Tip Source #

Semigroup Tip Source #

This mirrors the previously defined Tip which used the Last monoid definition.

Instance details

Defined in Plutus.ChainIndex.Types

Methods

(<>) :: Tip -> Tip -> Tip Source #

sconcat :: NonEmpty Tip -> Tip Source #

stimes :: Integral b => b -> Tip -> Tip Source #

Monoid Tip Source # 
Instance details

Defined in Plutus.ChainIndex.Types

ToJSON Tip Source # 
Instance details

Defined in Plutus.ChainIndex.Types

FromJSON Tip Source # 
Instance details

Defined in Plutus.ChainIndex.Types

ToSchema Tip Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Pretty Tip Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Methods

pretty :: Tip -> Doc ann Source #

prettyList :: [Tip] -> Doc ann Source #

HasDbType Tip Source # 
Instance details

Defined in Plutus.ChainIndex.DbSchema

Associated Types

type DbType Tip Source #

type Rep Tip Source # 
Instance details

Defined in Plutus.ChainIndex.Types

type Rep Tip = D1 ('MetaData "Tip" "Plutus.ChainIndex.Types" "plutus-chain-index-core-1.1.0.0-K7whjMLv5AnJVt0avXcbFn" 'False) (C1 ('MetaCons "TipAtGenesis" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Tip" 'PrefixI 'True) (S1 ('MetaSel ('Just "tipSlot") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Slot) :*: (S1 ('MetaSel ('Just "tipBlockId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 BlockId) :*: S1 ('MetaSel ('Just "tipBlockNo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 BlockNumber))))
type DbType Tip Source # 
Instance details

Defined in Plutus.ChainIndex.DbSchema

newtype BlockNumber Source #

Constructors

BlockNumber 

Instances

Instances details
Enum BlockNumber Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Eq BlockNumber Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Integral BlockNumber Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Num BlockNumber Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Ord BlockNumber Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Real BlockNumber Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Show BlockNumber Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Generic BlockNumber Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Associated Types

type Rep BlockNumber :: Type -> Type Source #

ToJSON BlockNumber Source # 
Instance details

Defined in Plutus.ChainIndex.Types

FromJSON BlockNumber Source # 
Instance details

Defined in Plutus.ChainIndex.Types

ToSchema BlockNumber Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Pretty BlockNumber Source # 
Instance details

Defined in Plutus.ChainIndex.Types

HasDbType BlockNumber Source # 
Instance details

Defined in Plutus.ChainIndex.DbSchema

Associated Types

type DbType BlockNumber Source #

type Rep BlockNumber Source # 
Instance details

Defined in Plutus.ChainIndex.Types

type Rep BlockNumber = D1 ('MetaData "BlockNumber" "Plutus.ChainIndex.Types" "plutus-chain-index-core-1.1.0.0-K7whjMLv5AnJVt0avXcbFn" 'True) (C1 ('MetaCons "BlockNumber" 'PrefixI 'True) (S1 ('MetaSel ('Just "unBlockNumber") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64)))
type DbType BlockNumber Source # 
Instance details

Defined in Plutus.ChainIndex.DbSchema

blockId :: Block -> BlockId Source #

Compute a hash of the block's contents.

data Point Source #

When performing a rollback the chain sync protocol does not provide a block number where to resume from.

Constructors

PointAtGenesis 
Point 

Fields

Instances

Instances details
Eq Point Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Methods

(==) :: Point -> Point -> Bool Source #

(/=) :: Point -> Point -> Bool Source #

Ord Point Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Show Point Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Generic Point Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Associated Types

type Rep Point :: Type -> Type Source #

Methods

from :: Point -> Rep Point x Source #

to :: Rep Point x -> Point Source #

Semigroup Point Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Monoid Point Source # 
Instance details

Defined in Plutus.ChainIndex.Types

ToJSON Point Source # 
Instance details

Defined in Plutus.ChainIndex.Types

FromJSON Point Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Pretty Point Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Methods

pretty :: Point -> Doc ann Source #

prettyList :: [Point] -> Doc ann Source #

type Rep Point Source # 
Instance details

Defined in Plutus.ChainIndex.Types

type Rep Point = D1 ('MetaData "Point" "Plutus.ChainIndex.Types" "plutus-chain-index-core-1.1.0.0-K7whjMLv5AnJVt0avXcbFn" 'False) (C1 ('MetaCons "PointAtGenesis" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Point" 'PrefixI 'True) (S1 ('MetaSel ('Just "pointSlot") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Slot) :*: S1 ('MetaSel ('Just "pointBlockId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 BlockId)))

data TxOutBalance Source #

The effect of a transaction (or a number of them) on the tx output set.

Constructors

TxOutBalance 

Fields

Instances

Instances details
Eq TxOutBalance Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Show TxOutBalance Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Generic TxOutBalance Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Associated Types

type Rep TxOutBalance :: Type -> Type Source #

Semigroup TxOutBalance Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Monoid TxOutBalance Source # 
Instance details

Defined in Plutus.ChainIndex.Types

ToJSON TxOutBalance Source # 
Instance details

Defined in Plutus.ChainIndex.Types

FromJSON TxOutBalance Source # 
Instance details

Defined in Plutus.ChainIndex.Types

type Rep TxOutBalance Source # 
Instance details

Defined in Plutus.ChainIndex.Types

type Rep TxOutBalance = D1 ('MetaData "TxOutBalance" "Plutus.ChainIndex.Types" "plutus-chain-index-core-1.1.0.0-K7whjMLv5AnJVt0avXcbFn" 'False) (C1 ('MetaCons "TxOutBalance" 'PrefixI 'True) (S1 ('MetaSel ('Just "_tobUnspentOutputs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Set TxOutRef)) :*: S1 ('MetaSel ('Just "_tobSpentOutputs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Map TxOutRef TxId))))

data TxConfirmedState Source #

Instances

Instances details
Eq TxConfirmedState Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Show TxConfirmedState Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Generic TxConfirmedState Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Associated Types

type Rep TxConfirmedState :: Type -> Type Source #

Semigroup TxConfirmedState Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Monoid TxConfirmedState Source # 
Instance details

Defined in Plutus.ChainIndex.Types

type Rep TxConfirmedState Source # 
Instance details

Defined in Plutus.ChainIndex.Types

type Rep TxConfirmedState = D1 ('MetaData "TxConfirmedState" "Plutus.ChainIndex.Types" "plutus-chain-index-core-1.1.0.0-K7whjMLv5AnJVt0avXcbFn" 'False) (C1 ('MetaCons "TxConfirmedState" 'PrefixI 'True) (S1 ('MetaSel ('Just "timesConfirmed") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Sum Int)) :*: (S1 ('MetaSel ('Just "blockAdded") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Last BlockNumber)) :*: S1 ('MetaSel ('Just "validity") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Last TxValidity)))))

data TxIdState Source #

Constructors

TxIdState 

Fields

Instances

Instances details
Eq TxIdState Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Show TxIdState Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Generic TxIdState Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Associated Types

type Rep TxIdState :: Type -> Type Source #

Semigroup TxIdState Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Monoid TxIdState Source # 
Instance details

Defined in Plutus.ChainIndex.Types

type Rep TxIdState Source # 
Instance details

Defined in Plutus.ChainIndex.Types

type Rep TxIdState = D1 ('MetaData "TxIdState" "Plutus.ChainIndex.Types" "plutus-chain-index-core-1.1.0.0-K7whjMLv5AnJVt0avXcbFn" 'False) (C1 ('MetaCons "TxIdState" 'PrefixI 'True) (S1 ('MetaSel ('Just "txnsConfirmed") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Map TxId TxConfirmedState)) :*: S1 ('MetaSel ('Just "txnsDeleted") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Map TxId (Sum Int)))))

data TxStatusFailure Source #

Datatype returned when we couldn't get the state of a tx or a tx output.

Constructors

TxIdStateInvalid BlockNumber TxId TxIdState

We couldn't return the status because the TxIdState was in a ... state ... that we didn't know how to decode in transactionStatus.

TxOutBalanceStateInvalid BlockNumber TxOutRef TxOutBalance

We couldn't return the status because the TxOutBalance does not contain the target tx output.

InvalidRollbackAttempt BlockNumber TxId TxIdState 

data Diagnostics Source #

Instances

Instances details
Eq Diagnostics Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Show Diagnostics Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Generic Diagnostics Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Associated Types

type Rep Diagnostics :: Type -> Type Source #

ToJSON Diagnostics Source # 
Instance details

Defined in Plutus.ChainIndex.Types

FromJSON Diagnostics Source # 
Instance details

Defined in Plutus.ChainIndex.Types

ToSchema Diagnostics Source # 
Instance details

Defined in Plutus.ChainIndex.Types

type Rep Diagnostics Source # 
Instance details

Defined in Plutus.ChainIndex.Types

type Rep Diagnostics = D1 ('MetaData "Diagnostics" "Plutus.ChainIndex.Types" "plutus-chain-index-core-1.1.0.0-K7whjMLv5AnJVt0avXcbFn" 'False) (C1 ('MetaCons "Diagnostics" 'PrefixI 'True) (((S1 ('MetaSel ('Just "numTransactions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Integer) :*: S1 ('MetaSel ('Just "numScripts") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Integer)) :*: (S1 ('MetaSel ('Just "numAddresses") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Integer) :*: S1 ('MetaSel ('Just "numAssetClasses") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Integer))) :*: ((S1 ('MetaSel ('Just "numUnspentOutputs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Just "numUnmatchedInputs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int)) :*: (S1 ('MetaSel ('Just "someTransactions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [TxId]) :*: S1 ('MetaSel ('Just "unspentTxOuts") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [ChainIndexTxOut])))))

data TxOutState Source #

Constructors

Spent TxId 
Unspent 

Instances

Instances details
Eq TxOutState Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Ord TxOutState Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Show TxOutState Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Generic TxOutState Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Associated Types

type Rep TxOutState :: Type -> Type Source #

ToJSON TxOutState Source # 
Instance details

Defined in Plutus.ChainIndex.Types

FromJSON TxOutState Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Pretty TxOutState Source # 
Instance details

Defined in Plutus.ChainIndex.Types

type Rep TxOutState Source # 
Instance details

Defined in Plutus.ChainIndex.Types

type Rep TxOutState = D1 ('MetaData "TxOutState" "Plutus.ChainIndex.Types" "plutus-chain-index-core-1.1.0.0-K7whjMLv5AnJVt0avXcbFn" 'False) (C1 ('MetaCons "Spent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 TxId)) :+: C1 ('MetaCons "Unspent" 'PrefixI 'False) (U1 :: Type -> Type))

data RollbackState a Source #

The rollback state of a Cardano transaction

Constructors

Unknown

The transaction is not on the chain. That's all we can say.

TentativelyConfirmed Depth TxValidity a

The transaction is on the chain, n blocks deep. It can still be rolled back.

Committed TxValidity a

The transaction is on the chain. It cannot be rolled back anymore.

Instances

Instances details
Functor RollbackState Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Methods

fmap :: (a -> b) -> RollbackState a -> RollbackState b Source #

(<$) :: a -> RollbackState b -> RollbackState a Source #

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

Defined in Plutus.ChainIndex.Types

Ord a => Ord (RollbackState a) Source # 
Instance details

Defined in Plutus.ChainIndex.Types

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

Defined in Plutus.ChainIndex.Types

Generic (RollbackState a) Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Associated Types

type Rep (RollbackState a) :: Type -> Type Source #

ToJSON a => ToJSON (RollbackState a) Source # 
Instance details

Defined in Plutus.ChainIndex.Types

FromJSON a => FromJSON (RollbackState a) Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Show a => Pretty (RollbackState a) Source # 
Instance details

Defined in Plutus.ChainIndex.Types

MeetSemiLattice a => MeetSemiLattice (RollbackState a) Source # 
Instance details

Defined in Plutus.ChainIndex.Types

type Rep (RollbackState a) Source # 
Instance details

Defined in Plutus.ChainIndex.Types

type TxStatus = RollbackState () Source #

The status of a Cardano transaction

newtype Depth Source #

How many blocks deep the tx is on the chain

Constructors

Depth 

Fields

Instances

Instances details
Enum Depth Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Eq Depth Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Methods

(==) :: Depth -> Depth -> Bool Source #

(/=) :: Depth -> Depth -> Bool Source #

Integral Depth Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Num Depth Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Ord Depth Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Real Depth Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Show Depth Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Generic Depth Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Associated Types

type Rep Depth :: Type -> Type Source #

Methods

from :: Depth -> Rep Depth x Source #

to :: Rep Depth x -> Depth Source #

ToJSON Depth Source # 
Instance details

Defined in Plutus.ChainIndex.Types

FromJSON Depth Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Pretty Depth Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Methods

pretty :: Depth -> Doc ann Source #

prettyList :: [Depth] -> Doc ann Source #

MeetSemiLattice Depth Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Methods

(/\) :: Depth -> Depth -> Depth Source #

type Rep Depth Source # 
Instance details

Defined in Plutus.ChainIndex.Types

type Rep Depth = D1 ('MetaData "Depth" "Plutus.ChainIndex.Types" "plutus-chain-index-core-1.1.0.0-K7whjMLv5AnJVt0avXcbFn" 'True) (C1 ('MetaCons "Depth" 'PrefixI 'True) (S1 ('MetaSel ('Just "unDepth") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))

data TxValidity Source #

Validity of a transaction that has been added to the ledger

Instances

Instances details
Eq TxValidity Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Ord TxValidity Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Show TxValidity Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Generic TxValidity Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Associated Types

type Rep TxValidity :: Type -> Type Source #

ToJSON TxValidity Source # 
Instance details

Defined in Plutus.ChainIndex.Types

FromJSON TxValidity Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Pretty TxValidity Source # 
Instance details

Defined in Plutus.ChainIndex.Types

MeetSemiLattice TxValidity Source # 
Instance details

Defined in Plutus.ChainIndex.Types

type Rep TxValidity Source # 
Instance details

Defined in Plutus.ChainIndex.Types

type Rep TxValidity = D1 ('MetaData "TxValidity" "Plutus.ChainIndex.Types" "plutus-chain-index-core-1.1.0.0-K7whjMLv5AnJVt0avXcbFn" 'False) (C1 ('MetaCons "TxValid" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "TxInvalid" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UnknownValidity" 'PrefixI 'False) (U1 :: Type -> Type)))

txOutStatusTxOutState :: TxOutStatus -> Maybe TxOutState Source #

Maybe extract the TxOutState (Spent or Unspent) of a TxOutStatus.

liftTxOutStatus :: TxOutStatus -> TxStatus Source #

Converts a TxOutStatus to a TxStatus. Possible since a transaction output belongs to a transaction.

Note, however, that we can't convert a TxStatus to a TxOutStatus.

data TxUtxoBalance Source #

The effect of a transaction (or a number of them) on the utxo set.

Constructors

TxUtxoBalance 

Fields

Instances

Instances details
Eq TxUtxoBalance Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Show TxUtxoBalance Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Generic TxUtxoBalance Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Associated Types

type Rep TxUtxoBalance :: Type -> Type Source #

Semigroup TxUtxoBalance Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Monoid TxUtxoBalance Source # 
Instance details

Defined in Plutus.ChainIndex.Types

ToJSON TxUtxoBalance Source # 
Instance details

Defined in Plutus.ChainIndex.Types

FromJSON TxUtxoBalance Source # 
Instance details

Defined in Plutus.ChainIndex.Types

Serialise TxUtxoBalance Source # 
Instance details

Defined in Plutus.ChainIndex.Types

type Rep TxUtxoBalance Source # 
Instance details

Defined in Plutus.ChainIndex.Types

type Rep TxUtxoBalance = D1 ('MetaData "TxUtxoBalance" "Plutus.ChainIndex.Types" "plutus-chain-index-core-1.1.0.0-K7whjMLv5AnJVt0avXcbFn" 'False) (C1 ('MetaCons "TxUtxoBalance" 'PrefixI 'True) (S1 ('MetaSel ('Just "_tubUnspentOutputs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Set TxOutRef)) :*: S1 ('MetaSel ('Just "_tubUnmatchedSpentInputs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Set TxOutRef))))

data ChainSyncBlock Source #

A block of transactions to be synced.

Constructors

Block 

Instances

Instances details
Show ChainSyncBlock Source # 
Instance details

Defined in Plutus.ChainIndex.Types

newtype TxProcessOption Source #

User-customizable options to process a transaction. See #73 for more motivations.

Constructors

TxProcessOption 

Fields

  • tpoStoreTx :: Bool

    Should the chain index store this transaction or not. If not, only handle the UTXOs. This, for example, allows applications to skip unwanted pre-Alonzo transactions.

data RollbackFailed Source #

Reason why the rollback operation failed

Constructors

RollbackNoTip

Rollback failed because the utxo index had no tip (not synchronised)

TipMismatch

Unable to roll back to expectedTip because the tip at that position was different

Fields

OldPointNotFound Point

Unable to find the old tip

Instances

Instances details
Eq RollbackFailed Source # 
Instance details

Defined in Plutus.ChainIndex.ChainIndexError

Ord RollbackFailed Source # 
Instance details

Defined in Plutus.ChainIndex.ChainIndexError

Show RollbackFailed Source # 
Instance details

Defined in Plutus.ChainIndex.ChainIndexError

Generic RollbackFailed Source # 
Instance details

Defined in Plutus.ChainIndex.ChainIndexError

Associated Types

type Rep RollbackFailed :: Type -> Type Source #

ToJSON RollbackFailed Source # 
Instance details

Defined in Plutus.ChainIndex.ChainIndexError

FromJSON RollbackFailed Source # 
Instance details

Defined in Plutus.ChainIndex.ChainIndexError

Pretty RollbackFailed Source # 
Instance details

Defined in Plutus.ChainIndex.ChainIndexError

type Rep RollbackFailed Source # 
Instance details

Defined in Plutus.ChainIndex.ChainIndexError

type Rep RollbackFailed = D1 ('MetaData "RollbackFailed" "Plutus.ChainIndex.ChainIndexError" "plutus-chain-index-core-1.1.0.0-K7whjMLv5AnJVt0avXcbFn" 'False) (C1 ('MetaCons "RollbackNoTip" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "TipMismatch" 'PrefixI 'True) (S1 ('MetaSel ('Just "foundTip") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Tip) :*: S1 ('MetaSel ('Just "targetPoint") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Point)) :+: C1 ('MetaCons "OldPointNotFound" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Point))))

data InsertUtxoFailed Source #

UTXO state could not be inserted into the chain index

Constructors

DuplicateBlock Tip

Insertion failed as there was already a block with the given number

InsertUtxoNoTip

The _usTip field of the argument was 'Last Nothing'

Instances

Instances details
Eq InsertUtxoFailed Source # 
Instance details

Defined in Plutus.ChainIndex.ChainIndexError

Ord InsertUtxoFailed Source # 
Instance details

Defined in Plutus.ChainIndex.ChainIndexError

Show InsertUtxoFailed Source # 
Instance details

Defined in Plutus.ChainIndex.ChainIndexError

Generic InsertUtxoFailed Source # 
Instance details

Defined in Plutus.ChainIndex.ChainIndexError

Associated Types

type Rep InsertUtxoFailed :: Type -> Type Source #

ToJSON InsertUtxoFailed Source # 
Instance details

Defined in Plutus.ChainIndex.ChainIndexError

FromJSON InsertUtxoFailed Source # 
Instance details

Defined in Plutus.ChainIndex.ChainIndexError

Pretty InsertUtxoFailed Source # 
Instance details

Defined in Plutus.ChainIndex.ChainIndexError

type Rep InsertUtxoFailed Source # 
Instance details

Defined in Plutus.ChainIndex.ChainIndexError

type Rep InsertUtxoFailed = D1 ('MetaData "InsertUtxoFailed" "Plutus.ChainIndex.ChainIndexError" "plutus-chain-index-core-1.1.0.0-K7whjMLv5AnJVt0avXcbFn" 'False) (C1 ('MetaCons "DuplicateBlock" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Tip)) :+: C1 ('MetaCons "InsertUtxoNoTip" 'PrefixI 'False) (U1 :: Type -> Type))

data ChainIndexError Source #

Constructors

InsertionFailed InsertUtxoFailed 
RollbackFailed RollbackFailed 
ResumeNotSupported 
QueryFailedNoTip

Query failed because the chain index does not have a tip (not synchronised with node)

BeamEffectError BeamError 

Instances

Instances details
Eq ChainIndexError Source # 
Instance details

Defined in Plutus.ChainIndex.ChainIndexError

Show ChainIndexError Source # 
Instance details

Defined in Plutus.ChainIndex.ChainIndexError

Generic ChainIndexError Source # 
Instance details

Defined in Plutus.ChainIndex.ChainIndexError

Associated Types

type Rep ChainIndexError :: Type -> Type Source #

ToJSON ChainIndexError Source # 
Instance details

Defined in Plutus.ChainIndex.ChainIndexError

FromJSON ChainIndexError Source # 
Instance details

Defined in Plutus.ChainIndex.ChainIndexError

Pretty ChainIndexError Source # 
Instance details

Defined in Plutus.ChainIndex.ChainIndexError

type Rep ChainIndexError Source # 
Instance details

Defined in Plutus.ChainIndex.ChainIndexError

type Rep ChainIndexError = D1 ('MetaData "ChainIndexError" "Plutus.ChainIndex.ChainIndexError" "plutus-chain-index-core-1.1.0.0-K7whjMLv5AnJVt0avXcbFn" 'False) ((C1 ('MetaCons "InsertionFailed" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 InsertUtxoFailed)) :+: C1 ('MetaCons "RollbackFailed" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RollbackFailed))) :+: (C1 ('MetaCons "ResumeNotSupported" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "QueryFailedNoTip" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BeamEffectError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BeamError)))))

txOuts :: ChainIndexTx -> [ChainIndexTxOut] Source #

Get tx outputs from tx.

txOutRefs :: ChainIndexTx -> [TxOutRef] Source #

Get tx output references from tx.

txOutsWithRef :: ChainIndexTx -> [(ChainIndexTxOut, TxOutRef)] Source #

Get tx output references and tx outputs from tx.

txOutRefMap :: ChainIndexTx -> Map TxOutRef (ChainIndexTxOut, ChainIndexTx) Source #

Get Map of tx outputs references to tx.

txOutRefMapForAddr :: CardanoAddress -> ChainIndexTx -> Map TxOutRef (ChainIndexTxOut, ChainIndexTx) Source #

Get Map of tx outputs from tx for a specific address.

fromOnChainTx :: OnChainTx -> ChainIndexTx Source #

Convert a OnChainTx to a ChainIndexTx. An invalid OnChainTx will not produce any ChainIndexTx outputs and the collateral inputs of the OnChainTx will be the inputs of the ChainIndexTx.

data ChainIndexQueryEffect r where Source #

Constructors

DatumFromHash :: DatumHash -> ChainIndexQueryEffect (Maybe Datum)

Get the datum from a datum hash (if available)

ValidatorFromHash :: ValidatorHash -> ChainIndexQueryEffect (Maybe (Versioned Validator))

Get the validator from a validator hash (if available)

MintingPolicyFromHash :: MintingPolicyHash -> ChainIndexQueryEffect (Maybe (Versioned MintingPolicy))

Get the monetary policy from an MPS hash (if available)

RedeemerFromHash :: RedeemerHash -> ChainIndexQueryEffect (Maybe Redeemer)

Get the redeemer from a redeemer hash (if available)

StakeValidatorFromHash :: StakeValidatorHash -> ChainIndexQueryEffect (Maybe (Versioned StakeValidator))

Get the stake validator from a stake validator hash (if available)

UnspentTxOutFromRef :: TxOutRef -> ChainIndexQueryEffect (Maybe DecoratedTxOut)

Get the TxOut from a TxOutRef (if available)

TxOutFromRef :: TxOutRef -> ChainIndexQueryEffect (Maybe DecoratedTxOut)

Get the TxOut from a TxOutRef (if available)

TxFromTxId :: TxId -> ChainIndexQueryEffect (Maybe ChainIndexTx)

Get the transaction for a tx ID

UtxoSetMembership :: TxOutRef -> ChainIndexQueryEffect IsUtxoResponse

Whether a tx output is part of the UTXO set

UtxoSetAtAddress :: PageQuery TxOutRef -> Credential -> ChainIndexQueryEffect UtxosResponse

Unspent outputs located at addresses with the given credential.

UnspentTxOutSetAtAddress :: PageQuery TxOutRef -> Credential -> ChainIndexQueryEffect (QueryResponse [(TxOutRef, DecoratedTxOut)])

Get the unspent txouts located at an address This is to avoid multiple queries from chain-index when using utxosAt

DatumsAtAddress :: PageQuery TxOutRef -> Credential -> ChainIndexQueryEffect (QueryResponse [Datum])

get the datums located at addresses with the given credential.

UtxoSetWithCurrency :: PageQuery TxOutRef -> AssetClass -> ChainIndexQueryEffect UtxosResponse

Unspent outputs containing a specific currency (AssetClass).

Note that requesting unspent outputs containing Ada should not return anything, as this request will always return all unspent outputs.

TxsFromTxIds :: [TxId] -> ChainIndexQueryEffect [ChainIndexTx]

Get the transactions for a list of tx IDs.

TxoSetAtAddress :: PageQuery TxOutRef -> Credential -> ChainIndexQueryEffect TxosResponse

Outputs located at addresses with the given credential.

GetTip :: ChainIndexQueryEffect Tip

Get the tip of the chain index

data ChainIndexControlEffect r where Source #

Constructors

AppendBlocks :: [ChainSyncBlock] -> ChainIndexControlEffect ()

Add new blocks to the chain index.

Rollback :: Point -> ChainIndexControlEffect ()

Roll back to a previous state (previous tip)

ResumeSync :: Point -> ChainIndexControlEffect ()

Resume syncing from a certain point

CollectGarbage :: ChainIndexControlEffect ()

Delete all data that is not covered by current UTxOs.

GetDiagnostics :: ChainIndexControlEffect Diagnostics 

getTip :: forall effs. Member ChainIndexQueryEffect effs => Eff effs Tip Source #

rollback :: forall effs. Member ChainIndexControlEffect effs => Point -> Eff effs () Source #

resumeSync :: forall effs. Member ChainIndexControlEffect effs => Point -> Eff effs () Source #

collectGarbage :: forall effs. Member ChainIndexControlEffect effs => Eff effs () Source #

data InsertUtxoPosition Source #

Outcome of inserting a UtxoState into the utxo index

Constructors

InsertAtEnd

The utxo state was added to the end. Returns the new index

InsertBeforeEnd

The utxo state was added somewhere before the end. Returns the new index and the tip

Instances

Instances details
Eq InsertUtxoPosition Source # 
Instance details

Defined in Plutus.ChainIndex.ChainIndexLog

Ord InsertUtxoPosition Source # 
Instance details

Defined in Plutus.ChainIndex.ChainIndexLog

Show InsertUtxoPosition Source # 
Instance details

Defined in Plutus.ChainIndex.ChainIndexLog

Generic InsertUtxoPosition Source # 
Instance details

Defined in Plutus.ChainIndex.ChainIndexLog

Associated Types

type Rep InsertUtxoPosition :: Type -> Type Source #

ToJSON InsertUtxoPosition Source # 
Instance details

Defined in Plutus.ChainIndex.ChainIndexLog

FromJSON InsertUtxoPosition Source # 
Instance details

Defined in Plutus.ChainIndex.ChainIndexLog

Pretty InsertUtxoPosition Source # 
Instance details

Defined in Plutus.ChainIndex.ChainIndexLog

type Rep InsertUtxoPosition Source # 
Instance details

Defined in Plutus.ChainIndex.ChainIndexLog

type Rep InsertUtxoPosition = D1 ('MetaData "InsertUtxoPosition" "Plutus.ChainIndex.ChainIndexLog" "plutus-chain-index-core-1.1.0.0-K7whjMLv5AnJVt0avXcbFn" 'False) (C1 ('MetaCons "InsertAtEnd" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "InsertBeforeEnd" 'PrefixI 'False) (U1 :: Type -> Type))

data ChainIndexLog Source #

Instances

Instances details
Eq ChainIndexLog Source # 
Instance details

Defined in Plutus.ChainIndex.ChainIndexLog

Show ChainIndexLog Source # 
Instance details

Defined in Plutus.ChainIndex.ChainIndexLog

Generic ChainIndexLog Source # 
Instance details

Defined in Plutus.ChainIndex.ChainIndexLog

Associated Types

type Rep ChainIndexLog :: Type -> Type Source #

ToJSON ChainIndexLog Source # 
Instance details

Defined in Plutus.ChainIndex.ChainIndexLog

FromJSON ChainIndexLog Source # 
Instance details

Defined in Plutus.ChainIndex.ChainIndexLog

Pretty ChainIndexLog Source # 
Instance details

Defined in Plutus.ChainIndex.ChainIndexLog

ToObject ChainIndexLog Source # 
Instance details

Defined in Plutus.ChainIndex.ChainIndexLog

Methods

toObject :: TracingVerbosity -> ChainIndexLog -> Object

textTransformer :: ChainIndexLog -> Object -> Text

type Rep ChainIndexLog Source # 
Instance details

Defined in Plutus.ChainIndex.ChainIndexLog

type Rep ChainIndexLog = D1 ('MetaData "ChainIndexLog" "Plutus.ChainIndex.ChainIndexLog" "plutus-chain-index-core-1.1.0.0-K7whjMLv5AnJVt0avXcbFn" 'False) (((C1 ('MetaCons "InsertionSuccess" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Tip) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 InsertUtxoPosition)) :+: C1 ('MetaCons "ConversionFailed" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FromCardanoError))) :+: (C1 ('MetaCons "RollbackSuccess" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Tip)) :+: C1 ('MetaCons "Err" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ChainIndexError)))) :+: ((C1 ('MetaCons "TxNotFound" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TxId)) :+: C1 ('MetaCons "TxOutNotFound" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TxOutRef))) :+: (C1 ('MetaCons "TipIsGenesis" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "NoDatumScriptAddr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ChainIndexTxOut)) :+: C1 ('MetaCons "BeamLogItem" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BeamLog))))))

data UtxoState a Source #

UTXO / ledger state, kept in memory. We are only interested in the UTXO set, everything else is stored on disk. This is OK because we don't need to validate transactions when they come in.

Constructors

UtxoState 

Fields

Instances

Instances details
Eq a => Eq (UtxoState a) Source # 
Instance details

Defined in Plutus.ChainIndex.UtxoState

Eq a => Ord (UtxoState a) Source # 
Instance details

Defined in Plutus.ChainIndex.UtxoState

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

Defined in Plutus.ChainIndex.UtxoState

Generic (UtxoState a) Source # 
Instance details

Defined in Plutus.ChainIndex.UtxoState

Associated Types

type Rep (UtxoState a) :: Type -> Type Source #

Methods

from :: UtxoState a -> Rep (UtxoState a) x Source #

to :: Rep (UtxoState a) x -> UtxoState a Source #

Semigroup a => Semigroup (UtxoState a) Source # 
Instance details

Defined in Plutus.ChainIndex.UtxoState

Monoid a => Monoid (UtxoState a) Source # 
Instance details

Defined in Plutus.ChainIndex.UtxoState

ToJSON a => ToJSON (UtxoState a) Source # 
Instance details

Defined in Plutus.ChainIndex.UtxoState

FromJSON a => FromJSON (UtxoState a) Source # 
Instance details

Defined in Plutus.ChainIndex.UtxoState

Monoid a => Measured (BlockCount, UtxoState a) (UtxoState a) Source # 
Instance details

Defined in Plutus.ChainIndex.UtxoState

type Rep (UtxoState a) Source # 
Instance details

Defined in Plutus.ChainIndex.UtxoState

type Rep (UtxoState a) = D1 ('MetaData "UtxoState" "Plutus.ChainIndex.UtxoState" "plutus-chain-index-core-1.1.0.0-K7whjMLv5AnJVt0avXcbFn" 'False) (C1 ('MetaCons "UtxoState" 'PrefixI 'True) (S1 ('MetaSel ('Just "_usTxUtxoData") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Just "_usTip") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Tip)))

data InsertUtxoSuccess a Source #

Instances

Instances details
Pretty (InsertUtxoSuccess a) Source # 
Instance details

Defined in Plutus.ChainIndex.UtxoState

usTip :: forall a. Lens' (UtxoState a) Tip Source #

usTxUtxoData :: forall a a. Lens (UtxoState a) (UtxoState a) a a Source #

insert :: (Monoid a, Eq a) => UtxoState a -> UtxoIndex a -> Either InsertUtxoFailed (InsertUtxoSuccess a) Source #

Insert a UtxoState into the index

rollbackWith Source #

Arguments

:: Monoid a 
=> (UtxoIndex a -> UtxoIndex a -> UtxoIndex a)

Calculate the new index given the index before and the index after the rollback point.

-> Point 
-> UtxoIndex a 
-> Either RollbackFailed (RollbackResult a) 

Perform a rollback on the utxo index, with a callback to calculate the new index.

reduceBlockCount :: Monoid a => Depth -> UtxoIndex a -> ReduceBlockCountResult a Source #

Reduce the number of UtxoStates. The given number is the minimum, the index is reduced when it larger than twice that size. The new index is prefixed with one UtxoState that contains the combined state of the removed UtxoStates.

pointLessThanTip :: Point -> Tip -> Bool Source #

Is the given point earlier than the provided tip. Yes, if the point is the genersis point, no if the tip is the genesis point, otherwise, just compare the slots.

initialStatus :: OnChainTx -> TxStatus Source #

The TxStatus of a transaction right after it was added to the chain

increaseDepth :: TxStatus -> TxStatus Source #

Increase the depth of a tentatively confirmed transaction

chainConstant :: Depth Source #

The depth (in blocks) after which a transaction cannot be rolled back anymore

dropOlder :: Monoid a => BlockNumber -> UtxoIndex a -> UtxoIndex a Source #

Drop everything older than BlockNumber in the index.

transactionStatus :: BlockNumber -> TxIdState -> TxId -> Either TxStatusFailure TxStatus Source #

Given the current block, compute the status for the given transaction by checking to see if it has been deleted.

transactionOutputStatus Source #

Arguments

:: BlockNumber

Current block number for inspecting the state of the transaction output

-> TxIdState

Information on the state of a transaction. Needed for determining its status.

-> TxOutBalance

Balance of spent and unspent transaction outputs.

-> TxOutRef

Target transaction output for inspecting its state.

-> Either TxStatusFailure TxOutStatus 

Given the current block, compute the status for the given transaction output by getting the state of the transaction that produced it and checking if the output is spent or unspent.