{-# LANGUAGE DataKinds     #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE TypeFamilies  #-}
{-# LANGUAGE TypeOperators #-}

module Avers.API
    ( AversCoreAPI, AversSessionAPI, AversBlobAPI, AversAccountAPI

    , CacheValidationToken, Cacheable

    , module Avers.API.Types
    , module Avers.API.Credentials
    ) where


import Data.Text            (Text)
import Data.ByteString      (ByteString)

import Avers.Types          (ObjId, RevId, BlobId, SessionId)

import Avers.API.Types
import Avers.API.Instances  ()
import Avers.API.Credentials

import Servant.API

import Web.Cookie



--------------------------------------------------------------------------------
-- General structure of endpoint definitions
--
-- The definition of an endpoint would be too much to put on a single line,
-- so it is split into multiple lines according to a fixed schema. Each line
-- represents a particular aspect of the request/response. Lines can be omitted
-- if they don't apply to the endpoint.
--
--  <path> including any captured components
--  <credentials>
--  <cache validation token>
--  <request body>
--  <method and response>



-- | The cache validator token when passed in the request. The server will
-- use it to determine if the cached response on the client can be reused
-- or not.
type CacheValidationToken = Header "If-None-Match" Text


-- | Includes @Cache-Control@ and @ETag@ headers in the response to mark
-- it as cacheable by the client.
type Cacheable a = Headers '[Header "Cache-Control" Text, Header "ETag" Text] a



--------------------------------------------------------------------------------
-- | The Core API to manipulate objects, patches, releases etc.

type AversCoreAPI

  ------------------------------------------------------------------------------
  -- CreateObject
  = "objects"
    :> Credentials
    :> ReqBody '[JSON] CreateObjectBody
    :> Post '[JSON] CreateObjectResponse

  ------------------------------------------------------------------------------
  -- LookupObject
  :<|> "objects" :> Capture "objId" ObjId
    :> Credentials
    :> CacheValidationToken
    :> Get '[JSON] (Cacheable LookupObjectResponse)

  ------------------------------------------------------------------------------
  -- PatchObject
  :<|> "objects" :> Capture "objId" ObjId
    :> Credentials
    :> ReqBody '[JSON] PatchObjectBody
    :> Patch '[JSON] PatchObjectResponse

  ------------------------------------------------------------------------------
  -- DeleteObject
  :<|> "objects" :> Capture "objId" ObjId
    :> Credentials
    :> Delete '[JSON] ()

  ------------------------------------------------------------------------------
  -- LookupPatch
  :<|> "objects" :> Capture "objId" ObjId :> "patches" :> Capture "revId" RevId
    :> Credentials
    :> CacheValidationToken
    :> Get '[JSON] (Cacheable LookupPatchResponse)

  ------------------------------------------------------------------------------
  -- ObjectChanges
  :<|> "objects" :> Capture "objId" ObjId :> "changes"
    :> Credentials
    :> Raw -- WebSocket, stream of ObjectChangeNotification

  ------------------------------------------------------------------------------
  -- CreateRelease
  :<|> "objects" :> Capture "objId" ObjId :> "releases"
    :> Credentials
    :> ReqBody '[JSON] CreateReleaseBody
    :> Post '[JSON] CreateReleaseResponse

  ------------------------------------------------------------------------------
  -- LookupRelease
  :<|> "objects" :> Capture "objId" ObjId :> "releases" :> Capture "revId" RevId
    :> Credentials
    :> CacheValidationToken
    :> Get '[JSON] (Cacheable LookupReleaseResponse)

  ------------------------------------------------------------------------------
  -- LookupLatestRelease
  :<|> "objects" :> Capture "objId" ObjId :> "releases" :> "_latest"
    :> Credentials
    :> CacheValidationToken
    :> Get '[JSON] (Cacheable LookupLatestReleaseResponse)

  ------------------------------------------------------------------------------
  -- Feed
  :<|> "feed"
    :> Credentials
    :> Raw -- WebSocket, stream of 'Change' objects

  ------------------------------------------------------------------------------
  -- ChangeSecret
  :<|> "secret"
    :> Credentials
    :> ReqBody '[JSON] ChangeSecretBody
    :> Post '[] ()



--------------------------------------------------------------------------------
-- | API to create and maintain sessions. Also contains API to
-- change the secret, which is part of the session code.

type AversSessionAPI

  ------------------------------------------------------------------------------
  -- CreateSession
  = "session"
    :> ReqBody '[JSON] CreateSessionBody
    :> Post '[JSON] (Headers '[Header "Set-Cookie" SetCookie] CreateSessionResponse)

  ------------------------------------------------------------------------------
  -- LookupSession
  :<|> "session"
    :> SessionId
    :> Get '[JSON] (Headers '[Header "Set-Cookie" SetCookie] LookupSessionResponse)

  ------------------------------------------------------------------------------
  -- DeleteSession
  :<|> "session"
    :> SessionId
    :> Delete '[JSON] (Headers '[Header "Set-Cookie" SetCookie] ())



--------------------------------------------------------------------------------
-- | API to manange blobs

type AversBlobAPI

  ------------------------------------------------------------------------------
  -- UploadBlob
  = "blobs"
    :> Header "Content-Type" Text
    :> ReqBody '[OctetStream] ByteString
    :> Post '[JSON] UploadBlobResponse

  ------------------------------------------------------------------------------
  -- LookupBlob
  :<|> "blobs" :> Capture "blobId" BlobId
    :> Get '[JSON] LookupBlobResponse

  ------------------------------------------------------------------------------
  -- BlobContent
  :<|> "blobs" :> Capture "blobId" BlobId :> "content"
    :> Get '[OctetStream] (Headers '[Header "Content-Type" Text] ByteString)



--------------------------------------
-- | API to manage accounts. These are optional and not really part of
-- Avers, but many applications do have a concept of a user or account,
-- some person which is using the API.

type AversAccountAPI

  ------------------------------------------------------------------------------
  -- Signup.
  --
  -- Similar to CreateObject but no authorization is required. Instead,
  -- a different mechanism is used to ensure that the client is allowed
  -- to execute the action (eg. an captcha).

  = "signup"
    :> ReqBody '[JSON] SignupBody
    :> Post '[JSON] SignupResponse