mirror of https://github.com/voidlizard/hbs2
still compiles
This commit is contained in:
parent
3322061b80
commit
66de448dca
|
@ -6,10 +6,12 @@ import Data.Kind
|
||||||
import Data.Proxy
|
import Data.Proxy
|
||||||
import GHC.TypeLits
|
import GHC.TypeLits
|
||||||
|
|
||||||
class HasProtocol p a | a -> p where
|
class HasPeer p where
|
||||||
|
type family (Peer p) :: Type
|
||||||
|
|
||||||
|
class HasPeer p => HasProtocol p a | a -> p where
|
||||||
type family ProtocolId a = (id :: Nat) | id -> a
|
type family ProtocolId a = (id :: Nat) | id -> a
|
||||||
type family Encoded p :: Type
|
type family Encoded p :: Type
|
||||||
type family (Peer p) :: Type
|
|
||||||
|
|
||||||
protoId :: forall . KnownNat (ProtocolId a) => Proxy a -> Integer
|
protoId :: forall . KnownNat (ProtocolId a) => Proxy a -> Integer
|
||||||
protoId _ = natVal (Proxy @(ProtocolId a))
|
protoId _ = natVal (Proxy @(ProtocolId a))
|
||||||
|
|
|
@ -31,10 +31,12 @@ type family Encoding a :: Type
|
||||||
|
|
||||||
data Fake
|
data Fake
|
||||||
|
|
||||||
|
instance HasPeer Fake where
|
||||||
|
type instance Peer Fake = Int
|
||||||
|
|
||||||
instance HasProtocol Fake PingPong where
|
instance HasProtocol Fake PingPong where
|
||||||
type instance ProtocolId PingPong = 1
|
type instance ProtocolId PingPong = 1
|
||||||
type instance Encoded Fake = String
|
type instance Encoded Fake = String
|
||||||
type instance Peer Fake = Int
|
|
||||||
decode = undefined
|
decode = undefined
|
||||||
encode = undefined
|
encode = undefined
|
||||||
|
|
||||||
|
@ -54,9 +56,9 @@ makeResponse h = AnyProtocol { getProtoId = natVal (Proxy @(ProtocolId p))
|
||||||
, handle = h
|
, handle = h
|
||||||
}
|
}
|
||||||
|
|
||||||
data EngineEnv =
|
data EngineEnv = forall p . HasPeer p =>
|
||||||
EngineEnv
|
EngineEnv
|
||||||
{
|
{ peer :: Maybe (Peer p)
|
||||||
}
|
}
|
||||||
|
|
||||||
newtype EngineM m a = EngineM { fromEngine :: ReaderT EngineEnv m a }
|
newtype EngineM m a = EngineM { fromEngine :: ReaderT EngineEnv m a }
|
||||||
|
@ -72,18 +74,18 @@ instance (Monad m, HasProtocol e p) => Response e p (EngineM m) where
|
||||||
-- TODO: sendTo
|
-- TODO: sendTo
|
||||||
undefined
|
undefined
|
||||||
|
|
||||||
|
pingPongHandler :: forall a m . (MonadIO m, Response a PingPong m) => PingPong -> m ()
|
||||||
|
pingPongHandler =
|
||||||
|
\case
|
||||||
|
Ping c -> liftIO (print "effect: PING") >> response @a @PingPong (Pong c)
|
||||||
|
Pong _ -> liftIO (print "effect: PONG")
|
||||||
|
|
||||||
testUniqiProtoId :: IO ()
|
testUniqiProtoId :: IO ()
|
||||||
testUniqiProtoId = do
|
testUniqiProtoId = do
|
||||||
|
|
||||||
let env = EngineEnv
|
let env = EngineEnv @Fake Nothing
|
||||||
|
|
||||||
-- let ssid = 0
|
let pingpong = makeResponse pingPongHandler
|
||||||
-- runEngineM env $ request 2 (Ping ssid)
|
|
||||||
|
|
||||||
let pingpong = makeResponse
|
|
||||||
\case
|
|
||||||
Ping c -> lift (print "effect: PING") >> response (Pong c)
|
|
||||||
Pong _ -> lift (print "effect: PONG")
|
|
||||||
|
|
||||||
let decoders = mempty :: Map Integer (AnyProtocol String (EngineM IO))
|
let decoders = mempty :: Map Integer (AnyProtocol String (EngineM IO))
|
||||||
let dec = Map.insert 1 pingpong decoders
|
let dec = Map.insert 1 pingpong decoders
|
||||||
|
|
Loading…
Reference in New Issue