This commit is contained in:
Dmitry Zuikov 2023-01-13 11:18:51 +03:00
parent 08c634a82c
commit 2da7ea122a
5 changed files with 53 additions and 7 deletions

View File

@ -64,7 +64,8 @@ library
import: shared-properties
exposed-modules:
HBS2.Clock
HBS2.Actors
, HBS2.Clock
, HBS2.Data.Types
, HBS2.Data.Types.Refs
, HBS2.Defaults
@ -101,6 +102,7 @@ library
, safe
, serialise
, stm
, stm-chans
, text
, uniplate

View File

@ -0,0 +1,5 @@
module HBS2.Actors where

View File

@ -1,8 +1,15 @@
module HBS2.Net.Proto where
import HBS2.Prelude.Plated
import Data.Kind
import Data.Hashable
class (Hashable (Peer a), Eq (Peer a)) => IsPeer a where
data family Peer a :: Type
newtype BlockInfo = BlockInfo Integer
deriving stock (Eq, Data)

View File

@ -2,11 +2,24 @@ module HBS2.Net.Proto.Actors.BlockInfo where
import HBS2.Prelude
import HBS2.Hash
import HBS2.Net.Proto
import HBS2.Clock
import Data.Function
import Control.Concurrent.STM.TBMQueue (TBMQueue)
import Control.Concurrent.STM.TBMQueue qualified as TBMQ
import Control.Concurrent.STM
-- needs: logger
-- needs: reader and shit
-- needs: messaging
newtype BlockInfoActor = BlockInfoActor ()
-- needs: cookie manager
-- needs: peer manager
data BlockInfoActor =
BlockInfoActor
{ tasks :: TBMQueue (IO ())
}
-- TODO: send block info request
@ -17,10 +30,29 @@ newtype BlockInfoActor = BlockInfoActor ()
createBlockInfoActor :: MonadIO m => m BlockInfoActor
createBlockInfoActor = do
pure $ BlockInfoActor ()
qtask <- liftIO $ atomically $ TBMQ.newTBMQueue 500 -- FIXME: settings
pure $ BlockInfoActor undefined
sendBlockInfoRequest :: MonadIO m => BlockInfoActor -> Hash h -> m ()
sendBlockInfoRequest b h = do
runBlockInfoActor :: MonadIO m => BlockInfoActor -> m ()
runBlockInfoActor _ =
fix \next -> do
pause (1 :: Timeout 'Seconds)
next
requestBlockInfo :: MonadIO m
=> BlockInfoActor
-> Maybe (Peer peer)
-> Hash h
-> m ()
requestBlockInfo b h = do
undefined
getBlockInfo :: MonadIO m
=> BlockInfoActor
-> Maybe (Peer peer)
-> m (Maybe BlockInfo)
getBlockInfo _ _ = undefined

View File

@ -1,13 +1,13 @@
module HBS2.Prelude
( module Data.String
, module Safe
, MonadIO
, MonadIO(..)
-- , module HBS2.Prelude
) where
import Data.String (IsString(..))
import Safe
import Control.Monad.IO.Class (MonadIO)
import Control.Monad.IO.Class (MonadIO(..))