{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Keycloak.Types where
import Data.Aeson
import Data.Aeson.Key
import Data.Aeson.Casing
import Data.Hashable
import Data.Text hiding (head, tail, map, toLower, drop)
import Data.String.Conversions
import Data.Maybe
import Data.Map hiding (drop, map)
import qualified Data.HashMap.Strict as HM
import Data.Char
import Control.Monad.Except (ExceptT, runExceptT)
import Control.Monad.Reader as R
import Control.Monad.Time (MonadTime)
import Control.Lens hiding ((.=))
import GHC.Generics (Generic)
import Network.HTTP.Client as HC hiding (responseBody)
import Crypto.JWT as JWT
type JWT = SignedJWT
type Keycloak a = KeycloakT IO a
newtype KeycloakT m a = KeycloakT { forall (m :: * -> *) a.
KeycloakT m a -> ReaderT KCConfig (ExceptT KCError m) a
unKeycloakT :: ReaderT KCConfig (ExceptT KCError m) a }
deriving newtype (forall a. a -> KeycloakT m a
forall a b. KeycloakT m a -> KeycloakT m b -> KeycloakT m b
forall a b. KeycloakT m a -> (a -> KeycloakT m b) -> KeycloakT m b
forall {m :: * -> *}. Monad m => Applicative (KeycloakT m)
forall (m :: * -> *) a. Monad m => a -> KeycloakT m a
forall (m :: * -> *) a b.
Monad m =>
KeycloakT m a -> KeycloakT m b -> KeycloakT m b
forall (m :: * -> *) a b.
Monad m =>
KeycloakT m a -> (a -> KeycloakT m b) -> KeycloakT m b
forall (m :: * -> *).
Applicative m
-> (forall a b. m a -> (a -> m b) -> m b)
-> (forall a b. m a -> m b -> m b)
-> (forall a. a -> m a)
-> Monad m
return :: forall a. a -> KeycloakT m a
$creturn :: forall (m :: * -> *) a. Monad m => a -> KeycloakT m a
>> :: forall a b. KeycloakT m a -> KeycloakT m b -> KeycloakT m b
$c>> :: forall (m :: * -> *) a b.
Monad m =>
KeycloakT m a -> KeycloakT m b -> KeycloakT m b
>>= :: forall a b. KeycloakT m a -> (a -> KeycloakT m b) -> KeycloakT m b
$c>>= :: forall (m :: * -> *) a b.
Monad m =>
KeycloakT m a -> (a -> KeycloakT m b) -> KeycloakT m b
Monad, forall a. a -> KeycloakT m a
forall a b. KeycloakT m a -> KeycloakT m b -> KeycloakT m a
forall a b. KeycloakT m a -> KeycloakT m b -> KeycloakT m b
forall a b. KeycloakT m (a -> b) -> KeycloakT m a -> KeycloakT m b
forall a b c.
(a -> b -> c) -> KeycloakT m a -> KeycloakT m b -> KeycloakT m c
forall {m :: * -> *}. Monad m => Functor (KeycloakT m)
forall (m :: * -> *) a. Monad m => a -> KeycloakT m a
forall (m :: * -> *) a b.
Monad m =>
KeycloakT m a -> KeycloakT m b -> KeycloakT m a
forall (m :: * -> *) a b.
Monad m =>
KeycloakT m a -> KeycloakT m b -> KeycloakT m b
forall (m :: * -> *) a b.
Monad m =>
KeycloakT m (a -> b) -> KeycloakT m a -> KeycloakT m b
forall (m :: * -> *) a b c.
Monad m =>
(a -> b -> c) -> KeycloakT m a -> KeycloakT m b -> KeycloakT m c
forall (f :: * -> *).
Functor f
-> (forall a. a -> f a)
-> (forall a b. f (a -> b) -> f a -> f b)
-> (forall a b c. (a -> b -> c) -> f a -> f b -> f c)
-> (forall a b. f a -> f b -> f b)
-> (forall a b. f a -> f b -> f a)
-> Applicative f
<* :: forall a b. KeycloakT m a -> KeycloakT m b -> KeycloakT m a
$c<* :: forall (m :: * -> *) a b.
Monad m =>
KeycloakT m a -> KeycloakT m b -> KeycloakT m a
*> :: forall a b. KeycloakT m a -> KeycloakT m b -> KeycloakT m b
$c*> :: forall (m :: * -> *) a b.
Monad m =>
KeycloakT m a -> KeycloakT m b -> KeycloakT m b
liftA2 :: forall a b c.
(a -> b -> c) -> KeycloakT m a -> KeycloakT m b -> KeycloakT m c
$cliftA2 :: forall (m :: * -> *) a b c.
Monad m =>
(a -> b -> c) -> KeycloakT m a -> KeycloakT m b -> KeycloakT m c
<*> :: forall a b. KeycloakT m (a -> b) -> KeycloakT m a -> KeycloakT m b
$c<*> :: forall (m :: * -> *) a b.
Monad m =>
KeycloakT m (a -> b) -> KeycloakT m a -> KeycloakT m b
pure :: forall a. a -> KeycloakT m a
$cpure :: forall (m :: * -> *) a. Monad m => a -> KeycloakT m a
Applicative, forall a b. a -> KeycloakT m b -> KeycloakT m a
forall a b. (a -> b) -> KeycloakT m a -> KeycloakT m b
forall (m :: * -> *) a b.
Functor m =>
a -> KeycloakT m b -> KeycloakT m a
forall (m :: * -> *) a b.
Functor m =>
(a -> b) -> KeycloakT m a -> KeycloakT m b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: forall a b. a -> KeycloakT m b -> KeycloakT m a
$c<$ :: forall (m :: * -> *) a b.
Functor m =>
a -> KeycloakT m b -> KeycloakT m a
fmap :: forall a b. (a -> b) -> KeycloakT m a -> KeycloakT m b
$cfmap :: forall (m :: * -> *) a b.
Functor m =>
(a -> b) -> KeycloakT m a -> KeycloakT m b
Functor, forall a. IO a -> KeycloakT m a
forall (m :: * -> *).
Monad m -> (forall a. IO a -> m a) -> MonadIO m
forall {m :: * -> *}. MonadIO m => Monad (KeycloakT m)
forall (m :: * -> *) a. MonadIO m => IO a -> KeycloakT m a
liftIO :: forall a. IO a -> KeycloakT m a
$cliftIO :: forall (m :: * -> *) a. MonadIO m => IO a -> KeycloakT m a
MonadIO, KeycloakT m Double
KeycloakT m UTCTime
forall (m :: * -> *).
Monad m -> m UTCTime -> m Double -> MonadTime m
forall {m :: * -> *}. MonadTime m => Monad (KeycloakT m)
forall (m :: * -> *). MonadTime m => KeycloakT m Double
forall (m :: * -> *). MonadTime m => KeycloakT m UTCTime
monotonicTime :: KeycloakT m Double
$cmonotonicTime :: forall (m :: * -> *). MonadTime m => KeycloakT m Double
currentTime :: KeycloakT m UTCTime
$ccurrentTime :: forall (m :: * -> *). MonadTime m => KeycloakT m UTCTime
MonadTime)
instance MonadTrans KeycloakT where
lift :: forall (m :: * -> *) a. Monad m => m a -> KeycloakT m a
lift = forall (m :: * -> *) a.
ReaderT KCConfig (ExceptT KCError m) a -> KeycloakT m a
KeycloakT forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift
data KCError = HTTPError HttpException
| ParseError Text
| JWTError JWTError
| EmptyError
deriving stock (Int -> KCError -> ShowS
[KCError] -> ShowS
KCError -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [KCError] -> ShowS
$cshowList :: [KCError] -> ShowS
show :: KCError -> String
$cshow :: KCError -> String
showsPrec :: Int -> KCError -> ShowS
$cshowsPrec :: Int -> KCError -> ShowS
Show)
instance AsJWTError KCError where
_JWTError :: Prism' KCError JWTError
_JWTError = forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism' JWTError -> KCError
JWTError KCError -> Maybe JWTError
up where
up :: KCError -> Maybe JWTError
up (JWTError JWTError
e) = forall a. a -> Maybe a
Just JWTError
e
up KCError
_ = forall a. Maybe a
Nothing
instance AsError KCError where
_Error :: Prism' KCError Error
_Error = forall r. AsJWTError r => Prism' r Error
_JWSError
data KCConfig = KCConfig {
KCConfig -> AdapterConfig
_confAdapterConfig :: AdapterConfig,
KCConfig -> [JWK]
_confJWKs :: [JWK]}
deriving (KCConfig -> KCConfig -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: KCConfig -> KCConfig -> Bool
$c/= :: KCConfig -> KCConfig -> Bool
== :: KCConfig -> KCConfig -> Bool
$c== :: KCConfig -> KCConfig -> Bool
Eq, Int -> KCConfig -> ShowS
[KCConfig] -> ShowS
KCConfig -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [KCConfig] -> ShowS
$cshowList :: [KCConfig] -> ShowS
show :: KCConfig -> String
$cshow :: KCConfig -> String
showsPrec :: Int -> KCConfig -> ShowS
$cshowsPrec :: Int -> KCConfig -> ShowS
Show, forall x. Rep KCConfig x -> KCConfig
forall x. KCConfig -> Rep KCConfig x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep KCConfig x -> KCConfig
$cfrom :: forall x. KCConfig -> Rep KCConfig x
Generic)
type Realm = Text
type ClientId = Text
type ServerURL = Text
data AdapterConfig = AdapterConfig {
AdapterConfig -> Realm
_confRealm :: Realm,
AdapterConfig -> Realm
_confAuthServerUrl :: ServerURL,
AdapterConfig -> Realm
_confResource :: ClientId,
AdapterConfig -> ClientCredentials
_confCredentials :: ClientCredentials}
deriving stock (AdapterConfig -> AdapterConfig -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AdapterConfig -> AdapterConfig -> Bool
$c/= :: AdapterConfig -> AdapterConfig -> Bool
== :: AdapterConfig -> AdapterConfig -> Bool
$c== :: AdapterConfig -> AdapterConfig -> Bool
Eq, Int -> AdapterConfig -> ShowS
[AdapterConfig] -> ShowS
AdapterConfig -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AdapterConfig] -> ShowS
$cshowList :: [AdapterConfig] -> ShowS
show :: AdapterConfig -> String
$cshow :: AdapterConfig -> String
showsPrec :: Int -> AdapterConfig -> ShowS
$cshowsPrec :: Int -> AdapterConfig -> ShowS
Show, forall x. Rep AdapterConfig x -> AdapterConfig
forall x. AdapterConfig -> Rep AdapterConfig x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AdapterConfig x -> AdapterConfig
$cfrom :: forall x. AdapterConfig -> Rep AdapterConfig x
Generic)
instance ToJSON AdapterConfig where
toJSON :: AdapterConfig -> Value
toJSON = forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON forall a b. (a -> b) -> a -> b
$ Int -> Options
trainDrop Int
5
instance FromJSON AdapterConfig where
parseJSON :: Value -> Parser AdapterConfig
parseJSON = forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON forall a b. (a -> b) -> a -> b
$ Int -> Options
trainDrop Int
5
data ClientCredentials = ClientCredentials {
ClientCredentials -> Realm
_confSecret :: Text}
deriving stock (ClientCredentials -> ClientCredentials -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ClientCredentials -> ClientCredentials -> Bool
$c/= :: ClientCredentials -> ClientCredentials -> Bool
== :: ClientCredentials -> ClientCredentials -> Bool
$c== :: ClientCredentials -> ClientCredentials -> Bool
Eq, Int -> ClientCredentials -> ShowS
[ClientCredentials] -> ShowS
ClientCredentials -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ClientCredentials] -> ShowS
$cshowList :: [ClientCredentials] -> ShowS
show :: ClientCredentials -> String
$cshow :: ClientCredentials -> String
showsPrec :: Int -> ClientCredentials -> ShowS
$cshowsPrec :: Int -> ClientCredentials -> ShowS
Show, forall x. Rep ClientCredentials x -> ClientCredentials
forall x. ClientCredentials -> Rep ClientCredentials x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ClientCredentials x -> ClientCredentials
$cfrom :: forall x. ClientCredentials -> Rep ClientCredentials x
Generic)
instance ToJSON ClientCredentials where
toJSON :: ClientCredentials -> Value
toJSON = forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON forall a b. (a -> b) -> a -> b
$ Int -> Options
trainDrop Int
5
instance FromJSON ClientCredentials where
parseJSON :: Value -> Parser ClientCredentials
parseJSON = forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON forall a b. (a -> b) -> a -> b
$ Int -> Options
trainDrop Int
5
trainDrop :: Int -> Options
trainDrop :: Int -> Options
trainDrop Int
n = Options
defaultOptions {fieldLabelModifier :: ShowS
fieldLabelModifier = ShowS
trainCase forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Int -> [a] -> [a]
drop Int
n, omitNothingFields :: Bool
omitNothingFields = Bool
True}
defaultAdapterConfig :: AdapterConfig
defaultAdapterConfig :: AdapterConfig
defaultAdapterConfig = AdapterConfig {
_confRealm :: Realm
_confRealm = Realm
"waziup",
_confAuthServerUrl :: Realm
_confAuthServerUrl = Realm
"http://localhost:8080/auth",
_confResource :: Realm
_confResource = Realm
"api-server",
_confCredentials :: ClientCredentials
_confCredentials = Realm -> ClientCredentials
ClientCredentials Realm
"4e9dcb80-efcd-484c-b3d7-1e95a0096ac0"}
runKeycloak :: Monad m => KeycloakT m a -> KCConfig -> m (Either KCError a)
runKeycloak :: forall (m :: * -> *) a.
Monad m =>
KeycloakT m a -> KCConfig -> m (Either KCError a)
runKeycloak KeycloakT m a
kc KCConfig
conf = forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT forall a b. (a -> b) -> a -> b
$ forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT (forall (m :: * -> *) a.
KeycloakT m a -> ReaderT KCConfig (ExceptT KCError m) a
unKeycloakT KeycloakT m a
kc) KCConfig
conf
type Path = Text
data TokenRep = TokenRep {
TokenRep -> Realm
accessToken :: Text,
TokenRep -> Int
expiresIn :: Int,
TokenRep -> Int
refreshExpriresIn :: Int,
TokenRep -> Realm
refreshToken :: Text,
TokenRep -> Realm
tokenType :: Text,
TokenRep -> Int
notBeforePolicy :: Int,
TokenRep -> Realm
sessionState :: Text,
TokenRep -> Realm
tokenScope :: Text} deriving stock (Int -> TokenRep -> ShowS
[TokenRep] -> ShowS
TokenRep -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TokenRep] -> ShowS
$cshowList :: [TokenRep] -> ShowS
show :: TokenRep -> String
$cshow :: TokenRep -> String
showsPrec :: Int -> TokenRep -> ShowS
$cshowsPrec :: Int -> TokenRep -> ShowS
Show, TokenRep -> TokenRep -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TokenRep -> TokenRep -> Bool
$c/= :: TokenRep -> TokenRep -> Bool
== :: TokenRep -> TokenRep -> Bool
$c== :: TokenRep -> TokenRep -> Bool
Eq)
instance FromJSON TokenRep where
parseJSON :: Value -> Parser TokenRep
parseJSON (Object Object
v) = Realm
-> Int
-> Int
-> Realm
-> Realm
-> Int
-> Realm
-> Realm
-> TokenRep
TokenRep forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"access_token"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"expires_in"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"refresh_expires_in"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"refresh_token"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"token_type"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"not-before-policy"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"session_state"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"scope"
parseJSON Value
_ = forall a. HasCallStack => String -> a
error String
"Not an object"
newtype ScopeName = ScopeName {ScopeName -> Realm
unScopeName :: Text}
deriving stock (ScopeName -> ScopeName -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ScopeName -> ScopeName -> Bool
$c/= :: ScopeName -> ScopeName -> Bool
== :: ScopeName -> ScopeName -> Bool
$c== :: ScopeName -> ScopeName -> Bool
Eq, forall x. Rep ScopeName x -> ScopeName
forall x. ScopeName -> Rep ScopeName x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ScopeName x -> ScopeName
$cfrom :: forall x. ScopeName -> Rep ScopeName x
Generic, Eq ScopeName
ScopeName -> ScopeName -> Bool
ScopeName -> ScopeName -> Ordering
ScopeName -> ScopeName -> ScopeName
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ScopeName -> ScopeName -> ScopeName
$cmin :: ScopeName -> ScopeName -> ScopeName
max :: ScopeName -> ScopeName -> ScopeName
$cmax :: ScopeName -> ScopeName -> ScopeName
>= :: ScopeName -> ScopeName -> Bool
$c>= :: ScopeName -> ScopeName -> Bool
> :: ScopeName -> ScopeName -> Bool
$c> :: ScopeName -> ScopeName -> Bool
<= :: ScopeName -> ScopeName -> Bool
$c<= :: ScopeName -> ScopeName -> Bool
< :: ScopeName -> ScopeName -> Bool
$c< :: ScopeName -> ScopeName -> Bool
compare :: ScopeName -> ScopeName -> Ordering
$ccompare :: ScopeName -> ScopeName -> Ordering
Ord)
deriving newtype (Eq ScopeName
Int -> ScopeName -> Int
ScopeName -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: ScopeName -> Int
$chash :: ScopeName -> Int
hashWithSalt :: Int -> ScopeName -> Int
$chashWithSalt :: Int -> ScopeName -> Int
Hashable)
instance ToJSON ScopeName where
toJSON :: ScopeName -> Value
toJSON = forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON (Options
defaultOptions {unwrapUnaryRecords :: Bool
unwrapUnaryRecords = Bool
True})
instance FromJSON ScopeName where
parseJSON :: Value -> Parser ScopeName
parseJSON = forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON (Options
defaultOptions {unwrapUnaryRecords :: Bool
unwrapUnaryRecords = Bool
True})
instance Show ScopeName where
show :: ScopeName -> String
show (ScopeName Realm
s) = forall a b. ConvertibleStrings a b => a -> b
convertString Realm
s
newtype ScopeId = ScopeId {ScopeId -> Realm
unScopeId :: Text} deriving (Int -> ScopeId -> ShowS
[ScopeId] -> ShowS
ScopeId -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ScopeId] -> ShowS
$cshowList :: [ScopeId] -> ShowS
show :: ScopeId -> String
$cshow :: ScopeId -> String
showsPrec :: Int -> ScopeId -> ShowS
$cshowsPrec :: Int -> ScopeId -> ShowS
Show, ScopeId -> ScopeId -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ScopeId -> ScopeId -> Bool
$c/= :: ScopeId -> ScopeId -> Bool
== :: ScopeId -> ScopeId -> Bool
$c== :: ScopeId -> ScopeId -> Bool
Eq, forall x. Rep ScopeId x -> ScopeId
forall x. ScopeId -> Rep ScopeId x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ScopeId x -> ScopeId
$cfrom :: forall x. ScopeId -> Rep ScopeId x
Generic)
instance ToJSON ScopeId where
toJSON :: ScopeId -> Value
toJSON = forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON (Options
defaultOptions {unwrapUnaryRecords :: Bool
unwrapUnaryRecords = Bool
True})
instance FromJSON ScopeId where
parseJSON :: Value -> Parser ScopeId
parseJSON = forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON (Options
defaultOptions {unwrapUnaryRecords :: Bool
unwrapUnaryRecords = Bool
True})
data Scope = Scope {
Scope -> Maybe ScopeId
scopeId :: Maybe ScopeId,
Scope -> ScopeName
scopeName :: ScopeName
} deriving (forall x. Rep Scope x -> Scope
forall x. Scope -> Rep Scope x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Scope x -> Scope
$cfrom :: forall x. Scope -> Rep Scope x
Generic, Int -> Scope -> ShowS
[Scope] -> ShowS
Scope -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Scope] -> ShowS
$cshowList :: [Scope] -> ShowS
show :: Scope -> String
$cshow :: Scope -> String
showsPrec :: Int -> Scope -> ShowS
$cshowsPrec :: Int -> Scope -> ShowS
Show, Scope -> Scope -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Scope -> Scope -> Bool
$c/= :: Scope -> Scope -> Bool
== :: Scope -> Scope -> Bool
$c== :: Scope -> Scope -> Bool
Eq)
instance ToJSON Scope where
toJSON :: Scope -> Value
toJSON = forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
defaultOptions {fieldLabelModifier :: ShowS
fieldLabelModifier = ShowS
unCapitalize forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Int -> [a] -> [a]
drop Int
5, omitNothingFields :: Bool
omitNothingFields = Bool
True}
instance FromJSON Scope where
parseJSON :: Value -> Parser Scope
parseJSON = forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
defaultOptions {fieldLabelModifier :: ShowS
fieldLabelModifier = ShowS
unCapitalize forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Int -> [a] -> [a]
drop Int
5}
data PermReq = PermReq
{ PermReq -> Maybe ResourceId
permReqResourceId :: Maybe ResourceId,
PermReq -> [ScopeName]
permReqScopes :: [ScopeName]
} deriving (forall x. Rep PermReq x -> PermReq
forall x. PermReq -> Rep PermReq x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PermReq x -> PermReq
$cfrom :: forall x. PermReq -> Rep PermReq x
Generic, PermReq -> PermReq -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PermReq -> PermReq -> Bool
$c/= :: PermReq -> PermReq -> Bool
== :: PermReq -> PermReq -> Bool
$c== :: PermReq -> PermReq -> Bool
Eq, Eq PermReq
PermReq -> PermReq -> Bool
PermReq -> PermReq -> Ordering
PermReq -> PermReq -> PermReq
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: PermReq -> PermReq -> PermReq
$cmin :: PermReq -> PermReq -> PermReq
max :: PermReq -> PermReq -> PermReq
$cmax :: PermReq -> PermReq -> PermReq
>= :: PermReq -> PermReq -> Bool
$c>= :: PermReq -> PermReq -> Bool
> :: PermReq -> PermReq -> Bool
$c> :: PermReq -> PermReq -> Bool
<= :: PermReq -> PermReq -> Bool
$c<= :: PermReq -> PermReq -> Bool
< :: PermReq -> PermReq -> Bool
$c< :: PermReq -> PermReq -> Bool
compare :: PermReq -> PermReq -> Ordering
$ccompare :: PermReq -> PermReq -> Ordering
Ord, Eq PermReq
Int -> PermReq -> Int
PermReq -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: PermReq -> Int
$chash :: PermReq -> Int
hashWithSalt :: Int -> PermReq -> Int
$chashWithSalt :: Int -> PermReq -> Int
Hashable)
instance Show PermReq where
show :: PermReq -> String
show (PermReq (Just (ResourceId Realm
res1)) [ScopeName]
scopes) = (forall a. Show a => a -> String
show Realm
res1) forall a. Semigroup a => a -> a -> a
<> String
" " forall a. Semigroup a => a -> a -> a
<> (forall a. Show a => a -> String
show [ScopeName]
scopes)
show (PermReq Maybe ResourceId
Nothing [ScopeName]
scopes) = String
"none " forall a. Semigroup a => a -> a -> a
<> (forall a. Show a => a -> String
show [ScopeName]
scopes)
data Permission = Permission
{ Permission -> Maybe ResourceId
permRsid :: Maybe ResourceId,
Permission -> Maybe Realm
permRsname :: Maybe ResourceName,
Permission -> [ScopeName]
permScopes :: [ScopeName]
} deriving (forall x. Rep Permission x -> Permission
forall x. Permission -> Rep Permission x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Permission x -> Permission
$cfrom :: forall x. Permission -> Rep Permission x
Generic, Int -> Permission -> ShowS
[Permission] -> ShowS
Permission -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Permission] -> ShowS
$cshowList :: [Permission] -> ShowS
show :: Permission -> String
$cshow :: Permission -> String
showsPrec :: Int -> Permission -> ShowS
$cshowsPrec :: Int -> Permission -> ShowS
Show, Permission -> Permission -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Permission -> Permission -> Bool
$c/= :: Permission -> Permission -> Bool
== :: Permission -> Permission -> Bool
$c== :: Permission -> Permission -> Bool
Eq)
instance ToJSON Permission where
toJSON :: Permission -> Value
toJSON = forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
defaultOptions {fieldLabelModifier :: ShowS
fieldLabelModifier = ShowS
unCapitalize forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Int -> [a] -> [a]
drop Int
4, omitNothingFields :: Bool
omitNothingFields = Bool
True}
instance FromJSON Permission where
parseJSON :: Value -> Parser Permission
parseJSON = forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
defaultOptions {fieldLabelModifier :: ShowS
fieldLabelModifier = ShowS
unCapitalize forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Int -> [a] -> [a]
drop Int
4}
type Username = Text
type Password = Text
type First = Int
type Max = Int
newtype UserId = UserId {UserId -> Realm
unUserId :: Text} deriving (Int -> UserId -> ShowS
[UserId] -> ShowS
UserId -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UserId] -> ShowS
$cshowList :: [UserId] -> ShowS
show :: UserId -> String
$cshow :: UserId -> String
showsPrec :: Int -> UserId -> ShowS
$cshowsPrec :: Int -> UserId -> ShowS
Show, UserId -> UserId -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UserId -> UserId -> Bool
$c/= :: UserId -> UserId -> Bool
== :: UserId -> UserId -> Bool
$c== :: UserId -> UserId -> Bool
Eq, forall x. Rep UserId x -> UserId
forall x. UserId -> Rep UserId x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UserId x -> UserId
$cfrom :: forall x. UserId -> Rep UserId x
Generic)
instance ToJSON UserId where
toJSON :: UserId -> Value
toJSON = forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON (Options
defaultOptions {unwrapUnaryRecords :: Bool
unwrapUnaryRecords = Bool
True})
instance FromJSON UserId where
parseJSON :: Value -> Parser UserId
parseJSON = forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON (Options
defaultOptions {unwrapUnaryRecords :: Bool
unwrapUnaryRecords = Bool
True})
data User = User
{ User -> Maybe UserId
userId :: Maybe UserId
, User -> Realm
userUsername :: Username
, User -> Maybe Realm
userFirstName :: Maybe Text
, User -> Maybe Realm
userLastName :: Maybe Text
, User -> Maybe Realm
userEmail :: Maybe Text
, User -> Maybe (Map Realm Value)
userAttributes :: Maybe (Map Text Value)
} deriving (Int -> User -> ShowS
[User] -> ShowS
User -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [User] -> ShowS
$cshowList :: [User] -> ShowS
show :: User -> String
$cshow :: User -> String
showsPrec :: Int -> User -> ShowS
$cshowsPrec :: Int -> User -> ShowS
Show, User -> User -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: User -> User -> Bool
$c/= :: User -> User -> Bool
== :: User -> User -> Bool
$c== :: User -> User -> Bool
Eq, forall x. Rep User x -> User
forall x. User -> Rep User x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep User x -> User
$cfrom :: forall x. User -> Rep User x
Generic)
unCapitalize :: String -> String
unCapitalize :: ShowS
unCapitalize (Char
a:String
as) = Char -> Char
toLower Char
a forall a. a -> [a] -> [a]
: String
as
unCapitalize [] = []
instance FromJSON User where
parseJSON :: Value -> Parser User
parseJSON = forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
defaultOptions {fieldLabelModifier :: ShowS
fieldLabelModifier = ShowS
unCapitalize forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Int -> [a] -> [a]
drop Int
4}
instance ToJSON User where
toJSON :: User -> Value
toJSON = forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
defaultOptions {fieldLabelModifier :: ShowS
fieldLabelModifier = ShowS
unCapitalize forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Int -> [a] -> [a]
drop Int
4, omitNothingFields :: Bool
omitNothingFields = Bool
True}
data Owner = Owner {
Owner -> Maybe Realm
ownId :: Maybe Text,
Owner -> Maybe Realm
ownName :: Maybe Username
} deriving (forall x. Rep Owner x -> Owner
forall x. Owner -> Rep Owner x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Owner x -> Owner
$cfrom :: forall x. Owner -> Rep Owner x
Generic, Int -> Owner -> ShowS
[Owner] -> ShowS
Owner -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Owner] -> ShowS
$cshowList :: [Owner] -> ShowS
show :: Owner -> String
$cshow :: Owner -> String
showsPrec :: Int -> Owner -> ShowS
$cshowsPrec :: Int -> Owner -> ShowS
Show)
instance FromJSON Owner where
parseJSON :: Value -> Parser Owner
parseJSON = forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON forall a b. (a -> b) -> a -> b
$ Int -> ShowS -> Options
aesonDrop Int
3 ShowS
snakeCase
instance ToJSON Owner where
toJSON :: Owner -> Value
toJSON = forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON forall a b. (a -> b) -> a -> b
$ (Int -> ShowS -> Options
aesonDrop Int
3 ShowS
snakeCase) {omitNothingFields :: Bool
omitNothingFields = Bool
True}
type ResourceName = Text
type ResourceType = Text
newtype ResourceId = ResourceId {ResourceId -> Realm
unResId :: Text}
deriving stock (Int -> ResourceId -> ShowS
[ResourceId] -> ShowS
ResourceId -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ResourceId] -> ShowS
$cshowList :: [ResourceId] -> ShowS
show :: ResourceId -> String
$cshow :: ResourceId -> String
showsPrec :: Int -> ResourceId -> ShowS
$cshowsPrec :: Int -> ResourceId -> ShowS
Show, ResourceId -> ResourceId -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ResourceId -> ResourceId -> Bool
$c/= :: ResourceId -> ResourceId -> Bool
== :: ResourceId -> ResourceId -> Bool
$c== :: ResourceId -> ResourceId -> Bool
Eq, forall x. Rep ResourceId x -> ResourceId
forall x. ResourceId -> Rep ResourceId x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ResourceId x -> ResourceId
$cfrom :: forall x. ResourceId -> Rep ResourceId x
Generic, Eq ResourceId
ResourceId -> ResourceId -> Bool
ResourceId -> ResourceId -> Ordering
ResourceId -> ResourceId -> ResourceId
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ResourceId -> ResourceId -> ResourceId
$cmin :: ResourceId -> ResourceId -> ResourceId
max :: ResourceId -> ResourceId -> ResourceId
$cmax :: ResourceId -> ResourceId -> ResourceId
>= :: ResourceId -> ResourceId -> Bool
$c>= :: ResourceId -> ResourceId -> Bool
> :: ResourceId -> ResourceId -> Bool
$c> :: ResourceId -> ResourceId -> Bool
<= :: ResourceId -> ResourceId -> Bool
$c<= :: ResourceId -> ResourceId -> Bool
< :: ResourceId -> ResourceId -> Bool
$c< :: ResourceId -> ResourceId -> Bool
compare :: ResourceId -> ResourceId -> Ordering
$ccompare :: ResourceId -> ResourceId -> Ordering
Ord)
deriving newtype (Eq ResourceId
Int -> ResourceId -> Int
ResourceId -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: ResourceId -> Int
$chash :: ResourceId -> Int
hashWithSalt :: Int -> ResourceId -> Int
$chashWithSalt :: Int -> ResourceId -> Int
Hashable)
instance ToJSON ResourceId where
toJSON :: ResourceId -> Value
toJSON = forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON (Options
defaultOptions {unwrapUnaryRecords :: Bool
unwrapUnaryRecords = Bool
True})
instance FromJSON ResourceId where
parseJSON :: Value -> Parser ResourceId
parseJSON = forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON (Options
defaultOptions {unwrapUnaryRecords :: Bool
unwrapUnaryRecords = Bool
True})
data Resource = Resource {
Resource -> Maybe ResourceId
resId :: Maybe ResourceId,
Resource -> Realm
resName :: ResourceName,
Resource -> Maybe Realm
resType :: Maybe ResourceType,
Resource -> [Realm]
resUris :: [Text],
Resource -> [Scope]
resScopes :: [Scope],
Resource -> Owner
resOwner :: Owner,
Resource -> Bool
resOwnerManagedAccess :: Bool,
Resource -> [Attribute]
resAttributes :: [Attribute]
} deriving (forall x. Rep Resource x -> Resource
forall x. Resource -> Rep Resource x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Resource x -> Resource
$cfrom :: forall x. Resource -> Rep Resource x
Generic, Int -> Resource -> ShowS
[Resource] -> ShowS
Resource -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Resource] -> ShowS
$cshowList :: [Resource] -> ShowS
show :: Resource -> String
$cshow :: Resource -> String
showsPrec :: Int -> Resource -> ShowS
$cshowsPrec :: Int -> Resource -> ShowS
Show)
instance FromJSON Resource where
parseJSON :: Value -> Parser Resource
parseJSON (Object Object
v) = do
Maybe ResourceId
rId <- Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"_id"
Realm
rName <- Object
v forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"name"
Maybe Realm
rType <- Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"type"
[Realm]
rUris <- Object
v forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"uris"
[Scope]
rScopes <- Object
v forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"scopes"
Owner
rOwn <- Object
v forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"owner"
Bool
rOMA <- Object
v forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"ownerManagedAccess"
Maybe (Map Realm [Realm])
rAtt <- Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"attributes"
let atts :: [(Realm, [Realm])]
atts = if forall a. Maybe a -> Bool
isJust Maybe (Map Realm [Realm])
rAtt then forall k a. Map k a -> [(k, a)]
toList forall a b. (a -> b) -> a -> b
$ forall a. HasCallStack => Maybe a -> a
fromJust Maybe (Map Realm [Realm])
rAtt else []
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Maybe ResourceId
-> Realm
-> Maybe Realm
-> [Realm]
-> [Scope]
-> Owner
-> Bool
-> [Attribute]
-> Resource
Resource Maybe ResourceId
rId Realm
rName Maybe Realm
rType [Realm]
rUris [Scope]
rScopes Owner
rOwn Bool
rOMA (forall a b. (a -> b) -> [a] -> [b]
map (\(Realm
a, [Realm]
b) -> Realm -> [Realm] -> Attribute
Attribute Realm
a [Realm]
b) [(Realm, [Realm])]
atts)
parseJSON Value
_ = forall a. HasCallStack => String -> a
error String
"not an object"
instance ToJSON Resource where
toJSON :: Resource -> Value
toJSON (Resource Maybe ResourceId
rid Realm
name Maybe Realm
typ [Realm]
uris [Scope]
scopes Owner
own Bool
uma [Attribute]
attrs) =
[Pair] -> Value
object [Key
"_id" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= forall a. ToJSON a => a -> Value
toJSON Maybe ResourceId
rid,
Key
"name" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= forall a. ToJSON a => a -> Value
toJSON Realm
name,
Key
"type" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= forall a. ToJSON a => a -> Value
toJSON Maybe Realm
typ,
Key
"uris" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= forall a. ToJSON a => a -> Value
toJSON [Realm]
uris,
Key
"scopes" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= forall a. ToJSON a => a -> Value
toJSON [Scope]
scopes,
Key
"owner" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= (forall a. ToJSON a => a -> Value
toJSON forall a b. (a -> b) -> a -> b
$ Owner -> Maybe Realm
ownName Owner
own),
Key
"ownerManagedAccess" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= forall a. ToJSON a => a -> Value
toJSON Bool
uma,
Key
"attributes" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [Pair] -> Value
object (forall a b. (a -> b) -> [a] -> [b]
map (\(Attribute Realm
aname [Realm]
vals) -> Realm -> Key
fromText Realm
aname forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= forall a. ToJSON a => a -> Value
toJSON [Realm]
vals) [Attribute]
attrs)]
data Attribute = Attribute {
Attribute -> Realm
attName :: Text,
Attribute -> [Realm]
attValues :: [Text]
} deriving (forall x. Rep Attribute x -> Attribute
forall x. Attribute -> Rep Attribute x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Attribute x -> Attribute
$cfrom :: forall x. Attribute -> Rep Attribute x
Generic, Int -> Attribute -> ShowS
[Attribute] -> ShowS
Attribute -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Attribute] -> ShowS
$cshowList :: [Attribute] -> ShowS
show :: Attribute -> String
$cshow :: Attribute -> String
showsPrec :: Int -> Attribute -> ShowS
$cshowsPrec :: Int -> Attribute -> ShowS
Show)
instance FromJSON Attribute where
parseJSON :: Value -> Parser Attribute
parseJSON = forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON forall a b. (a -> b) -> a -> b
$ Int -> ShowS -> Options
aesonDrop Int
3 ShowS
camelCase
instance ToJSON Attribute where
toJSON :: Attribute -> Value
toJSON (Attribute Realm
name [Realm]
vals) = [Pair] -> Value
object [Realm -> Key
fromText Realm
name forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= forall a. ToJSON a => a -> Value
toJSON [Realm]
vals]
makeLenses ''KCConfig
makeLenses ''ClientCredentials
makeLenses ''AdapterConfig