{-# LANGUAGE CPP                 #-}
{-# LANGUAGE FlexibleContexts    #-}
{-# LANGUAGE FlexibleInstances   #-}
{-# LANGUAGE LambdaCase          #-}
{-# LANGUAGE MultiWayIf          #-}
{-# LANGUAGE OverloadedStrings   #-}
{-# LANGUAGE RecordWildCards     #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskell     #-}
{-# LANGUAGE TupleSections       #-}
module Haskoin.Store.Web
    ( -- * Web
      WebConfig (..)
    , Except (..)
    , WebLimits (..)
    , WebTimeouts (..)
    , runWeb
    ) where

import           Conduit                       (await, runConduit, takeC, yield,
                                                (.|))
import           Control.Applicative           ((<|>))
import           Control.Arrow                 (second)
import           Control.Lens
import           Control.Monad                 (forever, unless, when, (<=<))
import           Control.Monad.Logger          (MonadLoggerIO, logDebugS,
                                                logErrorS, logInfoS)
import           Control.Monad.Reader          (ReaderT, ask, asks, local,
                                                runReaderT)
import           Control.Monad.Trans           (lift)
import           Control.Monad.Trans.Maybe     (MaybeT (..), runMaybeT)
import           Data.Aeson                    (Encoding, ToJSON (..), Value)
import           Data.Aeson.Encode.Pretty      (Config (..), defConfig,
                                                encodePretty')
import           Data.Aeson.Encoding           (encodingToLazyByteString, list)
import           Data.Aeson.Text               (encodeToLazyText)
import           Data.ByteString.Builder       (lazyByteString)
import qualified Data.ByteString.Lazy          as L
import qualified Data.ByteString.Lazy.Char8    as C
import           Data.Char                     (isSpace)
import           Data.Default                  (Default (..))
import           Data.Function                 ((&))
import           Data.HashMap.Strict           (HashMap)
import qualified Data.HashMap.Strict           as HashMap
import qualified Data.HashSet                  as HashSet
import           Data.List                     (nub)
import qualified Data.Map.Strict               as Map
import           Data.Maybe                    (catMaybes, fromJust, fromMaybe,
                                                listToMaybe, mapMaybe)
import           Data.Proxy                    (Proxy (..))
import           Data.Serialize                as Serialize
import qualified Data.Set                      as Set
import           Data.String                   (fromString)
import           Data.String.Conversions       (cs)
import           Data.Text                     (Text)
import qualified Data.Text                     as T
import qualified Data.Text.Encoding            as T
import           Data.Text.Lazy                (toStrict)
import qualified Data.Text.Lazy                as TL
import           Data.Time.Clock               (NominalDiffTime, diffUTCTime,
                                                getCurrentTime)
import           Data.Time.Clock.System        (getSystemTime, systemSeconds)
import           Data.Word                     (Word32, Word64)
import           Database.RocksDB              (Property (..), getProperty)
import           Haskoin.Address
import qualified Haskoin.Block                 as H
import           Haskoin.Constants
import           Haskoin.Keys
import           Haskoin.Network
import           Haskoin.Node                  (Chain, OnlinePeer (..),
                                                PeerManager, chainGetBest,
                                                getPeers, sendMessage)
import           Haskoin.Store.BlockStore
import           Haskoin.Store.Cache
import           Haskoin.Store.Common
import           Haskoin.Store.Data
import           Haskoin.Store.Database.Reader
import           Haskoin.Store.Manager
import           Haskoin.Store.WebCommon
import           Haskoin.Transaction
import           Haskoin.Util
import           Network.HTTP.Types            (Status (..), status400,
                                                status403, status404, status500,
                                                status503, statusIsSuccessful)
import           Network.Wai                   (Middleware, Request (..),
                                                responseStatus)
import           Network.Wai.Handler.Warp      (defaultSettings, setHost,
                                                setPort)
import qualified Network.Wreq                  as Wreq
import           NQE                           (Inbox, receive,
                                                withSubscription)
import           Text.Printf                   (printf)
import           UnliftIO                      (MonadIO, MonadUnliftIO, TVar,
                                                askRunInIO, atomically,
                                                handleAny, liftIO, newTVarIO,
                                                readTVarIO, timeout, withAsync,
                                                writeTVar)
import           UnliftIO.Concurrent           (threadDelay)
import           Web.Scotty.Internal.Types     (ActionT)
import           Web.Scotty.Trans              (Parsable)
import qualified Web.Scotty.Trans              as S

type WebT m = ActionT Except (ReaderT WebConfig m)

data WebLimits = WebLimits
    { WebLimits -> Word32
maxLimitCount      :: !Word32
    , WebLimits -> Word32
maxLimitFull       :: !Word32
    , WebLimits -> Word32
maxLimitOffset     :: !Word32
    , WebLimits -> Word32
maxLimitDefault    :: !Word32
    , WebLimits -> Word32
maxLimitGap        :: !Word32
    , WebLimits -> Word32
maxLimitInitialGap :: !Word32
    }
    deriving (WebLimits -> WebLimits -> Bool
(WebLimits -> WebLimits -> Bool)
-> (WebLimits -> WebLimits -> Bool) -> Eq WebLimits
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WebLimits -> WebLimits -> Bool
$c/= :: WebLimits -> WebLimits -> Bool
== :: WebLimits -> WebLimits -> Bool
$c== :: WebLimits -> WebLimits -> Bool
Eq, Int -> WebLimits -> ShowS
[WebLimits] -> ShowS
WebLimits -> String
(Int -> WebLimits -> ShowS)
-> (WebLimits -> String)
-> ([WebLimits] -> ShowS)
-> Show WebLimits
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WebLimits] -> ShowS
$cshowList :: [WebLimits] -> ShowS
show :: WebLimits -> String
$cshow :: WebLimits -> String
showsPrec :: Int -> WebLimits -> ShowS
$cshowsPrec :: Int -> WebLimits -> ShowS
Show)

instance Default WebLimits where
    def :: WebLimits
def =
        $WWebLimits :: Word32
-> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> WebLimits
WebLimits
            { maxLimitCount :: Word32
maxLimitCount = 200000
            , maxLimitFull :: Word32
maxLimitFull = 5000
            , maxLimitOffset :: Word32
maxLimitOffset = 50000
            , maxLimitDefault :: Word32
maxLimitDefault = 100
            , maxLimitGap :: Word32
maxLimitGap = 32
            , maxLimitInitialGap :: Word32
maxLimitInitialGap = 20
            }

data WebConfig = WebConfig
    { WebConfig -> String
webHost       :: !String
    , WebConfig -> Int
webPort       :: !Int
    , WebConfig -> Store
webStore      :: !Store
    , WebConfig -> Int
webMaxDiff    :: !Int
    , WebConfig -> Int
webMaxPending :: !Int
    , WebConfig -> WebLimits
webMaxLimits  :: !WebLimits
    , WebConfig -> WebTimeouts
webTimeouts   :: !WebTimeouts
    , WebConfig -> String
webVersion    :: !String
    , WebConfig -> Bool
webNoMempool  :: !Bool
    , WebConfig -> Bool
webNumTxId    :: !Bool
    }

data WebTimeouts = WebTimeouts
    { WebTimeouts -> Word64
txTimeout    :: !Word64
    , WebTimeouts -> Word64
blockTimeout :: !Word64
    }
    deriving (WebTimeouts -> WebTimeouts -> Bool
(WebTimeouts -> WebTimeouts -> Bool)
-> (WebTimeouts -> WebTimeouts -> Bool) -> Eq WebTimeouts
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WebTimeouts -> WebTimeouts -> Bool
$c/= :: WebTimeouts -> WebTimeouts -> Bool
== :: WebTimeouts -> WebTimeouts -> Bool
$c== :: WebTimeouts -> WebTimeouts -> Bool
Eq, Int -> WebTimeouts -> ShowS
[WebTimeouts] -> ShowS
WebTimeouts -> String
(Int -> WebTimeouts -> ShowS)
-> (WebTimeouts -> String)
-> ([WebTimeouts] -> ShowS)
-> Show WebTimeouts
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WebTimeouts] -> ShowS
$cshowList :: [WebTimeouts] -> ShowS
show :: WebTimeouts -> String
$cshow :: WebTimeouts -> String
showsPrec :: Int -> WebTimeouts -> ShowS
$cshowsPrec :: Int -> WebTimeouts -> ShowS
Show)

data SerialAs = SerialAsBinary | SerialAsJSON | SerialAsPrettyJSON
    deriving (SerialAs -> SerialAs -> Bool
(SerialAs -> SerialAs -> Bool)
-> (SerialAs -> SerialAs -> Bool) -> Eq SerialAs
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SerialAs -> SerialAs -> Bool
$c/= :: SerialAs -> SerialAs -> Bool
== :: SerialAs -> SerialAs -> Bool
$c== :: SerialAs -> SerialAs -> Bool
Eq, Int -> SerialAs -> ShowS
[SerialAs] -> ShowS
SerialAs -> String
(Int -> SerialAs -> ShowS)
-> (SerialAs -> String) -> ([SerialAs] -> ShowS) -> Show SerialAs
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SerialAs] -> ShowS
$cshowList :: [SerialAs] -> ShowS
show :: SerialAs -> String
$cshow :: SerialAs -> String
showsPrec :: Int -> SerialAs -> ShowS
$cshowsPrec :: Int -> SerialAs -> ShowS
Show)

instance Default WebTimeouts where
    def :: WebTimeouts
def = $WWebTimeouts :: Word64 -> Word64 -> WebTimeouts
WebTimeouts {txTimeout :: Word64
txTimeout = 300, blockTimeout :: Word64
blockTimeout = 7200}

instance (MonadUnliftIO m, MonadLoggerIO m) =>
         StoreReadBase (ReaderT WebConfig m) where
    getNetwork :: ReaderT WebConfig m Network
getNetwork = CacheT (DatabaseReaderT m) Network -> ReaderT WebConfig m Network
forall (m :: * -> *) a.
MonadIO m =>
CacheT (DatabaseReaderT m) a -> ReaderT WebConfig m a
runInWebReader CacheT (DatabaseReaderT m) Network
forall (m :: * -> *). StoreReadBase m => m Network
getNetwork
    getBestBlock :: ReaderT WebConfig m (Maybe BlockHash)
getBestBlock = CacheT (DatabaseReaderT m) (Maybe BlockHash)
-> ReaderT WebConfig m (Maybe BlockHash)
forall (m :: * -> *) a.
MonadIO m =>
CacheT (DatabaseReaderT m) a -> ReaderT WebConfig m a
runInWebReader CacheT (DatabaseReaderT m) (Maybe BlockHash)
forall (m :: * -> *). StoreReadBase m => m (Maybe BlockHash)
getBestBlock
    getBlocksAtHeight :: Word32 -> ReaderT WebConfig m [BlockHash]
getBlocksAtHeight height :: Word32
height = CacheT (DatabaseReaderT m) [BlockHash]
-> ReaderT WebConfig m [BlockHash]
forall (m :: * -> *) a.
MonadIO m =>
CacheT (DatabaseReaderT m) a -> ReaderT WebConfig m a
runInWebReader (Word32 -> CacheT (DatabaseReaderT m) [BlockHash]
forall (m :: * -> *). StoreReadBase m => Word32 -> m [BlockHash]
getBlocksAtHeight Word32
height)
    getBlock :: BlockHash -> ReaderT WebConfig m (Maybe BlockData)
getBlock bh :: BlockHash
bh = CacheT (DatabaseReaderT m) (Maybe BlockData)
-> ReaderT WebConfig m (Maybe BlockData)
forall (m :: * -> *) a.
MonadIO m =>
CacheT (DatabaseReaderT m) a -> ReaderT WebConfig m a
runInWebReader (BlockHash -> CacheT (DatabaseReaderT m) (Maybe BlockData)
forall (m :: * -> *).
StoreReadBase m =>
BlockHash -> m (Maybe BlockData)
getBlock BlockHash
bh)
    getTxData :: TxHash -> ReaderT WebConfig m (Maybe TxData)
getTxData th :: TxHash
th = CacheT (DatabaseReaderT m) (Maybe TxData)
-> ReaderT WebConfig m (Maybe TxData)
forall (m :: * -> *) a.
MonadIO m =>
CacheT (DatabaseReaderT m) a -> ReaderT WebConfig m a
runInWebReader (TxHash -> CacheT (DatabaseReaderT m) (Maybe TxData)
forall (m :: * -> *). StoreReadBase m => TxHash -> m (Maybe TxData)
getTxData TxHash
th)
    getSpender :: OutPoint -> ReaderT WebConfig m (Maybe Spender)
getSpender op :: OutPoint
op = CacheT (DatabaseReaderT m) (Maybe Spender)
-> ReaderT WebConfig m (Maybe Spender)
forall (m :: * -> *) a.
MonadIO m =>
CacheT (DatabaseReaderT m) a -> ReaderT WebConfig m a
runInWebReader (OutPoint -> CacheT (DatabaseReaderT m) (Maybe Spender)
forall (m :: * -> *).
StoreReadBase m =>
OutPoint -> m (Maybe Spender)
getSpender OutPoint
op)
    getUnspent :: OutPoint -> ReaderT WebConfig m (Maybe Unspent)
getUnspent op :: OutPoint
op = CacheT (DatabaseReaderT m) (Maybe Unspent)
-> ReaderT WebConfig m (Maybe Unspent)
forall (m :: * -> *) a.
MonadIO m =>
CacheT (DatabaseReaderT m) a -> ReaderT WebConfig m a
runInWebReader (OutPoint -> CacheT (DatabaseReaderT m) (Maybe Unspent)
forall (m :: * -> *).
StoreReadBase m =>
OutPoint -> m (Maybe Unspent)
getUnspent OutPoint
op)
    getBalance :: Address -> ReaderT WebConfig m (Maybe Balance)
getBalance a :: Address
a = CacheT (DatabaseReaderT m) (Maybe Balance)
-> ReaderT WebConfig m (Maybe Balance)
forall (m :: * -> *) a.
MonadIO m =>
CacheT (DatabaseReaderT m) a -> ReaderT WebConfig m a
runInWebReader (Address -> CacheT (DatabaseReaderT m) (Maybe Balance)
forall (m :: * -> *).
StoreReadBase m =>
Address -> m (Maybe Balance)
getBalance Address
a)
    getMempool :: ReaderT WebConfig m [(Word64, TxHash)]
getMempool = CacheT (DatabaseReaderT m) [(Word64, TxHash)]
-> ReaderT WebConfig m [(Word64, TxHash)]
forall (m :: * -> *) a.
MonadIO m =>
CacheT (DatabaseReaderT m) a -> ReaderT WebConfig m a
runInWebReader CacheT (DatabaseReaderT m) [(Word64, TxHash)]
forall (m :: * -> *). StoreReadBase m => m [(Word64, TxHash)]
getMempool

instance (MonadUnliftIO m, MonadLoggerIO m) =>
         StoreReadExtra (ReaderT WebConfig m) where
    getMaxGap :: ReaderT WebConfig m Word32
getMaxGap = CacheT (DatabaseReaderT m) Word32 -> ReaderT WebConfig m Word32
forall (m :: * -> *) a.
MonadIO m =>
CacheT (DatabaseReaderT m) a -> ReaderT WebConfig m a
runInWebReader CacheT (DatabaseReaderT m) Word32
forall (m :: * -> *). StoreReadExtra m => m Word32
getMaxGap
    getInitialGap :: ReaderT WebConfig m Word32
getInitialGap = CacheT (DatabaseReaderT m) Word32 -> ReaderT WebConfig m Word32
forall (m :: * -> *) a.
MonadIO m =>
CacheT (DatabaseReaderT m) a -> ReaderT WebConfig m a
runInWebReader CacheT (DatabaseReaderT m) Word32
forall (m :: * -> *). StoreReadExtra m => m Word32
getInitialGap
    getBalances :: [Address] -> ReaderT WebConfig m [Balance]
getBalances as :: [Address]
as = CacheT (DatabaseReaderT m) [Balance]
-> ReaderT WebConfig m [Balance]
forall (m :: * -> *) a.
MonadIO m =>
CacheT (DatabaseReaderT m) a -> ReaderT WebConfig m a
runInWebReader ([Address] -> CacheT (DatabaseReaderT m) [Balance]
forall (m :: * -> *). StoreReadExtra m => [Address] -> m [Balance]
getBalances [Address]
as)
    getAddressesTxs :: [Address] -> Limits -> ReaderT WebConfig m [TxRef]
getAddressesTxs as :: [Address]
as = CacheT (DatabaseReaderT m) [TxRef] -> ReaderT WebConfig m [TxRef]
forall (m :: * -> *) a.
MonadIO m =>
CacheT (DatabaseReaderT m) a -> ReaderT WebConfig m a
runInWebReader (CacheT (DatabaseReaderT m) [TxRef] -> ReaderT WebConfig m [TxRef])
-> (Limits -> CacheT (DatabaseReaderT m) [TxRef])
-> Limits
-> ReaderT WebConfig m [TxRef]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Address] -> Limits -> CacheT (DatabaseReaderT m) [TxRef]
forall (m :: * -> *).
StoreReadExtra m =>
[Address] -> Limits -> m [TxRef]
getAddressesTxs [Address]
as
    getAddressesUnspents :: [Address] -> Limits -> ReaderT WebConfig m [Unspent]
getAddressesUnspents as :: [Address]
as = CacheT (DatabaseReaderT m) [Unspent]
-> ReaderT WebConfig m [Unspent]
forall (m :: * -> *) a.
MonadIO m =>
CacheT (DatabaseReaderT m) a -> ReaderT WebConfig m a
runInWebReader (CacheT (DatabaseReaderT m) [Unspent]
 -> ReaderT WebConfig m [Unspent])
-> (Limits -> CacheT (DatabaseReaderT m) [Unspent])
-> Limits
-> ReaderT WebConfig m [Unspent]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Address] -> Limits -> CacheT (DatabaseReaderT m) [Unspent]
forall (m :: * -> *).
StoreReadExtra m =>
[Address] -> Limits -> m [Unspent]
getAddressesUnspents [Address]
as
    xPubBals :: XPubSpec -> ReaderT WebConfig m [XPubBal]
xPubBals = CacheT (DatabaseReaderT m) [XPubBal]
-> ReaderT WebConfig m [XPubBal]
forall (m :: * -> *) a.
MonadIO m =>
CacheT (DatabaseReaderT m) a -> ReaderT WebConfig m a
runInWebReader (CacheT (DatabaseReaderT m) [XPubBal]
 -> ReaderT WebConfig m [XPubBal])
-> (XPubSpec -> CacheT (DatabaseReaderT m) [XPubBal])
-> XPubSpec
-> ReaderT WebConfig m [XPubBal]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPubSpec -> CacheT (DatabaseReaderT m) [XPubBal]
forall (m :: * -> *). StoreReadExtra m => XPubSpec -> m [XPubBal]
xPubBals
    xPubSummary :: XPubSpec -> ReaderT WebConfig m XPubSummary
xPubSummary = CacheT (DatabaseReaderT m) XPubSummary
-> ReaderT WebConfig m XPubSummary
forall (m :: * -> *) a.
MonadIO m =>
CacheT (DatabaseReaderT m) a -> ReaderT WebConfig m a
runInWebReader (CacheT (DatabaseReaderT m) XPubSummary
 -> ReaderT WebConfig m XPubSummary)
-> (XPubSpec -> CacheT (DatabaseReaderT m) XPubSummary)
-> XPubSpec
-> ReaderT WebConfig m XPubSummary
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPubSpec -> CacheT (DatabaseReaderT m) XPubSummary
forall (m :: * -> *). StoreReadExtra m => XPubSpec -> m XPubSummary
xPubSummary
    xPubUnspents :: XPubSpec -> Limits -> ReaderT WebConfig m [XPubUnspent]
xPubUnspents xpub :: XPubSpec
xpub = CacheT (DatabaseReaderT m) [XPubUnspent]
-> ReaderT WebConfig m [XPubUnspent]
forall (m :: * -> *) a.
MonadIO m =>
CacheT (DatabaseReaderT m) a -> ReaderT WebConfig m a
runInWebReader (CacheT (DatabaseReaderT m) [XPubUnspent]
 -> ReaderT WebConfig m [XPubUnspent])
-> (Limits -> CacheT (DatabaseReaderT m) [XPubUnspent])
-> Limits
-> ReaderT WebConfig m [XPubUnspent]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPubSpec -> Limits -> CacheT (DatabaseReaderT m) [XPubUnspent]
forall (m :: * -> *).
StoreReadExtra m =>
XPubSpec -> Limits -> m [XPubUnspent]
xPubUnspents XPubSpec
xpub
    xPubTxs :: XPubSpec -> Limits -> ReaderT WebConfig m [TxRef]
xPubTxs xpub :: XPubSpec
xpub = CacheT (DatabaseReaderT m) [TxRef] -> ReaderT WebConfig m [TxRef]
forall (m :: * -> *) a.
MonadIO m =>
CacheT (DatabaseReaderT m) a -> ReaderT WebConfig m a
runInWebReader (CacheT (DatabaseReaderT m) [TxRef] -> ReaderT WebConfig m [TxRef])
-> (Limits -> CacheT (DatabaseReaderT m) [TxRef])
-> Limits
-> ReaderT WebConfig m [TxRef]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPubSpec -> Limits -> CacheT (DatabaseReaderT m) [TxRef]
forall (m :: * -> *).
StoreReadExtra m =>
XPubSpec -> Limits -> m [TxRef]
xPubTxs XPubSpec
xpub

instance (MonadUnliftIO m, MonadLoggerIO m) => StoreReadBase (WebT m) where
    getNetwork :: WebT m Network
getNetwork = ReaderT WebConfig m Network -> WebT m Network
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ReaderT WebConfig m Network
forall (m :: * -> *). StoreReadBase m => m Network
getNetwork
    getBestBlock :: WebT m (Maybe BlockHash)
getBestBlock = ReaderT WebConfig m (Maybe BlockHash) -> WebT m (Maybe BlockHash)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ReaderT WebConfig m (Maybe BlockHash)
forall (m :: * -> *). StoreReadBase m => m (Maybe BlockHash)
getBestBlock
    getBlocksAtHeight :: Word32 -> WebT m [BlockHash]
getBlocksAtHeight = ReaderT WebConfig m [BlockHash] -> WebT m [BlockHash]
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (ReaderT WebConfig m [BlockHash] -> WebT m [BlockHash])
-> (Word32 -> ReaderT WebConfig m [BlockHash])
-> Word32
-> WebT m [BlockHash]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word32 -> ReaderT WebConfig m [BlockHash]
forall (m :: * -> *). StoreReadBase m => Word32 -> m [BlockHash]
getBlocksAtHeight
    getBlock :: BlockHash -> WebT m (Maybe BlockData)
getBlock = ReaderT WebConfig m (Maybe BlockData) -> WebT m (Maybe BlockData)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (ReaderT WebConfig m (Maybe BlockData) -> WebT m (Maybe BlockData))
-> (BlockHash -> ReaderT WebConfig m (Maybe BlockData))
-> BlockHash
-> WebT m (Maybe BlockData)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BlockHash -> ReaderT WebConfig m (Maybe BlockData)
forall (m :: * -> *).
StoreReadBase m =>
BlockHash -> m (Maybe BlockData)
getBlock
    getTxData :: TxHash -> WebT m (Maybe TxData)
getTxData = ReaderT WebConfig m (Maybe TxData) -> WebT m (Maybe TxData)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (ReaderT WebConfig m (Maybe TxData) -> WebT m (Maybe TxData))
-> (TxHash -> ReaderT WebConfig m (Maybe TxData))
-> TxHash
-> WebT m (Maybe TxData)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TxHash -> ReaderT WebConfig m (Maybe TxData)
forall (m :: * -> *). StoreReadBase m => TxHash -> m (Maybe TxData)
getTxData
    getSpender :: OutPoint -> WebT m (Maybe Spender)
getSpender = ReaderT WebConfig m (Maybe Spender) -> WebT m (Maybe Spender)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (ReaderT WebConfig m (Maybe Spender) -> WebT m (Maybe Spender))
-> (OutPoint -> ReaderT WebConfig m (Maybe Spender))
-> OutPoint
-> WebT m (Maybe Spender)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OutPoint -> ReaderT WebConfig m (Maybe Spender)
forall (m :: * -> *).
StoreReadBase m =>
OutPoint -> m (Maybe Spender)
getSpender
    getUnspent :: OutPoint -> WebT m (Maybe Unspent)
getUnspent = ReaderT WebConfig m (Maybe Unspent) -> WebT m (Maybe Unspent)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (ReaderT WebConfig m (Maybe Unspent) -> WebT m (Maybe Unspent))
-> (OutPoint -> ReaderT WebConfig m (Maybe Unspent))
-> OutPoint
-> WebT m (Maybe Unspent)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OutPoint -> ReaderT WebConfig m (Maybe Unspent)
forall (m :: * -> *).
StoreReadBase m =>
OutPoint -> m (Maybe Unspent)
getUnspent
    getBalance :: Address -> WebT m (Maybe Balance)
getBalance = ReaderT WebConfig m (Maybe Balance) -> WebT m (Maybe Balance)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (ReaderT WebConfig m (Maybe Balance) -> WebT m (Maybe Balance))
-> (Address -> ReaderT WebConfig m (Maybe Balance))
-> Address
-> WebT m (Maybe Balance)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Address -> ReaderT WebConfig m (Maybe Balance)
forall (m :: * -> *).
StoreReadBase m =>
Address -> m (Maybe Balance)
getBalance
    getMempool :: WebT m [(Word64, TxHash)]
getMempool = ReaderT WebConfig m [(Word64, TxHash)] -> WebT m [(Word64, TxHash)]
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ReaderT WebConfig m [(Word64, TxHash)]
forall (m :: * -> *). StoreReadBase m => m [(Word64, TxHash)]
getMempool

instance (MonadUnliftIO m, MonadLoggerIO m) => StoreReadExtra (WebT m) where
    getBalances :: [Address] -> WebT m [Balance]
getBalances = ReaderT WebConfig m [Balance] -> WebT m [Balance]
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (ReaderT WebConfig m [Balance] -> WebT m [Balance])
-> ([Address] -> ReaderT WebConfig m [Balance])
-> [Address]
-> WebT m [Balance]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Address] -> ReaderT WebConfig m [Balance]
forall (m :: * -> *). StoreReadExtra m => [Address] -> m [Balance]
getBalances
    getAddressesTxs :: [Address] -> Limits -> WebT m [TxRef]
getAddressesTxs as :: [Address]
as = ReaderT WebConfig m [TxRef] -> WebT m [TxRef]
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (ReaderT WebConfig m [TxRef] -> WebT m [TxRef])
-> (Limits -> ReaderT WebConfig m [TxRef])
-> Limits
-> WebT m [TxRef]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Address] -> Limits -> ReaderT WebConfig m [TxRef]
forall (m :: * -> *).
StoreReadExtra m =>
[Address] -> Limits -> m [TxRef]
getAddressesTxs [Address]
as
    getAddressesUnspents :: [Address] -> Limits -> WebT m [Unspent]
getAddressesUnspents as :: [Address]
as = ReaderT WebConfig m [Unspent] -> WebT m [Unspent]
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (ReaderT WebConfig m [Unspent] -> WebT m [Unspent])
-> (Limits -> ReaderT WebConfig m [Unspent])
-> Limits
-> WebT m [Unspent]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Address] -> Limits -> ReaderT WebConfig m [Unspent]
forall (m :: * -> *).
StoreReadExtra m =>
[Address] -> Limits -> m [Unspent]
getAddressesUnspents [Address]
as
    xPubBals :: XPubSpec -> WebT m [XPubBal]
xPubBals = ReaderT WebConfig m [XPubBal] -> WebT m [XPubBal]
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (ReaderT WebConfig m [XPubBal] -> WebT m [XPubBal])
-> (XPubSpec -> ReaderT WebConfig m [XPubBal])
-> XPubSpec
-> WebT m [XPubBal]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPubSpec -> ReaderT WebConfig m [XPubBal]
forall (m :: * -> *). StoreReadExtra m => XPubSpec -> m [XPubBal]
xPubBals
    xPubSummary :: XPubSpec -> WebT m XPubSummary
xPubSummary = ReaderT WebConfig m XPubSummary -> WebT m XPubSummary
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (ReaderT WebConfig m XPubSummary -> WebT m XPubSummary)
-> (XPubSpec -> ReaderT WebConfig m XPubSummary)
-> XPubSpec
-> WebT m XPubSummary
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPubSpec -> ReaderT WebConfig m XPubSummary
forall (m :: * -> *). StoreReadExtra m => XPubSpec -> m XPubSummary
xPubSummary
    xPubUnspents :: XPubSpec -> Limits -> WebT m [XPubUnspent]
xPubUnspents xpub :: XPubSpec
xpub = ReaderT WebConfig m [XPubUnspent] -> WebT m [XPubUnspent]
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (ReaderT WebConfig m [XPubUnspent] -> WebT m [XPubUnspent])
-> (Limits -> ReaderT WebConfig m [XPubUnspent])
-> Limits
-> WebT m [XPubUnspent]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPubSpec -> Limits -> ReaderT WebConfig m [XPubUnspent]
forall (m :: * -> *).
StoreReadExtra m =>
XPubSpec -> Limits -> m [XPubUnspent]
xPubUnspents XPubSpec
xpub
    xPubTxs :: XPubSpec -> Limits -> WebT m [TxRef]
xPubTxs xpub :: XPubSpec
xpub = ReaderT WebConfig m [TxRef] -> WebT m [TxRef]
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (ReaderT WebConfig m [TxRef] -> WebT m [TxRef])
-> (Limits -> ReaderT WebConfig m [TxRef])
-> Limits
-> WebT m [TxRef]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPubSpec -> Limits -> ReaderT WebConfig m [TxRef]
forall (m :: * -> *).
StoreReadExtra m =>
XPubSpec -> Limits -> m [TxRef]
xPubTxs XPubSpec
xpub
    getMaxGap :: WebT m Word32
getMaxGap = ReaderT WebConfig m Word32 -> WebT m Word32
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ReaderT WebConfig m Word32
forall (m :: * -> *). StoreReadExtra m => m Word32
getMaxGap
    getInitialGap :: WebT m Word32
getInitialGap = ReaderT WebConfig m Word32 -> WebT m Word32
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ReaderT WebConfig m Word32
forall (m :: * -> *). StoreReadExtra m => m Word32
getInitialGap

-------------------
-- Path Handlers --
-------------------

runWeb :: (MonadUnliftIO m, MonadLoggerIO m) => WebConfig -> m ()
runWeb :: WebConfig -> m ()
runWeb cfg :: WebConfig
cfg@WebConfig{ webHost :: WebConfig -> String
webHost = String
host
                    , webPort :: WebConfig -> Int
webPort = Int
port
                    , webStore :: WebConfig -> Store
webStore = Store
store } = do
    TVar (HashMap Text BinfoTicker)
ticker <- HashMap Text BinfoTicker -> m (TVar (HashMap Text BinfoTicker))
forall (m :: * -> *) a. MonadIO m => a -> m (TVar a)
newTVarIO HashMap Text BinfoTicker
forall k v. HashMap k v
HashMap.empty
    m () -> (Async () -> m ()) -> m ()
forall (m :: * -> *) a b.
MonadUnliftIO m =>
m a -> (Async a -> m b) -> m b
withAsync (Network -> TVar (HashMap Text BinfoTicker) -> m ()
forall (m :: * -> *).
(MonadUnliftIO m, MonadLoggerIO m) =>
Network -> TVar (HashMap Text BinfoTicker) -> m ()
price (Store -> Network
storeNetwork Store
store) TVar (HashMap Text BinfoTicker)
ticker) ((Async () -> m ()) -> m ()) -> (Async () -> m ()) -> m ()
forall a b. (a -> b) -> a -> b
$ \_ -> do
        Middleware
reqLogger <- m Middleware
forall (m :: * -> *).
(MonadUnliftIO m, MonadLoggerIO m) =>
m Middleware
logIt
        m Response -> IO Response
runner <- m (m Response -> IO Response)
forall (m :: * -> *) a. MonadUnliftIO m => m (m a -> IO a)
askRunInIO
        Options
-> (ReaderT WebConfig m Response -> IO Response)
-> ScottyT Except (ReaderT WebConfig m) ()
-> m ()
forall (m :: * -> *) (n :: * -> *) e.
(Monad m, MonadIO n) =>
Options -> (m Response -> IO Response) -> ScottyT e m () -> n ()
S.scottyOptsT Options
opts (m Response -> IO Response
runner (m Response -> IO Response)
-> (ReaderT WebConfig m Response -> m Response)
-> ReaderT WebConfig m Response
-> IO Response
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ReaderT WebConfig m Response -> WebConfig -> m Response
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
`runReaderT` WebConfig
cfg)) (ScottyT Except (ReaderT WebConfig m) () -> m ())
-> ScottyT Except (ReaderT WebConfig m) () -> m ()
forall a b. (a -> b) -> a -> b
$ do
            Middleware -> ScottyT Except (ReaderT WebConfig m) ()
forall e (m :: * -> *). Middleware -> ScottyT e m ()
S.middleware Middleware
reqLogger
            (Except -> ActionT Except (ReaderT WebConfig m) ())
-> ScottyT Except (ReaderT WebConfig m) ()
forall e (m :: * -> *).
(ScottyError e, Monad m) =>
(e -> ActionT e m ()) -> ScottyT e m ()
S.defaultHandler Except -> ActionT Except (ReaderT WebConfig m) ()
forall (m :: * -> *). Monad m => Except -> WebT m ()
defHandler
            TVar (HashMap Text BinfoTicker)
-> ScottyT Except (ReaderT WebConfig m) ()
forall (m :: * -> *).
(MonadUnliftIO m, MonadLoggerIO m) =>
TVar (HashMap Text BinfoTicker)
-> ScottyT Except (ReaderT WebConfig m) ()
handlePaths TVar (HashMap Text BinfoTicker)
ticker
            ActionT Except (ReaderT WebConfig m) ()
-> ScottyT Except (ReaderT WebConfig m) ()
forall e (m :: * -> *).
(ScottyError e, MonadIO m) =>
ActionT e m () -> ScottyT e m ()
S.notFound (ActionT Except (ReaderT WebConfig m) ()
 -> ScottyT Except (ReaderT WebConfig m) ())
-> ActionT Except (ReaderT WebConfig m) ()
-> ScottyT Except (ReaderT WebConfig m) ()
forall a b. (a -> b) -> a -> b
$ Except -> ActionT Except (ReaderT WebConfig m) ()
forall e (m :: * -> *) a.
(ScottyError e, Monad m) =>
e -> ActionT e m a
S.raise Except
ThingNotFound
  where
    opts :: Options
opts = Options
forall a. Default a => a
def {settings :: Settings
S.settings = Settings -> Settings
settings Settings
defaultSettings}
    settings :: Settings -> Settings
settings = Int -> Settings -> Settings
setPort Int
port (Settings -> Settings)
-> (Settings -> Settings) -> Settings -> Settings
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HostPreference -> Settings -> Settings
setHost (String -> HostPreference
forall a. IsString a => String -> a
fromString String
host)

price :: (MonadUnliftIO m, MonadLoggerIO m)
      => Network
      -> TVar (HashMap Text BinfoTicker)
      -> m ()
price :: Network -> TVar (HashMap Text BinfoTicker) -> m ()
price net :: Network
net v :: TVar (HashMap Text BinfoTicker)
v =
    case Maybe String
code of
        Nothing -> () -> m ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
        Just s :: String
s  -> String -> m ()
forall (f :: * -> *) b.
(MonadUnliftIO f, MonadLogger f) =>
String -> f b
go String
s
  where
    code :: Maybe String
code | Network
net Network -> Network -> Bool
forall a. Eq a => a -> a -> Bool
== Network
btc = String -> Maybe String
forall a. a -> Maybe a
Just "btc"
         | Network
net Network -> Network -> Bool
forall a. Eq a => a -> a -> Bool
== Network
bch = String -> Maybe String
forall a. a -> Maybe a
Just "bch"
         | Bool
otherwise = Maybe String
forall a. Maybe a
Nothing
    go :: String -> f b
go s :: String
s = f () -> f b
forall (f :: * -> *) a b. Applicative f => f a -> f b
forever (f () -> f b) -> f () -> f b
forall a b. (a -> b) -> a -> b
$ do
        let err :: a -> m ()
err e :: a
e = $(Text
LogLevel
String -> String -> String -> CharPos -> CharPos -> Loc
Loc -> Text -> LogLevel -> Text -> m ()
forall (m :: * -> *) msg.
(MonadLogger m, ToLogStr msg) =>
Loc -> Text -> LogLevel -> msg -> m ()
monadLoggerLog :: forall (m :: * -> *) msg.
(MonadLogger m, ToLogStr msg) =>
Loc -> Text -> LogLevel -> msg -> m ()
b :: Text
a :: Text
logErrorS) "Price" (Text -> m ()) -> Text -> m ()
forall a b. (a -> b) -> a -> b
$ String -> Text
forall a b. ConvertibleStrings a b => a -> b
cs (a -> String
forall a. Show a => a -> String
show a
e)
            url :: String
url = "https://api.blockchain.info/ticker" String -> ShowS
forall a. Semigroup a => a -> a -> a
<> "?" String -> ShowS
forall a. Semigroup a => a -> a -> a
<>
                  "base" String -> ShowS
forall a. Semigroup a => a -> a -> a
<> "=" String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
s
        (SomeException -> f ()) -> f () -> f ()
forall (m :: * -> *) a.
MonadUnliftIO m =>
(SomeException -> m a) -> m a -> m a
handleAny SomeException -> f ()
forall (m :: * -> *) a. (MonadLogger m, Show a) => a -> m ()
err (f () -> f ()) -> f () -> f ()
forall a b. (a -> b) -> a -> b
$ do
            Response (HashMap Text BinfoTicker)
r <- IO (Response (HashMap Text BinfoTicker))
-> f (Response (HashMap Text BinfoTicker))
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Response (HashMap Text BinfoTicker))
 -> f (Response (HashMap Text BinfoTicker)))
-> IO (Response (HashMap Text BinfoTicker))
-> f (Response (HashMap Text BinfoTicker))
forall a b. (a -> b) -> a -> b
$ Response ByteString -> IO (Response (HashMap Text BinfoTicker))
forall (m :: * -> *) a.
(MonadThrow m, FromJSON a) =>
Response ByteString -> m (Response a)
Wreq.asJSON (Response ByteString -> IO (Response (HashMap Text BinfoTicker)))
-> IO (Response ByteString)
-> IO (Response (HashMap Text BinfoTicker))
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< String -> IO (Response ByteString)
Wreq.get String
url
            STM () -> f ()
forall (m :: * -> *) a. MonadIO m => STM a -> m a
atomically (STM () -> f ())
-> (HashMap Text BinfoTicker -> STM ())
-> HashMap Text BinfoTicker
-> f ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TVar (HashMap Text BinfoTicker)
-> HashMap Text BinfoTicker -> STM ()
forall a. TVar a -> a -> STM ()
writeTVar TVar (HashMap Text BinfoTicker)
v (HashMap Text BinfoTicker -> f ())
-> HashMap Text BinfoTicker -> f ()
forall a b. (a -> b) -> a -> b
$ Response (HashMap Text BinfoTicker)
r Response (HashMap Text BinfoTicker)
-> Getting
     (HashMap Text BinfoTicker)
     (Response (HashMap Text BinfoTicker))
     (HashMap Text BinfoTicker)
-> HashMap Text BinfoTicker
forall s a. s -> Getting a s a -> a
^. Getting
  (HashMap Text BinfoTicker)
  (Response (HashMap Text BinfoTicker))
  (HashMap Text BinfoTicker)
forall body0 body1.
Lens (Response body0) (Response body1) body0 body1
Wreq.responseBody
        Int -> f ()
forall (m :: * -> *). MonadIO m => Int -> m ()
threadDelay (Int -> f ()) -> Int -> f ()
forall a b. (a -> b) -> a -> b
$ 5 Int -> Int -> Int
forall a. Num a => a -> a -> a
* 60 Int -> Int -> Int
forall a. Num a => a -> a -> a
* 1000 Int -> Int -> Int
forall a. Num a => a -> a -> a
* 1000 -- five minutes


defHandler :: Monad m => Except -> WebT m ()
defHandler :: Except -> WebT m ()
defHandler e :: Except
e = do
    SerialAs
proto <- Bool -> ActionT Except (ReaderT WebConfig m) SerialAs
forall (m :: * -> *). Monad m => Bool -> ActionT Except m SerialAs
setupContentType Bool
False
    case Except
e of
        ThingNotFound -> Status -> WebT m ()
forall (m :: * -> *) e. Monad m => Status -> ActionT e m ()
S.status Status
status404
        BadRequest    -> Status -> WebT m ()
forall (m :: * -> *) e. Monad m => Status -> ActionT e m ()
S.status Status
status400
        UserError _   -> Status -> WebT m ()
forall (m :: * -> *) e. Monad m => Status -> ActionT e m ()
S.status Status
status400
        StringError _ -> Status -> WebT m ()
forall (m :: * -> *) e. Monad m => Status -> ActionT e m ()
S.status Status
status400
        ServerError   -> Status -> WebT m ()
forall (m :: * -> *) e. Monad m => Status -> ActionT e m ()
S.status Status
status500
        BlockTooLarge -> Status -> WebT m ()
forall (m :: * -> *) e. Monad m => Status -> ActionT e m ()
S.status Status
status403
    ByteString -> WebT m ()
forall (m :: * -> *) e. Monad m => ByteString -> ActionT e m ()
S.raw (ByteString -> WebT m ()) -> ByteString -> WebT m ()
forall a b. (a -> b) -> a -> b
$ SerialAs
-> (Except -> Encoding)
-> (Except -> Value)
-> Except
-> ByteString
forall a.
Serialize a =>
SerialAs -> (a -> Encoding) -> (a -> Value) -> a -> ByteString
protoSerial SerialAs
proto Except -> Encoding
forall a. ToJSON a => a -> Encoding
toEncoding Except -> Value
forall a. ToJSON a => a -> Value
toJSON Except
e

handlePaths ::
       (MonadUnliftIO m, MonadLoggerIO m)
    => TVar (HashMap Text BinfoTicker)
    -> S.ScottyT Except (ReaderT WebConfig m) ()
handlePaths :: TVar (HashMap Text BinfoTicker)
-> ScottyT Except (ReaderT WebConfig m) ()
handlePaths ticker :: TVar (HashMap Text BinfoTicker)
ticker = do
    -- Block Paths
    WebT m GetBlock
-> (GetBlock -> WebT m BlockData)
-> (Network -> BlockData -> Encoding)
-> (Network -> BlockData -> Value)
-> ScottyT Except (ReaderT WebConfig m) ()
forall a b (m :: * -> *).
(ApiResource a b, MonadIO m) =>
WebT m a
-> (a -> WebT m b)
-> (Network -> b -> Encoding)
-> (Network -> b -> Value)
-> ScottyT Except (ReaderT WebConfig m) ()
pathPretty
        (BlockHash -> NoTx -> GetBlock
GetBlock (BlockHash -> NoTx -> GetBlock)
-> ActionT Except (ReaderT WebConfig m) BlockHash
-> ActionT Except (ReaderT WebConfig m) (NoTx -> GetBlock)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ActionT Except (ReaderT WebConfig m) BlockHash
forall a (m :: * -> *). (Param a, Monad m) => WebT m a
paramLazy ActionT Except (ReaderT WebConfig m) (NoTx -> GetBlock)
-> ActionT Except (ReaderT WebConfig m) NoTx -> WebT m GetBlock
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ActionT Except (ReaderT WebConfig m) NoTx
forall a (m :: * -> *). (Default a, Param a, Monad m) => WebT m a
paramDef)
        GetBlock -> WebT m BlockData
forall (m :: * -> *).
(MonadUnliftIO m, MonadLoggerIO m) =>
GetBlock -> WebT m BlockData
scottyBlock
        Network -> BlockData -> Encoding
blockDataToEncoding
        Network -> BlockData -> Value
blockDataToJSON
    WebT m GetBlocks
-> (GetBlocks -> WebT m [BlockData])
-> (Network -> [BlockData] -> Encoding)
-> (Network -> [BlockData] -> Value)
-> ScottyT Except (ReaderT WebConfig m) ()
forall a b (m :: * -> *).
(ApiResource a b, MonadIO m) =>
WebT m a
-> (a -> WebT m b)
-> (Network -> b -> Encoding)
-> (Network -> b -> Value)
-> ScottyT Except (ReaderT WebConfig m) ()
pathCompact
        ([BlockHash] -> NoTx -> GetBlocks
GetBlocks ([BlockHash] -> NoTx -> GetBlocks)
-> ActionT Except (ReaderT WebConfig m) [BlockHash]
-> ActionT Except (ReaderT WebConfig m) (NoTx -> GetBlocks)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ActionT Except (ReaderT WebConfig m) [BlockHash]
forall a (m :: * -> *). (Param a, Monad m) => WebT m a
param ActionT Except (ReaderT WebConfig m) (NoTx -> GetBlocks)
-> ActionT Except (ReaderT WebConfig m) NoTx -> WebT m GetBlocks
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ActionT Except (ReaderT WebConfig m) NoTx
forall a (m :: * -> *). (Default a, Param a, Monad m) => WebT m a
paramDef)
        GetBlocks -> WebT m [BlockData]
forall (m :: * -> *).
(MonadUnliftIO m, MonadLoggerIO m) =>
GetBlocks -> WebT m [BlockData]
scottyBlocks
        ((BlockData -> Encoding) -> [BlockData] -> Encoding
forall a. (a -> Encoding) -> [a] -> Encoding
list ((BlockData -> Encoding) -> [BlockData] -> Encoding)
-> (Network -> BlockData -> Encoding)
-> Network
-> [BlockData]
-> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Network -> BlockData -> Encoding
blockDataToEncoding)
        ((Network -> BlockData -> Value) -> Network -> [BlockData] -> Value
forall a t a. ToJSON a => (t -> a -> a) -> t -> [a] -> Value
json_list Network -> BlockData -> Value
blockDataToJSON)
    WebT m GetBlockRaw
-> (GetBlockRaw -> WebT m (RawResult Block))
-> (Network -> RawResult Block -> Encoding)
-> (Network -> RawResult Block -> Value)
-> ScottyT Except (ReaderT WebConfig m) ()
forall a b (m :: * -> *).
(ApiResource a b, MonadIO m) =>
WebT m a
-> (a -> WebT m b)
-> (Network -> b -> Encoding)
-> (Network -> b -> Value)
-> ScottyT Except (ReaderT WebConfig m) ()
pathCompact
        (BlockHash -> GetBlockRaw
GetBlockRaw (BlockHash -> GetBlockRaw)
-> ActionT Except (ReaderT WebConfig m) BlockHash
-> WebT m GetBlockRaw
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ActionT Except (ReaderT WebConfig m) BlockHash
forall a (m :: * -> *). (Param a, Monad m) => WebT m a
paramLazy)
        GetBlockRaw -> WebT m (RawResult Block)
forall (m :: * -> *).
(MonadUnliftIO m, MonadLoggerIO m) =>
GetBlockRaw -> WebT m (RawResult Block)
scottyBlockRaw
        ((RawResult Block -> Encoding)
-> Network -> RawResult Block -> Encoding
forall a b. a -> b -> a
const RawResult Block -> Encoding
forall a. ToJSON a => a -> Encoding
toEncoding)
        ((RawResult Block -> Value) -> Network -> RawResult Block -> Value
forall a b. a -> b -> a
const RawResult Block -> Value
forall a. ToJSON a => a -> Value
toJSON)
    WebT m GetBlockBest
-> (GetBlockBest -> WebT m BlockData)
-> (Network -> BlockData -> Encoding)
-> (Network -> BlockData -> Value)
-> ScottyT Except (ReaderT WebConfig m) ()
forall a b (m :: * -> *).
(ApiResource a b, MonadIO m) =>
WebT m a
-> (a -> WebT m b)
-> (Network -> b -> Encoding)
-> (Network -> b -> Value)
-> ScottyT Except (ReaderT WebConfig m) ()
pathPretty
        (NoTx -> GetBlockBest
GetBlockBest (NoTx -> GetBlockBest)
-> ActionT Except (ReaderT WebConfig m) NoTx -> WebT m GetBlockBest
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ActionT Except (ReaderT WebConfig m) NoTx
forall a (m :: * -> *). (Default a, Param a, Monad m) => WebT m a
paramDef)
        GetBlockBest -> WebT m BlockData
forall (m :: * -> *).
(MonadUnliftIO m, MonadLoggerIO m) =>
GetBlockBest -> WebT m BlockData
scottyBlockBest
        Network -> BlockData -> Encoding
blockDataToEncoding
        Network -> BlockData -> Value
blockDataToJSON
    WebT m GetBlockBestRaw
-> (GetBlockBestRaw -> WebT m (RawResult Block))
-> (Network -> RawResult Block -> Encoding)
-> (Network -> RawResult Block -> Value)
-> ScottyT Except (ReaderT WebConfig m) ()
forall a b (m :: * -> *).
(ApiResource a b, MonadIO m) =>
WebT m a
-> (a -> WebT m b)
-> (Network -> b -> Encoding)
-> (Network -> b -> Value)
-> ScottyT Except (ReaderT WebConfig m) ()
pathCompact
        (GetBlockBestRaw
GetBlockBestRaw GetBlockBestRaw
-> (GetBlockBestRaw -> WebT m GetBlockBestRaw)
-> WebT m GetBlockBestRaw
forall a b. a -> (a -> b) -> b
& GetBlockBestRaw -> WebT m GetBlockBestRaw
forall (m :: * -> *) a. Monad m => a -> m a
return)
        GetBlockBestRaw -> WebT m (RawResult Block)
forall (m :: * -> *).
(MonadUnliftIO m, MonadLoggerIO m) =>
GetBlockBestRaw -> WebT m (RawResult Block)
scottyBlockBestRaw
        ((RawResult Block -> Encoding)
-> Network -> RawResult Block -> Encoding
forall a b. a -> b -> a
const RawResult Block -> Encoding
forall a. ToJSON a => a -> Encoding
toEncoding)
        ((RawResult Block -> Value) -> Network -> RawResult Block -> Value
forall a b. a -> b -> a
const RawResult Block -> Value
forall a. ToJSON a => a -> Value
toJSON)
    WebT m GetBlockLatest
-> (GetBlockLatest -> WebT m [BlockData])
-> (Network -> [BlockData] -> Encoding)
-> (Network -> [BlockData] -> Value)
-> ScottyT Except (ReaderT WebConfig m) ()
forall a b (m :: * -> *).
(ApiResource a b, MonadIO m) =>
WebT m a
-> (a -> WebT m b)
-> (Network -> b -> Encoding)
-> (Network -> b -> Value)
-> ScottyT Except (ReaderT WebConfig m) ()
pathCompact
        (NoTx -> GetBlockLatest
GetBlockLatest (NoTx -> GetBlockLatest)
-> ActionT Except (ReaderT WebConfig m) NoTx
-> WebT m GetBlockLatest
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ActionT Except (ReaderT WebConfig m) NoTx
forall a (m :: * -> *). (Default a, Param a, Monad m) => WebT m a
paramDef)
        GetBlockLatest -> WebT m [BlockData]
forall (m :: * -> *).
(MonadUnliftIO m, MonadLoggerIO m) =>
GetBlockLatest -> WebT m [BlockData]
scottyBlockLatest
        ((BlockData -> Encoding) -> [BlockData] -> Encoding
forall a. (a -> Encoding) -> [a] -> Encoding
list ((BlockData -> Encoding) -> [BlockData] -> Encoding)
-> (Network -> BlockData -> Encoding)
-> Network
-> [BlockData]
-> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Network -> BlockData -> Encoding
blockDataToEncoding)
        ((Network -> BlockData -> Value) -> Network -> [BlockData] -> Value
forall a t a. ToJSON a => (t -> a -> a) -> t -> [a] -> Value
json_list Network -> BlockData -> Value
blockDataToJSON)
    WebT m GetBlockHeight
-> (GetBlockHeight -> WebT m [BlockData])
-> (Network -> [BlockData] -> Encoding)
-> (Network -> [BlockData] -> Value)
-> ScottyT Except (ReaderT WebConfig m) ()
forall a b (m :: * -> *).
(ApiResource a b, MonadIO m) =>
WebT m a
-> (a -> WebT m b)
-> (Network -> b -> Encoding)
-> (Network -> b -> Value)
-> ScottyT Except (ReaderT WebConfig m) ()
pathPretty
        (HeightParam -> NoTx -> GetBlockHeight
GetBlockHeight (HeightParam -> NoTx -> GetBlockHeight)
-> ActionT Except (ReaderT WebConfig m) HeightParam
-> ActionT Except (ReaderT WebConfig m) (NoTx -> GetBlockHeight)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ActionT Except (ReaderT WebConfig m) HeightParam
forall a (m :: * -> *). (Param a, Monad m) => WebT m a
paramLazy ActionT Except (ReaderT WebConfig m) (NoTx -> GetBlockHeight)
-> ActionT Except (ReaderT WebConfig m) NoTx
-> WebT m GetBlockHeight
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ActionT Except (ReaderT WebConfig m) NoTx
forall a (m :: * -> *). (Default a, Param a, Monad m) => WebT m a
paramDef)
        GetBlockHeight -> WebT m [BlockData]
forall (m :: * -> *).
(MonadUnliftIO m, MonadLoggerIO m) =>
GetBlockHeight -> WebT m [BlockData]
scottyBlockHeight
        ((BlockData -> Encoding) -> [BlockData] -> Encoding
forall a. (a -> Encoding) -> [a] -> Encoding
list ((BlockData -> Encoding) -> [BlockData] -> Encoding)
-> (Network -> BlockData -> Encoding)
-> Network
-> [BlockData]
-> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Network -> BlockData -> Encoding
blockDataToEncoding)
        ((Network -> BlockData -> Value) -> Network -> [BlockData] -> Value
forall a t a. ToJSON a => (t -> a -> a) -> t -> [a] -> Value
json_list Network -> BlockData -> Value
blockDataToJSON)
    WebT m GetBlockHeights
-> (GetBlockHeights -> WebT m [BlockData])
-> (Network -> [BlockData] -> Encoding)
-> (Network -> [BlockData] -> Value)
-> ScottyT Except (ReaderT WebConfig m) ()
forall a b (m :: * -> *).
(ApiResource a b, MonadIO m) =>
WebT m a
-> (a -> WebT m b)
-> (Network -> b -> Encoding)
-> (Network -> b -> Value)
-> ScottyT Except (ReaderT WebConfig m) ()
pathCompact
        (HeightsParam -> NoTx -> GetBlockHeights
GetBlockHeights (HeightsParam -> NoTx -> GetBlockHeights)
-> ActionT Except (ReaderT WebConfig m) HeightsParam
-> ActionT Except (ReaderT WebConfig m) (NoTx -> GetBlockHeights)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ActionT Except (ReaderT WebConfig m) HeightsParam
forall a (m :: * -> *). (Param a, Monad m) => WebT m a
param ActionT Except (ReaderT WebConfig m) (NoTx -> GetBlockHeights)
-> ActionT Except (ReaderT WebConfig m) NoTx
-> WebT m GetBlockHeights
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ActionT Except (ReaderT WebConfig m) NoTx
forall a (m :: * -> *). (Default a, Param a, Monad m) => WebT m a
paramDef)
        GetBlockHeights -> WebT m [BlockData]
forall (m :: * -> *).
(MonadUnliftIO m, MonadLoggerIO m) =>
GetBlockHeights -> WebT m [BlockData]
scottyBlockHeights
        ((BlockData -> Encoding) -> [BlockData] -> Encoding
forall a. (a -> Encoding) -> [a] -> Encoding
list ((BlockData -> Encoding) -> [BlockData] -> Encoding)
-> (Network -> BlockData -> Encoding)
-> Network
-> [BlockData]
-> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Network -> BlockData -> Encoding
blockDataToEncoding)
        ((Network -> BlockData -> Value) -> Network -> [BlockData] -> Value
forall a t a. ToJSON a => (t -> a -> a) -> t -> [a] -> Value
json_list Network -> BlockData -> Value
blockDataToJSON)
    WebT m GetBlockHeightRaw
-> (GetBlockHeightRaw -> WebT m (RawResultList Block))
-> (Network -> RawResultList Block -> Encoding)
-> (Network -> RawResultList Block -> Value)
-> ScottyT Except (ReaderT WebConfig m) ()
forall a b (m :: * -> *).
(ApiResource a b, MonadIO m) =>
WebT m a
-> (a -> WebT m b)
-> (Network -> b -> Encoding)
-> (Network -> b -> Value)
-> ScottyT Except (ReaderT WebConfig m) ()
pathCompact
        (HeightParam -> GetBlockHeightRaw
GetBlockHeightRaw (HeightParam -> GetBlockHeightRaw)
-> ActionT Except (ReaderT WebConfig m) HeightParam
-> WebT m GetBlockHeightRaw
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ActionT Except (ReaderT WebConfig m) HeightParam
forall a (m :: * -> *). (Param a, Monad m) => WebT m a
paramLazy)
        GetBlockHeightRaw -> WebT m (RawResultList Block)
forall (m :: * -> *).
(MonadUnliftIO m, MonadLoggerIO m) =>
GetBlockHeightRaw -> WebT m (RawResultList Block)
scottyBlockHeightRaw
        ((RawResultList Block -> Encoding)
-> Network -> RawResultList Block -> Encoding
forall a b. a -> b -> a
const RawResultList Block -> Encoding
forall a. ToJSON a => a -> Encoding
toEncoding)
        ((RawResultList Block -> Value)
-> Network -> RawResultList Block -> Value
forall a b. a -> b -> a
const RawResultList Block -> Value
forall a. ToJSON a => a -> Value
toJSON)
    WebT m GetBlockTime
-> (GetBlockTime -> WebT m BlockData)
-> (Network -> BlockData -> Encoding)
-> (Network -> BlockData -> Value)
-> ScottyT Except (ReaderT WebConfig m) ()
forall a b (m :: * -> *).
(ApiResource a b, MonadIO m) =>
WebT m a
-> (a -> WebT m b)
-> (Network -> b -> Encoding)
-> (Network -> b -> Value)
-> ScottyT Except (ReaderT WebConfig m) ()
pathPretty
        (TimeParam -> NoTx -> GetBlockTime
GetBlockTime (TimeParam -> NoTx -> GetBlockTime)
-> ActionT Except (ReaderT WebConfig m) TimeParam
-> ActionT Except (ReaderT WebConfig m) (NoTx -> GetBlockTime)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ActionT Except (ReaderT WebConfig m) TimeParam
forall a (m :: * -> *). (Param a, Monad m) => WebT m a
paramLazy ActionT Except (ReaderT WebConfig m) (NoTx -> GetBlockTime)
-> ActionT Except (ReaderT WebConfig m) NoTx -> WebT m GetBlockTime
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ActionT Except (ReaderT WebConfig m) NoTx
forall a (m :: * -> *). (Default a, Param a, Monad m) => WebT m a
paramDef)
        GetBlockTime -> WebT m BlockData
forall (m :: * -> *).
(MonadUnliftIO m, MonadLoggerIO m) =>
GetBlockTime -> WebT m BlockData
scottyBlockTime
        Network -> BlockData -> Encoding
blockDataToEncoding
        Network -> BlockData -> Value
blockDataToJSON
    WebT m GetBlockTimeRaw
-> (GetBlockTimeRaw -> WebT m (RawResult Block))
-> (Network -> RawResult Block -> Encoding)
-> (Network -> RawResult Block -> Value)
-> ScottyT Except (ReaderT WebConfig m) ()
forall a b (m :: * -> *).
(ApiResource a b, MonadIO m) =>
WebT m a
-> (a -> WebT m b)
-> (Network -> b -> Encoding)
-> (Network -> b -> Value)
-> ScottyT Except (ReaderT WebConfig m) ()
pathCompact
        (TimeParam -> GetBlockTimeRaw
GetBlockTimeRaw (TimeParam -> GetBlockTimeRaw)
-> ActionT Except (ReaderT WebConfig m) TimeParam
-> WebT m GetBlockTimeRaw
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ActionT Except (ReaderT WebConfig m) TimeParam
forall a (m :: * -> *). (Param a, Monad m) => WebT m a
paramLazy)
        GetBlockTimeRaw -> WebT m (RawResult Block)
forall (m :: * -> *).
(MonadUnliftIO m, MonadLoggerIO m) =>
GetBlockTimeRaw -> WebT m (RawResult Block)
scottyBlockTimeRaw
        ((RawResult Block -> Encoding)
-> Network -> RawResult Block -> Encoding
forall a b. a -> b -> a
const RawResult Block -> Encoding
forall a. ToJSON a => a -> Encoding
toEncoding)
        ((RawResult Block -> Value) -> Network -> RawResult Block -> Value
forall a b. a -> b -> a
const RawResult Block -> Value
forall a. ToJSON a => a -> Value
toJSON)
    WebT m GetBlockMTP
-> (GetBlockMTP -> WebT m BlockData)
-> (Network -> BlockData -> Encoding)
-> (Network -> BlockData -> Value)
-> ScottyT Except (ReaderT WebConfig m) ()
forall a b (m :: * -> *).
(ApiResource a b, MonadIO m) =>
WebT m a
-> (a -> WebT m b)
-> (Network -> b -> Encoding)
-> (Network -> b -> Value)
-> ScottyT Except (ReaderT WebConfig m) ()
pathPretty
        (TimeParam -> NoTx -> GetBlockMTP
GetBlockMTP (TimeParam -> NoTx -> GetBlockMTP)
-> ActionT Except (ReaderT WebConfig m) TimeParam
-> ActionT Except (ReaderT WebConfig m) (NoTx -> GetBlockMTP)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ActionT Except (ReaderT WebConfig m) TimeParam
forall a (m :: * -> *). (Param a, Monad m) => WebT m a
paramLazy ActionT Except (ReaderT WebConfig m) (NoTx -> GetBlockMTP)
-> ActionT Except (ReaderT WebConfig m) NoTx -> WebT m GetBlockMTP
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ActionT Except (ReaderT WebConfig m) NoTx
forall a (m :: * -> *). (Default a, Param a, Monad m) => WebT m a
paramDef)
        GetBlockMTP -> WebT m BlockData
forall (m :: * -> *).
(MonadUnliftIO m, MonadLoggerIO m) =>
GetBlockMTP -> WebT m BlockData
scottyBlockMTP
        Network -> BlockData -> Encoding
blockDataToEncoding
        Network -> BlockData -> Value
blockDataToJSON
    WebT m GetBlockMTPRaw
-> (GetBlockMTPRaw -> WebT m (RawResult Block))
-> (Network -> RawResult Block -> Encoding)
-> (Network -> RawResult Block -> Value)
-> ScottyT Except (ReaderT WebConfig m) ()
forall a b (m :: * -> *).
(ApiResource a b, MonadIO m) =>
WebT m a
-> (a -> WebT m b)
-> (Network -> b -> Encoding)
-> (Network -> b -> Value)
-> ScottyT Except (ReaderT WebConfig m) ()
pathCompact
        (TimeParam -> GetBlockMTPRaw
GetBlockMTPRaw (TimeParam -> GetBlockMTPRaw)
-> ActionT Except (ReaderT WebConfig m) TimeParam
-> WebT m GetBlockMTPRaw
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ActionT Except (ReaderT WebConfig m) TimeParam
forall a (m :: * -> *). (Param a, Monad m) => WebT m a
paramLazy)
        GetBlockMTPRaw -> WebT m (RawResult Block)
forall (m :: * -> *).
(MonadUnliftIO m, MonadLoggerIO m) =>
GetBlockMTPRaw -> WebT m (RawResult Block)
scottyBlockMTPRaw
        ((RawResult Block -> Encoding)
-> Network -> RawResult Block -> Encoding
forall a b. a -> b -> a
const RawResult Block -> Encoding
forall a. ToJSON a => a -> Encoding
toEncoding)
        ((RawResult Block -> Value) -> Network -> RawResult Block -> Value
forall a b. a -> b -> a
const RawResult Block -> Value
forall a. ToJSON a => a -> Value
toJSON)
    -- Transaction Paths
    WebT m GetTx
-> (GetTx -> WebT m Transaction)
-> (Network -> Transaction -> Encoding)
-> (Network -> Transaction -> Value)
-> ScottyT Except (ReaderT WebConfig m) ()
forall a b (m :: * -> *).
(ApiResource a b, MonadIO m) =>
WebT m a
-> (a -> WebT m b)
-> (Network -> b -> Encoding)
-> (Network -> b -> Value)
-> ScottyT Except (ReaderT WebConfig m) ()
pathPretty
        (TxHash -> GetTx
GetTx (TxHash -> GetTx)
-> ActionT Except (ReaderT WebConfig m) TxHash -> WebT m GetTx
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ActionT Except (ReaderT WebConfig m) TxHash
forall a (m :: * -> *). (Param a, Monad m) => WebT m a
paramLazy)
        GetTx -> WebT m Transaction
forall (m :: * -> *).
(MonadUnliftIO m, MonadLoggerIO m) =>
GetTx -> WebT m Transaction
scottyTx
        Network -> Transaction -> Encoding
transactionToEncoding
        Network -> Transaction -> Value
transactionToJSON
    WebT m GetTxs
-> (GetTxs -> WebT m [Transaction])
-> (Network -> [Transaction] -> Encoding)
-> (Network -> [Transaction] -> Value)
-> ScottyT Except (ReaderT WebConfig m) ()
forall a b (m :: * -> *).
(ApiResource a b, MonadIO m) =>
WebT m a
-> (a -> WebT m b)
-> (Network -> b -> Encoding)
-> (Network -> b -> Value)
-> ScottyT Except (ReaderT WebConfig m) ()
pathCompact
        ([TxHash] -> GetTxs
GetTxs ([TxHash] -> GetTxs)
-> ActionT Except (ReaderT WebConfig m) [TxHash] -> WebT m GetTxs
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ActionT Except (ReaderT WebConfig m) [TxHash]
forall a (m :: * -> *). (Param a, Monad m) => WebT m a
param)
        GetTxs -> WebT m [Transaction]
forall (m :: * -> *).
(MonadUnliftIO m, MonadLoggerIO m) =>
GetTxs -> WebT m [Transaction]
scottyTxs
        ((Transaction -> Encoding) -> [Transaction] -> Encoding
forall a. (a -> Encoding) -> [a] -> Encoding
list ((Transaction -> Encoding) -> [Transaction] -> Encoding)
-> (Network -> Transaction -> Encoding)
-> Network
-> [Transaction]
-> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Network -> Transaction -> Encoding
transactionToEncoding)
        ((Network -> Transaction -> Value)
-> Network -> [Transaction] -> Value
forall a t a. ToJSON a => (t -> a -> a) -> t -> [a] -> Value
json_list Network -> Transaction -> Value
transactionToJSON)
    WebT m GetTxRaw
-> (GetTxRaw -> WebT m (RawResult Tx))
-> (Network -> RawResult Tx -> Encoding)
-> (Network -> RawResult Tx -> Value)
-> ScottyT Except (ReaderT WebConfig m) ()
forall a b (m :: * -> *).
(ApiResource a b, MonadIO m) =>
WebT m a
-> (a -> WebT m b)
-> (Network -> b -> Encoding)
-> (Network -> b -> Value)
-> ScottyT Except (ReaderT WebConfig m) ()
pathCompact
        (TxHash -> GetTxRaw
GetTxRaw (TxHash -> GetTxRaw)
-> ActionT Except (ReaderT WebConfig m) TxHash -> WebT m GetTxRaw
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ActionT Except (ReaderT WebConfig m) TxHash
forall a (m :: * -> *). (Param a, Monad m) => WebT m a
paramLazy)
        GetTxRaw -> WebT m (RawResult Tx)
forall (m :: * -> *).
(MonadUnliftIO m, MonadLoggerIO m) =>
GetTxRaw -> WebT m (RawResult Tx)
scottyTxRaw
        ((RawResult Tx -> Encoding) -> Network -> RawResult Tx -> Encoding
forall a b. a -> b -> a
const RawResult Tx -> Encoding
forall a. ToJSON a => a -> Encoding
toEncoding)
        ((RawResult Tx -> Value) -> Network -> RawResult Tx -> Value
forall a b. a -> b -> a
const RawResult Tx -> Value
forall a. ToJSON a => a -> Value
toJSON)
    WebT m GetTxsRaw
-> (GetTxsRaw -> WebT m (RawResultList Tx))
-> (Network -> RawResultList Tx -> Encoding)
-> (Network -> RawResultList Tx -> Value)
-> ScottyT Except (ReaderT WebConfig m) ()
forall a b (m :: * -> *).
(ApiResource a b, MonadIO m) =>
WebT m a
-> (a -> WebT m b)
-> (Network -> b -> Encoding)
-> (Network -> b -> Value)
-> ScottyT Except (ReaderT WebConfig m) ()
pathCompact
        ([TxHash] -> GetTxsRaw
GetTxsRaw ([TxHash] -> GetTxsRaw)
-> ActionT Except (ReaderT WebConfig m) [TxHash]
-> WebT m GetTxsRaw
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ActionT Except (ReaderT WebConfig m) [TxHash]
forall a (m :: * -> *). (Param a, Monad m) => WebT m a
param)
        GetTxsRaw -> WebT m (RawResultList Tx)
forall (m :: * -> *).
(MonadUnliftIO m, MonadLoggerIO m) =>
GetTxsRaw -> WebT m (RawResultList Tx)
scottyTxsRaw
        ((RawResultList Tx -> Encoding)
-> Network -> RawResultList Tx -> Encoding
forall a b. a -> b -> a
const RawResultList Tx -> Encoding
forall a. ToJSON a => a -> Encoding
toEncoding)
        ((RawResultList Tx -> Value) -> Network -> RawResultList Tx -> Value
forall a b. a -> b -> a
const RawResultList Tx -> Value
forall a. ToJSON a => a -> Value
toJSON)
    WebT m GetTxsBlock
-> (GetTxsBlock -> WebT m [Transaction])
-> (Network -> [Transaction] -> Encoding)
-> (Network -> [Transaction] -> Value)
-> ScottyT Except (ReaderT WebConfig m) ()
forall a b (m :: * -> *).
(ApiResource a b, MonadIO m) =>
WebT m a
-> (a -> WebT m b)
-> (Network -> b -> Encoding)
-> (Network -> b -> Value)
-> ScottyT Except (ReaderT WebConfig m) ()
pathCompact
        (BlockHash -> GetTxsBlock
GetTxsBlock (BlockHash -> GetTxsBlock)
-> ActionT Except (ReaderT WebConfig m) BlockHash
-> WebT m GetTxsBlock
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ActionT Except (ReaderT WebConfig m) BlockHash
forall a (m :: * -> *). (Param a, Monad m) => WebT m a
paramLazy)
        GetTxsBlock -> WebT m [Transaction]
forall (m :: * -> *).
(MonadUnliftIO m, MonadLoggerIO m) =>
GetTxsBlock -> WebT m [Transaction]
scottyTxsBlock
        ((Transaction -> Encoding) -> [Transaction] -> Encoding
forall a. (a -> Encoding) -> [a] -> Encoding
list ((Transaction -> Encoding) -> [Transaction] -> Encoding)
-> (Network -> Transaction -> Encoding)
-> Network
-> [Transaction]
-> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Network -> Transaction -> Encoding
transactionToEncoding)
        ((Network -> Transaction -> Value)
-> Network -> [Transaction] -> Value
forall a t a. ToJSON a => (t -> a -> a) -> t -> [a] -> Value
json_list Network -> Transaction -> Value
transactionToJSON)
    WebT m GetTxsBlockRaw
-> (GetTxsBlockRaw -> WebT m (RawResultList Tx))
-> (Network -> RawResultList Tx -> Encoding)
-> (Network -> RawResultList Tx -> Value)
-> ScottyT Except (ReaderT WebConfig m) ()
forall a b (m :: * -> *).
(ApiResource a b, MonadIO m) =>
WebT m a
-> (a -> WebT m b)
-> (Network -> b -> Encoding)
-> (Network -> b -> Value)
-> ScottyT Except (ReaderT WebConfig m) ()
pathCompact
        (BlockHash -> GetTxsBlockRaw
GetTxsBlockRaw (BlockHash -> GetTxsBlockRaw)
-> ActionT Except (ReaderT WebConfig m) BlockHash
-> WebT m GetTxsBlockRaw
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ActionT Except (ReaderT WebConfig m) BlockHash
forall a (m :: * -> *). (Param a, Monad m) => WebT m a
paramLazy)
        GetTxsBlockRaw -> WebT m (RawResultList Tx)
forall (m :: * -> *).
(MonadUnliftIO m, MonadLoggerIO m) =>
GetTxsBlockRaw -> WebT m (RawResultList Tx)
scottyTxsBlockRaw
        ((RawResultList Tx -> Encoding)
-> Network -> RawResultList Tx -> Encoding
forall a b. a -> b -> a
const RawResultList Tx -> Encoding
forall a. ToJSON a => a -> Encoding
toEncoding)
        ((RawResultList Tx -> Value) -> Network -> RawResultList Tx -> Value
forall a b. a -> b -> a
const RawResultList Tx -> Value
forall a. ToJSON a => a -> Value
toJSON)
    WebT m GetTxAfter
-> (GetTxAfter -> WebT m (GenericResult (Maybe Bool)))
-> (Network -> GenericResult (Maybe Bool) -> Encoding)
-> (Network -> GenericResult (Maybe Bool) -> Value)
-> ScottyT Except (ReaderT WebConfig m) ()
forall a b (m :: * -> *).
(ApiResource a b, MonadIO m) =>
WebT m a
-> (a -> WebT m b)
-> (Network -> b -> Encoding)
-> (Network -> b -> Value)
-> ScottyT Except (ReaderT WebConfig m) ()
pathCompact
        (TxHash -> HeightParam -> GetTxAfter
GetTxAfter (TxHash -> HeightParam -> GetTxAfter)
-> ActionT Except (ReaderT WebConfig m) TxHash
-> ActionT Except (ReaderT WebConfig m) (HeightParam -> GetTxAfter)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ActionT Except (ReaderT WebConfig m) TxHash
forall a (m :: * -> *). (Param a, Monad m) => WebT m a
paramLazy ActionT Except (ReaderT WebConfig m) (HeightParam -> GetTxAfter)
-> ActionT Except (ReaderT WebConfig m) HeightParam
-> WebT m GetTxAfter
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ActionT Except (ReaderT WebConfig m) HeightParam
forall a (m :: * -> *). (Param a, Monad m) => WebT m a
paramLazy)
        GetTxAfter -> WebT m (GenericResult (Maybe Bool))
forall (m :: * -> *).
(MonadUnliftIO m, MonadLoggerIO m) =>
GetTxAfter -> WebT m (GenericResult (Maybe Bool))
scottyTxAfter
        ((GenericResult (Maybe Bool) -> Encoding)
-> Network -> GenericResult (Maybe Bool) -> Encoding
forall a b. a -> b -> a
const GenericResult (Maybe Bool) -> Encoding
forall a. ToJSON a => a -> Encoding
toEncoding)
        ((GenericResult (Maybe Bool) -> Value)
-> Network -> GenericResult (Maybe Bool) -> Value
forall a b. a -> b -> a
const GenericResult (Maybe Bool) -> Value
forall a. ToJSON a => a -> Value
toJSON)
    WebT m PostTx
-> (PostTx -> WebT m TxId)
-> (Network -> TxId -> Encoding)
-> (Network -> TxId -> Value)
-> ScottyT Except (ReaderT WebConfig m) ()
forall a b (m :: * -> *).
(ApiResource a b, MonadIO m) =>
WebT m a
-> (a -> WebT m b)
-> (Network -> b -> Encoding)
-> (Network -> b -> Value)
-> ScottyT Except (ReaderT WebConfig m) ()
pathCompact
        (Tx -> PostTx
PostTx (Tx -> PostTx)
-> ActionT Except (ReaderT WebConfig m) Tx -> WebT m PostTx
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ActionT Except (ReaderT WebConfig m) Tx
forall (m :: * -> *) a. (MonadIO m, Serialize a) => WebT m a
parseBody)
        PostTx -> WebT m TxId
forall (m :: * -> *).
(MonadUnliftIO m, MonadLoggerIO m) =>
PostTx -> WebT m TxId
scottyPostTx
        ((TxId -> Encoding) -> Network -> TxId -> Encoding
forall a b. a -> b -> a
const TxId -> Encoding
forall a. ToJSON a => a -> Encoding
toEncoding)
        ((TxId -> Value) -> Network -> TxId -> Value
forall a b. a -> b -> a
const TxId -> Value
forall a. ToJSON a => a -> Value
toJSON)
    WebT m GetMempool
-> (GetMempool -> ActionT Except (ReaderT WebConfig m) [TxHash])
-> (Network -> [TxHash] -> Encoding)
-> (Network -> [TxHash] -> Value)
-> ScottyT Except (ReaderT WebConfig m) ()
forall a b (m :: * -> *).
(ApiResource a b, MonadIO m) =>
WebT m a
-> (a -> WebT m b)
-> (Network -> b -> Encoding)
-> (Network -> b -> Value)
-> ScottyT Except (ReaderT WebConfig m) ()
pathPretty
        (Maybe LimitParam -> OffsetParam -> GetMempool
GetMempool (Maybe LimitParam -> OffsetParam -> GetMempool)
-> ActionT Except (ReaderT WebConfig m) (Maybe LimitParam)
-> ActionT Except (ReaderT WebConfig m) (OffsetParam -> GetMempool)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ActionT Except (ReaderT WebConfig m) (Maybe LimitParam)
forall a (m :: * -> *). (Param a, Monad m) => WebT m (Maybe a)
paramOptional ActionT Except (ReaderT WebConfig m) (OffsetParam -> GetMempool)
-> ActionT Except (ReaderT WebConfig m) OffsetParam
-> WebT m GetMempool
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ActionT Except (ReaderT WebConfig m) OffsetParam
forall (m :: * -> *). Monad m => WebT m OffsetParam
parseOffset)
        GetMempool -> ActionT Except (ReaderT WebConfig m) [TxHash]
forall (m :: * -> *).
(MonadUnliftIO m, MonadLoggerIO m) =>
GetMempool -> WebT m [TxHash]
scottyMempool
        (([TxHash] -> Encoding) -> Network -> [TxHash] -> Encoding
forall a b. a -> b -> a
const [TxHash] -> Encoding
forall a. ToJSON a => a -> Encoding
toEncoding)
        (([TxHash] -> Value) -> Network -> [TxHash] -> Value
forall a b. a -> b -> a
const [TxHash] -> Value
forall a. ToJSON a => a -> Value
toJSON)
    -- Address Paths
    WebT m GetAddrTxs
-> (GetAddrTxs -> WebT m [TxRef])
-> (Network -> [TxRef] -> Encoding)
-> (Network -> [TxRef] -> Value)
-> ScottyT Except (ReaderT WebConfig m) ()
forall a b (m :: * -> *).
(ApiResource a b, MonadIO m) =>
WebT m a
-> (a -> WebT m b)
-> (Network -> b -> Encoding)
-> (Network -> b -> Value)
-> ScottyT Except (ReaderT WebConfig m) ()
pathPretty
        (Address -> LimitsParam -> GetAddrTxs
GetAddrTxs (Address -> LimitsParam -> GetAddrTxs)
-> ActionT Except (ReaderT WebConfig m) Address
-> ActionT Except (ReaderT WebConfig m) (LimitsParam -> GetAddrTxs)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ActionT Except (ReaderT WebConfig m) Address
forall a (m :: * -> *). (Param a, Monad m) => WebT m a
paramLazy ActionT Except (ReaderT WebConfig m) (LimitsParam -> GetAddrTxs)
-> ActionT Except (ReaderT WebConfig m) LimitsParam
-> WebT m GetAddrTxs
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ActionT Except (ReaderT WebConfig m) LimitsParam
forall (m :: * -> *). Monad m => WebT m LimitsParam
parseLimits)
        GetAddrTxs -> WebT m [TxRef]
forall (m :: * -> *).
(MonadUnliftIO m, MonadLoggerIO m) =>
GetAddrTxs -> WebT m [TxRef]
scottyAddrTxs
        (([TxRef] -> Encoding) -> Network -> [TxRef] -> Encoding
forall a b. a -> b -> a
const [TxRef] -> Encoding
forall a. ToJSON a => a -> Encoding
toEncoding)
        (([TxRef] -> Value) -> Network -> [TxRef] -> Value
forall a b. a -> b -> a
const [TxRef] -> Value
forall a. ToJSON a => a -> Value
toJSON)
    WebT m GetAddrsTxs
-> (GetAddrsTxs -> WebT m [TxRef])
-> (Network -> [TxRef] -> Encoding)
-> (Network -> [TxRef] -> Value)
-> ScottyT Except (ReaderT WebConfig m) ()
forall a b (m :: * -> *).
(ApiResource a b, MonadIO m) =>
WebT m a
-> (a -> WebT m b)
-> (Network -> b -> Encoding)
-> (Network -> b -> Value)
-> ScottyT Except (ReaderT WebConfig m) ()
pathCompact
        ([Address] -> LimitsParam -> GetAddrsTxs
GetAddrsTxs ([Address] -> LimitsParam -> GetAddrsTxs)
-> ActionT Except (ReaderT WebConfig m) [Address]
-> ActionT
     Except (ReaderT WebConfig m) (LimitsParam -> GetAddrsTxs)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ActionT Except (ReaderT WebConfig m) [Address]
forall a (m :: * -> *). (Param a, Monad m) => WebT m a
param ActionT Except (ReaderT WebConfig m) (LimitsParam -> GetAddrsTxs)
-> ActionT Except (ReaderT WebConfig m) LimitsParam
-> WebT m GetAddrsTxs
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ActionT Except (ReaderT WebConfig m) LimitsParam
forall (m :: * -> *). Monad m => WebT m LimitsParam
parseLimits)
        GetAddrsTxs -> WebT m [TxRef]
forall (m :: * -> *).
(MonadUnliftIO m, MonadLoggerIO m) =>
GetAddrsTxs -> WebT m [TxRef]
scottyAddrsTxs
        (([TxRef] -> Encoding) -> Network -> [TxRef] -> Encoding
forall a b. a -> b -> a
const [TxRef] -> Encoding
forall a. ToJSON a => a -> Encoding
toEncoding)
        (([TxRef] -> Value) -> Network -> [TxRef] -> Value
forall a b. a -> b -> a
const [TxRef] -> Value
forall a. ToJSON a => a -> Value
toJSON)
    WebT m GetAddrTxsFull
-> (GetAddrTxsFull -> WebT m [Transaction])
-> (Network -> [Transaction] -> Encoding)
-> (Network -> [Transaction] -> Value)
-> ScottyT Except (ReaderT WebConfig m) ()
forall a b (m :: * -> *).
(ApiResource a b, MonadIO m) =>
WebT m a
-> (a -> WebT m b)
-> (Network -> b -> Encoding)
-> (Network -> b -> Value)
-> ScottyT Except (ReaderT WebConfig m) ()
pathCompact
        (Address -> LimitsParam -> GetAddrTxsFull
GetAddrTxsFull (Address -> LimitsParam -> GetAddrTxsFull)
-> ActionT Except (ReaderT WebConfig m) Address
-> ActionT
     Except (ReaderT WebConfig m) (LimitsParam -> GetAddrTxsFull)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ActionT Except (ReaderT WebConfig m) Address
forall a (m :: * -> *). (Param a, Monad m) => WebT m a
paramLazy ActionT
  Except (ReaderT WebConfig m) (LimitsParam -> GetAddrTxsFull)
-> ActionT Except (ReaderT WebConfig m) LimitsParam
-> WebT m GetAddrTxsFull
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ActionT Except (ReaderT WebConfig m) LimitsParam
forall (m :: * -> *). Monad m => WebT m LimitsParam
parseLimits)
        GetAddrTxsFull -> WebT m [Transaction]
forall (m :: * -> *).
(MonadUnliftIO m, MonadLoggerIO m) =>
GetAddrTxsFull -> WebT m [Transaction]
scottyAddrTxsFull
        ((Transaction -> Encoding) -> [Transaction] -> Encoding
forall a. (a -> Encoding) -> [a] -> Encoding
list ((Transaction -> Encoding) -> [Transaction] -> Encoding)
-> (Network -> Transaction -> Encoding)
-> Network
-> [Transaction]
-> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Network -> Transaction -> Encoding
transactionToEncoding)
        ((Network -> Transaction -> Value)
-> Network -> [Transaction] -> Value
forall a t a. ToJSON a => (t -> a -> a) -> t -> [a] -> Value
json_list Network -> Transaction -> Value
transactionToJSON)
    WebT m GetAddrsTxsFull
-> (GetAddrsTxsFull -> WebT m [Transaction])
-> (Network -> [Transaction] -> Encoding)
-> (Network -> [Transaction] -> Value)
-> ScottyT Except (ReaderT WebConfig m) ()
forall a b (m :: * -> *).
(ApiResource a b, MonadIO m) =>
WebT m a
-> (a -> WebT m b)
-> (Network -> b -> Encoding)
-> (Network -> b -> Value)
-> ScottyT Except (ReaderT WebConfig m) ()
pathCompact
        ([Address] -> LimitsParam -> GetAddrsTxsFull
GetAddrsTxsFull ([Address] -> LimitsParam -> GetAddrsTxsFull)
-> ActionT Except (ReaderT WebConfig m) [Address]
-> ActionT
     Except (ReaderT WebConfig m) (LimitsParam -> GetAddrsTxsFull)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ActionT Except (ReaderT WebConfig m) [Address]
forall a (m :: * -> *). (Param a, Monad m) => WebT m a
param ActionT
  Except (ReaderT WebConfig m) (LimitsParam -> GetAddrsTxsFull)
-> ActionT Except (ReaderT WebConfig m) LimitsParam
-> WebT m GetAddrsTxsFull
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ActionT Except (ReaderT WebConfig m) LimitsParam
forall (m :: * -> *). Monad m => WebT m LimitsParam
parseLimits)
        GetAddrsTxsFull -> WebT m [Transaction]
forall (m :: * -> *).
(MonadUnliftIO m, MonadLoggerIO m) =>
GetAddrsTxsFull -> WebT m [Transaction]
scottyAddrsTxsFull
        ((Transaction -> Encoding) -> [Transaction] -> Encoding
forall a. (a -> Encoding) -> [a] -> Encoding
list ((Transaction -> Encoding) -> [Transaction] -> Encoding)
-> (Network -> Transaction -> Encoding)
-> Network
-> [Transaction]
-> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Network -> Transaction -> Encoding
transactionToEncoding)
        ((Network -> Transaction -> Value)
-> Network -> [Transaction] -> Value
forall a t a. ToJSON a => (t -> a -> a) -> t -> [a] -> Value
json_list Network -> Transaction -> Value
transactionToJSON)
    WebT m GetAddrBalance
-> (GetAddrBalance -> WebT m Balance)
-> (Network -> Balance -> Encoding)
-> (Network -> Balance -> Value)
-> ScottyT Except (ReaderT WebConfig m) ()
forall a b (m :: * -> *).
(ApiResource a b, MonadIO m) =>
WebT m a
-> (a -> WebT m b)
-> (Network -> b -> Encoding)
-> (Network -> b -> Value)
-> ScottyT Except (ReaderT WebConfig m) ()
pathPretty
        (Address -> GetAddrBalance
GetAddrBalance (Address -> GetAddrBalance)
-> ActionT Except (ReaderT WebConfig m) Address
-> WebT m GetAddrBalance
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ActionT Except (ReaderT WebConfig m) Address
forall a (m :: * -> *). (Param a, Monad m) => WebT m a
paramLazy)
        GetAddrBalance -> WebT m Balance
forall (m :: * -> *).
(MonadUnliftIO m, MonadLoggerIO m) =>
GetAddrBalance -> WebT m Balance
scottyAddrBalance
        Network -> Balance -> Encoding
balanceToEncoding
        Network -> Balance -> Value
balanceToJSON
    WebT m GetAddrsBalance
-> (GetAddrsBalance -> WebT m [Balance])
-> (Network -> [Balance] -> Encoding)
-> (Network -> [Balance] -> Value)
-> ScottyT Except (ReaderT WebConfig m) ()
forall a b (m :: * -> *).
(ApiResource a b, MonadIO m) =>
WebT m a
-> (a -> WebT m b)
-> (Network -> b -> Encoding)
-> (Network -> b -> Value)
-> ScottyT Except (ReaderT WebConfig m) ()
pathCompact
        ([Address] -> GetAddrsBalance
GetAddrsBalance ([Address] -> GetAddrsBalance)
-> ActionT Except (ReaderT WebConfig m) [Address]
-> WebT m GetAddrsBalance
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ActionT Except (ReaderT WebConfig m) [Address]
forall a (m :: * -> *). (Param a, Monad m) => WebT m a
param)
        GetAddrsBalance -> WebT m [Balance]
forall (m :: * -> *).
(MonadUnliftIO m, MonadLoggerIO m) =>
GetAddrsBalance -> WebT m [Balance]
scottyAddrsBalance
        ((Balance -> Encoding) -> [Balance] -> Encoding
forall a. (a -> Encoding) -> [a] -> Encoding
list ((Balance -> Encoding) -> [Balance] -> Encoding)
-> (Network -> Balance -> Encoding)
-> Network
-> [Balance]
-> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Network -> Balance -> Encoding
balanceToEncoding)
        ((Network -> Balance -> Value) -> Network -> [Balance] -> Value
forall a t a. ToJSON a => (t -> a -> a) -> t -> [a] -> Value
json_list Network -> Balance -> Value
balanceToJSON)
    WebT m GetAddrUnspent
-> (GetAddrUnspent -> WebT m [Unspent])
-> (Network -> [Unspent] -> Encoding)
-> (Network -> [Unspent] -> Value)
-> ScottyT Except (ReaderT WebConfig m) ()
forall a b (m :: * -> *).
(ApiResource a b, MonadIO m) =>
WebT m a
-> (a -> WebT m b)
-> (Network -> b -> Encoding)
-> (Network -> b -> Value)
-> ScottyT Except (ReaderT WebConfig m) ()
pathPretty
        (Address -> LimitsParam -> GetAddrUnspent
GetAddrUnspent (Address -> LimitsParam -> GetAddrUnspent)
-> ActionT Except (ReaderT WebConfig m) Address
-> ActionT
     Except (ReaderT WebConfig m) (LimitsParam -> GetAddrUnspent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ActionT Except (ReaderT WebConfig m) Address
forall a (m :: * -> *). (Param a, Monad m) => WebT m a
paramLazy ActionT
  Except (ReaderT WebConfig m) (LimitsParam -> GetAddrUnspent)
-> ActionT Except (ReaderT WebConfig m) LimitsParam
-> WebT m GetAddrUnspent
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ActionT Except (ReaderT WebConfig m) LimitsParam
forall (m :: * -> *). Monad m => WebT m LimitsParam
parseLimits)
        GetAddrUnspent -> WebT m [Unspent]
forall (m :: * -> *).
(MonadUnliftIO m, MonadLoggerIO m) =>
GetAddrUnspent -> WebT m [Unspent]
scottyAddrUnspent
        ((Unspent -> Encoding) -> [Unspent] -> Encoding
forall a. (a -> Encoding) -> [a] -> Encoding
list ((Unspent -> Encoding) -> [Unspent] -> Encoding)
-> (Network -> Unspent -> Encoding)
-> Network
-> [Unspent]
-> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Network -> Unspent -> Encoding
unspentToEncoding)
        ((Network -> Unspent -> Value) -> Network -> [Unspent] -> Value
forall a t a. ToJSON a => (t -> a -> a) -> t -> [a] -> Value
json_list Network -> Unspent -> Value
unspentToJSON)
    WebT m GetAddrsUnspent
-> (GetAddrsUnspent -> WebT m [Unspent])
-> (Network -> [Unspent] -> Encoding)
-> (Network -> [Unspent] -> Value)
-> ScottyT Except (ReaderT WebConfig m) ()
forall a b (m :: * -> *).
(ApiResource a b, MonadIO m) =>
WebT m a
-> (a -> WebT m b)
-> (Network -> b -> Encoding)
-> (Network -> b -> Value)
-> ScottyT Except (ReaderT WebConfig m) ()
pathCompact
        ([Address] -> LimitsParam -> GetAddrsUnspent
GetAddrsUnspent ([Address] -> LimitsParam -> GetAddrsUnspent)
-> ActionT Except (ReaderT WebConfig m) [Address]
-> ActionT
     Except (ReaderT WebConfig m) (LimitsParam -> GetAddrsUnspent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ActionT Except (ReaderT WebConfig m) [Address]
forall a (m :: * -> *). (Param a, Monad m) => WebT m a
param ActionT
  Except (ReaderT WebConfig m) (LimitsParam -> GetAddrsUnspent)
-> ActionT Except (ReaderT WebConfig m) LimitsParam
-> WebT m GetAddrsUnspent
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ActionT Except (ReaderT WebConfig m) LimitsParam
forall (m :: * -> *). Monad m => WebT m LimitsParam
parseLimits)
        GetAddrsUnspent -> WebT m [Unspent]
forall (m :: * -> *).
(MonadUnliftIO m, MonadLoggerIO m) =>
GetAddrsUnspent -> WebT m [Unspent]
scottyAddrsUnspent
        ((Unspent -> Encoding) -> [Unspent] -> Encoding
forall a. (a -> Encoding) -> [a] -> Encoding
list ((Unspent -> Encoding) -> [Unspent] -> Encoding)
-> (Network -> Unspent -> Encoding)
-> Network
-> [Unspent]
-> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Network -> Unspent -> Encoding
unspentToEncoding)
        ((Network -> Unspent -> Value) -> Network -> [Unspent] -> Value
forall a t a. ToJSON a => (t -> a -> a) -> t -> [a] -> Value
json_list Network -> Unspent -> Value
unspentToJSON)
    -- XPubs
    WebT m GetXPub
-> (GetXPub -> WebT m XPubSummary)
-> (Network -> XPubSummary -> Encoding)
-> (Network -> XPubSummary -> Value)
-> ScottyT Except (ReaderT WebConfig m) ()
forall a b (m :: * -> *).
(ApiResource a b, MonadIO m) =>
WebT m a
-> (a -> WebT m b)
-> (Network -> b -> Encoding)
-> (Network -> b -> Value)
-> ScottyT Except (ReaderT WebConfig m) ()
pathPretty
        (XPubKey -> DeriveType -> NoCache -> GetXPub
GetXPub (XPubKey -> DeriveType -> NoCache -> GetXPub)
-> ActionT Except (ReaderT WebConfig m) XPubKey
-> ActionT
     Except (ReaderT WebConfig m) (DeriveType -> NoCache -> GetXPub)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ActionT Except (ReaderT WebConfig m) XPubKey
forall a (m :: * -> *). (Param a, Monad m) => WebT m a
paramLazy ActionT
  Except (ReaderT WebConfig m) (DeriveType -> NoCache -> GetXPub)
-> ActionT Except (ReaderT WebConfig m) DeriveType
-> ActionT Except (ReaderT WebConfig m) (NoCache -> GetXPub)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ActionT Except (ReaderT WebConfig m) DeriveType
forall a (m :: * -> *). (Default a, Param a, Monad m) => WebT m a
paramDef ActionT Except (ReaderT WebConfig m) (NoCache -> GetXPub)
-> ActionT Except (ReaderT WebConfig m) NoCache -> WebT m GetXPub
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ActionT Except (ReaderT WebConfig m) NoCache
forall a (m :: * -> *). (Default a, Param a, Monad m) => WebT m a
paramDef)
        GetXPub -> WebT m XPubSummary
forall (m :: * -> *).
(MonadUnliftIO m, MonadLoggerIO m) =>
GetXPub -> WebT m XPubSummary
scottyXPub
        ((XPubSummary -> Encoding) -> Network -> XPubSummary -> Encoding
forall a b. a -> b -> a
const XPubSummary -> Encoding
forall a. ToJSON a => a -> Encoding
toEncoding)
        ((XPubSummary -> Value) -> Network -> XPubSummary -> Value
forall a b. a -> b -> a
const XPubSummary -> Value
forall a. ToJSON a => a -> Value
toJSON)
    WebT m GetXPubTxs
-> (GetXPubTxs -> WebT m [TxRef])
-> (Network -> [TxRef] -> Encoding)
-> (Network -> [TxRef] -> Value)
-> ScottyT Except (ReaderT WebConfig m) ()
forall a b (m :: * -> *).
(ApiResource a b, MonadIO m) =>
WebT m a
-> (a -> WebT m b)
-> (Network -> b -> Encoding)
-> (Network -> b -> Value)
-> ScottyT Except (ReaderT WebConfig m) ()
pathPretty
        (XPubKey -> DeriveType -> LimitsParam -> NoCache -> GetXPubTxs
GetXPubTxs (XPubKey -> DeriveType -> LimitsParam -> NoCache -> GetXPubTxs)
-> ActionT Except (ReaderT WebConfig m) XPubKey
-> ActionT
     Except
     (ReaderT WebConfig m)
     (DeriveType -> LimitsParam -> NoCache -> GetXPubTxs)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ActionT Except (ReaderT WebConfig m) XPubKey
forall a (m :: * -> *). (Param a, Monad m) => WebT m a
paramLazy ActionT
  Except
  (ReaderT WebConfig m)
  (DeriveType -> LimitsParam -> NoCache -> GetXPubTxs)
-> ActionT Except (ReaderT WebConfig m) DeriveType
-> ActionT
     Except (ReaderT WebConfig m) (LimitsParam -> NoCache -> GetXPubTxs)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ActionT Except (ReaderT WebConfig m) DeriveType
forall a (m :: * -> *). (Default a, Param a, Monad m) => WebT m a
paramDef ActionT
  Except (ReaderT WebConfig m) (LimitsParam -> NoCache -> GetXPubTxs)
-> ActionT Except (ReaderT WebConfig m) LimitsParam
-> ActionT Except (ReaderT WebConfig m) (NoCache -> GetXPubTxs)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ActionT Except (ReaderT WebConfig m) LimitsParam
forall (m :: * -> *). Monad m => WebT m LimitsParam
parseLimits ActionT Except (ReaderT WebConfig m) (NoCache -> GetXPubTxs)
-> ActionT Except (ReaderT WebConfig m) NoCache
-> WebT m GetXPubTxs
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ActionT Except (ReaderT WebConfig m) NoCache
forall a (m :: * -> *). (Default a, Param a, Monad m) => WebT m a
paramDef)
        GetXPubTxs -> WebT m [TxRef]
forall (m :: * -> *).
(MonadUnliftIO m, MonadLoggerIO m) =>
GetXPubTxs -> WebT m [TxRef]
scottyXPubTxs
        (([TxRef] -> Encoding) -> Network -> [TxRef] -> Encoding
forall a b. a -> b -> a
const [TxRef] -> Encoding
forall a. ToJSON a => a -> Encoding
toEncoding)
        (([TxRef] -> Value) -> Network -> [TxRef] -> Value
forall a b. a -> b -> a
const [TxRef] -> Value
forall a. ToJSON a => a -> Value
toJSON)
    WebT m GetXPubTxsFull
-> (GetXPubTxsFull -> WebT m [Transaction])
-> (Network -> [Transaction] -> Encoding)
-> (Network -> [Transaction] -> Value)
-> ScottyT Except (ReaderT WebConfig m) ()
forall a b (m :: * -> *).
(ApiResource a b, MonadIO m) =>
WebT m a
-> (a -> WebT m b)
-> (Network -> b -> Encoding)
-> (Network -> b -> Value)
-> ScottyT Except (ReaderT WebConfig m) ()
pathCompact
        (XPubKey -> DeriveType -> LimitsParam -> NoCache -> GetXPubTxsFull
GetXPubTxsFull (XPubKey -> DeriveType -> LimitsParam -> NoCache -> GetXPubTxsFull)
-> ActionT Except (ReaderT WebConfig m) XPubKey
-> ActionT
     Except
     (ReaderT WebConfig m)
     (DeriveType -> LimitsParam -> NoCache -> GetXPubTxsFull)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ActionT Except (ReaderT WebConfig m) XPubKey
forall a (m :: * -> *). (Param a, Monad m) => WebT m a
paramLazy ActionT
  Except
  (ReaderT WebConfig m)
  (DeriveType -> LimitsParam -> NoCache -> GetXPubTxsFull)
-> ActionT Except (ReaderT WebConfig m) DeriveType
-> ActionT
     Except
     (ReaderT WebConfig m)
     (LimitsParam -> NoCache -> GetXPubTxsFull)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ActionT Except (ReaderT WebConfig m) DeriveType
forall a (m :: * -> *). (Default a, Param a, Monad m) => WebT m a
paramDef ActionT
  Except
  (ReaderT WebConfig m)
  (LimitsParam -> NoCache -> GetXPubTxsFull)
-> ActionT Except (ReaderT WebConfig m) LimitsParam
-> ActionT Except (ReaderT WebConfig m) (NoCache -> GetXPubTxsFull)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ActionT Except (ReaderT WebConfig m) LimitsParam
forall (m :: * -> *). Monad m => WebT m LimitsParam
parseLimits ActionT Except (ReaderT WebConfig m) (NoCache -> GetXPubTxsFull)
-> ActionT Except (ReaderT WebConfig m) NoCache
-> WebT m GetXPubTxsFull
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ActionT Except (ReaderT WebConfig m) NoCache
forall a (m :: * -> *). (Default a, Param a, Monad m) => WebT m a
paramDef)
        GetXPubTxsFull -> WebT m [Transaction]
forall (m :: * -> *).
(MonadUnliftIO m, MonadLoggerIO m) =>
GetXPubTxsFull -> WebT m [Transaction]
scottyXPubTxsFull
        ((Transaction -> Encoding) -> [Transaction] -> Encoding
forall a. (a -> Encoding) -> [a] -> Encoding
list ((Transaction -> Encoding) -> [Transaction] -> Encoding)
-> (Network -> Transaction -> Encoding)
-> Network
-> [Transaction]
-> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Network -> Transaction -> Encoding
transactionToEncoding)
        ((Network -> Transaction -> Value)
-> Network -> [Transaction] -> Value
forall a t a. ToJSON a => (t -> a -> a) -> t -> [a] -> Value
json_list Network -> Transaction -> Value
transactionToJSON)
    WebT m GetXPubBalances
-> (GetXPubBalances -> WebT m [XPubBal])
-> (Network -> [XPubBal] -> Encoding)
-> (Network -> [XPubBal] -> Value)
-> ScottyT Except (ReaderT WebConfig m) ()
forall a b (m :: * -> *).
(ApiResource a b, MonadIO m) =>
WebT m a
-> (a -> WebT m b)
-> (Network -> b -> Encoding)
-> (Network -> b -> Value)
-> ScottyT Except (ReaderT WebConfig m) ()
pathPretty
        (XPubKey -> DeriveType -> NoCache -> GetXPubBalances
GetXPubBalances (XPubKey -> DeriveType -> NoCache -> GetXPubBalances)
-> ActionT Except (ReaderT WebConfig m) XPubKey
-> ActionT
     Except
     (ReaderT WebConfig m)
     (DeriveType -> NoCache -> GetXPubBalances)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ActionT Except (ReaderT WebConfig m) XPubKey
forall a (m :: * -> *). (Param a, Monad m) => WebT m a
paramLazy ActionT
  Except
  (ReaderT WebConfig m)
  (DeriveType -> NoCache -> GetXPubBalances)
-> ActionT Except (ReaderT WebConfig m) DeriveType
-> ActionT
     Except (ReaderT WebConfig m) (NoCache -> GetXPubBalances)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ActionT Except (ReaderT WebConfig m) DeriveType
forall a (m :: * -> *). (Default a, Param a, Monad m) => WebT m a
paramDef ActionT Except (ReaderT WebConfig m) (NoCache -> GetXPubBalances)
-> ActionT Except (ReaderT WebConfig m) NoCache
-> WebT m GetXPubBalances
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ActionT Except (ReaderT WebConfig m) NoCache
forall a (m :: * -> *). (Default a, Param a, Monad m) => WebT m a
paramDef)
        GetXPubBalances -> WebT m [XPubBal]
forall (m :: * -> *).
(MonadUnliftIO m, MonadLoggerIO m) =>
GetXPubBalances -> WebT m [XPubBal]
scottyXPubBalances
        ((XPubBal -> Encoding) -> [XPubBal] -> Encoding
forall a. (a -> Encoding) -> [a] -> Encoding
list ((XPubBal -> Encoding) -> [XPubBal] -> Encoding)
-> (Network -> XPubBal -> Encoding)
-> Network
-> [XPubBal]
-> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Network -> XPubBal -> Encoding
xPubBalToEncoding)
        ((Network -> XPubBal -> Value) -> Network -> [XPubBal] -> Value
forall a t a. ToJSON a => (t -> a -> a) -> t -> [a] -> Value
json_list Network -> XPubBal -> Value
xPubBalToJSON)
    WebT m GetXPubUnspent
-> (GetXPubUnspent -> WebT m [XPubUnspent])
-> (Network -> [XPubUnspent] -> Encoding)
-> (Network -> [XPubUnspent] -> Value)
-> ScottyT Except (ReaderT WebConfig m) ()
forall a b (m :: * -> *).
(ApiResource a b, MonadIO m) =>
WebT m a
-> (a -> WebT m b)
-> (Network -> b -> Encoding)
-> (Network -> b -> Value)
-> ScottyT Except (ReaderT WebConfig m) ()
pathPretty
        (XPubKey -> DeriveType -> LimitsParam -> NoCache -> GetXPubUnspent
GetXPubUnspent (XPubKey -> DeriveType -> LimitsParam -> NoCache -> GetXPubUnspent)
-> ActionT Except (ReaderT WebConfig m) XPubKey
-> ActionT
     Except
     (ReaderT WebConfig m)
     (DeriveType -> LimitsParam -> NoCache -> GetXPubUnspent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ActionT Except (ReaderT WebConfig m) XPubKey
forall a (m :: * -> *). (Param a, Monad m) => WebT m a
paramLazy ActionT
  Except
  (ReaderT WebConfig m)
  (DeriveType -> LimitsParam -> NoCache -> GetXPubUnspent)
-> ActionT Except (ReaderT WebConfig m) DeriveType
-> ActionT
     Except
     (ReaderT WebConfig m)
     (LimitsParam -> NoCache -> GetXPubUnspent)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ActionT Except (ReaderT WebConfig m) DeriveType
forall a (m :: * -> *). (Default a, Param a, Monad m) => WebT m a
paramDef ActionT
  Except
  (ReaderT WebConfig m)
  (LimitsParam -> NoCache -> GetXPubUnspent)
-> ActionT Except (ReaderT WebConfig m) LimitsParam
-> ActionT Except (ReaderT WebConfig m) (NoCache -> GetXPubUnspent)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ActionT Except (ReaderT WebConfig m) LimitsParam
forall (m :: * -> *). Monad m => WebT m LimitsParam
parseLimits ActionT Except (ReaderT WebConfig m) (NoCache -> GetXPubUnspent)
-> ActionT Except (ReaderT WebConfig m) NoCache
-> WebT m GetXPubUnspent
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ActionT Except (ReaderT WebConfig m) NoCache
forall a (m :: * -> *). (Default a, Param a, Monad m) => WebT m a
paramDef)
        GetXPubUnspent -> WebT m [XPubUnspent]
forall (m :: * -> *).
(MonadUnliftIO m, MonadLoggerIO m) =>
GetXPubUnspent -> WebT m [XPubUnspent]
scottyXPubUnspent
        ((XPubUnspent -> Encoding) -> [XPubUnspent] -> Encoding
forall a. (a -> Encoding) -> [a] -> Encoding
list ((XPubUnspent -> Encoding) -> [XPubUnspent] -> Encoding)
-> (Network -> XPubUnspent -> Encoding)
-> Network
-> [XPubUnspent]
-> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Network -> XPubUnspent -> Encoding
xPubUnspentToEncoding)
        ((Network -> XPubUnspent -> Value)
-> Network -> [XPubUnspent] -> Value
forall a t a. ToJSON a => (t -> a -> a) -> t -> [a] -> Value
json_list Network -> XPubUnspent -> Value
xPubUnspentToJSON)
    WebT m GetXPubEvict
-> (GetXPubEvict -> WebT m (GenericResult Bool))
-> (Network -> GenericResult Bool -> Encoding)
-> (Network -> GenericResult Bool -> Value)
-> ScottyT Except (ReaderT WebConfig m) ()
forall a b (m :: * -> *).
(ApiResource a b, MonadIO m) =>
WebT m a
-> (a -> WebT m b)
-> (Network -> b -> Encoding)
-> (Network -> b -> Value)
-> ScottyT Except (ReaderT WebConfig m) ()
pathCompact
        (XPubKey -> DeriveType -> GetXPubEvict
GetXPubEvict (XPubKey -> DeriveType -> GetXPubEvict)
-> ActionT Except (ReaderT WebConfig m) XPubKey
-> ActionT
     Except (ReaderT WebConfig m) (DeriveType -> GetXPubEvict)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ActionT Except (ReaderT WebConfig m) XPubKey
forall a (m :: * -> *). (Param a, Monad m) => WebT m a
paramLazy ActionT Except (ReaderT WebConfig m) (DeriveType -> GetXPubEvict)
-> ActionT Except (ReaderT WebConfig m) DeriveType
-> WebT m GetXPubEvict
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ActionT Except (ReaderT WebConfig m) DeriveType
forall a (m :: * -> *). (Default a, Param a, Monad m) => WebT m a
paramDef)
        GetXPubEvict -> WebT m (GenericResult Bool)
forall (m :: * -> *).
(MonadUnliftIO m, MonadLoggerIO m) =>
GetXPubEvict -> WebT m (GenericResult Bool)
scottyXPubEvict
        ((GenericResult Bool -> Encoding)
-> Network -> GenericResult Bool -> Encoding
forall a b. a -> b -> a
const GenericResult Bool -> Encoding
forall a. ToJSON a => a -> Encoding
toEncoding)
        ((GenericResult Bool -> Value)
-> Network -> GenericResult Bool -> Value
forall a b. a -> b -> a
const GenericResult Bool -> Value
forall a. ToJSON a => a -> Value
toJSON)
    -- Network
    WebT m GetPeers
-> (GetPeers -> WebT m [PeerInformation])
-> (Network -> [PeerInformation] -> Encoding)
-> (Network -> [PeerInformation] -> Value)
-> ScottyT Except (ReaderT WebConfig m) ()
forall a b (m :: * -> *).
(ApiResource a b, MonadIO m) =>
WebT m a
-> (a -> WebT m b)
-> (Network -> b -> Encoding)
-> (Network -> b -> Value)
-> ScottyT Except (ReaderT WebConfig m) ()
pathPretty
        (GetPeers
GetPeers GetPeers -> (GetPeers -> WebT m GetPeers) -> WebT m GetPeers
forall a b. a -> (a -> b) -> b
& GetPeers -> WebT m GetPeers
forall (m :: * -> *) a. Monad m => a -> m a
return)
        GetPeers -> WebT m [PeerInformation]
forall (m :: * -> *).
MonadLoggerIO m =>
GetPeers -> WebT m [PeerInformation]
scottyPeers
        (([PeerInformation] -> Encoding)
-> Network -> [PeerInformation] -> Encoding
forall a b. a -> b -> a
const [PeerInformation] -> Encoding
forall a. ToJSON a => a -> Encoding
toEncoding)
        (([PeerInformation] -> Value)
-> Network -> [PeerInformation] -> Value
forall a b. a -> b -> a
const [PeerInformation] -> Value
forall a. ToJSON a => a -> Value
toJSON)
    WebT m GetHealth
-> (GetHealth -> WebT m HealthCheck)
-> (Network -> HealthCheck -> Encoding)
-> (Network -> HealthCheck -> Value)
-> ScottyT Except (ReaderT WebConfig m) ()
forall a b (m :: * -> *).
(ApiResource a b, MonadIO m) =>
WebT m a
-> (a -> WebT m b)
-> (Network -> b -> Encoding)
-> (Network -> b -> Value)
-> ScottyT Except (ReaderT WebConfig m) ()
pathPretty
         (GetHealth
GetHealth GetHealth -> (GetHealth -> WebT m GetHealth) -> WebT m GetHealth
forall a b. a -> (a -> b) -> b
& GetHealth -> WebT m GetHealth
forall (m :: * -> *) a. Monad m => a -> m a
return)
         GetHealth -> WebT m HealthCheck
forall (m :: * -> *).
(MonadUnliftIO m, MonadLoggerIO m) =>
GetHealth -> WebT m HealthCheck
scottyHealth
         ((HealthCheck -> Encoding) -> Network -> HealthCheck -> Encoding
forall a b. a -> b -> a
const HealthCheck -> Encoding
forall a. ToJSON a => a -> Encoding
toEncoding)
         ((HealthCheck -> Value) -> Network -> HealthCheck -> Value
forall a b. a -> b -> a
const HealthCheck -> Value
forall a. ToJSON a => a -> Value
toJSON)
    RoutePattern
-> ActionT Except (ReaderT WebConfig m) ()
-> ScottyT Except (ReaderT WebConfig m) ()
forall e (m :: * -> *).
(ScottyError e, MonadIO m) =>
RoutePattern -> ActionT e m () -> ScottyT e m ()
S.get "/events" ActionT Except (ReaderT WebConfig m) ()
forall (m :: * -> *). MonadLoggerIO m => WebT m ()
scottyEvents
    RoutePattern
-> ActionT Except (ReaderT WebConfig m) ()
-> ScottyT Except (ReaderT WebConfig m) ()
forall e (m :: * -> *).
(ScottyError e, MonadIO m) =>
RoutePattern -> ActionT e m () -> ScottyT e m ()
S.get "/dbstats" ActionT Except (ReaderT WebConfig m) ()
forall (m :: * -> *). MonadLoggerIO m => WebT m ()
scottyDbStats
    -- Blockchain.info
    RoutePattern
-> ActionT Except (ReaderT WebConfig m) ()
-> ScottyT Except (ReaderT WebConfig m) ()
forall e (m :: * -> *).
(ScottyError e, MonadIO m) =>
RoutePattern -> ActionT e m () -> ScottyT e m ()
S.post "/blockchain/multiaddr" (TVar (HashMap Text BinfoTicker)
-> ActionT Except (ReaderT WebConfig m) ()
forall (m :: * -> *).
(MonadUnliftIO m, MonadLoggerIO m) =>
TVar (HashMap Text BinfoTicker) -> WebT m ()
scottyMultiAddr TVar (HashMap Text BinfoTicker)
ticker)
    RoutePattern
-> ActionT Except (ReaderT WebConfig m) ()
-> ScottyT Except (ReaderT WebConfig m) ()
forall e (m :: * -> *).
(ScottyError e, MonadIO m) =>
RoutePattern -> ActionT e m () -> ScottyT e m ()
S.get "/blockchain/rawtx/:txid" ActionT Except (ReaderT WebConfig m) ()
forall (m :: * -> *).
(MonadUnliftIO m, MonadLoggerIO m) =>
WebT m ()
scottyBinfoTx
  where
    json_list :: (t -> a -> a) -> t -> [a] -> Value
json_list f :: t -> a -> a
f net :: t
net = [a] -> Value
forall a. ToJSON a => [a] -> Value
toJSONList ([a] -> Value) -> ([a] -> [a]) -> [a] -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> a) -> [a] -> [a]
forall a b. (a -> b) -> [a] -> [b]
map (t -> a -> a
f t
net)

pathPretty ::
       (ApiResource a b, MonadIO m)
    => WebT m a
    -> (a -> WebT m b)
    -> (Network -> b -> Encoding)
    -> (Network -> b -> Value)
    -> S.ScottyT Except (ReaderT WebConfig m) ()
pathPretty :: WebT m a
-> (a -> WebT m b)
-> (Network -> b -> Encoding)
-> (Network -> b -> Value)
-> ScottyT Except (ReaderT WebConfig m) ()
pathPretty parser :: WebT m a
parser action :: a -> WebT m b
action encJson :: Network -> b -> Encoding
encJson encValue :: Network -> b -> Value
encValue =
    WebT m a
-> (a -> WebT m b)
-> (Network -> b -> Encoding)
-> (Network -> b -> Value)
-> Bool
-> ScottyT Except (ReaderT WebConfig m) ()
forall a b (m :: * -> *).
(ApiResource a b, MonadIO m) =>
WebT m a
-> (a -> WebT m b)
-> (Network -> b -> Encoding)
-> (Network -> b -> Value)
-> Bool
-> ScottyT Except (ReaderT WebConfig m) ()
pathCommon WebT m a
parser a -> WebT m b
action Network -> b -> Encoding
encJson Network -> b -> Value
encValue Bool
True

pathCompact ::
       (ApiResource a b, MonadIO m)
    => WebT m a
    -> (a -> WebT m b)
    -> (Network -> b -> Encoding)
    -> (Network -> b -> Value)
    -> S.ScottyT Except (ReaderT WebConfig m) ()
pathCompact :: WebT m a
-> (a -> WebT m b)
-> (Network -> b -> Encoding)
-> (Network -> b -> Value)
-> ScottyT Except (ReaderT WebConfig m) ()
pathCompact parser :: WebT m a
parser action :: a -> WebT m b
action encJson :: Network -> b -> Encoding
encJson encValue :: Network -> b -> Value
encValue =
    WebT m a
-> (a -> WebT m b)
-> (Network -> b -> Encoding)
-> (Network -> b -> Value)
-> Bool
-> ScottyT Except (ReaderT WebConfig m) ()
forall a b (m :: * -> *).
(ApiResource a b, MonadIO m) =>
WebT m a
-> (a -> WebT m b)
-> (Network -> b -> Encoding)
-> (Network -> b -> Value)
-> Bool
-> ScottyT Except (ReaderT WebConfig m) ()
pathCommon WebT m a
parser a -> WebT m b
action Network -> b -> Encoding
encJson Network -> b -> Value
encValue Bool
False

pathCommon ::
       (ApiResource a b, MonadIO m)
    => WebT m a
    -> (a -> WebT m b)
    -> (Network -> b -> Encoding)
    -> (Network -> b -> Value)
    -> Bool
    -> S.ScottyT Except (ReaderT WebConfig m) ()
pathCommon :: WebT m a
-> (a -> WebT m b)
-> (Network -> b -> Encoding)
-> (Network -> b -> Value)
-> Bool
-> ScottyT Except (ReaderT WebConfig m) ()
pathCommon parser :: WebT m a
parser action :: a -> WebT m b
action encJson :: Network -> b -> Encoding
encJson encValue :: Network -> b -> Value
encValue pretty :: Bool
pretty =
    StdMethod
-> RoutePattern
-> ActionT Except (ReaderT WebConfig m) ()
-> ScottyT Except (ReaderT WebConfig m) ()
forall e (m :: * -> *).
(ScottyError e, MonadIO m) =>
StdMethod -> RoutePattern -> ActionT e m () -> ScottyT e m ()
S.addroute (Proxy a -> StdMethod
forall a b. ApiResource a b => Proxy a -> StdMethod
resourceMethod Proxy a
proxy) (Proxy a -> RoutePattern
forall a b. ApiResource a b => Proxy a -> RoutePattern
capturePath Proxy a
proxy) (ActionT Except (ReaderT WebConfig m) ()
 -> ScottyT Except (ReaderT WebConfig m) ())
-> ActionT Except (ReaderT WebConfig m) ()
-> ScottyT Except (ReaderT WebConfig m) ()
forall a b. (a -> b) -> a -> b
$ do
        ActionT Except (ReaderT WebConfig m) ()
forall (m :: * -> *) e. (Monad m, ScottyError e) => ActionT e m ()
setHeaders
        SerialAs
proto <- Bool -> ActionT Except (ReaderT WebConfig m) SerialAs
forall (m :: * -> *). Monad m => Bool -> ActionT Except m SerialAs
setupContentType Bool
pretty
        Network
net <- ReaderT WebConfig m Network
-> ActionT Except (ReaderT WebConfig m) Network
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (ReaderT WebConfig m Network
 -> ActionT Except (ReaderT WebConfig m) Network)
-> ReaderT WebConfig m Network
-> ActionT Except (ReaderT WebConfig m) Network
forall a b. (a -> b) -> a -> b
$ (WebConfig -> Network) -> ReaderT WebConfig m Network
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks (Store -> Network
storeNetwork (Store -> Network) -> (WebConfig -> Store) -> WebConfig -> Network
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebConfig -> Store
webStore)
        a
apiRes <- WebT m a
parser
        b
res <- a -> WebT m b
action a
apiRes
        ByteString -> ActionT Except (ReaderT WebConfig m) ()
forall (m :: * -> *) e. Monad m => ByteString -> ActionT e m ()
S.raw (ByteString -> ActionT Except (ReaderT WebConfig m) ())
-> ByteString -> ActionT Except (ReaderT WebConfig m) ()
forall a b. (a -> b) -> a -> b
$ SerialAs -> (b -> Encoding) -> (b -> Value) -> b -> ByteString
forall a.
Serialize a =>
SerialAs -> (a -> Encoding) -> (a -> Value) -> a -> ByteString
protoSerial SerialAs
proto (Network -> b -> Encoding
encJson Network
net) (Network -> b -> Value
encValue Network
net) b
res
  where
    toProxy :: WebT m a -> Proxy a
    toProxy :: WebT m a -> Proxy a
toProxy = Proxy a -> WebT m a -> Proxy a
forall a b. a -> b -> a
const Proxy a
forall k (t :: k). Proxy t
Proxy
    proxy :: Proxy a
proxy = WebT m a -> Proxy a
forall (m :: * -> *) a. WebT m a -> Proxy a
toProxy WebT m a
parser

protoSerial
    :: Serialize a
    => SerialAs
    -> (a -> Encoding)
    -> (a -> Value)
    -> a
    -> L.ByteString
protoSerial :: SerialAs -> (a -> Encoding) -> (a -> Value) -> a -> ByteString
protoSerial SerialAsBinary _ _     = Put -> ByteString
runPutLazy (Put -> ByteString) -> (a -> Put) -> a -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Put
forall t. Serialize t => Putter t
put
protoSerial SerialAsJSON f :: a -> Encoding
f _       = Encoding -> ByteString
forall a. Encoding' a -> ByteString
encodingToLazyByteString (Encoding -> ByteString) -> (a -> Encoding) -> a -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Encoding
f
protoSerial SerialAsPrettyJSON _ g :: a -> Value
g =
    Config -> Value -> ByteString
forall a. ToJSON a => Config -> a -> ByteString
encodePretty' Config
defConfig {confTrailingNewline :: Bool
confTrailingNewline = Bool
True} (Value -> ByteString) -> (a -> Value) -> a -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Value
g

setHeaders :: (Monad m, S.ScottyError e) => ActionT e m ()
setHeaders :: ActionT e m ()
setHeaders = Text -> Text -> ActionT e m ()
forall (m :: * -> *) e. Monad m => Text -> Text -> ActionT e m ()
S.setHeader "Access-Control-Allow-Origin" "*"

setupContentType :: Monad m => Bool -> ActionT Except m SerialAs
setupContentType :: Bool -> ActionT Except m SerialAs
setupContentType pretty :: Bool
pretty = do
    Maybe Text
accept <- Text -> ActionT Except m (Maybe Text)
forall e (m :: * -> *).
(ScottyError e, Monad m) =>
Text -> ActionT e m (Maybe Text)
S.header "accept"
    ActionT Except m SerialAs
-> (Text -> ActionT Except m SerialAs)
-> Maybe Text
-> ActionT Except m SerialAs
forall b a. b -> (a -> b) -> Maybe a -> b
maybe ActionT Except m SerialAs
goJson Text -> ActionT Except m SerialAs
forall a. (Eq a, IsString a) => a -> ActionT Except m SerialAs
setType Maybe Text
accept
  where
    setType :: a -> ActionT Except m SerialAs
setType "application/octet-stream" = ActionT Except m SerialAs
goBinary
    setType _                          = ActionT Except m SerialAs
goJson
    goBinary :: ActionT Except m SerialAs
goBinary = do
        Text -> Text -> ActionT Except m ()
forall (m :: * -> *) e. Monad m => Text -> Text -> ActionT e m ()
S.setHeader "Content-Type" "application/octet-stream"
        SerialAs -> ActionT Except m SerialAs
forall (m :: * -> *) a. Monad m => a -> m a
return SerialAs
SerialAsBinary
    goJson :: ActionT Except m SerialAs
goJson = do
        Text -> Text -> ActionT Except m ()
forall (m :: * -> *) e. Monad m => Text -> Text -> ActionT e m ()
S.setHeader "Content-Type" "application/json"
        Bool
p <- Text -> ActionT Except m Bool
forall a e (m :: * -> *).
(Parsable a, ScottyError e, Monad m) =>
Text -> ActionT e m a
S.param "pretty" ActionT Except m Bool
-> (Except -> ActionT Except m Bool) -> ActionT Except m Bool
forall e (m :: * -> *) a.
(ScottyError e, Monad m) =>
ActionT e m a -> (e -> ActionT e m a) -> ActionT e m a
`S.rescue` ActionT Except m Bool -> Except -> ActionT Except m Bool
forall a b. a -> b -> a
const (Bool -> ActionT Except m Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
pretty)
        SerialAs -> ActionT Except m SerialAs
forall (m :: * -> *) a. Monad m => a -> m a
return (SerialAs -> ActionT Except m SerialAs)
-> SerialAs -> ActionT Except m SerialAs
forall a b. (a -> b) -> a -> b
$ if Bool
p then SerialAs
SerialAsPrettyJSON else SerialAs
SerialAsJSON

-- GET Block / GET Blocks --

scottyBlock ::
       (MonadUnliftIO m, MonadLoggerIO m) => GetBlock -> WebT m BlockData
scottyBlock :: GetBlock -> WebT m BlockData
scottyBlock (GetBlock h :: BlockHash
h (NoTx noTx :: Bool
noTx)) =
    WebT m BlockData
-> (BlockData -> WebT m BlockData)
-> Maybe BlockData
-> WebT m BlockData
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Except -> WebT m BlockData
forall e (m :: * -> *) a.
(ScottyError e, Monad m) =>
e -> ActionT e m a
S.raise Except
ThingNotFound) (BlockData -> WebT m BlockData
forall (m :: * -> *) a. Monad m => a -> m a
return (BlockData -> WebT m BlockData)
-> (BlockData -> BlockData) -> BlockData -> WebT m BlockData
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> BlockData -> BlockData
pruneTx Bool
noTx) (Maybe BlockData -> WebT m BlockData)
-> ActionT Except (ReaderT WebConfig m) (Maybe BlockData)
-> WebT m BlockData
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< BlockHash -> ActionT Except (ReaderT WebConfig m) (Maybe BlockData)
forall (m :: * -> *).
StoreReadBase m =>
BlockHash -> m (Maybe BlockData)
getBlock BlockHash
h

scottyBlocks ::
       (MonadUnliftIO m, MonadLoggerIO m) => GetBlocks -> WebT m [BlockData]
scottyBlocks :: GetBlocks -> WebT m [BlockData]
scottyBlocks (GetBlocks hs :: [BlockHash]
hs (NoTx noTx :: Bool
noTx)) =
    (Bool -> BlockData -> BlockData
pruneTx Bool
noTx (BlockData -> BlockData) -> [BlockData] -> [BlockData]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>) ([BlockData] -> [BlockData])
-> ([Maybe BlockData] -> [BlockData])
-> [Maybe BlockData]
-> [BlockData]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Maybe BlockData] -> [BlockData]
forall a. [Maybe a] -> [a]
catMaybes ([Maybe BlockData] -> [BlockData])
-> ActionT Except (ReaderT WebConfig m) [Maybe BlockData]
-> WebT m [BlockData]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (BlockHash
 -> ActionT Except (ReaderT WebConfig m) (Maybe BlockData))
-> [BlockHash]
-> ActionT Except (ReaderT WebConfig m) [Maybe BlockData]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM BlockHash -> ActionT Except (ReaderT WebConfig m) (Maybe BlockData)
forall (m :: * -> *).
StoreReadBase m =>
BlockHash -> m (Maybe BlockData)
getBlock ([BlockHash] -> [BlockHash]
forall a. Eq a => [a] -> [a]
nub [BlockHash]
hs)

pruneTx :: Bool -> BlockData -> BlockData
pruneTx :: Bool -> BlockData -> BlockData
pruneTx False b :: BlockData
b = BlockData
b
pruneTx True b :: BlockData
b  = BlockData
b {blockDataTxs :: [TxHash]
blockDataTxs = Int -> [TxHash] -> [TxHash]
forall a. Int -> [a] -> [a]
take 1 (BlockData -> [TxHash]
blockDataTxs BlockData
b)}

-- GET BlockRaw --

scottyBlockRaw ::
       (MonadUnliftIO m, MonadLoggerIO m)
    => GetBlockRaw
    -> WebT m (RawResult H.Block)
scottyBlockRaw :: GetBlockRaw -> WebT m (RawResult Block)
scottyBlockRaw (GetBlockRaw h :: BlockHash
h) = Block -> RawResult Block
forall a. a -> RawResult a
RawResult (Block -> RawResult Block)
-> ActionT Except (ReaderT WebConfig m) Block
-> WebT m (RawResult Block)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> BlockHash -> ActionT Except (ReaderT WebConfig m) Block
forall (m :: * -> *).
(MonadUnliftIO m, MonadLoggerIO m) =>
BlockHash -> WebT m Block
getRawBlock BlockHash
h

getRawBlock ::
       (MonadUnliftIO m, MonadLoggerIO m) => H.BlockHash -> WebT m H.Block
getRawBlock :: BlockHash -> WebT m Block
getRawBlock h :: BlockHash
h = do
    BlockData
b <- ActionT Except (ReaderT WebConfig m) BlockData
-> (BlockData -> ActionT Except (ReaderT WebConfig m) BlockData)
-> Maybe BlockData
-> ActionT Except (ReaderT WebConfig m) BlockData
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Except -> ActionT Except (ReaderT WebConfig m) BlockData
forall e (m :: * -> *) a.
(ScottyError e, Monad m) =>
e -> ActionT e m a
S.raise Except
ThingNotFound) BlockData -> ActionT Except (ReaderT WebConfig m) BlockData
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe BlockData -> ActionT Except (ReaderT WebConfig m) BlockData)
-> ActionT Except (ReaderT WebConfig m) (Maybe BlockData)
-> ActionT Except (ReaderT WebConfig m) BlockData
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< BlockHash -> ActionT Except (ReaderT WebConfig m) (Maybe BlockData)
forall (m :: * -> *).
StoreReadBase m =>
BlockHash -> m (Maybe BlockData)
getBlock BlockHash
h
    BlockData -> WebT m ()
forall (m :: * -> *). Monad m => BlockData -> WebT m ()
refuseLargeBlock BlockData
b
    BlockData -> WebT m Block
forall (m :: * -> *).
(Monad m, StoreReadBase m) =>
BlockData -> m Block
toRawBlock BlockData
b

toRawBlock :: (Monad m, StoreReadBase m) => BlockData -> m H.Block
toRawBlock :: BlockData -> m Block
toRawBlock b :: BlockData
b = do
    let ths :: [TxHash]
ths = BlockData -> [TxHash]
blockDataTxs BlockData
b
    [Tx]
txs <- (Transaction -> Tx) -> [Transaction] -> [Tx]
forall a b. (a -> b) -> [a] -> [b]
map Transaction -> Tx
transactionData ([Transaction] -> [Tx])
-> ([Maybe Transaction] -> [Transaction])
-> [Maybe Transaction]
-> [Tx]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Maybe Transaction] -> [Transaction]
forall a. [Maybe a] -> [a]
catMaybes ([Maybe Transaction] -> [Tx]) -> m [Maybe Transaction] -> m [Tx]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (TxHash -> m (Maybe Transaction))
-> [TxHash] -> m [Maybe Transaction]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM TxHash -> m (Maybe Transaction)
forall (m :: * -> *).
(Monad m, StoreReadBase m) =>
TxHash -> m (Maybe Transaction)
getTransaction [TxHash]
ths
    Block -> m Block
forall (m :: * -> *) a. Monad m => a -> m a
return $WBlock :: BlockHeader -> [Tx] -> Block
H.Block {blockHeader :: BlockHeader
H.blockHeader = BlockData -> BlockHeader
blockDataHeader BlockData
b, blockTxns :: [Tx]
H.blockTxns = [Tx]
txs}

refuseLargeBlock :: Monad m => BlockData -> WebT m ()
refuseLargeBlock :: BlockData -> WebT m ()
refuseLargeBlock BlockData {blockDataTxs :: BlockData -> [TxHash]
blockDataTxs = [TxHash]
txs} = do
    WebLimits {maxLimitFull :: WebLimits -> Word32
maxLimitFull = Word32
f} <- ReaderT WebConfig m WebLimits
-> ActionT Except (ReaderT WebConfig m) WebLimits
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (ReaderT WebConfig m WebLimits
 -> ActionT Except (ReaderT WebConfig m) WebLimits)
-> ReaderT WebConfig m WebLimits
-> ActionT Except (ReaderT WebConfig m) WebLimits
forall a b. (a -> b) -> a -> b
$ (WebConfig -> WebLimits) -> ReaderT WebConfig m WebLimits
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WebConfig -> WebLimits
webMaxLimits
    Bool -> WebT m () -> WebT m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when ([TxHash] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [TxHash]
txs Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
f) (WebT m () -> WebT m ()) -> WebT m () -> WebT m ()
forall a b. (a -> b) -> a -> b
$ Except -> WebT m ()
forall e (m :: * -> *) a.
(ScottyError e, Monad m) =>
e -> ActionT e m a
S.raise Except
BlockTooLarge

-- GET BlockBest / BlockBestRaw --

scottyBlockBest ::
       (MonadUnliftIO m, MonadLoggerIO m) => GetBlockBest -> WebT m BlockData
scottyBlockBest :: GetBlockBest -> WebT m BlockData
scottyBlockBest (GetBlockBest noTx :: NoTx
noTx) = do
    Maybe BlockHash
bestM <- ActionT Except (ReaderT WebConfig m) (Maybe BlockHash)
forall (m :: * -> *). StoreReadBase m => m (Maybe BlockHash)
getBestBlock
    WebT m BlockData
-> (BlockHash -> WebT m BlockData)
-> Maybe BlockHash
-> WebT m BlockData
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Except -> WebT m BlockData
forall e (m :: * -> *) a.
(ScottyError e, Monad m) =>
e -> ActionT e m a
S.raise Except
ThingNotFound) (GetBlock -> WebT m BlockData
forall (m :: * -> *).
(MonadUnliftIO m, MonadLoggerIO m) =>
GetBlock -> WebT m BlockData
scottyBlock (GetBlock -> WebT m BlockData)
-> (BlockHash -> GetBlock) -> BlockHash -> WebT m BlockData
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (BlockHash -> NoTx -> GetBlock
`GetBlock` NoTx
noTx)) Maybe BlockHash
bestM

scottyBlockBestRaw ::
       (MonadUnliftIO m, MonadLoggerIO m)
    => GetBlockBestRaw
    -> WebT m (RawResult H.Block)
scottyBlockBestRaw :: GetBlockBestRaw -> WebT m (RawResult Block)
scottyBlockBestRaw _ =
    Block -> RawResult Block
forall a. a -> RawResult a
RawResult (Block -> RawResult Block)
-> ActionT Except (ReaderT WebConfig m) Block
-> WebT m (RawResult Block)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ActionT Except (ReaderT WebConfig m) Block
-> (BlockHash -> ActionT Except (ReaderT WebConfig m) Block)
-> Maybe BlockHash
-> ActionT Except (ReaderT WebConfig m) Block
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Except -> ActionT Except (ReaderT WebConfig m) Block
forall e (m :: * -> *) a.
(ScottyError e, Monad m) =>
e -> ActionT e m a
S.raise Except
ThingNotFound) BlockHash -> ActionT Except (ReaderT WebConfig m) Block
forall (m :: * -> *).
(MonadUnliftIO m, MonadLoggerIO m) =>
BlockHash -> WebT m Block
getRawBlock (Maybe BlockHash -> ActionT Except (ReaderT WebConfig m) Block)
-> ActionT Except (ReaderT WebConfig m) (Maybe BlockHash)
-> ActionT Except (ReaderT WebConfig m) Block
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< ActionT Except (ReaderT WebConfig m) (Maybe BlockHash)
forall (m :: * -> *). StoreReadBase m => m (Maybe BlockHash)
getBestBlock)

-- GET BlockLatest --

scottyBlockLatest ::
       (MonadUnliftIO m, MonadLoggerIO m)
    => GetBlockLatest
    -> WebT m [BlockData]
scottyBlockLatest :: GetBlockLatest -> WebT m [BlockData]
scottyBlockLatest (GetBlockLatest (NoTx noTx :: Bool
noTx)) =
    WebT m [BlockData]
-> (BlockHash -> WebT m [BlockData])
-> Maybe BlockHash
-> WebT m [BlockData]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Except -> WebT m [BlockData]
forall e (m :: * -> *) a.
(ScottyError e, Monad m) =>
e -> ActionT e m a
S.raise Except
ThingNotFound) ([BlockData] -> Maybe BlockData -> WebT m [BlockData]
forall (m :: * -> *).
StoreReadBase m =>
[BlockData] -> Maybe BlockData -> m [BlockData]
go [] (Maybe BlockData -> WebT m [BlockData])
-> (BlockHash
    -> ActionT Except (ReaderT WebConfig m) (Maybe BlockData))
-> BlockHash
-> WebT m [BlockData]
forall (m :: * -> *) b c a.
Monad m =>
(b -> m c) -> (a -> m b) -> a -> m c
<=< BlockHash -> ActionT Except (ReaderT WebConfig m) (Maybe BlockData)
forall (m :: * -> *).
StoreReadBase m =>
BlockHash -> m (Maybe BlockData)
getBlock) (Maybe BlockHash -> WebT m [BlockData])
-> ActionT Except (ReaderT WebConfig m) (Maybe BlockHash)
-> WebT m [BlockData]
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< ActionT Except (ReaderT WebConfig m) (Maybe BlockHash)
forall (m :: * -> *). StoreReadBase m => m (Maybe BlockHash)
getBestBlock
  where
    go :: [BlockData] -> Maybe BlockData -> m [BlockData]
go acc :: [BlockData]
acc Nothing = [BlockData] -> m [BlockData]
forall (m :: * -> *) a. Monad m => a -> m a
return [BlockData]
acc
    go acc :: [BlockData]
acc (Just b :: BlockData
b)
        | BlockData -> Word32
blockDataHeight BlockData
b Word32 -> Word32 -> Bool
forall a. Ord a => a -> a -> Bool
<= 0 = [BlockData] -> m [BlockData]
forall (m :: * -> *) a. Monad m => a -> m a
return [BlockData]
acc
        | [BlockData] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [BlockData]
acc Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== 99 = [BlockData] -> m [BlockData]
forall (m :: * -> *) a. Monad m => a -> m a
return (BlockData
bBlockData -> [BlockData] -> [BlockData]
forall a. a -> [a] -> [a]
:[BlockData]
acc)
        | Bool
otherwise = do
            let prev :: BlockHash
prev = BlockHeader -> BlockHash
H.prevBlock (BlockData -> BlockHeader
blockDataHeader BlockData
b)
            [BlockData] -> Maybe BlockData -> m [BlockData]
go (Bool -> BlockData -> BlockData
pruneTx Bool
noTx BlockData
b BlockData -> [BlockData] -> [BlockData]
forall a. a -> [a] -> [a]
: [BlockData]
acc) (Maybe BlockData -> m [BlockData])
-> m (Maybe BlockData) -> m [BlockData]
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< BlockHash -> m (Maybe BlockData)
forall (m :: * -> *).
StoreReadBase m =>
BlockHash -> m (Maybe BlockData)
getBlock BlockHash
prev

-- GET BlockHeight / BlockHeights / BlockHeightRaw --

scottyBlockHeight ::
       (MonadUnliftIO m, MonadLoggerIO m) => GetBlockHeight -> WebT m [BlockData]
scottyBlockHeight :: GetBlockHeight -> WebT m [BlockData]
scottyBlockHeight (GetBlockHeight h :: HeightParam
h noTx :: NoTx
noTx) =
    GetBlocks -> WebT m [BlockData]
forall (m :: * -> *).
(MonadUnliftIO m, MonadLoggerIO m) =>
GetBlocks -> WebT m [BlockData]
scottyBlocks (GetBlocks -> WebT m [BlockData])
-> ([BlockHash] -> GetBlocks) -> [BlockHash] -> WebT m [BlockData]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([BlockHash] -> NoTx -> GetBlocks
`GetBlocks` NoTx
noTx) ([BlockHash] -> WebT m [BlockData])
-> ActionT Except (ReaderT WebConfig m) [BlockHash]
-> WebT m [BlockData]
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Word32 -> ActionT Except (ReaderT WebConfig m) [BlockHash]
forall (m :: * -> *). StoreReadBase m => Word32 -> m [BlockHash]
getBlocksAtHeight (HeightParam -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral HeightParam
h)

scottyBlockHeights ::
       (MonadUnliftIO m, MonadLoggerIO m)
    => GetBlockHeights
    -> WebT m [BlockData]
scottyBlockHeights :: GetBlockHeights -> WebT m [BlockData]
scottyBlockHeights (GetBlockHeights (HeightsParam heights :: [Natural]
heights) noTx :: NoTx
noTx) = do
    [BlockHash]
bhs <- [[BlockHash]] -> [BlockHash]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[BlockHash]] -> [BlockHash])
-> ActionT Except (ReaderT WebConfig m) [[BlockHash]]
-> ActionT Except (ReaderT WebConfig m) [BlockHash]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Word32 -> ActionT Except (ReaderT WebConfig m) [BlockHash])
-> [Word32] -> ActionT Except (ReaderT WebConfig m) [[BlockHash]]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Word32 -> ActionT Except (ReaderT WebConfig m) [BlockHash]
forall (m :: * -> *). StoreReadBase m => Word32 -> m [BlockHash]
getBlocksAtHeight (Natural -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Natural -> Word32) -> [Natural] -> [Word32]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Natural]
heights)
    GetBlocks -> WebT m [BlockData]
forall (m :: * -> *).
(MonadUnliftIO m, MonadLoggerIO m) =>
GetBlocks -> WebT m [BlockData]
scottyBlocks ([BlockHash] -> NoTx -> GetBlocks
GetBlocks [BlockHash]
bhs NoTx
noTx)

scottyBlockHeightRaw ::
       (MonadUnliftIO m, MonadLoggerIO m)
    => GetBlockHeightRaw
    -> WebT m (RawResultList H.Block)
scottyBlockHeightRaw :: GetBlockHeightRaw -> WebT m (RawResultList Block)
scottyBlockHeightRaw (GetBlockHeightRaw h :: HeightParam
h) =
    [Block] -> RawResultList Block
forall a. [a] -> RawResultList a
RawResultList ([Block] -> RawResultList Block)
-> ActionT Except (ReaderT WebConfig m) [Block]
-> WebT m (RawResultList Block)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ((BlockHash -> ActionT Except (ReaderT WebConfig m) Block)
-> [BlockHash] -> ActionT Except (ReaderT WebConfig m) [Block]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM BlockHash -> ActionT Except (ReaderT WebConfig m) Block
forall (m :: * -> *).
(MonadUnliftIO m, MonadLoggerIO m) =>
BlockHash -> WebT m Block
getRawBlock ([BlockHash] -> ActionT Except (ReaderT WebConfig m) [Block])
-> ActionT Except (ReaderT WebConfig m) [BlockHash]
-> ActionT Except (ReaderT WebConfig m) [Block]
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Word32 -> ActionT Except (ReaderT WebConfig m) [BlockHash]
forall (m :: * -> *). StoreReadBase m => Word32 -> m [BlockHash]
getBlocksAtHeight (HeightParam -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral HeightParam
h))

-- GET BlockTime / BlockTimeRaw --

scottyBlockTime :: (MonadUnliftIO m, MonadLoggerIO m)
                => GetBlockTime -> WebT m BlockData
scottyBlockTime :: GetBlockTime -> WebT m BlockData
scottyBlockTime (GetBlockTime (TimeParam t :: Word64
t) (NoTx noTx :: Bool
noTx)) = do
    Chain
ch <- ReaderT WebConfig m Chain
-> ActionT Except (ReaderT WebConfig m) Chain
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (ReaderT WebConfig m Chain
 -> ActionT Except (ReaderT WebConfig m) Chain)
-> ReaderT WebConfig m Chain
-> ActionT Except (ReaderT WebConfig m) Chain
forall a b. (a -> b) -> a -> b
$ (WebConfig -> Chain) -> ReaderT WebConfig m Chain
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks (Store -> Chain
storeChain (Store -> Chain) -> (WebConfig -> Store) -> WebConfig -> Chain
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebConfig -> Store
webStore)
    Maybe BlockData
m <- Chain
-> Word64 -> ActionT Except (ReaderT WebConfig m) (Maybe BlockData)
forall (m :: * -> *).
(MonadIO m, StoreReadExtra m) =>
Chain -> Word64 -> m (Maybe BlockData)
blockAtOrBefore Chain
ch Word64
t
    WebT m BlockData
-> (BlockData -> WebT m BlockData)
-> Maybe BlockData
-> WebT m BlockData
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Except -> WebT m BlockData
forall e (m :: * -> *) a.
(ScottyError e, Monad m) =>
e -> ActionT e m a
S.raise Except
ThingNotFound) (BlockData -> WebT m BlockData
forall (m :: * -> *) a. Monad m => a -> m a
return (BlockData -> WebT m BlockData)
-> (BlockData -> BlockData) -> BlockData -> WebT m BlockData
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> BlockData -> BlockData
pruneTx Bool
noTx) Maybe BlockData
m

scottyBlockMTP :: (MonadUnliftIO m, MonadLoggerIO m)
               => GetBlockMTP -> WebT m BlockData
scottyBlockMTP :: GetBlockMTP -> WebT m BlockData
scottyBlockMTP (GetBlockMTP (TimeParam t :: Word64
t) (NoTx noTx :: Bool
noTx)) = do
    Chain
ch <- ReaderT WebConfig m Chain
-> ActionT Except (ReaderT WebConfig m) Chain
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (ReaderT WebConfig m Chain
 -> ActionT Except (ReaderT WebConfig m) Chain)
-> ReaderT WebConfig m Chain
-> ActionT Except (ReaderT WebConfig m) Chain
forall a b. (a -> b) -> a -> b
$ (WebConfig -> Chain) -> ReaderT WebConfig m Chain
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks (Store -> Chain
storeChain (Store -> Chain) -> (WebConfig -> Store) -> WebConfig -> Chain
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebConfig -> Store
webStore)
    Maybe BlockData
m <- Chain
-> Word64 -> ActionT Except (ReaderT WebConfig m) (Maybe BlockData)
forall (m :: * -> *).
(MonadIO m, StoreReadExtra m) =>
Chain -> Word64 -> m (Maybe BlockData)
blockAtOrAfterMTP Chain
ch Word64
t
    WebT m BlockData
-> (BlockData -> WebT m BlockData)
-> Maybe BlockData
-> WebT m BlockData
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Except -> WebT m BlockData
forall e (m :: * -> *) a.
(ScottyError e, Monad m) =>
e -> ActionT e m a
S.raise Except
ThingNotFound) (BlockData -> WebT m BlockData
forall (m :: * -> *) a. Monad m => a -> m a
return (BlockData -> WebT m BlockData)
-> (BlockData -> BlockData) -> BlockData -> WebT m BlockData
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> BlockData -> BlockData
pruneTx Bool
noTx) Maybe BlockData
m

scottyBlockTimeRaw :: (MonadUnliftIO m, MonadLoggerIO m)
                   => GetBlockTimeRaw -> WebT m (RawResult H.Block)
scottyBlockTimeRaw :: GetBlockTimeRaw -> WebT m (RawResult Block)
scottyBlockTimeRaw (GetBlockTimeRaw (TimeParam t :: Word64
t)) = do
    Chain
ch <- ReaderT WebConfig m Chain
-> ActionT Except (ReaderT WebConfig m) Chain
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (ReaderT WebConfig m Chain
 -> ActionT Except (ReaderT WebConfig m) Chain)
-> ReaderT WebConfig m Chain
-> ActionT Except (ReaderT WebConfig m) Chain
forall a b. (a -> b) -> a -> b
$ (WebConfig -> Chain) -> ReaderT WebConfig m Chain
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks (Store -> Chain
storeChain (Store -> Chain) -> (WebConfig -> Store) -> WebConfig -> Chain
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebConfig -> Store
webStore)
    Maybe BlockData
m <- Chain
-> Word64 -> ActionT Except (ReaderT WebConfig m) (Maybe BlockData)
forall (m :: * -> *).
(MonadIO m, StoreReadExtra m) =>
Chain -> Word64 -> m (Maybe BlockData)
blockAtOrBefore Chain
ch Word64
t
    BlockData
b <- ActionT Except (ReaderT WebConfig m) BlockData
-> (BlockData -> ActionT Except (ReaderT WebConfig m) BlockData)
-> Maybe BlockData
-> ActionT Except (ReaderT WebConfig m) BlockData
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Except -> ActionT Except (ReaderT WebConfig m) BlockData
forall e (m :: * -> *) a.
(ScottyError e, Monad m) =>
e -> ActionT e m a
S.raise Except
ThingNotFound) BlockData -> ActionT Except (ReaderT WebConfig m) BlockData
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe BlockData
m
    BlockData -> WebT m ()
forall (m :: * -> *). Monad m => BlockData -> WebT m ()
refuseLargeBlock BlockData
b
    Block -> RawResult Block
forall a. a -> RawResult a
RawResult (Block -> RawResult Block)
-> ActionT Except (ReaderT WebConfig m) Block
-> WebT m (RawResult Block)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> BlockData -> ActionT Except (ReaderT WebConfig m) Block
forall (m :: * -> *).
(Monad m, StoreReadBase m) =>
BlockData -> m Block
toRawBlock BlockData
b

scottyBlockMTPRaw :: (MonadUnliftIO m, MonadLoggerIO m)
                  => GetBlockMTPRaw -> WebT m (RawResult H.Block)
scottyBlockMTPRaw :: GetBlockMTPRaw -> WebT m (RawResult Block)
scottyBlockMTPRaw (GetBlockMTPRaw (TimeParam t :: Word64
t)) = do
    Chain
ch <- ReaderT WebConfig m Chain
-> ActionT Except (ReaderT WebConfig m) Chain
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (ReaderT WebConfig m Chain
 -> ActionT Except (ReaderT WebConfig m) Chain)
-> ReaderT WebConfig m Chain
-> ActionT Except (ReaderT WebConfig m) Chain
forall a b. (a -> b) -> a -> b
$ (WebConfig -> Chain) -> ReaderT WebConfig m Chain
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks (Store -> Chain
storeChain (Store -> Chain) -> (WebConfig -> Store) -> WebConfig -> Chain
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebConfig -> Store
webStore)
    Maybe BlockData
m <- Chain
-> Word64 -> ActionT Except (ReaderT WebConfig m) (Maybe BlockData)
forall (m :: * -> *).
(MonadIO m, StoreReadExtra m) =>
Chain -> Word64 -> m (Maybe BlockData)
blockAtOrAfterMTP Chain
ch Word64
t
    BlockData
b <- ActionT Except (ReaderT WebConfig m) BlockData
-> (BlockData -> ActionT Except (ReaderT WebConfig m) BlockData)
-> Maybe BlockData
-> ActionT Except (ReaderT WebConfig m) BlockData
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Except -> ActionT Except (ReaderT WebConfig m) BlockData
forall e (m :: * -> *) a.
(ScottyError e, Monad m) =>
e -> ActionT e m a
S.raise Except
ThingNotFound) BlockData -> ActionT Except (ReaderT WebConfig m) BlockData
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe BlockData
m
    BlockData -> WebT m ()
forall (m :: * -> *). Monad m => BlockData -> WebT m ()
refuseLargeBlock BlockData
b
    Block -> RawResult Block
forall a. a -> RawResult a
RawResult (Block -> RawResult Block)
-> ActionT Except (ReaderT WebConfig m) Block
-> WebT m (RawResult Block)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> BlockData -> ActionT Except (ReaderT WebConfig m) Block
forall (m :: * -> *).
(Monad m, StoreReadBase m) =>
BlockData -> m Block
toRawBlock BlockData
b

-- GET Transactions --

scottyTx :: (MonadUnliftIO m, MonadLoggerIO m) => GetTx -> WebT m Transaction
scottyTx :: GetTx -> WebT m Transaction
scottyTx (GetTx txid :: TxHash
txid) =
    WebT m Transaction
-> (Transaction -> WebT m Transaction)
-> Maybe Transaction
-> WebT m Transaction
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Except -> WebT m Transaction
forall e (m :: * -> *) a.
(ScottyError e, Monad m) =>
e -> ActionT e m a
S.raise Except
ThingNotFound) Transaction -> WebT m Transaction
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe Transaction -> WebT m Transaction)
-> ActionT Except (ReaderT WebConfig m) (Maybe Transaction)
-> WebT m Transaction
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< TxHash -> ActionT Except (ReaderT WebConfig m) (Maybe Transaction)
forall (m :: * -> *).
(Monad m, StoreReadBase m) =>
TxHash -> m (Maybe Transaction)
getTransaction TxHash
txid

scottyTxs ::
       (MonadUnliftIO m, MonadLoggerIO m) => GetTxs -> WebT m [Transaction]
scottyTxs :: GetTxs -> WebT m [Transaction]
scottyTxs (GetTxs txids :: [TxHash]
txids) = [Maybe Transaction] -> [Transaction]
forall a. [Maybe a] -> [a]
catMaybes ([Maybe Transaction] -> [Transaction])
-> ActionT Except (ReaderT WebConfig m) [Maybe Transaction]
-> WebT m [Transaction]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (TxHash
 -> ActionT Except (ReaderT WebConfig m) (Maybe Transaction))
-> [TxHash]
-> ActionT Except (ReaderT WebConfig m) [Maybe Transaction]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM TxHash -> ActionT Except (ReaderT WebConfig m) (Maybe Transaction)
forall (m :: * -> *).
(Monad m, StoreReadBase m) =>
TxHash -> m (Maybe Transaction)
getTransaction ([TxHash] -> [TxHash]
forall a. Eq a => [a] -> [a]
nub [TxHash]
txids)

scottyTxRaw ::
       (MonadUnliftIO m, MonadLoggerIO m) => GetTxRaw -> WebT m (RawResult Tx)
scottyTxRaw :: GetTxRaw -> WebT m (RawResult Tx)
scottyTxRaw (GetTxRaw txid :: TxHash
txid) = do
    Transaction
tx <- ActionT Except (ReaderT WebConfig m) Transaction
-> (Transaction
    -> ActionT Except (ReaderT WebConfig m) Transaction)
-> Maybe Transaction
-> ActionT Except (ReaderT WebConfig m) Transaction
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Except -> ActionT Except (ReaderT WebConfig m) Transaction
forall e (m :: * -> *) a.
(ScottyError e, Monad m) =>
e -> ActionT e m a
S.raise Except
ThingNotFound) Transaction -> ActionT Except (ReaderT WebConfig m) Transaction
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe Transaction
 -> ActionT Except (ReaderT WebConfig m) Transaction)
-> ActionT Except (ReaderT WebConfig m) (Maybe Transaction)
-> ActionT Except (ReaderT WebConfig m) Transaction
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< TxHash -> ActionT Except (ReaderT WebConfig m) (Maybe Transaction)
forall (m :: * -> *).
(Monad m, StoreReadBase m) =>
TxHash -> m (Maybe Transaction)
getTransaction TxHash
txid
    RawResult Tx -> WebT m (RawResult Tx)
forall (m :: * -> *) a. Monad m => a -> m a
return (RawResult Tx -> WebT m (RawResult Tx))
-> RawResult Tx -> WebT m (RawResult Tx)
forall a b. (a -> b) -> a -> b
$ Tx -> RawResult Tx
forall a. a -> RawResult a
RawResult (Tx -> RawResult Tx) -> Tx -> RawResult Tx
forall a b. (a -> b) -> a -> b
$ Transaction -> Tx
transactionData Transaction
tx

scottyTxsRaw ::
       (MonadUnliftIO m, MonadLoggerIO m)
    => GetTxsRaw
    -> WebT m (RawResultList Tx)
scottyTxsRaw :: GetTxsRaw -> WebT m (RawResultList Tx)
scottyTxsRaw (GetTxsRaw txids :: [TxHash]
txids) = do
    [Transaction]
txs <- [Maybe Transaction] -> [Transaction]
forall a. [Maybe a] -> [a]
catMaybes ([Maybe Transaction] -> [Transaction])
-> ActionT Except (ReaderT WebConfig m) [Maybe Transaction]
-> ActionT Except (ReaderT WebConfig m) [Transaction]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (TxHash
 -> ActionT Except (ReaderT WebConfig m) (Maybe Transaction))
-> [TxHash]
-> ActionT Except (ReaderT WebConfig m) [Maybe Transaction]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM TxHash -> ActionT Except (ReaderT WebConfig m) (Maybe Transaction)
forall (m :: * -> *).
(Monad m, StoreReadBase m) =>
TxHash -> m (Maybe Transaction)
getTransaction ([TxHash] -> [TxHash]
forall a. Eq a => [a] -> [a]
nub [TxHash]
txids)
    RawResultList Tx -> WebT m (RawResultList Tx)
forall (m :: * -> *) a. Monad m => a -> m a
return (RawResultList Tx -> WebT m (RawResultList Tx))
-> RawResultList Tx -> WebT m (RawResultList Tx)
forall a b. (a -> b) -> a -> b
$ [Tx] -> RawResultList Tx
forall a. [a] -> RawResultList a
RawResultList ([Tx] -> RawResultList Tx) -> [Tx] -> RawResultList Tx
forall a b. (a -> b) -> a -> b
$ Transaction -> Tx
transactionData (Transaction -> Tx) -> [Transaction] -> [Tx]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Transaction]
txs

scottyTxsBlock ::
       (MonadUnliftIO m, MonadLoggerIO m) => GetTxsBlock -> WebT m [Transaction]
scottyTxsBlock :: GetTxsBlock -> WebT m [Transaction]
scottyTxsBlock (GetTxsBlock h :: BlockHash
h) = do
    BlockData
b <- ActionT Except (ReaderT WebConfig m) BlockData
-> (BlockData -> ActionT Except (ReaderT WebConfig m) BlockData)
-> Maybe BlockData
-> ActionT Except (ReaderT WebConfig m) BlockData
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Except -> ActionT Except (ReaderT WebConfig m) BlockData
forall e (m :: * -> *) a.
(ScottyError e, Monad m) =>
e -> ActionT e m a
S.raise Except
ThingNotFound) BlockData -> ActionT Except (ReaderT WebConfig m) BlockData
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe BlockData -> ActionT Except (ReaderT WebConfig m) BlockData)
-> ActionT Except (ReaderT WebConfig m) (Maybe BlockData)
-> ActionT Except (ReaderT WebConfig m) BlockData
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< BlockHash -> ActionT Except (ReaderT WebConfig m) (Maybe BlockData)
forall (m :: * -> *).
StoreReadBase m =>
BlockHash -> m (Maybe BlockData)
getBlock BlockHash
h
    BlockData -> WebT m ()
forall (m :: * -> *). Monad m => BlockData -> WebT m ()
refuseLargeBlock BlockData
b
    [Maybe Transaction] -> [Transaction]
forall a. [Maybe a] -> [a]
catMaybes ([Maybe Transaction] -> [Transaction])
-> ActionT Except (ReaderT WebConfig m) [Maybe Transaction]
-> WebT m [Transaction]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (TxHash
 -> ActionT Except (ReaderT WebConfig m) (Maybe Transaction))
-> [TxHash]
-> ActionT Except (ReaderT WebConfig m) [Maybe Transaction]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM TxHash -> ActionT Except (ReaderT WebConfig m) (Maybe Transaction)
forall (m :: * -> *).
(Monad m, StoreReadBase m) =>
TxHash -> m (Maybe Transaction)
getTransaction (BlockData -> [TxHash]
blockDataTxs BlockData
b)

scottyTxsBlockRaw ::
       (MonadUnliftIO m, MonadLoggerIO m)
    => GetTxsBlockRaw
    -> WebT m (RawResultList Tx)
scottyTxsBlockRaw :: GetTxsBlockRaw -> WebT m (RawResultList Tx)
scottyTxsBlockRaw (GetTxsBlockRaw h :: BlockHash
h) =
    [Tx] -> RawResultList Tx
forall a. [a] -> RawResultList a
RawResultList ([Tx] -> RawResultList Tx)
-> ([Transaction] -> [Tx]) -> [Transaction] -> RawResultList Tx
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Transaction -> Tx) -> [Transaction] -> [Tx]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Transaction -> Tx
transactionData ([Transaction] -> RawResultList Tx)
-> ActionT Except (ReaderT WebConfig m) [Transaction]
-> WebT m (RawResultList Tx)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GetTxsBlock -> ActionT Except (ReaderT WebConfig m) [Transaction]
forall (m :: * -> *).
(MonadUnliftIO m, MonadLoggerIO m) =>
GetTxsBlock -> WebT m [Transaction]
scottyTxsBlock (BlockHash -> GetTxsBlock
GetTxsBlock BlockHash
h)

-- GET TransactionAfterHeight --

scottyTxAfter ::
       (MonadUnliftIO m, MonadLoggerIO m)
    => GetTxAfter
    -> WebT m (GenericResult (Maybe Bool))
scottyTxAfter :: GetTxAfter -> WebT m (GenericResult (Maybe Bool))
scottyTxAfter (GetTxAfter txid :: TxHash
txid height :: HeightParam
height) =
    Maybe Bool -> GenericResult (Maybe Bool)
forall a. a -> GenericResult a
GenericResult (Maybe Bool -> GenericResult (Maybe Bool))
-> ActionT Except (ReaderT WebConfig m) (Maybe Bool)
-> WebT m (GenericResult (Maybe Bool))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Word32
-> TxHash -> ActionT Except (ReaderT WebConfig m) (Maybe Bool)
forall (m :: * -> *).
(MonadIO m, StoreReadBase m) =>
Word32 -> TxHash -> m (Maybe Bool)
cbAfterHeight (HeightParam -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral HeightParam
height) TxHash
txid

-- | Check if any of the ancestors of this transaction is a coinbase after the
-- specified height. Returns 'Nothing' if answer cannot be computed before
-- hitting limits.
cbAfterHeight ::
       (MonadIO m, StoreReadBase m)
    => H.BlockHeight
    -> TxHash
    -> m (Maybe Bool)
cbAfterHeight :: Word32 -> TxHash -> m (Maybe Bool)
cbAfterHeight height :: Word32
height txid :: TxHash
txid =
    Integer
-> HashSet TxHash -> HashSet TxHash -> [TxHash] -> m (Maybe Bool)
forall a (m :: * -> *).
(Eq a, Num a, StoreReadBase m) =>
a -> HashSet TxHash -> HashSet TxHash -> [TxHash] -> m (Maybe Bool)
inputs 10000 HashSet TxHash
forall a. HashSet a
HashSet.empty HashSet TxHash
forall a. HashSet a
HashSet.empty [TxHash
txid]
  where
    inputs :: a -> HashSet TxHash -> HashSet TxHash -> [TxHash] -> m (Maybe Bool)
inputs 0 _ _ [] = Maybe Bool -> m (Maybe Bool)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Bool
forall a. Maybe a
Nothing
    inputs i :: a
i is :: HashSet TxHash
is ns :: HashSet TxHash
ns [] =
        let is' :: HashSet TxHash
is' = HashSet TxHash -> HashSet TxHash -> HashSet TxHash
forall a. (Eq a, Hashable a) => HashSet a -> HashSet a -> HashSet a
HashSet.union HashSet TxHash
is HashSet TxHash
ns
            ns' :: HashSet a
ns' = HashSet a
forall a. HashSet a
HashSet.empty
            ts :: [TxHash]
ts = HashSet TxHash -> [TxHash]
forall a. HashSet a -> [a]
HashSet.toList (HashSet TxHash -> HashSet TxHash -> HashSet TxHash
forall a. (Eq a, Hashable a) => HashSet a -> HashSet a -> HashSet a
HashSet.difference HashSet TxHash
ns HashSet TxHash
is)
        in case [TxHash]
ts of
               [] -> Maybe Bool -> m (Maybe Bool)
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
False)
               _  -> a -> HashSet TxHash -> HashSet TxHash -> [TxHash] -> m (Maybe Bool)
inputs a
i HashSet TxHash
is' HashSet TxHash
forall a. HashSet a
ns' [TxHash]
ts
    inputs i :: a
i is :: HashSet TxHash
is ns :: HashSet TxHash
ns (t :: TxHash
t:ts :: [TxHash]
ts) = TxHash -> m (Maybe Transaction)
forall (m :: * -> *).
(Monad m, StoreReadBase m) =>
TxHash -> m (Maybe Transaction)
getTransaction TxHash
t m (Maybe Transaction)
-> (Maybe Transaction -> m (Maybe Bool)) -> m (Maybe Bool)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
        Nothing -> Maybe Bool -> m (Maybe Bool)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Bool
forall a. Maybe a
Nothing
        Just tx :: Transaction
tx | Transaction -> Bool
height_check Transaction
tx ->
                      if Transaction -> Bool
cb_check Transaction
tx
                      then Maybe Bool -> m (Maybe Bool)
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
True)
                      else let ns' :: HashSet TxHash
ns' = HashSet TxHash -> HashSet TxHash -> HashSet TxHash
forall a. (Eq a, Hashable a) => HashSet a -> HashSet a -> HashSet a
HashSet.union (Transaction -> HashSet TxHash
ins Transaction
tx) HashSet TxHash
ns
                          in a -> HashSet TxHash -> HashSet TxHash -> [TxHash] -> m (Maybe Bool)
inputs (a
i a -> a -> a
forall a. Num a => a -> a -> a
- 1) HashSet TxHash
is HashSet TxHash
ns' [TxHash]
ts
                | Bool
otherwise -> a -> HashSet TxHash -> HashSet TxHash -> [TxHash] -> m (Maybe Bool)
inputs (a
i a -> a -> a
forall a. Num a => a -> a -> a
- 1) HashSet TxHash
is HashSet TxHash
ns [TxHash]
ts
    cb_check :: Transaction -> Bool
cb_check = (StoreInput -> Bool) -> [StoreInput] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any StoreInput -> Bool
isCoinbase ([StoreInput] -> Bool)
-> (Transaction -> [StoreInput]) -> Transaction -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Transaction -> [StoreInput]
transactionInputs
    ins :: Transaction -> HashSet TxHash
ins = [TxHash] -> HashSet TxHash
forall a. (Eq a, Hashable a) => [a] -> HashSet a
HashSet.fromList ([TxHash] -> HashSet TxHash)
-> (Transaction -> [TxHash]) -> Transaction -> HashSet TxHash
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (StoreInput -> TxHash) -> [StoreInput] -> [TxHash]
forall a b. (a -> b) -> [a] -> [b]
map (OutPoint -> TxHash
outPointHash (OutPoint -> TxHash)
-> (StoreInput -> OutPoint) -> StoreInput -> TxHash
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StoreInput -> OutPoint
inputPoint) ([StoreInput] -> [TxHash])
-> (Transaction -> [StoreInput]) -> Transaction -> [TxHash]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Transaction -> [StoreInput]
transactionInputs
    height_check :: Transaction -> Bool
height_check tx :: Transaction
tx =
        case Transaction -> BlockRef
transactionBlock Transaction
tx of
            BlockRef h :: Word32
h _ -> Word32
h Word32 -> Word32 -> Bool
forall a. Ord a => a -> a -> Bool
> Word32
height
            _            -> Bool
True

-- POST Transaction --

scottyPostTx :: (MonadUnliftIO m, MonadLoggerIO m) => PostTx -> WebT m TxId
scottyPostTx :: PostTx -> WebT m TxId
scottyPostTx (PostTx tx :: Tx
tx) =
    ReaderT WebConfig m WebConfig
-> ActionT Except (ReaderT WebConfig m) WebConfig
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ReaderT WebConfig m WebConfig
forall r (m :: * -> *). MonadReader r m => m r
ask ActionT Except (ReaderT WebConfig m) WebConfig
-> (WebConfig -> WebT m TxId) -> WebT m TxId
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \cfg :: WebConfig
cfg -> ReaderT WebConfig m (Either PubExcept ())
-> ActionT Except (ReaderT WebConfig m) (Either PubExcept ())
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (WebConfig -> Tx -> ReaderT WebConfig m (Either PubExcept ())
forall (m :: * -> *).
(MonadUnliftIO m, MonadLoggerIO m, StoreReadBase m) =>
WebConfig -> Tx -> m (Either PubExcept ())
publishTx WebConfig
cfg Tx
tx) ActionT Except (ReaderT WebConfig m) (Either PubExcept ())
-> (Either PubExcept () -> WebT m TxId) -> WebT m TxId
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
        Right () -> TxId -> WebT m TxId
forall (m :: * -> *) a. Monad m => a -> m a
return (TxId -> WebT m TxId) -> TxId -> WebT m TxId
forall a b. (a -> b) -> a -> b
$ TxHash -> TxId
TxId (Tx -> TxHash
txHash Tx
tx)
        Left e :: PubExcept
e@(PubReject _) -> Except -> WebT m TxId
forall e (m :: * -> *) a.
(ScottyError e, Monad m) =>
e -> ActionT e m a
S.raise (Except -> WebT m TxId) -> Except -> WebT m TxId
forall a b. (a -> b) -> a -> b
$ String -> Except
UserError (String -> Except) -> String -> Except
forall a b. (a -> b) -> a -> b
$ PubExcept -> String
forall a. Show a => a -> String
show PubExcept
e
        _ -> Except -> WebT m TxId
forall e (m :: * -> *) a.
(ScottyError e, Monad m) =>
e -> ActionT e m a
S.raise Except
ServerError

-- | Publish a new transaction to the network.
publishTx ::
       (MonadUnliftIO m, MonadLoggerIO m, StoreReadBase m)
    => WebConfig
    -> Tx
    -> m (Either PubExcept ())
publishTx :: WebConfig -> Tx -> m (Either PubExcept ())
publishTx cfg :: WebConfig
cfg tx :: Tx
tx =
    Publisher StoreEvent
-> (Inbox StoreEvent -> m (Either PubExcept ()))
-> m (Either PubExcept ())
forall (m :: * -> *) msg a.
MonadUnliftIO m =>
Publisher msg -> (Inbox msg -> m a) -> m a
withSubscription Publisher StoreEvent
pub ((Inbox StoreEvent -> m (Either PubExcept ()))
 -> m (Either PubExcept ()))
-> (Inbox StoreEvent -> m (Either PubExcept ()))
-> m (Either PubExcept ())
forall a b. (a -> b) -> a -> b
$ \s :: Inbox StoreEvent
s ->
        TxHash -> m (Maybe Transaction)
forall (m :: * -> *).
(Monad m, StoreReadBase m) =>
TxHash -> m (Maybe Transaction)
getTransaction (Tx -> TxHash
txHash Tx
tx) m (Maybe Transaction)
-> (Maybe Transaction -> m (Either PubExcept ()))
-> m (Either PubExcept ())
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
            Just _ -> Either PubExcept () -> m (Either PubExcept ())
forall (m :: * -> *) a. Monad m => a -> m a
return (Either PubExcept () -> m (Either PubExcept ()))
-> Either PubExcept () -> m (Either PubExcept ())
forall a b. (a -> b) -> a -> b
$ () -> Either PubExcept ()
forall a b. b -> Either a b
Right ()
            Nothing -> Inbox StoreEvent -> m (Either PubExcept ())
forall (m :: * -> *) (mbox :: * -> *).
(MonadIO m, InChan mbox) =>
mbox StoreEvent -> m (Either PubExcept ())
go Inbox StoreEvent
s
  where
    pub :: Publisher StoreEvent
pub = Store -> Publisher StoreEvent
storePublisher (WebConfig -> Store
webStore WebConfig
cfg)
    mgr :: PeerManager
mgr = Store -> PeerManager
storeManager (WebConfig -> Store
webStore WebConfig
cfg)
    net :: Network
net = Store -> Network
storeNetwork (WebConfig -> Store
webStore WebConfig
cfg)
    go :: mbox StoreEvent -> m (Either PubExcept ())
go s :: mbox StoreEvent
s =
        PeerManager -> m [OnlinePeer]
forall (m :: * -> *). MonadIO m => PeerManager -> m [OnlinePeer]
getPeers PeerManager
mgr m [OnlinePeer]
-> ([OnlinePeer] -> m (Either PubExcept ()))
-> m (Either PubExcept ())
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
            [] -> Either PubExcept () -> m (Either PubExcept ())
forall (m :: * -> *) a. Monad m => a -> m a
return (Either PubExcept () -> m (Either PubExcept ()))
-> Either PubExcept () -> m (Either PubExcept ())
forall a b. (a -> b) -> a -> b
$ PubExcept -> Either PubExcept ()
forall a b. a -> Either a b
Left PubExcept
PubNoPeers
            OnlinePeer {onlinePeerMailbox :: OnlinePeer -> Peer
onlinePeerMailbox = Peer
p}:_ -> do
                Tx -> Message
MTx Tx
tx Message -> Peer -> m ()
forall (m :: * -> *). MonadIO m => Message -> Peer -> m ()
`sendMessage` Peer
p
                let v :: InvType
v =
                        if Network -> Bool
getSegWit Network
net
                            then InvType
InvWitnessTx
                            else InvType
InvTx
                Message -> Peer -> m ()
forall (m :: * -> *). MonadIO m => Message -> Peer -> m ()
sendMessage
                    (GetData -> Message
MGetData ([InvVector] -> GetData
GetData [InvType -> Hash256 -> InvVector
InvVector InvType
v (TxHash -> Hash256
getTxHash (Tx -> TxHash
txHash Tx
tx))]))
                    Peer
p
                Peer -> mbox StoreEvent -> m (Either PubExcept ())
forall (m :: * -> *) (mbox :: * -> *).
(MonadIO m, InChan mbox) =>
Peer -> mbox StoreEvent -> m (Either PubExcept ())
f Peer
p mbox StoreEvent
s
    t :: Int
t = 5 Int -> Int -> Int
forall a. Num a => a -> a -> a
* 1000 Int -> Int -> Int
forall a. Num a => a -> a -> a
* 1000
    f :: Peer -> mbox StoreEvent -> m (Either PubExcept ())
f p :: Peer
p s :: mbox StoreEvent
s
      | WebConfig -> Bool
webNoMempool WebConfig
cfg = Either PubExcept () -> m (Either PubExcept ())
forall (m :: * -> *) a. Monad m => a -> m a
return (Either PubExcept () -> m (Either PubExcept ()))
-> Either PubExcept () -> m (Either PubExcept ())
forall a b. (a -> b) -> a -> b
$ () -> Either PubExcept ()
forall a b. b -> Either a b
Right ()
      | Bool
otherwise =
        IO (Maybe (Either PubExcept ())) -> m (Maybe (Either PubExcept ()))
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (Int -> IO (Either PubExcept ()) -> IO (Maybe (Either PubExcept ()))
forall (m :: * -> *) a.
MonadUnliftIO m =>
Int -> m a -> m (Maybe a)
timeout Int
t (Peer -> mbox StoreEvent -> IO (Either PubExcept ())
forall (m :: * -> *) (mbox :: * -> *).
(InChan mbox, MonadIO m) =>
Peer -> mbox StoreEvent -> m (Either PubExcept ())
g Peer
p mbox StoreEvent
s)) m (Maybe (Either PubExcept ()))
-> (Maybe (Either PubExcept ()) -> m (Either PubExcept ()))
-> m (Either PubExcept ())
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
            Nothing -> Either PubExcept () -> m (Either PubExcept ())
forall (m :: * -> *) a. Monad m => a -> m a
return (Either PubExcept () -> m (Either PubExcept ()))
-> Either PubExcept () -> m (Either PubExcept ())
forall a b. (a -> b) -> a -> b
$ PubExcept -> Either PubExcept ()
forall a b. a -> Either a b
Left PubExcept
PubTimeout
            Just (Left e :: PubExcept
e) -> Either PubExcept () -> m (Either PubExcept ())
forall (m :: * -> *) a. Monad m => a -> m a
return (Either PubExcept () -> m (Either PubExcept ()))
-> Either PubExcept () -> m (Either PubExcept ())
forall a b. (a -> b) -> a -> b
$ PubExcept -> Either PubExcept ()
forall a b. a -> Either a b
Left PubExcept
e
            Just (Right ()) -> Either PubExcept () -> m (Either PubExcept ())
forall (m :: * -> *) a. Monad m => a -> m a
return (Either PubExcept () -> m (Either PubExcept ()))
-> Either PubExcept () -> m (Either PubExcept ())
forall a b. (a -> b) -> a -> b
$ () -> Either PubExcept ()
forall a b. b -> Either a b
Right ()
    g :: Peer -> mbox StoreEvent -> m (Either PubExcept ())
g p :: Peer
p s :: mbox StoreEvent
s =
        mbox StoreEvent -> m StoreEvent
forall (mbox :: * -> *) (m :: * -> *) msg.
(InChan mbox, MonadIO m) =>
mbox msg -> m msg
receive mbox StoreEvent
s m StoreEvent
-> (StoreEvent -> m (Either PubExcept ()))
-> m (Either PubExcept ())
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
            StoreTxReject p' :: Peer
p' h' :: TxHash
h' c :: RejectCode
c _
                | Peer
p Peer -> Peer -> Bool
forall a. Eq a => a -> a -> Bool
== Peer
p' Bool -> Bool -> Bool
&& TxHash
h' TxHash -> TxHash -> Bool
forall a. Eq a => a -> a -> Bool
== Tx -> TxHash
txHash Tx
tx -> Either PubExcept () -> m (Either PubExcept ())
forall (m :: * -> *) a. Monad m => a -> m a
return (Either PubExcept () -> m (Either PubExcept ()))
-> (PubExcept -> Either PubExcept ())
-> PubExcept
-> m (Either PubExcept ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PubExcept -> Either PubExcept ()
forall a b. a -> Either a b
Left (PubExcept -> m (Either PubExcept ()))
-> PubExcept -> m (Either PubExcept ())
forall a b. (a -> b) -> a -> b
$ RejectCode -> PubExcept
PubReject RejectCode
c
            StorePeerDisconnected p' :: Peer
p'
                | Peer
p Peer -> Peer -> Bool
forall a. Eq a => a -> a -> Bool
== Peer
p' -> Either PubExcept () -> m (Either PubExcept ())
forall (m :: * -> *) a. Monad m => a -> m a
return (Either PubExcept () -> m (Either PubExcept ()))
-> Either PubExcept () -> m (Either PubExcept ())
forall a b. (a -> b) -> a -> b
$ PubExcept -> Either PubExcept ()
forall a b. a -> Either a b
Left PubExcept
PubPeerDisconnected
            StoreMempoolNew h' :: TxHash
h'
                | TxHash
h' TxHash -> TxHash -> Bool
forall a. Eq a => a -> a -> Bool
== Tx -> TxHash
txHash Tx
tx -> Either PubExcept () -> m (Either PubExcept ())
forall (m :: * -> *) a. Monad m => a -> m a
return (Either PubExcept () -> m (Either PubExcept ()))
-> Either PubExcept () -> m (Either PubExcept ())
forall a b. (a -> b) -> a -> b
$ () -> Either PubExcept ()
forall a b. b -> Either a b
Right ()
            _ -> Peer -> mbox StoreEvent -> m (Either PubExcept ())
g Peer
p mbox StoreEvent
s

-- GET Mempool / Events --

scottyMempool ::
       (MonadUnliftIO m, MonadLoggerIO m) => GetMempool -> WebT m [TxHash]
scottyMempool :: GetMempool -> WebT m [TxHash]
scottyMempool (GetMempool limitM :: Maybe LimitParam
limitM (OffsetParam o :: Natural
o)) = do
    WebLimits
wl <- ReaderT WebConfig m WebLimits
-> ActionT Except (ReaderT WebConfig m) WebLimits
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (ReaderT WebConfig m WebLimits
 -> ActionT Except (ReaderT WebConfig m) WebLimits)
-> ReaderT WebConfig m WebLimits
-> ActionT Except (ReaderT WebConfig m) WebLimits
forall a b. (a -> b) -> a -> b
$ (WebConfig -> WebLimits) -> ReaderT WebConfig m WebLimits
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WebConfig -> WebLimits
webMaxLimits
    let wl' :: WebLimits
wl' = WebLimits
wl { maxLimitCount :: Word32
maxLimitCount = 0 }
        l :: Limits
l = Word32 -> Word32 -> Maybe Start -> Limits
Limits (WebLimits -> Bool -> Maybe LimitParam -> Word32
validateLimit WebLimits
wl' Bool
False Maybe LimitParam
limitM) (Natural -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Natural
o) Maybe Start
forall a. Maybe a
Nothing
    ((Word64, TxHash) -> TxHash) -> [(Word64, TxHash)] -> [TxHash]
forall a b. (a -> b) -> [a] -> [b]
map (Word64, TxHash) -> TxHash
forall a b. (a, b) -> b
snd ([(Word64, TxHash)] -> [TxHash])
-> ([(Word64, TxHash)] -> [(Word64, TxHash)])
-> [(Word64, TxHash)]
-> [TxHash]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Limits -> [(Word64, TxHash)] -> [(Word64, TxHash)]
forall a. Limits -> [a] -> [a]
applyLimits Limits
l ([(Word64, TxHash)] -> [TxHash])
-> ActionT Except (ReaderT WebConfig m) [(Word64, TxHash)]
-> WebT m [TxHash]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ActionT Except (ReaderT WebConfig m) [(Word64, TxHash)]
forall (m :: * -> *). StoreReadBase m => m [(Word64, TxHash)]
getMempool

scottyEvents :: MonadLoggerIO m => WebT m ()
scottyEvents :: WebT m ()
scottyEvents = do
    WebT m ()
forall (m :: * -> *) e. (Monad m, ScottyError e) => ActionT e m ()
setHeaders
    SerialAs
proto <- Bool -> ActionT Except (ReaderT WebConfig m) SerialAs
forall (m :: * -> *). Monad m => Bool -> ActionT Except m SerialAs
setupContentType Bool
False
    Publisher StoreEvent
pub <- ReaderT WebConfig m (Publisher StoreEvent)
-> ActionT Except (ReaderT WebConfig m) (Publisher StoreEvent)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (ReaderT WebConfig m (Publisher StoreEvent)
 -> ActionT Except (ReaderT WebConfig m) (Publisher StoreEvent))
-> ReaderT WebConfig m (Publisher StoreEvent)
-> ActionT Except (ReaderT WebConfig m) (Publisher StoreEvent)
forall a b. (a -> b) -> a -> b
$ (WebConfig -> Publisher StoreEvent)
-> ReaderT WebConfig m (Publisher StoreEvent)
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks (Store -> Publisher StoreEvent
storePublisher (Store -> Publisher StoreEvent)
-> (WebConfig -> Store) -> WebConfig -> Publisher StoreEvent
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebConfig -> Store
webStore)
    StreamingBody -> WebT m ()
forall (m :: * -> *) e. Monad m => StreamingBody -> ActionT e m ()
S.stream (StreamingBody -> WebT m ()) -> StreamingBody -> WebT m ()
forall a b. (a -> b) -> a -> b
$ \io :: Builder -> IO ()
io flush' :: IO ()
flush' ->
        Publisher StoreEvent -> (Inbox StoreEvent -> IO ()) -> IO ()
forall (m :: * -> *) msg a.
MonadUnliftIO m =>
Publisher msg -> (Inbox msg -> m a) -> m a
withSubscription Publisher StoreEvent
pub ((Inbox StoreEvent -> IO ()) -> IO ())
-> (Inbox StoreEvent -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \sub :: Inbox StoreEvent
sub ->
            IO () -> IO ()
forall (f :: * -> *) a b. Applicative f => f a -> f b
forever (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
            IO ()
flush' IO () -> IO (Maybe Event) -> IO (Maybe Event)
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Inbox StoreEvent -> IO (Maybe Event)
receiveEvent Inbox StoreEvent
sub IO (Maybe Event) -> (Maybe Event -> IO ()) -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= IO () -> (Event -> IO ()) -> Maybe Event -> IO ()
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()) (Builder -> IO ()
io (Builder -> IO ()) -> (Event -> Builder) -> Event -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SerialAs -> Event -> Builder
forall a. (Serialize a, ToJSON a) => SerialAs -> a -> Builder
serial SerialAs
proto)
  where
    serial :: SerialAs -> a -> Builder
serial proto :: SerialAs
proto e :: a
e =
        ByteString -> Builder
lazyByteString (ByteString -> Builder) -> ByteString -> Builder
forall a b. (a -> b) -> a -> b
$ SerialAs -> (a -> Encoding) -> (a -> Value) -> a -> ByteString
forall a.
Serialize a =>
SerialAs -> (a -> Encoding) -> (a -> Value) -> a -> ByteString
protoSerial SerialAs
proto a -> Encoding
forall a. ToJSON a => a -> Encoding
toEncoding a -> Value
forall a. ToJSON a => a -> Value
toJSON a
e ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> SerialAs -> ByteString
forall p. (Monoid p, IsString p) => SerialAs -> p
newLine SerialAs
proto
    newLine :: SerialAs -> p
newLine SerialAsBinary     = p
forall a. Monoid a => a
mempty
    newLine SerialAsJSON       = "\n"
    newLine SerialAsPrettyJSON = p
forall a. Monoid a => a
mempty

receiveEvent :: Inbox StoreEvent -> IO (Maybe Event)
receiveEvent :: Inbox StoreEvent -> IO (Maybe Event)
receiveEvent sub :: Inbox StoreEvent
sub = do
    StoreEvent
se <- Inbox StoreEvent -> IO StoreEvent
forall (mbox :: * -> *) (m :: * -> *) msg.
(InChan mbox, MonadIO m) =>
mbox msg -> m msg
receive Inbox StoreEvent
sub
    Maybe Event -> IO (Maybe Event)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe Event -> IO (Maybe Event))
-> Maybe Event -> IO (Maybe Event)
forall a b. (a -> b) -> a -> b
$
        case StoreEvent
se of
            StoreBestBlock b :: BlockHash
b  -> Event -> Maybe Event
forall a. a -> Maybe a
Just (BlockHash -> Event
EventBlock BlockHash
b)
            StoreMempoolNew t :: TxHash
t -> Event -> Maybe Event
forall a. a -> Maybe a
Just (TxHash -> Event
EventTx TxHash
t)
            _                 -> Maybe Event
forall a. Maybe a
Nothing

-- GET Address Transactions --

scottyAddrTxs ::
       (MonadUnliftIO m, MonadLoggerIO m) => GetAddrTxs -> WebT m [TxRef]
scottyAddrTxs :: GetAddrTxs -> WebT m [TxRef]
scottyAddrTxs (GetAddrTxs addr :: Address
addr pLimits :: LimitsParam
pLimits) =
    Address -> Limits -> WebT m [TxRef]
forall (m :: * -> *).
StoreReadExtra m =>
Address -> Limits -> m [TxRef]
getAddressTxs Address
addr (Limits -> WebT m [TxRef])
-> ActionT Except (ReaderT WebConfig m) Limits -> WebT m [TxRef]
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Bool -> LimitsParam -> ActionT Except (ReaderT WebConfig m) Limits
forall (m :: * -> *).
(MonadUnliftIO m, MonadLoggerIO m) =>
Bool -> LimitsParam -> WebT m Limits
paramToLimits Bool
False LimitsParam
pLimits

scottyAddrsTxs ::
       (MonadUnliftIO m, MonadLoggerIO m) => GetAddrsTxs -> WebT m [TxRef]
scottyAddrsTxs :: GetAddrsTxs -> WebT m [TxRef]
scottyAddrsTxs (GetAddrsTxs addrs :: [Address]
addrs pLimits :: LimitsParam
pLimits) =
    [Address] -> Limits -> WebT m [TxRef]
forall (m :: * -> *).
StoreReadExtra m =>
[Address] -> Limits -> m [TxRef]
getAddressesTxs [Address]
addrs (Limits -> WebT m [TxRef])
-> ActionT Except (ReaderT WebConfig m) Limits -> WebT m [TxRef]
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Bool -> LimitsParam -> ActionT Except (ReaderT WebConfig m) Limits
forall (m :: * -> *).
(MonadUnliftIO m, MonadLoggerIO m) =>
Bool -> LimitsParam -> WebT m Limits
paramToLimits Bool
False LimitsParam
pLimits

scottyAddrTxsFull ::
       (MonadUnliftIO m, MonadLoggerIO m)
    => GetAddrTxsFull
    -> WebT m [Transaction]
scottyAddrTxsFull :: GetAddrTxsFull -> WebT m [Transaction]
scottyAddrTxsFull (GetAddrTxsFull addr :: Address
addr pLimits :: LimitsParam
pLimits) = do
    [TxRef]
txs <- Address -> Limits -> ActionT Except (ReaderT WebConfig m) [TxRef]
forall (m :: * -> *).
StoreReadExtra m =>
Address -> Limits -> m [TxRef]
getAddressTxs Address
addr (Limits -> ActionT Except (ReaderT WebConfig m) [TxRef])
-> ActionT Except (ReaderT WebConfig m) Limits
-> ActionT Except (ReaderT WebConfig m) [TxRef]
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Bool -> LimitsParam -> ActionT Except (ReaderT WebConfig m) Limits
forall (m :: * -> *).
(MonadUnliftIO m, MonadLoggerIO m) =>
Bool -> LimitsParam -> WebT m Limits
paramToLimits Bool
True LimitsParam
pLimits
    [Maybe Transaction] -> [Transaction]
forall a. [Maybe a] -> [a]
catMaybes ([Maybe Transaction] -> [Transaction])
-> ActionT Except (ReaderT WebConfig m) [Maybe Transaction]
-> WebT m [Transaction]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (TxRef -> ActionT Except (ReaderT WebConfig m) (Maybe Transaction))
-> [TxRef]
-> ActionT Except (ReaderT WebConfig m) [Maybe Transaction]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (TxHash -> ActionT Except (ReaderT WebConfig m) (Maybe Transaction)
forall (m :: * -> *).
(Monad m, StoreReadBase m) =>
TxHash -> m (Maybe Transaction)
getTransaction (TxHash
 -> ActionT Except (ReaderT WebConfig m) (Maybe Transaction))
-> (TxRef -> TxHash)
-> TxRef
-> ActionT Except (ReaderT WebConfig m) (Maybe Transaction)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TxRef -> TxHash
txRefHash) [TxRef]
txs

scottyAddrsTxsFull :: (MonadUnliftIO m, MonadLoggerIO m)
                   => GetAddrsTxsFull -> WebT m [Transaction]
scottyAddrsTxsFull :: GetAddrsTxsFull -> WebT m [Transaction]
scottyAddrsTxsFull (GetAddrsTxsFull addrs :: [Address]
addrs pLimits :: LimitsParam
pLimits) = do
    [TxRef]
txs <- [Address] -> Limits -> ActionT Except (ReaderT WebConfig m) [TxRef]
forall (m :: * -> *).
StoreReadExtra m =>
[Address] -> Limits -> m [TxRef]
getAddressesTxs [Address]
addrs (Limits -> ActionT Except (ReaderT WebConfig m) [TxRef])
-> ActionT Except (ReaderT WebConfig m) Limits
-> ActionT Except (ReaderT WebConfig m) [TxRef]
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Bool -> LimitsParam -> ActionT Except (ReaderT WebConfig m) Limits
forall (m :: * -> *).
(MonadUnliftIO m, MonadLoggerIO m) =>
Bool -> LimitsParam -> WebT m Limits
paramToLimits Bool
True LimitsParam
pLimits
    [Maybe Transaction] -> [Transaction]
forall a. [Maybe a] -> [a]
catMaybes ([Maybe Transaction] -> [Transaction])
-> ActionT Except (ReaderT WebConfig m) [Maybe Transaction]
-> WebT m [Transaction]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (TxRef -> ActionT Except (ReaderT WebConfig m) (Maybe Transaction))
-> [TxRef]
-> ActionT Except (ReaderT WebConfig m) [Maybe Transaction]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (TxHash -> ActionT Except (ReaderT WebConfig m) (Maybe Transaction)
forall (m :: * -> *).
(Monad m, StoreReadBase m) =>
TxHash -> m (Maybe Transaction)
getTransaction (TxHash
 -> ActionT Except (ReaderT WebConfig m) (Maybe Transaction))
-> (TxRef -> TxHash)
-> TxRef
-> ActionT Except (ReaderT WebConfig m) (Maybe Transaction)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TxRef -> TxHash
txRefHash) [TxRef]
txs

scottyAddrBalance :: (MonadUnliftIO m, MonadLoggerIO m)
                  => GetAddrBalance -> WebT m Balance
scottyAddrBalance :: GetAddrBalance -> WebT m Balance
scottyAddrBalance (GetAddrBalance addr :: Address
addr) = Address -> WebT m Balance
forall (m :: * -> *). StoreReadBase m => Address -> m Balance
getDefaultBalance Address
addr

scottyAddrsBalance ::
       (MonadUnliftIO m, MonadLoggerIO m) => GetAddrsBalance -> WebT m [Balance]
scottyAddrsBalance :: GetAddrsBalance -> WebT m [Balance]
scottyAddrsBalance (GetAddrsBalance addrs :: [Address]
addrs) = [Address] -> WebT m [Balance]
forall (m :: * -> *). StoreReadExtra m => [Address] -> m [Balance]
getBalances [Address]
addrs

scottyAddrUnspent ::
       (MonadUnliftIO m, MonadLoggerIO m) => GetAddrUnspent -> WebT m [Unspent]
scottyAddrUnspent :: GetAddrUnspent -> WebT m [Unspent]
scottyAddrUnspent (GetAddrUnspent addr :: Address
addr pLimits :: LimitsParam
pLimits) =
    Address -> Limits -> WebT m [Unspent]
forall (m :: * -> *).
StoreReadExtra m =>
Address -> Limits -> m [Unspent]
getAddressUnspents Address
addr (Limits -> WebT m [Unspent])
-> ActionT Except (ReaderT WebConfig m) Limits -> WebT m [Unspent]
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Bool -> LimitsParam -> ActionT Except (ReaderT WebConfig m) Limits
forall (m :: * -> *).
(MonadUnliftIO m, MonadLoggerIO m) =>
Bool -> LimitsParam -> WebT m Limits
paramToLimits Bool
False LimitsParam
pLimits

scottyAddrsUnspent ::
       (MonadUnliftIO m, MonadLoggerIO m) => GetAddrsUnspent -> WebT m [Unspent]
scottyAddrsUnspent :: GetAddrsUnspent -> WebT m [Unspent]
scottyAddrsUnspent (GetAddrsUnspent addrs :: [Address]
addrs pLimits :: LimitsParam
pLimits) =
    [Address] -> Limits -> WebT m [Unspent]
forall (m :: * -> *).
StoreReadExtra m =>
[Address] -> Limits -> m [Unspent]
getAddressesUnspents [Address]
addrs (Limits -> WebT m [Unspent])
-> ActionT Except (ReaderT WebConfig m) Limits -> WebT m [Unspent]
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Bool -> LimitsParam -> ActionT Except (ReaderT WebConfig m) Limits
forall (m :: * -> *).
(MonadUnliftIO m, MonadLoggerIO m) =>
Bool -> LimitsParam -> WebT m Limits
paramToLimits Bool
False LimitsParam
pLimits

-- GET XPubs --

scottyXPub ::
       (MonadUnliftIO m, MonadLoggerIO m) => GetXPub -> WebT m XPubSummary
scottyXPub :: GetXPub -> WebT m XPubSummary
scottyXPub (GetXPub xpub :: XPubKey
xpub deriv :: DeriveType
deriv (NoCache noCache :: Bool
noCache)) =
    ReaderT WebConfig m XPubSummary -> WebT m XPubSummary
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (ReaderT WebConfig m XPubSummary -> WebT m XPubSummary)
-> (ReaderT WebConfig m XPubSummary
    -> ReaderT WebConfig m XPubSummary)
-> ReaderT WebConfig m XPubSummary
-> WebT m XPubSummary
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool
-> ReaderT WebConfig m XPubSummary
-> ReaderT WebConfig m XPubSummary
forall (m :: * -> *) a.
MonadIO m =>
Bool -> ReaderT WebConfig m a -> ReaderT WebConfig m a
runNoCache Bool
noCache (ReaderT WebConfig m XPubSummary -> WebT m XPubSummary)
-> ReaderT WebConfig m XPubSummary -> WebT m XPubSummary
forall a b. (a -> b) -> a -> b
$ XPubSpec -> ReaderT WebConfig m XPubSummary
forall (m :: * -> *). StoreReadExtra m => XPubSpec -> m XPubSummary
xPubSummary (XPubSpec -> ReaderT WebConfig m XPubSummary)
-> XPubSpec -> ReaderT WebConfig m XPubSummary
forall a b. (a -> b) -> a -> b
$ XPubKey -> DeriveType -> XPubSpec
XPubSpec XPubKey
xpub DeriveType
deriv

scottyXPubTxs ::
       (MonadUnliftIO m, MonadLoggerIO m) => GetXPubTxs -> WebT m [TxRef]
scottyXPubTxs :: GetXPubTxs -> WebT m [TxRef]
scottyXPubTxs (GetXPubTxs xpub :: XPubKey
xpub deriv :: DeriveType
deriv pLimits :: LimitsParam
pLimits (NoCache noCache :: Bool
noCache)) = do
    Limits
limits <- Bool -> LimitsParam -> WebT m Limits
forall (m :: * -> *).
(MonadUnliftIO m, MonadLoggerIO m) =>
Bool -> LimitsParam -> WebT m Limits
paramToLimits Bool
False LimitsParam
pLimits
    ReaderT WebConfig m [TxRef] -> WebT m [TxRef]
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (ReaderT WebConfig m [TxRef] -> WebT m [TxRef])
-> (ReaderT WebConfig m [TxRef] -> ReaderT WebConfig m [TxRef])
-> ReaderT WebConfig m [TxRef]
-> WebT m [TxRef]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> ReaderT WebConfig m [TxRef] -> ReaderT WebConfig m [TxRef]
forall (m :: * -> *) a.
MonadIO m =>
Bool -> ReaderT WebConfig m a -> ReaderT WebConfig m a
runNoCache Bool
noCache (ReaderT WebConfig m [TxRef] -> WebT m [TxRef])
-> ReaderT WebConfig m [TxRef] -> WebT m [TxRef]
forall a b. (a -> b) -> a -> b
$ XPubSpec -> Limits -> ReaderT WebConfig m [TxRef]
forall (m :: * -> *).
StoreReadExtra m =>
XPubSpec -> Limits -> m [TxRef]
xPubTxs (XPubKey -> DeriveType -> XPubSpec
XPubSpec XPubKey
xpub DeriveType
deriv) Limits
limits

scottyXPubTxsFull ::
       (MonadUnliftIO m, MonadLoggerIO m)
    => GetXPubTxsFull
    -> WebT m [Transaction]
scottyXPubTxsFull :: GetXPubTxsFull -> WebT m [Transaction]
scottyXPubTxsFull (GetXPubTxsFull xpub :: XPubKey
xpub deriv :: DeriveType
deriv pLimits :: LimitsParam
pLimits n :: NoCache
n@(NoCache noCache :: Bool
noCache)) = do
    [TxRef]
refs <- GetXPubTxs -> WebT m [TxRef]
forall (m :: * -> *).
(MonadUnliftIO m, MonadLoggerIO m) =>
GetXPubTxs -> WebT m [TxRef]
scottyXPubTxs (XPubKey -> DeriveType -> LimitsParam -> NoCache -> GetXPubTxs
GetXPubTxs XPubKey
xpub DeriveType
deriv LimitsParam
pLimits NoCache
n)
    [Maybe Transaction]
txs <- ReaderT WebConfig m [Maybe Transaction]
-> ActionT Except (ReaderT WebConfig m) [Maybe Transaction]
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (ReaderT WebConfig m [Maybe Transaction]
 -> ActionT Except (ReaderT WebConfig m) [Maybe Transaction])
-> (ReaderT WebConfig m [Maybe Transaction]
    -> ReaderT WebConfig m [Maybe Transaction])
-> ReaderT WebConfig m [Maybe Transaction]
-> ActionT Except (ReaderT WebConfig m) [Maybe Transaction]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool
-> ReaderT WebConfig m [Maybe Transaction]
-> ReaderT WebConfig m [Maybe Transaction]
forall (m :: * -> *) a.
MonadIO m =>
Bool -> ReaderT WebConfig m a -> ReaderT WebConfig m a
runNoCache Bool
noCache (ReaderT WebConfig m [Maybe Transaction]
 -> ActionT Except (ReaderT WebConfig m) [Maybe Transaction])
-> ReaderT WebConfig m [Maybe Transaction]
-> ActionT Except (ReaderT WebConfig m) [Maybe Transaction]
forall a b. (a -> b) -> a -> b
$ (TxRef -> ReaderT WebConfig m (Maybe Transaction))
-> [TxRef] -> ReaderT WebConfig m [Maybe Transaction]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (TxHash -> ReaderT WebConfig m (Maybe Transaction)
forall (m :: * -> *).
(Monad m, StoreReadBase m) =>
TxHash -> m (Maybe Transaction)
getTransaction (TxHash -> ReaderT WebConfig m (Maybe Transaction))
-> (TxRef -> TxHash)
-> TxRef
-> ReaderT WebConfig m (Maybe Transaction)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TxRef -> TxHash
txRefHash) [TxRef]
refs
    [Transaction] -> WebT m [Transaction]
forall (m :: * -> *) a. Monad m => a -> m a
return ([Transaction] -> WebT m [Transaction])
-> [Transaction] -> WebT m [Transaction]
forall a b. (a -> b) -> a -> b
$ [Maybe Transaction] -> [Transaction]
forall a. [Maybe a] -> [a]
catMaybes [Maybe Transaction]
txs

scottyXPubBalances ::
       (MonadUnliftIO m, MonadLoggerIO m) => GetXPubBalances -> WebT m [XPubBal]
scottyXPubBalances :: GetXPubBalances -> WebT m [XPubBal]
scottyXPubBalances (GetXPubBalances xpub :: XPubKey
xpub deriv :: DeriveType
deriv (NoCache noCache :: Bool
noCache)) =
    (XPubBal -> Bool) -> [XPubBal] -> [XPubBal]
forall a. (a -> Bool) -> [a] -> [a]
filter XPubBal -> Bool
f ([XPubBal] -> [XPubBal]) -> WebT m [XPubBal] -> WebT m [XPubBal]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReaderT WebConfig m [XPubBal] -> WebT m [XPubBal]
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (Bool
-> ReaderT WebConfig m [XPubBal] -> ReaderT WebConfig m [XPubBal]
forall (m :: * -> *) a.
MonadIO m =>
Bool -> ReaderT WebConfig m a -> ReaderT WebConfig m a
runNoCache Bool
noCache (XPubSpec -> ReaderT WebConfig m [XPubBal]
forall (m :: * -> *). StoreReadExtra m => XPubSpec -> m [XPubBal]
xPubBals XPubSpec
spec))
  where
    spec :: XPubSpec
spec = XPubKey -> DeriveType -> XPubSpec
XPubSpec XPubKey
xpub DeriveType
deriv
    f :: XPubBal -> Bool
f = Bool -> Bool
not (Bool -> Bool) -> (XPubBal -> Bool) -> XPubBal -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Balance -> Bool
nullBalance (Balance -> Bool) -> (XPubBal -> Balance) -> XPubBal -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPubBal -> Balance
xPubBal

scottyXPubUnspent ::
       (MonadUnliftIO m, MonadLoggerIO m)
    => GetXPubUnspent
    -> WebT m [XPubUnspent]
scottyXPubUnspent :: GetXPubUnspent -> WebT m [XPubUnspent]
scottyXPubUnspent (GetXPubUnspent xpub :: XPubKey
xpub deriv :: DeriveType
deriv pLimits :: LimitsParam
pLimits (NoCache noCache :: Bool
noCache)) = do
    Limits
limits <- Bool -> LimitsParam -> WebT m Limits
forall (m :: * -> *).
(MonadUnliftIO m, MonadLoggerIO m) =>
Bool -> LimitsParam -> WebT m Limits
paramToLimits Bool
False LimitsParam
pLimits
    ReaderT WebConfig m [XPubUnspent] -> WebT m [XPubUnspent]
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (ReaderT WebConfig m [XPubUnspent] -> WebT m [XPubUnspent])
-> (ReaderT WebConfig m [XPubUnspent]
    -> ReaderT WebConfig m [XPubUnspent])
-> ReaderT WebConfig m [XPubUnspent]
-> WebT m [XPubUnspent]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool
-> ReaderT WebConfig m [XPubUnspent]
-> ReaderT WebConfig m [XPubUnspent]
forall (m :: * -> *) a.
MonadIO m =>
Bool -> ReaderT WebConfig m a -> ReaderT WebConfig m a
runNoCache Bool
noCache (ReaderT WebConfig m [XPubUnspent] -> WebT m [XPubUnspent])
-> ReaderT WebConfig m [XPubUnspent] -> WebT m [XPubUnspent]
forall a b. (a -> b) -> a -> b
$ XPubSpec -> Limits -> ReaderT WebConfig m [XPubUnspent]
forall (m :: * -> *).
StoreReadExtra m =>
XPubSpec -> Limits -> m [XPubUnspent]
xPubUnspents (XPubKey -> DeriveType -> XPubSpec
XPubSpec XPubKey
xpub DeriveType
deriv) Limits
limits

scottyXPubEvict ::
       (MonadUnliftIO m, MonadLoggerIO m)
    => GetXPubEvict
    -> WebT m (GenericResult Bool)
scottyXPubEvict :: GetXPubEvict -> WebT m (GenericResult Bool)
scottyXPubEvict (GetXPubEvict xpub :: XPubKey
xpub deriv :: DeriveType
deriv) = do
    Maybe CacheConfig
cache <- ReaderT WebConfig m (Maybe CacheConfig)
-> ActionT Except (ReaderT WebConfig m) (Maybe CacheConfig)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (ReaderT WebConfig m (Maybe CacheConfig)
 -> ActionT Except (ReaderT WebConfig m) (Maybe CacheConfig))
-> ReaderT WebConfig m (Maybe CacheConfig)
-> ActionT Except (ReaderT WebConfig m) (Maybe CacheConfig)
forall a b. (a -> b) -> a -> b
$ (WebConfig -> Maybe CacheConfig)
-> ReaderT WebConfig m (Maybe CacheConfig)
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks (Store -> Maybe CacheConfig
storeCache (Store -> Maybe CacheConfig)
-> (WebConfig -> Store) -> WebConfig -> Maybe CacheConfig
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebConfig -> Store
webStore)
    ReaderT WebConfig m () -> ActionT Except (ReaderT WebConfig m) ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (ReaderT WebConfig m () -> ActionT Except (ReaderT WebConfig m) ())
-> (CacheT (ReaderT WebConfig m) () -> ReaderT WebConfig m ())
-> CacheT (ReaderT WebConfig m) ()
-> ActionT Except (ReaderT WebConfig m) ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe CacheConfig
-> CacheT (ReaderT WebConfig m) () -> ReaderT WebConfig m ()
forall (m :: * -> *) a.
StoreReadBase m =>
Maybe CacheConfig -> CacheT m a -> m a
withCache Maybe CacheConfig
cache (CacheT (ReaderT WebConfig m) ()
 -> ActionT Except (ReaderT WebConfig m) ())
-> CacheT (ReaderT WebConfig m) ()
-> ActionT Except (ReaderT WebConfig m) ()
forall a b. (a -> b) -> a -> b
$ [XPubSpec] -> CacheT (ReaderT WebConfig m) ()
forall (m :: * -> *).
(MonadUnliftIO m, MonadLoggerIO m, StoreReadBase m) =>
[XPubSpec] -> CacheT m ()
evictFromCache [XPubKey -> DeriveType -> XPubSpec
XPubSpec XPubKey
xpub DeriveType
deriv]
    GenericResult Bool -> WebT m (GenericResult Bool)
forall (m :: * -> *) a. Monad m => a -> m a
return (GenericResult Bool -> WebT m (GenericResult Bool))
-> GenericResult Bool -> WebT m (GenericResult Bool)
forall a b. (a -> b) -> a -> b
$ Bool -> GenericResult Bool
forall a. a -> GenericResult a
GenericResult Bool
True

---------------------------------------
-- Blockchain.info API Compatibility --
---------------------------------------

netBinfoSymbol :: Network -> BinfoSymbol
netBinfoSymbol :: Network -> BinfoSymbol
netBinfoSymbol net :: Network
net
  | Network
net Network -> Network -> Bool
forall a. Eq a => a -> a -> Bool
== Network
btc =
        $WBinfoSymbol :: Text -> Text -> Text -> Double -> Bool -> Bool -> BinfoSymbol
BinfoSymbol{ getBinfoSymbolCode :: Text
getBinfoSymbolCode = "BTC"
                   , getBinfoSymbolString :: Text
getBinfoSymbolString = "BTC"
                   , getBinfoSymbolName :: Text
getBinfoSymbolName = "Bitcoin"
                   , getBinfoSymbolConversion :: Double
getBinfoSymbolConversion = 100 Double -> Double -> Double
forall a. Num a => a -> a -> a
* 1000 Double -> Double -> Double
forall a. Num a => a -> a -> a
* 1000
                   , getBinfoSymbolAfter :: Bool
getBinfoSymbolAfter = Bool
True
                   , getBinfoSymbolLocal :: Bool
getBinfoSymbolLocal = Bool
False
                   }
  | Network
net Network -> Network -> Bool
forall a. Eq a => a -> a -> Bool
== Network
bch =
        $WBinfoSymbol :: Text -> Text -> Text -> Double -> Bool -> Bool -> BinfoSymbol
BinfoSymbol{ getBinfoSymbolCode :: Text
getBinfoSymbolCode = "BCH"
                   , getBinfoSymbolString :: Text
getBinfoSymbolString = "BCH"
                   , getBinfoSymbolName :: Text
getBinfoSymbolName = "Bitcoin Cash"
                   , getBinfoSymbolConversion :: Double
getBinfoSymbolConversion = 100 Double -> Double -> Double
forall a. Num a => a -> a -> a
* 1000 Double -> Double -> Double
forall a. Num a => a -> a -> a
* 1000
                   , getBinfoSymbolAfter :: Bool
getBinfoSymbolAfter = Bool
True
                   , getBinfoSymbolLocal :: Bool
getBinfoSymbolLocal = Bool
False
                   }
  | Bool
otherwise =
        $WBinfoSymbol :: Text -> Text -> Text -> Double -> Bool -> Bool -> BinfoSymbol
BinfoSymbol{ getBinfoSymbolCode :: Text
getBinfoSymbolCode = "XTS"
                   , getBinfoSymbolString :: Text
getBinfoSymbolString = "¤"
                   , getBinfoSymbolName :: Text
getBinfoSymbolName = "Test"
                   , getBinfoSymbolConversion :: Double
getBinfoSymbolConversion = 100 Double -> Double -> Double
forall a. Num a => a -> a -> a
* 1000 Double -> Double -> Double
forall a. Num a => a -> a -> a
* 1000
                   , getBinfoSymbolAfter :: Bool
getBinfoSymbolAfter = Bool
False
                   , getBinfoSymbolLocal :: Bool
getBinfoSymbolLocal = Bool
False
                   }

binfoTickerToSymbol :: Text -> BinfoTicker -> BinfoSymbol
binfoTickerToSymbol :: Text -> BinfoTicker -> BinfoSymbol
binfoTickerToSymbol code :: Text
code BinfoTicker{..} =
    $WBinfoSymbol :: Text -> Text -> Text -> Double -> Bool -> Bool -> BinfoSymbol
BinfoSymbol{ getBinfoSymbolCode :: Text
getBinfoSymbolCode = Text
code
               , getBinfoSymbolString :: Text
getBinfoSymbolString = Text
binfoTickerSymbol
               , getBinfoSymbolName :: Text
getBinfoSymbolName = Text
name
               , getBinfoSymbolConversion :: Double
getBinfoSymbolConversion =
                       100 Double -> Double -> Double
forall a. Num a => a -> a -> a
* 1000 Double -> Double -> Double
forall a. Num a => a -> a -> a
* 1000 Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
binfoTicker15m -- sat/usd
               , getBinfoSymbolAfter :: Bool
getBinfoSymbolAfter = Bool
False
               , getBinfoSymbolLocal :: Bool
getBinfoSymbolLocal = Bool
True
               }
  where
    name :: Text
name = case Text
code of
        "EUR" -> "Euro"
        "USD" -> "U.S. dollar"
        "GBP" -> "British pound"
        x :: Text
x     -> Text
x

scottyMultiAddr :: (MonadUnliftIO m, MonadLoggerIO m)
                => TVar (HashMap Text BinfoTicker)
                -> WebT m ()
scottyMultiAddr :: TVar (HashMap Text BinfoTicker) -> WebT m ()
scottyMultiAddr ticker :: TVar (HashMap Text BinfoTicker)
ticker = do
    Bool
prune <- ActionT Except (ReaderT WebConfig m) Bool
get_prune
    Int
n <- ActionT Except (ReaderT WebConfig m) Int
get_count
    Int
offset <- ActionT Except (ReaderT WebConfig m) Int
get_offset
    Bool
cashaddr <- ActionT Except (ReaderT WebConfig m) Bool
get_cashaddr
    Bool
numtxid <- ReaderT WebConfig m Bool
-> ActionT Except (ReaderT WebConfig m) Bool
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (ReaderT WebConfig m Bool
 -> ActionT Except (ReaderT WebConfig m) Bool)
-> ReaderT WebConfig m Bool
-> ActionT Except (ReaderT WebConfig m) Bool
forall a b. (a -> b) -> a -> b
$ (WebConfig -> Bool) -> ReaderT WebConfig m Bool
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WebConfig -> Bool
webNumTxId
    (addrs :: HashSet Address
addrs, xpubs :: HashSet XPubKey
xpubs, saddrs :: HashSet Address
saddrs, sxpubs :: HashSet XPubKey
sxpubs, xspecs :: HashMap XPubKey XPubSpec
xspecs) <- ActionT
  Except
  (ReaderT WebConfig m)
  (HashSet Address, HashSet XPubKey, HashSet Address,
   HashSet XPubKey, HashMap XPubKey XPubSpec)
get_addrs
    HashMap XPubKey [XPubBal]
xbals <- HashMap XPubKey XPubSpec
-> ActionT Except (ReaderT WebConfig m) (HashMap XPubKey [XPubBal])
get_xbals HashMap XPubKey XPubSpec
xspecs
    let sxbals :: HashMap XPubKey [XPubBal]
sxbals = HashSet XPubKey
-> HashMap XPubKey [XPubBal] -> HashMap XPubKey [XPubBal]
forall a p.
(Eq a, Hashable a) =>
HashSet a -> HashMap a p -> HashMap a p
compute_sxbals HashSet XPubKey
sxpubs HashMap XPubKey [XPubBal]
xbals
    HashMap XPubKey [TxRef]
sxtrs <- HashSet XPubKey
-> HashMap XPubKey XPubSpec
-> ActionT Except (ReaderT WebConfig m) (HashMap XPubKey [TxRef])
forall (f :: * -> *) k.
(StoreReadExtra f, Eq k, Hashable k) =>
HashSet k -> HashMap k XPubSpec -> f (HashMap k [TxRef])
get_sxtrs HashSet XPubKey
sxpubs HashMap XPubKey XPubSpec
xspecs
    HashMap Address Balance
sabals <- HashSet Address
-> ActionT Except (ReaderT WebConfig m) (HashMap Address Balance)
get_abals HashSet Address
saddrs
    Set TxRef
satrs <- Int
-> Int
-> HashSet Address
-> ActionT Except (ReaderT WebConfig m) (Set TxRef)
forall (f :: * -> *) a.
(StoreReadExtra f, Integral a) =>
a -> a -> HashSet Address -> f (Set TxRef)
get_atrs Int
n Int
offset HashSet Address
saddrs
    BinfoSymbol
local <- TVar (HashMap Text BinfoTicker)
-> ActionT Except (ReaderT WebConfig m) BinfoSymbol
forall (m :: * -> *) b.
(ScottyError b, MonadIO m) =>
TVar (HashMap Text BinfoTicker) -> ActionT b m BinfoSymbol
get_price TVar (HashMap Text BinfoTicker)
ticker
    let sxtns :: HashMap XPubKey Int
sxtns = ([TxRef] -> Int) -> HashMap XPubKey [TxRef] -> HashMap XPubKey Int
forall v1 v2 k. (v1 -> v2) -> HashMap k v1 -> HashMap k v2
HashMap.map [TxRef] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length HashMap XPubKey [TxRef]
sxtrs
        sxtrset :: Set TxRef
sxtrset = [TxRef] -> Set TxRef
forall a. Ord a => [a] -> Set a
Set.fromList ([TxRef] -> Set TxRef)
-> ([[TxRef]] -> [TxRef]) -> [[TxRef]] -> Set TxRef
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[TxRef]] -> [TxRef]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[TxRef]] -> Set TxRef) -> [[TxRef]] -> Set TxRef
forall a b. (a -> b) -> a -> b
$ HashMap XPubKey [TxRef] -> [[TxRef]]
forall k v. HashMap k v -> [v]
HashMap.elems HashMap XPubKey [TxRef]
sxtrs
        sxabals :: HashMap Address Balance
sxabals = HashMap XPubKey [XPubBal] -> HashMap Address Balance
forall k. HashMap k [XPubBal] -> HashMap Address Balance
compute_xabals HashMap XPubKey [XPubBal]
sxbals
        sallbals :: HashMap Address Balance
sallbals = HashMap Address Balance
sabals HashMap Address Balance
-> HashMap Address Balance -> HashMap Address Balance
forall a. Semigroup a => a -> a -> a
<> HashMap Address Balance
sxabals
        abook :: HashMap Address (Maybe BinfoXPubPath)
abook = HashSet Address
-> HashMap XPubKey [XPubBal]
-> HashMap Address (Maybe BinfoXPubPath)
compute_abook HashSet Address
addrs HashMap XPubKey [XPubBal]
xbals
        sxaddrs :: HashSet Address
sxaddrs = HashMap XPubKey [XPubBal] -> HashSet Address
forall k. HashMap k [XPubBal] -> HashSet Address
compute_xaddrs HashMap XPubKey [XPubBal]
sxbals
        salladdrs :: HashSet Address
salladdrs = HashSet Address
sxaddrs HashSet Address -> HashSet Address -> HashSet Address
forall a. Semigroup a => a -> a -> a
<> HashSet Address
saddrs
        bal :: Word64
bal = HashMap Address Balance -> Word64
forall k. HashMap k Balance -> Word64
compute_bal HashMap Address Balance
sallbals
        salltrs :: Set TxRef
salltrs = Set TxRef
sxtrset Set TxRef -> Set TxRef -> Set TxRef
forall a. Semigroup a => a -> a -> a
<> Set TxRef
satrs
        stxids :: [TxHash]
stxids = Int -> Int -> Set TxRef -> [TxHash]
compute_txids Int
n Int
offset Set TxRef
salltrs
    [Transaction]
stxs <- [TxHash] -> ActionT Except (ReaderT WebConfig m) [Transaction]
get_txs [TxHash]
stxids
    let etxids :: [TxHash]
etxids = if Bool
numtxid
                 then Bool
-> HashMap Address (Maybe BinfoXPubPath)
-> [Transaction]
-> [TxHash]
forall a. Bool -> HashMap Address a -> [Transaction] -> [TxHash]
compute_etxids Bool
prune HashMap Address (Maybe BinfoXPubPath)
abook [Transaction]
stxs
                 else []
    Maybe (HashMap TxHash Transaction)
etxs <- if Bool
numtxid
            then HashMap TxHash Transaction -> Maybe (HashMap TxHash Transaction)
forall a. a -> Maybe a
Just (HashMap TxHash Transaction -> Maybe (HashMap TxHash Transaction))
-> ActionT
     Except (ReaderT WebConfig m) (HashMap TxHash Transaction)
-> ActionT
     Except (ReaderT WebConfig m) (Maybe (HashMap TxHash Transaction))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [TxHash]
-> ActionT
     Except (ReaderT WebConfig m) (HashMap TxHash Transaction)
get_etxs [TxHash]
etxids
            else Maybe (HashMap TxHash Transaction)
-> ActionT
     Except (ReaderT WebConfig m) (Maybe (HashMap TxHash Transaction))
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe (HashMap TxHash Transaction)
forall a. Maybe a
Nothing
    BlockData
best <- GetBlockBest -> WebT m BlockData
forall (m :: * -> *).
(MonadUnliftIO m, MonadLoggerIO m) =>
GetBlockBest -> WebT m BlockData
scottyBlockBest (NoTx -> GetBlockBest
GetBlockBest (Bool -> NoTx
NoTx Bool
True))
    Word32
peers <- ActionT Except (ReaderT WebConfig m) Word32
get_peers
    Network
net <- ReaderT WebConfig m Network
-> ActionT Except (ReaderT WebConfig m) Network
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (ReaderT WebConfig m Network
 -> ActionT Except (ReaderT WebConfig m) Network)
-> ReaderT WebConfig m Network
-> ActionT Except (ReaderT WebConfig m) Network
forall a b. (a -> b) -> a -> b
$ (WebConfig -> Network) -> ReaderT WebConfig m Network
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks (Store -> Network
storeNetwork (Store -> Network) -> (WebConfig -> Store) -> WebConfig -> Network
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebConfig -> Store
webStore)
    let ibal :: Int64
ibal = Word64 -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word64
bal
        btxs :: [BinfoTx]
btxs = Maybe (HashMap TxHash Transaction)
-> HashMap Address (Maybe BinfoXPubPath)
-> HashSet Address
-> Bool
-> Int64
-> [Transaction]
-> [BinfoTx]
binfo_txs Maybe (HashMap TxHash Transaction)
etxs HashMap Address (Maybe BinfoXPubPath)
abook HashSet Address
salladdrs Bool
prune Int64
ibal [Transaction]
stxs
        ftxs :: [BinfoTx]
ftxs = Int -> [BinfoTx] -> [BinfoTx]
forall a. Int -> [a] -> [a]
take Int
n ([BinfoTx] -> [BinfoTx]) -> [BinfoTx] -> [BinfoTx]
forall a b. (a -> b) -> a -> b
$ Int -> [BinfoTx] -> [BinfoTx]
forall a. Int -> [a] -> [a]
drop Int
offset [BinfoTx]
btxs
        addrs :: [BinfoAddress]
addrs = HashMap Address Balance
-> HashMap XPubKey [XPubBal]
-> HashMap XPubKey Int
-> [BinfoAddress]
toBinfoAddrs HashMap Address Balance
sabals HashMap XPubKey [XPubBal]
sxbals HashMap XPubKey Int
sxtns
        recv :: Word64
recv = [Word64] -> Word64
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum ([Word64] -> Word64) -> [Word64] -> Word64
forall a b. (a -> b) -> a -> b
$ (BinfoAddress -> Word64) -> [BinfoAddress] -> [Word64]
forall a b. (a -> b) -> [a] -> [b]
map BinfoAddress -> Word64
getBinfoAddrReceived [BinfoAddress]
addrs
        sent :: Word64
sent = [Word64] -> Word64
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum ([Word64] -> Word64) -> [Word64] -> Word64
forall a b. (a -> b) -> a -> b
$ (BinfoAddress -> Word64) -> [BinfoAddress] -> [Word64]
forall a b. (a -> b) -> [a] -> [b]
map BinfoAddress -> Word64
getBinfoAddrSent [BinfoAddress]
addrs
        txn :: Word64
txn = [Word64] -> Word64
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum ([Word64] -> Word64) -> [Word64] -> Word64
forall a b. (a -> b) -> a -> b
$ (BinfoAddress -> Word64) -> [BinfoAddress] -> [Word64]
forall a b. (a -> b) -> [a] -> [b]
map BinfoAddress -> Word64
getBinfoAddrTxCount [BinfoAddress]
addrs
        wallet :: BinfoWallet
wallet =
            $WBinfoWallet :: Word64 -> Word64 -> Word64 -> Word64 -> Word64 -> BinfoWallet
BinfoWallet
            { getBinfoWalletBalance :: Word64
getBinfoWalletBalance = Word64
bal
            , getBinfoWalletTxCount :: Word64
getBinfoWalletTxCount = Word64
txn
            , getBinfoWalletFilteredCount :: Word64
getBinfoWalletFilteredCount = Int -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral ([BinfoTx] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [BinfoTx]
ftxs)
            , getBinfoWalletTotalReceived :: Word64
getBinfoWalletTotalReceived = Word64
recv
            , getBinfoWalletTotalSent :: Word64
getBinfoWalletTotalSent = Word64
sent
            }
        coin :: BinfoSymbol
coin = Network -> BinfoSymbol
netBinfoSymbol Network
net
        block :: BinfoBlockInfo
block =
            $WBinfoBlockInfo :: BlockHash -> Word32 -> Word32 -> Word32 -> BinfoBlockInfo
BinfoBlockInfo
            { getBinfoBlockInfoHash :: BlockHash
getBinfoBlockInfoHash = BlockHeader -> BlockHash
H.headerHash (BlockData -> BlockHeader
blockDataHeader BlockData
best)
            , getBinfoBlockInfoHeight :: Word32
getBinfoBlockInfoHeight = BlockData -> Word32
blockDataHeight BlockData
best
            , getBinfoBlockInfoTime :: Word32
getBinfoBlockInfoTime = BlockHeader -> Word32
H.blockTimestamp (BlockData -> BlockHeader
blockDataHeader BlockData
best)
            , getBinfoBlockInfoIndex :: Word32
getBinfoBlockInfoIndex = BlockData -> Word32
blockDataHeight BlockData
best
            }
        info :: BinfoInfo
info =
            $WBinfoInfo :: Word32
-> Double
-> BinfoSymbol
-> BinfoSymbol
-> BinfoBlockInfo
-> BinfoInfo
BinfoInfo
            { getBinfoConnected :: Word32
getBinfoConnected = Word32
peers
            , getBinfoConversion :: Double
getBinfoConversion = 100 Double -> Double -> Double
forall a. Num a => a -> a -> a
* 1000 Double -> Double -> Double
forall a. Num a => a -> a -> a
* 1000
            , getBinfoLocal :: BinfoSymbol
getBinfoLocal = BinfoSymbol
local
            , getBinfoBTC :: BinfoSymbol
getBinfoBTC = BinfoSymbol
coin
            , getBinfoLatestBlock :: BinfoBlockInfo
getBinfoLatestBlock = BinfoBlockInfo
block
            }
    WebT m ()
forall (m :: * -> *) e. (Monad m, ScottyError e) => ActionT e m ()
setHeaders
    Value -> WebT m ()
forall a e (m :: * -> *).
(ToJSON a, ScottyError e, Monad m) =>
a -> ActionT e m ()
S.json (Value -> WebT m ()) -> Value -> WebT m ()
forall a b. (a -> b) -> a -> b
$ Network -> BinfoMultiAddr -> Value
binfoMultiAddrToJSON Network
net
        $WBinfoMultiAddr :: [BinfoAddress]
-> BinfoWallet
-> [BinfoTx]
-> BinfoInfo
-> Bool
-> Bool
-> BinfoMultiAddr
BinfoMultiAddr
        { getBinfoMultiAddrAddresses :: [BinfoAddress]
getBinfoMultiAddrAddresses = [BinfoAddress]
addrs
        , getBinfoMultiAddrWallet :: BinfoWallet
getBinfoMultiAddrWallet = BinfoWallet
wallet
        , getBinfoMultiAddrTxs :: [BinfoTx]
getBinfoMultiAddrTxs = [BinfoTx]
ftxs
        , getBinfoMultiAddrInfo :: BinfoInfo
getBinfoMultiAddrInfo = BinfoInfo
info
        , getBinfoMultiAddrRecommendFee :: Bool
getBinfoMultiAddrRecommendFee = Bool
True
        , getBinfoMultiAddrCashAddr :: Bool
getBinfoMultiAddrCashAddr = Bool
cashaddr
        }
  where
    get_price :: TVar (HashMap Text BinfoTicker) -> ActionT b m BinfoSymbol
get_price ticker :: TVar (HashMap Text BinfoTicker)
ticker = do
        Text
code <- Text -> Text
T.toUpper (Text -> Text) -> ActionT b m Text -> ActionT b m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ActionT b m Text
forall a e (m :: * -> *).
(Parsable a, ScottyError e, Monad m) =>
Text -> ActionT e m a
S.param "local" ActionT b m Text -> (b -> ActionT b m Text) -> ActionT b m Text
forall e (m :: * -> *) a.
(ScottyError e, Monad m) =>
ActionT e m a -> (e -> ActionT e m a) -> ActionT e m a
`S.rescue` ActionT b m Text -> b -> ActionT b m Text
forall a b. a -> b -> a
const (Text -> ActionT b m Text
forall (m :: * -> *) a. Monad m => a -> m a
return "USD")
        HashMap Text BinfoTicker
prices <- TVar (HashMap Text BinfoTicker)
-> ActionT b m (HashMap Text BinfoTicker)
forall (m :: * -> *) a. MonadIO m => TVar a -> m a
readTVarIO TVar (HashMap Text BinfoTicker)
ticker
        case Text -> HashMap Text BinfoTicker -> Maybe BinfoTicker
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
HashMap.lookup Text
code HashMap Text BinfoTicker
prices of
            Nothing -> BinfoSymbol -> ActionT b m BinfoSymbol
forall (m :: * -> *) a. Monad m => a -> m a
return BinfoSymbol
forall a. Default a => a
def
            Just p :: BinfoTicker
p  -> BinfoSymbol -> ActionT b m BinfoSymbol
forall (m :: * -> *) a. Monad m => a -> m a
return (BinfoSymbol -> ActionT b m BinfoSymbol)
-> BinfoSymbol -> ActionT b m BinfoSymbol
forall a b. (a -> b) -> a -> b
$ Text -> BinfoTicker -> BinfoSymbol
binfoTickerToSymbol Text
code BinfoTicker
p
    get_prune :: ActionT Except (ReaderT WebConfig m) Bool
get_prune = (Bool -> Bool)
-> ActionT Except (ReaderT WebConfig m) Bool
-> ActionT Except (ReaderT WebConfig m) Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Bool -> Bool
not (ActionT Except (ReaderT WebConfig m) Bool
 -> ActionT Except (ReaderT WebConfig m) Bool)
-> ActionT Except (ReaderT WebConfig m) Bool
-> ActionT Except (ReaderT WebConfig m) Bool
forall a b. (a -> b) -> a -> b
$ Text -> ActionT Except (ReaderT WebConfig m) Bool
forall a e (m :: * -> *).
(Parsable a, ScottyError e, Monad m) =>
Text -> ActionT e m a
S.param "no_compact"
        ActionT Except (ReaderT WebConfig m) Bool
-> (Except -> ActionT Except (ReaderT WebConfig m) Bool)
-> ActionT Except (ReaderT WebConfig m) Bool
forall e (m :: * -> *) a.
(ScottyError e, Monad m) =>
ActionT e m a -> (e -> ActionT e m a) -> ActionT e m a
`S.rescue` ActionT Except (ReaderT WebConfig m) Bool
-> Except -> ActionT Except (ReaderT WebConfig m) Bool
forall a b. a -> b -> a
const (Bool -> ActionT Except (ReaderT WebConfig m) Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False)
    get_cashaddr :: ActionT Except (ReaderT WebConfig m) Bool
get_cashaddr = Text -> ActionT Except (ReaderT WebConfig m) Bool
forall a e (m :: * -> *).
(Parsable a, ScottyError e, Monad m) =>
Text -> ActionT e m a
S.param "cashaddr"
        ActionT Except (ReaderT WebConfig m) Bool
-> (Except -> ActionT Except (ReaderT WebConfig m) Bool)
-> ActionT Except (ReaderT WebConfig m) Bool
forall e (m :: * -> *) a.
(ScottyError e, Monad m) =>
ActionT e m a -> (e -> ActionT e m a) -> ActionT e m a
`S.rescue` ActionT Except (ReaderT WebConfig m) Bool
-> Except -> ActionT Except (ReaderT WebConfig m) Bool
forall a b. a -> b -> a
const (Bool -> ActionT Except (ReaderT WebConfig m) Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False)
    get_count :: ActionT Except (ReaderT WebConfig m) Int
get_count = do
        Word32
d <- ReaderT WebConfig m Word32
-> ActionT Except (ReaderT WebConfig m) Word32
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ((WebConfig -> Word32) -> ReaderT WebConfig m Word32
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks (WebLimits -> Word32
maxLimitDefault (WebLimits -> Word32)
-> (WebConfig -> WebLimits) -> WebConfig -> Word32
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebConfig -> WebLimits
webMaxLimits))
        Word32
x <- ReaderT WebConfig m Word32
-> ActionT Except (ReaderT WebConfig m) Word32
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ((WebConfig -> Word32) -> ReaderT WebConfig m Word32
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks (WebLimits -> Word32
maxLimitFull (WebLimits -> Word32)
-> (WebConfig -> WebLimits) -> WebConfig -> Word32
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebConfig -> WebLimits
webMaxLimits))
        Word32
i <- Word32 -> Word32 -> Word32
forall a. Ord a => a -> a -> a
min Word32
x (Word32 -> Word32)
-> ActionT Except (ReaderT WebConfig m) Word32
-> ActionT Except (ReaderT WebConfig m) Word32
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Text -> ActionT Except (ReaderT WebConfig m) Word32
forall a e (m :: * -> *).
(Parsable a, ScottyError e, Monad m) =>
Text -> ActionT e m a
S.param "n" ActionT Except (ReaderT WebConfig m) Word32
-> (Except -> ActionT Except (ReaderT WebConfig m) Word32)
-> ActionT Except (ReaderT WebConfig m) Word32
forall e (m :: * -> *) a.
(ScottyError e, Monad m) =>
ActionT e m a -> (e -> ActionT e m a) -> ActionT e m a
`S.rescue` ActionT Except (ReaderT WebConfig m) Word32
-> Except -> ActionT Except (ReaderT WebConfig m) Word32
forall a b. a -> b -> a
const (Word32 -> ActionT Except (ReaderT WebConfig m) Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
d))
        Int -> ActionT Except (ReaderT WebConfig m) Int
forall (m :: * -> *) a. Monad m => a -> m a
return (Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
i :: Int)
    get_offset :: ActionT Except (ReaderT WebConfig m) Int
get_offset = do
        Word32
x <- ReaderT WebConfig m Word32
-> ActionT Except (ReaderT WebConfig m) Word32
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ((WebConfig -> Word32) -> ReaderT WebConfig m Word32
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks (WebLimits -> Word32
maxLimitOffset (WebLimits -> Word32)
-> (WebConfig -> WebLimits) -> WebConfig -> Word32
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebConfig -> WebLimits
webMaxLimits))
        Word32
o <- Word32 -> Word32 -> Word32
forall a. Ord a => a -> a -> a
min Word32
x (Word32 -> Word32)
-> ActionT Except (ReaderT WebConfig m) Word32
-> ActionT Except (ReaderT WebConfig m) Word32
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Text -> ActionT Except (ReaderT WebConfig m) Word32
forall a e (m :: * -> *).
(Parsable a, ScottyError e, Monad m) =>
Text -> ActionT e m a
S.param "offset" ActionT Except (ReaderT WebConfig m) Word32
-> (Except -> ActionT Except (ReaderT WebConfig m) Word32)
-> ActionT Except (ReaderT WebConfig m) Word32
forall e (m :: * -> *) a.
(ScottyError e, Monad m) =>
ActionT e m a -> (e -> ActionT e m a) -> ActionT e m a
`S.rescue` ActionT Except (ReaderT WebConfig m) Word32
-> Except -> ActionT Except (ReaderT WebConfig m) Word32
forall a b. a -> b -> a
const (Word32 -> ActionT Except (ReaderT WebConfig m) Word32
forall (m :: * -> *) a. Monad m => a -> m a
return 0))
        Int -> ActionT Except (ReaderT WebConfig m) Int
forall (m :: * -> *) a. Monad m => a -> m a
return (Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
o :: Int)
    get_addrs_param :: Text -> ActionT Except m (HashSet BinfoAddr)
get_addrs_param name :: Text
name = do
        Network
net <- m Network -> ActionT Except m Network
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ((WebConfig -> Network) -> m Network
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks (Store -> Network
storeNetwork (Store -> Network) -> (WebConfig -> Store) -> WebConfig -> Network
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebConfig -> Store
webStore))
        Text
p <- Text -> ActionT Except m Text
forall a e (m :: * -> *).
(Parsable a, ScottyError e, Monad m) =>
Text -> ActionT e m a
S.param Text
name ActionT Except m Text
-> (Except -> ActionT Except m Text) -> ActionT Except m Text
forall e (m :: * -> *) a.
(ScottyError e, Monad m) =>
ActionT e m a -> (e -> ActionT e m a) -> ActionT e m a
`S.rescue` ActionT Except m Text -> Except -> ActionT Except m Text
forall a b. a -> b -> a
const (Text -> ActionT Except m Text
forall (m :: * -> *) a. Monad m => a -> m a
return "")
        case Network -> Text -> Maybe [BinfoAddr]
parseBinfoAddr Network
net Text
p of
            Nothing -> Except -> ActionT Except m (HashSet BinfoAddr)
forall e (m :: * -> *) a.
(ScottyError e, Monad m) =>
e -> ActionT e m a
S.raise (String -> Except
UserError "invalid active address")
            Just xs :: [BinfoAddr]
xs -> HashSet BinfoAddr -> ActionT Except m (HashSet BinfoAddr)
forall (m :: * -> *) a. Monad m => a -> m a
return (HashSet BinfoAddr -> ActionT Except m (HashSet BinfoAddr))
-> HashSet BinfoAddr -> ActionT Except m (HashSet BinfoAddr)
forall a b. (a -> b) -> a -> b
$ [BinfoAddr] -> HashSet BinfoAddr
forall a. (Eq a, Hashable a) => [a] -> HashSet a
HashSet.fromList [BinfoAddr]
xs
    addr :: BinfoAddr -> Maybe Address
addr (BinfoAddr a :: Address
a) = Address -> Maybe Address
forall a. a -> Maybe a
Just Address
a
    addr (BinfoXpub x :: XPubKey
x) = Maybe Address
forall a. Maybe a
Nothing
    xpub :: BinfoAddr -> Maybe XPubKey
xpub (BinfoXpub x :: XPubKey
x) = XPubKey -> Maybe XPubKey
forall a. a -> Maybe a
Just XPubKey
x
    xpub (BinfoAddr _) = Maybe XPubKey
forall a. Maybe a
Nothing
    binfo_txs :: Maybe (HashMap TxHash Transaction)
-> HashMap Address (Maybe BinfoXPubPath)
-> HashSet Address
-> Bool
-> Int64
-> [Transaction]
-> [BinfoTx]
binfo_txs _ _ _ _ _ [] = []
    binfo_txs etxs :: Maybe (HashMap TxHash Transaction)
etxs abook :: HashMap Address (Maybe BinfoXPubPath)
abook salladdrs :: HashSet Address
salladdrs prune :: Bool
prune ibal :: Int64
ibal (t :: Transaction
t:ts :: [Transaction]
ts) =
        let b :: BinfoTx
b = Maybe (HashMap TxHash Transaction)
-> HashMap Address (Maybe BinfoXPubPath)
-> HashSet Address
-> Bool
-> Int64
-> Transaction
-> BinfoTx
toBinfoTx Maybe (HashMap TxHash Transaction)
etxs HashMap Address (Maybe BinfoXPubPath)
abook HashSet Address
salladdrs Bool
prune Int64
ibal Transaction
t
            nbal :: Int64
nbal = case BinfoTx -> Maybe (Int64, Int64)
getBinfoTxResultBal BinfoTx
b of
                Nothing     -> Int64
ibal
                Just (_, x :: Int64
x) -> Int64
ibal Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
- Int64
x
         in BinfoTx
b BinfoTx -> [BinfoTx] -> [BinfoTx]
forall a. a -> [a] -> [a]
: Maybe (HashMap TxHash Transaction)
-> HashMap Address (Maybe BinfoXPubPath)
-> HashSet Address
-> Bool
-> Int64
-> [Transaction]
-> [BinfoTx]
binfo_txs Maybe (HashMap TxHash Transaction)
etxs HashMap Address (Maybe BinfoXPubPath)
abook HashSet Address
salladdrs Bool
prune Int64
nbal [Transaction]
ts
    get_addrs :: ActionT
  Except
  (ReaderT WebConfig m)
  (HashSet Address, HashSet XPubKey, HashSet Address,
   HashSet XPubKey, HashMap XPubKey XPubSpec)
get_addrs = do
        HashSet BinfoAddr
active <- Text -> ActionT Except (ReaderT WebConfig m) (HashSet BinfoAddr)
forall (m :: * -> *).
MonadReader WebConfig m =>
Text -> ActionT Except m (HashSet BinfoAddr)
get_addrs_param "active"
        HashSet BinfoAddr
p2sh <- Text -> ActionT Except (ReaderT WebConfig m) (HashSet BinfoAddr)
forall (m :: * -> *).
MonadReader WebConfig m =>
Text -> ActionT Except m (HashSet BinfoAddr)
get_addrs_param "activeP2SH"
        HashSet BinfoAddr
bech32 <- Text -> ActionT Except (ReaderT WebConfig m) (HashSet BinfoAddr)
forall (m :: * -> *).
MonadReader WebConfig m =>
Text -> ActionT Except m (HashSet BinfoAddr)
get_addrs_param "activeBech32"
        HashSet BinfoAddr
sh <- Text -> ActionT Except (ReaderT WebConfig m) (HashSet BinfoAddr)
forall (m :: * -> *).
MonadReader WebConfig m =>
Text -> ActionT Except m (HashSet BinfoAddr)
get_addrs_param "onlyShow"
        let xspec :: DeriveType -> BinfoAddr -> Maybe (XPubKey, XPubSpec)
xspec d :: DeriveType
d b :: BinfoAddr
b = (\x :: XPubKey
x -> (XPubKey
x, XPubKey -> DeriveType -> XPubSpec
XPubSpec XPubKey
x DeriveType
d)) (XPubKey -> (XPubKey, XPubSpec))
-> Maybe XPubKey -> Maybe (XPubKey, XPubSpec)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> BinfoAddr -> Maybe XPubKey
xpub BinfoAddr
b
            xspecs :: HashMap XPubKey XPubSpec
xspecs = [(XPubKey, XPubSpec)] -> HashMap XPubKey XPubSpec
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList ([(XPubKey, XPubSpec)] -> HashMap XPubKey XPubSpec)
-> [(XPubKey, XPubSpec)] -> HashMap XPubKey XPubSpec
forall a b. (a -> b) -> a -> b
$ [[(XPubKey, XPubSpec)]] -> [(XPubKey, XPubSpec)]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
                     [ (BinfoAddr -> Maybe (XPubKey, XPubSpec))
-> [BinfoAddr] -> [(XPubKey, XPubSpec)]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (DeriveType -> BinfoAddr -> Maybe (XPubKey, XPubSpec)
xspec DeriveType
DeriveNormal) (HashSet BinfoAddr -> [BinfoAddr]
forall a. HashSet a -> [a]
HashSet.toList HashSet BinfoAddr
active)
                     , (BinfoAddr -> Maybe (XPubKey, XPubSpec))
-> [BinfoAddr] -> [(XPubKey, XPubSpec)]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (DeriveType -> BinfoAddr -> Maybe (XPubKey, XPubSpec)
xspec DeriveType
DeriveP2SH) (HashSet BinfoAddr -> [BinfoAddr]
forall a. HashSet a -> [a]
HashSet.toList HashSet BinfoAddr
p2sh)
                     , (BinfoAddr -> Maybe (XPubKey, XPubSpec))
-> [BinfoAddr] -> [(XPubKey, XPubSpec)]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (DeriveType -> BinfoAddr -> Maybe (XPubKey, XPubSpec)
xspec DeriveType
DeriveP2WPKH) (HashSet BinfoAddr -> [BinfoAddr]
forall a. HashSet a -> [a]
HashSet.toList HashSet BinfoAddr
bech32)
                     ]
            actives :: HashSet BinfoAddr
actives = HashSet BinfoAddr
active HashSet BinfoAddr -> HashSet BinfoAddr -> HashSet BinfoAddr
forall a. Semigroup a => a -> a -> a
<> HashSet BinfoAddr
p2sh HashSet BinfoAddr -> HashSet BinfoAddr -> HashSet BinfoAddr
forall a. Semigroup a => a -> a -> a
<> HashSet BinfoAddr
bech32
            addrs :: HashSet Address
addrs = [Address] -> HashSet Address
forall a. (Eq a, Hashable a) => [a] -> HashSet a
HashSet.fromList ([Address] -> HashSet Address)
-> ([BinfoAddr] -> [Address]) -> [BinfoAddr] -> HashSet Address
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (BinfoAddr -> Maybe Address) -> [BinfoAddr] -> [Address]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe BinfoAddr -> Maybe Address
addr ([BinfoAddr] -> HashSet Address) -> [BinfoAddr] -> HashSet Address
forall a b. (a -> b) -> a -> b
$ HashSet BinfoAddr -> [BinfoAddr]
forall a. HashSet a -> [a]
HashSet.toList HashSet BinfoAddr
actives
            xpubs :: HashSet XPubKey
xpubs = [XPubKey] -> HashSet XPubKey
forall a. (Eq a, Hashable a) => [a] -> HashSet a
HashSet.fromList ([XPubKey] -> HashSet XPubKey)
-> ([BinfoAddr] -> [XPubKey]) -> [BinfoAddr] -> HashSet XPubKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (BinfoAddr -> Maybe XPubKey) -> [BinfoAddr] -> [XPubKey]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe BinfoAddr -> Maybe XPubKey
xpub ([BinfoAddr] -> HashSet XPubKey) -> [BinfoAddr] -> HashSet XPubKey
forall a b. (a -> b) -> a -> b
$ HashSet BinfoAddr -> [BinfoAddr]
forall a. HashSet a -> [a]
HashSet.toList HashSet BinfoAddr
actives
            sh' :: HashSet BinfoAddr
sh' = if HashSet BinfoAddr -> Bool
forall a. HashSet a -> Bool
HashSet.null HashSet BinfoAddr
sh
                  then HashSet BinfoAddr
actives
                  else HashSet BinfoAddr
sh HashSet BinfoAddr -> HashSet BinfoAddr -> HashSet BinfoAddr
forall a. (Eq a, Hashable a) => HashSet a -> HashSet a -> HashSet a
`HashSet.intersection` HashSet BinfoAddr
actives
            saddrs :: HashSet Address
saddrs = [Address] -> HashSet Address
forall a. (Eq a, Hashable a) => [a] -> HashSet a
HashSet.fromList ([Address] -> HashSet Address)
-> ([BinfoAddr] -> [Address]) -> [BinfoAddr] -> HashSet Address
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (BinfoAddr -> Maybe Address) -> [BinfoAddr] -> [Address]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe BinfoAddr -> Maybe Address
addr ([BinfoAddr] -> HashSet Address) -> [BinfoAddr] -> HashSet Address
forall a b. (a -> b) -> a -> b
$ HashSet BinfoAddr -> [BinfoAddr]
forall a. HashSet a -> [a]
HashSet.toList HashSet BinfoAddr
sh'
            sxpubs :: HashSet XPubKey
sxpubs = [XPubKey] -> HashSet XPubKey
forall a. (Eq a, Hashable a) => [a] -> HashSet a
HashSet.fromList ([XPubKey] -> HashSet XPubKey)
-> ([BinfoAddr] -> [XPubKey]) -> [BinfoAddr] -> HashSet XPubKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (BinfoAddr -> Maybe XPubKey) -> [BinfoAddr] -> [XPubKey]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe BinfoAddr -> Maybe XPubKey
xpub ([BinfoAddr] -> HashSet XPubKey) -> [BinfoAddr] -> HashSet XPubKey
forall a b. (a -> b) -> a -> b
$ HashSet BinfoAddr -> [BinfoAddr]
forall a. HashSet a -> [a]
HashSet.toList HashSet BinfoAddr
sh'
        (HashSet Address, HashSet XPubKey, HashSet Address,
 HashSet XPubKey, HashMap XPubKey XPubSpec)
-> ActionT
     Except
     (ReaderT WebConfig m)
     (HashSet Address, HashSet XPubKey, HashSet Address,
      HashSet XPubKey, HashMap XPubKey XPubSpec)
forall (m :: * -> *) a. Monad m => a -> m a
return (HashSet Address
addrs, HashSet XPubKey
xpubs, HashSet Address
saddrs, HashSet XPubKey
sxpubs, HashMap XPubKey XPubSpec
xspecs)
    get_xbals :: HashMap XPubKey XPubSpec
-> ActionT Except (ReaderT WebConfig m) (HashMap XPubKey [XPubBal])
get_xbals =
        let f :: XPubBal -> Bool
f = Bool -> Bool
not (Bool -> Bool) -> (XPubBal -> Bool) -> XPubBal -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Balance -> Bool
nullBalance (Balance -> Bool) -> (XPubBal -> Balance) -> XPubBal -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPubBal -> Balance
xPubBal
            g :: [(XPubKey, [XPubBal])] -> HashMap XPubKey [XPubBal]
g = [(XPubKey, [XPubBal])] -> HashMap XPubKey [XPubBal]
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList ([(XPubKey, [XPubBal])] -> HashMap XPubKey [XPubBal])
-> ([(XPubKey, [XPubBal])] -> [(XPubKey, [XPubBal])])
-> [(XPubKey, [XPubBal])]
-> HashMap XPubKey [XPubBal]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((XPubKey, [XPubBal]) -> (XPubKey, [XPubBal]))
-> [(XPubKey, [XPubBal])] -> [(XPubKey, [XPubBal])]
forall a b. (a -> b) -> [a] -> [b]
map (([XPubBal] -> [XPubBal])
-> (XPubKey, [XPubBal]) -> (XPubKey, [XPubBal])
forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (d, b) (d, c)
second ((XPubBal -> Bool) -> [XPubBal] -> [XPubBal]
forall a. (a -> Bool) -> [a] -> [a]
filter XPubBal -> Bool
f))
            h :: (a, XPubSpec) -> f (a, [XPubBal])
h (k :: a
k, s :: XPubSpec
s) = (,) a
k ([XPubBal] -> (a, [XPubBal])) -> f [XPubBal] -> f (a, [XPubBal])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> XPubSpec -> f [XPubBal]
forall (m :: * -> *). StoreReadExtra m => XPubSpec -> m [XPubBal]
xPubBals XPubSpec
s
        in ([(XPubKey, [XPubBal])] -> HashMap XPubKey [XPubBal])
-> ActionT Except (ReaderT WebConfig m) [(XPubKey, [XPubBal])]
-> ActionT Except (ReaderT WebConfig m) (HashMap XPubKey [XPubBal])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [(XPubKey, [XPubBal])] -> HashMap XPubKey [XPubBal]
g (ActionT Except (ReaderT WebConfig m) [(XPubKey, [XPubBal])]
 -> ActionT
      Except (ReaderT WebConfig m) (HashMap XPubKey [XPubBal]))
-> (HashMap XPubKey XPubSpec
    -> ActionT Except (ReaderT WebConfig m) [(XPubKey, [XPubBal])])
-> HashMap XPubKey XPubSpec
-> ActionT Except (ReaderT WebConfig m) (HashMap XPubKey [XPubBal])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((XPubKey, XPubSpec)
 -> ActionT Except (ReaderT WebConfig m) (XPubKey, [XPubBal]))
-> [(XPubKey, XPubSpec)]
-> ActionT Except (ReaderT WebConfig m) [(XPubKey, [XPubBal])]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (XPubKey, XPubSpec)
-> ActionT Except (ReaderT WebConfig m) (XPubKey, [XPubBal])
forall (f :: * -> *) a.
StoreReadExtra f =>
(a, XPubSpec) -> f (a, [XPubBal])
h ([(XPubKey, XPubSpec)]
 -> ActionT Except (ReaderT WebConfig m) [(XPubKey, [XPubBal])])
-> (HashMap XPubKey XPubSpec -> [(XPubKey, XPubSpec)])
-> HashMap XPubKey XPubSpec
-> ActionT Except (ReaderT WebConfig m) [(XPubKey, [XPubBal])]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HashMap XPubKey XPubSpec -> [(XPubKey, XPubSpec)]
forall k v. HashMap k v -> [(k, v)]
HashMap.toList
    get_abals :: HashSet Address
-> ActionT Except (ReaderT WebConfig m) (HashMap Address Balance)
get_abals =
        let f :: Balance -> (Address, Balance)
f b :: Balance
b = (Balance -> Address
balanceAddress Balance
b, Balance
b)
            g :: [Balance] -> HashMap Address Balance
g = [(Address, Balance)] -> HashMap Address Balance
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList ([(Address, Balance)] -> HashMap Address Balance)
-> ([Balance] -> [(Address, Balance)])
-> [Balance]
-> HashMap Address Balance
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Balance -> (Address, Balance))
-> [Balance] -> [(Address, Balance)]
forall a b. (a -> b) -> [a] -> [b]
map Balance -> (Address, Balance)
f
        in ([Balance] -> HashMap Address Balance)
-> ActionT Except (ReaderT WebConfig m) [Balance]
-> ActionT Except (ReaderT WebConfig m) (HashMap Address Balance)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [Balance] -> HashMap Address Balance
g (ActionT Except (ReaderT WebConfig m) [Balance]
 -> ActionT Except (ReaderT WebConfig m) (HashMap Address Balance))
-> (HashSet Address
    -> ActionT Except (ReaderT WebConfig m) [Balance])
-> HashSet Address
-> ActionT Except (ReaderT WebConfig m) (HashMap Address Balance)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Address] -> ActionT Except (ReaderT WebConfig m) [Balance]
forall (m :: * -> *). StoreReadExtra m => [Address] -> m [Balance]
getBalances ([Address] -> ActionT Except (ReaderT WebConfig m) [Balance])
-> (HashSet Address -> [Address])
-> HashSet Address
-> ActionT Except (ReaderT WebConfig m) [Balance]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HashSet Address -> [Address]
forall a. HashSet a -> [a]
HashSet.toList
    get_sxtrs :: HashSet k -> HashMap k XPubSpec -> f (HashMap k [TxRef])
get_sxtrs sxpubs :: HashSet k
sxpubs =
        let f :: (a, XPubSpec) -> f (a, [TxRef])
f (k :: a
k, s :: XPubSpec
s) = (,) a
k ([TxRef] -> (a, [TxRef])) -> f [TxRef] -> f (a, [TxRef])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> XPubSpec -> Limits -> f [TxRef]
forall (m :: * -> *).
StoreReadExtra m =>
XPubSpec -> Limits -> m [TxRef]
xPubTxs XPubSpec
s Limits
forall a. Default a => a
def
            g :: (k, b) -> Bool
g = ((k -> HashSet k -> Bool
forall a. (Eq a, Hashable a) => a -> HashSet a -> Bool
`HashSet.member` HashSet k
sxpubs) (k -> Bool) -> ((k, b) -> k) -> (k, b) -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (k, b) -> k
forall a b. (a, b) -> a
fst)
        in ([(k, [TxRef])] -> HashMap k [TxRef])
-> f [(k, [TxRef])] -> f (HashMap k [TxRef])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [(k, [TxRef])] -> HashMap k [TxRef]
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList (f [(k, [TxRef])] -> f (HashMap k [TxRef]))
-> (HashMap k XPubSpec -> f [(k, [TxRef])])
-> HashMap k XPubSpec
-> f (HashMap k [TxRef])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((k, XPubSpec) -> f (k, [TxRef]))
-> [(k, XPubSpec)] -> f [(k, [TxRef])]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (k, XPubSpec) -> f (k, [TxRef])
forall (f :: * -> *) a.
StoreReadExtra f =>
(a, XPubSpec) -> f (a, [TxRef])
f ([(k, XPubSpec)] -> f [(k, [TxRef])])
-> (HashMap k XPubSpec -> [(k, XPubSpec)])
-> HashMap k XPubSpec
-> f [(k, [TxRef])]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((k, XPubSpec) -> Bool) -> [(k, XPubSpec)] -> [(k, XPubSpec)]
forall a. (a -> Bool) -> [a] -> [a]
filter (k, XPubSpec) -> Bool
forall b. (k, b) -> Bool
g ([(k, XPubSpec)] -> [(k, XPubSpec)])
-> (HashMap k XPubSpec -> [(k, XPubSpec)])
-> HashMap k XPubSpec
-> [(k, XPubSpec)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HashMap k XPubSpec -> [(k, XPubSpec)]
forall k v. HashMap k v -> [(k, v)]
HashMap.toList
    get_atrs :: a -> a -> HashSet Address -> f (Set TxRef)
get_atrs n :: a
n offset :: a
offset =
        let i :: Word32
i = a -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (a
n a -> a -> a
forall a. Num a => a -> a -> a
+ a
offset)
            f :: [Address] -> m [TxRef]
f x :: [Address]
x = [Address] -> Limits -> m [TxRef]
forall (m :: * -> *).
StoreReadExtra m =>
[Address] -> Limits -> m [TxRef]
getAddressesTxs [Address]
x Limits
forall a. Default a => a
def{limit :: Word32
limit = Word32
i}
        in ([TxRef] -> Set TxRef) -> f [TxRef] -> f (Set TxRef)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [TxRef] -> Set TxRef
forall a. Ord a => [a] -> Set a
Set.fromList (f [TxRef] -> f (Set TxRef))
-> (HashSet Address -> f [TxRef])
-> HashSet Address
-> f (Set TxRef)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Address] -> f [TxRef]
forall (m :: * -> *). StoreReadExtra m => [Address] -> m [TxRef]
f ([Address] -> f [TxRef])
-> (HashSet Address -> [Address]) -> HashSet Address -> f [TxRef]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HashSet Address -> [Address]
forall a. HashSet a -> [a]
HashSet.toList
    get_txs :: [TxHash] -> ActionT Except (ReaderT WebConfig m) [Transaction]
get_txs = ([Maybe Transaction] -> [Transaction])
-> ActionT Except (ReaderT WebConfig m) [Maybe Transaction]
-> ActionT Except (ReaderT WebConfig m) [Transaction]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [Maybe Transaction] -> [Transaction]
forall a. [Maybe a] -> [a]
catMaybes (ActionT Except (ReaderT WebConfig m) [Maybe Transaction]
 -> ActionT Except (ReaderT WebConfig m) [Transaction])
-> ([TxHash]
    -> ActionT Except (ReaderT WebConfig m) [Maybe Transaction])
-> [TxHash]
-> ActionT Except (ReaderT WebConfig m) [Transaction]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (TxHash
 -> ActionT Except (ReaderT WebConfig m) (Maybe Transaction))
-> [TxHash]
-> ActionT Except (ReaderT WebConfig m) [Maybe Transaction]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM TxHash -> ActionT Except (ReaderT WebConfig m) (Maybe Transaction)
forall (m :: * -> *).
(Monad m, StoreReadBase m) =>
TxHash -> m (Maybe Transaction)
getTransaction
    get_etxs :: [TxHash]
-> ActionT
     Except (ReaderT WebConfig m) (HashMap TxHash Transaction)
get_etxs =
        let f :: Transaction -> (TxHash, Transaction)
f t :: Transaction
t = (Tx -> TxHash
txHash (Transaction -> Tx
transactionData Transaction
t), Transaction
t)
            g :: [Maybe Transaction] -> HashMap TxHash Transaction
g = [(TxHash, Transaction)] -> HashMap TxHash Transaction
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList ([(TxHash, Transaction)] -> HashMap TxHash Transaction)
-> ([Maybe Transaction] -> [(TxHash, Transaction)])
-> [Maybe Transaction]
-> HashMap TxHash Transaction
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Transaction -> (TxHash, Transaction))
-> [Transaction] -> [(TxHash, Transaction)]
forall a b. (a -> b) -> [a] -> [b]
map Transaction -> (TxHash, Transaction)
f ([Transaction] -> [(TxHash, Transaction)])
-> ([Maybe Transaction] -> [Transaction])
-> [Maybe Transaction]
-> [(TxHash, Transaction)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Maybe Transaction] -> [Transaction]
forall a. [Maybe a] -> [a]
catMaybes
        in ([Maybe Transaction] -> HashMap TxHash Transaction)
-> ActionT Except (ReaderT WebConfig m) [Maybe Transaction]
-> ActionT
     Except (ReaderT WebConfig m) (HashMap TxHash Transaction)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [Maybe Transaction] -> HashMap TxHash Transaction
g (ActionT Except (ReaderT WebConfig m) [Maybe Transaction]
 -> ActionT
      Except (ReaderT WebConfig m) (HashMap TxHash Transaction))
-> ([TxHash]
    -> ActionT Except (ReaderT WebConfig m) [Maybe Transaction])
-> [TxHash]
-> ActionT
     Except (ReaderT WebConfig m) (HashMap TxHash Transaction)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (TxHash
 -> ActionT Except (ReaderT WebConfig m) (Maybe Transaction))
-> [TxHash]
-> ActionT Except (ReaderT WebConfig m) [Maybe Transaction]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM TxHash -> ActionT Except (ReaderT WebConfig m) (Maybe Transaction)
forall (m :: * -> *).
(Monad m, StoreReadBase m) =>
TxHash -> m (Maybe Transaction)
getTransaction
    get_peers :: ActionT Except (ReaderT WebConfig m) Word32
get_peers = do
        [PeerInformation]
ps <- ReaderT WebConfig m [PeerInformation]
-> ActionT Except (ReaderT WebConfig m) [PeerInformation]
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (ReaderT WebConfig m [PeerInformation]
 -> ActionT Except (ReaderT WebConfig m) [PeerInformation])
-> ReaderT WebConfig m [PeerInformation]
-> ActionT Except (ReaderT WebConfig m) [PeerInformation]
forall a b. (a -> b) -> a -> b
$ PeerManager -> ReaderT WebConfig m [PeerInformation]
forall (m :: * -> *).
MonadLoggerIO m =>
PeerManager -> m [PeerInformation]
getPeersInformation (PeerManager -> ReaderT WebConfig m [PeerInformation])
-> ReaderT WebConfig m PeerManager
-> ReaderT WebConfig m [PeerInformation]
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< (WebConfig -> PeerManager) -> ReaderT WebConfig m PeerManager
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks (Store -> PeerManager
storeManager (Store -> PeerManager)
-> (WebConfig -> Store) -> WebConfig -> PeerManager
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebConfig -> Store
webStore)
        Word32 -> ActionT Except (ReaderT WebConfig m) Word32
forall (m :: * -> *) a. Monad m => a -> m a
return (Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral ([PeerInformation] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [PeerInformation]
ps))
    compute_txids :: Int -> Int -> Set TxRef -> [TxHash]
compute_txids n :: Int
n offset :: Int
offset = (TxRef -> TxHash) -> [TxRef] -> [TxHash]
forall a b. (a -> b) -> [a] -> [b]
map TxRef -> TxHash
txRefHash ([TxRef] -> [TxHash])
-> (Set TxRef -> [TxRef]) -> Set TxRef -> [TxHash]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> [TxRef] -> [TxRef]
forall a. Int -> [a] -> [a]
take (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
offset) ([TxRef] -> [TxRef])
-> (Set TxRef -> [TxRef]) -> Set TxRef -> [TxRef]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set TxRef -> [TxRef]
forall a. Set a -> [a]
Set.toDescList
    compute_etxids :: Bool -> HashMap Address a -> [Transaction] -> [TxHash]
compute_etxids prune :: Bool
prune abook :: HashMap Address a
abook =
        let f :: Transaction -> HashSet TxHash
f = HashSet Address -> Bool -> Transaction -> HashSet TxHash
relevantTxs (HashMap Address a -> HashSet Address
forall k a. HashMap k a -> HashSet k
HashMap.keysSet HashMap Address a
abook) Bool
prune
        in HashSet TxHash -> [TxHash]
forall a. HashSet a -> [a]
HashSet.toList (HashSet TxHash -> [TxHash])
-> ([Transaction] -> HashSet TxHash) -> [Transaction] -> [TxHash]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (HashSet TxHash -> HashSet TxHash -> HashSet TxHash)
-> HashSet TxHash -> [HashSet TxHash] -> HashSet TxHash
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl HashSet TxHash -> HashSet TxHash -> HashSet TxHash
forall a. (Eq a, Hashable a) => HashSet a -> HashSet a -> HashSet a
HashSet.union HashSet TxHash
forall a. HashSet a
HashSet.empty ([HashSet TxHash] -> HashSet TxHash)
-> ([Transaction] -> [HashSet TxHash])
-> [Transaction]
-> HashSet TxHash
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Transaction -> HashSet TxHash)
-> [Transaction] -> [HashSet TxHash]
forall a b. (a -> b) -> [a] -> [b]
map Transaction -> HashSet TxHash
f
    compute_sxbals :: HashSet a -> HashMap a p -> HashMap a p
compute_sxbals sxpubs :: HashSet a
sxpubs =
        let f :: a -> p -> Bool
f k :: a
k _ = a
k a -> HashSet a -> Bool
forall a. (Eq a, Hashable a) => a -> HashSet a -> Bool
`HashSet.member` HashSet a
sxpubs
        in (a -> p -> Bool) -> HashMap a p -> HashMap a p
forall k v. (k -> v -> Bool) -> HashMap k v -> HashMap k v
HashMap.filterWithKey a -> p -> Bool
forall p. a -> p -> Bool
f
    compute_xabals :: HashMap k [XPubBal] -> HashMap Address Balance
compute_xabals =
        let f :: XPubBal -> (Address, Balance)
f b :: XPubBal
b = (Balance -> Address
balanceAddress (XPubBal -> Balance
xPubBal XPubBal
b), XPubBal -> Balance
xPubBal XPubBal
b)
        in [(Address, Balance)] -> HashMap Address Balance
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList ([(Address, Balance)] -> HashMap Address Balance)
-> (HashMap k [XPubBal] -> [(Address, Balance)])
-> HashMap k [XPubBal]
-> HashMap Address Balance
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([XPubBal] -> [(Address, Balance)])
-> [[XPubBal]] -> [(Address, Balance)]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap ((XPubBal -> (Address, Balance))
-> [XPubBal] -> [(Address, Balance)]
forall a b. (a -> b) -> [a] -> [b]
map XPubBal -> (Address, Balance)
f) ([[XPubBal]] -> [(Address, Balance)])
-> (HashMap k [XPubBal] -> [[XPubBal]])
-> HashMap k [XPubBal]
-> [(Address, Balance)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HashMap k [XPubBal] -> [[XPubBal]]
forall k v. HashMap k v -> [v]
HashMap.elems
    compute_bal :: HashMap k Balance -> Word64
compute_bal =
        let f :: Balance -> Word64
f b :: Balance
b = Balance -> Word64
balanceAmount Balance
b Word64 -> Word64 -> Word64
forall a. Num a => a -> a -> a
+ Balance -> Word64
balanceZero Balance
b
        in [Word64] -> Word64
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum ([Word64] -> Word64)
-> (HashMap k Balance -> [Word64]) -> HashMap k Balance -> Word64
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Balance -> Word64) -> [Balance] -> [Word64]
forall a b. (a -> b) -> [a] -> [b]
map Balance -> Word64
f ([Balance] -> [Word64])
-> (HashMap k Balance -> [Balance])
-> HashMap k Balance
-> [Word64]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HashMap k Balance -> [Balance]
forall k v. HashMap k v -> [v]
HashMap.elems
    compute_abook :: HashSet Address
-> HashMap XPubKey [XPubBal]
-> HashMap Address (Maybe BinfoXPubPath)
compute_abook addrs :: HashSet Address
addrs xbals :: HashMap XPubKey [XPubBal]
xbals =
        let f :: XPubKey -> XPubBal -> (Address, Maybe BinfoXPubPath)
f k :: XPubKey
k XPubBal{..} =
                let a :: Address
a = Balance -> Address
balanceAddress Balance
xPubBal
                    e :: a
e = String -> a
forall a. HasCallStack => String -> a
error "lions and tigers and bears"
                    s :: Maybe SoftPath
s = DerivPathI AnyDeriv -> Maybe SoftPath
forall t. DerivPathI t -> Maybe SoftPath
toSoft ([Word32] -> DerivPathI AnyDeriv
listToPath [Word32]
xPubBalPath)
                    m :: SoftPath
m = SoftPath -> Maybe SoftPath -> SoftPath
forall a. a -> Maybe a -> a
fromMaybe SoftPath
forall a. a
e Maybe SoftPath
s
                in (Address
a, BinfoXPubPath -> Maybe BinfoXPubPath
forall a. a -> Maybe a
Just (XPubKey -> SoftPath -> BinfoXPubPath
BinfoXPubPath XPubKey
k SoftPath
m))
            g :: XPubKey -> [XPubBal] -> [(Address, Maybe BinfoXPubPath)]
g k :: XPubKey
k = (XPubBal -> (Address, Maybe BinfoXPubPath))
-> [XPubBal] -> [(Address, Maybe BinfoXPubPath)]
forall a b. (a -> b) -> [a] -> [b]
map (XPubKey -> XPubBal -> (Address, Maybe BinfoXPubPath)
f XPubKey
k)
            amap :: HashMap Address (Maybe a)
amap = (() -> Maybe a) -> HashMap Address () -> HashMap Address (Maybe a)
forall v1 v2 k. (v1 -> v2) -> HashMap k v1 -> HashMap k v2
HashMap.map (Maybe a -> () -> Maybe a
forall a b. a -> b -> a
const Maybe a
forall a. Maybe a
Nothing) (HashMap Address () -> HashMap Address (Maybe a))
-> HashMap Address () -> HashMap Address (Maybe a)
forall a b. (a -> b) -> a -> b
$
                   HashSet Address -> HashMap Address ()
forall a. HashSet a -> HashMap a ()
HashSet.toMap HashSet Address
addrs
            xmap :: HashMap Address (Maybe BinfoXPubPath)
xmap = [(Address, Maybe BinfoXPubPath)]
-> HashMap Address (Maybe BinfoXPubPath)
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList ([(Address, Maybe BinfoXPubPath)]
 -> HashMap Address (Maybe BinfoXPubPath))
-> ([(XPubKey, [XPubBal])] -> [(Address, Maybe BinfoXPubPath)])
-> [(XPubKey, [XPubBal])]
-> HashMap Address (Maybe BinfoXPubPath)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                   ((XPubKey, [XPubBal]) -> [(Address, Maybe BinfoXPubPath)])
-> [(XPubKey, [XPubBal])] -> [(Address, Maybe BinfoXPubPath)]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap ((XPubKey -> [XPubBal] -> [(Address, Maybe BinfoXPubPath)])
-> (XPubKey, [XPubBal]) -> [(Address, Maybe BinfoXPubPath)]
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry XPubKey -> [XPubBal] -> [(Address, Maybe BinfoXPubPath)]
g) ([(XPubKey, [XPubBal])] -> HashMap Address (Maybe BinfoXPubPath))
-> [(XPubKey, [XPubBal])] -> HashMap Address (Maybe BinfoXPubPath)
forall a b. (a -> b) -> a -> b
$
                   HashMap XPubKey [XPubBal] -> [(XPubKey, [XPubBal])]
forall k v. HashMap k v -> [(k, v)]
HashMap.toList HashMap XPubKey [XPubBal]
xbals
        in HashMap Address (Maybe BinfoXPubPath)
forall a. HashMap Address (Maybe a)
amap HashMap Address (Maybe BinfoXPubPath)
-> HashMap Address (Maybe BinfoXPubPath)
-> HashMap Address (Maybe BinfoXPubPath)
forall a. Semigroup a => a -> a -> a
<> HashMap Address (Maybe BinfoXPubPath)
xmap
    compute_xaddrs :: HashMap k [XPubBal] -> HashSet Address
compute_xaddrs =
        let f :: [XPubBal] -> [Address]
f = (XPubBal -> Address) -> [XPubBal] -> [Address]
forall a b. (a -> b) -> [a] -> [b]
map (Balance -> Address
balanceAddress (Balance -> Address) -> (XPubBal -> Balance) -> XPubBal -> Address
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPubBal -> Balance
xPubBal)
        in [Address] -> HashSet Address
forall a. (Eq a, Hashable a) => [a] -> HashSet a
HashSet.fromList ([Address] -> HashSet Address)
-> (HashMap k [XPubBal] -> [Address])
-> HashMap k [XPubBal]
-> HashSet Address
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([XPubBal] -> [Address]) -> [[XPubBal]] -> [Address]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap [XPubBal] -> [Address]
f ([[XPubBal]] -> [Address])
-> (HashMap k [XPubBal] -> [[XPubBal]])
-> HashMap k [XPubBal]
-> [Address]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HashMap k [XPubBal] -> [[XPubBal]]
forall k v. HashMap k v -> [v]
HashMap.elems
    sent :: BinfoTx -> p
sent BinfoTx{getBinfoTxResultBal :: BinfoTx -> Maybe (Int64, Int64)
getBinfoTxResultBal = Just (r :: Int64
r, _)}
      | Int64
r Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
< 0 = Int64 -> p
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int64 -> Int64
forall a. Num a => a -> a
negate Int64
r)
      | Bool
otherwise = 0
    sent _ = 0
    received :: BinfoTx -> p
received BinfoTx{getBinfoTxResultBal :: BinfoTx -> Maybe (Int64, Int64)
getBinfoTxResultBal = Just (r :: Int64
r, _)}
      | Int64
r Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
> 0 = Int64 -> p
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
r
      | Bool
otherwise = 0
    received _ = 0

scottyBinfoTx :: (MonadUnliftIO m, MonadLoggerIO m) => WebT m ()
scottyBinfoTx :: WebT m ()
scottyBinfoTx =
    ReaderT WebConfig m Bool
-> ActionT Except (ReaderT WebConfig m) Bool
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ((WebConfig -> Bool) -> ReaderT WebConfig m Bool
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WebConfig -> Bool
webNumTxId) ActionT Except (ReaderT WebConfig m) Bool
-> (Bool -> WebT m ()) -> WebT m ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \num :: Bool
num -> Text -> ActionT Except (ReaderT WebConfig m) BinfoTxId
forall a e (m :: * -> *).
(Parsable a, ScottyError e, Monad m) =>
Text -> ActionT e m a
S.param "txid" ActionT Except (ReaderT WebConfig m) BinfoTxId
-> (BinfoTxId -> WebT m ()) -> WebT m ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
        BinfoTxIdHash h :: TxHash
h -> Bool -> TxHash -> WebT m ()
go Bool
num TxHash
h
        BinfoTxIdIndex i :: Int64
i ->
            if | Bool -> Bool
not Bool
num Bool -> Bool -> Bool
|| Int64 -> Bool
isBinfoTxIndexNull Int64
i -> Except -> WebT m ()
forall e (m :: * -> *) a.
(ScottyError e, Monad m) =>
e -> ActionT e m a
S.raise Except
ThingNotFound
               | Int64 -> Bool
isBinfoTxIndexBlock Int64
i -> Int64 -> WebT m ()
block Int64
i
               | Int64 -> Bool
isBinfoTxIndexHash Int64
i -> Int64 -> WebT m ()
hash Int64
i
  where
    get_format :: ActionT Except (ReaderT WebConfig m) Text
get_format = Text -> ActionT Except (ReaderT WebConfig m) Text
forall a e (m :: * -> *).
(Parsable a, ScottyError e, Monad m) =>
Text -> ActionT e m a
S.param "format" ActionT Except (ReaderT WebConfig m) Text
-> (Except -> ActionT Except (ReaderT WebConfig m) Text)
-> ActionT Except (ReaderT WebConfig m) Text
forall e (m :: * -> *) a.
(ScottyError e, Monad m) =>
ActionT e m a -> (e -> ActionT e m a) -> ActionT e m a
`S.rescue` ActionT Except (ReaderT WebConfig m) Text
-> Except -> ActionT Except (ReaderT WebConfig m) Text
forall a b. a -> b -> a
const (Text -> ActionT Except (ReaderT WebConfig m) Text
forall (m :: * -> *) a. Monad m => a -> m a
return ("json" :: Text))
    js :: Bool -> Transaction -> ActionT e m ()
js num :: Bool
num t :: Transaction
t = do
        let etxids :: [TxHash]
etxids = if Bool
num
                     then HashSet TxHash -> [TxHash]
forall a. HashSet a -> [a]
HashSet.toList (HashSet TxHash -> [TxHash]) -> HashSet TxHash -> [TxHash]
forall a b. (a -> b) -> a -> b
$ HashSet Address -> Bool -> Transaction -> HashSet TxHash
relevantTxs HashSet Address
forall a. HashSet a
HashSet.empty Bool
False Transaction
t
                     else []
        Maybe [Transaction]
etxs' <- if Bool
num
                 then [Transaction] -> Maybe [Transaction]
forall a. a -> Maybe a
Just ([Transaction] -> Maybe [Transaction])
-> ([Maybe Transaction] -> [Transaction])
-> [Maybe Transaction]
-> Maybe [Transaction]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Maybe Transaction] -> [Transaction]
forall a. [Maybe a] -> [a]
catMaybes ([Maybe Transaction] -> Maybe [Transaction])
-> ActionT e m [Maybe Transaction]
-> ActionT e m (Maybe [Transaction])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (TxHash -> ActionT e m (Maybe Transaction))
-> [TxHash] -> ActionT e m [Maybe Transaction]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM TxHash -> ActionT e m (Maybe Transaction)
forall (m :: * -> *).
(Monad m, StoreReadBase m) =>
TxHash -> m (Maybe Transaction)
getTransaction [TxHash]
etxids
                 else Maybe [Transaction] -> ActionT e m (Maybe [Transaction])
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe [Transaction]
forall a. Maybe a
Nothing
        let f :: Transaction -> (TxHash, Transaction)
f t :: Transaction
t = (Tx -> TxHash
txHash (Transaction -> Tx
transactionData Transaction
t), Transaction
t)
            etxs :: Maybe (HashMap TxHash Transaction)
etxs = [(TxHash, Transaction)] -> HashMap TxHash Transaction
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList ([(TxHash, Transaction)] -> HashMap TxHash Transaction)
-> ([Transaction] -> [(TxHash, Transaction)])
-> [Transaction]
-> HashMap TxHash Transaction
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Transaction -> (TxHash, Transaction))
-> [Transaction] -> [(TxHash, Transaction)]
forall a b. (a -> b) -> [a] -> [b]
map Transaction -> (TxHash, Transaction)
f ([Transaction] -> HashMap TxHash Transaction)
-> Maybe [Transaction] -> Maybe (HashMap TxHash Transaction)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe [Transaction]
etxs'
        Network
net <- m Network -> ActionT e m Network
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m Network -> ActionT e m Network)
-> m Network -> ActionT e m Network
forall a b. (a -> b) -> a -> b
$ (WebConfig -> Network) -> m Network
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks (Store -> Network
storeNetwork (Store -> Network) -> (WebConfig -> Store) -> WebConfig -> Network
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebConfig -> Store
webStore)
        ActionT e m ()
forall (m :: * -> *) e. (Monad m, ScottyError e) => ActionT e m ()
setHeaders
        Value -> ActionT e m ()
forall a e (m :: * -> *).
(ToJSON a, ScottyError e, Monad m) =>
a -> ActionT e m ()
S.json (Value -> ActionT e m ())
-> (BinfoTx -> Value) -> BinfoTx -> ActionT e m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Network -> BinfoTx -> Value
binfoTxToJSON Network
net (BinfoTx -> ActionT e m ()) -> BinfoTx -> ActionT e m ()
forall a b. (a -> b) -> a -> b
$ Maybe (HashMap TxHash Transaction) -> Transaction -> BinfoTx
toBinfoTxSimple Maybe (HashMap TxHash Transaction)
etxs Transaction
t
    hex :: Transaction -> ActionT e m ()
hex t :: Transaction
t = do
        ActionT e m ()
forall (m :: * -> *) e. (Monad m, ScottyError e) => ActionT e m ()
setHeaders
        Text -> ActionT e m ()
forall e (m :: * -> *).
(ScottyError e, Monad m) =>
Text -> ActionT e m ()
S.text (Text -> ActionT e m ()) -> (Tx -> Text) -> Tx -> ActionT e m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
TL.fromStrict (Text -> Text) -> (Tx -> Text) -> Tx -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Text
encodeHex (ByteString -> Text) -> (Tx -> ByteString) -> Tx -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Tx -> ByteString
forall a. Serialize a => a -> ByteString
encode (Tx -> ActionT e m ()) -> Tx -> ActionT e m ()
forall a b. (a -> b) -> a -> b
$ Transaction -> Tx
transactionData Transaction
t
    go :: Bool -> TxHash -> WebT m ()
go num :: Bool
num h :: TxHash
h = TxHash -> ActionT Except (ReaderT WebConfig m) (Maybe Transaction)
forall (m :: * -> *).
(Monad m, StoreReadBase m) =>
TxHash -> m (Maybe Transaction)
getTransaction TxHash
h ActionT Except (ReaderT WebConfig m) (Maybe Transaction)
-> (Maybe Transaction -> WebT m ()) -> WebT m ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
        Nothing -> Except -> WebT m ()
forall e (m :: * -> *) a.
(ScottyError e, Monad m) =>
e -> ActionT e m a
S.raise Except
ThingNotFound
        Just t :: Transaction
t -> ActionT Except (ReaderT WebConfig m) Text
get_format ActionT Except (ReaderT WebConfig m) Text
-> (Text -> WebT m ()) -> WebT m ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
            "hex" -> Transaction -> WebT m ()
forall (m :: * -> *) e.
(Monad m, ScottyError e) =>
Transaction -> ActionT e m ()
hex Transaction
t
            _ -> Bool -> Transaction -> WebT m ()
forall (m :: * -> *) e.
(ScottyError e, StoreReadBase (ActionT e m),
 MonadReader WebConfig m) =>
Bool -> Transaction -> ActionT e m ()
js Bool
num Transaction
t
    block :: Int64 -> WebT m ()
block i :: Int64
i =
        let Just (height :: Word32
height, pos :: Word32
pos) = Int64 -> Maybe (Word32, Word32)
binfoTxIndexBlock Int64
i
        in Word32 -> ActionT Except (ReaderT WebConfig m) [BlockHash]
forall (m :: * -> *). StoreReadBase m => Word32 -> m [BlockHash]
getBlocksAtHeight Word32
height ActionT Except (ReaderT WebConfig m) [BlockHash]
-> ([BlockHash] -> WebT m ()) -> WebT m ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
            [] -> Except -> WebT m ()
forall e (m :: * -> *) a.
(ScottyError e, Monad m) =>
e -> ActionT e m a
S.raise Except
ThingNotFound
            h :: BlockHash
h:_ -> BlockHash -> ActionT Except (ReaderT WebConfig m) (Maybe BlockData)
forall (m :: * -> *).
StoreReadBase m =>
BlockHash -> m (Maybe BlockData)
getBlock BlockHash
h ActionT Except (ReaderT WebConfig m) (Maybe BlockData)
-> (Maybe BlockData -> WebT m ()) -> WebT m ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
                Nothing -> Except -> WebT m ()
forall e (m :: * -> *) a.
(ScottyError e, Monad m) =>
e -> ActionT e m a
S.raise Except
ThingNotFound
                Just BlockData{..} ->
                    if [TxHash] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [TxHash]
blockDataTxs Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
pos
                    then Bool -> TxHash -> WebT m ()
go Bool
True ([TxHash]
blockDataTxs [TxHash] -> Int -> TxHash
forall a. [a] -> Int -> a
!! Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
pos)
                    else Except -> WebT m ()
forall e (m :: * -> *) a.
(ScottyError e, Monad m) =>
e -> ActionT e m a
S.raise Except
ThingNotFound
    hmatch :: Int64 -> [TxHash] -> Maybe TxHash
hmatch h :: Int64
h = [TxHash] -> Maybe TxHash
forall a. [a] -> Maybe a
listToMaybe ([TxHash] -> Maybe TxHash)
-> ([TxHash] -> [TxHash]) -> [TxHash] -> Maybe TxHash
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (TxHash -> Bool) -> [TxHash] -> [TxHash]
forall a. (a -> Bool) -> [a] -> [a]
filter (Int64 -> TxHash -> Bool
matchBinfoTxHash Int64
h)
    hmem :: Int64 -> f (Maybe TxHash)
hmem h :: Int64
h = Int64 -> [TxHash] -> Maybe TxHash
hmatch Int64
h ([TxHash] -> Maybe TxHash)
-> ([(Word64, TxHash)] -> [TxHash])
-> [(Word64, TxHash)]
-> Maybe TxHash
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Word64, TxHash) -> TxHash) -> [(Word64, TxHash)] -> [TxHash]
forall a b. (a -> b) -> [a] -> [b]
map (Word64, TxHash) -> TxHash
forall a b. (a, b) -> b
snd ([(Word64, TxHash)] -> Maybe TxHash)
-> f [(Word64, TxHash)] -> f (Maybe TxHash)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> f [(Word64, TxHash)]
forall (m :: * -> *). StoreReadBase m => m [(Word64, TxHash)]
getMempool
    hblock :: Int64 -> m (Maybe TxHash)
hblock h :: Int64
h =
        let g :: t -> BlockHash -> m (Maybe TxHash)
g 0 _ = Maybe TxHash -> m (Maybe TxHash)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe TxHash
forall a. Maybe a
Nothing
            g i :: t
i k :: BlockHash
k =
                BlockHash -> m (Maybe BlockData)
forall (m :: * -> *).
StoreReadBase m =>
BlockHash -> m (Maybe BlockData)
getBlock BlockHash
k m (Maybe BlockData)
-> (Maybe BlockData -> m (Maybe TxHash)) -> m (Maybe TxHash)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
                Nothing -> Maybe TxHash -> m (Maybe TxHash)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe TxHash
forall a. Maybe a
Nothing
                Just BlockData{..} ->
                    case Int64 -> [TxHash] -> Maybe TxHash
hmatch Int64
h [TxHash]
blockDataTxs of
                        Nothing -> t -> BlockHash -> m (Maybe TxHash)
g (t
i t -> t -> t
forall a. Num a => a -> a -> a
- 1) (BlockHeader -> BlockHash
H.prevBlock BlockHeader
blockDataHeader)
                        Just x :: TxHash
x  -> Maybe TxHash -> m (Maybe TxHash)
forall (m :: * -> *) a. Monad m => a -> m a
return (TxHash -> Maybe TxHash
forall a. a -> Maybe a
Just TxHash
x)
        in m (Maybe BlockHash)
forall (m :: * -> *). StoreReadBase m => m (Maybe BlockHash)
getBestBlock m (Maybe BlockHash)
-> (Maybe BlockHash -> m (Maybe TxHash)) -> m (Maybe TxHash)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
            Nothing -> Maybe TxHash -> m (Maybe TxHash)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe TxHash
forall a. Maybe a
Nothing
            Just k :: BlockHash
k -> Integer -> BlockHash -> m (Maybe TxHash)
forall t (m :: * -> *).
(Eq t, Num t, StoreReadBase m) =>
t -> BlockHash -> m (Maybe TxHash)
g 10 BlockHash
k
    hash :: Int64 -> WebT m ()
hash h :: Int64
h = Int64 -> ActionT Except (ReaderT WebConfig m) (Maybe TxHash)
forall (f :: * -> *). StoreReadBase f => Int64 -> f (Maybe TxHash)
hmem Int64
h ActionT Except (ReaderT WebConfig m) (Maybe TxHash)
-> (Maybe TxHash -> WebT m ()) -> WebT m ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
        Nothing -> Int64 -> ActionT Except (ReaderT WebConfig m) (Maybe TxHash)
forall (f :: * -> *). StoreReadBase f => Int64 -> f (Maybe TxHash)
hblock Int64
h ActionT Except (ReaderT WebConfig m) (Maybe TxHash)
-> (Maybe TxHash -> WebT m ()) -> WebT m ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
            Nothing -> Except -> WebT m ()
forall e (m :: * -> *) a.
(ScottyError e, Monad m) =>
e -> ActionT e m a
S.raise Except
ThingNotFound
            Just x :: TxHash
x -> Bool -> TxHash -> WebT m ()
go Bool
True TxHash
x
        Just x :: TxHash
x -> Bool -> TxHash -> WebT m ()
go Bool
True TxHash
x

-- GET Network Information --

scottyPeers :: MonadLoggerIO m => GetPeers -> WebT m [PeerInformation]
scottyPeers :: GetPeers -> WebT m [PeerInformation]
scottyPeers _ = ReaderT WebConfig m [PeerInformation] -> WebT m [PeerInformation]
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (ReaderT WebConfig m [PeerInformation] -> WebT m [PeerInformation])
-> ReaderT WebConfig m [PeerInformation]
-> WebT m [PeerInformation]
forall a b. (a -> b) -> a -> b
$
    PeerManager -> ReaderT WebConfig m [PeerInformation]
forall (m :: * -> *).
MonadLoggerIO m =>
PeerManager -> m [PeerInformation]
getPeersInformation (PeerManager -> ReaderT WebConfig m [PeerInformation])
-> ReaderT WebConfig m PeerManager
-> ReaderT WebConfig m [PeerInformation]
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< (WebConfig -> PeerManager) -> ReaderT WebConfig m PeerManager
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks (Store -> PeerManager
storeManager (Store -> PeerManager)
-> (WebConfig -> Store) -> WebConfig -> PeerManager
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebConfig -> Store
webStore)

-- | Obtain information about connected peers from peer manager process.
getPeersInformation
    :: MonadLoggerIO m => PeerManager -> m [PeerInformation]
getPeersInformation :: PeerManager -> m [PeerInformation]
getPeersInformation mgr :: PeerManager
mgr =
    (OnlinePeer -> Maybe PeerInformation)
-> [OnlinePeer] -> [PeerInformation]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe OnlinePeer -> Maybe PeerInformation
toInfo ([OnlinePeer] -> [PeerInformation])
-> m [OnlinePeer] -> m [PeerInformation]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> PeerManager -> m [OnlinePeer]
forall (m :: * -> *). MonadIO m => PeerManager -> m [OnlinePeer]
getPeers PeerManager
mgr
  where
    toInfo :: OnlinePeer -> Maybe PeerInformation
toInfo op :: OnlinePeer
op = do
        Version
ver <- OnlinePeer -> Maybe Version
onlinePeerVersion OnlinePeer
op
        let as :: SockAddr
as = OnlinePeer -> SockAddr
onlinePeerAddress OnlinePeer
op
            ua :: ByteString
ua = VarString -> ByteString
getVarString (VarString -> ByteString) -> VarString -> ByteString
forall a b. (a -> b) -> a -> b
$ Version -> VarString
userAgent Version
ver
            vs :: Word32
vs = Version -> Word32
version Version
ver
            sv :: Word64
sv = Version -> Word64
services Version
ver
            rl :: Bool
rl = Version -> Bool
relay Version
ver
        PeerInformation -> Maybe PeerInformation
forall (m :: * -> *) a. Monad m => a -> m a
return
            $WPeerInformation :: ByteString -> String -> Word32 -> Word64 -> Bool -> PeerInformation
PeerInformation
                { peerUserAgent :: ByteString
peerUserAgent = ByteString
ua
                , peerAddress :: String
peerAddress = SockAddr -> String
forall a. Show a => a -> String
show SockAddr
as
                , peerVersion :: Word32
peerVersion = Word32
vs
                , peerServices :: Word64
peerServices = Word64
sv
                , peerRelay :: Bool
peerRelay = Bool
rl
                }

scottyHealth ::
       (MonadUnliftIO m, MonadLoggerIO m) => GetHealth -> WebT m HealthCheck
scottyHealth :: GetHealth -> WebT m HealthCheck
scottyHealth _ = do
    HealthCheck
h <- ReaderT WebConfig m HealthCheck -> WebT m HealthCheck
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (ReaderT WebConfig m HealthCheck -> WebT m HealthCheck)
-> ReaderT WebConfig m HealthCheck -> WebT m HealthCheck
forall a b. (a -> b) -> a -> b
$ ReaderT WebConfig m WebConfig
forall r (m :: * -> *). MonadReader r m => m r
ask ReaderT WebConfig m WebConfig
-> (WebConfig -> ReaderT WebConfig m HealthCheck)
-> ReaderT WebConfig m HealthCheck
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= WebConfig -> ReaderT WebConfig m HealthCheck
forall (m :: * -> *).
(MonadUnliftIO m, MonadLoggerIO m, StoreReadBase m) =>
WebConfig -> m HealthCheck
healthCheck
    Bool
-> ActionT Except (ReaderT WebConfig m) ()
-> ActionT Except (ReaderT WebConfig m) ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (HealthCheck -> Bool
forall a. Healthy a => a -> Bool
isOK HealthCheck
h) (ActionT Except (ReaderT WebConfig m) ()
 -> ActionT Except (ReaderT WebConfig m) ())
-> ActionT Except (ReaderT WebConfig m) ()
-> ActionT Except (ReaderT WebConfig m) ()
forall a b. (a -> b) -> a -> b
$ Status -> ActionT Except (ReaderT WebConfig m) ()
forall (m :: * -> *) e. Monad m => Status -> ActionT e m ()
S.status Status
status503
    HealthCheck -> WebT m HealthCheck
forall (m :: * -> *) a. Monad m => a -> m a
return HealthCheck
h

blockHealthCheck :: (MonadUnliftIO m, MonadLoggerIO m, StoreReadBase m)
                 => WebConfig -> m BlockHealth
blockHealthCheck :: WebConfig -> m BlockHealth
blockHealthCheck cfg :: WebConfig
cfg = do
    let ch :: Chain
ch = Store -> Chain
storeChain (Store -> Chain) -> Store -> Chain
forall a b. (a -> b) -> a -> b
$ WebConfig -> Store
webStore WebConfig
cfg
        blockHealthMaxDiff :: Int
blockHealthMaxDiff = WebConfig -> Int
webMaxDiff WebConfig
cfg
    Word32
blockHealthHeaders <-
        BlockNode -> Word32
H.nodeHeight (BlockNode -> Word32) -> m BlockNode -> m Word32
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Chain -> m BlockNode
forall (m :: * -> *). MonadIO m => Chain -> m BlockNode
chainGetBest Chain
ch
    Word32
blockHealthBlocks <-
        Word32 -> (BlockData -> Word32) -> Maybe BlockData -> Word32
forall b a. b -> (a -> b) -> Maybe a -> b
maybe 0 BlockData -> Word32
blockDataHeight (Maybe BlockData -> Word32) -> m (Maybe BlockData) -> m Word32
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
        MaybeT m BlockData -> m (Maybe BlockData)
forall (m :: * -> *) a. MaybeT m a -> m (Maybe a)
runMaybeT (m (Maybe BlockHash) -> MaybeT m BlockHash
forall (m :: * -> *) a. m (Maybe a) -> MaybeT m a
MaybeT m (Maybe BlockHash)
forall (m :: * -> *). StoreReadBase m => m (Maybe BlockHash)
getBestBlock MaybeT m BlockHash
-> (BlockHash -> MaybeT m BlockData) -> MaybeT m BlockData
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= m (Maybe BlockData) -> MaybeT m BlockData
forall (m :: * -> *) a. m (Maybe a) -> MaybeT m a
MaybeT (m (Maybe BlockData) -> MaybeT m BlockData)
-> (BlockHash -> m (Maybe BlockData))
-> BlockHash
-> MaybeT m BlockData
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BlockHash -> m (Maybe BlockData)
forall (m :: * -> *).
StoreReadBase m =>
BlockHash -> m (Maybe BlockData)
getBlock)
    BlockHealth -> m BlockHealth
forall (m :: * -> *) a. Monad m => a -> m a
return $WBlockHealth :: Word32 -> Word32 -> Int -> BlockHealth
BlockHealth {..}

lastBlockHealthCheck :: (MonadUnliftIO m, MonadLoggerIO m, StoreReadBase m)
                     => Chain -> WebTimeouts -> m TimeHealth
lastBlockHealthCheck :: Chain -> WebTimeouts -> m TimeHealth
lastBlockHealthCheck ch :: Chain
ch tos :: WebTimeouts
tos = do
    Int
n <- Int64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int64 -> Int) -> (SystemTime -> Int64) -> SystemTime -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SystemTime -> Int64
systemSeconds (SystemTime -> Int) -> m SystemTime -> m Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO SystemTime -> m SystemTime
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO SystemTime
getSystemTime
    Int
t <- Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32 -> Int) -> (BlockNode -> Word32) -> BlockNode -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BlockHeader -> Word32
H.blockTimestamp (BlockHeader -> Word32)
-> (BlockNode -> BlockHeader) -> BlockNode -> Word32
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BlockNode -> BlockHeader
H.nodeHeader (BlockNode -> Int) -> m BlockNode -> m Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Chain -> m BlockNode
forall (m :: * -> *). MonadIO m => Chain -> m BlockNode
chainGetBest Chain
ch
    let timeHealthAge :: Int
timeHealthAge = Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
t
        timeHealthMax :: Int
timeHealthMax = Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word64 -> Int) -> Word64 -> Int
forall a b. (a -> b) -> a -> b
$ WebTimeouts -> Word64
blockTimeout WebTimeouts
tos
    TimeHealth -> m TimeHealth
forall (m :: * -> *) a. Monad m => a -> m a
return $WTimeHealth :: Int -> Int -> TimeHealth
TimeHealth {..}

lastTxHealthCheck :: (MonadUnliftIO m, MonadLoggerIO m, StoreReadBase m)
                  => WebConfig -> m TimeHealth
lastTxHealthCheck :: WebConfig -> m TimeHealth
lastTxHealthCheck WebConfig {..} = do
    Int
n <- Int64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int64 -> Int) -> (SystemTime -> Int64) -> SystemTime -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SystemTime -> Int64
systemSeconds (SystemTime -> Int) -> m SystemTime -> m Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO SystemTime -> m SystemTime
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO SystemTime
getSystemTime
    Int
b <- Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32 -> Int) -> (BlockNode -> Word32) -> BlockNode -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BlockHeader -> Word32
H.blockTimestamp (BlockHeader -> Word32)
-> (BlockNode -> BlockHeader) -> BlockNode -> Word32
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BlockNode -> BlockHeader
H.nodeHeader (BlockNode -> Int) -> m BlockNode -> m Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Chain -> m BlockNode
forall (m :: * -> *). MonadIO m => Chain -> m BlockNode
chainGetBest Chain
ch
    Int
t <- [(Word64, TxHash)] -> Maybe (Word64, TxHash)
forall a. [a] -> Maybe a
listToMaybe ([(Word64, TxHash)] -> Maybe (Word64, TxHash))
-> m [(Word64, TxHash)] -> m (Maybe (Word64, TxHash))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> m [(Word64, TxHash)]
forall (m :: * -> *). StoreReadBase m => m [(Word64, TxHash)]
getMempool m (Maybe (Word64, TxHash))
-> (Maybe (Word64, TxHash) -> m Int) -> m Int
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
        Just t :: (Word64, TxHash)
t -> let x :: Int
x = Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word64 -> Int) -> Word64 -> Int
forall a b. (a -> b) -> a -> b
$ (Word64, TxHash) -> Word64
forall a b. (a, b) -> a
fst (Word64, TxHash)
t
                  in Int -> m Int
forall (m :: * -> *) a. Monad m => a -> m a
return (Int -> m Int) -> Int -> m Int
forall a b. (a -> b) -> a -> b
$ Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
x Int
b
        Nothing -> Int -> m Int
forall (m :: * -> *) a. Monad m => a -> m a
return Int
b
    let timeHealthAge :: Int
timeHealthAge = Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
t
        timeHealthMax :: Int
timeHealthMax = Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word64
to
    TimeHealth -> m TimeHealth
forall (m :: * -> *) a. Monad m => a -> m a
return $WTimeHealth :: Int -> Int -> TimeHealth
TimeHealth {..}
  where
    ch :: Chain
ch = Store -> Chain
storeChain Store
webStore
    to :: Word64
to = if Bool
webNoMempool then WebTimeouts -> Word64
blockTimeout WebTimeouts
webTimeouts else WebTimeouts -> Word64
txTimeout WebTimeouts
webTimeouts

pendingTxsHealthCheck :: (MonadUnliftIO m, MonadLoggerIO m, StoreReadBase m)
                      => WebConfig -> m MaxHealth
pendingTxsHealthCheck :: WebConfig -> m MaxHealth
pendingTxsHealthCheck cfg :: WebConfig
cfg = do
    let maxHealthMax :: Int
maxHealthMax = WebConfig -> Int
webMaxPending WebConfig
cfg
    Int
maxHealthNum <- BlockStore -> m Int
forall (m :: * -> *). MonadIO m => BlockStore -> m Int
blockStorePendingTxs (Store -> BlockStore
storeBlock (WebConfig -> Store
webStore WebConfig
cfg))
    MaxHealth -> m MaxHealth
forall (m :: * -> *) a. Monad m => a -> m a
return $WMaxHealth :: Int -> Int -> MaxHealth
MaxHealth {..}

peerHealthCheck :: (MonadUnliftIO m, MonadLoggerIO m, StoreReadBase m)
                => PeerManager -> m CountHealth
peerHealthCheck :: PeerManager -> m CountHealth
peerHealthCheck mgr :: PeerManager
mgr = do
    let countHealthMin :: Int
countHealthMin = 1
    Int
countHealthNum <- [OnlinePeer] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length ([OnlinePeer] -> Int) -> m [OnlinePeer] -> m Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> PeerManager -> m [OnlinePeer]
forall (m :: * -> *). MonadIO m => PeerManager -> m [OnlinePeer]
getPeers PeerManager
mgr
    CountHealth -> m CountHealth
forall (m :: * -> *) a. Monad m => a -> m a
return $WCountHealth :: Int -> Int -> CountHealth
CountHealth {..}

healthCheck :: (MonadUnliftIO m, MonadLoggerIO m, StoreReadBase m)
            => WebConfig -> m HealthCheck
healthCheck :: WebConfig -> m HealthCheck
healthCheck cfg :: WebConfig
cfg@WebConfig {..} = do
    BlockHealth
healthBlocks     <- WebConfig -> m BlockHealth
forall (m :: * -> *).
(MonadUnliftIO m, MonadLoggerIO m, StoreReadBase m) =>
WebConfig -> m BlockHealth
blockHealthCheck WebConfig
cfg
    TimeHealth
healthLastBlock  <- Chain -> WebTimeouts -> m TimeHealth
forall (m :: * -> *).
(MonadUnliftIO m, MonadLoggerIO m, StoreReadBase m) =>
Chain -> WebTimeouts -> m TimeHealth
lastBlockHealthCheck (Store -> Chain
storeChain Store
webStore) WebTimeouts
webTimeouts
    TimeHealth
healthLastTx     <- WebConfig -> m TimeHealth
forall (m :: * -> *).
(MonadUnliftIO m, MonadLoggerIO m, StoreReadBase m) =>
WebConfig -> m TimeHealth
lastTxHealthCheck WebConfig
cfg
    MaxHealth
healthPendingTxs <- WebConfig -> m MaxHealth
forall (m :: * -> *).
(MonadUnliftIO m, MonadLoggerIO m, StoreReadBase m) =>
WebConfig -> m MaxHealth
pendingTxsHealthCheck WebConfig
cfg
    CountHealth
healthPeers      <- PeerManager -> m CountHealth
forall (m :: * -> *).
(MonadUnliftIO m, MonadLoggerIO m, StoreReadBase m) =>
PeerManager -> m CountHealth
peerHealthCheck (Store -> PeerManager
storeManager Store
webStore)
    let healthNetwork :: String
healthNetwork = Network -> String
getNetworkName (Store -> Network
storeNetwork Store
webStore)
        healthVersion :: String
healthVersion = String
webVersion
        hc :: HealthCheck
hc = $WHealthCheck :: BlockHealth
-> TimeHealth
-> TimeHealth
-> MaxHealth
-> CountHealth
-> String
-> String
-> HealthCheck
HealthCheck {..}
    Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (HealthCheck -> Bool
forall a. Healthy a => a -> Bool
isOK HealthCheck
hc) (m () -> m ()) -> m () -> m ()
forall a b. (a -> b) -> a -> b
$ do
        let t :: Text
t = Text -> Text
toStrict (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ HealthCheck -> Text
forall a. ToJSON a => a -> Text
encodeToLazyText HealthCheck
hc
        $(Text
LogLevel
String -> String -> String -> CharPos -> CharPos -> Loc
Loc -> Text -> LogLevel -> Text -> m ()
forall (m :: * -> *) msg.
(MonadLogger m, ToLogStr msg) =>
Loc -> Text -> LogLevel -> msg -> m ()
b :: Text
a :: Text
monadLoggerLog :: forall (m :: * -> *) msg.
(MonadLogger m, ToLogStr msg) =>
Loc -> Text -> LogLevel -> msg -> m ()
logErrorS) "Web" (Text -> m ()) -> Text -> m ()
forall a b. (a -> b) -> a -> b
$ "Health check failed: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
t
    HealthCheck -> m HealthCheck
forall (m :: * -> *) a. Monad m => a -> m a
return HealthCheck
hc

scottyDbStats :: MonadLoggerIO m => WebT m ()
scottyDbStats :: WebT m ()
scottyDbStats = do
    WebT m ()
forall (m :: * -> *) e. (Monad m, ScottyError e) => ActionT e m ()
setHeaders
    DB
db <- ReaderT WebConfig m DB -> ActionT Except (ReaderT WebConfig m) DB
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (ReaderT WebConfig m DB -> ActionT Except (ReaderT WebConfig m) DB)
-> ReaderT WebConfig m DB
-> ActionT Except (ReaderT WebConfig m) DB
forall a b. (a -> b) -> a -> b
$ (WebConfig -> DB) -> ReaderT WebConfig m DB
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks (DatabaseReader -> DB
databaseHandle (DatabaseReader -> DB)
-> (WebConfig -> DatabaseReader) -> WebConfig -> DB
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Store -> DatabaseReader
storeDB (Store -> DatabaseReader)
-> (WebConfig -> Store) -> WebConfig -> DatabaseReader
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebConfig -> Store
webStore)
    Maybe ByteString
statsM <- ReaderT WebConfig m (Maybe ByteString)
-> ActionT Except (ReaderT WebConfig m) (Maybe ByteString)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (DB -> Property -> ReaderT WebConfig m (Maybe ByteString)
forall (m :: * -> *).
MonadIO m =>
DB -> Property -> m (Maybe ByteString)
getProperty DB
db Property
Stats)
    Text -> WebT m ()
forall e (m :: * -> *).
(ScottyError e, Monad m) =>
Text -> ActionT e m ()
S.text (Text -> WebT m ()) -> Text -> WebT m ()
forall a b. (a -> b) -> a -> b
$ Text -> (ByteString -> Text) -> Maybe ByteString -> Text
forall b a. b -> (a -> b) -> Maybe a -> b
maybe "Could not get stats" ByteString -> Text
forall a b. ConvertibleStrings a b => a -> b
cs Maybe ByteString
statsM

-----------------------
-- Parameter Parsing --
-----------------------

-- | Returns @Nothing@ if the parameter is not supplied. Raises an exception on
-- parse failure.
paramOptional :: (Param a, Monad m) => WebT m (Maybe a)
paramOptional :: WebT m (Maybe a)
paramOptional = Proxy a -> WebT m (Maybe a)
forall a (m :: * -> *).
(Param a, Monad m) =>
Proxy a -> WebT m (Maybe a)
go Proxy a
forall k (t :: k). Proxy t
Proxy
  where
    go :: (Param a, Monad m) => Proxy a -> WebT m (Maybe a)
    go :: Proxy a -> WebT m (Maybe a)
go proxy :: Proxy a
proxy = do
        Network
net <- ReaderT WebConfig m Network
-> ActionT Except (ReaderT WebConfig m) Network
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (ReaderT WebConfig m Network
 -> ActionT Except (ReaderT WebConfig m) Network)
-> ReaderT WebConfig m Network
-> ActionT Except (ReaderT WebConfig m) Network
forall a b. (a -> b) -> a -> b
$ (WebConfig -> Network) -> ReaderT WebConfig m Network
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks (Store -> Network
storeNetwork (Store -> Network) -> (WebConfig -> Store) -> WebConfig -> Network
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebConfig -> Store
webStore)
        Maybe [Text]
tsM :: Maybe [Text] <- ActionT Except (ReaderT WebConfig m) (Maybe [Text])
p ActionT Except (ReaderT WebConfig m) (Maybe [Text])
-> (Except -> ActionT Except (ReaderT WebConfig m) (Maybe [Text]))
-> ActionT Except (ReaderT WebConfig m) (Maybe [Text])
forall e (m :: * -> *) a.
(ScottyError e, Monad m) =>
ActionT e m a -> (e -> ActionT e m a) -> ActionT e m a
`S.rescue` ActionT Except (ReaderT WebConfig m) (Maybe [Text])
-> Except -> ActionT Except (ReaderT WebConfig m) (Maybe [Text])
forall a b. a -> b -> a
const (Maybe [Text] -> ActionT Except (ReaderT WebConfig m) (Maybe [Text])
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe [Text]
forall a. Maybe a
Nothing)
        case Maybe [Text]
tsM of
            Nothing -> Maybe a -> WebT m (Maybe a)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe a
forall a. Maybe a
Nothing -- Parameter was not supplied
            Just ts :: [Text]
ts -> WebT m (Maybe a)
-> (a -> WebT m (Maybe a)) -> Maybe a -> WebT m (Maybe a)
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Except -> WebT m (Maybe a)
forall e (m :: * -> *) a.
(ScottyError e, Monad m) =>
e -> ActionT e m a
S.raise Except
err) (Maybe a -> WebT m (Maybe a)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe a -> WebT m (Maybe a))
-> (a -> Maybe a) -> a -> WebT m (Maybe a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Maybe a
forall a. a -> Maybe a
Just) (Maybe a -> WebT m (Maybe a)) -> Maybe a -> WebT m (Maybe a)
forall a b. (a -> b) -> a -> b
$ Network -> [Text] -> Maybe a
forall a. Param a => Network -> [Text] -> Maybe a
parseParam Network
net [Text]
ts
      where
        l :: Text
l = Proxy a -> Text
forall a. Param a => Proxy a -> Text
proxyLabel Proxy a
proxy
        p :: ActionT Except (ReaderT WebConfig m) (Maybe [Text])
p = [Text] -> Maybe [Text]
forall a. a -> Maybe a
Just ([Text] -> Maybe [Text])
-> ActionT Except (ReaderT WebConfig m) [Text]
-> ActionT Except (ReaderT WebConfig m) (Maybe [Text])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ActionT Except (ReaderT WebConfig m) [Text]
forall a e (m :: * -> *).
(Parsable a, ScottyError e, Monad m) =>
Text -> ActionT e m a
S.param (Text -> Text
forall a b. ConvertibleStrings a b => a -> b
cs Text
l)
        err :: Except
err = String -> Except
UserError (String -> Except) -> String -> Except
forall a b. (a -> b) -> a -> b
$ "Unable to parse param " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Text -> String
forall a b. ConvertibleStrings a b => a -> b
cs Text
l

-- | Raises an exception if the parameter is not supplied
param :: (Param a, Monad m) => WebT m a
param :: WebT m a
param = Proxy a -> WebT m a
forall a (m :: * -> *). (Param a, Monad m) => Proxy a -> WebT m a
go Proxy a
forall k (t :: k). Proxy t
Proxy
  where
    go :: (Param a, Monad m) => Proxy a -> WebT m a
    go :: Proxy a -> WebT m a
go proxy :: Proxy a
proxy = do
        Maybe a
resM <- WebT m (Maybe a)
forall a (m :: * -> *). (Param a, Monad m) => WebT m (Maybe a)
paramOptional
        case Maybe a
resM of
            Just res :: a
res -> a -> WebT m a
forall (m :: * -> *) a. Monad m => a -> m a
return a
res
            _ ->
                Except -> WebT m a
forall e (m :: * -> *) a.
(ScottyError e, Monad m) =>
e -> ActionT e m a
S.raise (Except -> WebT m a) -> (String -> Except) -> String -> WebT m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Except
UserError (String -> WebT m a) -> String -> WebT m a
forall a b. (a -> b) -> a -> b
$
                "The param " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Text -> String
forall a b. ConvertibleStrings a b => a -> b
cs (Proxy a -> Text
forall a. Param a => Proxy a -> Text
proxyLabel Proxy a
proxy) String -> ShowS
forall a. Semigroup a => a -> a -> a
<> " was not defined"

-- | Returns the default value of a parameter if it is not supplied. Raises an
-- exception on parse failure.
paramDef :: (Default a, Param a, Monad m) => WebT m a
paramDef :: WebT m a
paramDef = a -> Maybe a -> a
forall a. a -> Maybe a -> a
fromMaybe a
forall a. Default a => a
def (Maybe a -> a)
-> ActionT Except (ReaderT WebConfig m) (Maybe a) -> WebT m a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ActionT Except (ReaderT WebConfig m) (Maybe a)
forall a (m :: * -> *). (Param a, Monad m) => WebT m (Maybe a)
paramOptional

-- | Does not raise exceptions. Will call @Scotty.next@ if the parameter is
-- not supplied or if parsing fails.
paramLazy :: (Param a, Monad m) => WebT m a
paramLazy :: WebT m a
paramLazy = do
    Maybe a
resM <- WebT m (Maybe a)
forall a (m :: * -> *). (Param a, Monad m) => WebT m (Maybe a)
paramOptional WebT m (Maybe a)
-> (Except -> WebT m (Maybe a)) -> WebT m (Maybe a)
forall e (m :: * -> *) a.
(ScottyError e, Monad m) =>
ActionT e m a -> (e -> ActionT e m a) -> ActionT e m a
`S.rescue` WebT m (Maybe a) -> Except -> WebT m (Maybe a)
forall a b. a -> b -> a
const (Maybe a -> WebT m (Maybe a)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe a
forall a. Maybe a
Nothing)
    WebT m a -> (a -> WebT m a) -> Maybe a -> WebT m a
forall b a. b -> (a -> b) -> Maybe a -> b
maybe WebT m a
forall e (m :: * -> *) a. (ScottyError e, Monad m) => ActionT e m a
S.next a -> WebT m a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe a
resM

parseBody :: (MonadIO m, Serialize a) => WebT m a
parseBody :: WebT m a
parseBody = do
    ByteString
b <- ActionT Except (ReaderT WebConfig m) ByteString
forall e (m :: * -> *).
(ScottyError e, MonadIO m) =>
ActionT e m ByteString
S.body
    case ByteString -> Maybe a
hex ByteString
b Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ByteString -> Maybe a
bin (ByteString -> ByteString
L.toStrict ByteString
b) of
        Nothing -> Except -> WebT m a
forall e (m :: * -> *) a.
(ScottyError e, Monad m) =>
e -> ActionT e m a
S.raise (Except -> WebT m a) -> Except -> WebT m a
forall a b. (a -> b) -> a -> b
$ String -> Except
UserError "Failed to parse request body"
        Just x :: a
x  -> a -> WebT m a
forall (m :: * -> *) a. Monad m => a -> m a
return a
x
  where
    bin :: ByteString -> Maybe a
bin = Either String a -> Maybe a
forall a b. Either a b -> Maybe b
eitherToMaybe (Either String a -> Maybe a)
-> (ByteString -> Either String a) -> ByteString -> Maybe a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Either String a
forall a. Serialize a => ByteString -> Either String a
Serialize.decode
    hex :: ByteString -> Maybe a
hex = ByteString -> Maybe a
bin (ByteString -> Maybe a)
-> (ByteString -> Maybe ByteString) -> ByteString -> Maybe a
forall (m :: * -> *) b c a.
Monad m =>
(b -> m c) -> (a -> m b) -> a -> m c
<=< Text -> Maybe ByteString
decodeHex (Text -> Maybe ByteString)
-> (ByteString -> Text) -> ByteString -> Maybe ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Text
forall a b. ConvertibleStrings a b => a -> b
cs (ByteString -> Text)
-> (ByteString -> ByteString) -> ByteString -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Bool) -> ByteString -> ByteString
C.filter (Bool -> Bool
not (Bool -> Bool) -> (Char -> Bool) -> Char -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Bool
isSpace)

parseOffset :: Monad m => WebT m OffsetParam
parseOffset :: WebT m OffsetParam
parseOffset = do
    res :: OffsetParam
res@(OffsetParam o :: Natural
o) <- WebT m OffsetParam
forall a (m :: * -> *). (Default a, Param a, Monad m) => WebT m a
paramDef
    WebLimits
limits <- ReaderT WebConfig m WebLimits
-> ActionT Except (ReaderT WebConfig m) WebLimits
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (ReaderT WebConfig m WebLimits
 -> ActionT Except (ReaderT WebConfig m) WebLimits)
-> ReaderT WebConfig m WebLimits
-> ActionT Except (ReaderT WebConfig m) WebLimits
forall a b. (a -> b) -> a -> b
$ (WebConfig -> WebLimits) -> ReaderT WebConfig m WebLimits
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WebConfig -> WebLimits
webMaxLimits
    Bool
-> ActionT Except (ReaderT WebConfig m) ()
-> ActionT Except (ReaderT WebConfig m) ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (WebLimits -> Word32
maxLimitOffset WebLimits
limits Word32 -> Word32 -> Bool
forall a. Ord a => a -> a -> Bool
> 0 Bool -> Bool -> Bool
&& Natural -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Natural
o Word32 -> Word32 -> Bool
forall a. Ord a => a -> a -> Bool
> WebLimits -> Word32
maxLimitOffset WebLimits
limits) (ActionT Except (ReaderT WebConfig m) ()
 -> ActionT Except (ReaderT WebConfig m) ())
-> ActionT Except (ReaderT WebConfig m) ()
-> ActionT Except (ReaderT WebConfig m) ()
forall a b. (a -> b) -> a -> b
$
        Except -> ActionT Except (ReaderT WebConfig m) ()
forall e (m :: * -> *) a.
(ScottyError e, Monad m) =>
e -> ActionT e m a
S.raise (Except -> ActionT Except (ReaderT WebConfig m) ())
-> (String -> Except)
-> String
-> ActionT Except (ReaderT WebConfig m) ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Except
UserError (String -> ActionT Except (ReaderT WebConfig m) ())
-> String -> ActionT Except (ReaderT WebConfig m) ()
forall a b. (a -> b) -> a -> b
$
        "offset exceeded: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Natural -> String
forall a. Show a => a -> String
show Natural
o String -> ShowS
forall a. Semigroup a => a -> a -> a
<> " > " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Word32 -> String
forall a. Show a => a -> String
show (WebLimits -> Word32
maxLimitOffset WebLimits
limits)
    OffsetParam -> WebT m OffsetParam
forall (m :: * -> *) a. Monad m => a -> m a
return OffsetParam
res

parseStart ::
       (MonadUnliftIO m, MonadLoggerIO m)
    => Maybe StartParam
    -> WebT m (Maybe Start)
parseStart :: Maybe StartParam -> WebT m (Maybe Start)
parseStart Nothing = Maybe Start -> WebT m (Maybe Start)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Start
forall a. Maybe a
Nothing
parseStart (Just s :: StartParam
s) =
    MaybeT (ActionT Except (ReaderT WebConfig m)) Start
-> WebT m (Maybe Start)
forall (m :: * -> *) a. MaybeT m a -> m (Maybe a)
runMaybeT (MaybeT (ActionT Except (ReaderT WebConfig m)) Start
 -> WebT m (Maybe Start))
-> MaybeT (ActionT Except (ReaderT WebConfig m)) Start
-> WebT m (Maybe Start)
forall a b. (a -> b) -> a -> b
$
    case StartParam
s of
        StartParamHash {startParamHash :: StartParam -> Hash256
startParamHash = Hash256
h}     -> Hash256 -> MaybeT (ActionT Except (ReaderT WebConfig m)) Start
forall (m :: * -> *). StoreReadBase m => Hash256 -> MaybeT m Start
start_tx Hash256
h MaybeT (ActionT Except (ReaderT WebConfig m)) Start
-> MaybeT (ActionT Except (ReaderT WebConfig m)) Start
-> MaybeT (ActionT Except (ReaderT WebConfig m)) Start
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Hash256 -> MaybeT (ActionT Except (ReaderT WebConfig m)) Start
forall (m :: * -> *). StoreReadBase m => Hash256 -> MaybeT m Start
start_block Hash256
h
        StartParamHeight {startParamHeight :: StartParam -> Natural
startParamHeight = Natural
h} -> Natural -> MaybeT (ActionT Except (ReaderT WebConfig m)) Start
forall (m :: * -> *) a. (Monad m, Integral a) => a -> m Start
start_height Natural
h
        StartParamTime {startParamTime :: StartParam -> Word64
startParamTime = Word64
q}     -> Word64 -> MaybeT (ActionT Except (ReaderT WebConfig m)) Start
forall (m :: * -> *).
(MonadReader WebConfig m, MonadIO m, StoreReadExtra m) =>
Word64 -> MaybeT m Start
start_time Word64
q
  where
    start_height :: a -> m Start
start_height h :: a
h = Start -> m Start
forall (m :: * -> *) a. Monad m => a -> m a
return (Start -> m Start) -> Start -> m Start
forall a b. (a -> b) -> a -> b
$ Word32 -> Start
AtBlock (Word32 -> Start) -> Word32 -> Start
forall a b. (a -> b) -> a -> b
$ a -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
h
    start_block :: Hash256 -> MaybeT m Start
start_block h :: Hash256
h = do
        BlockData
b <- m (Maybe BlockData) -> MaybeT m BlockData
forall (m :: * -> *) a. m (Maybe a) -> MaybeT m a
MaybeT (m (Maybe BlockData) -> MaybeT m BlockData)
-> m (Maybe BlockData) -> MaybeT m BlockData
forall a b. (a -> b) -> a -> b
$ BlockHash -> m (Maybe BlockData)
forall (m :: * -> *).
StoreReadBase m =>
BlockHash -> m (Maybe BlockData)
getBlock (Hash256 -> BlockHash
H.BlockHash Hash256
h)
        Start -> MaybeT m Start
forall (m :: * -> *) a. Monad m => a -> m a
return (Start -> MaybeT m Start) -> Start -> MaybeT m Start
forall a b. (a -> b) -> a -> b
$ Word32 -> Start
AtBlock (BlockData -> Word32
blockDataHeight BlockData
b)
    start_tx :: Hash256 -> MaybeT m Start
start_tx h :: Hash256
h = do
        TxData
_ <- m (Maybe TxData) -> MaybeT m TxData
forall (m :: * -> *) a. m (Maybe a) -> MaybeT m a
MaybeT (m (Maybe TxData) -> MaybeT m TxData)
-> m (Maybe TxData) -> MaybeT m TxData
forall a b. (a -> b) -> a -> b
$ TxHash -> m (Maybe TxData)
forall (m :: * -> *). StoreReadBase m => TxHash -> m (Maybe TxData)
getTxData (Hash256 -> TxHash
TxHash Hash256
h)
        Start -> MaybeT m Start
forall (m :: * -> *) a. Monad m => a -> m a
return (Start -> MaybeT m Start) -> Start -> MaybeT m Start
forall a b. (a -> b) -> a -> b
$ TxHash -> Start
AtTx (Hash256 -> TxHash
TxHash Hash256
h)
    start_time :: Word64 -> MaybeT m Start
start_time q :: Word64
q = do
        Chain
ch <- m Chain -> MaybeT m Chain
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m Chain -> MaybeT m Chain) -> m Chain -> MaybeT m Chain
forall a b. (a -> b) -> a -> b
$ (WebConfig -> Chain) -> m Chain
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks (Store -> Chain
storeChain (Store -> Chain) -> (WebConfig -> Store) -> WebConfig -> Chain
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebConfig -> Store
webStore)
        BlockData
b <- m (Maybe BlockData) -> MaybeT m BlockData
forall (m :: * -> *) a. m (Maybe a) -> MaybeT m a
MaybeT (m (Maybe BlockData) -> MaybeT m BlockData)
-> m (Maybe BlockData) -> MaybeT m BlockData
forall a b. (a -> b) -> a -> b
$ Chain -> Word64 -> m (Maybe BlockData)
forall (m :: * -> *).
(MonadIO m, StoreReadExtra m) =>
Chain -> Word64 -> m (Maybe BlockData)
blockAtOrBefore Chain
ch Word64
q
        let g :: Word32
g = BlockData -> Word32
blockDataHeight BlockData
b
        Start -> MaybeT m Start
forall (m :: * -> *) a. Monad m => a -> m a
return (Start -> MaybeT m Start) -> Start -> MaybeT m Start
forall a b. (a -> b) -> a -> b
$ Word32 -> Start
AtBlock Word32
g

parseLimits :: Monad m => WebT m LimitsParam
parseLimits :: WebT m LimitsParam
parseLimits = Maybe LimitParam -> OffsetParam -> Maybe StartParam -> LimitsParam
LimitsParam (Maybe LimitParam
 -> OffsetParam -> Maybe StartParam -> LimitsParam)
-> ActionT Except (ReaderT WebConfig m) (Maybe LimitParam)
-> ActionT
     Except
     (ReaderT WebConfig m)
     (OffsetParam -> Maybe StartParam -> LimitsParam)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ActionT Except (ReaderT WebConfig m) (Maybe LimitParam)
forall a (m :: * -> *). (Param a, Monad m) => WebT m (Maybe a)
paramOptional ActionT
  Except
  (ReaderT WebConfig m)
  (OffsetParam -> Maybe StartParam -> LimitsParam)
-> ActionT Except (ReaderT WebConfig m) OffsetParam
-> ActionT
     Except (ReaderT WebConfig m) (Maybe StartParam -> LimitsParam)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ActionT Except (ReaderT WebConfig m) OffsetParam
forall (m :: * -> *). Monad m => WebT m OffsetParam
parseOffset ActionT
  Except (ReaderT WebConfig m) (Maybe StartParam -> LimitsParam)
-> ActionT Except (ReaderT WebConfig m) (Maybe StartParam)
-> WebT m LimitsParam
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ActionT Except (ReaderT WebConfig m) (Maybe StartParam)
forall a (m :: * -> *). (Param a, Monad m) => WebT m (Maybe a)
paramOptional

paramToLimits ::
       (MonadUnliftIO m, MonadLoggerIO m)
    => Bool
    -> LimitsParam
    -> WebT m Limits
paramToLimits :: Bool -> LimitsParam -> WebT m Limits
paramToLimits full :: Bool
full (LimitsParam limitM :: Maybe LimitParam
limitM o :: OffsetParam
o startM :: Maybe StartParam
startM) = do
    WebLimits
wl <- ReaderT WebConfig m WebLimits
-> ActionT Except (ReaderT WebConfig m) WebLimits
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (ReaderT WebConfig m WebLimits
 -> ActionT Except (ReaderT WebConfig m) WebLimits)
-> ReaderT WebConfig m WebLimits
-> ActionT Except (ReaderT WebConfig m) WebLimits
forall a b. (a -> b) -> a -> b
$ (WebConfig -> WebLimits) -> ReaderT WebConfig m WebLimits
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WebConfig -> WebLimits
webMaxLimits
    Word32 -> Word32 -> Maybe Start -> Limits
Limits (WebLimits -> Bool -> Maybe LimitParam -> Word32
validateLimit WebLimits
wl Bool
full Maybe LimitParam
limitM) (OffsetParam -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral OffsetParam
o) (Maybe Start -> Limits)
-> ActionT Except (ReaderT WebConfig m) (Maybe Start)
-> WebT m Limits
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe StartParam
-> ActionT Except (ReaderT WebConfig m) (Maybe Start)
forall (m :: * -> *).
(MonadUnliftIO m, MonadLoggerIO m) =>
Maybe StartParam -> WebT m (Maybe Start)
parseStart Maybe StartParam
startM

validateLimit :: WebLimits -> Bool -> Maybe LimitParam -> Word32
validateLimit :: WebLimits -> Bool -> Maybe LimitParam -> Word32
validateLimit wl :: WebLimits
wl full :: Bool
full limitM :: Maybe LimitParam
limitM =
    Word32 -> Word32 -> Word32
forall a. (Num a, Ord a) => a -> a -> a
f Word32
m (Word32 -> Word32) -> Word32 -> Word32
forall a b. (a -> b) -> a -> b
$ Word32 -> (LimitParam -> Word32) -> Maybe LimitParam -> Word32
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Word32
d (Natural -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Natural -> Word32)
-> (LimitParam -> Natural) -> LimitParam -> Word32
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LimitParam -> Natural
getLimitParam) Maybe LimitParam
limitM
  where
    m :: Word32
m | Bool
full Bool -> Bool -> Bool
&& WebLimits -> Word32
maxLimitFull WebLimits
wl Word32 -> Word32 -> Bool
forall a. Ord a => a -> a -> Bool
> 0 = WebLimits -> Word32
maxLimitFull WebLimits
wl
      | Bool
otherwise = WebLimits -> Word32
maxLimitCount WebLimits
wl
    d :: Word32
d = WebLimits -> Word32
maxLimitDefault WebLimits
wl
    f :: a -> a -> a
f a :: a
a 0 = a
a
    f 0 b :: a
b = a
b
    f a :: a
a b :: a
b = a -> a -> a
forall a. Ord a => a -> a -> a
min a
a a
b

---------------
-- Utilities --
---------------

runInWebReader ::
       MonadIO m
    => CacheT (DatabaseReaderT m) a
    -> ReaderT WebConfig m a
runInWebReader :: CacheT (DatabaseReaderT m) a -> ReaderT WebConfig m a
runInWebReader f :: CacheT (DatabaseReaderT m) a
f = do
    DatabaseReader
bdb <- (WebConfig -> DatabaseReader) -> ReaderT WebConfig m DatabaseReader
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks (Store -> DatabaseReader
storeDB (Store -> DatabaseReader)
-> (WebConfig -> Store) -> WebConfig -> DatabaseReader
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebConfig -> Store
webStore)
    Maybe CacheConfig
mc <- (WebConfig -> Maybe CacheConfig)
-> ReaderT WebConfig m (Maybe CacheConfig)
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks (Store -> Maybe CacheConfig
storeCache (Store -> Maybe CacheConfig)
-> (WebConfig -> Store) -> WebConfig -> Maybe CacheConfig
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WebConfig -> Store
webStore)
    m a -> ReaderT WebConfig m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m a -> ReaderT WebConfig m a) -> m a -> ReaderT WebConfig m a
forall a b. (a -> b) -> a -> b
$ ReaderT DatabaseReader m a -> DatabaseReader -> m a
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT (Maybe CacheConfig
-> CacheT (DatabaseReaderT m) a -> ReaderT DatabaseReader m a
forall (m :: * -> *) a.
StoreReadBase m =>
Maybe CacheConfig -> CacheT m a -> m a
withCache Maybe CacheConfig
mc CacheT (DatabaseReaderT m) a
f) DatabaseReader
bdb

runNoCache :: MonadIO m => Bool -> ReaderT WebConfig m a -> ReaderT WebConfig m a
runNoCache :: Bool -> ReaderT WebConfig m a -> ReaderT WebConfig m a
runNoCache False f :: ReaderT WebConfig m a
f = ReaderT WebConfig m a
f
runNoCache True f :: ReaderT WebConfig m a
f =
    (WebConfig -> WebConfig)
-> ReaderT WebConfig m a -> ReaderT WebConfig m a
forall r (m :: * -> *) a. MonadReader r m => (r -> r) -> m a -> m a
local (\s :: WebConfig
s -> WebConfig
s {webStore :: Store
webStore = (WebConfig -> Store
webStore WebConfig
s) {storeCache :: Maybe CacheConfig
storeCache = Maybe CacheConfig
forall a. Maybe a
Nothing}}) ReaderT WebConfig m a
f

logIt :: (MonadUnliftIO m, MonadLoggerIO m) => m Middleware
logIt :: m Middleware
logIt = do
    m () -> IO ()
runner <- m (m () -> IO ())
forall (m :: * -> *) a. MonadUnliftIO m => m (m a -> IO a)
askRunInIO
    Middleware -> m Middleware
forall (m :: * -> *) a. Monad m => a -> m a
return (Middleware -> m Middleware) -> Middleware -> m Middleware
forall a b. (a -> b) -> a -> b
$ \app :: Request -> (Response -> IO ResponseReceived) -> IO ResponseReceived
app req :: Request
req respond :: Response -> IO ResponseReceived
respond -> do
        UTCTime
t1 <- IO UTCTime
getCurrentTime
        Request -> (Response -> IO ResponseReceived) -> IO ResponseReceived
app Request
req ((Response -> IO ResponseReceived) -> IO ResponseReceived)
-> (Response -> IO ResponseReceived) -> IO ResponseReceived
forall a b. (a -> b) -> a -> b
$ \res :: Response
res -> do
            UTCTime
t2 <- IO UTCTime
getCurrentTime
            let d :: NominalDiffTime
d = UTCTime -> UTCTime -> NominalDiffTime
diffUTCTime UTCTime
t2 UTCTime
t1
                s :: Status
s = Response -> Status
responseStatus Response
res
                msg :: Text
msg = Request -> Text
fmtReq Request
req Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> " [" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Status -> Text
fmtStatus Status
s Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> " / " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> NominalDiffTime -> Text
fmtDiff NominalDiffTime
d Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> "]"
            if Status -> Bool
statusIsSuccessful Status
s
                then m () -> IO ()
runner (m () -> IO ()) -> m () -> IO ()
forall a b. (a -> b) -> a -> b
$ $(Text
LogLevel
String -> String -> String -> CharPos -> CharPos -> Loc
Loc -> Text -> LogLevel -> Text -> m ()
forall (m :: * -> *) msg.
(MonadLogger m, ToLogStr msg) =>
Loc -> Text -> LogLevel -> msg -> m ()
b :: Text
a :: Text
monadLoggerLog :: forall (m :: * -> *) msg.
(MonadLogger m, ToLogStr msg) =>
Loc -> Text -> LogLevel -> msg -> m ()
logDebugS) "Web" Text
msg
                else m () -> IO ()
runner (m () -> IO ()) -> m () -> IO ()
forall a b. (a -> b) -> a -> b
$ $(Text
LogLevel
String -> String -> String -> CharPos -> CharPos -> Loc
Loc -> Text -> LogLevel -> Text -> m ()
forall (m :: * -> *) msg.
(MonadLogger m, ToLogStr msg) =>
Loc -> Text -> LogLevel -> msg -> m ()
b :: Text
a :: Text
monadLoggerLog :: forall (m :: * -> *) msg.
(MonadLogger m, ToLogStr msg) =>
Loc -> Text -> LogLevel -> msg -> m ()
logErrorS) "Web" Text
msg
            Response -> IO ResponseReceived
respond Response
res

fmtReq :: Request -> Text
fmtReq :: Request -> Text
fmtReq req :: Request
req =
    let m :: ByteString
m = Request -> ByteString
requestMethod Request
req
        v :: HttpVersion
v = Request -> HttpVersion
httpVersion Request
req
        p :: ByteString
p = Request -> ByteString
rawPathInfo Request
req
        q :: ByteString
q = Request -> ByteString
rawQueryString Request
req
     in ByteString -> Text
T.decodeUtf8 (ByteString -> Text) -> ByteString -> Text
forall a b. (a -> b) -> a -> b
$ ByteString
m ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> " " ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
p ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
q ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> " " ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> String -> ByteString
forall a b. ConvertibleStrings a b => a -> b
cs (HttpVersion -> String
forall a. Show a => a -> String
show HttpVersion
v)

fmtDiff :: NominalDiffTime -> Text
fmtDiff :: NominalDiffTime -> Text
fmtDiff d :: NominalDiffTime
d =
    String -> Text
forall a b. ConvertibleStrings a b => a -> b
cs (String -> Double -> String
forall r. PrintfType r => String -> r
printf "%0.3f" (NominalDiffTime -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac (NominalDiffTime
d NominalDiffTime -> NominalDiffTime -> NominalDiffTime
forall a. Num a => a -> a -> a
* 1000) :: Double) :: String) Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> " ms"

fmtStatus :: Status -> Text
fmtStatus :: Status -> Text
fmtStatus s :: Status
s = String -> Text
forall a b. ConvertibleStrings a b => a -> b
cs (Int -> String
forall a. Show a => a -> String
show (Status -> Int
statusCode Status
s)) Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> " " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> ByteString -> Text
forall a b. ConvertibleStrings a b => a -> b
cs (Status -> ByteString
statusMessage Status
s)