libjwt-typed-0.2: A Haskell implementation of JSON Web Token (JWT)
Safe HaskellNone
LanguageHaskell2010
Extensions
  • UndecidableInstances
  • MonoLocalBinds
  • TypeFamilies
  • RecordPuns
  • DataKinds
  • StandaloneDeriving
  • DerivingStrategies
  • TypeSynonymInstances
  • FlexibleContexts
  • FlexibleInstances
  • KindSignatures
  • GeneralizedNewtypeDeriving
  • ExplicitNamespaces

Libjwt.Payload

Description

JWT payload structure and convenient builders.

Synopsis

Documentation

data Payload pc ns Source #

JWT payload representation

Constructors

ClaimsSet 

Fields

Instances

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

Defined in Libjwt.Payload

Methods

(==) :: Payload pc ns -> Payload pc ns -> Bool #

(/=) :: Payload pc ns -> Payload pc ns -> Bool #

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

Defined in Libjwt.Payload

Methods

showsPrec :: Int -> Payload pc ns -> ShowS #

show :: Payload pc ns -> String #

showList :: [Payload pc ns] -> ShowS #

(pc ~ Empty, ns ~ 'NoNs) => Default (Payload pc ns) Source # 
Instance details

Defined in Libjwt.Payload

Methods

def :: Payload pc ns #

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

Defined in Libjwt.Payload

Methods

encode :: Payload pc ns -> JwtT -> EncodeResult Source #

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

Defined in Libjwt.Payload

Methods

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

withIssuer :: String -> JwtBuilder any1 any2 Source #

Set iss claim

issuedBy :: String -> JwtBuilder any1 any2 Source #

Set iss claim

withSubject :: String -> JwtBuilder any1 any2 Source #

Set sub claim

issuedTo :: String -> JwtBuilder any1 any2 Source #

Set sub claim

withRecipient :: String -> JwtBuilder any1 any2 Source #

Append one item to aud claim

intendedFor :: String -> JwtBuilder any1 any2 Source #

Append one item to aud claim

withAudience :: [String] -> JwtBuilder any1 any2 Source #

Set aud claim

setTtl :: NominalDiffTime -> JwtBuilder any1 any2 Source #

Set iat claim to currentTime and exp claim to currentTime plus the argument

expiresAt :: UTCTime -> JwtBuilder any1 any2 Source #

Set exp claim

notBefore :: UTCTime -> JwtBuilder any1 any2 Source #

Set nbf claim

notBeforeNow :: JwtBuilder any1 any2 Source #

Set nbf claim to currentTime

notUntil :: NominalDiffTime -> JwtBuilder any1 any2 Source #

Set nbf claim to currentTime plus the argument

issuedNow :: JwtBuilder any1 any2 Source #

Set iat claim to currentTime

withJwtId :: UUID -> JwtBuilder any1 any2 Source #

Set jti claim

data JwtBuilder any1 any2 Source #

Instances

Instances details
Semigroup (JwtBuilder any1 any2) Source # 
Instance details

Defined in Libjwt.Payload

Methods

(<>) :: JwtBuilder any1 any2 -> JwtBuilder any1 any2 -> JwtBuilder any1 any2 #

sconcat :: NonEmpty (JwtBuilder any1 any2) -> JwtBuilder any1 any2 #

stimes :: Integral b => b -> JwtBuilder any1 any2 -> JwtBuilder any1 any2 #

Monoid (JwtBuilder any1 any2) Source # 
Instance details

Defined in Libjwt.Payload

Methods

mempty :: JwtBuilder any1 any2 #

mappend :: JwtBuilder any1 any2 -> JwtBuilder any1 any2 -> JwtBuilder any1 any2 #

mconcat :: [JwtBuilder any1 any2] -> JwtBuilder any1 any2 #

jwtPayload :: (MonadTime m, ToPrivateClaims a, Claims a ~ b, OutNs a ~ ns) => JwtBuilder b ns -> a -> m (Payload b ns) Source #

Create a payload from the builder and the value representing private claims

For example:

jwtPayload
  (withIssuer "myApp" <> withRecipient "https://myApp.com" <> setTtl 300)
  ( #userName ->> "John Doe"
  , #isRoot ->> False
  , #userId ->> (12345 :: Int)
  )

The resulting payload will be the equivalent of:

{
  "aud": [
    "https://myApp.com"
  ],
  "exp": 1599499073,
  "iat": 1599498773,
  "isRoot": false,
  "iss": "myApp",
  "userId": 12345,
  "userName": "JohnDoe"
}

An identical payload can be constructed from the following record type:

data MyClaims = MyClaims { userName :: String
                         , isRoot :: Bool
                         , userId :: Int
                         }
  deriving stock (Eq, Show, Generic)

instance ToPrivateClaims UserClaims

jwtPayload
  (withIssuer "myApp" <> withRecipient "https://myApp.com" <> setTtl 300)
  MyClaims { userName = "John Doe"
           , isRoot   = False
           , userId   = 12345
           }

If you want to assign a namespace to your private claims, you can do:

jwtPayload
    (withIssuer "myApp" <> withRecipient "https://myApp.com" <> setTtl 300)
  $ withNs
      (Ns @"https://myApp.com")
      MyClaims
        { userId    = 12345
        , userName  = JohnDoe
        , isRoot    = False
        }

The resulting payload will be the equivalent of:

{
  "aud": [
    "https://myApp.com"
  ],
  "exp": 1599499073,
  "iat": 1599498773,
  "https://myApp.com/isRoot": false,
  "iss": "myApp",
  "https://myApp.com/userId": 12345,
  "https://myApp.com/userName": "JohnDoe"
}