{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE ViewPatterns #-}
module Keycloak.Config where
import Data.Aeson as JSON
import qualified Data.ByteString.Lazy as BL
import Keycloak.Types
import Keycloak.Tokens
readConfig :: FilePath -> IO AdapterConfig
readConfig :: FilePath -> IO AdapterConfig
readConfig FilePath
f = do
ByteString
j <- FilePath -> IO ByteString
BL.readFile FilePath
f
case forall a. FromJSON a => ByteString -> Either FilePath a
eitherDecode ByteString
j of
Right AdapterConfig
c -> forall (m :: * -> *) a. Monad m => a -> m a
return AdapterConfig
c
Left FilePath
e -> forall a. HasCallStack => FilePath -> a
error FilePath
e
configureKeycloak :: FilePath -> IO KCConfig
configureKeycloak :: FilePath -> IO KCConfig
configureKeycloak FilePath
f = do
AdapterConfig
adapterConf <- FilePath -> IO AdapterConfig
readConfig FilePath
f
[JWK]
jwks <- Realm -> Realm -> IO [JWK]
getJWKs (AdapterConfig -> Realm
_confRealm AdapterConfig
adapterConf) (AdapterConfig -> Realm
_confAuthServerUrl AdapterConfig
adapterConf)
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ AdapterConfig -> [JWK] -> KCConfig
KCConfig AdapterConfig
adapterConf [JWK]
jwks