Safe Haskell | None |
---|---|
Language | GHC2021 |
Binrep.Type.AsciiNat
Description
Naturals represented via ASCII digits.
A concept which sees occasional use in places where neither speed nor size efficiency matter. The tar file format uses it, apparently to sidestep making a decision on byte ordering. Pretty silly.
As with other binrep string-likes, you probably want to wrap this with
Sized
or SizePrefixed
.
We use a refinement to permit using any numeric type, while ensuring that negative values are not permitted.
Synopsis
- data AsciiNat (base :: Natural)
- asciiNatCompare :: forall a (bl :: Natural) (br :: Natural). Ord a => Refined (AsciiNat bl) a -> Refined (AsciiNat br) a -> Ordering
- class HasBaseOps a where
- sizeInBase# :: Word# -> a -> Word#
- sizeInBaseWordSize :: Integral a => Word# -> a -> Word#
- getAsciiNatByByte :: Num a => a -> Builder -> (a -> Maybe a) -> Getter a
- unsafeDigits :: forall b a. (Integral a, Integral b) => a -> a -> NonEmpty b
- asciiBytesToNat :: Num a => (a -> Maybe a) -> a -> ByteString -> Either Word8 a
- parseBinaryAsciiDigit :: (Num a, Ord a) => a -> Maybe a
- parseOctalAsciiDigit :: (Num a, Ord a) => a -> Maybe a
- parseDecimalAsciiDigit :: (Num a, Ord a) => a -> Maybe a
- parseHexAsciiDigit :: (Num a, Ord a) => a -> Maybe a
- unsafeHexDigitToAsciiLower :: (Num a, Ord a) => a -> a
Documentation
data AsciiNat (base :: Natural) Source #
A natural represented in binary as an ASCII string, where each character is a digit in the given base.
Only certain bases are supported: 2, 8, 10 and 16.
Hex parsing permits mixed case digits when parsing (1-9a-fA-F
), and
serializes with lower-case ASCII hex digits.
Instances
Predicate (AsciiNat base :: Type) Source # | |
Defined in Binrep.Type.AsciiNat | |
(KnownPredicateName (AsciiNat base), Num a, Ord a) => Refine (AsciiNat base :: Type) a Source # | |
Defined in Binrep.Type.AsciiNat | |
(HasBaseOps a, KnownNat base) => BLen (Refined (AsciiNat base) a) Source # | The bytelength of an |
(Num a, Ord a) => Get (Refined (AsciiNat 2) a) Source # | Parse a binary (base 2) ASCII natural to any |
(Num a, Ord a) => Get (Refined (AsciiNat 8) a) Source # | Parse an octal (base 8) ASCII natural to any |
(Num a, Ord a) => Get (Refined (AsciiNat 10) a) Source # | Parse a decimal (base 10) ASCII natural to any |
(Num a, Ord a) => Get (Refined (AsciiNat 16) a) Source # | Parse a hex (base 16) ASCII natural to any Parses lower and upper case (mixed permitted). |
Integral a => Put (Refined (AsciiNat 2) a) Source # | Serialize any term of an |
Integral a => Put (Refined (AsciiNat 8) a) Source # | Serialize any term of an |
Integral a => Put (Refined (AsciiNat 10) a) Source # | Serialize any term of an |
Integral a => Put (Refined (AsciiNat 16) a) Source # | Serialize any term of an Uses lower-case ASCII. |
type PredicateName d (AsciiNat base :: Type) Source # | |
Defined in Binrep.Type.AsciiNat |
asciiNatCompare :: forall a (bl :: Natural) (br :: Natural). Ord a => Refined (AsciiNat bl) a -> Refined (AsciiNat br) a -> Ordering Source #
Compare two AsciiNat
s, ignoring base information.
class HasBaseOps a where Source #
Instances
HasBaseOps Int16 Source # | |
Defined in Binrep.Type.AsciiNat | |
HasBaseOps Int32 Source # | |
Defined in Binrep.Type.AsciiNat | |
HasBaseOps Int64 Source # | TODO unsafe for 32-bit platform |
Defined in Binrep.Type.AsciiNat | |
HasBaseOps Int8 Source # | |
Defined in Binrep.Type.AsciiNat | |
HasBaseOps Word16 Source # | |
Defined in Binrep.Type.AsciiNat | |
HasBaseOps Word32 Source # | |
Defined in Binrep.Type.AsciiNat | |
HasBaseOps Word64 Source # | TODO unsafe for 32-bit platform |
Defined in Binrep.Type.AsciiNat | |
HasBaseOps Word8 Source # | |
Defined in Binrep.Type.AsciiNat | |
HasBaseOps Natural Source # | |
Defined in Binrep.Type.AsciiNat | |
HasBaseOps Int Source # |
|
Defined in Binrep.Type.AsciiNat | |
HasBaseOps Word Source # | |
Defined in Binrep.Type.AsciiNat |
sizeInBaseWordSize :: Integral a => Word# -> a -> Word# Source #
Safe for types smaller than a Word
.
Uses ghc-bignum internals. Slightly unwrapped for better performance.
One could perhaps write faster algorithms for smaller primitive types too... but performance increase would be minimal if even present.
getAsciiNatByByte :: Num a => a -> Builder -> (a -> Maybe a) -> Getter a Source #
Parse an ASCII natural in the given base with the given digit parser.
Parses byte-by-byte. As such, it only supports bases up to 256.
unsafeDigits :: forall b a. (Integral a, Integral b) => a -> a -> NonEmpty b Source #
Get the digits in the given number as rendered in the given base.
Digits will be between 0-base. The return type must be sized to support this.
Base must be > 2. This is not checked. (Internal function eh.)
Note the NonEmpty
return type. Returns [0]
for 0 input. (This does not match
ghc-bignum's sizeInBase
primitives!)
asciiBytesToNat :: Num a => (a -> Maybe a) -> a -> ByteString -> Either Word8 a Source #
unsafeHexDigitToAsciiLower :: (Num a, Ord a) => a -> a Source #
May only be called with 0<=n<=15.