Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data Scientific
- type Scientific# = (# Int#, Int#, LargeScientific #)
- small :: Int -> Int -> Scientific
- large :: Integer -> Integer -> Scientific
- fromFixed :: HasResolution e => Fixed e -> Scientific
- fromWord8 :: Word8 -> Scientific
- fromWord16 :: Word16 -> Scientific
- fromWord32 :: Word32 -> Scientific
- fromWord64 :: Word64 -> Scientific
- fromInt :: Int -> Scientific
- fromInt8 :: Int8 -> Scientific
- fromInt16 :: Int16 -> Scientific
- fromInt32 :: Int32 -> Scientific
- fromInt64 :: Int64 -> 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
- toInteger :: Scientific -> Maybe Integer
- withExposed :: (Int -> Int -> a) -> (Integer -> Integer -> a) -> Scientific -> a
- roundShiftedToInt64 :: Int -> Scientific -> Maybe Int64
- greaterThanInt64 :: Scientific -> Int64 -> Bool
- 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#
- encode :: Scientific -> ShortText
- builderUtf8 :: Scientific -> Builder
Documentation
data Scientific Source #
Instances
Show Scientific Source # | |
Defined in Data.Number.Scientific showsPrec :: Int -> Scientific -> ShowS # show :: Scientific -> String # showList :: [Scientific] -> ShowS # | |
Eq Scientific Source # | |
Defined in Data.Number.Scientific (==) :: Scientific -> Scientific -> Bool # (/=) :: Scientific -> Scientific -> Bool # |
type Scientific# = (# Int#, Int#, LargeScientific #) Source #
Produce
:: Int | Coefficient |
-> Int | Exponent |
-> Scientific |
Construct a Scientific
from a coefficient and exponent
that fit in a machine word.
:: 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.
fromWord8 :: Word8 -> Scientific Source #
Convert an 8-bit unsigned word to a Scientific
.
fromWord16 :: Word16 -> Scientific Source #
Convert a 16-bit unsigned word to a Scientific
.
fromWord32 :: Word32 -> Scientific Source #
Convert a 32-bit unsigned word to a Scientific
.
fromWord64 :: Word64 -> Scientific Source #
Convert a 64-bit unsigned word to a Scientific
.
fromInt :: Int -> Scientific Source #
fromInt8 :: Int8 -> Scientific Source #
fromInt16 :: Int16 -> Scientific Source #
fromInt32 :: Int32 -> Scientific Source #
fromInt64 :: Int64 -> Scientific Source #
Consume
toInteger :: Scientific -> Maybe Integer Source #
This can exhaust memory. Do not use on untrusted input.
:: (Int -> Int -> a) | Called when coefficient and exponent are small |
-> (Integer -> Integer -> a) | Called when coefficient and exponent are large |
-> Scientific | |
-> a |
Expose the non-normalized exponent and coefficient.
Scale and Consume
:: Int | Exponent |
-> Scientific | Number |
-> Maybe Int64 |
This works even if the number has a fractional component. For example:
>>>
roundShiftedToInt64 2 (fromFixed @E3 1.037)
103
The shift amount should be a small constant between -100 and 100. The behavior of a shift outside this range is undefined.
Compare
greaterThanInt64 :: Scientific -> Int64 -> Bool Source #
Is the number represented in scientific notation greater than the 64-bit integer argument?
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 #
:: 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 #
:: e | Error message |
-> Int | Leading digit, should be between |
-> Parser e s Scientific |
parserSignedUtf8Bytes# Source #
:: e | Error message |
-> Parser e s Scientific# |
parserTrailingUtf8Bytes# Source #
:: e | Error message |
-> Int# | Leading digit |
-> Parser e s Scientific# |
parserUnsignedUtf8Bytes# Source #
:: e | Error message |
-> Parser e s Scientific# |
Variant of parseUnsignedUtf8Bytes
where all arguments are
unboxed.
parserNegatedUtf8Bytes# Source #
:: e | Error message |
-> Parser e s Scientific# |
parserNegatedTrailingUtf8Bytes# Source #
:: e | Error message |
-> Int# | Leading digit |
-> Parser e s Scientific# |
Encode
encode :: Scientific -> ShortText Source #
Encode a number as text. If the exponent is between -50 and +50 (exclusive), this represents the number without any exponent. For example:
>>>
encode (small 87654321 (-3))
"87654.321">>>
encode (small 5000 (-3))
"-5000"
The decision of when to use an exponent is not considered stable part of this library's API. Check the test suite for examples of what to expect, and feel free to open an issue or contribute if the output of this function is unsightly in certain situations.
builderUtf8 :: Scientific -> Builder Source #
Variant of encode
that provides a builder instead.