3

What would the proper way to store an OAuth2 jwk in haskell? The certs i am retrieving are from https://www.googleapis.com/oauth2/v3/certs and I would like to avoid calling out for certs each time i need to verify the signature on a token. The options seem to be MVar, TVar, IORef, or the state monad although i am not quite sure how i would implement the state monad for this.

The basic steps would be the following (running behind a scotty server):

  1. Receive Token from IDP
  2. Decode Jwt with JWk's
  3. If the decode fails due to a bad signature then check the endpoint for new certs and modify the current variable containing the cert

I am using jose-jwt, wreq, and scotty right now and have something that works but i would like to implement the approach that i am asking about rather than my existing approach.

module Main where


import ClassyPrelude
import Web.Scotty as S
import Network.Wreq as W
import Control.Lens as CL
import qualified Data.Text.Lazy as TL
import qualified Network.URI.Encode as URI
import Network.Wai.Middleware.RequestLogger
import Jose.Jwe
import Jose.Jwa
import Jose.Jwk
import Jose.Jwt
import Jose.Jws
import Data.Aeson
import qualified Data.HashMap.Strict as HM 
import qualified Data.Text as T
import qualified Data.List as DL
import qualified Data.ByteString.Base64 as B64

main :: IO ()
main = scotty 8080 $ do
  middleware logStdoutDev
  redirectCallback
  oauthCallback
  oauthGen
  home

home :: ScottyM ()
home = do
  S.get "/:word" $ do
    beam <- S.param "word"
    html $ mconcat ["<h1>Scotty, ", beam, " me up!</h1>"]

redirectCallback :: ScottyM ()
redirectCallback = do
  S.get "/redirect" $ do
    let v = uriSchemeBuilder
    redirect $ TL.fromStrict v

oauthCallback :: ScottyM ()
oauthCallback = do
  matchAny "/goauth2callback" $ do
    val <- body
    pars <- S.params
    c <- S.param "code" `rescue` (\_ -> return "haskell")
    let c1 = c <> (""::Text)
    r <- liftIO $ W.post "https://oauth2.googleapis.com/token" 
     [ "code" := (encodeUtf8 (c))
     , "client_id" := (encodeUtf8 consumerAccess)
     , "client_secret" := (encodeUtf8 consumerSecret)
     , "redirect_uri" := (encodeUtf8 redirectURI)
     , "grant_type" := ("authorization_code"::ByteString)
     , "access_type" := ("offline"::ByteString)
     ] 
    let newUser = (r ^? responseBody)
    case newUser of
     Just b -> do
      let jwt = decodeStrict (toStrict b) :: Maybe Value
      case jwt of
       Just (Object v) -> do
        let s = HM.lookup "id_token" v
        case s of
         Just (String k) -> do
          isValid <- liftIO $ validateToken (encodeUtf8 k)
          liftIO $ print isValid
          redirect "/hello_world" 
         _ -> redirect "/hello_world"  
       _ -> redirect "/hello_world"       
     Nothing -> redirect "/hello_world"


oauthGen :: ScottyM ()
oauthGen = do
  matchAny "/callback_gen" $ do
    val <- body
    redirect "/hello_world"

consumerAccess :: Text
consumerAccess = "google public key"

consumerSecret :: Text
consumerSecret = "google secret key"

oAuthScopes :: Text
oAuthScopes = "https://www.googleapis.com/auth/userinfo.profile https://www.googleapis.com/auth/userinfo.email"

redirectURI :: Text
redirectURI = "http://localhost:8080/goauth2callback"

authURI :: Text
authURI = "https://accounts.google.com/o/oauth2/auth"

tokenURI :: Text
tokenURI = "https://oauth2.googleapis.com/token"

projectId :: Text
projectId = "project name"

responseType :: Text
responseType = "code"

oAuthUriBuilder :: [(Text, Text)]
oAuthUriBuilder = 
  [ ("client_id", consumerAccess)
  , ("redirect_uri", redirectURI)
  , ("scope", oAuthScopes)
  , ("response_type", responseType)
  ]

uriSchemeBuilder :: Text
uriSchemeBuilder = authURI <> "?" <> (foldr (\x y -> (fst x ++ "=" ++ (URI.encodeText $ snd x)) ++ "&" ++ y) "" oAuthUriBuilder)

validateToken :: ByteString -> IO (Either JwtError  JwtContent)
validateToken b = do
  keySet <- retrievePublicKeys
  case keySet of
   Left e -> return $ Left $ KeyError "No keyset supplied"
   Right k -> do
    let header = JwsEncoding RS256
    Jose.Jwt.decode k (Just $ header) b

retrievePublicKeys :: IO (Either String [Jwk])
retrievePublicKeys = do
 r <- liftIO $ W.get "https://www.googleapis.com/oauth2/v3/certs"
 case (r ^? responseBody) of
  Nothing -> return $ Left "No body in response from google oauth api"
  Just a -> do
   let v = eitherDecode a :: Either String Value
   case v of
    Left e -> return $ Left e
    Right (Object a) -> do
     let keySet = HM.lookup "keys" a
     case keySet of
      Just k -> do
       let kS = eitherDecode (Data.Aeson.encode k) :: Either String [Jwk]
       return $ kS
      _      -> return $ Left "No Key set provided"
    _ -> return $ Left $ "Incorrect response type from https://www.googleapis.com/oauth2/v3/certs"

The specific part i am interested in replacing is:

retrievePublicKeys :: IO (Either String [Jwk])
retrievePublicKeys = do
 r <- liftIO $ W.get "https://www.googleapis.com/oauth2/v3/certs"
 case (r ^? responseBody) of
  Nothing -> return $ Left "No body in response from google oauth api"
  Just a -> do
   let v = eitherDecode a :: Either String Value
   case v of
    Left e -> return $ Left e
    Right (Object a) -> do
     let keySet = HM.lookup "keys" a
     case keySet of
      Just k -> do
       let kS = eitherDecode (Data.Aeson.encode k) :: Either String [Jwk]
       return $ kS
      _      -> return $ Left "No Key set provided"
    _ -> return $ Left $ "Incorrect response type from https://www.googleapis.com/oauth2/v3/certs"

I've though about storing the Jwk's in redis but i would think that there is a better approach available.

The expected result is to be able to safely modify the cert that i am obtaining from google and using it on subsequent decodings without the need to constantly hit the endpoint.
(Note: Yes i know that it is bad practice to roll your own security but this is just out of interest)

emg184
  • 850
  • 8
  • 19

1 Answers1

2

If you go by something like three layers (ReaderT design pattern), then caching an IORef or TVar in the environment part in a ReaderT YourEnv IO would be the way to go. (atomicModifyIORef' should be sufficient.)

The Holmusk link will recommend the jwt package, but having just added, in another language at work, in-memory caching of Google's OAuth2 certificates, picking a JWT library in Haskell also appears very much like a feature trade-off:

For example, jwt explicitly states that it doesn't check the exp expiration timestamp, but as far as I can see, jose-jwt doesn't even address the exp expiration timestamp that it decodes. google-oauth2-jwt does, and embeds the endpoint (for good and for bad, harder to mock), but doesn't provide a lot of ergonomics beyond that. (Edit: It appears that jose does handle expiration, and that it's also the most popular of those I mentioned on Hackage.)

sshine
  • 15,635
  • 1
  • 41
  • 66