{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
{-# options_ghc -Wno-missing-signatures #-}
module Plutus.ChainIndex.DbSchema where
import Codec.Serialise (Serialise, deserialiseOrFail, serialise)
import Data.ByteString (ByteString)
import Data.ByteString qualified as BS
import Data.ByteString.Lazy qualified as BSL
import Data.Coerce (coerce)
import Data.Either (fromRight)
import Data.Kind (Constraint)
import Data.Semigroup.Generic (GenericSemigroupMonoid (..))
import Data.Word (Word64)
import Database.Beam (Beamable, Columnar, Database, DatabaseSettings, FromBackendRow, Generic, Identity, Table (..),
TableEntity, dbModification, withDbModification)
import Database.Beam.Migrate (CheckedDatabaseSettings, defaultMigratableDbSettings, renameCheckedEntity,
unCheckDatabase)
import Database.Beam.Sqlite (Sqlite)
import Ledger (BlockId (..), DecoratedTxOut (..), Slot, Versioned)
import Plutus.ChainIndex.Tx (ChainIndexTx)
import Plutus.ChainIndex.Tx qualified as CI
import Plutus.ChainIndex.Types (BlockNumber (..), Tip (..))
import Plutus.V1.Ledger.Api (Credential, Datum, DatumHash (..), MintingPolicy, MintingPolicyHash (..), Redeemer,
RedeemerHash (..), Script, StakeValidator, StakeValidatorHash (..), TxId (..),
TxOutRef (..), Validator, ValidatorHash (..))
import Plutus.V1.Ledger.Scripts (ScriptHash (..))
import Plutus.V1.Ledger.Value (AssetClass)
import PlutusTx.Builtins qualified as PlutusTx
import PlutusTx.Builtins.Internal (BuiltinByteString (..), emptyByteString)
data DatumRowT f = DatumRow
{ DatumRowT f -> Columnar f ByteString
_datumRowHash :: Columnar f ByteString
, DatumRowT f -> Columnar f ByteString
_datumRowDatum :: Columnar f ByteString
} deriving ((forall x. DatumRowT f -> Rep (DatumRowT f) x)
-> (forall x. Rep (DatumRowT f) x -> DatumRowT f)
-> Generic (DatumRowT f)
forall x. Rep (DatumRowT f) x -> DatumRowT f
forall x. DatumRowT f -> Rep (DatumRowT f) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (f :: * -> *) x. Rep (DatumRowT f) x -> DatumRowT f
forall (f :: * -> *) x. DatumRowT f -> Rep (DatumRowT f) x
$cto :: forall (f :: * -> *) x. Rep (DatumRowT f) x -> DatumRowT f
$cfrom :: forall (f :: * -> *) x. DatumRowT f -> Rep (DatumRowT f) x
Generic, TableSkeleton DatumRowT
(forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> DatumRowT f -> DatumRowT g -> m (DatumRowT h))
-> TableSkeleton DatumRowT -> Beamable DatumRowT
forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> DatumRowT f -> DatumRowT g -> m (DatumRowT h)
forall (table :: (* -> *) -> *).
(forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> table f -> table g -> m (table h))
-> TableSkeleton table -> Beamable table
tblSkeleton :: TableSkeleton DatumRowT
$ctblSkeleton :: TableSkeleton DatumRowT
zipBeamFieldsM :: (forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> DatumRowT f -> DatumRowT g -> m (DatumRowT h)
$czipBeamFieldsM :: forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> DatumRowT f -> DatumRowT g -> m (DatumRowT h)
Beamable)
type DatumRow = DatumRowT Identity
instance Table DatumRowT where
data PrimaryKey DatumRowT f = DatumRowId (Columnar f ByteString) deriving ((forall x.
PrimaryKey DatumRowT f -> Rep (PrimaryKey DatumRowT f) x)
-> (forall x.
Rep (PrimaryKey DatumRowT f) x -> PrimaryKey DatumRowT f)
-> Generic (PrimaryKey DatumRowT f)
forall x. Rep (PrimaryKey DatumRowT f) x -> PrimaryKey DatumRowT f
forall x. PrimaryKey DatumRowT f -> Rep (PrimaryKey DatumRowT f) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (f :: * -> *) x.
Rep (PrimaryKey DatumRowT f) x -> PrimaryKey DatumRowT f
forall (f :: * -> *) x.
PrimaryKey DatumRowT f -> Rep (PrimaryKey DatumRowT f) x
$cto :: forall (f :: * -> *) x.
Rep (PrimaryKey DatumRowT f) x -> PrimaryKey DatumRowT f
$cfrom :: forall (f :: * -> *) x.
PrimaryKey DatumRowT f -> Rep (PrimaryKey DatumRowT f) x
Generic, TableSkeleton (PrimaryKey DatumRowT)
(forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> PrimaryKey DatumRowT f
-> PrimaryKey DatumRowT g
-> m (PrimaryKey DatumRowT h))
-> TableSkeleton (PrimaryKey DatumRowT)
-> Beamable (PrimaryKey DatumRowT)
forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> PrimaryKey DatumRowT f
-> PrimaryKey DatumRowT g
-> m (PrimaryKey DatumRowT h)
forall (table :: (* -> *) -> *).
(forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> table f -> table g -> m (table h))
-> TableSkeleton table -> Beamable table
tblSkeleton :: TableSkeleton (PrimaryKey DatumRowT)
$ctblSkeleton :: TableSkeleton (PrimaryKey DatumRowT)
zipBeamFieldsM :: (forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> PrimaryKey DatumRowT f
-> PrimaryKey DatumRowT g
-> m (PrimaryKey DatumRowT h)
$czipBeamFieldsM :: forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> PrimaryKey DatumRowT f
-> PrimaryKey DatumRowT g
-> m (PrimaryKey DatumRowT h)
Beamable)
primaryKey :: DatumRowT column -> PrimaryKey DatumRowT column
primaryKey = Columnar column ByteString -> PrimaryKey DatumRowT column
forall (f :: * -> *).
Columnar f ByteString -> PrimaryKey DatumRowT f
DatumRowId (Columnar column ByteString -> PrimaryKey DatumRowT column)
-> (DatumRowT column -> Columnar column ByteString)
-> DatumRowT column
-> PrimaryKey DatumRowT column
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DatumRowT column -> Columnar column ByteString
forall (f :: * -> *). DatumRowT f -> Columnar f ByteString
_datumRowHash
data ScriptRowT f = ScriptRow
{ ScriptRowT f -> Columnar f ByteString
_scriptRowHash :: Columnar f ByteString
, ScriptRowT f -> Columnar f ByteString
_scriptRowScript :: Columnar f ByteString
} deriving ((forall x. ScriptRowT f -> Rep (ScriptRowT f) x)
-> (forall x. Rep (ScriptRowT f) x -> ScriptRowT f)
-> Generic (ScriptRowT f)
forall x. Rep (ScriptRowT f) x -> ScriptRowT f
forall x. ScriptRowT f -> Rep (ScriptRowT f) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (f :: * -> *) x. Rep (ScriptRowT f) x -> ScriptRowT f
forall (f :: * -> *) x. ScriptRowT f -> Rep (ScriptRowT f) x
$cto :: forall (f :: * -> *) x. Rep (ScriptRowT f) x -> ScriptRowT f
$cfrom :: forall (f :: * -> *) x. ScriptRowT f -> Rep (ScriptRowT f) x
Generic, TableSkeleton ScriptRowT
(forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> ScriptRowT f -> ScriptRowT g -> m (ScriptRowT h))
-> TableSkeleton ScriptRowT -> Beamable ScriptRowT
forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> ScriptRowT f -> ScriptRowT g -> m (ScriptRowT h)
forall (table :: (* -> *) -> *).
(forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> table f -> table g -> m (table h))
-> TableSkeleton table -> Beamable table
tblSkeleton :: TableSkeleton ScriptRowT
$ctblSkeleton :: TableSkeleton ScriptRowT
zipBeamFieldsM :: (forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> ScriptRowT f -> ScriptRowT g -> m (ScriptRowT h)
$czipBeamFieldsM :: forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> ScriptRowT f -> ScriptRowT g -> m (ScriptRowT h)
Beamable)
type ScriptRow = ScriptRowT Identity
instance Table ScriptRowT where
data PrimaryKey ScriptRowT f = ScriptRowId (Columnar f ByteString) deriving ((forall x.
PrimaryKey ScriptRowT f -> Rep (PrimaryKey ScriptRowT f) x)
-> (forall x.
Rep (PrimaryKey ScriptRowT f) x -> PrimaryKey ScriptRowT f)
-> Generic (PrimaryKey ScriptRowT f)
forall x.
Rep (PrimaryKey ScriptRowT f) x -> PrimaryKey ScriptRowT f
forall x.
PrimaryKey ScriptRowT f -> Rep (PrimaryKey ScriptRowT f) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (f :: * -> *) x.
Rep (PrimaryKey ScriptRowT f) x -> PrimaryKey ScriptRowT f
forall (f :: * -> *) x.
PrimaryKey ScriptRowT f -> Rep (PrimaryKey ScriptRowT f) x
$cto :: forall (f :: * -> *) x.
Rep (PrimaryKey ScriptRowT f) x -> PrimaryKey ScriptRowT f
$cfrom :: forall (f :: * -> *) x.
PrimaryKey ScriptRowT f -> Rep (PrimaryKey ScriptRowT f) x
Generic, TableSkeleton (PrimaryKey ScriptRowT)
(forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> PrimaryKey ScriptRowT f
-> PrimaryKey ScriptRowT g
-> m (PrimaryKey ScriptRowT h))
-> TableSkeleton (PrimaryKey ScriptRowT)
-> Beamable (PrimaryKey ScriptRowT)
forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> PrimaryKey ScriptRowT f
-> PrimaryKey ScriptRowT g
-> m (PrimaryKey ScriptRowT h)
forall (table :: (* -> *) -> *).
(forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> table f -> table g -> m (table h))
-> TableSkeleton table -> Beamable table
tblSkeleton :: TableSkeleton (PrimaryKey ScriptRowT)
$ctblSkeleton :: TableSkeleton (PrimaryKey ScriptRowT)
zipBeamFieldsM :: (forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> PrimaryKey ScriptRowT f
-> PrimaryKey ScriptRowT g
-> m (PrimaryKey ScriptRowT h)
$czipBeamFieldsM :: forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> PrimaryKey ScriptRowT f
-> PrimaryKey ScriptRowT g
-> m (PrimaryKey ScriptRowT h)
Beamable)
primaryKey :: ScriptRowT column -> PrimaryKey ScriptRowT column
primaryKey = Columnar column ByteString -> PrimaryKey ScriptRowT column
forall (f :: * -> *).
Columnar f ByteString -> PrimaryKey ScriptRowT f
ScriptRowId (Columnar column ByteString -> PrimaryKey ScriptRowT column)
-> (ScriptRowT column -> Columnar column ByteString)
-> ScriptRowT column
-> PrimaryKey ScriptRowT column
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ScriptRowT column -> Columnar column ByteString
forall (f :: * -> *). ScriptRowT f -> Columnar f ByteString
_scriptRowHash
data RedeemerRowT f = RedeemerRow
{ RedeemerRowT f -> Columnar f ByteString
_redeemerRowHash :: Columnar f ByteString
, RedeemerRowT f -> Columnar f ByteString
_redeemerRowRedeemer :: Columnar f ByteString
} deriving ((forall x. RedeemerRowT f -> Rep (RedeemerRowT f) x)
-> (forall x. Rep (RedeemerRowT f) x -> RedeemerRowT f)
-> Generic (RedeemerRowT f)
forall x. Rep (RedeemerRowT f) x -> RedeemerRowT f
forall x. RedeemerRowT f -> Rep (RedeemerRowT f) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (f :: * -> *) x. Rep (RedeemerRowT f) x -> RedeemerRowT f
forall (f :: * -> *) x. RedeemerRowT f -> Rep (RedeemerRowT f) x
$cto :: forall (f :: * -> *) x. Rep (RedeemerRowT f) x -> RedeemerRowT f
$cfrom :: forall (f :: * -> *) x. RedeemerRowT f -> Rep (RedeemerRowT f) x
Generic, TableSkeleton RedeemerRowT
(forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> RedeemerRowT f -> RedeemerRowT g -> m (RedeemerRowT h))
-> TableSkeleton RedeemerRowT -> Beamable RedeemerRowT
forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> RedeemerRowT f -> RedeemerRowT g -> m (RedeemerRowT h)
forall (table :: (* -> *) -> *).
(forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> table f -> table g -> m (table h))
-> TableSkeleton table -> Beamable table
tblSkeleton :: TableSkeleton RedeemerRowT
$ctblSkeleton :: TableSkeleton RedeemerRowT
zipBeamFieldsM :: (forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> RedeemerRowT f -> RedeemerRowT g -> m (RedeemerRowT h)
$czipBeamFieldsM :: forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> RedeemerRowT f -> RedeemerRowT g -> m (RedeemerRowT h)
Beamable)
type RedeemerRow = RedeemerRowT Identity
instance Table RedeemerRowT where
data PrimaryKey RedeemerRowT f = RedeemerRowId (Columnar f ByteString) deriving ((forall x.
PrimaryKey RedeemerRowT f -> Rep (PrimaryKey RedeemerRowT f) x)
-> (forall x.
Rep (PrimaryKey RedeemerRowT f) x -> PrimaryKey RedeemerRowT f)
-> Generic (PrimaryKey RedeemerRowT f)
forall x.
Rep (PrimaryKey RedeemerRowT f) x -> PrimaryKey RedeemerRowT f
forall x.
PrimaryKey RedeemerRowT f -> Rep (PrimaryKey RedeemerRowT f) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (f :: * -> *) x.
Rep (PrimaryKey RedeemerRowT f) x -> PrimaryKey RedeemerRowT f
forall (f :: * -> *) x.
PrimaryKey RedeemerRowT f -> Rep (PrimaryKey RedeemerRowT f) x
$cto :: forall (f :: * -> *) x.
Rep (PrimaryKey RedeemerRowT f) x -> PrimaryKey RedeemerRowT f
$cfrom :: forall (f :: * -> *) x.
PrimaryKey RedeemerRowT f -> Rep (PrimaryKey RedeemerRowT f) x
Generic, TableSkeleton (PrimaryKey RedeemerRowT)
(forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> PrimaryKey RedeemerRowT f
-> PrimaryKey RedeemerRowT g
-> m (PrimaryKey RedeemerRowT h))
-> TableSkeleton (PrimaryKey RedeemerRowT)
-> Beamable (PrimaryKey RedeemerRowT)
forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> PrimaryKey RedeemerRowT f
-> PrimaryKey RedeemerRowT g
-> m (PrimaryKey RedeemerRowT h)
forall (table :: (* -> *) -> *).
(forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> table f -> table g -> m (table h))
-> TableSkeleton table -> Beamable table
tblSkeleton :: TableSkeleton (PrimaryKey RedeemerRowT)
$ctblSkeleton :: TableSkeleton (PrimaryKey RedeemerRowT)
zipBeamFieldsM :: (forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> PrimaryKey RedeemerRowT f
-> PrimaryKey RedeemerRowT g
-> m (PrimaryKey RedeemerRowT h)
$czipBeamFieldsM :: forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> PrimaryKey RedeemerRowT f
-> PrimaryKey RedeemerRowT g
-> m (PrimaryKey RedeemerRowT h)
Beamable)
primaryKey :: RedeemerRowT column -> PrimaryKey RedeemerRowT column
primaryKey = Columnar column ByteString -> PrimaryKey RedeemerRowT column
forall (f :: * -> *).
Columnar f ByteString -> PrimaryKey RedeemerRowT f
RedeemerRowId (Columnar column ByteString -> PrimaryKey RedeemerRowT column)
-> (RedeemerRowT column -> Columnar column ByteString)
-> RedeemerRowT column
-> PrimaryKey RedeemerRowT column
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RedeemerRowT column -> Columnar column ByteString
forall (f :: * -> *). RedeemerRowT f -> Columnar f ByteString
_redeemerRowHash
data TxRowT f = TxRow
{ TxRowT f -> Columnar f ByteString
_txRowTxId :: Columnar f ByteString
, TxRowT f -> Columnar f ByteString
_txRowTx :: Columnar f ByteString
} deriving ((forall x. TxRowT f -> Rep (TxRowT f) x)
-> (forall x. Rep (TxRowT f) x -> TxRowT f) -> Generic (TxRowT f)
forall x. Rep (TxRowT f) x -> TxRowT f
forall x. TxRowT f -> Rep (TxRowT f) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (f :: * -> *) x. Rep (TxRowT f) x -> TxRowT f
forall (f :: * -> *) x. TxRowT f -> Rep (TxRowT f) x
$cto :: forall (f :: * -> *) x. Rep (TxRowT f) x -> TxRowT f
$cfrom :: forall (f :: * -> *) x. TxRowT f -> Rep (TxRowT f) x
Generic, TableSkeleton TxRowT
(forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> TxRowT f -> TxRowT g -> m (TxRowT h))
-> TableSkeleton TxRowT -> Beamable TxRowT
forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> TxRowT f -> TxRowT g -> m (TxRowT h)
forall (table :: (* -> *) -> *).
(forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> table f -> table g -> m (table h))
-> TableSkeleton table -> Beamable table
tblSkeleton :: TableSkeleton TxRowT
$ctblSkeleton :: TableSkeleton TxRowT
zipBeamFieldsM :: (forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> TxRowT f -> TxRowT g -> m (TxRowT h)
$czipBeamFieldsM :: forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> TxRowT f -> TxRowT g -> m (TxRowT h)
Beamable)
type TxRow = TxRowT Identity
instance Table TxRowT where
data PrimaryKey TxRowT f = TxRowId (Columnar f ByteString) deriving ((forall x. PrimaryKey TxRowT f -> Rep (PrimaryKey TxRowT f) x)
-> (forall x. Rep (PrimaryKey TxRowT f) x -> PrimaryKey TxRowT f)
-> Generic (PrimaryKey TxRowT f)
forall x. Rep (PrimaryKey TxRowT f) x -> PrimaryKey TxRowT f
forall x. PrimaryKey TxRowT f -> Rep (PrimaryKey TxRowT f) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (f :: * -> *) x.
Rep (PrimaryKey TxRowT f) x -> PrimaryKey TxRowT f
forall (f :: * -> *) x.
PrimaryKey TxRowT f -> Rep (PrimaryKey TxRowT f) x
$cto :: forall (f :: * -> *) x.
Rep (PrimaryKey TxRowT f) x -> PrimaryKey TxRowT f
$cfrom :: forall (f :: * -> *) x.
PrimaryKey TxRowT f -> Rep (PrimaryKey TxRowT f) x
Generic, TableSkeleton (PrimaryKey TxRowT)
(forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> PrimaryKey TxRowT f
-> PrimaryKey TxRowT g
-> m (PrimaryKey TxRowT h))
-> TableSkeleton (PrimaryKey TxRowT)
-> Beamable (PrimaryKey TxRowT)
forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> PrimaryKey TxRowT f
-> PrimaryKey TxRowT g
-> m (PrimaryKey TxRowT h)
forall (table :: (* -> *) -> *).
(forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> table f -> table g -> m (table h))
-> TableSkeleton table -> Beamable table
tblSkeleton :: TableSkeleton (PrimaryKey TxRowT)
$ctblSkeleton :: TableSkeleton (PrimaryKey TxRowT)
zipBeamFieldsM :: (forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> PrimaryKey TxRowT f
-> PrimaryKey TxRowT g
-> m (PrimaryKey TxRowT h)
$czipBeamFieldsM :: forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> PrimaryKey TxRowT f
-> PrimaryKey TxRowT g
-> m (PrimaryKey TxRowT h)
Beamable)
primaryKey :: TxRowT column -> PrimaryKey TxRowT column
primaryKey = Columnar column ByteString -> PrimaryKey TxRowT column
forall (f :: * -> *). Columnar f ByteString -> PrimaryKey TxRowT f
TxRowId (Columnar column ByteString -> PrimaryKey TxRowT column)
-> (TxRowT column -> Columnar column ByteString)
-> TxRowT column
-> PrimaryKey TxRowT column
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TxRowT column -> Columnar column ByteString
forall (f :: * -> *). TxRowT f -> Columnar f ByteString
_txRowTxId
data AddressRowT f = AddressRow
{ AddressRowT f -> Columnar f ByteString
_addressRowCred :: Columnar f ByteString
, AddressRowT f -> Columnar f ByteString
_addressRowOutRef :: Columnar f ByteString
, AddressRowT f -> Columnar f ByteString
_addressRowDatumHash :: Columnar f ByteString
} deriving ((forall x. AddressRowT f -> Rep (AddressRowT f) x)
-> (forall x. Rep (AddressRowT f) x -> AddressRowT f)
-> Generic (AddressRowT f)
forall x. Rep (AddressRowT f) x -> AddressRowT f
forall x. AddressRowT f -> Rep (AddressRowT f) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (f :: * -> *) x. Rep (AddressRowT f) x -> AddressRowT f
forall (f :: * -> *) x. AddressRowT f -> Rep (AddressRowT f) x
$cto :: forall (f :: * -> *) x. Rep (AddressRowT f) x -> AddressRowT f
$cfrom :: forall (f :: * -> *) x. AddressRowT f -> Rep (AddressRowT f) x
Generic, TableSkeleton AddressRowT
(forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> AddressRowT f -> AddressRowT g -> m (AddressRowT h))
-> TableSkeleton AddressRowT -> Beamable AddressRowT
forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> AddressRowT f -> AddressRowT g -> m (AddressRowT h)
forall (table :: (* -> *) -> *).
(forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> table f -> table g -> m (table h))
-> TableSkeleton table -> Beamable table
tblSkeleton :: TableSkeleton AddressRowT
$ctblSkeleton :: TableSkeleton AddressRowT
zipBeamFieldsM :: (forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> AddressRowT f -> AddressRowT g -> m (AddressRowT h)
$czipBeamFieldsM :: forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> AddressRowT f -> AddressRowT g -> m (AddressRowT h)
Beamable)
type AddressRow = AddressRowT Identity
instance Table AddressRowT where
data PrimaryKey AddressRowT f = AddressRowId (Columnar f ByteString) (Columnar f ByteString) (Columnar f ByteString) deriving ((forall x.
PrimaryKey AddressRowT f -> Rep (PrimaryKey AddressRowT f) x)
-> (forall x.
Rep (PrimaryKey AddressRowT f) x -> PrimaryKey AddressRowT f)
-> Generic (PrimaryKey AddressRowT f)
forall x.
Rep (PrimaryKey AddressRowT f) x -> PrimaryKey AddressRowT f
forall x.
PrimaryKey AddressRowT f -> Rep (PrimaryKey AddressRowT f) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (f :: * -> *) x.
Rep (PrimaryKey AddressRowT f) x -> PrimaryKey AddressRowT f
forall (f :: * -> *) x.
PrimaryKey AddressRowT f -> Rep (PrimaryKey AddressRowT f) x
$cto :: forall (f :: * -> *) x.
Rep (PrimaryKey AddressRowT f) x -> PrimaryKey AddressRowT f
$cfrom :: forall (f :: * -> *) x.
PrimaryKey AddressRowT f -> Rep (PrimaryKey AddressRowT f) x
Generic, TableSkeleton (PrimaryKey AddressRowT)
(forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> PrimaryKey AddressRowT f
-> PrimaryKey AddressRowT g
-> m (PrimaryKey AddressRowT h))
-> TableSkeleton (PrimaryKey AddressRowT)
-> Beamable (PrimaryKey AddressRowT)
forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> PrimaryKey AddressRowT f
-> PrimaryKey AddressRowT g
-> m (PrimaryKey AddressRowT h)
forall (table :: (* -> *) -> *).
(forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> table f -> table g -> m (table h))
-> TableSkeleton table -> Beamable table
tblSkeleton :: TableSkeleton (PrimaryKey AddressRowT)
$ctblSkeleton :: TableSkeleton (PrimaryKey AddressRowT)
zipBeamFieldsM :: (forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> PrimaryKey AddressRowT f
-> PrimaryKey AddressRowT g
-> m (PrimaryKey AddressRowT h)
$czipBeamFieldsM :: forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> PrimaryKey AddressRowT f
-> PrimaryKey AddressRowT g
-> m (PrimaryKey AddressRowT h)
Beamable)
primaryKey :: AddressRowT column -> PrimaryKey AddressRowT column
primaryKey (AddressRow Columnar column ByteString
c Columnar column ByteString
o Columnar column ByteString
d) = Columnar column ByteString
-> Columnar column ByteString
-> Columnar column ByteString
-> PrimaryKey AddressRowT column
forall (f :: * -> *).
Columnar f ByteString
-> Columnar f ByteString
-> Columnar f ByteString
-> PrimaryKey AddressRowT f
AddressRowId Columnar column ByteString
c Columnar column ByteString
o Columnar column ByteString
d
data AssetClassRowT f = AssetClassRow
{ AssetClassRowT f -> Columnar f ByteString
_assetClassRowAssetClass :: Columnar f ByteString
, AssetClassRowT f -> Columnar f ByteString
_assetClassRowOutRef :: Columnar f ByteString
} deriving ((forall x. AssetClassRowT f -> Rep (AssetClassRowT f) x)
-> (forall x. Rep (AssetClassRowT f) x -> AssetClassRowT f)
-> Generic (AssetClassRowT f)
forall x. Rep (AssetClassRowT f) x -> AssetClassRowT f
forall x. AssetClassRowT f -> Rep (AssetClassRowT f) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (f :: * -> *) x.
Rep (AssetClassRowT f) x -> AssetClassRowT f
forall (f :: * -> *) x.
AssetClassRowT f -> Rep (AssetClassRowT f) x
$cto :: forall (f :: * -> *) x.
Rep (AssetClassRowT f) x -> AssetClassRowT f
$cfrom :: forall (f :: * -> *) x.
AssetClassRowT f -> Rep (AssetClassRowT f) x
Generic, TableSkeleton AssetClassRowT
(forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> AssetClassRowT f -> AssetClassRowT g -> m (AssetClassRowT h))
-> TableSkeleton AssetClassRowT -> Beamable AssetClassRowT
forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> AssetClassRowT f -> AssetClassRowT g -> m (AssetClassRowT h)
forall (table :: (* -> *) -> *).
(forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> table f -> table g -> m (table h))
-> TableSkeleton table -> Beamable table
tblSkeleton :: TableSkeleton AssetClassRowT
$ctblSkeleton :: TableSkeleton AssetClassRowT
zipBeamFieldsM :: (forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> AssetClassRowT f -> AssetClassRowT g -> m (AssetClassRowT h)
$czipBeamFieldsM :: forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> AssetClassRowT f -> AssetClassRowT g -> m (AssetClassRowT h)
Beamable)
type AssetClassRow = AssetClassRowT Identity
instance Table AssetClassRowT where
data PrimaryKey AssetClassRowT f = AssetClassRowId (Columnar f ByteString)
(Columnar f ByteString)
deriving ((forall x.
PrimaryKey AssetClassRowT f -> Rep (PrimaryKey AssetClassRowT f) x)
-> (forall x.
Rep (PrimaryKey AssetClassRowT f) x -> PrimaryKey AssetClassRowT f)
-> Generic (PrimaryKey AssetClassRowT f)
forall x.
Rep (PrimaryKey AssetClassRowT f) x -> PrimaryKey AssetClassRowT f
forall x.
PrimaryKey AssetClassRowT f -> Rep (PrimaryKey AssetClassRowT f) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (f :: * -> *) x.
Rep (PrimaryKey AssetClassRowT f) x -> PrimaryKey AssetClassRowT f
forall (f :: * -> *) x.
PrimaryKey AssetClassRowT f -> Rep (PrimaryKey AssetClassRowT f) x
$cto :: forall (f :: * -> *) x.
Rep (PrimaryKey AssetClassRowT f) x -> PrimaryKey AssetClassRowT f
$cfrom :: forall (f :: * -> *) x.
PrimaryKey AssetClassRowT f -> Rep (PrimaryKey AssetClassRowT f) x
Generic, TableSkeleton (PrimaryKey AssetClassRowT)
(forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> PrimaryKey AssetClassRowT f
-> PrimaryKey AssetClassRowT g
-> m (PrimaryKey AssetClassRowT h))
-> TableSkeleton (PrimaryKey AssetClassRowT)
-> Beamable (PrimaryKey AssetClassRowT)
forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> PrimaryKey AssetClassRowT f
-> PrimaryKey AssetClassRowT g
-> m (PrimaryKey AssetClassRowT h)
forall (table :: (* -> *) -> *).
(forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> table f -> table g -> m (table h))
-> TableSkeleton table -> Beamable table
tblSkeleton :: TableSkeleton (PrimaryKey AssetClassRowT)
$ctblSkeleton :: TableSkeleton (PrimaryKey AssetClassRowT)
zipBeamFieldsM :: (forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> PrimaryKey AssetClassRowT f
-> PrimaryKey AssetClassRowT g
-> m (PrimaryKey AssetClassRowT h)
$czipBeamFieldsM :: forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> PrimaryKey AssetClassRowT f
-> PrimaryKey AssetClassRowT g
-> m (PrimaryKey AssetClassRowT h)
Beamable)
primaryKey :: AssetClassRowT column -> PrimaryKey AssetClassRowT column
primaryKey (AssetClassRow Columnar column ByteString
c Columnar column ByteString
o) = Columnar column ByteString
-> Columnar column ByteString -> PrimaryKey AssetClassRowT column
forall (f :: * -> *).
Columnar f ByteString
-> Columnar f ByteString -> PrimaryKey AssetClassRowT f
AssetClassRowId Columnar column ByteString
c Columnar column ByteString
o
data TipRowT f = TipRow
{ TipRowT f -> Columnar f Word64
_tipRowSlot :: Columnar f Word64
, TipRowT f -> Columnar f ByteString
_tipRowBlockId :: Columnar f ByteString
, TipRowT f -> Columnar f Word64
_tipRowBlockNumber :: Columnar f Word64
} deriving ((forall x. TipRowT f -> Rep (TipRowT f) x)
-> (forall x. Rep (TipRowT f) x -> TipRowT f)
-> Generic (TipRowT f)
forall x. Rep (TipRowT f) x -> TipRowT f
forall x. TipRowT f -> Rep (TipRowT f) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (f :: * -> *) x. Rep (TipRowT f) x -> TipRowT f
forall (f :: * -> *) x. TipRowT f -> Rep (TipRowT f) x
$cto :: forall (f :: * -> *) x. Rep (TipRowT f) x -> TipRowT f
$cfrom :: forall (f :: * -> *) x. TipRowT f -> Rep (TipRowT f) x
Generic, TableSkeleton TipRowT
(forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> TipRowT f -> TipRowT g -> m (TipRowT h))
-> TableSkeleton TipRowT -> Beamable TipRowT
forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> TipRowT f -> TipRowT g -> m (TipRowT h)
forall (table :: (* -> *) -> *).
(forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> table f -> table g -> m (table h))
-> TableSkeleton table -> Beamable table
tblSkeleton :: TableSkeleton TipRowT
$ctblSkeleton :: TableSkeleton TipRowT
zipBeamFieldsM :: (forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> TipRowT f -> TipRowT g -> m (TipRowT h)
$czipBeamFieldsM :: forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> TipRowT f -> TipRowT g -> m (TipRowT h)
Beamable)
type TipRow = TipRowT Identity
instance Table TipRowT where
data PrimaryKey TipRowT f = TipRowId { PrimaryKey TipRowT f -> Columnar f Word64
unTipRowId :: Columnar f Word64 } deriving ((forall x. PrimaryKey TipRowT f -> Rep (PrimaryKey TipRowT f) x)
-> (forall x. Rep (PrimaryKey TipRowT f) x -> PrimaryKey TipRowT f)
-> Generic (PrimaryKey TipRowT f)
forall x. Rep (PrimaryKey TipRowT f) x -> PrimaryKey TipRowT f
forall x. PrimaryKey TipRowT f -> Rep (PrimaryKey TipRowT f) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (f :: * -> *) x.
Rep (PrimaryKey TipRowT f) x -> PrimaryKey TipRowT f
forall (f :: * -> *) x.
PrimaryKey TipRowT f -> Rep (PrimaryKey TipRowT f) x
$cto :: forall (f :: * -> *) x.
Rep (PrimaryKey TipRowT f) x -> PrimaryKey TipRowT f
$cfrom :: forall (f :: * -> *) x.
PrimaryKey TipRowT f -> Rep (PrimaryKey TipRowT f) x
Generic, TableSkeleton (PrimaryKey TipRowT)
(forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> PrimaryKey TipRowT f
-> PrimaryKey TipRowT g
-> m (PrimaryKey TipRowT h))
-> TableSkeleton (PrimaryKey TipRowT)
-> Beamable (PrimaryKey TipRowT)
forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> PrimaryKey TipRowT f
-> PrimaryKey TipRowT g
-> m (PrimaryKey TipRowT h)
forall (table :: (* -> *) -> *).
(forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> table f -> table g -> m (table h))
-> TableSkeleton table -> Beamable table
tblSkeleton :: TableSkeleton (PrimaryKey TipRowT)
$ctblSkeleton :: TableSkeleton (PrimaryKey TipRowT)
zipBeamFieldsM :: (forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> PrimaryKey TipRowT f
-> PrimaryKey TipRowT g
-> m (PrimaryKey TipRowT h)
$czipBeamFieldsM :: forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> PrimaryKey TipRowT f
-> PrimaryKey TipRowT g
-> m (PrimaryKey TipRowT h)
Beamable)
primaryKey :: TipRowT column -> PrimaryKey TipRowT column
primaryKey = Columnar column Word64 -> PrimaryKey TipRowT column
forall (f :: * -> *). Columnar f Word64 -> PrimaryKey TipRowT f
TipRowId (Columnar column Word64 -> PrimaryKey TipRowT column)
-> (TipRowT column -> Columnar column Word64)
-> TipRowT column
-> PrimaryKey TipRowT column
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TipRowT column -> Columnar column Word64
forall (f :: * -> *). TipRowT f -> Columnar f Word64
_tipRowSlot
data UnspentOutputRowT f = UnspentOutputRow
{ UnspentOutputRowT f -> PrimaryKey TipRowT f
_unspentOutputRowTip :: PrimaryKey TipRowT f
, UnspentOutputRowT f -> Columnar f ByteString
_unspentOutputRowOutRef :: Columnar f ByteString
} deriving ((forall x. UnspentOutputRowT f -> Rep (UnspentOutputRowT f) x)
-> (forall x. Rep (UnspentOutputRowT f) x -> UnspentOutputRowT f)
-> Generic (UnspentOutputRowT f)
forall x. Rep (UnspentOutputRowT f) x -> UnspentOutputRowT f
forall x. UnspentOutputRowT f -> Rep (UnspentOutputRowT f) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (f :: * -> *) x.
Rep (UnspentOutputRowT f) x -> UnspentOutputRowT f
forall (f :: * -> *) x.
UnspentOutputRowT f -> Rep (UnspentOutputRowT f) x
$cto :: forall (f :: * -> *) x.
Rep (UnspentOutputRowT f) x -> UnspentOutputRowT f
$cfrom :: forall (f :: * -> *) x.
UnspentOutputRowT f -> Rep (UnspentOutputRowT f) x
Generic, TableSkeleton UnspentOutputRowT
(forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> UnspentOutputRowT f
-> UnspentOutputRowT g
-> m (UnspentOutputRowT h))
-> TableSkeleton UnspentOutputRowT -> Beamable UnspentOutputRowT
forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> UnspentOutputRowT f
-> UnspentOutputRowT g
-> m (UnspentOutputRowT h)
forall (table :: (* -> *) -> *).
(forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> table f -> table g -> m (table h))
-> TableSkeleton table -> Beamable table
tblSkeleton :: TableSkeleton UnspentOutputRowT
$ctblSkeleton :: TableSkeleton UnspentOutputRowT
zipBeamFieldsM :: (forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> UnspentOutputRowT f
-> UnspentOutputRowT g
-> m (UnspentOutputRowT h)
$czipBeamFieldsM :: forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> UnspentOutputRowT f
-> UnspentOutputRowT g
-> m (UnspentOutputRowT h)
Beamable)
type UnspentOutputRow = UnspentOutputRowT Identity
instance Table UnspentOutputRowT where
data PrimaryKey UnspentOutputRowT f = UnspentOutputRowId (PrimaryKey TipRowT f) (Columnar f ByteString) deriving ((forall x.
PrimaryKey UnspentOutputRowT f
-> Rep (PrimaryKey UnspentOutputRowT f) x)
-> (forall x.
Rep (PrimaryKey UnspentOutputRowT f) x
-> PrimaryKey UnspentOutputRowT f)
-> Generic (PrimaryKey UnspentOutputRowT f)
forall x.
Rep (PrimaryKey UnspentOutputRowT f) x
-> PrimaryKey UnspentOutputRowT f
forall x.
PrimaryKey UnspentOutputRowT f
-> Rep (PrimaryKey UnspentOutputRowT f) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (f :: * -> *) x.
Rep (PrimaryKey UnspentOutputRowT f) x
-> PrimaryKey UnspentOutputRowT f
forall (f :: * -> *) x.
PrimaryKey UnspentOutputRowT f
-> Rep (PrimaryKey UnspentOutputRowT f) x
$cto :: forall (f :: * -> *) x.
Rep (PrimaryKey UnspentOutputRowT f) x
-> PrimaryKey UnspentOutputRowT f
$cfrom :: forall (f :: * -> *) x.
PrimaryKey UnspentOutputRowT f
-> Rep (PrimaryKey UnspentOutputRowT f) x
Generic, TableSkeleton (PrimaryKey UnspentOutputRowT)
(forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> PrimaryKey UnspentOutputRowT f
-> PrimaryKey UnspentOutputRowT g
-> m (PrimaryKey UnspentOutputRowT h))
-> TableSkeleton (PrimaryKey UnspentOutputRowT)
-> Beamable (PrimaryKey UnspentOutputRowT)
forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> PrimaryKey UnspentOutputRowT f
-> PrimaryKey UnspentOutputRowT g
-> m (PrimaryKey UnspentOutputRowT h)
forall (table :: (* -> *) -> *).
(forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> table f -> table g -> m (table h))
-> TableSkeleton table -> Beamable table
tblSkeleton :: TableSkeleton (PrimaryKey UnspentOutputRowT)
$ctblSkeleton :: TableSkeleton (PrimaryKey UnspentOutputRowT)
zipBeamFieldsM :: (forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> PrimaryKey UnspentOutputRowT f
-> PrimaryKey UnspentOutputRowT g
-> m (PrimaryKey UnspentOutputRowT h)
$czipBeamFieldsM :: forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> PrimaryKey UnspentOutputRowT f
-> PrimaryKey UnspentOutputRowT g
-> m (PrimaryKey UnspentOutputRowT h)
Beamable)
primaryKey :: UnspentOutputRowT column -> PrimaryKey UnspentOutputRowT column
primaryKey (UnspentOutputRow PrimaryKey TipRowT column
t Columnar column ByteString
o) = PrimaryKey TipRowT column
-> Columnar column ByteString
-> PrimaryKey UnspentOutputRowT column
forall (f :: * -> *).
PrimaryKey TipRowT f
-> Columnar f ByteString -> PrimaryKey UnspentOutputRowT f
UnspentOutputRowId PrimaryKey TipRowT column
t Columnar column ByteString
o
data UnmatchedInputRowT f = UnmatchedInputRow
{ UnmatchedInputRowT f -> PrimaryKey TipRowT f
_unmatchedInputRowTip :: PrimaryKey TipRowT f
, UnmatchedInputRowT f -> Columnar f ByteString
_unmatchedInputRowOutRef :: Columnar f ByteString
} deriving ((forall x. UnmatchedInputRowT f -> Rep (UnmatchedInputRowT f) x)
-> (forall x. Rep (UnmatchedInputRowT f) x -> UnmatchedInputRowT f)
-> Generic (UnmatchedInputRowT f)
forall x. Rep (UnmatchedInputRowT f) x -> UnmatchedInputRowT f
forall x. UnmatchedInputRowT f -> Rep (UnmatchedInputRowT f) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (f :: * -> *) x.
Rep (UnmatchedInputRowT f) x -> UnmatchedInputRowT f
forall (f :: * -> *) x.
UnmatchedInputRowT f -> Rep (UnmatchedInputRowT f) x
$cto :: forall (f :: * -> *) x.
Rep (UnmatchedInputRowT f) x -> UnmatchedInputRowT f
$cfrom :: forall (f :: * -> *) x.
UnmatchedInputRowT f -> Rep (UnmatchedInputRowT f) x
Generic, TableSkeleton UnmatchedInputRowT
(forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> UnmatchedInputRowT f
-> UnmatchedInputRowT g
-> m (UnmatchedInputRowT h))
-> TableSkeleton UnmatchedInputRowT -> Beamable UnmatchedInputRowT
forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> UnmatchedInputRowT f
-> UnmatchedInputRowT g
-> m (UnmatchedInputRowT h)
forall (table :: (* -> *) -> *).
(forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> table f -> table g -> m (table h))
-> TableSkeleton table -> Beamable table
tblSkeleton :: TableSkeleton UnmatchedInputRowT
$ctblSkeleton :: TableSkeleton UnmatchedInputRowT
zipBeamFieldsM :: (forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> UnmatchedInputRowT f
-> UnmatchedInputRowT g
-> m (UnmatchedInputRowT h)
$czipBeamFieldsM :: forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> UnmatchedInputRowT f
-> UnmatchedInputRowT g
-> m (UnmatchedInputRowT h)
Beamable)
type UnmatchedInputRow = UnmatchedInputRowT Identity
instance Table UnmatchedInputRowT where
data PrimaryKey UnmatchedInputRowT f = UnmatchedInputRowId (PrimaryKey TipRowT f) (Columnar f ByteString) deriving ((forall x.
PrimaryKey UnmatchedInputRowT f
-> Rep (PrimaryKey UnmatchedInputRowT f) x)
-> (forall x.
Rep (PrimaryKey UnmatchedInputRowT f) x
-> PrimaryKey UnmatchedInputRowT f)
-> Generic (PrimaryKey UnmatchedInputRowT f)
forall x.
Rep (PrimaryKey UnmatchedInputRowT f) x
-> PrimaryKey UnmatchedInputRowT f
forall x.
PrimaryKey UnmatchedInputRowT f
-> Rep (PrimaryKey UnmatchedInputRowT f) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (f :: * -> *) x.
Rep (PrimaryKey UnmatchedInputRowT f) x
-> PrimaryKey UnmatchedInputRowT f
forall (f :: * -> *) x.
PrimaryKey UnmatchedInputRowT f
-> Rep (PrimaryKey UnmatchedInputRowT f) x
$cto :: forall (f :: * -> *) x.
Rep (PrimaryKey UnmatchedInputRowT f) x
-> PrimaryKey UnmatchedInputRowT f
$cfrom :: forall (f :: * -> *) x.
PrimaryKey UnmatchedInputRowT f
-> Rep (PrimaryKey UnmatchedInputRowT f) x
Generic, TableSkeleton (PrimaryKey UnmatchedInputRowT)
(forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> PrimaryKey UnmatchedInputRowT f
-> PrimaryKey UnmatchedInputRowT g
-> m (PrimaryKey UnmatchedInputRowT h))
-> TableSkeleton (PrimaryKey UnmatchedInputRowT)
-> Beamable (PrimaryKey UnmatchedInputRowT)
forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> PrimaryKey UnmatchedInputRowT f
-> PrimaryKey UnmatchedInputRowT g
-> m (PrimaryKey UnmatchedInputRowT h)
forall (table :: (* -> *) -> *).
(forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> table f -> table g -> m (table h))
-> TableSkeleton table -> Beamable table
tblSkeleton :: TableSkeleton (PrimaryKey UnmatchedInputRowT)
$ctblSkeleton :: TableSkeleton (PrimaryKey UnmatchedInputRowT)
zipBeamFieldsM :: (forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> PrimaryKey UnmatchedInputRowT f
-> PrimaryKey UnmatchedInputRowT g
-> m (PrimaryKey UnmatchedInputRowT h)
$czipBeamFieldsM :: forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> PrimaryKey UnmatchedInputRowT f
-> PrimaryKey UnmatchedInputRowT g
-> m (PrimaryKey UnmatchedInputRowT h)
Beamable)
primaryKey :: UnmatchedInputRowT column -> PrimaryKey UnmatchedInputRowT column
primaryKey (UnmatchedInputRow PrimaryKey TipRowT column
t Columnar column ByteString
o) = PrimaryKey TipRowT column
-> Columnar column ByteString
-> PrimaryKey UnmatchedInputRowT column
forall (f :: * -> *).
PrimaryKey TipRowT f
-> Columnar f ByteString -> PrimaryKey UnmatchedInputRowT f
UnmatchedInputRowId PrimaryKey TipRowT column
t Columnar column ByteString
o
data UtxoRowT f = UtxoRow
{ UtxoRowT f -> Columnar f ByteString
_utxoRowOutRef :: Columnar f ByteString
, UtxoRowT f -> Columnar f ByteString
_utxoRowTxOut :: Columnar f ByteString
} deriving ((forall x. UtxoRowT f -> Rep (UtxoRowT f) x)
-> (forall x. Rep (UtxoRowT f) x -> UtxoRowT f)
-> Generic (UtxoRowT f)
forall x. Rep (UtxoRowT f) x -> UtxoRowT f
forall x. UtxoRowT f -> Rep (UtxoRowT f) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (f :: * -> *) x. Rep (UtxoRowT f) x -> UtxoRowT f
forall (f :: * -> *) x. UtxoRowT f -> Rep (UtxoRowT f) x
$cto :: forall (f :: * -> *) x. Rep (UtxoRowT f) x -> UtxoRowT f
$cfrom :: forall (f :: * -> *) x. UtxoRowT f -> Rep (UtxoRowT f) x
Generic, TableSkeleton UtxoRowT
(forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> UtxoRowT f -> UtxoRowT g -> m (UtxoRowT h))
-> TableSkeleton UtxoRowT -> Beamable UtxoRowT
forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> UtxoRowT f -> UtxoRowT g -> m (UtxoRowT h)
forall (table :: (* -> *) -> *).
(forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> table f -> table g -> m (table h))
-> TableSkeleton table -> Beamable table
tblSkeleton :: TableSkeleton UtxoRowT
$ctblSkeleton :: TableSkeleton UtxoRowT
zipBeamFieldsM :: (forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> UtxoRowT f -> UtxoRowT g -> m (UtxoRowT h)
$czipBeamFieldsM :: forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> UtxoRowT f -> UtxoRowT g -> m (UtxoRowT h)
Beamable)
type UtxoRow = UtxoRowT Identity
instance Table UtxoRowT where
data PrimaryKey UtxoRowT f = UtxoRowOutRef (Columnar f ByteString) deriving ((forall x. PrimaryKey UtxoRowT f -> Rep (PrimaryKey UtxoRowT f) x)
-> (forall x.
Rep (PrimaryKey UtxoRowT f) x -> PrimaryKey UtxoRowT f)
-> Generic (PrimaryKey UtxoRowT f)
forall x. Rep (PrimaryKey UtxoRowT f) x -> PrimaryKey UtxoRowT f
forall x. PrimaryKey UtxoRowT f -> Rep (PrimaryKey UtxoRowT f) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (f :: * -> *) x.
Rep (PrimaryKey UtxoRowT f) x -> PrimaryKey UtxoRowT f
forall (f :: * -> *) x.
PrimaryKey UtxoRowT f -> Rep (PrimaryKey UtxoRowT f) x
$cto :: forall (f :: * -> *) x.
Rep (PrimaryKey UtxoRowT f) x -> PrimaryKey UtxoRowT f
$cfrom :: forall (f :: * -> *) x.
PrimaryKey UtxoRowT f -> Rep (PrimaryKey UtxoRowT f) x
Generic, TableSkeleton (PrimaryKey UtxoRowT)
(forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> PrimaryKey UtxoRowT f
-> PrimaryKey UtxoRowT g
-> m (PrimaryKey UtxoRowT h))
-> TableSkeleton (PrimaryKey UtxoRowT)
-> Beamable (PrimaryKey UtxoRowT)
forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> PrimaryKey UtxoRowT f
-> PrimaryKey UtxoRowT g
-> m (PrimaryKey UtxoRowT h)
forall (table :: (* -> *) -> *).
(forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> table f -> table g -> m (table h))
-> TableSkeleton table -> Beamable table
tblSkeleton :: TableSkeleton (PrimaryKey UtxoRowT)
$ctblSkeleton :: TableSkeleton (PrimaryKey UtxoRowT)
zipBeamFieldsM :: (forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> PrimaryKey UtxoRowT f
-> PrimaryKey UtxoRowT g
-> m (PrimaryKey UtxoRowT h)
$czipBeamFieldsM :: forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> PrimaryKey UtxoRowT f
-> PrimaryKey UtxoRowT g
-> m (PrimaryKey UtxoRowT h)
Beamable)
primaryKey :: UtxoRowT column -> PrimaryKey UtxoRowT column
primaryKey = Columnar column ByteString -> PrimaryKey UtxoRowT column
forall (f :: * -> *).
Columnar f ByteString -> PrimaryKey UtxoRowT f
UtxoRowOutRef (Columnar column ByteString -> PrimaryKey UtxoRowT column)
-> (UtxoRowT column -> Columnar column ByteString)
-> UtxoRowT column
-> PrimaryKey UtxoRowT column
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UtxoRowT column -> Columnar column ByteString
forall (f :: * -> *). UtxoRowT f -> Columnar f ByteString
_utxoRowOutRef
data Db f = Db
{ Db f -> f (TableEntity DatumRowT)
datumRows :: f (TableEntity DatumRowT)
, Db f -> f (TableEntity ScriptRowT)
scriptRows :: f (TableEntity ScriptRowT)
, Db f -> f (TableEntity RedeemerRowT)
redeemerRows :: f (TableEntity RedeemerRowT)
, Db f -> f (TableEntity TxRowT)
txRows :: f (TableEntity TxRowT)
, Db f -> f (TableEntity UtxoRowT)
utxoOutRefRows :: f (TableEntity UtxoRowT)
, Db f -> f (TableEntity AddressRowT)
addressRows :: f (TableEntity AddressRowT)
, Db f -> f (TableEntity AssetClassRowT)
assetClassRows :: f (TableEntity AssetClassRowT)
, Db f -> f (TableEntity TipRowT)
tipRows :: f (TableEntity TipRowT)
, Db f -> f (TableEntity UnspentOutputRowT)
unspentOutputRows :: f (TableEntity UnspentOutputRowT)
, Db f -> f (TableEntity UnmatchedInputRowT)
unmatchedInputRows :: f (TableEntity UnmatchedInputRowT)
} deriving ((forall x. Db f -> Rep (Db f) x)
-> (forall x. Rep (Db f) x -> Db f) -> Generic (Db f)
forall x. Rep (Db f) x -> Db f
forall x. Db f -> Rep (Db f) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (f :: * -> *) x. Rep (Db f) x -> Db f
forall (f :: * -> *) x. Db f -> Rep (Db f) x
$cto :: forall (f :: * -> *) x. Rep (Db f) x -> Db f
$cfrom :: forall (f :: * -> *) x. Db f -> Rep (Db f) x
Generic, Database be)
type AllTables (c :: * -> Constraint) f =
( c (f (TableEntity DatumRowT))
, c (f (TableEntity ScriptRowT))
, c (f (TableEntity RedeemerRowT))
, c (f (TableEntity TxRowT))
, c (f (TableEntity UtxoRowT))
, c (f (TableEntity AddressRowT))
, c (f (TableEntity AssetClassRowT))
, c (f (TableEntity TipRowT))
, c (f (TableEntity UnspentOutputRowT))
, c (f (TableEntity UnmatchedInputRowT))
)
deriving via (GenericSemigroupMonoid (Db f)) instance AllTables Semigroup f => Semigroup (Db f)
deriving via (GenericSemigroupMonoid (Db f)) instance AllTables Monoid f => Monoid (Db f)
db :: DatabaseSettings Sqlite Db
db :: DatabaseSettings Sqlite Db
db = CheckedDatabaseSettings Sqlite Db -> DatabaseSettings Sqlite Db
forall be (db :: (* -> *) -> *).
Database be db =>
CheckedDatabaseSettings be db -> DatabaseSettings be db
unCheckDatabase CheckedDatabaseSettings Sqlite Db
checkedSqliteDb
checkedSqliteDb :: CheckedDatabaseSettings Sqlite Db
checkedSqliteDb :: CheckedDatabaseSettings Sqlite Db
checkedSqliteDb = CheckedDatabaseSettings Sqlite Db
forall be (db :: (* -> *) -> *).
(Generic (CheckedDatabaseSettings be db),
GAutoMigratableDb be (Rep (CheckedDatabaseSettings be db))) =>
CheckedDatabaseSettings be db
defaultMigratableDbSettings
CheckedDatabaseSettings Sqlite Db
-> DatabaseModification (CheckedDatabaseEntity Sqlite Db) Sqlite Db
-> CheckedDatabaseSettings Sqlite Db
forall (db :: (* -> *) -> *) be
(entity :: * -> ((* -> *) -> *) -> * -> *).
Database be db =>
db (entity be db)
-> DatabaseModification (entity be db) be db -> db (entity be db)
`withDbModification` DatabaseModification Any Any Db
forall (f :: * -> *) be (db :: (* -> *) -> *).
Database be db =>
DatabaseModification f be db
dbModification
{ datumRows :: EntityModification
(CheckedDatabaseEntity Sqlite Db) Sqlite (TableEntity DatumRowT)
datumRows = (Text -> Text)
-> EntityModification
(CheckedDatabaseEntity Sqlite Db) Sqlite (TableEntity DatumRowT)
forall be (db :: (* -> *) -> *) ent.
(Text -> Text)
-> EntityModification (CheckedDatabaseEntity be db) be ent
renameCheckedEntity (Text -> Text -> Text
forall a b. a -> b -> a
const Text
"datums")
, scriptRows :: EntityModification
(CheckedDatabaseEntity Sqlite Db) Sqlite (TableEntity ScriptRowT)
scriptRows = (Text -> Text)
-> EntityModification
(CheckedDatabaseEntity Sqlite Db) Sqlite (TableEntity ScriptRowT)
forall be (db :: (* -> *) -> *) ent.
(Text -> Text)
-> EntityModification (CheckedDatabaseEntity be db) be ent
renameCheckedEntity (Text -> Text -> Text
forall a b. a -> b -> a
const Text
"scripts")
, redeemerRows :: EntityModification
(CheckedDatabaseEntity Sqlite Db) Sqlite (TableEntity RedeemerRowT)
redeemerRows = (Text -> Text)
-> EntityModification
(CheckedDatabaseEntity Sqlite Db) Sqlite (TableEntity RedeemerRowT)
forall be (db :: (* -> *) -> *) ent.
(Text -> Text)
-> EntityModification (CheckedDatabaseEntity be db) be ent
renameCheckedEntity (Text -> Text -> Text
forall a b. a -> b -> a
const Text
"redeemers")
, txRows :: EntityModification
(CheckedDatabaseEntity Sqlite Db) Sqlite (TableEntity TxRowT)
txRows = (Text -> Text)
-> EntityModification
(CheckedDatabaseEntity Sqlite Db) Sqlite (TableEntity TxRowT)
forall be (db :: (* -> *) -> *) ent.
(Text -> Text)
-> EntityModification (CheckedDatabaseEntity be db) be ent
renameCheckedEntity (Text -> Text -> Text
forall a b. a -> b -> a
const Text
"txs")
, utxoOutRefRows :: EntityModification
(CheckedDatabaseEntity Sqlite Db) Sqlite (TableEntity UtxoRowT)
utxoOutRefRows = (Text -> Text)
-> EntityModification
(CheckedDatabaseEntity Sqlite Db) Sqlite (TableEntity UtxoRowT)
forall be (db :: (* -> *) -> *) ent.
(Text -> Text)
-> EntityModification (CheckedDatabaseEntity be db) be ent
renameCheckedEntity (Text -> Text -> Text
forall a b. a -> b -> a
const Text
"utxo_out_refs")
, addressRows :: EntityModification
(CheckedDatabaseEntity Sqlite Db) Sqlite (TableEntity AddressRowT)
addressRows = (Text -> Text)
-> EntityModification
(CheckedDatabaseEntity Sqlite Db) Sqlite (TableEntity AddressRowT)
forall be (db :: (* -> *) -> *) ent.
(Text -> Text)
-> EntityModification (CheckedDatabaseEntity be db) be ent
renameCheckedEntity (Text -> Text -> Text
forall a b. a -> b -> a
const Text
"addresses")
, assetClassRows :: EntityModification
(CheckedDatabaseEntity Sqlite Db)
Sqlite
(TableEntity AssetClassRowT)
assetClassRows = (Text -> Text)
-> EntityModification
(CheckedDatabaseEntity Sqlite Db)
Sqlite
(TableEntity AssetClassRowT)
forall be (db :: (* -> *) -> *) ent.
(Text -> Text)
-> EntityModification (CheckedDatabaseEntity be db) be ent
renameCheckedEntity (Text -> Text -> Text
forall a b. a -> b -> a
const Text
"asset_classes")
, tipRows :: EntityModification
(CheckedDatabaseEntity Sqlite Db) Sqlite (TableEntity TipRowT)
tipRows = (Text -> Text)
-> EntityModification
(CheckedDatabaseEntity Sqlite Db) Sqlite (TableEntity TipRowT)
forall be (db :: (* -> *) -> *) ent.
(Text -> Text)
-> EntityModification (CheckedDatabaseEntity be db) be ent
renameCheckedEntity (Text -> Text -> Text
forall a b. a -> b -> a
const Text
"tips")
, unspentOutputRows :: EntityModification
(CheckedDatabaseEntity Sqlite Db)
Sqlite
(TableEntity UnspentOutputRowT)
unspentOutputRows = (Text -> Text)
-> EntityModification
(CheckedDatabaseEntity Sqlite Db)
Sqlite
(TableEntity UnspentOutputRowT)
forall be (db :: (* -> *) -> *) ent.
(Text -> Text)
-> EntityModification (CheckedDatabaseEntity be db) be ent
renameCheckedEntity (Text -> Text -> Text
forall a b. a -> b -> a
const Text
"unspent_outputs")
, unmatchedInputRows :: EntityModification
(CheckedDatabaseEntity Sqlite Db)
Sqlite
(TableEntity UnmatchedInputRowT)
unmatchedInputRows = (Text -> Text)
-> EntityModification
(CheckedDatabaseEntity Sqlite Db)
Sqlite
(TableEntity UnmatchedInputRowT)
forall be (db :: (* -> *) -> *) ent.
(Text -> Text)
-> EntityModification (CheckedDatabaseEntity be db) be ent
renameCheckedEntity (Text -> Text -> Text
forall a b. a -> b -> a
const Text
"unmatched_inputs")
}
class FromBackendRow Sqlite (DbType a) => HasDbType a where
type DbType a
toDbValue :: a -> DbType a
fromDbValue :: DbType a -> a
instance HasDbType ByteString where
type DbType ByteString = ByteString
toDbValue :: ByteString -> DbType ByteString
toDbValue = ByteString -> DbType ByteString
forall a. a -> a
id
fromDbValue :: DbType ByteString -> ByteString
fromDbValue = DbType ByteString -> ByteString
forall a. a -> a
id
instance HasDbType PlutusTx.BuiltinByteString where
type DbType PlutusTx.BuiltinByteString = ByteString
toDbValue :: BuiltinByteString -> DbType BuiltinByteString
toDbValue = BuiltinByteString -> DbType BuiltinByteString
forall arep a. FromBuiltin arep a => arep -> a
PlutusTx.fromBuiltin
fromDbValue :: DbType BuiltinByteString -> BuiltinByteString
fromDbValue = DbType BuiltinByteString -> BuiltinByteString
forall a arep. ToBuiltin a arep => a -> arep
PlutusTx.toBuiltin
deriving via PlutusTx.BuiltinByteString instance HasDbType DatumHash
deriving via PlutusTx.BuiltinByteString instance HasDbType ValidatorHash
deriving via PlutusTx.BuiltinByteString instance HasDbType MintingPolicyHash
deriving via PlutusTx.BuiltinByteString instance HasDbType RedeemerHash
deriving via PlutusTx.BuiltinByteString instance HasDbType StakeValidatorHash
deriving via PlutusTx.BuiltinByteString instance HasDbType TxId
deriving via ByteString instance HasDbType BlockId
deriving via PlutusTx.BuiltinByteString instance HasDbType ScriptHash
newtype Serialisable a = Serialisable { Serialisable a -> a
getSerialisable :: a }
instance Serialise a => HasDbType (Serialisable a) where
type DbType (Serialisable a) = ByteString
fromDbValue :: DbType (Serialisable a) -> Serialisable a
fromDbValue
= a -> Serialisable a
forall a. a -> Serialisable a
Serialisable
(a -> Serialisable a)
-> (ByteString -> a) -> ByteString -> Serialisable a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Either DeserialiseFailure a -> a
forall b a. b -> Either a b -> b
fromRight ([Char] -> a
forall a. HasCallStack => [Char] -> a
error [Char]
"Deserialisation failed. Delete your chain index database and resync.")
(Either DeserialiseFailure a -> a)
-> (ByteString -> Either DeserialiseFailure a) -> ByteString -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Either DeserialiseFailure a
forall a. Serialise a => ByteString -> Either DeserialiseFailure a
deserialiseOrFail
(ByteString -> Either DeserialiseFailure a)
-> (ByteString -> ByteString)
-> ByteString
-> Either DeserialiseFailure a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
BSL.fromStrict
toDbValue :: Serialisable a -> DbType (Serialisable a)
toDbValue = ByteString -> ByteString
BSL.toStrict (ByteString -> ByteString)
-> (Serialisable a -> ByteString) -> Serialisable a -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> ByteString
forall a. Serialise a => a -> ByteString
serialise (a -> ByteString)
-> (Serialisable a -> a) -> Serialisable a -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Serialisable a -> a
forall a. Serialisable a -> a
getSerialisable
deriving via Serialisable Datum instance HasDbType Datum
deriving via Serialisable Redeemer instance HasDbType Redeemer
deriving via Serialisable (Versioned MintingPolicy) instance HasDbType (Versioned MintingPolicy)
deriving via Serialisable (Versioned StakeValidator) instance HasDbType (Versioned StakeValidator)
deriving via Serialisable (Versioned Validator) instance HasDbType (Versioned Validator)
deriving via Serialisable (Versioned Script) instance HasDbType (Versioned Script)
deriving via Serialisable ChainIndexTx instance HasDbType ChainIndexTx
deriving via Serialisable DecoratedTxOut instance HasDbType DecoratedTxOut
deriving via Serialisable TxOutRef instance HasDbType TxOutRef
deriving via Serialisable CI.ChainIndexTxOut instance HasDbType CI.ChainIndexTxOut
deriving via Serialisable Credential instance HasDbType Credential
deriving via Serialisable AssetClass instance HasDbType AssetClass
instance HasDbType Slot where
type DbType Slot = Word64
toDbValue :: Slot -> DbType Slot
toDbValue = Slot -> DbType Slot
forall a b. (Integral a, Num b) => a -> b
fromIntegral
fromDbValue :: DbType Slot -> Slot
fromDbValue = DbType Slot -> Slot
forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance HasDbType BlockNumber where
type DbType BlockNumber = Word64
toDbValue :: BlockNumber -> DbType BlockNumber
toDbValue = BlockNumber -> DbType BlockNumber
coerce
fromDbValue :: DbType BlockNumber -> BlockNumber
fromDbValue = DbType BlockNumber -> BlockNumber
coerce
instance HasDbType Tip where
type DbType Tip = Maybe TipRow
toDbValue :: Tip -> DbType Tip
toDbValue Tip
TipAtGenesis = DbType Tip
forall a. Maybe a
Nothing
toDbValue (Tip Slot
sl BlockId
bi BlockNumber
bn) = TipRowT Identity -> Maybe (TipRowT Identity)
forall a. a -> Maybe a
Just (Columnar Identity Word64
-> Columnar Identity ByteString
-> Columnar Identity Word64
-> TipRowT Identity
forall (f :: * -> *).
Columnar f Word64
-> Columnar f ByteString -> Columnar f Word64 -> TipRowT f
TipRow (Slot -> DbType Slot
forall a. HasDbType a => a -> DbType a
toDbValue Slot
sl) (BlockId -> DbType BlockId
forall a. HasDbType a => a -> DbType a
toDbValue BlockId
bi) (BlockNumber -> DbType BlockNumber
forall a. HasDbType a => a -> DbType a
toDbValue BlockNumber
bn))
fromDbValue :: DbType Tip -> Tip
fromDbValue DbType Tip
Nothing = Tip
TipAtGenesis
fromDbValue (Just (TipRow sl bi bn)) = Slot -> BlockId -> BlockNumber -> Tip
Tip (DbType Slot -> Slot
forall a. HasDbType a => DbType a -> a
fromDbValue Columnar Identity Word64
DbType Slot
sl) (DbType BlockId -> BlockId
forall a. HasDbType a => DbType a -> a
fromDbValue Columnar Identity ByteString
DbType BlockId
bi) (DbType BlockNumber -> BlockNumber
forall a. HasDbType a => DbType a -> a
fromDbValue Columnar Identity Word64
DbType BlockNumber
bn)
instance HasDbType (DatumHash, Datum) where
type DbType (DatumHash, Datum) = DatumRow
toDbValue :: (DatumHash, Datum) -> DbType (DatumHash, Datum)
toDbValue (DatumHash
hash, Datum
datum) = Columnar Identity ByteString
-> Columnar Identity ByteString -> DatumRowT Identity
forall (f :: * -> *).
Columnar f ByteString -> Columnar f ByteString -> DatumRowT f
DatumRow (DatumHash -> DbType DatumHash
forall a. HasDbType a => a -> DbType a
toDbValue DatumHash
hash) (Datum -> DbType Datum
forall a. HasDbType a => a -> DbType a
toDbValue Datum
datum)
fromDbValue :: DbType (DatumHash, Datum) -> (DatumHash, Datum)
fromDbValue (DatumRow hash datum) = (DbType DatumHash -> DatumHash
forall a. HasDbType a => DbType a -> a
fromDbValue Columnar Identity ByteString
DbType DatumHash
hash, DbType Datum -> Datum
forall a. HasDbType a => DbType a -> a
fromDbValue Columnar Identity ByteString
DbType Datum
datum)
instance HasDbType (ScriptHash, Versioned Script) where
type DbType (ScriptHash, Versioned Script) = ScriptRow
toDbValue :: (ScriptHash, Versioned Script)
-> DbType (ScriptHash, Versioned Script)
toDbValue (ScriptHash
hash, Versioned Script
script) = Columnar Identity ByteString
-> Columnar Identity ByteString -> ScriptRowT Identity
forall (f :: * -> *).
Columnar f ByteString -> Columnar f ByteString -> ScriptRowT f
ScriptRow (ScriptHash -> DbType ScriptHash
forall a. HasDbType a => a -> DbType a
toDbValue ScriptHash
hash) (Versioned Script -> DbType (Versioned Script)
forall a. HasDbType a => a -> DbType a
toDbValue Versioned Script
script)
fromDbValue :: DbType (ScriptHash, Versioned Script)
-> (ScriptHash, Versioned Script)
fromDbValue (ScriptRow hash script) = (DbType ScriptHash -> ScriptHash
forall a. HasDbType a => DbType a -> a
fromDbValue Columnar Identity ByteString
DbType ScriptHash
hash, DbType (Versioned Script) -> Versioned Script
forall a. HasDbType a => DbType a -> a
fromDbValue Columnar Identity ByteString
DbType (Versioned Script)
script)
instance HasDbType (RedeemerHash, Redeemer) where
type DbType (RedeemerHash, Redeemer) = RedeemerRow
toDbValue :: (RedeemerHash, Redeemer) -> DbType (RedeemerHash, Redeemer)
toDbValue (RedeemerHash
hash, Redeemer
redeemer) = Columnar Identity ByteString
-> Columnar Identity ByteString -> RedeemerRowT Identity
forall (f :: * -> *).
Columnar f ByteString -> Columnar f ByteString -> RedeemerRowT f
RedeemerRow (RedeemerHash -> DbType RedeemerHash
forall a. HasDbType a => a -> DbType a
toDbValue RedeemerHash
hash) (Redeemer -> DbType Redeemer
forall a. HasDbType a => a -> DbType a
toDbValue Redeemer
redeemer)
fromDbValue :: DbType (RedeemerHash, Redeemer) -> (RedeemerHash, Redeemer)
fromDbValue (RedeemerRow hash redeemer) = (DbType RedeemerHash -> RedeemerHash
forall a. HasDbType a => DbType a -> a
fromDbValue Columnar Identity ByteString
DbType RedeemerHash
hash, DbType Redeemer -> Redeemer
forall a. HasDbType a => DbType a -> a
fromDbValue Columnar Identity ByteString
DbType Redeemer
redeemer)
instance HasDbType (TxId, ChainIndexTx) where
type DbType (TxId, ChainIndexTx) = TxRow
toDbValue :: (TxId, ChainIndexTx) -> DbType (TxId, ChainIndexTx)
toDbValue (TxId
txId, ChainIndexTx
tx) = Columnar Identity ByteString
-> Columnar Identity ByteString -> TxRowT Identity
forall (f :: * -> *).
Columnar f ByteString -> Columnar f ByteString -> TxRowT f
TxRow (TxId -> DbType TxId
forall a. HasDbType a => a -> DbType a
toDbValue TxId
txId) (ChainIndexTx -> DbType ChainIndexTx
forall a. HasDbType a => a -> DbType a
toDbValue ChainIndexTx
tx)
fromDbValue :: DbType (TxId, ChainIndexTx) -> (TxId, ChainIndexTx)
fromDbValue (TxRow txId tx) = (DbType TxId -> TxId
forall a. HasDbType a => DbType a -> a
fromDbValue Columnar Identity ByteString
DbType TxId
txId, DbType ChainIndexTx -> ChainIndexTx
forall a. HasDbType a => DbType a -> a
fromDbValue Columnar Identity ByteString
DbType ChainIndexTx
tx)
instance HasDbType (Credential, TxOutRef, Maybe DatumHash) where
type DbType (Credential, TxOutRef, Maybe DatumHash) = AddressRow
toDbValue :: (Credential, TxOutRef, Maybe DatumHash)
-> DbType (Credential, TxOutRef, Maybe DatumHash)
toDbValue (Credential
cred, TxOutRef
outRef, Maybe DatumHash
Nothing) = Columnar Identity ByteString
-> Columnar Identity ByteString
-> Columnar Identity ByteString
-> AddressRowT Identity
forall (f :: * -> *).
Columnar f ByteString
-> Columnar f ByteString -> Columnar f ByteString -> AddressRowT f
AddressRow (Credential -> DbType Credential
forall a. HasDbType a => a -> DbType a
toDbValue Credential
cred) (TxOutRef -> DbType TxOutRef
forall a. HasDbType a => a -> DbType a
toDbValue TxOutRef
outRef) (DatumHash -> DbType DatumHash
forall a. HasDbType a => a -> DbType a
toDbValue (DatumHash -> DbType DatumHash) -> DatumHash -> DbType DatumHash
forall a b. (a -> b) -> a -> b
$ BuiltinByteString -> DatumHash
DatumHash BuiltinByteString
emptyByteString)
toDbValue (Credential
cred, TxOutRef
outRef, Just DatumHash
dh) = Columnar Identity ByteString
-> Columnar Identity ByteString
-> Columnar Identity ByteString
-> AddressRowT Identity
forall (f :: * -> *).
Columnar f ByteString
-> Columnar f ByteString -> Columnar f ByteString -> AddressRowT f
AddressRow (Credential -> DbType Credential
forall a. HasDbType a => a -> DbType a
toDbValue Credential
cred) (TxOutRef -> DbType TxOutRef
forall a. HasDbType a => a -> DbType a
toDbValue TxOutRef
outRef) (DatumHash -> DbType DatumHash
forall a. HasDbType a => a -> DbType a
toDbValue DatumHash
dh)
fromDbValue :: DbType (Credential, TxOutRef, Maybe DatumHash)
-> (Credential, TxOutRef, Maybe DatumHash)
fromDbValue (AddressRow cred outRef dh) =
let dh' :: DatumHash
dh'@(DatumHash (BuiltinByteString ByteString
bs)) = DbType DatumHash -> DatumHash
forall a. HasDbType a => DbType a -> a
fromDbValue Columnar Identity ByteString
DbType DatumHash
dh in
if ByteString -> Bool
BS.null ByteString
bs then
(DbType Credential -> Credential
forall a. HasDbType a => DbType a -> a
fromDbValue Columnar Identity ByteString
DbType Credential
cred, DbType TxOutRef -> TxOutRef
forall a. HasDbType a => DbType a -> a
fromDbValue Columnar Identity ByteString
DbType TxOutRef
outRef, Maybe DatumHash
forall a. Maybe a
Nothing)
else
(DbType Credential -> Credential
forall a. HasDbType a => DbType a -> a
fromDbValue Columnar Identity ByteString
DbType Credential
cred, DbType TxOutRef -> TxOutRef
forall a. HasDbType a => DbType a -> a
fromDbValue Columnar Identity ByteString
DbType TxOutRef
outRef, DatumHash -> Maybe DatumHash
forall a. a -> Maybe a
Just DatumHash
dh')
instance HasDbType (AssetClass, TxOutRef) where
type DbType (AssetClass, TxOutRef) = AssetClassRow
toDbValue :: (AssetClass, TxOutRef) -> DbType (AssetClass, TxOutRef)
toDbValue (AssetClass
ac, TxOutRef
outRef) = Columnar Identity ByteString
-> Columnar Identity ByteString -> AssetClassRowT Identity
forall (f :: * -> *).
Columnar f ByteString -> Columnar f ByteString -> AssetClassRowT f
AssetClassRow (AssetClass -> DbType AssetClass
forall a. HasDbType a => a -> DbType a
toDbValue AssetClass
ac) (TxOutRef -> DbType TxOutRef
forall a. HasDbType a => a -> DbType a
toDbValue TxOutRef
outRef)
fromDbValue :: DbType (AssetClass, TxOutRef) -> (AssetClass, TxOutRef)
fromDbValue (AssetClassRow ac outRef) = (DbType AssetClass -> AssetClass
forall a. HasDbType a => DbType a -> a
fromDbValue Columnar Identity ByteString
DbType AssetClass
ac, DbType TxOutRef -> TxOutRef
forall a. HasDbType a => DbType a -> a
fromDbValue Columnar Identity ByteString
DbType TxOutRef
outRef)