morley-prelude-0.5.1: A custom prelude used in Morley
Safe HaskellNone
LanguageHaskell2010

Morley.Prelude.FromIntegral

Description

Safe(r) converters from Integral types

Synopsis

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 instance IntBaseType Nibble = FixedWordTag 4

-- user-implemented signed 7-bit integer
data MyInt7 = …

-- declare meta-information
type instance IntBaseType MyInt7 = FixedIntTag 7

The type-level predicate IsIntSubType provides a partial ordering based on the types above. See also intCast.

Instances

Instances details
type IntBaseType Int 
Instance details

Defined in Data.IntCast

type IntBaseType Int8 
Instance details

Defined in Data.IntCast

type IntBaseType Int16 
Instance details

Defined in Data.IntCast

type IntBaseType Int32 
Instance details

Defined in Data.IntCast

type IntBaseType Int64 
Instance details

Defined in Data.IntCast

type IntBaseType Integer 
Instance details

Defined in Data.IntCast

type IntBaseType Natural 
Instance details

Defined in Data.IntCast

type IntBaseType Word 
Instance details

Defined in Data.IntCast

type IntBaseType Word8 
Instance details

Defined in Data.IntCast

type IntBaseType Word16 
Instance details

Defined in Data.IntCast

type IntBaseType Word32 
Instance details

Defined in Data.IntCast

type IntBaseType Word64 
Instance details

Defined in Data.IntCast

type IntBaseType Word62 Source # 
Instance details

Defined in Morley.Prelude.Word

type IntBaseType Word63 Source # 
Instance details

Defined in Morley.Prelude.Word

type IntBaseType CChar 
Instance details

Defined in Data.IntCast

type IntBaseType CSChar 
Instance details

Defined in Data.IntCast

type IntBaseType CUChar 
Instance details

Defined in Data.IntCast

type IntBaseType CShort 
Instance details

Defined in Data.IntCast

type IntBaseType CUShort 
Instance details

Defined in Data.IntCast

type IntBaseType CInt 
Instance details

Defined in Data.IntCast

type IntBaseType CUInt 
Instance details

Defined in Data.IntCast

type IntBaseType CLong 
Instance details

Defined in Data.IntCast

type IntBaseType CULong 
Instance details

Defined in Data.IntCast

type IntBaseType CLLong 
Instance details

Defined in Data.IntCast

type IntBaseType CULLong 
Instance details

Defined in Data.IntCast

type IntBaseType CPtrdiff 
Instance details

Defined in Data.IntCast

type IntBaseType CSize 
Instance details

Defined in Data.IntCast

type IntBaseType CSigAtomic 
Instance details

Defined in Data.IntCast

type IntBaseType CIntPtr 
Instance details

Defined in Data.IntCast

type IntBaseType CUIntPtr 
Instance details

Defined in Data.IntCast

type IntBaseType CIntMax 
Instance details

Defined in Data.IntCast

type IntBaseType CUIntMax 
Instance details

Defined in Data.IntCast

type CheckIntSubType a b = (CheckIntSubTypeErrors a b (IsIntSubType a b), IsIntSubType a b ~ 'True) Source #

Constraint synonym equivalent to IsIntSubType a b ~ 'True, but with better error messages

fromIntegral :: (Integral a, Integral b, CheckIntSubType a b) => a -> b Source #

Statically safe converter between Integral types, which is just intCast under the hood.

It is used to turn the value of type a into the value of type b such that a is subtype of b. It is needed to prevent silent unsafe conversions.

>>> fromIntegral @Int @Word 1
...
... error:
... Can not safely cast 'Int' to 'Word':
... 'Int' is not a subtype of 'Word'
...
>>> fromIntegral @Word @Natural 1
1

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, CheckIntSubType a Integer) => 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.