-- SPDX-FileCopyrightText: 2021 Tocqueville Group
--
-- SPDX-License-Identifier: LicenseRef-MIT-TQ

{-# LANGUAGE NoImplicitPrelude #-}

-- | Unsafe utilities.
--
-- This module should be imported qualified.
module Unsafe
  ( module Universum.Unsafe

  -- * Unsafe converters between @Integral@ types checking for overflow/underflow
  , Unsafe.fromIntegral
  , Unsafe.fromInteger
  ) where

import Morley.Prelude.FromIntegral (fromIntegralNoOverflow)
import Universum
import Universum.Unsafe

-- | Unsafe converter between 'Integral' types
-- checking for overflow/underflow. Return
-- @value@ if conversion does not produce
-- overflow/underflow and raise an exception
-- with corresponding error message otherwise.
--
-- It is needed to replace 'Universum.Base.fromIntegral'
-- which misses most of the overflow/underflow checks.
--
-- Note the function is strict in its argument.
fromIntegral :: (HasCallStack, Integral a, Integral b) => a -> b
fromIntegral :: a -> b
fromIntegral = (ArithException -> b) -> (b -> b) -> Either ArithException b -> b
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Text -> b
forall a. HasCallStack => Text -> a
error (Text -> b) -> (ArithException -> Text) -> ArithException -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
forall a. IsString a => String -> a
fromString (String -> Text)
-> (ArithException -> String) -> ArithException -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ArithException -> String
forall e. Exception e => e -> String
displayException) b -> b
forall a. a -> a
id (Either ArithException b -> b)
-> (a -> Either ArithException b) -> a -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Either ArithException b
forall a b.
(Integral a, Integral b) =>
a -> Either ArithException b
fromIntegralNoOverflow

-- | Unsafe converter between 'Integer' and 'Integral'
-- types checking for overflow/underflow. Return @value@
-- if conversion does not produce overflow/underflow and
-- raise an exception with corresponding error message
-- otherwise.
--
-- Note the function is strict in its argument.
fromInteger :: (HasCallStack, Integral a) => Integer -> a
fromInteger :: Integer -> a
fromInteger = Integer -> a
forall a b. (HasCallStack, Integral a, Integral b) => a -> b
Unsafe.fromIntegral