libjwt-typed-0.1: A Haskell implementation of JSON Web Token (JWT)
Safe HaskellNone
LanguageHaskell2010
Extensions
  • OverloadedStrings
  • DefaultSignatures
  • TypeSynonymInstances
  • FlexibleInstances
  • ConstrainedClassMethods
  • MultiParamTypeClasses
  • FunctionalDependencies
  • TupleSections

Libjwt.Classes

Description

The classes in this module are responsible for encoding and decoding values into JWT objects.

Encoding

The encoders are divided into three groups:

  • Native - types: ByteString, Bool, Int, NumericDate and JsonByteString. They are encoded by simply calling the appropriate FFI function
  • Derived - types for which there is an instance of JwtRep. They are converted via rep (transitively) to something we know how to encode
  • Specialized - Maybe and lists

JwtRep typeclass and derived encoders

This typeclass converts a value to its encodable representation. E.g., to encode UUID we first convert it to something we know how to encode (ByteString).

instance JwtRep ByteString UUID where
  rep = UUID.toASCIIBytes

This is an example of derived encoder that calls rep and then uses a different encoder (native) to perform the actual encoding. This is sufficent to encode any single UUID as ByteString is natively supported. Native encoders automatically take care of converting values to JSON format (escaping, quoting, UTF-8 encoding etc).

You can use the same method to extend the library to support your type.

newtype UserName = Un { toText :: Text }
 deriving stock (Show, Eq)

instance JwtRep Text UserName where
 rep   = toText
 unRep = Just . Un   

But there is an easier way. Just use deriving clause

newtype UserName = Un { toText :: Text }
 deriving stock (Show, Eq)
 deriving newtype (JwtRep ByteString)

JsonBuilder and lists

To encode values such as lists, a different strategy has to be used. Because JWT values have to be in JSON format and there is no native support for more complex data structures (such as JSON arrays) we have to do the conversion ourselves. For this we must know how to encode the value as a JSON value

This is the role of JsonBuilder typeclass. You must provide its instance if you want to be able to encode lists of values of a custom type.

If you already have a JwtRep instance, the default implementation (use JsonBuilder of the rep) should be fine

instance JsonBuilder UserName

or

newtype UserName = Un { toText :: Text }
 deriving stock (Show, Eq)
 deriving newtype (JwtRep ByteString, JsonBuilder)

Decoding

The decoders are similarily divided into three groups:

  • Native - types: ByteString, Bool, Int, NumericDate and JsonByteString. Decoded in C
  • Derived - types for which a JwtRep instance exists. They are extracted via unRep (transitively) from something we could decode
  • Specialized - Lists

JwtRep typeclass

JwtRep also knows how to go backwards - from the JWT representation to, maybe, a value. To complete the UUID example

instance JwtRep ByteString UUID where
  rep = toASCIIBytes
  unRep = fromASCIIBytes

Derived decoder will first try to parse a byteString from JSON, and then convert it via unRep to a UUID. Each of these steps can fail - the failure will manifest itself as Libjwt.Exceptions.MissingClaim or Nothing if all you want is Maybe UUID

And of course, JwtRep of UserName handles decoding the same way as described.

JsonParser and lists

JsonParser performs the opposite role of JsonBuilder during decoding. It is used for extracting values out of JSON arrays

You must provide its instance if you want to be able to decode lists of values of a custom type.

And again - the default implementation (unRep <=< jsonParser) should be fine

instance JsonParser UserName

or

newtype UserName = Un { toText :: Text }
 deriving stock (Show, Eq)
 deriving newtype (JwtRep ByteString, JsonBuilder, JsonParser)

Integration with aeson

If you want to work with more complex objects as claims (e.g. lists of records) or you just want to integrate this library with your existing code that uses aeson - it's simple

data Account = MkAccount { account_name :: Text, account_id :: UUID }
  deriving stock (Show, Eq, Generic)

instance FromJSON Account
instance ToJSON Account

instance JwtRep JsonByteString Account where
  rep   = Json . encode
  unRep = decode . toJson

instance JsonBuilder Account
instance JsonParser Account

JsonByteString is for cases where you already have your claims correctly represented as JSON, so you can use aeson (or any other method) to create JsonByteString.

Warning

Do not use NUL characters in strings you encode or decode with this library. Safety is not guaranteed (ie, may crash your program) due to the way libjwt works.

Synopsis

Documentation

class JwtRep a b | b -> a where Source #

Conversion between a and b

If an instance of this typeclass exists for a type b, then JWT encoder and decoder can be derived for that type. This derived encoderdecoder will use the encoderdecoder of a and perform the convertions through this typeclass.

Methods

rep :: b -> a Source #

Convert b to a

unRep :: a -> Maybe b Source #

Try to convert a to b, returning Nothing if unable

Instances

Instances details
JwtRep ByteString String Source # 
Instance details

Defined in Libjwt.Classes

JwtRep ByteString Text Source # 
Instance details

Defined in Libjwt.Classes

JwtRep ByteString UUID Source # 
Instance details

Defined in Libjwt.Classes

JwtRep ByteString ASCII Source # 
Instance details

Defined in Libjwt.Classes

JwtRep ASCII ZonedTime Source # 
Instance details

Defined in Libjwt.Classes

JwtRep ASCII LocalTime Source # 
Instance details

Defined in Libjwt.Classes

JwtRep ASCII UTCTime Source # 
Instance details

Defined in Libjwt.Classes

JwtRep ASCII Day Source # 
Instance details

Defined in Libjwt.Classes

AFlag a => JwtRep ASCII (Flag a) Source # 
Instance details

Defined in Libjwt.Classes

Methods

rep :: Flag a -> ASCII Source #

unRep :: ASCII -> Maybe (Flag a) Source #

JwtRep [a] (NonEmpty a) Source # 
Instance details

Defined in Libjwt.Classes

Methods

rep :: NonEmpty a -> [a] Source #

unRep :: [a] -> Maybe (NonEmpty a) Source #

class JsonBuilder t where Source #

Types that can be converted to a valid JSON representation

This typeclass will be used to encode a list of t values (or a list of tuples whose element is of type t)

Minimal complete definition

Nothing

Methods

jsonBuilder :: t -> Builder Source #

Encode as JSON.

Must generate a valid JSON value: take care of quoting, escaping, UTF-8 encoding etc.

default jsonBuilder :: (JwtRep a t, JsonBuilder a) => t -> Builder Source #

Instances

Instances details
JsonBuilder Bool Source # 
Instance details

Defined in Libjwt.Classes

JsonBuilder Int Source # 
Instance details

Defined in Libjwt.Classes

JsonBuilder String Source # 
Instance details

Defined in Libjwt.Classes

JsonBuilder ByteString Source # 
Instance details

Defined in Libjwt.Classes

JsonBuilder Text Source # 
Instance details

Defined in Libjwt.Classes

JsonBuilder ZonedTime Source # 
Instance details

Defined in Libjwt.Classes

JsonBuilder LocalTime Source # 
Instance details

Defined in Libjwt.Classes

JsonBuilder UTCTime Source # 
Instance details

Defined in Libjwt.Classes

JsonBuilder Day Source # 
Instance details

Defined in Libjwt.Classes

JsonBuilder UUID Source # 
Instance details

Defined in Libjwt.Classes

JsonBuilder ASCII Source # 
Instance details

Defined in Libjwt.Classes

JsonBuilder JsonByteString Source # 
Instance details

Defined in Libjwt.Classes

JsonBuilder NumericDate Source # 
Instance details

Defined in Libjwt.Classes

JsonBuilder a => JsonBuilder [a] Source # 
Instance details

Defined in Libjwt.Classes

Methods

jsonBuilder :: [a] -> Builder Source #

JsonBuilder a => JsonBuilder (Maybe a) Source # 
Instance details

Defined in Libjwt.Classes

AFlag a => JsonBuilder (Flag a) Source # 
Instance details

Defined in Libjwt.Classes

(JsonBuilder a, JsonBuilder b) => JsonBuilder (a, b) Source # 
Instance details

Defined in Libjwt.Classes

Methods

jsonBuilder :: (a, b) -> Builder Source #

class JsonParser a where Source #

Types that can be converted from JSON representation

This typeclass will be used to decode a list of a values (or a list of tuples whose element is of type a)

Minimal complete definition

Nothing

Methods

jsonParser :: JsonToken -> Maybe a Source #

Decode from JSON token.

default jsonParser :: (JwtRep t a, JsonParser t) => JsonToken -> Maybe a Source #

Instances

Instances details
JsonParser Bool Source # 
Instance details

Defined in Libjwt.Classes

JsonParser Int Source # 
Instance details

Defined in Libjwt.Classes

JsonParser String Source # 
Instance details

Defined in Libjwt.Classes

JsonParser ByteString Source # 
Instance details

Defined in Libjwt.Classes

JsonParser Text Source # 
Instance details

Defined in Libjwt.Classes

JsonParser ZonedTime Source # 
Instance details

Defined in Libjwt.Classes

JsonParser LocalTime Source # 
Instance details

Defined in Libjwt.Classes

JsonParser UTCTime Source # 
Instance details

Defined in Libjwt.Classes

JsonParser Day Source # 
Instance details

Defined in Libjwt.Classes

JsonParser UUID Source # 
Instance details

Defined in Libjwt.Classes

JsonParser ASCII Source # 
Instance details

Defined in Libjwt.Classes

JsonParser JsonByteString Source # 
Instance details

Defined in Libjwt.Classes

JsonParser NumericDate Source # 
Instance details

Defined in Libjwt.Classes

JsonParser a => JsonParser [a] Source # 
Instance details

Defined in Libjwt.Classes

Methods

jsonParser :: JsonToken -> Maybe [a] Source #

JsonParser a => JsonParser (Maybe a) Source # 
Instance details

Defined in Libjwt.Classes

AFlag a => JsonParser (Flag a) Source # 
Instance details

Defined in Libjwt.Classes

(JsonParser a, JsonParser b) => JsonParser (a, b) Source # 
Instance details

Defined in Libjwt.Classes

Methods

jsonParser :: JsonToken -> Maybe (a, b) Source #

data JsonToken Source #

Low-level representation of JSON tokenization. Tokens are an exact representation of the underlying JSON, ie no conversions or unescaping has been performed.

The only exception is JsStr which is already unquoted (JsStr value is the string between the first and last quotation marks of the corresponding JSON string).

JSON objects are not parsed at all, but presented as one byte string (JsBlob).