| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
ASCII.Hexadecimal
Synopsis
- showNatural :: HexStringSuperset string => Case -> Natural -> string
- readNatural :: HexStringSuperset string => string -> Maybe Natural
- showInteger :: StringSuperset string => Case -> Integer -> string
- readInteger :: StringSuperset string => string -> Maybe Integer
- showIntegral :: (StringSuperset string, Integral number) => Case -> number -> string
- readIntegral :: (StringSuperset string, Integral number, Bits number) => string -> Maybe number
- data HexChar
- data HexLetter
- data HexCharBreakdown
- hexLetterD16 :: HexLetter -> Word4
- d16HexLetter :: Word4 -> Maybe HexLetter
- letterHexChar :: Case -> HexLetter -> HexChar
- hexCharLetter :: HexChar -> Maybe HexLetter
- hexAsciiChar :: HexChar -> Char
- asciiCharHex :: Char -> Maybe HexChar
- d16HexChar :: Case -> Word4 -> HexChar
- hexCharD16 :: HexChar -> Word4
- breakDownHexChar :: HexChar -> HexCharBreakdown
- assembleHexChar :: HexCharBreakdown -> HexChar
- class HexCharSuperset char where
- fromHexChar :: HexChar -> char
- isHexChar :: char -> Bool
- toHexCharUnsafe :: char -> HexChar
- toHexCharMaybe :: char -> Maybe HexChar
- class HexStringSuperset string where
- fromHexCharList :: [HexChar] -> string
- isHexString :: string -> Bool
- toHexCharListUnsafe :: string -> [HexChar]
- toHexCharListMaybe :: string -> Maybe [HexChar]
- naturalHexCharMaybe :: Case -> Natural -> Maybe HexChar
- hexCharNatural :: HexChar -> Natural
- naturalHexCharUnsafe :: Case -> Natural -> HexChar
- naturalD16Maybe :: Natural -> Maybe Word4
- d16Natural :: Word4 -> Natural
- naturalD16Unsafe :: Natural -> Word4
- integerHexCharMaybe :: Case -> Integer -> Maybe HexChar
- hexCharInteger :: HexChar -> Integer
- integerHexCharUnsafe :: Case -> Integer -> HexChar
- integerD16Maybe :: Integer -> Maybe Word4
- d16Integer :: Word4 -> Integer
- integerD16Unsafe :: Integer -> Word4
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 5readNatural "-5"=NothingreadNatural "1f"=Just 31readNatural "1F"=Just 31readNatural "xa"=NothingreadNatural ""=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 5readInteger "-5"=Just (-5)readInteger "1f"=Just 31readInteger "1F"=Just 31readInteger "xa"=NothingreadInteger ""=NothingreadInteger "-"=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
The subset of ASCII used to represent hexadecimal numbers:
Constructors
Instances
| HexCharSuperset HexChar Source # | |
| Data HexChar Source # | |
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 # | |
| Bounded HexChar Source # | |
| Enum HexChar Source # | |
| Generic HexChar Source # | |
| Show HexChar Source # | |
| Eq HexChar Source # | |
| Ord HexChar Source # | |
| Hashable HexChar Source # | |
Defined in ASCII.Hexadecimal | |
| HexStringSuperset [HexChar] Source # | |
Defined in ASCII.Hexadecimal | |
| type Rep HexChar Source # | |
Defined in ASCII.Hexadecimal type Rep HexChar = D1 ('MetaData "HexChar" "ASCII.Hexadecimal" "ascii-numbers-1.2.0.2-JMEpF4iwTFDAp3Gjf5xk8D" '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)))))) | |
Letters used as hexadecimal digits above 9, without a notion of case.
Instances
| Data HexLetter Source # | |
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 # | |
| Bounded HexLetter Source # | |
| Enum HexLetter Source # | |
Defined in ASCII.Hexadecimal Methods succ :: HexLetter -> HexLetter # pred :: HexLetter -> HexLetter # fromEnum :: HexLetter -> Int # enumFrom :: HexLetter -> [HexLetter] # enumFromThen :: HexLetter -> HexLetter -> [HexLetter] # enumFromTo :: HexLetter -> HexLetter -> [HexLetter] # enumFromThenTo :: HexLetter -> HexLetter -> HexLetter -> [HexLetter] # | |
| Generic HexLetter Source # | |
| Show HexLetter Source # | |
| Eq HexLetter Source # | |
| Ord HexLetter Source # | |
| Hashable HexLetter Source # | |
Defined in ASCII.Hexadecimal | |
| type Rep HexLetter Source # | |
Defined in ASCII.Hexadecimal type Rep HexLetter = D1 ('MetaData "HexLetter" "ASCII.Hexadecimal" "ascii-numbers-1.2.0.2-JMEpF4iwTFDAp3Gjf5xk8D" '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
Monomorphic character conversions
HexLetter ↔ D16
hexLetterD16 :: HexLetter -> Word4 Source #
HexLetter ↔ HexChar
HexChar ↔ ASCII Char
hexAsciiChar :: HexChar -> Char Source #
HexChar ↔ D16
hexCharD16 :: HexChar -> Word4 Source #
HexChar ↔ HexCharBreakdown
Hexadecimal character superset classes
Of hex character
class HexCharSuperset char where Source #
Minimal complete definition
Methods
fromHexChar :: HexChar -> char Source #
isHexChar :: char -> Bool Source #
toHexCharUnsafe :: char -> HexChar Source #
toHexCharMaybe :: char -> Maybe HexChar Source #
Instances
Of hex character lists
class HexStringSuperset string where Source #
Minimal complete definition
fromHexCharList, (isHexString, toHexCharListUnsafe | toHexCharListMaybe)
Methods
fromHexCharList :: [HexChar] -> string Source #
isHexString :: string -> Bool Source #
toHexCharListUnsafe :: string -> [HexChar] Source #
toHexCharListMaybe :: string -> Maybe [HexChar] Source #
Instances
Character/number conversions
Natural ↔ HexChar
hexCharNatural :: HexChar -> Natural Source #
Natural ↔ D16
d16Natural :: Word4 -> Natural Source #
naturalD16Unsafe :: Natural -> Word4 Source #
Integer ↔ HexChar
hexCharInteger :: HexChar -> Integer Source #
Integer ↔ D16
d16Integer :: Word4 -> Integer Source #
integerD16Unsafe :: Integer -> Word4 Source #