module Servant.Auth.Server
  (
  -- | This package provides implementations for some common authentication
  -- methods. Authentication yields a trustworthy (because generated by the
  -- server) value of an some arbitrary type:
  --
  -- > type MyApi = Protected
  -- >
  -- > type Protected = Auth '[JWT, Cookie] User :> Get '[JSON] UserAccountDetails
  -- >
  -- > server :: Server Protected
  -- > server (Authenticated usr) = ... -- here we know the client really is
  -- >                                  -- who she claims to be
  -- > server _ = throwAll err401
  --
  -- Additional configuration happens via 'Context'.
  --
  -- == Example for Custom Handler
  -- To use a custom 'Servant.Server.Handler' it is necessary to use
  -- 'Servant.Server.hoistServerWithContext' instead of
  -- 'Servant.Server.hoistServer' and specify the 'Context'.
  --
  -- Below is an example of passing 'CookieSettings' and 'JWTSettings' in the
  -- 'Context' to create a specialized function equivalent to
  -- 'Servant.Server.hoistServer' for an API that includes cookie
  -- authentication.
  --
  -- > hoistServerWithAuth
  -- >   :: HasServer api '[CookieSettings, JWTSettings]
  -- >   => Proxy api
  -- >   -> (forall x. m x -> n x)
  -- >   -> ServerT api m
  -- >   -> ServerT api n
  -- > hoistServerWithAuth api =
  -- >   hoistServerWithContext api (Proxy :: Proxy '[CookieSettings, JWTSettings])

  ----------------------------------------------------------------------------
  -- * Auth
  -- | Basic types
    Auth
  , AuthResult(..)
  , AuthCheck(..)

  ----------------------------------------------------------------------------
  -- * JWT
  -- | JSON Web Tokens (JWT) are a compact and secure way of transferring
  -- information between parties. In this library, they are signed by the
  -- server (or by some other party posessing the relevant key), and used to
  -- indicate the bearer's identity or authorization.
  --
  -- Arbitrary information can be encoded - just declare instances for the
  -- 'FromJWT' and 'ToJWT' classes. Don't go overboard though - be aware that
  -- usually you'll be trasmitting this information on each request (and
  -- response!).
  --
  -- Note that, while the tokens are signed, they are not encrypted. Do not put
  -- any information you do not wish the client to know in them!

  -- ** Combinator
  -- | Re-exported from 'servant-auth'
  , JWT

  -- ** Classes
  , FromJWT(..)
  , ToJWT(..)

  -- ** Related types
  , IsMatch(..)

  -- ** Settings
  , JWTSettings(..)
  , defaultJWTSettings

  -- ** Create check
  , jwtAuthCheck


  ----------------------------------------------------------------------------
  -- * Cookie
  -- | Cookies are also a method of identifying and authenticating a user. They
  -- are particular common when the client is a browser

  -- ** Combinator
  -- | Re-exported from 'servant-auth'
  , Cookie

  -- ** Settings
  , CookieSettings(..)
  , XsrfCookieSettings(..)
  , defaultCookieSettings
  , defaultXsrfCookieSettings
  , makeSessionCookie
  , makeSessionCookieBS
  , makeXsrfCookie
  , makeCsrfCookie
  , makeCookie
  , makeCookieBS
  , acceptLogin
  , clearSession


  -- ** Related types
  , IsSecure(..)
  , SameSite(..)
  , AreAuths

  ----------------------------------------------------------------------------
  -- * BasicAuth
  -- ** Combinator
  -- | Re-exported from 'servant-auth'
  , BasicAuth

  -- ** Classes
  , FromBasicAuthData(..)

  -- ** Settings
  , BasicAuthCfg

  -- ** Related types
  , BasicAuthData(..)
  , IsPasswordCorrect(..)

  -- ** Authentication request
  , wwwAuthenticatedErr

  ----------------------------------------------------------------------------
  -- * Utilies
  , ThrowAll(throwAll)
  , generateKey
  , generateSecret
  , fromSecret
  , writeKey
  , readKey
  , makeJWT

  -- ** Re-exports
  , Default(def)
  , SetCookie
  ) where

import Prelude hiding                           (readFile, writeFile)
import Data.ByteString                          (ByteString, writeFile, readFile)
import Data.Default.Class                       (Default (def))
import Servant.Auth
import Servant.Auth.Server.Internal             ()
import Servant.Auth.Server.Internal.BasicAuth
import Servant.Auth.Server.Internal.Class
import Servant.Auth.Server.Internal.ConfigTypes
import Servant.Auth.Server.Internal.Cookie
import Servant.Auth.Server.Internal.JWT
import Servant.Auth.Server.Internal.ThrowAll
import Servant.Auth.Server.Internal.Types

import Crypto.JOSE as Jose
import Servant     (BasicAuthData (..))
import Web.Cookie  (SetCookie)

-- | Generate a key suitable for use with 'defaultConfig'.
generateKey :: IO Jose.JWK
generateKey = Jose.genJWK $ Jose.OctGenParam 256

-- | Generate a bytestring suitable for use with 'fromSecret'.
generateSecret :: MonadRandom m => m ByteString
generateSecret = Jose.getRandomBytes 256

-- | Restores a key from a bytestring.
fromSecret :: ByteString -> Jose.JWK
fromSecret = Jose.fromOctets

-- | Writes a secret to a file. Can for instance be used from the REPL
-- to persist a key to a file, which can then be included with the
-- application. Restore the key using 'readKey'.
writeKey :: FilePath -> IO ()
writeKey fp = writeFile fp =<< generateSecret

-- | Reads a key from a file.
readKey :: FilePath -> IO Jose.JWK
readKey fp = fromSecret <$> readFile fp