Safe Haskell | None |
---|---|
Language | GHC2021 |
Polysemy.Http.Effect.Entity
Description
Synopsis
- data EntityError = EntityError {}
- data EntityEncode d (a :: Type -> Type) b where
- EncodeLazy :: forall d (a :: Type -> Type). d -> EntityEncode d a ByteString
- EncodeStrict :: forall d (a :: Type -> Type). d -> EntityEncode d a ByteString
- encodeLazy :: forall d (r :: EffectRow). Member (EntityEncode d) r => d -> Sem r LByteString
- encodeStrict :: forall d (r :: EffectRow). Member (EntityEncode d) r => d -> Sem r ByteString
- encode :: forall d (r :: EffectRow). Member (EntityEncode d) r => d -> Sem r ByteString
- data EntityDecode d (a :: Type -> Type) b where
- DecodeLazy :: forall d (a :: Type -> Type). LByteString -> EntityDecode d a (Either EntityError d)
- DecodeStrict :: forall d (a :: Type -> Type). ByteString -> EntityDecode d a (Either EntityError d)
- decodeLazy :: forall d (r :: EffectRow). Member (EntityDecode d) r => LByteString -> Sem r (Either EntityError d)
- decodeStrict :: forall d (r :: EffectRow). Member (EntityDecode d) r => ByteString -> Sem r (Either EntityError d)
- decode :: forall d (r :: EffectRow). Member (EntityDecode d) r => ByteString -> Sem r (Either EntityError d)
- data Encode (a :: k)
- data Decode (a :: k)
- type family Entities (es :: [Type]) (r :: EffectRow) where ...
- type family Encoders (es :: [Type]) (r :: EffectRow) where ...
- type family Decoders (ds :: [Type]) (r :: EffectRow) where ...
Documentation
data EntityError Source #
Generic error type for decoders.
Constructors
EntityError | |
Instances
Show EntityError Source # | |
Defined in Polysemy.Http.Effect.Entity Methods showsPrec :: Int -> EntityError -> ShowS # show :: EntityError -> String # showList :: [EntityError] -> ShowS # | |
Eq EntityError Source # | |
Defined in Polysemy.Http.Effect.Entity |
data EntityEncode d (a :: Type -> Type) b where Source #
Abstraction of json encoding, potentially usable for other content types like xml.
Constructors
EncodeLazy :: forall d (a :: Type -> Type). d -> EntityEncode d a ByteString | |
EncodeStrict :: forall d (a :: Type -> Type). d -> EntityEncode d a ByteString |
encodeLazy :: forall d (r :: EffectRow). Member (EntityEncode d) r => d -> Sem r LByteString Source #
Lazily encode a value of type d
to a LByteString
encodeStrict :: forall d (r :: EffectRow). Member (EntityEncode d) r => d -> Sem r ByteString Source #
Strictly encode a value of type d
to a ByteString
encode :: forall d (r :: EffectRow). Member (EntityEncode d) r => d -> Sem r ByteString Source #
Strictly encode a value of type d
to a ByteString
data EntityDecode d (a :: Type -> Type) b where Source #
Abstraction of json decoding, potentially usable for other content types like xml.
Constructors
DecodeLazy :: forall d (a :: Type -> Type). LByteString -> EntityDecode d a (Either EntityError d) | |
DecodeStrict :: forall d (a :: Type -> Type). ByteString -> EntityDecode d a (Either EntityError d) |
decodeLazy :: forall d (r :: EffectRow). 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 :: EffectRow). Member (EntityDecode d) r => ByteString -> Sem r (Either EntityError d) Source #
Strictly decode a ByteString
to a value of type d
decode :: forall d (r :: EffectRow). Member (EntityDecode d) r => ByteString -> Sem r (Either EntityError d) Source #
Strictly decode a ByteString
to a value of type d
type family Entities (es :: [Type]) (r :: EffectRow) where ... Source #
Convenience constraint for requiring multiple entity effects, to be used like Members
.
foo :: Entities [Encode Int, Decode Double] r => Sem r ()