-- | Aeson represents
module Freckle.App.Json.Empty
  ( Empty (..)
  ) where

import Freckle.App.Prelude

import Autodocodec (Autodocodec (..), HasCodec (..), HasObjectCodec (..), object)
import Autodocodec.OpenAPI ()
import Data.Aeson (FromJSON, ToJSON)
import Data.OpenApi (ToSchema (..))
import Test.QuickCheck (Arbitrary (..))

-- | A unit value encoded as an empty JSON object
--
-- Useful as the response body of a POST request when the server doesn't
-- need to return anything.
--
-- (One would expect to be able to use () for this, but Aeson encodes unit
-- as an empty list, not as an object.)
data Empty = Empty
  deriving ([Empty] -> Value
[Empty] -> Encoding
Empty -> Value
Empty -> Encoding
(Empty -> Value)
-> (Empty -> Encoding)
-> ([Empty] -> Value)
-> ([Empty] -> Encoding)
-> ToJSON Empty
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: Empty -> Value
toJSON :: Empty -> Value
$ctoEncoding :: Empty -> Encoding
toEncoding :: Empty -> Encoding
$ctoJSONList :: [Empty] -> Value
toJSONList :: [Empty] -> Value
$ctoEncodingList :: [Empty] -> Encoding
toEncodingList :: [Empty] -> Encoding
ToJSON, Value -> Parser [Empty]
Value -> Parser Empty
(Value -> Parser Empty)
-> (Value -> Parser [Empty]) -> FromJSON Empty
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
$cparseJSON :: Value -> Parser Empty
parseJSON :: Value -> Parser Empty
$cparseJSONList :: Value -> Parser [Empty]
parseJSONList :: Value -> Parser [Empty]
FromJSON, Typeable Empty
Typeable Empty
-> (Proxy Empty -> Declare (Definitions Schema) NamedSchema)
-> ToSchema Empty
Proxy Empty -> Declare (Definitions Schema) NamedSchema
forall a.
Typeable a
-> (Proxy a -> Declare (Definitions Schema) NamedSchema)
-> ToSchema a
$cdeclareNamedSchema :: Proxy Empty -> Declare (Definitions Schema) NamedSchema
declareNamedSchema :: Proxy Empty -> Declare (Definitions Schema) NamedSchema
ToSchema) via (Autodocodec Empty)

instance Arbitrary Empty where
  arbitrary :: Gen Empty
arbitrary = Empty -> Gen Empty
forall a. a -> Gen a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Empty
Empty

instance HasCodec Empty where
  codec :: JSONCodec Empty
codec = Text -> ObjectCodec Empty Empty -> JSONCodec Empty
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"Empty" ObjectCodec Empty Empty
forall object. HasObjectCodec object => JSONObjectCodec object
objectCodec

instance HasObjectCodec Empty where
  objectCodec :: ObjectCodec Empty Empty
objectCodec = Empty -> ObjectCodec Empty Empty
forall a. a -> Codec Object Empty a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Empty
Empty

instance Semigroup Empty where
  Empty
_ <> :: Empty -> Empty -> Empty
<> Empty
_ = Empty
Empty

instance Monoid Empty where
  mempty :: Empty
mempty = Empty
Empty