libjwt-typed-0.2: A Haskell implementation of JSON Web Token (JWT)
Safe HaskellNone
LanguageHaskell2010
Extensions
  • UndecidableInstances
  • MonoLocalBinds
  • ScopedTypeVariables
  • TypeFamilies
  • DataKinds
  • DerivingStrategies
  • DerivingVia
  • TypeSynonymInstances
  • FlexibleInstances
  • ConstrainedClassMethods
  • MultiParamTypeClasses
  • KindSignatures
  • ExplicitNamespaces
  • ExplicitForAll

Libjwt.Decoding

Description

JWT decoding definition

This module can be considered internal to the library Users should never need to implement the Decode typeclass or use any of the exported functions or types directly. You'll only need to know of Decode typeclass if you want to write a function polymorphic in the type of payloads.

If you want to extend the types supported by the library, see Libjwt.Classes

Synopsis

Documentation

newtype DecodeResult t Source #

Constructors

Result 

Fields

Instances

Instances details
Monad DecodeResult Source # 
Instance details

Defined in Libjwt.Decoding

Functor DecodeResult Source # 
Instance details

Defined in Libjwt.Decoding

Methods

fmap :: (a -> b) -> DecodeResult a -> DecodeResult b #

(<$) :: a -> DecodeResult b -> DecodeResult a #

Applicative DecodeResult Source # 
Instance details

Defined in Libjwt.Decoding

Alternative DecodeResult Source # 
Instance details

Defined in Libjwt.Decoding

hoistResult :: Maybe a -> DecodeResult a Source #

Lift pure value

class ClaimDecoder t where Source #

Low-level definition of claims decoding.

Methods

decodeClaim :: String -> JwtT -> DecodeResult t Source #

Given a pointer to jwt_t, try to decode the value of type t

Instances

Instances details
(DecoderDef a ~ ty, ClaimDecoder' ty a) => ClaimDecoder a Source # 
Instance details

Defined in Libjwt.Decoding

class Decode c where Source #

Definition of claims decoding.

The only use for the user is probably to write a function that is polymorphic in the payload type

Methods

decode :: JwtT -> JwtIO c Source #

Construct an action that decodes the value of type c, given a pointer to jwt_t. The action may fail.

Instances

Instances details
Decode Header Source # 
Instance details

Defined in Libjwt.Header

Decode Typ Source # 
Instance details

Defined in Libjwt.Header

Methods

decode :: JwtT -> JwtIO Typ Source #

Decode Alg Source # 
Instance details

Defined in Libjwt.Header

Methods

decode :: JwtT -> JwtIO Alg Source #

Decode Jti Source # 
Instance details

Defined in Libjwt.RegisteredClaims

Methods

decode :: JwtT -> JwtIO Jti Source #

Decode Iat Source # 
Instance details

Defined in Libjwt.RegisteredClaims

Methods

decode :: JwtT -> JwtIO Iat Source #

Decode Nbf Source # 
Instance details

Defined in Libjwt.RegisteredClaims

Methods

decode :: JwtT -> JwtIO Nbf Source #

Decode Exp Source # 
Instance details

Defined in Libjwt.RegisteredClaims

Methods

decode :: JwtT -> JwtIO Exp Source #

Decode Aud Source # 
Instance details

Defined in Libjwt.RegisteredClaims

Methods

decode :: JwtT -> JwtIO Aud Source #

Decode Sub Source # 
Instance details

Defined in Libjwt.RegisteredClaims

Methods

decode :: JwtT -> JwtIO Sub Source #

Decode Iss Source # 
Instance details

Defined in Libjwt.RegisteredClaims

Methods

decode :: JwtT -> JwtIO Iss Source #

(ty ~ DecodeAuxDef a, DecodeAux ty ns name a, CanAdd name tl, Decode (PrivateClaims tl ns)) => Decode (PrivateClaims ((name ->> a) ': tl) ns) Source # 
Instance details

Defined in Libjwt.PrivateClaims

Methods

decode :: JwtT -> JwtIO (PrivateClaims ((name ->> a) ': tl) ns) Source #

Decode (PrivateClaims Empty ns) Source # 
Instance details

Defined in Libjwt.PrivateClaims

Decode (PrivateClaims pc ns) => Decode (Payload pc ns) Source # 
Instance details

Defined in Libjwt.Payload

Methods

decode :: JwtT -> JwtIO (Payload pc ns) Source #

getOrEmpty :: Monoid a => DecodeResult a -> JwtIO a Source #

Action that returns mempty if decoding has failed

decodeClaimOrThrow :: ClaimDecoder t => String -> proxy t -> JwtT -> JwtIO t Source #

Action that throws MissingClaim if decoding has failed

decodeClaimProxied :: ClaimDecoder t => String -> proxy t -> JwtT -> DecodeResult t Source #

decodeClaim through proxy

type family Decodable t :: Constraint where ... Source #

Equations

Decodable t = ClaimDecoder' (DecoderDef t) t 

data JwtIO a Source #

IO restricted to calling libjwt and jsmn

Instances

Instances details
Monad JwtIO Source # 
Instance details

Defined in Libjwt.FFI.Jwt

Methods

(>>=) :: JwtIO a -> (a -> JwtIO b) -> JwtIO b #

(>>) :: JwtIO a -> JwtIO b -> JwtIO b #

return :: a -> JwtIO a #

Functor JwtIO Source # 
Instance details

Defined in Libjwt.FFI.Jwt

Methods

fmap :: (a -> b) -> JwtIO a -> JwtIO b #

(<$) :: a -> JwtIO b -> JwtIO a #

Applicative JwtIO Source # 
Instance details

Defined in Libjwt.FFI.Jwt

Methods

pure :: a -> JwtIO a #

(<*>) :: JwtIO (a -> b) -> JwtIO a -> JwtIO b #

liftA2 :: (a -> b -> c) -> JwtIO a -> JwtIO b -> JwtIO c #

(*>) :: JwtIO a -> JwtIO b -> JwtIO b #

(<*) :: JwtIO a -> JwtIO b -> JwtIO a #

MonadThrow JwtIO Source # 
Instance details

Defined in Libjwt.FFI.Jwt

Methods

throwM :: Exception e => e -> JwtIO a #

MonadCatch JwtIO Source # 
Instance details

Defined in Libjwt.FFI.Jwt

Methods

catch :: Exception e => JwtIO a -> (e -> JwtIO a) -> JwtIO a #