ascii-numbers-1.0.0.0: ASCII representations of numbers
Safe HaskellNone
LanguageHaskell2010

ASCII.Hexadecimal

Synopsis

Read/show for numeric strings

Natural

showNatural :: HexStringSuperset string => Case -> Natural -> string Source #

Examples:

  • showNatural LowerCase 12 = "c"
  • showNatural UpperCase (256 + 12) = "10C"
  • showNatural UpperCase 0 = "0"

readNatural :: HexStringSuperset string => string -> Maybe Natural Source #

Examples:

  • readNatural "5" = Just 5
  • readNatural "-5" = Nothing
  • readNatural "1f" = Just 31
  • readNatural "1F" = Just 31
  • readNatural "xa" = Nothing
  • readNatural "" = Nothing

Integer

showInteger :: StringSuperset string => Case -> Integer -> string Source #

Examples:

  • showInteger LowerCase 12 = "c"
  • showInteger LowerCase (negate 12) = "-c"
  • showInteger UpperCase (256 + 12) = "10C"
  • showInteger UpperCase (negate (256 + 12)) = "-10C"
  • showInteger UpperCase 0 = "0"

readInteger :: StringSuperset string => string -> Maybe Integer Source #

Examples:

  • readInteger "5" = Just 5
  • readInteger "-5" = Just (-5)
  • readInteger "1f" = Just 31
  • readInteger "1F" = Just 31
  • readInteger "xa" = Nothing
  • readInteger "" = Nothing
  • readInteger "-" = Nothing

Integral

showIntegral :: (StringSuperset string, Integral number) => Case -> number -> string Source #

readIntegral :: (StringSuperset string, Integral number, Bits number) => string -> Maybe number Source #

Examples:

  • readIntegral "0014" = Just (20 :: Word8)
  • readIntegral "" = (Nothing :: Maybe Word8)
  • readIntegral "-4" = (Nothing :: Maybe Word8)
  • readIntegral "1234" = (Nothing :: Maybe Word8)

Various digit types

data D16 Source #

A whole number between 0 and 15

Constructors

D0

Zero

D1

One

D2

Two

D3

Three

D4

Four

D5

Five

D6

Six

D7

Seven

D8

Eight

D9

Nine

D10

Ten (A)

D11

Eleven (B)

D12

Twelve (C)

D13

Thirteen (D)

D14

Fourteen (E)

D15

Fifteen (F)

Instances

Instances details
Bounded D16 Source # 
Instance details

Defined in ASCII.Hexadecimal

Methods

minBound :: D16 #

maxBound :: D16 #

Enum D16 Source # 
Instance details

Defined in ASCII.Hexadecimal

Methods

succ :: D16 -> D16 #

pred :: D16 -> D16 #

toEnum :: Int -> D16 #

fromEnum :: D16 -> Int #

enumFrom :: D16 -> [D16] #

enumFromThen :: D16 -> D16 -> [D16] #

enumFromTo :: D16 -> D16 -> [D16] #

enumFromThenTo :: D16 -> D16 -> D16 -> [D16] #

Eq D16 Source # 
Instance details

Defined in ASCII.Hexadecimal

Methods

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

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

Data D16 Source # 
Instance details

Defined in ASCII.Hexadecimal

Methods

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

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

toConstr :: D16 -> Constr #

dataTypeOf :: D16 -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord D16 Source # 
Instance details

Defined in ASCII.Hexadecimal

Methods

compare :: D16 -> D16 -> Ordering #

(<) :: D16 -> D16 -> Bool #

(<=) :: D16 -> D16 -> Bool #

(>) :: D16 -> D16 -> Bool #

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

max :: D16 -> D16 -> D16 #

min :: D16 -> D16 -> D16 #

Show D16 Source # 
Instance details

Defined in ASCII.Hexadecimal

Methods

showsPrec :: Int -> D16 -> ShowS #

show :: D16 -> String #

showList :: [D16] -> ShowS #

Generic D16 Source # 
Instance details

Defined in ASCII.Hexadecimal

Associated Types

type Rep D16 :: Type -> Type #

Methods

from :: D16 -> Rep D16 x #

to :: Rep D16 x -> D16 #

Hashable D16 Source # 
Instance details

Defined in ASCII.Hexadecimal

Methods

hashWithSalt :: Int -> D16 -> Int #

hash :: D16 -> Int #

type Rep D16 Source # 
Instance details

Defined in ASCII.Hexadecimal

type Rep D16 = D1 ('MetaData "D16" "ASCII.Hexadecimal" "ascii-numbers-1.0.0.0-Ph9fR7aOEX2uBqj267gHs" 'False) ((((C1 ('MetaCons "D0" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "D1" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "D2" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "D3" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "D4" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "D5" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "D6" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "D7" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "D8" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "D9" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "D10" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "D11" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "D12" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "D13" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "D14" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "D15" 'PrefixI 'False) (U1 :: Type -> Type)))))

data HexChar Source #

The subset of ASCII used to represent hexadecimal numbers:

Instances

Instances details
Bounded HexChar Source # 
Instance details

Defined in ASCII.Hexadecimal

Enum HexChar Source # 
Instance details

Defined in ASCII.Hexadecimal

Eq HexChar Source # 
Instance details

Defined in ASCII.Hexadecimal

Methods

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

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

Data HexChar Source # 
Instance details

Defined in ASCII.Hexadecimal

Methods

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

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

toConstr :: HexChar -> Constr #

dataTypeOf :: HexChar -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord HexChar Source # 
Instance details

Defined in ASCII.Hexadecimal

Show HexChar Source # 
Instance details

Defined in ASCII.Hexadecimal

Generic HexChar Source # 
Instance details

Defined in ASCII.Hexadecimal

Associated Types

type Rep HexChar :: Type -> Type #

Methods

from :: HexChar -> Rep HexChar x #

to :: Rep HexChar x -> HexChar #

Hashable HexChar Source # 
Instance details

Defined in ASCII.Hexadecimal

Methods

hashWithSalt :: Int -> HexChar -> Int #

hash :: HexChar -> Int #

HexCharSuperset HexChar Source # 
Instance details

Defined in ASCII.Hexadecimal

HexStringSuperset [HexChar] Source # 
Instance details

Defined in ASCII.Hexadecimal

type Rep HexChar Source # 
Instance details

Defined in ASCII.Hexadecimal

type Rep HexChar = D1 ('MetaData "HexChar" "ASCII.Hexadecimal" "ascii-numbers-1.0.0.0-Ph9fR7aOEX2uBqj267gHs" 'False) ((((C1 ('MetaCons "Digit0" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Digit1" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Digit2" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Digit3" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Digit4" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Digit5" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Digit6" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Digit7" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "Digit8" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Digit9" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CapitalLetterA" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "CapitalLetterB" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CapitalLetterC" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CapitalLetterD" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CapitalLetterE" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CapitalLetterF" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "SmallLetterA" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "SmallLetterB" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SmallLetterC" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "SmallLetterD" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "SmallLetterE" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SmallLetterF" 'PrefixI 'False) (U1 :: Type -> Type))))))

data HexLetter Source #

Letters used as hexadecimal digits above 9, without a notion of case.

Instances

Instances details
Bounded HexLetter Source # 
Instance details

Defined in ASCII.Hexadecimal

Enum HexLetter Source # 
Instance details

Defined in ASCII.Hexadecimal

Eq HexLetter Source # 
Instance details

Defined in ASCII.Hexadecimal

Data HexLetter Source # 
Instance details

Defined in ASCII.Hexadecimal

Methods

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

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

toConstr :: HexLetter -> Constr #

dataTypeOf :: HexLetter -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord HexLetter Source # 
Instance details

Defined in ASCII.Hexadecimal

Show HexLetter Source # 
Instance details

Defined in ASCII.Hexadecimal

Generic HexLetter Source # 
Instance details

Defined in ASCII.Hexadecimal

Associated Types

type Rep HexLetter :: Type -> Type #

Hashable HexLetter Source # 
Instance details

Defined in ASCII.Hexadecimal

type Rep HexLetter Source # 
Instance details

Defined in ASCII.Hexadecimal

type Rep HexLetter = D1 ('MetaData "HexLetter" "ASCII.Hexadecimal" "ascii-numbers-1.0.0.0-Ph9fR7aOEX2uBqj267gHs" 'False) ((C1 ('MetaCons "LetterA" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "LetterB" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LetterC" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "LetterD" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "LetterE" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LetterF" 'PrefixI 'False) (U1 :: Type -> Type))))

data HexCharBreakdown Source #

Instances

Instances details
Bounded HexCharBreakdown Source #

Behaves the same as HexChar

Instance details

Defined in ASCII.Hexadecimal

Enum HexCharBreakdown Source #

Behaves the same as HexChar

Instance details

Defined in ASCII.Hexadecimal

Eq HexCharBreakdown Source # 
Instance details

Defined in ASCII.Hexadecimal

Data HexCharBreakdown Source # 
Instance details

Defined in ASCII.Hexadecimal

Methods

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

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

toConstr :: HexCharBreakdown -> Constr #

dataTypeOf :: HexCharBreakdown -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord HexCharBreakdown Source # 
Instance details

Defined in ASCII.Hexadecimal

Show HexCharBreakdown Source # 
Instance details

Defined in ASCII.Hexadecimal

Generic HexCharBreakdown Source # 
Instance details

Defined in ASCII.Hexadecimal

Associated Types

type Rep HexCharBreakdown :: Type -> Type #

Hashable HexCharBreakdown Source # 
Instance details

Defined in ASCII.Hexadecimal

type Rep HexCharBreakdown Source # 
Instance details

Defined in ASCII.Hexadecimal

Monomorphic character conversions

HexLetter ↔ D16

HexLetter ↔ HexChar

HexChar ↔ ASCII Char

HexChar ↔ D16

HexChar ↔ HexCharBreakdown

Hexadecimal character superset classes

Of hex character

class HexCharSuperset char where Source #

Minimal complete definition

fromHexChar, (isHexChar, toHexCharUnsafe | toHexCharMaybe)

Of hex character lists

class HexStringSuperset string where Source #

Instances

Instances details
HexStringSuperset ByteString Source # 
Instance details

Defined in ASCII.Hexadecimal

HexStringSuperset ByteString Source # 
Instance details

Defined in ASCII.Hexadecimal

HexStringSuperset Builder Source # 
Instance details

Defined in ASCII.Hexadecimal

HexStringSuperset Builder Source # 
Instance details

Defined in ASCII.Hexadecimal

HexStringSuperset Text Source # 
Instance details

Defined in ASCII.Hexadecimal

HexStringSuperset Text Source # 
Instance details

Defined in ASCII.Hexadecimal

HexStringSuperset [Char] Source # 
Instance details

Defined in ASCII.Hexadecimal

HexStringSuperset [Char] Source # 
Instance details

Defined in ASCII.Hexadecimal

HexStringSuperset [HexChar] Source # 
Instance details

Defined in ASCII.Hexadecimal

HexStringSuperset char => HexStringSuperset (ASCII char) Source # 
Instance details

Defined in ASCII.Hexadecimal

Character/number conversions

Natural ↔ HexChar

Natural ↔ D16

Integer ↔ HexChar

Integer ↔ D16