{-# options_haddock prune #-}
module Polysemy.Http.Effect.Entity where
import Polysemy (makeSem_)
data EntityError =
EntityError {
EntityError -> Text
body :: Text,
EntityError -> Text
message :: Text
}
deriving (EntityError -> EntityError -> Bool
(EntityError -> EntityError -> Bool)
-> (EntityError -> EntityError -> Bool) -> Eq EntityError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EntityError -> EntityError -> Bool
$c/= :: EntityError -> EntityError -> Bool
== :: EntityError -> EntityError -> Bool
$c== :: EntityError -> EntityError -> Bool
Eq, Int -> EntityError -> ShowS
[EntityError] -> ShowS
EntityError -> String
(Int -> EntityError -> ShowS)
-> (EntityError -> String)
-> ([EntityError] -> ShowS)
-> Show EntityError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EntityError] -> ShowS
$cshowList :: [EntityError] -> ShowS
show :: EntityError -> String
$cshow :: EntityError -> String
showsPrec :: Int -> EntityError -> ShowS
$cshowsPrec :: Int -> EntityError -> ShowS
Show)
data EntityEncode d :: Effect where
Encode :: d -> EntityEncode d m LByteString
EncodeStrict :: d -> EntityEncode d m ByteString
makeSem_ ''EntityEncode
encode ::
∀ d r .
Member (EntityEncode d) r =>
d ->
Sem r LByteString
encodeStrict ::
∀ d r .
Member (EntityEncode d) r =>
d ->
Sem r ByteString
data EntityDecode d :: Effect where
Decode :: LByteString -> EntityDecode d m (Either EntityError d)
DecodeStrict :: ByteString -> EntityDecode d m (Either EntityError d)
makeSem_ ''EntityDecode
decode ::
∀ d r .
Member (EntityDecode d) r =>
LByteString ->
Sem r (Either EntityError d)
decodeStrict ::
∀ d r .
Member (EntityDecode d) r =>
ByteString ->
Sem r (Either EntityError d)
data Encode a
data Decode a
type family Entities es r :: Constraint where
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
Encoders '[] r = ()
Encoders (d ': ds) r = (Member (EntityEncode d) r, Encoders ds r)
type family Decoders ds r :: Constraint where
Decoders '[] r = ()
Decoders (d ': ds) r = (Member (EntityDecode d) r, Decoders ds r)