module Avers.API.Types where
import GHC.Generics
import Data.ByteString (ByteString)
import Data.ByteString.Lazy (toStrict, fromStrict)
import Data.Text (Text)
import Data.Aeson as A
import Data.Vector as V
import Data.Time
import Avers
import Servant.API (MimeRender(..), MimeUnrender(..), OctetStream)
data CreateObjectBody = CreateObjectBody
{ cobType :: !Text
, cobContent :: !Value
} deriving (Generic)
instance FromJSON CreateObjectBody where
parseJSON (A.Object o) = CreateObjectBody <$> o .: "type" <*> o .: "content"
parseJSON _ = fail "CreateObjectBody"
data CreateObjectResponse = CreateObjectResponse
{ corId :: !ObjId
, corType :: !Text
, corContent :: !Value
} deriving (Generic)
instance ToJSON CreateObjectResponse where
toJSON x = object
[ "id" .= corId x
, "type" .= corType x
, "content" .= corContent x
]
data LookupObjectResponse = LookupObjectResponse
{ lorId :: !ObjId
, lorType :: !Text
, lorCreatedAt :: !UTCTime
, lorCreatedBy :: !ObjId
, lorRevisionId :: !RevId
, lorContent :: !Value
} deriving (Generic)
instance ToJSON LookupObjectResponse where
toJSON x = object
[ "id" .= lorId x
, "type" .= lorType x
, "createdAt" .= lorCreatedAt x
, "createdBy" .= lorCreatedBy x
, "revisionId" .= lorRevisionId x
, "content" .= lorContent x
]
data PatchObjectBody = PatchObjectBody
{ pobRevisionId :: !RevId
, pobOperations :: ![Operation]
} deriving (Generic)
instance FromJSON PatchObjectBody where
parseJSON (A.Object o) = PatchObjectBody <$> o .: "revisionId" <*> o .: "operations"
parseJSON _ = fail "PatchObjectBody"
data PatchObjectResponse = PatchObjectResponse
{ porPreviousPatches :: ![Patch]
, porNumProcessedOperations :: !Int
, porResultingPatches :: ![Patch]
} deriving (Generic)
instance ToJSON PatchObjectResponse where
toJSON x = object
[ "previousPatches" .= porPreviousPatches x
, "numProcessedOperations" .= porNumProcessedOperations x
, "resultingPatches" .= porResultingPatches x
]
data ObjectChangeNotification
= PatchNotification !Patch
deriving (Generic)
instance ToJSON ObjectChangeNotification where
toJSON (PatchNotification p) = object [ "type" .= ("patch" :: Text), "content" .= p ]
type LookupPatchResponse = Patch
data CreateReleaseBody = CreateReleaseBody
{
} deriving (Generic)
instance FromJSON CreateReleaseBody where
parseJSON = undefined
data CreateReleaseResponse = CreateReleaseResponse
{
} deriving (Generic)
instance ToJSON CreateReleaseResponse where
toJSON = undefined
data LookupReleaseResponse = LookupReleaseResponse
{
} deriving (Generic)
instance ToJSON LookupReleaseResponse where
toJSON = undefined
data LookupLatestReleaseResponse = LookupLatestReleaseResponse
{
} deriving (Generic)
instance ToJSON LookupLatestReleaseResponse where
toJSON = undefined
data CreateSessionBody = CreateSessionBody
{ csbLogin :: !SecretId
, csbSecret :: !Text
} deriving (Generic)
instance FromJSON CreateSessionBody where
parseJSON (A.Object o) = CreateSessionBody <$> o .: "login" <*> o .: "secret"
parseJSON _ = fail "CreateSessionBody"
data CreateSessionResponse = CreateSessionResponse
{ csrSessionId :: !SessionId
, csrSessionObjId :: !ObjId
} deriving (Generic)
instance ToJSON CreateSessionResponse where
toJSON x = object
[ "id" .= csrSessionId x
, "objId" .= csrSessionObjId x
]
data LookupSessionResponse = LookupSessionResponse
{ lsrSessionId :: !SessionId
, lsrSessionObjId :: !ObjId
} deriving (Generic)
instance ToJSON LookupSessionResponse where
toJSON x = object
[ "id" .= lsrSessionId x
, "objId" .= lsrSessionObjId x
]
data ChangeFeedSubscription
= IncludeObjectChanges ObjId
instance FromJSON ChangeFeedSubscription where
parseJSON (Array a) = case V.toList a of
["+", objId] -> IncludeObjectChanges <$> parseJSON objId
_ -> fail "ChangeFeedSubscription"
parseJSON _ = fail "ChangeFeedSubscription"
data ChangeSecretBody = ChangeSecretBody
{ csbNewSecret :: !Text
} deriving (Generic)
instance FromJSON ChangeSecretBody where
parseJSON (A.Object o) = ChangeSecretBody <$> o .: "secret"
parseJSON _ = fail "ChangeSecretBody"
newtype BlobContent = BlobContent ByteString
instance MimeUnrender OctetStream BlobContent where
mimeUnrender _ bs = Right (BlobContent $ toStrict bs)
instance MimeRender OctetStream BlobContent where
mimeRender _ (BlobContent bs) = fromStrict bs
data UploadBlobResponse = UploadBlobResponse
{ ubrId :: !BlobId
, ubrSize :: !Int
, ubrContentType :: !Text
} deriving (Generic)
instance ToJSON UploadBlobResponse where
toJSON x = object
[ "id" .= ubrId x
, "size" .= ubrSize x
, "contentType" .= ubrContentType x
]
data LookupBlobResponse = LookupBlobResponse
{ lbrId :: !BlobId
, lbrSize :: !Int
, lbrContentType :: !Text
} deriving (Generic)
instance ToJSON LookupBlobResponse where
toJSON x = object
[ "id" .= lbrId x
, "size" .= lbrSize x
, "contentType" .= lbrContentType x
]