Safe Haskell | None |
---|---|
Language | Haskell2010 |
Safe(r) converters from Integral
types
Synopsis
- type family IntBaseType a :: IntBaseTypeK
- type IsIntSubType a b = IsIntBaseSubType (IntBaseType a) (IntBaseType b)
- fromIntegral :: (Integral a, Integral b, IsIntSubType a b ~ 'True) => a -> b
- fromIntegralMaybe :: (Integral a, Integral b, Bits a, Bits b) => a -> Maybe b
- fromIntegralNoOverflow :: (Integral a, Integral b) => a -> Either ArithException b
- fromIntegralOverflowing :: (Integral a, Num b) => a -> b
- fromIntegralToRealFrac :: (Integral a, RealFrac b, IsIntSubType a Integer ~ 'True) => a -> b
Documentation
type family IntBaseType a :: IntBaseTypeK #
The (open) type family IntBaseType
encodes type-level
information about the value range of an integral type.
This module also provides type family instances for the standard
Haskell 2010 integral types (including Foreign.C.Types) as well
as the Natural
type.
Here's a simple example for registering a custom type with the Data.IntCast facilities:
-- user-implemented unsigned 4-bit integer data Nibble = … -- declare meta-information type instanceIntBaseType
Nibble =FixedWordTag
4 -- user-implemented signed 7-bit integer data MyInt7 = … -- declare meta-information type instanceIntBaseType
MyInt7 =FixedIntTag
7
The type-level predicate IsIntSubType
provides a partial
ordering based on the types above. See also intCast
.
Instances
type IsIntSubType a b = IsIntBaseSubType (IntBaseType a) (IntBaseType b) #
fromIntegral :: (Integral a, Integral b, IsIntSubType a b ~ 'True) => a -> b Source #
fromIntegralMaybe :: (Integral a, Integral b, Bits a, Bits b) => a -> Maybe b Source #
Statically safe converter between Integral
types, which is just intCastMaybe
under the
hood. Unlike fromIntegral
accept any a
and
b
. Return Just value
if conversion is
possible at runtime and Nothing
otherwise.
fromIntegralNoOverflow :: (Integral a, Integral b) => a -> Either ArithException b Source #
Statically safe converter between Integral
types
checking for overflow/underflow. Returns Right value
if conversion does not
produce overflow/underflow and Left ArithException
with corresponding
ArithException
(Overflow
/Underflow
) otherwise.
Note the function is strict in its argument.
>>>
fromIntegralNoOverflow @Int @Word 123
Right 123>>>
fromIntegralNoOverflow @Int @Word (-123)
Left arithmetic underflow>>>
fromIntegralNoOverflow @Int @Integer (-123)
Right (-123)>>>
fromIntegralNoOverflow @Int @Natural (-123)
Left arithmetic underflow>>>
fromIntegralNoOverflow @Int @Int8 127
Right 127>>>
fromIntegralNoOverflow @Int @Int8 128
Left arithmetic overflow
fromIntegralOverflowing :: (Integral a, Num b) => a -> b Source #
Runtime-safe converter between Integral
types, which is just
fromIntegral
under the hood.
It is needed to semantically distinguish usages, where overflow is intended,
from those that have to fail on overflow. E.g. Int8 -> Word8
with intended
bits reinterpretation from lossy Integer -> Int
.
>>>
fromIntegralOverflowing @Int8 @Word8 (-1)
255>>>
fromIntegralOverflowing @Natural @Int8 450
-62
Please note that like fromIntegral
from base
, this will throw on some
conversions!
>>>
fromIntegralOverflowing @Int @Natural (-1)
*** Exception: arithmetic underflow
See fromIntegralNoOverflow
for an alternative that doesn't throw.
fromIntegralToRealFrac :: (Integral a, RealFrac b, IsIntSubType a Integer ~ 'True) => a -> b Source #
Statically safe converter between Integral
and RealFrac
types. Could be applied to cast
common types like Float
, Double
and Scientific
.
It is primarily needed to replace usages of
fromIntegral
, which are safe actually
as integral numbers are being casted to
fractional ones.