Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Data types for the JOSE library.
Synopsis
- newtype Base64Integer = Base64Integer Integer
- _Base64Integer :: Iso' Base64Integer Integer
- data SizedBase64Integer = SizedBase64Integer Int Integer
- makeSizedBase64Integer :: Integer -> SizedBase64Integer
- checkSize :: Int -> SizedBase64Integer -> Parser SizedBase64Integer
- newtype Base64Octets = Base64Octets ByteString
- newtype Base64SHA1 = Base64SHA1 ByteString
- newtype Base64SHA256 = Base64SHA256 ByteString
- newtype Base64X509 = Base64X509 SignedCertificate
- type SignedCertificate = SignedExact Certificate
- data URI
- base64url :: (AsEmpty s1, AsEmpty s2, Cons s1 s1 Word8 Word8, Cons s2 s2 Word8 Word8) => Prism' s1 s2
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.
Instances
FromJSON Base64Integer Source # | |
Defined in Crypto.JOSE.Types parseJSON :: Value -> Parser Base64Integer # parseJSONList :: Value -> Parser [Base64Integer] # | |
ToJSON Base64Integer Source # | |
Defined in Crypto.JOSE.Types toJSON :: Base64Integer -> Value # toEncoding :: Base64Integer -> Encoding # toJSONList :: [Base64Integer] -> Value # toEncodingList :: [Base64Integer] -> Encoding # | |
Show Base64Integer Source # | |
Defined in Crypto.JOSE.Types showsPrec :: Int -> Base64Integer -> ShowS # show :: Base64Integer -> String # showList :: [Base64Integer] -> ShowS # | |
Eq Base64Integer Source # | |
Defined in Crypto.JOSE.Types (==) :: Base64Integer -> Base64Integer -> Bool # (/=) :: Base64Integer -> Base64Integer -> Bool # |
data SizedBase64Integer Source #
A base64url encoded octet sequence interpreted as an integer and where the number of octets carries explicit bit-length information.
Instances
FromJSON SizedBase64Integer Source # | |
Defined in Crypto.JOSE.Types parseJSON :: Value -> Parser SizedBase64Integer # parseJSONList :: Value -> Parser [SizedBase64Integer] # | |
ToJSON SizedBase64Integer Source # | |
Defined in Crypto.JOSE.Types toJSON :: SizedBase64Integer -> Value # toEncoding :: SizedBase64Integer -> Encoding # toJSONList :: [SizedBase64Integer] -> Value # toEncodingList :: [SizedBase64Integer] -> Encoding # | |
Show SizedBase64Integer Source # | |
Defined in Crypto.JOSE.Types showsPrec :: Int -> SizedBase64Integer -> ShowS # show :: SizedBase64Integer -> String # showList :: [SizedBase64Integer] -> ShowS # | |
Eq SizedBase64Integer Source # | |
Defined in Crypto.JOSE.Types (==) :: SizedBase64Integer -> SizedBase64Integer -> Bool # (/=) :: SizedBase64Integer -> SizedBase64Integer -> Bool # |
makeSizedBase64Integer :: Integer -> SizedBase64Integer Source #
Create a SizedBase64Integer'
from an Integer
.
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.
Instances
FromJSON Base64Octets Source # | |
Defined in Crypto.JOSE.Types parseJSON :: Value -> Parser Base64Octets # parseJSONList :: Value -> Parser [Base64Octets] # | |
ToJSON Base64Octets Source # | |
Defined in Crypto.JOSE.Types toJSON :: Base64Octets -> Value # toEncoding :: Base64Octets -> Encoding # toJSONList :: [Base64Octets] -> Value # toEncodingList :: [Base64Octets] -> Encoding # | |
Show Base64Octets Source # | |
Defined in Crypto.JOSE.Types showsPrec :: Int -> Base64Octets -> ShowS # show :: Base64Octets -> String # showList :: [Base64Octets] -> ShowS # | |
Eq Base64Octets Source # | |
Defined in Crypto.JOSE.Types (==) :: Base64Octets -> Base64Octets -> Bool # (/=) :: Base64Octets -> Base64Octets -> Bool # |
newtype Base64SHA1 Source #
A base64url encoded SHA-1 digest. Used for X.509 certificate thumbprints.
Instances
FromJSON Base64SHA1 Source # | |
Defined in Crypto.JOSE.Types parseJSON :: Value -> Parser Base64SHA1 # parseJSONList :: Value -> Parser [Base64SHA1] # | |
ToJSON Base64SHA1 Source # | |
Defined in Crypto.JOSE.Types toJSON :: Base64SHA1 -> Value # toEncoding :: Base64SHA1 -> Encoding # toJSONList :: [Base64SHA1] -> Value # toEncodingList :: [Base64SHA1] -> Encoding # | |
Show Base64SHA1 Source # | |
Defined in Crypto.JOSE.Types showsPrec :: Int -> Base64SHA1 -> ShowS # show :: Base64SHA1 -> String # showList :: [Base64SHA1] -> ShowS # | |
Eq Base64SHA1 Source # | |
Defined in Crypto.JOSE.Types (==) :: Base64SHA1 -> Base64SHA1 -> Bool # (/=) :: Base64SHA1 -> Base64SHA1 -> Bool # |
newtype Base64SHA256 Source #
A base64url encoded SHA-256 digest. Used for X.509 certificate thumbprints.
Instances
FromJSON Base64SHA256 Source # | |
Defined in Crypto.JOSE.Types parseJSON :: Value -> Parser Base64SHA256 # parseJSONList :: Value -> Parser [Base64SHA256] # | |
ToJSON Base64SHA256 Source # | |
Defined in Crypto.JOSE.Types toJSON :: Base64SHA256 -> Value # toEncoding :: Base64SHA256 -> Encoding # toJSONList :: [Base64SHA256] -> Value # toEncodingList :: [Base64SHA256] -> Encoding # | |
Show Base64SHA256 Source # | |
Defined in Crypto.JOSE.Types showsPrec :: Int -> Base64SHA256 -> ShowS # show :: Base64SHA256 -> String # showList :: [Base64SHA256] -> ShowS # | |
Eq Base64SHA256 Source # | |
Defined in Crypto.JOSE.Types (==) :: Base64SHA256 -> Base64SHA256 -> Bool # (/=) :: Base64SHA256 -> Base64SHA256 -> Bool # |
newtype Base64X509 Source #
A base64 encoded X.509 certificate.
Instances
FromJSON Base64X509 Source # | |
Defined in Crypto.JOSE.Types parseJSON :: Value -> Parser Base64X509 # parseJSONList :: Value -> Parser [Base64X509] # | |
ToJSON Base64X509 Source # | |
Defined in Crypto.JOSE.Types toJSON :: Base64X509 -> Value # toEncoding :: Base64X509 -> Encoding # toJSONList :: [Base64X509] -> Value # toEncodingList :: [Base64X509] -> Encoding # | |
Show Base64X509 Source # | |
Defined in Crypto.JOSE.Types showsPrec :: Int -> Base64X509 -> ShowS # show :: Base64X509 -> String # showList :: [Base64X509] -> ShowS # | |
Eq Base64X509 Source # | |
Defined in Crypto.JOSE.Types (==) :: Base64X509 -> Base64X509 -> Bool # (/=) :: Base64X509 -> Base64X509 -> Bool # |
type SignedCertificate = SignedExact Certificate #
A Signed Certificate
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
Data URI | |
Defined in Network.URI 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 # 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 # | |
Generic URI | |
Show URI | |
NFData URI | |
Defined in Network.URI | |
Eq URI | |
Ord URI | |
Lift URI | |
type Rep URI | |
Defined in Network.URI type Rep URI = D1 ('MetaData "URI" "Network.URI" "network-uri-2.6.4.1-DXx94Tarxth8HOiU66mdO8" 'False) (C1 ('MetaCons "URI" 'PrefixI 'True) ((S1 ('MetaSel ('Just "uriScheme") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Just "uriAuthority") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe URIAuth))) :*: (S1 ('MetaSel ('Just "uriPath") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: (S1 ('MetaSel ('Just "uriQuery") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Just "uriFragment") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))))) |