mirror of https://github.com/voidlizard/hbs2
wip
This commit is contained in:
parent
08c634a82c
commit
2da7ea122a
|
@ -64,7 +64,8 @@ library
|
||||||
import: shared-properties
|
import: shared-properties
|
||||||
|
|
||||||
exposed-modules:
|
exposed-modules:
|
||||||
HBS2.Clock
|
HBS2.Actors
|
||||||
|
, HBS2.Clock
|
||||||
, HBS2.Data.Types
|
, HBS2.Data.Types
|
||||||
, HBS2.Data.Types.Refs
|
, HBS2.Data.Types.Refs
|
||||||
, HBS2.Defaults
|
, HBS2.Defaults
|
||||||
|
@ -101,6 +102,7 @@ library
|
||||||
, safe
|
, safe
|
||||||
, serialise
|
, serialise
|
||||||
, stm
|
, stm
|
||||||
|
, stm-chans
|
||||||
, text
|
, text
|
||||||
, uniplate
|
, uniplate
|
||||||
|
|
||||||
|
|
|
@ -0,0 +1,5 @@
|
||||||
|
module HBS2.Actors where
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
|
|
|
@ -1,8 +1,15 @@
|
||||||
module HBS2.Net.Proto where
|
module HBS2.Net.Proto where
|
||||||
|
|
||||||
|
import HBS2.Prelude.Plated
|
||||||
|
|
||||||
import Data.Kind
|
import Data.Kind
|
||||||
import Data.Hashable
|
import Data.Hashable
|
||||||
|
|
||||||
class (Hashable (Peer a), Eq (Peer a)) => IsPeer a where
|
class (Hashable (Peer a), Eq (Peer a)) => IsPeer a where
|
||||||
data family Peer a :: Type
|
data family Peer a :: Type
|
||||||
|
|
||||||
|
|
||||||
|
newtype BlockInfo = BlockInfo Integer
|
||||||
|
deriving stock (Eq, Data)
|
||||||
|
|
||||||
|
|
||||||
|
|
|
@ -2,11 +2,24 @@ module HBS2.Net.Proto.Actors.BlockInfo where
|
||||||
|
|
||||||
import HBS2.Prelude
|
import HBS2.Prelude
|
||||||
import HBS2.Hash
|
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: logger
|
||||||
-- needs: reader and shit
|
-- needs: reader and shit
|
||||||
-- needs: messaging
|
-- needs: messaging
|
||||||
newtype BlockInfoActor = BlockInfoActor ()
|
-- needs: cookie manager
|
||||||
|
-- needs: peer manager
|
||||||
|
|
||||||
|
data BlockInfoActor =
|
||||||
|
BlockInfoActor
|
||||||
|
{ tasks :: TBMQueue (IO ())
|
||||||
|
}
|
||||||
|
|
||||||
|
|
||||||
-- TODO: send block info request
|
-- TODO: send block info request
|
||||||
|
@ -17,10 +30,29 @@ newtype BlockInfoActor = BlockInfoActor ()
|
||||||
|
|
||||||
createBlockInfoActor :: MonadIO m => m BlockInfoActor
|
createBlockInfoActor :: MonadIO m => m BlockInfoActor
|
||||||
createBlockInfoActor = do
|
createBlockInfoActor = do
|
||||||
pure $ BlockInfoActor ()
|
qtask <- liftIO $ atomically $ TBMQ.newTBMQueue 500 -- FIXME: settings
|
||||||
|
pure $ BlockInfoActor undefined
|
||||||
|
|
||||||
sendBlockInfoRequest :: MonadIO m => BlockInfoActor -> Hash h -> m ()
|
runBlockInfoActor :: MonadIO m => BlockInfoActor -> m ()
|
||||||
sendBlockInfoRequest b h = do
|
runBlockInfoActor _ =
|
||||||
|
fix \next -> do
|
||||||
|
pause (1 :: Timeout 'Seconds)
|
||||||
|
next
|
||||||
|
|
||||||
|
requestBlockInfo :: MonadIO m
|
||||||
|
=> BlockInfoActor
|
||||||
|
-> Maybe (Peer peer)
|
||||||
|
-> Hash h
|
||||||
|
-> m ()
|
||||||
|
|
||||||
|
requestBlockInfo b h = do
|
||||||
undefined
|
undefined
|
||||||
|
|
||||||
|
getBlockInfo :: MonadIO m
|
||||||
|
=> BlockInfoActor
|
||||||
|
-> Maybe (Peer peer)
|
||||||
|
-> m (Maybe BlockInfo)
|
||||||
|
|
||||||
|
getBlockInfo _ _ = undefined
|
||||||
|
|
||||||
|
|
||||||
|
|
|
@ -1,13 +1,13 @@
|
||||||
module HBS2.Prelude
|
module HBS2.Prelude
|
||||||
( module Data.String
|
( module Data.String
|
||||||
, module Safe
|
, module Safe
|
||||||
, MonadIO
|
, MonadIO(..)
|
||||||
-- , module HBS2.Prelude
|
-- , module HBS2.Prelude
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Data.String (IsString(..))
|
import Data.String (IsString(..))
|
||||||
import Safe
|
import Safe
|
||||||
import Control.Monad.IO.Class (MonadIO)
|
import Control.Monad.IO.Class (MonadIO(..))
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
|
|
Loading…
Reference in New Issue