{-# LANGUAGE DataKinds #-}

module Hercules.API.Auth where

import Hercules.API.Prelude
import Hercules.API.Servant.Status
import Servant.API
import Servant.API.Generic
import Web.Cookie (SetCookie)

-- | Endpoints for authentication
data AuthAPI auth f = AuthAPI
  { forall auth f.
AuthAPI auth f
-> f
   :- ("api"
       :> ("auth"
           :> ("github"
               :> (QueryParam' '[Optional, Strict] "redirect" Text
                   :> Get302 '[PlainText, JSON] '[]))))
initiateGitHubLogin ::
      f :- "api"
        :> "auth"
        :> "github"
        :> QueryParam' '[Optional, Strict] "redirect" Text
        :> Get302 '[PlainText, JSON] '[],
    forall auth f.
AuthAPI auth f
-> f
   :- ("api"
       :> ("auth"
           :> ("sign-out"
               :> (auth
                   :> Post
                        '[JSON]
                        (Headers
                           '[Header "Set-Cookie" SetCookie, Header "Set-Cookie" SetCookie]
                           NoContent)))))
signOut ::
      f :- "api"
        :> "auth"
        :> "sign-out"
        :> auth
        :> Post '[JSON] (Headers '[Header "Set-Cookie" SetCookie, Header "Set-Cookie" SetCookie] NoContent)
  }
  deriving ((forall x. AuthAPI auth f -> Rep (AuthAPI auth f) x)
-> (forall x. Rep (AuthAPI auth f) x -> AuthAPI auth f)
-> Generic (AuthAPI auth f)
forall x. Rep (AuthAPI auth f) x -> AuthAPI auth f
forall x. AuthAPI auth f -> Rep (AuthAPI auth f) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall auth f x. Rep (AuthAPI auth f) x -> AuthAPI auth f
forall auth f x. AuthAPI auth f -> Rep (AuthAPI auth f) x
$cto :: forall auth f x. Rep (AuthAPI auth f) x -> AuthAPI auth f
$cfrom :: forall auth f x. AuthAPI auth f -> Rep (AuthAPI auth f) x
Generic)