ascii-numbers-1.2.0.0: ASCII representations of numbers
Safe HaskellSafe-Inferred
LanguageHaskell2010

ASCII.Decimal

Synopsis

Read/show for numeric strings

Natural

showNatural :: DigitStringSuperset string => Natural -> string Source #

Examples:

  • showNatural 0 = "0"
  • showNatural 268 = "268"

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

Examples:

  • readNatural "0" = Just 0
  • readNatural "268" = Just 268
  • readNatural "0004" = Just 4
  • readNatural "" = Nothing
  • readNatural "-4" = Nothing
  • readNatural "12345678901234567890" = Just 12345678901234567890

Integer

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

Examples:

  • showInteger 0 = "0"
  • showInteger 12 = "12"
  • showInteger (negate 12) = "-12"

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

Examples:

  • readInteger "0" = Just 0
  • readInteger "268" = Just 268
  • readInteger "0004" = Just 4
  • readInteger "" = Nothing
  • readInteger "-4" = Just (-4)
  • readInteger "12345678901234567890" = Just 12345678901234567890

Integral

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

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

Examples:

  • readIntegral "0" = Just (0 :: Word8)
  • readIntegral "175" = Just (175 :: Word8)
  • readIntegral "268" = (Nothing :: Maybe Word8)
  • readIntegral "0004" = Just (4 :: Word8)
  • readIntegral "" = (Nothing :: Maybe Word8)
  • readIntegral "-4" = (Nothing :: Maybe Word8)
  • readIntegral "12345678901234567890" = (Nothing :: Maybe Word8)

The digit type

data Digit Source #

The subset of ASCII used to represent unsigned decimal numbers:

Constructors

Digit0

Zero

Digit1

One

Digit2

Two

Digit3

Three

Digit4

Four

Digit5

Five

Digit6

Six

Digit7

Seven

Digit8

Eight

Digit9

Nine

Instances

Instances details
DigitSuperset Digit Source # 
Instance details

Defined in ASCII.Decimal

Data Digit Source # 
Instance details

Defined in ASCII.Decimal

Methods

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

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

toConstr :: Digit -> Constr #

dataTypeOf :: Digit -> DataType #

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

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

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

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

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

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

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

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

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

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

Bounded Digit Source # 
Instance details

Defined in ASCII.Decimal

Enum Digit Source # 
Instance details

Defined in ASCII.Decimal

Generic Digit Source # 
Instance details

Defined in ASCII.Decimal

Associated Types

type Rep Digit :: Type -> Type #

Methods

from :: Digit -> Rep Digit x #

to :: Rep Digit x -> Digit #

Show Digit Source # 
Instance details

Defined in ASCII.Decimal

Methods

showsPrec :: Int -> Digit -> ShowS #

show :: Digit -> String #

showList :: [Digit] -> ShowS #

Eq Digit Source # 
Instance details

Defined in ASCII.Decimal

Methods

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

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

Ord Digit Source # 
Instance details

Defined in ASCII.Decimal

Methods

compare :: Digit -> Digit -> Ordering #

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

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

(>) :: Digit -> Digit -> Bool #

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

max :: Digit -> Digit -> Digit #

min :: Digit -> Digit -> Digit #

Hashable Digit Source # 
Instance details

Defined in ASCII.Decimal

Methods

hashWithSalt :: Int -> Digit -> Int #

hash :: Digit -> Int #

DigitStringSuperset [Digit] Source # 
Instance details

Defined in ASCII.Decimal

type Rep Digit Source # 
Instance details

Defined in ASCII.Decimal

type Rep Digit = D1 ('MetaData "Digit" "ASCII.Decimal" "ascii-numbers-1.2.0.0-EgPb9BKveBi2bByYv4gh7X" '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)))))

Decimal digit superset classes

Of digit

class DigitSuperset char where Source #

Minimal complete definition

fromDigit, (isDigit, toDigitUnsafe | toDigitMaybe)

Methods

fromDigit :: Digit -> char Source #

isDigit :: char -> Bool Source #

toDigitUnsafe :: char -> Digit Source #

toDigitMaybe :: char -> Maybe Digit Source #

Of digit lists

class DigitStringSuperset string where Source #

Methods

fromDigitList :: [Digit] -> string Source #

isDigitString :: string -> Bool Source #

toDigitListUnsafe :: string -> [Digit] Source #

toDigitListMaybe :: string -> Maybe [Digit] Source #

Instances

Instances details
DigitStringSuperset Builder Source # 
Instance details

Defined in ASCII.Decimal

DigitStringSuperset ByteString Source # 
Instance details

Defined in ASCII.Decimal

DigitStringSuperset ByteString Source # 
Instance details

Defined in ASCII.Decimal

DigitStringSuperset Text Source # 
Instance details

Defined in ASCII.Decimal

DigitStringSuperset Builder Source # 
Instance details

Defined in ASCII.Decimal

DigitStringSuperset Text Source # 
Instance details

Defined in ASCII.Decimal

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

Defined in ASCII.Decimal

DigitStringSuperset [Char] Source # 
Instance details

Defined in ASCII.Decimal

DigitStringSuperset [Digit] Source # 
Instance details

Defined in ASCII.Decimal

DigitStringSuperset [Char] Source # 
Instance details

Defined in ASCII.Decimal

Character/number conversions

Natural

naturalDigitMaybe :: Natural -> Maybe Digit Source #

Examples:

  • naturalDigitMaybe 5 = Just Digit5
  • naturalDigitMaybe 12 = Nothing

Integer

integerDigitMaybe :: Integer -> Maybe Digit Source #

Examples:

  • integerDigitMaybe 5 = Just Digit5
  • integerDigitMaybe 12 = Nothing