jose-0.6.0.3: Javascript Object Signing and Encryption and JSON Web Token library

Safe HaskellNone
LanguageHaskell98

Crypto.JOSE.Types

Description

Data types for the JOSE library.

Synopsis

Documentation

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.

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

Eq URI 

Methods

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

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

Data 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 :: (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 

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 

Methods

showsPrec :: Int -> URI -> ShowS #

show :: URI -> String #

showList :: [URI] -> ShowS #

Generic URI 

Associated Types

type Rep URI :: * -> * #

Methods

from :: URI -> Rep URI x #

to :: Rep URI x -> URI #

NFData URI 

Methods

rnf :: URI -> () #

type Rep 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.