| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Data.Number.Scientific
Synopsis
- data Scientific
- type Scientific# = (#Int#, Int#, LargeScientific#)
- small :: Int -> Int -> Scientific
- large :: Integer -> Integer -> Scientific
- fromFixed :: HasResolution e => Fixed e -> Scientific
- toWord :: Scientific -> Maybe Word
- toWord8 :: Scientific -> Maybe Word8
- toWord16 :: Scientific -> Maybe Word16
- toWord32 :: Scientific -> Maybe Word32
- toWord64 :: Scientific -> Maybe Word64
- toInt :: Scientific -> Maybe Int
- toInt32 :: Scientific -> Maybe Int32
- toInt64 :: Scientific -> Maybe Int64
- parserSignedUtf8Bytes :: e -> Parser e s Scientific
- parserTrailingUtf8Bytes :: e -> Int -> Parser e s Scientific
- parserUnsignedUtf8Bytes :: e -> Parser e s Scientific
- parserNegatedUtf8Bytes :: e -> Parser e s Scientific
- parserNegatedTrailingUtf8Bytes :: e -> Int -> Parser e s Scientific
- parserSignedUtf8Bytes# :: e -> Parser e s Scientific#
- parserTrailingUtf8Bytes# :: e -> Int# -> Parser e s Scientific#
- parserUnsignedUtf8Bytes# :: e -> Parser e s Scientific#
- parserNegatedUtf8Bytes# :: e -> Parser e s Scientific#
- parserNegatedTrailingUtf8Bytes# :: e -> Int# -> Parser e s Scientific#
Documentation
data Scientific Source #
Instances
| Eq Scientific Source # | |
| Defined in Data.Number.Scientific | |
| Show Scientific Source # | |
| Defined in Data.Number.Scientific Methods showsPrec :: Int -> Scientific -> ShowS # show :: Scientific -> String # showList :: [Scientific] -> ShowS # | |
type Scientific# = (#Int#, Int#, LargeScientific#) Source #
Produce
Arguments
| :: Int | Coefficient | 
| -> Int | Exponent | 
| -> Scientific | 
Construct a Scientific from a coefficient and exponent
 that fit in a machine word.
Arguments
| :: Integer | Coefficient | 
| -> Integer | Exponent | 
| -> Scientific | 
Construct a Scientific from a coefficient and exponent
 of arbitrary size.
fromFixed :: HasResolution e => Fixed e -> Scientific Source #
Construct a Scientific from a fixed-precision number.
 This does not perform well and is only included for convenience.
Consume
Decode
parserSignedUtf8Bytes :: e -> Parser e s Scientific Source #
Parse a number that is encoded in UTF-8 and in scientific notation. All of these are accepted:
- 330e-1
- 330e+1
- 330e1
- 330.0e1
- -330.0e1
- 12
- 00012
- 2.05
- +2.05
- +33.6e+1
parserTrailingUtf8Bytes Source #
Arguments
| :: e | Error message | 
| -> Int | Leading digit, should be between  | 
| -> Parser e s Scientific | 
parserUnsignedUtf8Bytes :: e -> Parser e s Scientific Source #
Variant of parserSignedUtf8Bytes that rejects strings with
 a leading plus or minus sign.
parserNegatedUtf8Bytes :: e -> Parser e s Scientific Source #
Variant of parserUnsignedUtf8Bytes that negates the result.
parserNegatedTrailingUtf8Bytes Source #
Arguments
| :: e | Error message | 
| -> Int | Leading digit, should be between  | 
| -> Parser e s Scientific | 
parserSignedUtf8Bytes# Source #
Arguments
| :: e | Error message | 
| -> Parser e s Scientific# | 
parserTrailingUtf8Bytes# Source #
Arguments
| :: e | Error message | 
| -> Int# | Leading digit | 
| -> Parser e s Scientific# | 
parserUnsignedUtf8Bytes# Source #
Arguments
| :: e | Error message | 
| -> Parser e s Scientific# | 
Variant of parseUnsignedUtf8Bytes where all arguments are
 unboxed.
parserNegatedUtf8Bytes# Source #
Arguments
| :: e | Error message | 
| -> Parser e s Scientific# | 
parserNegatedTrailingUtf8Bytes# Source #
Arguments
| :: e | Error message | 
| -> Int# | Leading digit | 
| -> Parser e s Scientific# |