fix compile

This commit is contained in:
Dmitry Zuikov 2023-01-16 22:13:29 +03:00
parent b0e4152d98
commit 8e0340197c
4 changed files with 7 additions and 4 deletions

View File

@ -119,7 +119,6 @@ test-suite test
other-modules: TestFakeMessaging other-modules: TestFakeMessaging
, TestActors , TestActors
, TestBlockInfoActor , TestBlockInfoActor
, TestAbstractDispatch
, TestUniqProtoId , TestUniqProtoId
, FakeMessaging , FakeMessaging
, HasProtocol , HasProtocol
@ -149,6 +148,7 @@ test-suite test
, transformers , transformers
, uniplate , uniplate
, vector , vector
, simple-logger

View File

@ -5,11 +5,12 @@ module HasProtocol where
import Data.Kind import Data.Kind
import Data.Proxy import Data.Proxy
import GHC.TypeLits import GHC.TypeLits
import Data.Hashable
-- e -> Transport (like, UDP or TChan) -- e -> Transport (like, UDP or TChan)
-- p -> L4 Protocol (like Ping/Pong) -- 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 data family (Peer e) :: Type
class (KnownNat (ProtocolId p), HasPeer e) => HasProtocol e p | p -> e where class (KnownNat (ProtocolId p), HasPeer e) => HasProtocol e p | p -> e where

View File

@ -3,7 +3,6 @@ module Main where
import TestFakeMessaging import TestFakeMessaging
import TestActors import TestActors
import TestBlockInfoActor import TestBlockInfoActor
import TestAbstractDispatch
import Test.Tasty import Test.Tasty
import Test.Tasty.HUnit import Test.Tasty.HUnit
@ -16,7 +15,6 @@ main =
testCase "testFakeMessaging1" testFakeMessaging1 testCase "testFakeMessaging1" testFakeMessaging1
, testCase "testActorsBasic" testActorsBasic , testCase "testActorsBasic" testActorsBasic
, testCase "testBlockInfoActor" testBlockInfoActor , testCase "testBlockInfoActor" testBlockInfoActor
, testCase "testAbstractDispatch" testAbstractDispatch
] ]

View File

@ -28,6 +28,8 @@ import Data.List qualified as List
import Data.Maybe import Data.Maybe
import Safe import Safe
import Control.Logger.Simple qualified as Log
import Prettyprinter hiding (pipe) import Prettyprinter hiding (pipe)
newtype From a = From (Peer a) newtype From a = From (Peer a)
@ -213,6 +215,8 @@ peekPokeHandler =
testUniqiProtoId :: IO () testUniqiProtoId :: IO ()
testUniqiProtoId = do testUniqiProtoId = do
-- setLogLevel
fake <- newFakeP2P True fake <- newFakeP2P True
let peer0 = FakePeer 0 let peer0 = FakePeer 0