mmm-0.1.0.0: Minecraft 1.21.4 implementation in Haskell
LicenseBSD-3-Clause
Safe HaskellNone
LanguageGHC2021

M.IO.Internal.EffectTypes

Description

This module defines the core effects used for networking in the Minecraft protocol implementation. It provides bidirectional packet communication with compression and encryption support.

Synopsis

Core effect

data Talking (a :: Type -> Type) b where Source #

the communication effect

Constructors

Hear :: forall b (a :: Type -> Type). (Unpack b, Typeable b) => Immediately -> Talking a b

listen for a message and assert its type

when immediately is set and message missing, invoke Empty

HearU :: forall (a :: Type -> Type). Immediately -> Talking a Uninterpreted

listen for a raw uninterpreted message

when immediately is set and message missing, invoke Empty

HearA :: forall (a :: Type -> Type). Immediately -> Talking a SomeUnpack

listen for a message with dynamic unpacking

when immediately is set and message missing, invoke Empty

Say :: forall a1 (a :: Type -> Type). (Pack a1, Typeable a1) => a1 -> Talking a ()

send a message

Setcompression :: forall (a :: Type -> Type). Int -> Talking a ()

set the compression threshold

  • non-negative: compress messages larger than this size
  • negative: disable compression
Setencryption :: forall (a :: Type -> Type). ByteString -> Talking a ()

set the encryption key

Instances

Instances details
type DispatchOf Talking Source # 
Instance details

Defined in M.IO.Internal.EffectTypes

type DispatchOf Talking = 'Dynamic

Types

data Direction Source #

relative packet direction. Used to identify packet flow without hardcoding client/server roles

Constructors

Inbound 
Outbound 

Instances

Instances details
Data Direction Source # 
Instance details

Defined in M.IO.Internal.EffectTypes

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Direction -> c Direction #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Direction #

toConstr :: Direction -> Constr #

dataTypeOf :: Direction -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Direction) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Direction) #

gmapT :: (forall b. Data b => b -> b) -> Direction -> Direction #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Direction -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Direction -> r #

gmapQ :: (forall d. Data d => d -> u) -> Direction -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Direction -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Direction -> m Direction #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Direction -> m Direction #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Direction -> m Direction #

Bounded Direction Source # 
Instance details

Defined in M.IO.Internal.EffectTypes

Enum Direction Source # 
Instance details

Defined in M.IO.Internal.EffectTypes

Generic Direction Source # 
Instance details

Defined in M.IO.Internal.EffectTypes

Associated Types

type Rep Direction 
Instance details

Defined in M.IO.Internal.EffectTypes

type Rep Direction = D1 ('MetaData "Direction" "M.IO.Internal.EffectTypes" "mmm-0.1.0.0-oCDsNp3EBL2JzoyA6cTai" 'False) (C1 ('MetaCons "Inbound" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Outbound" 'PrefixI 'False) (U1 :: Type -> Type))
Read Direction Source # 
Instance details

Defined in M.IO.Internal.EffectTypes

Show Direction Source # 
Instance details

Defined in M.IO.Internal.EffectTypes

NFData Direction Source # 
Instance details

Defined in M.IO.Internal.EffectTypes

Methods

rnf :: Direction -> () #

Eq Direction Source # 
Instance details

Defined in M.IO.Internal.EffectTypes

Ord Direction Source # 
Instance details

Defined in M.IO.Internal.EffectTypes

Hashable Direction Source # 
Instance details

Defined in M.IO.Internal.EffectTypes

Lift Direction Source # 
Instance details

Defined in M.IO.Internal.EffectTypes

Methods

lift :: Quote m => Direction -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Direction -> Code m Direction #

type Rep Direction Source # 
Instance details

Defined in M.IO.Internal.EffectTypes

type Rep Direction = D1 ('MetaData "Direction" "M.IO.Internal.EffectTypes" "mmm-0.1.0.0-oCDsNp3EBL2JzoyA6cTai" 'False) (C1 ('MetaCons "Inbound" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Outbound" 'PrefixI 'False) (U1 :: Type -> Type))

data Immediately Source #

urgency level for receiving packets

Constructors

Immediately 
Eventually 

Instances

Instances details
Data Immediately Source # 
Instance details

Defined in M.IO.Internal.EffectTypes

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Immediately -> c Immediately #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Immediately #

toConstr :: Immediately -> Constr #

dataTypeOf :: Immediately -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Immediately) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Immediately) #

gmapT :: (forall b. Data b => b -> b) -> Immediately -> Immediately #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Immediately -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Immediately -> r #

gmapQ :: (forall d. Data d => d -> u) -> Immediately -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Immediately -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Immediately -> m Immediately #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Immediately -> m Immediately #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Immediately -> m Immediately #

Bounded Immediately Source # 
Instance details

Defined in M.IO.Internal.EffectTypes

Enum Immediately Source # 
Instance details

Defined in M.IO.Internal.EffectTypes

Generic Immediately Source # 
Instance details

Defined in M.IO.Internal.EffectTypes

Associated Types

type Rep Immediately 
Instance details

Defined in M.IO.Internal.EffectTypes

type Rep Immediately = D1 ('MetaData "Immediately" "M.IO.Internal.EffectTypes" "mmm-0.1.0.0-oCDsNp3EBL2JzoyA6cTai" 'False) (C1 ('MetaCons "Immediately" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Eventually" 'PrefixI 'False) (U1 :: Type -> Type))
Read Immediately Source # 
Instance details

Defined in M.IO.Internal.EffectTypes

Show Immediately Source # 
Instance details

Defined in M.IO.Internal.EffectTypes

NFData Immediately Source # 
Instance details

Defined in M.IO.Internal.EffectTypes

Methods

rnf :: Immediately -> () #

Eq Immediately Source # 
Instance details

Defined in M.IO.Internal.EffectTypes

Ord Immediately Source # 
Instance details

Defined in M.IO.Internal.EffectTypes

Hashable Immediately Source # 
Instance details

Defined in M.IO.Internal.EffectTypes

Lift Immediately Source # 
Instance details

Defined in M.IO.Internal.EffectTypes

Methods

lift :: Quote m => Immediately -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Immediately -> Code m Immediately #

type Rep Immediately Source # 
Instance details

Defined in M.IO.Internal.EffectTypes

type Rep Immediately = D1 ('MetaData "Immediately" "M.IO.Internal.EffectTypes" "mmm-0.1.0.0-oCDsNp3EBL2JzoyA6cTai" 'False) (C1 ('MetaCons "Immediately" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Eventually" 'PrefixI 'False) (U1 :: Type -> Type))

data Op r where Source #

operations on a packet

Constructors

Parse :: Uninterpreted -> Op SomeUnpack

parse any packet

Code :: Direction -> TypeRep -> Op (Maybe Word8)

find code of a packet based on its TypeRep

Instances

Instances details
Show (Op r) Source # 
Instance details

Defined in M.IO.Internal.EffectTypes

Methods

showsPrec :: Int -> Op r -> ShowS #

show :: Op r -> String #

showList :: [Op r] -> ShowS #

NFData (Op r) Source # 
Instance details

Defined in M.IO.Internal.EffectTypes

Methods

rnf :: Op r -> () #

Eq (Op r) Source # 
Instance details

Defined in M.IO.Internal.EffectTypes

Methods

(==) :: Op r -> Op r -> Bool #

(/=) :: Op r -> Op r -> Bool #

Ord (Op r) Source # 
Instance details

Defined in M.IO.Internal.EffectTypes

Methods

compare :: Op r -> Op r -> Ordering #

(<) :: Op r -> Op r -> Bool #

(<=) :: Op r -> Op r -> Bool #

(>) :: Op r -> Op r -> Bool #

(>=) :: Op r -> Op r -> Bool #

max :: Op r -> Op r -> Op r #

min :: Op r -> Op r -> Op r #

Hashable (Op r) Source # 
Instance details

Defined in M.IO.Internal.EffectTypes

Methods

hashWithSalt :: Int -> Op r -> Int

hash :: Op r -> Int

newtype ParserState Source #

parser state object (as in object-oriented programming)

Constructors

ParserState 

Fields

  • send2parserstate :: forall r. Op r -> r

    send a "message" to the parser state and get a response

Effect operations

type Talking' (es :: [Effect]) = (Talking :> es, State ParserState :> es, NonDet :> es) Source #

the communication effect with parser state and non-determinism

hear :: forall a (es :: [Effect]). (HasCallStack, Talking :> es, Unpack a, Typeable a) => Immediately -> Eff es a Source #

listen for a message and assert its type

when immediately is set and message missing, invoke Empty

hearU :: forall (es :: [Effect]). (HasCallStack, Talking :> es) => Immediately -> Eff es Uninterpreted Source #

listen for a raw uninterpreted message

when immediately is set and message missing, invoke Empty

hearA :: forall (es :: [Effect]). (HasCallStack, Talking :> es) => Immediately -> Eff es SomeUnpack Source #

listen for a message with dynamic unpacking

when immediately is set and message missing, invoke Empty

say :: forall a (es :: [Effect]). (HasCallStack, Talking :> es, Pack a, Typeable a) => a -> Eff es () Source #

send a message

Configuration

setcompression :: forall (es :: [Effect]). (HasCallStack, Talking :> es) => Int -> Eff es () Source #

set the compression threshold

  • non-negative: compress messages larger than this size
  • negative: disable compression

setencryption :: forall (es :: [Effect]). (HasCallStack, Talking :> es) => ByteString -> Eff es () Source #

set the encryption key

enter :: forall (es :: [Effect]). State ParserState :> es => ParserState -> Eff es () Source #

enter the parser state