-- SPDX-FileCopyrightText: 2021 Oxhead Alpha -- SPDX-License-Identifier: LicenseRef-MIT-OA {-# 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 -- * Unsafe converters from @Either@ for making unsafe counter-parts of safe functions , unsafe , unsafeM ) where import Fmt (Buildable, pretty) 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 = either (error . fromString . displayException) id . 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 = Unsafe.fromIntegral -- | Unsafe converter from 'Either', which uses buildable -- 'Left' to throw an exception with 'error'. -- -- It is primarily needed for making unsafe counter-parts -- of safe functions. In particular, for replacing -- @unsafeFName x = either (error . pretty) id@ -- constructors and converters, which produce many similar -- functions at the call site, with @unsafe . fName $ x@. unsafe :: (HasCallStack, Buildable a) => Either a b -> b unsafe = either (error . pretty) id {-# INLINE unsafe #-} -- | Similar to 'unsafe' converter, but with the use of -- monadic 'fail' and returning the result wrapped in a monad. unsafeM :: (MonadFail m, Buildable a) => Either a b -> m b unsafeM = either (fail . pretty) pure {-# INLINE unsafeM #-}