Copyright | 2019 Monadic GmbH |
---|---|
License | BSD3 |
Maintainer | kim@monadic.xyz, alfredo@monadic.xyz, team@monadic.xyz |
Stability | provisional |
Portability | non-portable (GHC extensions) |
Safe Haskell | None |
Language | Haskell2010 |
Type-safe kitchen sink base-N encoding and decoding of strict ByteString
s.
Synopsis
- data Base (a :: Symbol) where
- BaseIdentity :: Base "id"
- Base2 :: Base "2"
- Base16 :: Base "16"
- Base64 :: Base "64"
- Base16upper :: Base "16u"
- Base32hex :: Base "32x"
- Base32hexupper :: Base "32xu"
- Base32hexpad :: Base "32xp"
- Base32hexpadupper :: Base "32xpu"
- Base32 :: Base "32"
- Base32z :: Base "32z"
- Base32upper :: Base "32u"
- Base32pad :: Base "32p"
- Base32padupper :: Base "32pu"
- Base58flickr :: Base "58flickr"
- Base58btc :: Base "58btc"
- Base64pad :: Base "64p"
- Base64url :: Base "64url"
- Base64urlpad :: Base "64urlp"
- data AtBase (b :: Symbol)
- encodedBytes :: AtBase b -> ByteString
- encodedBuilder :: AtBase b -> Builder
- type Base2 = AtBase "2"
- type Base16 = AtBase "16"
- type Base58 = AtBase "58"
- type Base64 = AtBase "64"
- type BaseIdentity = AtBase "id"
- type Base16upper = AtBase "16u"
- type Base32hex = AtBase "16x"
- type Base32hexupper = AtBase "16xu"
- type Base32hexpad = AtBase "16xp"
- type Base32hexpadupper = AtBase "16xup"
- type Base32 = AtBase "32"
- type Base32z = AtBase "32z"
- type Base32upper = AtBase "32u"
- type Base32pad = AtBase "32p"
- type Base32padupper = AtBase "32pu"
- type Base58flickr = AtBase "58flickr"
- type Base58btc = AtBase "58btc"
- type Base64pad = AtBase "64p"
- type Base64url = AtBase "64url"
- type Base64urlpad = AtBase "16urlp"
- data AtBaseCompact (b :: Symbol)
- compact :: AtBase b -> AtBaseCompact b
- expand :: AtBaseCompact b -> AtBase b
- type Base16Of a = Tagged a (AtBase "16")
- type Base58Of a = Tagged a (AtBase "58")
- type Base64Of a = Tagged a (AtBase "64")
- tagWith :: forall k proxy (s :: k) a. proxy s -> a -> Tagged s a
- unTagged :: Tagged s b -> b
- data DeserialiseError
- deserialiseAtBase :: (Serialise a, DecodeBase b) => proxy b -> ByteString -> Either DeserialiseError a
- encodeBase16 :: ByteString -> AtBase "16"
- encodeBase58btc :: ByteString -> AtBase "58btc"
- encodeBase64 :: ByteString -> AtBase "64"
- encodeAtBase :: Base b -> ByteString -> AtBase b
- class DecodeBase (b :: Symbol)
- decodeBase16 :: ByteString -> Maybe ByteString
- decodeBase16Either :: ByteString -> Either String ByteString
- decodeBase58btc :: ByteString -> Either String ByteString
- decodeBase64 :: ByteString -> Maybe ByteString
- decodeBase64Either :: ByteString -> Either String ByteString
- decodeBase64Lenient :: ByteString -> ByteString
- decodeAtBase :: DecodeBase b => proxy b -> ByteString -> Maybe ByteString
- decodeAtBaseEither :: DecodeBase b => proxy b -> ByteString -> Either String ByteString
- decode :: DecodeBase b => AtBase b -> ByteString
- class KnownSymbol b => ValidBase (b :: Symbol)
- validBase16 :: ByteString -> Maybe (AtBase "16")
- validBase16Either :: ByteString -> Either String (AtBase "16")
- validBase58btc :: ByteString -> Maybe (AtBase "58btc")
- validBase58btcEither :: ByteString -> Either String (AtBase "58btc")
- validBase64 :: ByteString -> Maybe (AtBase "64")
- validBase64Either :: ByteString -> Either String (AtBase "64")
- validAtBase :: ValidBase b => proxy b -> ByteString -> Maybe (AtBase b)
- validAtBaseEither :: ValidBase b => proxy b -> ByteString -> Either String (AtBase b)
- validAndDecoded :: DecodeBase b => proxy b -> ByteString -> Maybe (AtBase b, ByteString)
- validAndDecodedEither :: DecodeBase b => proxy b -> ByteString -> Either String (AtBase b, ByteString)
- encodedTextAtBase :: Base b -> Text -> AtBase b
- encodedText :: AtBase b -> Text
- encodedTextBuilder :: AtBase b -> Builder
- format :: Format r (AtBase b -> r)
- formatAtBase :: Format r (AtBase b -> r)
Documentation
data Base (a :: Symbol) where Source #
Supported bases.
BaseIdentity :: Base "id" | |
Base2 :: Base "2" | |
Base16 :: Base "16" | |
Base64 :: Base "64" | |
Base16upper :: Base "16u" | hexadecimal, uppercase alphabet |
Base32hex :: Base "32x" | RFC4648 no padding - highest char |
Base32hexupper :: Base "32xu" | RFC4648 no padding - highest char, uppercase alphabet |
Base32hexpad :: Base "32xp" | RFC4648 with padding |
Base32hexpadupper :: Base "32xpu" | RFC4648 with padding, uppercase alphabet |
Base32 :: Base "32" | RFC4648 no padding |
Base32z :: Base "32z" | z-base-32 (used by Tahoe-LAFS) |
Base32upper :: Base "32u" | RFC4648 no padding, uppercase alphabet |
Base32pad :: Base "32p" | RFC4648 with padding |
Base32padupper :: Base "32pu" | RFC4648 with padding, uppercase alphabet |
Base58flickr :: Base "58flickr" | base58 flickr alphabet |
Base58btc :: Base "58btc" | base58 bitcoint alphabet |
Base64pad :: Base "64p" | RFC4648 with padding (MIME-encoding) |
Base64url :: Base "64url" | RFC4648 no padding |
Base64urlpad :: Base "64urlp" | RFC4648 with padding |
data AtBase (b :: Symbol) Source #
A ByteString
encoded at a specific base.
Instances
Eq (AtBase b) Source # | |
Ord (AtBase b) Source # | |
Defined in Data.ByteString.BaseN | |
KnownSymbol b => Show (AtBase b) Source # | |
ValidBase b => IsString (AtBase b) Source # | |
Defined in Data.ByteString.BaseN fromString :: String -> AtBase b # | |
Hashable (AtBase b) Source # | |
Defined in Data.ByteString.BaseN | |
ToJSON (AtBase b) Source # | |
Defined in Data.ByteString.BaseN | |
ToJSONKey (AtBase b) Source # | |
Defined in Data.ByteString.BaseN toJSONKey :: ToJSONKeyFunction (AtBase b) # toJSONKeyList :: ToJSONKeyFunction [AtBase b] # | |
(ValidBase b, KnownSymbol b) => FromJSON (AtBase b) Source # | |
(ValidBase b, KnownSymbol b) => FromJSONKey (AtBase b) Source # | |
Defined in Data.ByteString.BaseN fromJSONKey :: FromJSONKeyFunction (AtBase b) # | |
NFData (AtBase b) Source # | |
Defined in Data.ByteString.BaseN |
encodedBytes :: AtBase b -> ByteString Source #
Extract the base-n encoded bytes from an AtBase
.
To recover the original ByteString
(*not* base-n encoded), use decode
.
encodedBuilder :: AtBase b -> Builder Source #
Like encodedBytes
, but return a Builder
.
type BaseIdentity = AtBase "id" Source #
type Base16upper = AtBase "16u" Source #
type Base32hexupper = AtBase "16xu" Source #
type Base32hexpad = AtBase "16xp" Source #
type Base32hexpadupper = AtBase "16xup" Source #
type Base32upper = AtBase "32u" Source #
type Base32padupper = AtBase "32pu" Source #
type Base58flickr = AtBase "58flickr" Source #
type Base64urlpad = AtBase "16urlp" Source #
Compact Representation
data AtBaseCompact (b :: Symbol) Source #
A more memory-efficient representation of base-n encoded bytes.
Uses ShortByteString
, recommendations and caveats described there apply.
Instances
compact :: AtBase b -> AtBaseCompact b Source #
expand :: AtBaseCompact b -> AtBase b Source #
Tagged
AtBase
values tagged by the type they're representing.
Re-exports
tagWith :: forall k proxy (s :: k) a. proxy s -> a -> Tagged s a #
Another way to convert a proxy to a tag.
CBOR
Directly go from (presumed to be) base-n encoded ByteString
to
de-Serialise
-able value.
data DeserialiseError Source #
Instances
Show DeserialiseError Source # | |
Defined in Data.ByteString.BaseN showsPrec :: Int -> DeserialiseError -> ShowS # show :: DeserialiseError -> String # showList :: [DeserialiseError] -> ShowS # |
deserialiseAtBase :: (Serialise a, DecodeBase b) => proxy b -> ByteString -> Either DeserialiseError a Source #
Encoding
encodeBase16 :: ByteString -> AtBase "16" Source #
encodeBase58btc :: ByteString -> AtBase "58btc" Source #
>>>
fromAtBase . encodeBase58btc $ "hello world"
"StV1DL6CwTryKyV"
encodeBase64 :: ByteString -> AtBase "64" Source #
encodeAtBase :: Base b -> ByteString -> AtBase b Source #
Encode at a base supplied at runtime.
Decoding Bytes
Decode (presumed to be) base-n encoded ByteString
s to their original
(base-2) value.
class DecodeBase (b :: Symbol) Source #
Instances
decodeBase16 :: ByteString -> Maybe ByteString Source #
decodeBase58btc :: ByteString -> Either String ByteString Source #
\(Bytes bytes) -> decodeBase58btc (fromAtBase $ encodeBase58btc bytes) === Right bytes
decodeBase64 :: ByteString -> Maybe ByteString Source #
decodeAtBase :: DecodeBase b => proxy b -> ByteString -> Maybe ByteString Source #
decodeAtBaseEither :: DecodeBase b => proxy b -> ByteString -> Either String ByteString Source #
Decoding
decode :: DecodeBase b => AtBase b -> ByteString Source #
Recover the original ByteString
of a base-n encoded value.
Untrusted Input
Construct AtBase
s from raw ByteString
s. Note that this attempts to decode
using the functions from $decoding, and throws away the result.
class KnownSymbol b => ValidBase (b :: Symbol) Source #
Instances
validBase16 :: ByteString -> Maybe (AtBase "16") Source #
validBase16Either :: ByteString -> Either String (AtBase "16") Source #
validBase58btc :: ByteString -> Maybe (AtBase "58btc") Source #
validBase58btcEither :: ByteString -> Either String (AtBase "58btc") Source #
validBase64 :: ByteString -> Maybe (AtBase "64") Source #
validBase64Either :: ByteString -> Either String (AtBase "64") Source #
validAtBase :: ValidBase b => proxy b -> ByteString -> Maybe (AtBase b) Source #
validAtBaseEither :: ValidBase b => proxy b -> ByteString -> Either String (AtBase b) Source #
validAndDecoded :: DecodeBase b => proxy b -> ByteString -> Maybe (AtBase b, ByteString) Source #
Like validAtBase
, but also return the decoded ByteString
.
validAndDecodedEither :: DecodeBase b => proxy b -> ByteString -> Either String (AtBase b, ByteString) Source #
Like validAtBaseEither
, but also return the decoded ByteString
.
Text
encodedTextAtBase :: Base b -> Text -> AtBase b Source #
Like encodeAtBase
, but from a Text
value.
encodedText :: AtBase b -> Text Source #
Like encodedBytes
, but returns a Text
value.
encodedTextBuilder :: AtBase b -> Builder Source #
Like encodedBuilder
, but returns a text Builder
.
Formatting
formatAtBase :: Format r (AtBase b -> r) Source #
Format a base-n encoded value.