-----------------------------------------------------------------------------
-- |
-- Module      :  Data.Integral
-- 
-- Maintainer  :  Isaac Jones <ijones@galois.com>
-- Stability   :  alpha
-- Portability :  GHC
--
-- Cues Integralitis.
module Data.Integral
        ( fromIntegral'   -- :: (Bounded a, Integral a, Bounded b, Integral b) => a -> b
	, fromIntegral''  -- :: (Bounded a, Integral a, Bounded b, Integral b) => a -> b
	
        , INInt
	, INLong

	, inIntToInt      -- :: INInt -> Int
	, intToINLong     -- :: Int -> INLong
	, inIntToINLong   -- :: INInt -> INLong
	, intToINInt      -- :: Int -> INInt

        ) where

import Data.Int ( Int32, Int64 )
import Control.Exception ( assert )

type INInt  = Int32
type INLong = Int64

-- This section should only allow _correct_ conversions between types.
-- Raw fromIntegral should be avoided because it can cause overflow
-- and underflow.

inIntToInt :: INInt -> Int
inIntToInt = fromIntegral'

intToINLong :: Int -> INLong
intToINLong = fromIntegral'

inIntToINLong :: INInt -> INLong
inIntToINLong = fromIntegral'

intToINInt :: Int -> INInt
intToINInt = fromIntegral'


-- |Almost like fromIntegral, but checks the bounds to make sure its
-- definitely safe.  Uses assert, so without assertions, check won't
-- happen.
fromIntegral' :: (Bounded a, Integral a, Bounded b, Integral b) => a -> b
fromIntegral' x = let i = fromIntegral x
                  in assert ((toInteger (maxBound `asTypeOf` i)
                                            >= toInteger (maxBound `asTypeOf` x))
                             && (toInteger (minBound `asTypeOf` i)
                                            <= toInteger (minBound `asTypeOf` x)))
                            i

-- |A bit less safe than fromIntegral'; just runtime checks actual
-- value you're trying to convert.
fromIntegral'' :: (Integral a, Bounded b, Integral b) => a -> b
fromIntegral'' x = let i = fromIntegral x
                    in assert ((toInteger (maxBound `asTypeOf` i)
                                              >= toInteger x)
                               && (toInteger (minBound `asTypeOf` i)
                                              <= toInteger  x))
                              i