{-# LANGUAGE DataKinds #-}

module Hercules.API.Auth where

import Hercules.API.Prelude
import Hercules.API.Servant.Status
import Servant.API
import Servant.API.Generic

-- | Endpoints for authentication
data AuthAPI f = AuthAPI
  { AuthAPI 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] '[]
  }
  deriving ((forall x. AuthAPI f -> Rep (AuthAPI f) x)
-> (forall x. Rep (AuthAPI f) x -> AuthAPI f)
-> Generic (AuthAPI f)
forall x. Rep (AuthAPI f) x -> AuthAPI f
forall x. AuthAPI f -> Rep (AuthAPI f) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall f x. Rep (AuthAPI f) x -> AuthAPI f
forall f x. AuthAPI f -> Rep (AuthAPI f) x
$cto :: forall f x. Rep (AuthAPI f) x -> AuthAPI f
$cfrom :: forall f x. AuthAPI f -> Rep (AuthAPI f) x
Generic)