jose-0.9: JSON Object Signing and Encryption (JOSE) and JSON Web Token (JWT) library
Safe HaskellNone
LanguageHaskell2010

Crypto.JOSE.Types

Description

Data types for the JOSE library.

Synopsis

Documentation

newtype Base64Integer Source #

A base64url encoded octet sequence interpreted as an integer.

The value is encoded in the minimum number of octets (no leading zeros) with the exception of 0 which is encoded as AA. A leading zero when decoding is an error.

Constructors

Base64Integer Integer 

data SizedBase64Integer Source #

A base64url encoded octet sequence interpreted as an integer and where the number of octets carries explicit bit-length information.

makeSizedBase64Integer :: Integer -> SizedBase64Integer Source #

Create a SizedBase64Integer' from an Integer.

genSizedBase64IntegerOf :: Int -> Gen SizedBase64Integer Source #

Generate a SizedBase64Integer of the given number of bytes

checkSize :: Int -> SizedBase64Integer -> Parser SizedBase64Integer Source #

Parsed a SizedBase64Integer with an expected number of bytes.

newtype Base64Octets Source #

A base64url encoded octet sequence. Used for payloads, signatures, symmetric keys, salts, initialisation vectors, etc.

Constructors

Base64Octets ByteString 

newtype Base64SHA1 Source #

A base64url encoded SHA-1 digest. Used for X.509 certificate thumbprints.

Constructors

Base64SHA1 ByteString 

newtype Base64SHA256 Source #

A base64url encoded SHA-256 digest. Used for X.509 certificate thumbprints.

Constructors

Base64SHA256 ByteString 

newtype Base64X509 Source #

A base64 encoded X.509 certificate.

Instances

Instances details
Eq Base64X509 Source # 
Instance details

Defined in Crypto.JOSE.Types

Show Base64X509 Source # 
Instance details

Defined in Crypto.JOSE.Types

ToJSON Base64X509 Source # 
Instance details

Defined in Crypto.JOSE.Types

FromJSON Base64X509 Source # 
Instance details

Defined in Crypto.JOSE.Types

type SignedCertificate = SignedExact Certificate #

A Signed Certificate

data URI #

Represents a general universal resource identifier using its component parts.

For example, for the URI

  foo://anonymous@www.haskell.org:42/ghc?query#frag

the components are:

Instances

Instances details
Eq URI 
Instance details

Defined in Network.URI

Methods

(==) :: URI -> URI -> Bool #

(/=) :: URI -> URI -> Bool #

Data URI 
Instance details

Defined in Network.URI

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> URI -> c URI #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c URI #

toConstr :: URI -> Constr #

dataTypeOf :: URI -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c URI) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c URI) #

gmapT :: (forall b. Data b => b -> b) -> URI -> URI #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> URI -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> URI -> r #

gmapQ :: (forall d. Data d => d -> u) -> URI -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> URI -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> URI -> m URI #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> URI -> m URI #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> URI -> m URI #

Ord URI 
Instance details

Defined in Network.URI

Methods

compare :: URI -> URI -> Ordering #

(<) :: URI -> URI -> Bool #

(<=) :: URI -> URI -> Bool #

(>) :: URI -> URI -> Bool #

(>=) :: URI -> URI -> Bool #

max :: URI -> URI -> URI #

min :: URI -> URI -> URI #

Show URI 
Instance details

Defined in Network.URI

Methods

showsPrec :: Int -> URI -> ShowS #

show :: URI -> String #

showList :: [URI] -> ShowS #

Generic URI 
Instance details

Defined in Network.URI

Associated Types

type Rep URI :: Type -> Type #

Methods

from :: URI -> Rep URI x #

to :: Rep URI x -> URI #

ToJSON URI Source # 
Instance details

Defined in Crypto.JOSE.Types.Orphans

FromJSON URI Source # 
Instance details

Defined in Crypto.JOSE.Types.Orphans

NFData URI 
Instance details

Defined in Network.URI

Methods

rnf :: URI -> () #

Lift URI 
Instance details

Defined in Network.URI

Methods

lift :: URI -> Q Exp #

liftTyped :: URI -> Q (TExp URI) #

type Rep URI 
Instance details

Defined in Network.URI

base64url :: (AsEmpty s1, AsEmpty s2, Cons s1 s1 Word8 Word8, Cons s2 s2 Word8 Word8) => Prism' s1 s2 Source #

Prism for encoding / decoding base64url.

To encode, review base64url. To decode, preview base64url.

Works with any combinations of strict/lazy ByteString.