binrep-0.3.1: Encode precise binary representations directly in types
Safe HaskellSafe-Inferred
LanguageHaskell2010

Binrep.Type.AsciiNat

Description

Naturals represented via ASCII numerals.

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. Though digits are encoded "big-endian", so, uh. I don't get it.

I don't really see the usage of these. It seems silly and inefficient, aimed solely at easing debugging.

Synopsis

Documentation

newtype AsciiNat (base :: Natural) Source #

A Natural represented in binary as an ASCII string, where each character a is a digit in the given base (> 1).

Show instances display the stored number in the given base. If the base has a common prefix (e.g. 0x for hex), it is used.

Constructors

AsciiNat 

Fields

Instances

Instances details
KnownNat base => Data (AsciiNat base) Source # 
Instance details

Defined in Binrep.Type.AsciiNat

Methods

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

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

toConstr :: AsciiNat base -> Constr #

dataTypeOf :: AsciiNat base -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic (AsciiNat base) Source # 
Instance details

Defined in Binrep.Type.AsciiNat

Associated Types

type Rep (AsciiNat base) :: Type -> Type #

Methods

from :: AsciiNat base -> Rep (AsciiNat base) x #

to :: Rep (AsciiNat base) x -> AsciiNat base #

Show (AsciiNat 2) Source # 
Instance details

Defined in Binrep.Type.AsciiNat

Methods

showsPrec :: Int -> AsciiNat 2 -> ShowS #

show :: AsciiNat 2 -> String #

showList :: [AsciiNat 2] -> ShowS #

Show (AsciiNat 8) Source # 
Instance details

Defined in Binrep.Type.AsciiNat

Methods

showsPrec :: Int -> AsciiNat 8 -> ShowS #

show :: AsciiNat 8 -> String #

showList :: [AsciiNat 8] -> ShowS #

Show (AsciiNat 10) Source # 
Instance details

Defined in Binrep.Type.AsciiNat

Methods

showsPrec :: Int -> AsciiNat 10 -> ShowS #

show :: AsciiNat 10 -> String #

showList :: [AsciiNat 10] -> ShowS #

Show (AsciiNat 16) Source # 
Instance details

Defined in Binrep.Type.AsciiNat

Methods

showsPrec :: Int -> AsciiNat 16 -> ShowS #

show :: AsciiNat 16 -> String #

showList :: [AsciiNat 16] -> ShowS #

KnownNat base => BLen (AsciiNat base) Source #

The bytelength of an AsciiNat is the number of digits in the number in the given base. We can calculate this generically with great efficiency using GHC primitives.

Instance details

Defined in Binrep.Type.AsciiNat

Associated Types

type CBLen (AsciiNat base) :: Natural Source #

Methods

blen :: AsciiNat base -> BLenT Source #

Get (AsciiNat 8) Source # 
Instance details

Defined in Binrep.Type.AsciiNat

Methods

get :: Getter (AsciiNat 8) Source #

Put (AsciiNat 8) Source # 
Instance details

Defined in Binrep.Type.AsciiNat

Methods

put :: AsciiNat 8 -> Builder Source #

Eq (AsciiNat base) Source # 
Instance details

Defined in Binrep.Type.AsciiNat

Methods

(==) :: AsciiNat base -> AsciiNat base -> Bool #

(/=) :: AsciiNat base -> AsciiNat base -> Bool #

Ord (AsciiNat base) Source # 
Instance details

Defined in Binrep.Type.AsciiNat

Methods

compare :: AsciiNat base -> AsciiNat base -> Ordering #

(<) :: AsciiNat base -> AsciiNat base -> Bool #

(<=) :: AsciiNat base -> AsciiNat base -> Bool #

(>) :: AsciiNat base -> AsciiNat base -> Bool #

(>=) :: AsciiNat base -> AsciiNat base -> Bool #

max :: AsciiNat base -> AsciiNat base -> AsciiNat base #

min :: AsciiNat base -> AsciiNat base -> AsciiNat base #

type Rep (AsciiNat base) Source # 
Instance details

Defined in Binrep.Type.AsciiNat

type Rep (AsciiNat base) = D1 ('MetaData "AsciiNat" "Binrep.Type.AsciiNat" "binrep-0.3.1-inplace" 'True) (C1 ('MetaCons "AsciiNat" 'PrefixI 'True) (S1 ('MetaSel ('Just "getAsciiNat") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Natural)))
type CBLen (AsciiNat base) Source # 
Instance details

Defined in Binrep.Type.AsciiNat

type CBLen (AsciiNat base) = TypeError ('Text "No CBLen associated family instance defined for " :<>: 'ShowType (AsciiNat base)) :: Natural

asciiNatCompare :: AsciiNat b1 -> AsciiNat b2 -> Ordering Source #

Compare two AsciiNats with arbitrary bases.

digits :: forall b a. (Integral a, Integral b) => a -> a -> NonEmpty b Source #