hnix-store-remote-0.7.0.0: Remote hnix store
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Serializer.Example

Synopsis

Simple protocol

data OpCode Source #

OpCode used to differentiate between operations

Constructors

OpCode_Int 
OpCode_Bool 

Instances

Instances details
Bounded OpCode Source # 
Instance details

Defined in Data.Serializer.Example

Enum OpCode Source # 
Instance details

Defined in Data.Serializer.Example

Generic OpCode Source # 
Instance details

Defined in Data.Serializer.Example

Associated Types

type Rep OpCode :: Type -> Type #

Methods

from :: OpCode -> Rep OpCode x #

to :: Rep OpCode x -> OpCode #

Show OpCode Source # 
Instance details

Defined in Data.Serializer.Example

Eq OpCode Source # 
Instance details

Defined in Data.Serializer.Example

Methods

(==) :: OpCode -> OpCode -> Bool #

(/=) :: OpCode -> OpCode -> Bool #

Ord OpCode Source # 
Instance details

Defined in Data.Serializer.Example

type Rep OpCode Source # 
Instance details

Defined in Data.Serializer.Example

type Rep OpCode = D1 ('MetaData "OpCode" "Data.Serializer.Example" "hnix-store-remote-0.7.0.0-3KzMSkqSXnCD71veVOrNoM" 'False) (C1 ('MetaCons "OpCode_Int" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OpCode_Bool" 'PrefixI 'False) (U1 :: Type -> Type))

data Cmd :: Type -> Type where Source #

Protocol operations

Constructors

Cmd_Int :: Int8 -> Cmd Int8 
Cmd_Bool :: Bool -> Cmd Bool 

Instances

Instances details
TestEquality Cmd Source # 
Instance details

Defined in Data.Serializer.Example

Methods

testEquality :: forall (a :: k) (b :: k). Cmd a -> Cmd b -> Maybe (a :~: b) #

GShow Cmd Source # 
Instance details

Defined in Data.Serializer.Example

Methods

gshowsPrec :: forall (a :: k). Int -> Cmd a -> ShowS #

Show (Cmd a) Source # 
Instance details

Defined in Data.Serializer.Example

Methods

showsPrec :: Int -> Cmd a -> ShowS #

show :: Cmd a -> String #

showList :: [Cmd a] -> ShowS #

Eq (Cmd a) Source # 
Instance details

Defined in Data.Serializer.Example

Methods

(==) :: Cmd a -> Cmd a -> Bool #

(/=) :: Cmd a -> Cmd a -> Bool #

Arbitrary (Some Cmd) Source # 
Instance details

Defined in Data.Serializer.Example

Methods

arbitrary :: Gen (Some Cmd) #

shrink :: Some Cmd -> [Some Cmd] #

Eq (Some Cmd) Source # 
Instance details

Defined in Data.Serializer.Example

Methods

(==) :: Some Cmd -> Some Cmd -> Bool #

(/=) :: Some Cmd -> Some Cmd -> Bool #

Cmd Serializer

cmdS :: forall t. (MonadTrans t, Monad (t Get), Monad (t PutM)) => Serializer t (Some Cmd) Source #

Cmd Serializer

Runners

runG :: Serializer (ExceptT e) a -> ByteString -> Either (GetSerializerError e) a Source #

runGetS specialized to ExceptT e

runP :: Serializer (ExceptT e) a -> a -> Either e ByteString Source #

runPutS specialized to ExceptT e

Custom errors

data MyGetError Source #

Constructors

MyGetError_Example 

Instances

Instances details
Show MyGetError Source # 
Instance details

Defined in Data.Serializer.Example

Eq MyGetError Source # 
Instance details

Defined in Data.Serializer.Example

data MyPutError Source #

Instances

Instances details
Show MyPutError Source # 
Instance details

Defined in Data.Serializer.Example

Eq MyPutError Source # 
Instance details

Defined in Data.Serializer.Example

Erroring variants of cmdS

putS with throwError and MyPutError

getS with throwError and MyGetError

getS with fail

putS with fail

cmdSPutFail :: (MonadTrans t, MonadFail (t PutM), Monad (t Get)) => Serializer t (Some Cmd) Source #

Unused as PutM doesn't have MonadFail >>> serializerPutFail = cmdPutFail @(ExceptT MyGetError) No instance for (MonadFail PutM) as expected

Elaborate

runGRest :: Serializer (REST r e s) a -> r -> s -> ByteString -> Either (GetSerializerError e) a Source #

runPRest :: Serializer (REST r e s) a -> r -> s -> a -> Either e ByteString Source #