{-# LANGUAGE DataKinds #-} {-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE DeriveTraversable #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE RecordWildCards #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE ViewPatterns #-} {-# OPTIONS_GHC -fno-warn-unused-binds -fno-warn-unused-imports -freduction-depth=328 #-} module OryKratos.API ( -- * Client and Server Config (..), OryKratosBackend (..), createOryKratosClient, runOryKratosServer, runOryKratosMiddlewareServer, runOryKratosClient, runOryKratosClientWithManager, callOryKratos, OryKratosClient, OryKratosClientError (..), -- ** Servant OryKratosAPI, -- ** Plain WAI Application serverWaiApplicationOryKratos, ) where import Control.Monad.Catch (Exception, MonadThrow, throwM) import Control.Monad.Except (ExceptT, runExceptT) import Control.Monad.IO.Class import Control.Monad.Trans.Reader (ReaderT (..)) import Data.Aeson (FromJSON, ToJSON, Value) import Data.Coerce (coerce) import Data.Data (Data) import Data.Function ((&)) import qualified Data.Map as Map import Data.Monoid ((<>)) import Data.Proxy (Proxy (..)) import Data.Set (Set) import Data.Text (Text) import qualified Data.Text as T import Data.Time import Data.UUID (UUID) import GHC.Exts (IsString (..)) import GHC.Generics (Generic) import Network.HTTP.Client (Manager, newManager) import Network.HTTP.Client.TLS (tlsManagerSettings) import Network.HTTP.Types.Method (methodOptions) import Network.Wai (Middleware) import qualified Network.Wai.Handler.Warp as Warp import OryKratos.Types import Servant (ServerError, serve) import Servant.API import Servant.API.Verbs (StdMethod (..), Verb) import Servant.Client ( ClientEnv, ClientError, Scheme (Http), client, mkClientEnv, parseBaseUrl, ) import Servant.Client.Core (baseUrlHost, baseUrlPort) import Servant.Client.Internal.HttpClient (ClientM (..)) import Servant.Server (Application, Handler (..)) import Servant.Server.StaticFiles (serveDirectoryFileServer) import Web.FormUrlEncoded import Web.HttpApiData -- | List of elements parsed from a query. newtype QueryList (p :: CollectionFormat) a = QueryList { fromQueryList :: [a] } deriving stock (Traversable) deriving newtype (Functor, Applicative, Monad, Foldable) -- | Formats in which a list can be encoded into a HTTP path. data CollectionFormat = -- | CSV format for multiple parameters. CommaSeparated | -- | Also called "SSV" SpaceSeparated | -- | Also called "TSV" TabSeparated | -- | `value1|value2|value2` PipeSeparated | -- | Using multiple GET parameters, e.g. `foo=bar&foo=baz`. Only for GET params. MultiParamArray instance FromHttpApiData a => FromHttpApiData (QueryList 'CommaSeparated a) where parseQueryParam = parseSeparatedQueryList ',' instance FromHttpApiData a => FromHttpApiData (QueryList 'TabSeparated a) where parseQueryParam = parseSeparatedQueryList '\t' instance FromHttpApiData a => FromHttpApiData (QueryList 'SpaceSeparated a) where parseQueryParam = parseSeparatedQueryList ' ' instance FromHttpApiData a => FromHttpApiData (QueryList 'PipeSeparated a) where parseQueryParam = parseSeparatedQueryList '|' instance FromHttpApiData a => FromHttpApiData (QueryList 'MultiParamArray a) where parseQueryParam = Prelude.error "unimplemented FromHttpApiData for MultiParamArray collection format" parseSeparatedQueryList :: FromHttpApiData a => Char -> Text -> Either Text (QueryList p a) parseSeparatedQueryList char = fmap QueryList . mapM parseQueryParam . T.split (== char) instance ToHttpApiData a => ToHttpApiData (QueryList 'CommaSeparated a) where toQueryParam = formatSeparatedQueryList ',' instance ToHttpApiData a => ToHttpApiData (QueryList 'TabSeparated a) where toQueryParam = formatSeparatedQueryList '\t' instance ToHttpApiData a => ToHttpApiData (QueryList 'SpaceSeparated a) where toQueryParam = formatSeparatedQueryList ' ' instance ToHttpApiData a => ToHttpApiData (QueryList 'PipeSeparated a) where toQueryParam = formatSeparatedQueryList '|' instance ToHttpApiData a => ToHttpApiData (QueryList 'MultiParamArray a) where toQueryParam = Prelude.error "unimplemented ToHttpApiData for MultiParamArray collection format" formatSeparatedQueryList :: ToHttpApiData a => Char -> QueryList p a -> Text formatSeparatedQueryList char = T.intercalate (T.singleton char) . map toQueryParam . fromQueryList -- | Servant type-level API, generated from the OpenAPI spec for OryKratos. type OryKratosAPI traits metadataAdmin metadataPublic = "version" :> Verb 'GET 200 '[JSON] GetVersion200Response -- 'getVersion' route :<|> "health" :> "alive" :> Verb 'GET 200 '[JSON] IsAlive200Response -- 'isAlive' route :<|> "health" :> "ready" :> Verb 'GET 200 '[JSON] IsAlive200Response -- 'isReady' route :<|> "admin" :> "identities" :> ReqBody '[JSON] AdminCreateIdentityBody :> Verb 'POST 200 '[JSON] (Identity traits metadataAdmin metadataPublic) -- 'adminCreateIdentity' route :<|> "admin" :> "recovery" :> "link" :> ReqBody '[JSON] AdminCreateSelfServiceRecoveryLinkBody :> Verb 'POST 200 '[JSON] SelfServiceRecoveryLink -- 'adminCreateSelfServiceRecoveryLink' route :<|> "admin" :> "identities" :> Capture "id" Text :> Verb 'DELETE 200 '[JSON] NoContent -- 'adminDeleteIdentity' route :<|> "admin" :> "identities" :> Capture "id" Text :> "sessions" :> Verb 'DELETE 200 '[JSON] NoContent -- 'adminDeleteIdentitySessions' route :<|> "admin" :> "sessions" :> Capture "id" Text :> "extend" :> Verb 'PATCH 200 '[JSON] (Session traits metadataAdmin metadataPublic) -- 'adminExtendSession' route :<|> "admin" :> "identities" :> Capture "id" Text :> QueryParam "include_credential" (QueryList 'MultiParamArray (Text)) :> Verb 'GET 200 '[JSON] (Identity traits metadataAdmin metadataPublic) -- 'adminGetIdentity' route :<|> "admin" :> "identities" :> QueryParam "per_page" Integer :> QueryParam "page" Integer :> Verb 'GET 200 '[JSON] [(Identity traits metadataAdmin metadataPublic)] -- 'adminListIdentities' route :<|> "admin" :> "identities" :> Capture "id" Text :> "sessions" :> QueryParam "per_page" Integer :> QueryParam "page" Integer :> QueryParam "active" Bool :> Verb 'GET 200 '[JSON] [(Session traits metadataAdmin metadataPublic)] -- 'adminListIdentitySessions' route :<|> "admin" :> "identities" :> Capture "id" Text :> ReqBody '[JSON] AdminUpdateIdentityBody :> Verb 'PUT 200 '[JSON] (Identity traits metadataAdmin metadataPublic) -- 'adminUpdateIdentity' route :<|> "self-service" :> "logout" :> "browser" :> Header "cookie" Text :> Verb 'GET 200 '[JSON] SelfServiceLogoutUrl -- 'createSelfServiceLogoutFlowUrlForBrowsers' route :<|> "schemas" :> Capture "id" Text :> Verb 'GET 200 '[JSON] Value -- 'getJsonSchema' route :<|> "self-service" :> "errors" :> QueryParam "id" Text :> Verb 'GET 200 '[JSON] SelfServiceError -- 'getSelfServiceError' route :<|> "self-service" :> "login" :> "flows" :> QueryParam "id" Text :> Header "Cookie" Text :> Verb 'GET 200 '[JSON] SelfServiceLoginFlow -- 'getSelfServiceLoginFlow' route :<|> "self-service" :> "recovery" :> "flows" :> QueryParam "id" Text :> Header "Cookie" Text :> Verb 'GET 200 '[JSON] SelfServiceRecoveryFlow -- 'getSelfServiceRecoveryFlow' route :<|> "self-service" :> "registration" :> "flows" :> QueryParam "id" Text :> Header "Cookie" Text :> Verb 'GET 200 '[JSON] SelfServiceRegistrationFlow -- 'getSelfServiceRegistrationFlow' route :<|> "self-service" :> "settings" :> "flows" :> QueryParam "id" Text :> Header "X-Session-Token" Text :> Header "Cookie" Text :> Verb 'GET 200 '[JSON] (SelfServiceSettingsFlow traits metadataAdmin metadataPublic) -- 'getSelfServiceSettingsFlow' route :<|> "self-service" :> "verification" :> "flows" :> QueryParam "id" Text :> Header "cookie" Text :> Verb 'GET 200 '[JSON] SelfServiceVerificationFlow -- 'getSelfServiceVerificationFlow' route :<|> ".well-known" :> "ory" :> "webauthn.js" :> Verb 'GET 200 '[JSON] Text -- 'getWebAuthnJavaScript' route :<|> "self-service" :> "login" :> "browser" :> QueryParam "refresh" Bool :> QueryParam "aal" Text :> QueryParam "return_to" Text :> Verb 'GET 200 '[JSON] SelfServiceLoginFlow -- 'initializeSelfServiceLoginFlowForBrowsers' route :<|> "self-service" :> "login" :> "api" :> QueryParam "refresh" Bool :> QueryParam "aal" Text :> Header "X-Session-Token" Text :> Verb 'GET 200 '[JSON] SelfServiceLoginFlow -- 'initializeSelfServiceLoginFlowWithoutBrowser' route :<|> "self-service" :> "recovery" :> "browser" :> QueryParam "return_to" Text :> Verb 'GET 200 '[JSON] SelfServiceRecoveryFlow -- 'initializeSelfServiceRecoveryFlowForBrowsers' route :<|> "self-service" :> "recovery" :> "api" :> Verb 'GET 200 '[JSON] SelfServiceRecoveryFlow -- 'initializeSelfServiceRecoveryFlowWithoutBrowser' route :<|> "self-service" :> "registration" :> "browser" :> QueryParam "return_to" Text :> Verb 'GET 200 '[JSON] SelfServiceRegistrationFlow -- 'initializeSelfServiceRegistrationFlowForBrowsers' route :<|> "self-service" :> "registration" :> "api" :> Verb 'GET 200 '[JSON] SelfServiceRegistrationFlow -- 'initializeSelfServiceRegistrationFlowWithoutBrowser' route :<|> "self-service" :> "settings" :> "browser" :> QueryParam "return_to" Text :> Verb 'GET 200 '[JSON] (SelfServiceSettingsFlow traits metadataAdmin metadataPublic) -- 'initializeSelfServiceSettingsFlowForBrowsers' route :<|> "self-service" :> "settings" :> "api" :> Header "X-Session-Token" Text :> Verb 'GET 200 '[JSON] (SelfServiceSettingsFlow traits metadataAdmin metadataPublic) -- 'initializeSelfServiceSettingsFlowWithoutBrowser' route :<|> "self-service" :> "verification" :> "browser" :> QueryParam "return_to" Text :> Verb 'GET 200 '[JSON] SelfServiceVerificationFlow -- 'initializeSelfServiceVerificationFlowForBrowsers' route :<|> "self-service" :> "verification" :> "api" :> Verb 'GET 200 '[JSON] SelfServiceVerificationFlow -- 'initializeSelfServiceVerificationFlowWithoutBrowser' route :<|> "schemas" :> QueryParam "per_page" Integer :> QueryParam "page" Integer :> Verb 'GET 200 '[JSON] [IdentitySchema] -- 'listIdentitySchemas' route :<|> "sessions" :> QueryParam "per_page" Integer :> QueryParam "page" Integer :> Header "X-Session-Token" Text :> Header "Cookie" Text :> Verb 'GET 200 '[JSON] [(Session traits metadataAdmin metadataPublic)] -- 'listSessions' route :<|> "sessions" :> Capture "id" Text :> Verb 'DELETE 200 '[JSON] NoContent -- 'revokeSession' route :<|> "sessions" :> Header "X-Session-Token" Text :> Header "Cookie" Text :> Verb 'DELETE 200 '[JSON] RevokedSessions -- 'revokeSessions' route :<|> "self-service" :> "login" :> QueryParam "flow" Text :> ReqBody '[JSON] SubmitSelfServiceLoginFlowBody :> Header "X-Session-Token" Text :> Header "Cookie" Text :> Verb 'POST 200 '[JSON] (SuccessfulSelfServiceLoginWithoutBrowser traits metadataAdmin metadataPublic) -- 'submitSelfServiceLoginFlow' route :<|> "self-service" :> "logout" :> QueryParam "token" Text :> QueryParam "return_to" Text :> Verb 'GET 200 '[JSON] NoContent -- 'submitSelfServiceLogoutFlow' route :<|> "self-service" :> "logout" :> "api" :> ReqBody '[JSON] SubmitSelfServiceLogoutFlowWithoutBrowserBody :> Verb 'DELETE 200 '[JSON] NoContent -- 'submitSelfServiceLogoutFlowWithoutBrowser' route :<|> "self-service" :> "recovery" :> QueryParam "flow" Text :> QueryParam "token" Text :> ReqBody '[JSON] SubmitSelfServiceRecoveryFlowBody :> Header "Cookie" Text :> Verb 'POST 200 '[JSON] SelfServiceRecoveryFlow -- 'submitSelfServiceRecoveryFlow' route :<|> "self-service" :> "registration" :> QueryParam "flow" Text :> ReqBody '[JSON] SubmitSelfServiceRegistrationFlowBody :> Header "Cookie" Text :> Verb 'POST 200 '[JSON] (SuccessfulSelfServiceRegistrationWithoutBrowser traits metadataAdmin metadataPublic) -- 'submitSelfServiceRegistrationFlow' route :<|> "self-service" :> "settings" :> QueryParam "flow" Text :> ReqBody '[JSON] SubmitSelfServiceSettingsFlowBody :> Header "X-Session-Token" Text :> Header "Cookie" Text :> Verb 'POST 200 '[JSON] (SelfServiceSettingsFlow traits metadataAdmin metadataPublic) -- 'submitSelfServiceSettingsFlow' route :<|> "self-service" :> "verification" :> QueryParam "flow" Text :> QueryParam "token" Text :> ReqBody '[JSON] SubmitSelfServiceVerificationFlowBody :> Header "Cookie" Text :> Verb 'POST 200 '[JSON] SelfServiceVerificationFlow -- 'submitSelfServiceVerificationFlow' route :<|> "sessions" :> "whoami" :> Header "X-Session-Token" Text :> Header "Cookie" Text :> Verb 'GET 200 '[JSON] (Session traits metadataAdmin metadataPublic) -- 'toSession' route :<|> Raw -- | Server or client configuration, specifying the host and port to query or serve on. data Config = Config { -- | scheme://hostname:port/path, e.g. "http://localhost:8080/" configUrl :: String } deriving stock (Eq, Ord, Show, Read) -- | Custom exception type for our Prelude.errors. newtype OryKratosClientError = OryKratosClientError ClientError deriving newtype (Show, Exception) -- | Configuration, specifying the full url of the service. -- | Backend for OryKratos. -- The backend can be used both for the client and the server. The client generated from the OryKratos OpenAPI spec -- is a backend that executes actions by sending HTTP requests (see @createOryKratosClient@). Alternatively, provided -- a backend, the API can be served using @runOryKratosMiddlewareServer@. data OryKratosBackend m traits metadataAdmin metadataPublic = OryKratosBackend { -- | This endpoint returns the version of Ory Kratos. If the service supports TLS Edge Termination, this endpoint does not require the `X-Forwarded-Proto` header to be set. Be aware that if you are running multiple nodes of this service, the version will never refer to the cluster state, only to a single instance. getVersion :: m GetVersion200Response, -- | This endpoint returns a HTTP 200 status code when Ory Kratos is accepting incoming HTTP requests. This status does currently not include checks whether the database connection is working. If the service supports TLS Edge Termination, this endpoint does not require the `X-Forwarded-Proto` header to be set. Be aware that if you are running multiple nodes of this service, the health status will never refer to the cluster state, only to a single instance. isAlive :: m IsAlive200Response, -- | This endpoint returns a HTTP 200 status code when Ory Kratos is up running and the environment dependencies (e.g. the database) are responsive as well. If the service supports TLS Edge Termination, this endpoint does not require the `X-Forwarded-Proto` header to be set. Be aware that if you are running multiple nodes of Ory Kratos, the health status will never refer to the cluster state, only to a single instance. isReady :: m IsAlive200Response, -- | This endpoint creates an identity. Learn how identities work in [Ory Kratos' User And Identity Model Documentation](https://www.ory.sh/docs/next/kratos/concepts/identity-user-model). adminCreateIdentity :: AdminCreateIdentityBody -> m (Identity traits metadataAdmin metadataPublic), -- | This endpoint creates a recovery link which should be given to the user in order for them to recover (or activate) their account. adminCreateSelfServiceRecoveryLink :: AdminCreateSelfServiceRecoveryLinkBody -> m SelfServiceRecoveryLink, -- | Calling this endpoint irrecoverably and permanently deletes the identity given its ID. This action can not be undone. This endpoint returns 204 when the identity was deleted or when the identity was not found, in which case it is assumed that is has been deleted already. Learn how identities work in [Ory Kratos' User And Identity Model Documentation](https://www.ory.sh/docs/next/kratos/concepts/identity-user-model). adminDeleteIdentity :: Text -> m NoContent, -- | This endpoint is useful for: To forcefully logout Identity from all devices and sessions adminDeleteIdentitySessions :: Text -> m NoContent, -- | Retrieve the session ID from the `/sessions/whoami` endpoint / `toSession` SDK method. adminExtendSession :: Text -> m (Session traits metadataAdmin metadataPublic), -- | Learn how identities work in [Ory Kratos' User And Identity Model Documentation](https://www.ory.sh/docs/next/kratos/concepts/identity-user-model). adminGetIdentity :: Text -> Maybe [Text] -> m (Identity traits metadataAdmin metadataPublic), -- | Lists all identities. Does not support search at the moment. Learn how identities work in [Ory Kratos' User And Identity Model Documentation](https://www.ory.sh/docs/next/kratos/concepts/identity-user-model). adminListIdentities :: Maybe Integer -> Maybe Integer -> m [(Identity traits metadataAdmin metadataPublic)], -- | This endpoint is useful for: Listing all sessions that belong to an Identity in an administrative context. adminListIdentitySessions :: Text -> Maybe Integer -> Maybe Integer -> Maybe Bool -> m [(Session traits metadataAdmin metadataPublic)], -- | This endpoint updates an identity. The full identity payload (except credentials) is expected. This endpoint does not support patching. Learn how identities work in [Ory Kratos' User And Identity Model Documentation](https://www.ory.sh/docs/next/kratos/concepts/identity-user-model). adminUpdateIdentity :: Text -> AdminUpdateIdentityBody -> m (Identity traits metadataAdmin metadataPublic), -- | This endpoint initializes a browser-based user logout flow and a URL which can be used to log out the user. This endpoint is NOT INTENDED for API clients and only works with browsers (Chrome, Firefox, ...). For API clients you can call the `/self-service/logout/api` URL directly with the Ory Session Token. The URL is only valid for the currently signed in user. If no user is signed in, this endpoint returns a 401 Prelude.error. When calling this endpoint from a backend, please ensure to properly forward the HTTP cookies. createSelfServiceLogoutFlowUrlForBrowsers :: Maybe Text -> m SelfServiceLogoutUrl, -- | Get a JSON Schema getJsonSchema :: Text -> m Value, -- | This endpoint returns the Prelude.error associated with a user-facing self service Prelude.errors. This endpoint supports stub values to help you implement the Prelude.error UI: `?id=stub:500` - returns a stub 500 (Internal Server Error) Prelude.error. More information can be found at [Ory Kratos User User Facing Error Documentation](https://www.ory.sh/docs/kratos/self-service/flows/user-facing-errors). getSelfServiceError :: Maybe Text -> m SelfServiceError, -- | This endpoint returns a login flow's context with, for example, Prelude.error details and other information. Browser flows expect the anti-CSRF cookie to be included in the request's HTTP Cookie Header. For AJAX requests you must ensure that cookies are included in the request or requests will fail. If you use the browser-flow for server-side apps, the services need to run on a common top-level-domain and you need to forward the incoming HTTP Cookie header to this endpoint: ```js pseudo-code example router.get('/login', async function (req, res) { const flow = await client.getSelfServiceLoginFlow(req.header('cookie'), req.query['flow']) res.render('login', flow) }) ``` This request may fail due to several reasons. The `error.id` can be one of: `session_already_available`: The user is already signed in. `self_service_flow_expired`: The flow is expired and you should request a new one. More information can be found at [Ory Kratos User Login](https://www.ory.sh/docs/kratos/self-service/flows/user-login) and [User Registration Documentation](https://www.ory.sh/docs/kratos/self-service/flows/user-registration). getSelfServiceLoginFlow :: Maybe Text -> Maybe Text -> m SelfServiceLoginFlow, -- | This endpoint returns a recovery flow's context with, for example, Prelude.error details and other information. Browser flows expect the anti-CSRF cookie to be included in the request's HTTP Cookie Header. For AJAX requests you must ensure that cookies are included in the request or requests will fail. If you use the browser-flow for server-side apps, the services need to run on a common top-level-domain and you need to forward the incoming HTTP Cookie header to this endpoint: ```js pseudo-code example router.get('/recovery', async function (req, res) { const flow = await client.getSelfServiceRecoveryFlow(req.header('Cookie'), req.query['flow']) res.render('recovery', flow) }) ``` More information can be found at [Ory Kratos Account Recovery Documentation](../self-service/flows/account-recovery). getSelfServiceRecoveryFlow :: Maybe Text -> Maybe Text -> m SelfServiceRecoveryFlow, -- | This endpoint returns a registration flow's context with, for example, Prelude.error details and other information. Browser flows expect the anti-CSRF cookie to be included in the request's HTTP Cookie Header. For AJAX requests you must ensure that cookies are included in the request or requests will fail. If you use the browser-flow for server-side apps, the services need to run on a common top-level-domain and you need to forward the incoming HTTP Cookie header to this endpoint: ```js pseudo-code example router.get('/registration', async function (req, res) { const flow = await client.getSelfServiceRegistrationFlow(req.header('cookie'), req.query['flow']) res.render('registration', flow) }) ``` This request may fail due to several reasons. The `error.id` can be one of: `session_already_available`: The user is already signed in. `self_service_flow_expired`: The flow is expired and you should request a new one. More information can be found at [Ory Kratos User Login](https://www.ory.sh/docs/kratos/self-service/flows/user-login) and [User Registration Documentation](https://www.ory.sh/docs/kratos/self-service/flows/user-registration). getSelfServiceRegistrationFlow :: Maybe Text -> Maybe Text -> m SelfServiceRegistrationFlow, -- | When accessing this endpoint through Ory Kratos' Public API you must ensure that either the Ory Kratos Session Cookie or the Ory Kratos Session Token are set. Depending on your configuration this endpoint might return a 403 Prelude.error if the session has a lower Authenticator Assurance Level (AAL) than is possible for the identity. This can happen if the identity has password + webauthn credentials (which would result in AAL2) but the session has only AAL1. If this Prelude.error occurs, ask the user to sign in with the second factor or change the configuration. You can access this endpoint without credentials when using Ory Kratos' Admin API. If this endpoint is called via an AJAX request, the response contains the flow without a redirect. In the case of an Prelude.error, the `error.id` of the JSON response body can be one of: `security_csrf_violation`: Unable to fetch the flow because a CSRF violation occurred. `session_inactive`: No Ory Session was found - sign in a user first. `security_identity_mismatch`: The flow was interrupted with `session_refresh_required` but apparently some other identity logged in instead. More information can be found at [Ory Kratos User Settings & Profile Management Documentation](../self-service/flows/user-settings). getSelfServiceSettingsFlow :: Maybe Text -> Maybe Text -> Maybe Text -> m (SelfServiceSettingsFlow traits metadataAdmin metadataPublic), -- | This endpoint returns a verification flow's context with, for example, Prelude.error details and other information. Browser flows expect the anti-CSRF cookie to be included in the request's HTTP Cookie Header. For AJAX requests you must ensure that cookies are included in the request or requests will fail. If you use the browser-flow for server-side apps, the services need to run on a common top-level-domain and you need to forward the incoming HTTP Cookie header to this endpoint: ```js pseudo-code example router.get('/recovery', async function (req, res) { const flow = await client.getSelfServiceVerificationFlow(req.header('cookie'), req.query['flow']) res.render('verification', flow) }) More information can be found at [Ory Kratos Email and Phone Verification Documentation](https://www.ory.sh/docs/kratos/selfservice/flows/verify-email-account-activation). getSelfServiceVerificationFlow :: Maybe Text -> Maybe Text -> m SelfServiceVerificationFlow, -- | This endpoint provides JavaScript which is needed in order to perform WebAuthn login and registration. If you are building a JavaScript Browser App (e.g. in ReactJS or AngularJS) you will need to load this file: ```html