module OpenID.Connect.TokenResponse
(
TokenResponse(..)
, Words(..)
, toWords
, fromWords
) where
import Data.Text (Text)
import GHC.Generics (Generic)
import OpenID.Connect.JSON
data TokenResponse a = TokenResponse
{ TokenResponse a -> Text
accessToken :: Text
, TokenResponse a -> Text
tokenType :: Text
, TokenResponse a -> Maybe Int
expiresIn :: Maybe Int
, TokenResponse a -> Maybe Text
refreshToken :: Maybe Text
, TokenResponse a -> Maybe Words
scope :: Maybe Words
, TokenResponse a -> a
idToken :: a
, TokenResponse a -> Maybe Text
atHash :: Maybe Text
}
deriving stock ((forall x. TokenResponse a -> Rep (TokenResponse a) x)
-> (forall x. Rep (TokenResponse a) x -> TokenResponse a)
-> Generic (TokenResponse a)
forall x. Rep (TokenResponse a) x -> TokenResponse a
forall x. TokenResponse a -> Rep (TokenResponse a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (TokenResponse a) x -> TokenResponse a
forall a x. TokenResponse a -> Rep (TokenResponse a) x
$cto :: forall a x. Rep (TokenResponse a) x -> TokenResponse a
$cfrom :: forall a x. TokenResponse a -> Rep (TokenResponse a) x
Generic, a -> TokenResponse b -> TokenResponse a
(a -> b) -> TokenResponse a -> TokenResponse b
(forall a b. (a -> b) -> TokenResponse a -> TokenResponse b)
-> (forall a b. a -> TokenResponse b -> TokenResponse a)
-> Functor TokenResponse
forall a b. a -> TokenResponse b -> TokenResponse a
forall a b. (a -> b) -> TokenResponse a -> TokenResponse b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> TokenResponse b -> TokenResponse a
$c<$ :: forall a b. a -> TokenResponse b -> TokenResponse a
fmap :: (a -> b) -> TokenResponse a -> TokenResponse b
$cfmap :: forall a b. (a -> b) -> TokenResponse a -> TokenResponse b
Functor)
deriving via (GenericJSON (TokenResponse Text)) instance ToJSON (TokenResponse Text)
deriving via (GenericJSON (TokenResponse Text)) instance FromJSON (TokenResponse Text)
deriving via (GenericJSON (TokenResponse (Maybe Text))) instance ToJSON (TokenResponse (Maybe Text))
deriving via (GenericJSON (TokenResponse (Maybe Text))) instance FromJSON (TokenResponse (Maybe Text))