int-cast-0.1.2.0: Checked conversions between integral types

Copyright© 2014 Herbert Valerio Riedel
LicenseBSD-style (see the LICENSE file)
MaintainerHerbert Valerio Riedel <hvr@gnu.org>
Stabilityexperimental
PortabilityGHC ≥ 7.8
Safe HaskellNone
LanguageHaskell2010

Data.IntCast

Contents

Description

This module provides for statically or dynamically checked conversions between Integral types.

Synopsis

Conversion functions

statically checked

intCast :: (Integral a, Integral b, IsIntSubType a b ~ True) => a -> b Source

Statically checked integer conversion which satisfies the property

Note: This is just a type-restricted alias of fromIntegral and should therefore lead to the same compiled code as if fromIntegral had been used instead of intCast.

intCastIso :: (Integral a, Integral b, IsIntTypeIso a b ~ True) => a -> b Source

Statically checked integer conversion which satisfies the properties

Note: This is just a type-restricted alias of fromIntegral and should therefore lead to the same compiled code as if fromIntegral had been used instead of intCast.

intCastEq :: (Integral a, Integral b, IsIntTypeEq a b ~ True) => a -> b Source

Version of intCast restricted to casts between types with same value domain.

dynamically checked

intCastMaybe :: (Integral a, Integral b, Bits a, Bits b) => a -> Maybe b Source

Run-time-checked integer conversion

This is an optimized version of the following generic code below

intCastMaybeRef :: (Integral a, Integral b) => a -> Maybe b
intCastMaybeRef x
  | toInteger x == toInteger y = Just y
  | otherwise                  = Nothing
  where
    y = fromIntegral x

The code above is rather inefficient as it needs to go via the Integer type. The function intCastMaybe, however, is marked INLINEABLE and if both integral types are statically known, GHC will be able optimize the code signficantly (for -O1 and better).

For instance (as of GHC 7.8.1) the following definitions

w16_to_i32 = intCastMaybe :: Word16 -> Maybe Int32

i16_to_w16 = intCastMaybe :: Int16 -> Maybe Word16

are translated into the following (simplified) GHC Core language

w16_to_i32 = \x -> Just (case x of _ { W16# x# -> I32# (word2Int# x#) })

i16_to_w16 = \x -> case eta of _
  { I16# b1 -> case tagToEnum# (<=# 0 b1) of _
      { False -> Nothing
      ; True -> Just (W16# (narrow16Word# (int2Word# b1)))
      }
  }

Registering new integer types

type family IntBaseType a :: IntBaseTypeK Source

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 MyWord7 = FixedIntTag 4

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

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

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

data IntBaseTypeK Source

(Kind) Meta-information about integral types.

If also a Bits instance is defined, the type-level information provided by IntBaseType ought to match the meta-information that is conveyed by the Bits class' isSigned and bitSizeMaybe methods.

Constructors

FixedIntTag Nat

fixed-width n-bit integers with value range [-2ⁿ⁻¹, 2ⁿ⁻¹-1].

FixedWordTag Nat

fixed-width n-bit integers with value range [0, 2ⁿ-1].

BigIntTag

integers with value range ]-∞,+∞[.

BigWordTag

naturals with value range [0,+∞[.

Instances

Type-level predicates

The following type-level predicates are used by intCast, intCastIso, and intCastEq respectively.

type family IsIntBaseTypeEq a b :: Bool Source

Equations

IsIntBaseTypeEq a a = True 
IsIntBaseTypeEq a b = False