Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- showNatural :: DigitStringSuperset string => Natural -> string
- readNatural :: DigitStringSuperset string => string -> Maybe Natural
- showInteger :: StringSuperset string => Integer -> string
- readInteger :: StringSuperset string => string -> Maybe Integer
- showIntegral :: (Integral n, StringSuperset string) => n -> string
- readIntegral :: (StringSuperset string, Integral num, Bits num) => string -> Maybe num
- data Digit
- class DigitSuperset char where
- fromDigit :: Digit -> char
- isDigit :: char -> Bool
- toDigitUnsafe :: char -> Digit
- toDigitMaybe :: char -> Maybe Digit
- class DigitStringSuperset string where
- fromDigitList :: [Digit] -> string
- isDigitString :: string -> Bool
- toDigitListUnsafe :: string -> [Digit]
- toDigitListMaybe :: string -> Maybe [Digit]
- naturalDigitMaybe :: Natural -> Maybe Digit
- digitNatural :: Digit -> Natural
- integerDigitMaybe :: Integer -> Maybe Digit
- digitInteger :: Digit -> Integer
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
Digit0 | Zero |
Digit1 | One |
Digit2 | Two |
Digit3 | Three |
Digit4 | Four |
Digit5 | Five |
Digit6 | Six |
Digit7 | Seven |
Digit8 | Eight |
Digit9 | Nine |
Instances
Bounded Digit Source # | |
Enum Digit Source # | |
Eq Digit Source # | |
Data Digit Source # | |
Defined in ASCII.Decimal 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 # 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 # | |
Ord Digit Source # | |
Show Digit Source # | |
Generic Digit Source # | |
Hashable Digit Source # | |
Defined in ASCII.Decimal | |
DigitSuperset Digit Source # | |
DigitSuperset char => Lift Digit char Source # | |
Defined in ASCII.Decimal | |
DigitStringSuperset [Digit] Source # | |
Defined in ASCII.Decimal | |
DigitStringSuperset string => Lift [Digit] string Source # | |
Defined in ASCII.Decimal | |
type Rep Digit Source # | |
Defined in ASCII.Decimal type Rep Digit = D1 ('MetaData "Digit" "ASCII.Decimal" "ascii-numbers-1.1.0.2-inplace" '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 #
fromDigit :: Digit -> char Source #
isDigit :: char -> Bool Source #
toDigitUnsafe :: char -> Digit Source #
toDigitMaybe :: char -> Maybe Digit Source #
Instances
DigitSuperset Char Source # | |
DigitSuperset Word8 Source # | |
DigitSuperset Char Source # | |
DigitSuperset Digit Source # | |
DigitSuperset char => DigitSuperset (ASCII char) Source # | |
Of digit lists
class DigitStringSuperset string where Source #
fromDigitList :: [Digit] -> string Source #
isDigitString :: string -> Bool Source #
toDigitListUnsafe :: string -> [Digit] Source #
toDigitListMaybe :: string -> Maybe [Digit] Source #
Instances
Character/number conversions
Natural
naturalDigitMaybe :: Natural -> Maybe Digit Source #
Examples:
naturalDigitMaybe 5
=Just Digit5
naturalDigitMaybe 12
=Nothing
digitNatural :: Digit -> Natural Source #
Integer
integerDigitMaybe :: Integer -> Maybe Digit Source #
Examples:
integerDigitMaybe 5
=Just Digit5
integerDigitMaybe 12
=Nothing
digitInteger :: Digit -> Integer Source #