polysemy-http-0.4.0.2: Polysemy effect for http-client
Safe HaskellNone
LanguageHaskell2010

Polysemy.Http.Data.Entity

Synopsis

Documentation

data EntityError Source #

Generic error type for decoders.

Constructors

EntityError 

Fields

Instances

Instances details
Eq EntityError Source # 
Instance details

Defined in Polysemy.Http.Data.Entity

Show EntityError Source # 
Instance details

Defined in Polysemy.Http.Data.Entity

data EntityEncode d :: Effect where Source #

Abstraction of json encoding, potentially usable for other content types like xml.

Constructors

Encode :: d -> EntityEncode d m LByteString 
EncodeStrict :: d -> EntityEncode d m ByteString 

Instances

Instances details
type DefiningModule EntityEncode Source # 
Instance details

Defined in Polysemy.Http.Data.Entity

type DefiningModule EntityEncode = "Polysemy.Http.Data.Entity"

encode :: forall d r. Member (EntityEncode d) r => d -> Sem r LByteString Source #

Lazily encode a value of type d to a LByteString

encodeStrict :: forall d r. Member (EntityEncode d) r => d -> Sem r ByteString Source #

Strictly encode a value of type d to a ByteString

data EntityDecode d :: Effect where Source #

Abstraction of json decoding, potentially usable for other content types like xml.

Instances

Instances details
type DefiningModule EntityDecode Source # 
Instance details

Defined in Polysemy.Http.Data.Entity

type DefiningModule EntityDecode = "Polysemy.Http.Data.Entity"

decode :: forall d r. Member (EntityDecode d) r => LByteString -> Sem r (Either EntityError d) Source #

Lazily decode a LByteString to a value of type d

decodeStrict :: forall d r. Member (EntityDecode d) r => ByteString -> Sem r (Either EntityError d) Source #

Strictly decode a ByteString to a value of type d

data Encode a Source #

Marker type to be used with Entities

data Decode a Source #

Marker type to be used with Entities

type family Entities es r :: Constraint where ... Source #

Convenience constraint for requiring multiple entity effects, to be used like Members.

foo :: Entities [Encode Int, Decode Double] r => Sem r ()

Equations

Entities '[] r = () 
Entities (Encode d ': ds) r = (Member (EntityEncode d) r, Entities ds r) 
Entities (Decode d ': ds) r = (Member (EntityDecode d) r, Entities ds r) 

type family Encoders es r :: Constraint where ... Source #

Convenience constraint for requiring multiple encoders.

foo :: Encoders [Int, Double] r => Sem r ()

Equations

Encoders '[] r = () 
Encoders (d ': ds) r = (Member (EntityEncode d) r, Encoders ds r) 

type family Decoders ds r :: Constraint where ... Source #

Convenience constraint for requiring multiple decoders.

foo :: Decoders [Int, Double] r => Sem r ()

Equations

Decoders '[] r = () 
Decoders (d ': ds) r = (Member (EntityDecode d) r, Decoders ds r)