Skip to content
This repository has been archived by the owner on Apr 6, 2020. It is now read-only.

Commit

Permalink
Merge pull request #108 from input-output-hk/erikd/genesis-address
Browse files Browse the repository at this point in the history
webapi: Implement /api/genesis/address endpoint
  • Loading branch information
erikd committed Oct 20, 2019
2 parents 6d764ac + ed3fe0c commit 9548fdc
Show file tree
Hide file tree
Showing 5 changed files with 118 additions and 46 deletions.
1 change: 1 addition & 0 deletions cabal.project
@@ -1,5 +1,6 @@
packages:
cardano-explorer-db
cardano-explorer-db/test
cardano-explorer-node
cardano-explorer

Expand Down
1 change: 0 additions & 1 deletion cardano-explorer-db/test/cardano-explorer-db-test.cabal
Expand Up @@ -16,7 +16,6 @@ maintainer: operations@iohk.io
copyright: (c) 2019 IOHK
category: Cryptocurrency
build-type: Simple
extra-source-files: CHANGELOG.md

library
default-language: Haskell2010
Expand Down
1 change: 1 addition & 0 deletions cardano-explorer/cardano-explorer.cabal
Expand Up @@ -44,6 +44,7 @@ library
, Explorer.Web.Query
, Explorer.Web.Server
, Explorer.Web.Server.BlockPages
, Explorer.Web.Server.GenesisAddress
, Explorer.Web.Server.GenesisPages
, Explorer.Web.Server.GenesisSummary
, Explorer.Web.Server.TxLast
Expand Down
48 changes: 3 additions & 45 deletions cardano-explorer/src/Explorer/Web/Server.hs
Expand Up @@ -8,8 +8,7 @@ import Explorer.DB (Ada, Block (..), Tx (..), TxOut (..),
readPGPassFileEnv, toConnectionString)
import Explorer.Web.Api (ExplorerApi, explorerApi)
import Explorer.Web.ClientTypes (CAddress (..), CAddressSummary (..), CAddressType (..),
CAddressesFilter (..), CBlockEntry (..), CBlockRange (..), CBlockSummary (..),
CGenesisAddressInfo (..), CHash (CHash), CCoin,
CBlockEntry (..), CBlockRange (..), CBlockSummary (..), CHash (..), CCoin,
CTxBrief (..), CTxHash (..), CTxSummary (..), CUtxo (..),
mkCCoin, adaToCCoin)
import Explorer.Web.Error (ExplorerError (..))
Expand All @@ -21,6 +20,7 @@ import Explorer.Web.LegacyApi (ExplorerApiRecord (..), TxsStats, PageN
import Explorer.Web.Server.Types (PageNo (..), PageSize (..))

import Explorer.Web.Server.BlockPages
import Explorer.Web.Server.GenesisAddress
import Explorer.Web.Server.GenesisPages
import Explorer.Web.Server.GenesisSummary
import Explorer.Web.Server.TxLast
Expand Down Expand Up @@ -79,7 +79,7 @@ explorerHandlers backend = (toServant oldHandlers) :<|> (toServant newHandlers)
, _epochSlots = testEpochSlotSearch backend
, _genesisSummary = genesisSummary backend
, _genesisPagesTotal = genesisPages backend
, _genesisAddressInfo = testGenesisAddressInfo backend
, _genesisAddressInfo = genesisAddressInfo backend
, _statsTxs = testStatsTxs backend
} :: ExplorerApiRecord (AsServerT Handler)
newHandlers = ExplorerApi1Record
Expand Down Expand Up @@ -300,48 +300,6 @@ testEpochPageSearch _backend _ _ = pure $ Right (1, [CBlockEntry
, cbeFees = mkCCoin 0
}])

-- mock CGenesisAddressInfo
gAddressInfoA :: CGenesisAddressInfo
gAddressInfoA = CGenesisAddressInfo
{ cgaiCardanoAddress = CAddress "not-implemented-yet"
, cgaiGenesisAmount = mkCCoin 2225295000000
, cgaiIsRedeemed = True
}

-- mock another CGenesisAddressInfo
gAddressInfoB :: CGenesisAddressInfo
gAddressInfoB = CGenesisAddressInfo
{ cgaiCardanoAddress = CAddress "not-implemented-yet"
, cgaiGenesisAmount = mkCCoin 15000000
, cgaiIsRedeemed = False
}

-- mock another CGenesisAddressInfo
gAddressInfoC :: CGenesisAddressInfo
gAddressInfoC = CGenesisAddressInfo
{ cgaiCardanoAddress = CAddress "not-implemented-yet"
, cgaiGenesisAmount = mkCCoin 333000000
, cgaiIsRedeemed = False
}

testGenesisAddressInfo
:: SqlBackend -> Maybe PageNo
-> Maybe PageSize
-> Maybe CAddressesFilter
-> Handler (Either ExplorerError [CGenesisAddressInfo])
-- filter redeemed addresses
testGenesisAddressInfo _backend _ _ (Just RedeemedAddresses) = pure $ Right [ gAddressInfoA ]
-- filter non-redeemed addresses
testGenesisAddressInfo _backend _ _ (Just NonRedeemedAddresses) = pure $ Right [ gAddressInfoB, gAddressInfoC ]
-- all addresses (w/o filtering) - page 1
testGenesisAddressInfo _backend (Just (PageNo 1)) _ (Just AllAddresses) = pure $ Right [ gAddressInfoA, gAddressInfoB ]
testGenesisAddressInfo _backend (Just (PageNo 1)) _ Nothing = pure $ Right [ gAddressInfoA, gAddressInfoB ]
-- all addresses (w/o filtering) - page 2
testGenesisAddressInfo _backend (Just (PageNo 2)) _ (Just AllAddresses) = pure $ Right [ gAddressInfoC ]
testGenesisAddressInfo _backend (Just (PageNo 2)) _ Nothing = pure $ Right [ gAddressInfoC ]
-- all others requests will ended up with an error
testGenesisAddressInfo _backend _ _ _ = pure $ Left $ Internal "Error while pagening genesis addresses"

testStatsTxs
:: SqlBackend -> Maybe PageNo
-> Handler (Either ExplorerError TxsStats)
Expand Down
113 changes: 113 additions & 0 deletions cardano-explorer/src/Explorer/Web/Server/GenesisAddress.hs
@@ -0,0 +1,113 @@
{-# LANGUAGE OverloadedStrings #-}
module Explorer.Web.Server.GenesisAddress
( genesisAddressInfo
) where

import Control.Monad (when)
import Control.Monad.IO.Class (MonadIO)
import Control.Monad.Trans.Reader (ReaderT)

import Data.Maybe (fromMaybe)
import Data.Text (Text)
import Data.Word (Word64)

import Database.Esqueleto (InnerJoin (..), Value, (^.), (==.),
desc, from, limit, offset, on, orderBy, select, unValue, val, where_)
import Database.Persist.Sql (SqlBackend)

import Explorer.DB (EntityField (..), txOutSpentB, txOutSpentP, txOutUnspentP)

import Explorer.Web.ClientTypes (CAddress (..), CAddressesFilter (..),
CGenesisAddressInfo (..), mkCCoin)
import Explorer.Web.Error (ExplorerError (..))
import Explorer.Web.Server.Types (PageNo (..), PageSize (..))
import Explorer.Web.Server.Util (runQuery, toPageSize)

import Servant (Handler)


genesisAddressInfo
:: SqlBackend -> Maybe PageNo -> Maybe PageSize -> Maybe CAddressesFilter
-> Handler (Either ExplorerError [CGenesisAddressInfo])
-- filter redeemed addresses
genesisAddressInfo backend mPage mPageSize mAddrFilter =
if unPageSize pageSize < 1
then pure $ Left (Internal "Page size must be greater than 1.")
else genesisAddrInfo backend page pageSize addrFilter
where
pageSize = toPageSize mPageSize
page = fromMaybe (PageNo 0) mPage
addrFilter = fromMaybe AllAddresses mAddrFilter

genesisAddrInfo
:: SqlBackend -> PageNo -> PageSize -> CAddressesFilter
-> Handler (Either ExplorerError [CGenesisAddressInfo])
-- filter redeemed addresses
genesisAddrInfo backend page pageSize addrFilter =
runQuery backend $
case addrFilter of
RedeemedAddresses -> Right <$> queryRedeemedGenesisAddresses page pageSize
NonRedeemedAddresses -> Right <$> queryNonRedeemedGenesisAddresses page pageSize
AllAddresses -> Right <$> queryAllGenesisAddresses page pageSize

queryRedeemedGenesisAddresses
:: MonadIO m
=> PageNo -> PageSize
-> ReaderT SqlBackend m [CGenesisAddressInfo]
queryRedeemedGenesisAddresses (PageNo page) (PageSize pageSize) = do
rows <- select . from $ \ (blk `InnerJoin` tx `InnerJoin` txOut) -> do
on (tx ^. TxId ==. txOut ^. TxOutTxId)
on (blk ^. BlockId ==. tx ^. TxBlock)
-- Only the initial genesis block has a size of 0.
where_ (blk ^. BlockSize ==. val 0)
txOutSpentP txOut
orderBy [desc (txOut ^. TxOutValue)]
when (page > 0) $
offset (fromIntegral page)
limit (fromIntegral pageSize)
pure (txOut ^. TxOutAddress, txOut ^. TxOutValue, txOutSpentB txOut)
pure $ map mkCGenesisAddressInfo rows

queryNonRedeemedGenesisAddresses
:: MonadIO m
=> PageNo -> PageSize
-> ReaderT SqlBackend m [CGenesisAddressInfo]
queryNonRedeemedGenesisAddresses (PageNo page) (PageSize pageSize) = do
rows <- select . from $ \ (blk `InnerJoin` tx `InnerJoin` txOut) -> do
on (tx ^. TxId ==. txOut ^. TxOutTxId)
on (blk ^. BlockId ==. tx ^. TxBlock)
-- Only the initial genesis block has a size of 0.
where_ (blk ^. BlockSize ==. val 0)
txOutUnspentP txOut
orderBy [desc (txOut ^. TxOutValue)]
when (page > 0) $
offset (fromIntegral page)
limit (fromIntegral pageSize)
pure (txOut ^. TxOutAddress, txOut ^. TxOutValue, txOutSpentB txOut)
pure $ map mkCGenesisAddressInfo rows

queryAllGenesisAddresses
:: MonadIO m
=> PageNo -> PageSize
-> ReaderT SqlBackend m [CGenesisAddressInfo]
queryAllGenesisAddresses (PageNo page) (PageSize pageSize) = do
rows <- select . from $ \ (blk `InnerJoin` tx `InnerJoin` txOut) -> do
on (tx ^. TxId ==. txOut ^. TxOutTxId)
on (blk ^. BlockId ==. tx ^. TxBlock)
-- Only the initial genesis block has a size of 0.
where_ (blk ^. BlockSize ==. val 0)
orderBy [desc (txOut ^. TxOutValue)]
when (page > 0) $
offset (fromIntegral page)
limit (fromIntegral pageSize)
pure (txOut ^. TxOutAddress, txOut ^. TxOutValue, txOutSpentB txOut)
pure $ map mkCGenesisAddressInfo rows


mkCGenesisAddressInfo :: (Value Text, Value Word64, Value Bool) -> CGenesisAddressInfo
mkCGenesisAddressInfo (vaddr, vvalue, vRedeemed) =
CGenesisAddressInfo
{ cgaiCardanoAddress = CAddress (unValue vaddr)
, cgaiGenesisAmount = mkCCoin (fromIntegral $ unValue vvalue)
, cgaiIsRedeemed = unValue vRedeemed
}

0 comments on commit 9548fdc

Please sign in to comment.