mirror of https://github.com/voidlizard/hbs2
fix compile
This commit is contained in:
parent
b0e4152d98
commit
8e0340197c
|
@ -119,7 +119,6 @@ test-suite test
|
|||
other-modules: TestFakeMessaging
|
||||
, TestActors
|
||||
, TestBlockInfoActor
|
||||
, TestAbstractDispatch
|
||||
, TestUniqProtoId
|
||||
, FakeMessaging
|
||||
, HasProtocol
|
||||
|
@ -149,6 +148,7 @@ test-suite test
|
|||
, transformers
|
||||
, uniplate
|
||||
, vector
|
||||
, simple-logger
|
||||
|
||||
|
||||
|
||||
|
|
|
@ -5,11 +5,12 @@ module HasProtocol where
|
|||
import Data.Kind
|
||||
import Data.Proxy
|
||||
import GHC.TypeLits
|
||||
import Data.Hashable
|
||||
|
||||
-- e -> Transport (like, UDP or TChan)
|
||||
-- p -> L4 Protocol (like Ping/Pong)
|
||||
|
||||
class HasPeer e where
|
||||
class (Hashable (Peer e), Eq (Peer e)) =>HasPeer e where
|
||||
data family (Peer e) :: Type
|
||||
|
||||
class (KnownNat (ProtocolId p), HasPeer e) => HasProtocol e p | p -> e where
|
||||
|
|
|
@ -3,7 +3,6 @@ module Main where
|
|||
import TestFakeMessaging
|
||||
import TestActors
|
||||
import TestBlockInfoActor
|
||||
import TestAbstractDispatch
|
||||
|
||||
import Test.Tasty
|
||||
import Test.Tasty.HUnit
|
||||
|
@ -16,7 +15,6 @@ main =
|
|||
testCase "testFakeMessaging1" testFakeMessaging1
|
||||
, testCase "testActorsBasic" testActorsBasic
|
||||
, testCase "testBlockInfoActor" testBlockInfoActor
|
||||
, testCase "testAbstractDispatch" testAbstractDispatch
|
||||
]
|
||||
|
||||
|
||||
|
|
|
@ -28,6 +28,8 @@ import Data.List qualified as List
|
|||
import Data.Maybe
|
||||
import Safe
|
||||
|
||||
import Control.Logger.Simple qualified as Log
|
||||
|
||||
import Prettyprinter hiding (pipe)
|
||||
|
||||
newtype From a = From (Peer a)
|
||||
|
@ -213,6 +215,8 @@ peekPokeHandler =
|
|||
testUniqiProtoId :: IO ()
|
||||
testUniqiProtoId = do
|
||||
|
||||
-- setLogLevel
|
||||
|
||||
fake <- newFakeP2P True
|
||||
|
||||
let peer0 = FakePeer 0
|
||||
|
|
Loading…
Reference in New Issue