-- SPDX-FileCopyrightText: 2021 Oxhead Alpha -- SPDX-License-Identifier: LicenseRef-MIT-OA -- | This module essentially replaces the default "Prelude" with "Universum". -- -- It works because we are using the @base-noprelude@ package instead of @base@. module Prelude ( module Control.Lens , module Universum , for , toEnumSafe -- * Converters from @Integral@ types , module FromIntegral -- * Overloaded boolean operators , module Boolean -- * Polymorphic length , module Length -- * Unsafe conversions , Unsafe.fromInteger -- * Safer @show@ , module Show -- * Oddly sized @Word@ types , module Word -- * Re-exports , Unsafe.unsafe , Unsafe.unsafeM ) where import Control.Lens (Lens, Lens', Traversal, Traversal', _1, _2, _3, _4, _5, over, preuse, preview, set, use, view, (%~), (&), (.~), (<&>), (^.), (^..), (^?)) import Data.Ix (inRange) import Data.Traversable (for) import Morley.Prelude.Boolean as Boolean import Morley.Prelude.FromIntegral as FromIntegral import Morley.Prelude.Length as Length import Morley.Prelude.Show as Show import Morley.Prelude.Word as Word import Universum hiding (All(..), Any(..), Key, Lens, Lens', Nat, Traversal, Traversal', Val, _1, _2, _3, _4, _5, all, and, any, fromInteger, fromIntegral, length, not, or, over, preuse, preview, readFile, set, show, use, view, writeFile, (%~), (&&), (&), (.~), (<&>), (^.), (^..), (^?), (||)) import Unsafe qualified (fromInteger, unsafe, unsafeM) -- | A safe version of 'toEnum' for 'Bounded' types. toEnumSafe :: forall a. (Enum a, Bounded a) => Int -> Maybe a toEnumSafe i = guard (inBounds i) $> toEnum i where inBounds :: Int -> Bool inBounds = inRange (fromEnum (minBound :: a), fromEnum (maxBound :: a)) {-# INLINE toEnumSafe #-}