ascii-numbers-1.0.0.0: ASCII representations of numbers
Safe HaskellNone
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 D10 #

A whole number between 0 and 9

Constructors

D0

Zero

D1

One

D2

Two

D3

Three

D4

Four

D5

Five

D6

Six

D7

Seven

D8

Eight

D9

Nine

Instances

Instances details
Bounded D10 
Instance details

Defined in D10.Safe.Type

Methods

minBound :: D10 #

maxBound :: D10 #

Enum D10 
Instance details

Defined in D10.Safe.Type

Methods

succ :: D10 -> D10 #

pred :: D10 -> D10 #

toEnum :: Int -> D10 #

fromEnum :: D10 -> Int #

enumFrom :: D10 -> [D10] #

enumFromThen :: D10 -> D10 -> [D10] #

enumFromTo :: D10 -> D10 -> [D10] #

enumFromThenTo :: D10 -> D10 -> D10 -> [D10] #

Eq D10 
Instance details

Defined in D10.Safe.Type

Methods

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

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

Data D10 
Instance details

Defined in D10.Safe.Type

Methods

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

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

toConstr :: D10 -> Constr #

dataTypeOf :: D10 -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord D10 
Instance details

Defined in D10.Safe.Type

Methods

compare :: D10 -> D10 -> Ordering #

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

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

(>) :: D10 -> D10 -> Bool #

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

max :: D10 -> D10 -> D10 #

min :: D10 -> D10 -> D10 #

Show D10 
Instance details

Defined in D10.Safe.Type

Methods

showsPrec :: Int -> D10 -> ShowS #

show :: D10 -> String #

showList :: [D10] -> ShowS #

Generic D10 
Instance details

Defined in D10.Safe.Type

Associated Types

type Rep D10 :: Type -> Type #

Methods

from :: D10 -> Rep D10 x #

to :: Rep D10 x -> D10 #

Hashable D10 
Instance details

Defined in D10.Safe.Type

Methods

hashWithSalt :: Int -> D10 -> Int #

hash :: D10 -> Int #

DigitSuperset D10 Source # 
Instance details

Defined in ASCII.Decimal

DigitStringSuperset [D10] Source # 
Instance details

Defined in ASCII.Decimal

type Rep D10 
Instance details

Defined in D10.Safe.Type

type Rep D10 = D1 ('MetaData "D10" "D10.Safe.Type" "d10-1.0.1.0-9ktrmbFvcHrFz0mMEocWkQ" '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)))))

Decimal digit superset classes

Of digit

class DigitSuperset char where Source #

Minimal complete definition

fromDigit, (isDigit, toDigitUnsafe | toDigitMaybe)

Methods

fromDigit :: D10 -> char Source #

isDigit :: char -> Bool Source #

toDigitUnsafe :: char -> D10 Source #

toDigitMaybe :: char -> Maybe D10 Source #

Of digit lists

class DigitStringSuperset string where Source #

Methods

fromDigitList :: [D10] -> string Source #

isDigitString :: string -> Bool Source #

toDigitListUnsafe :: string -> [D10] Source #

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

Instances

Instances details
DigitStringSuperset ByteString Source # 
Instance details

Defined in ASCII.Decimal

DigitStringSuperset ByteString Source # 
Instance details

Defined in ASCII.Decimal

DigitStringSuperset Builder 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 Text Source # 
Instance details

Defined in ASCII.Decimal

DigitStringSuperset [Char] Source # 
Instance details

Defined in ASCII.Decimal

DigitStringSuperset [Char] Source # 
Instance details

Defined in ASCII.Decimal

DigitStringSuperset [D10] Source # 
Instance details

Defined in ASCII.Decimal

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

Defined in ASCII.Decimal

Character/number conversions

Natural

naturalDigitMaybe :: Natural -> Maybe D10 Source #

Examples:

  • naturalDigitMaybe 5 = Just Digit5
  • naturalDigitMaybe 12 = Nothing

Integer

integerDigitMaybe :: Integer -> Maybe D10 Source #

Examples:

  • integerDigitMaybe 5 = Just Digit5
  • integerDigitMaybe 12 = Nothing