Skip to content

Commit

Permalink
version 0.1.3.9: pass access token to handlers (#28)
Browse files Browse the repository at this point in the history
  • Loading branch information
maksbotan authored Jul 16, 2021
1 parent 87b2905 commit c84776f
Show file tree
Hide file tree
Showing 5 changed files with 31 additions and 7 deletions.
4 changes: 4 additions & 0 deletions CHANGELOG.md
Original file line number Diff line number Diff line change
Expand Up @@ -6,6 +6,10 @@ and this project adheres to [Semantic Versioning](https://semver.org/spec/v2.0.0

## [Unreleased]

## [0.1.3.9] - 2021-07-015
### Changed
- Pass access token to handlers.

## [0.1.3.8] - 2021-06-22
### Added
- Possibility to accept Service Token in `OIDCAuth`. Token is considered a Service Token if it
Expand Down
9 changes: 5 additions & 4 deletions app/ServantApp.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,6 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeOperators #-}

Expand All @@ -12,9 +13,9 @@ import Servant (Description, Get, Handler, JSON, PlainTe
import Servant.OpenApi (toOpenApi)
import Servant.Server.Internal.Context (Context (..))

import Web.Template.Servant (OIDCAuth, OIDCConfig (..), Permit, SwaggerSchemaUI, UserId (..),
Version, defaultOIDCCfg, runServantServerWithContext,
swaggerSchemaUIServer)
import Web.Template.Servant (OIDCAuth, OIDCConfig (..), OIDCUser (OIDCUser, oidcUserId), Permit,
SwaggerSchemaUI, UserId (..), Version, defaultOIDCCfg,
runServantServerWithContext, swaggerSchemaUIServer)
import Web.Template.Wai (defaultHandleLog, defaultHeaderCORS)

type API = Version "1" :>
Expand Down Expand Up @@ -46,7 +47,7 @@ main = do
(defaultHeaderCORS . defaultHandleLog)
5000
(cfg {oidcIssuer = uri, oidcClientId = cId} :. EmptyContext )
$ swaggerSchemaUIServer swagger :<|> (pingH :<|> (\userId -> helloH userId :<|> postH userId))
$ swaggerSchemaUIServer swagger :<|> (pingH :<|> (\OIDCUser{..} -> helloH oidcUserId :<|> postH oidcUserId))
where
uri = error "set uri here"
cId = error "set client id here"
5 changes: 5 additions & 0 deletions src/Web/Template/Servant.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,6 +6,10 @@ module Web.Template.Servant
, SwaggerSchemaUI
, swaggerSchemaUIServer

, userIdVaultKey
, tokenVaultKey
, pTokenVaultKey

, module Web.Template.Servant.Aeson
, module Web.Template.Servant.API
, module Web.Template.Servant.Auth
Expand All @@ -20,6 +24,7 @@ import Servant.Swagger.UI (SwaggerSchemaUI, swaggerSchemaUIServer)
import Servant.Server (Context, DefaultErrorFormatters, ErrorFormatters, HasContextEntry,
HasServer, Server, serveWithContext, type (.++), (.++))

import Web.Template.Log (pTokenVaultKey, tokenVaultKey, userIdVaultKey)
import Web.Template.Types (Port)
import Web.Template.Wai (defaultHandleLog, defaultHeaderCORS, warpSettings)

Expand Down
18 changes: 16 additions & 2 deletions src/Web/Template/Servant/Auth.hs
Original file line number Diff line number Diff line change
Expand Up @@ -9,6 +9,7 @@ module Web.Template.Servant.Auth
, UserId (..)
, OIDCConfig (..)
, defaultOIDCCfg
, OIDCUser (..)
, Permit
) where

Expand Down Expand Up @@ -122,6 +123,15 @@ instance HasOpenApi api => HasOpenApi (CbdAuth :> api) where
-- Stores token and claims in vault.
data OIDCAuth


data OIDCUser
= OIDCUser
{ oidcUserId :: UserId
, oidcAccessToken :: Text
, oidcParsedToken :: ClaimsSet
}
deriving (Eq, Show, Generic)

-- | Info needed for OIDC authorization & key cache
data OIDCConfig
= OIDCConfig
Expand Down Expand Up @@ -160,7 +170,7 @@ instance ( HasServer api context
, HasContextEntry context OIDCConfig
) => HasServer (OIDCAuth :> api) context where

type ServerT (OIDCAuth :> api) m = UserId -> ServerT api m
type ServerT (OIDCAuth :> api) m = OIDCUser -> ServerT api m

hoistServerWithContext _ pc nt s = hoistServerWithContext @api Proxy pc nt . s

Expand Down Expand Up @@ -195,7 +205,11 @@ instance ( HasServer api context
, pTokenVaultKey <?> req <&> flip writeIORef (Just claims)
]

return $ UserId uid
return OIDCUser
{ oidcUserId = UserId uid
, oidcAccessToken = decodeUtf8 token
, oidcParsedToken = claims
}
where
https mgr = (`httpLbs` mgr)

Expand Down
2 changes: 1 addition & 1 deletion web-template.cabal
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
name: web-template
version: 0.1.3.8
version: 0.1.3.9
synopsis: Web template
description:
Web template includes:
Expand Down

0 comments on commit c84776f

Please sign in to comment.