Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
ZkFold.Symbolic.Data.JWT
Synopsis
- data Certificate ctx = Certificate {
- pubKid :: VarByteString 320 ctx
- pubKey :: PublicKey 2048 ctx
- data SigningKey ctx = SigningKey {
- prvKid :: VarByteString 320 ctx
- prvKey :: PrivateKey 2048 ctx
- data TokenHeader ctx = TokenHeader {
- hdAlg :: VarByteString 72 ctx
- hdKid :: VarByteString 320 ctx
- hdTyp :: VarByteString 32 ctx
- data TokenPayload ctx = TokenPayload {
- plIss :: VarByteString 256 ctx
- plAzp :: VarByteString 1024 ctx
- plAud :: VarByteString 1024 ctx
- plSub :: VarByteString 256 ctx
- plHd :: VarByteString 256 ctx
- plEmail :: VarByteString 512 ctx
- plEmailVerified :: VarByteString 40 ctx
- plAtHash :: VarByteString 256 ctx
- plName :: VarByteString 512 ctx
- plPicture :: VarByteString 1024 ctx
- plGivenName :: VarByteString 256 ctx
- plFamilyName :: VarByteString 256 ctx
- plIat :: VarByteString 80 ctx
- plExp :: VarByteString 80 ctx
- type Signature keyLen ctx = ByteString keyLen ctx
- data ClientSecret ctx = ClientSecret {
- csHeader :: TokenHeader ctx
- csPayload :: TokenPayload ctx
- csSignature :: Signature 2048 ctx
- class IsSymbolicJSON a where
- type MaxLength a :: Natural
- toJsonBits :: a -> VarByteString (MaxLength a) (Context a)
- type SecretBits ctx = (NFData (ctx (Vector 8)), NFData (ctx (Vector 648)), NFData (ctx (Vector 864)), NFData (ctx (Vector 9456)), NFData (ctx (Vector 10328)), NFData (ctx Par1))
- secretBits :: forall ctx. Symbolic ctx => SecretBits ctx => ClientSecret ctx -> VarByteString 10328 ctx
- toAsciiBits :: forall a ctx. IsSymbolicJSON a => Context a ~ ctx => KnownNat (MaxLength a) => Symbolic ctx => NFData (ctx (Vector 8)) => NFData (ctx (Vector (ASCII (Next6 (MaxLength a))))) => a -> VarByteString (ASCII (Next6 (MaxLength a))) ctx
- signPayload :: (SecretBits ctx, RSA 2048 10328 ctx) => SigningKey ctx -> TokenPayload ctx -> ClientSecret ctx
- verifySignature :: (SecretBits ctx, RSA 2048 10328 ctx) => Certificate ctx -> ClientSecret ctx -> (Bool ctx, ByteString 256 ctx)
Documentation
data Certificate ctx Source #
RSA Public key with Key ID
Constructors
Certificate | |
Fields
|
Instances
data SigningKey ctx Source #
RSA Private key with Key ID
Constructors
SigningKey | |
Fields
|
Instances
data TokenHeader ctx Source #
Json Web Token header with information about encryption algorithm and signature
Constructors
TokenHeader | |
Fields
|
Instances
data TokenPayload ctx Source #
Json Web Token payload with information about the issuer, bearer and TTL
Constructors
TokenPayload | |
Fields
|
Instances
type Signature keyLen ctx = ByteString keyLen ctx Source #
data ClientSecret ctx Source #
Constructors
ClientSecret | |
Fields
|
Instances
class IsSymbolicJSON a where Source #
Methods
toJsonBits :: a -> VarByteString (MaxLength a) (Context a) Source #
Instances
(Symbolic ctx, Context (TokenHeader ctx) ~ ctx, NFData (VarByteString (MaxLength (TokenHeader ctx)) ctx)) => IsSymbolicJSON (TokenHeader ctx) Source # | |
Defined in ZkFold.Symbolic.Data.JWT Associated Types type MaxLength (TokenHeader ctx) :: Natural Source # Methods toJsonBits :: TokenHeader ctx -> VarByteString (MaxLength (TokenHeader ctx)) (Context (TokenHeader ctx)) Source # | |
(Symbolic ctx, Context (TokenPayload ctx) ~ ctx) => IsSymbolicJSON (TokenPayload ctx) Source # | |
Defined in ZkFold.Symbolic.Data.JWT Associated Types type MaxLength (TokenPayload ctx) :: Natural Source # Methods toJsonBits :: TokenPayload ctx -> VarByteString (MaxLength (TokenPayload ctx)) (Context (TokenPayload ctx)) Source # |
type SecretBits ctx = (NFData (ctx (Vector 8)), NFData (ctx (Vector 648)), NFData (ctx (Vector 864)), NFData (ctx (Vector 9456)), NFData (ctx (Vector 10328)), NFData (ctx Par1)) Source #
secretBits :: forall ctx. Symbolic ctx => SecretBits ctx => ClientSecret ctx -> VarByteString 10328 ctx Source #
Client secret as a ByteString: ASCII(base64UrlEncode(header) + "." + base64UrlEncode(payload))
toAsciiBits :: forall a ctx. IsSymbolicJSON a => Context a ~ ctx => KnownNat (MaxLength a) => Symbolic ctx => NFData (ctx (Vector 8)) => NFData (ctx (Vector (ASCII (Next6 (MaxLength a))))) => a -> VarByteString (ASCII (Next6 (MaxLength a))) ctx Source #
signPayload :: (SecretBits ctx, RSA 2048 10328 ctx) => SigningKey ctx -> TokenPayload ctx -> ClientSecret ctx Source #
Sign token payload and form a ClientSecret
verifySignature :: (SecretBits ctx, RSA 2048 10328 ctx) => Certificate ctx -> ClientSecret ctx -> (Bool ctx, ByteString 256 ctx) Source #
Verify that the given JWT was correctly signed with a matching key (i.e. Key IDs match and the signature is correct).