Copyright | (c) 2021 Kowainik |
---|---|
License | MIT |
Maintainer | Kowainik <xrom.xkov@gmail.com> |
Stability | Stable |
Portability | Portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Reexports Enum
related typeclasses and functions. Also introduces a few useful
helpers to work with Enums.
Note: universe
, universeNonEmpty
and inverseMap
were previously in the
extra modules, but due to their benefit in different use cases. If you imported
Relude.Extra.Enum
module, you can remove it now, as these functions are
reexported in the main Relude module.
Since: 1.0.0.0
Synopsis
- universe :: (Bounded a, Enum a) => [a]
- universeNonEmpty :: forall a. (Bounded a, Enum a) => NonEmpty a
- inverseMap :: forall a k. (Bounded a, Enum a, Ord k) => (a -> k) -> k -> Maybe a
- class Bounded a where
- class Enum a where
- succ :: a -> a
- pred :: a -> a
- toEnum :: Int -> a
- fromEnum :: a -> Int
- enumFrom :: a -> [a]
- enumFromThen :: a -> a -> [a]
- enumFromTo :: a -> a -> [a]
- enumFromThenTo :: a -> a -> a -> [a]
- boundedEnumFromThen :: (Enum a, Bounded a) => a -> a -> [a]
- boundedEnumFrom :: (Enum a, Bounded a) => a -> [a]
Useful combinators for Enums
universe :: (Bounded a, Enum a) => [a] Source #
Returns all values of some Bounded
Enum
in ascending order.
>>>
universe :: [Bool]
[False,True]
>>>
universe @Ordering
[LT,EQ,GT]
>>>
data TrafficLight = Red | Blue | Green deriving (Show, Enum, Bounded)
>>>
universe :: [TrafficLight]
[Red,Blue,Green]
>>>
data Singleton = Singleton deriving (Show, Enum, Bounded)
>>>
universe @Singleton
[Singleton]
Since: 0.1.0
universeNonEmpty :: forall a. (Bounded a, Enum a) => NonEmpty a Source #
Like universe
, but returns NonEmpty
list of some enumeration
>>>
universeNonEmpty :: NonEmpty Bool
False :| [True]
>>>
universeNonEmpty @Ordering
LT :| [EQ,GT]
>>>
data TrafficLight = Red | Blue | Green deriving (Show, Eq, Enum, Bounded)
>>>
universeNonEmpty :: NonEmpty TrafficLight
Red :| [Blue,Green]
>>>
data Singleton = Singleton deriving (Show, Eq, Enum, Bounded)
>>>
universeNonEmpty @Singleton
Singleton :| []
Since: 0.7.0.0
inverseMap :: forall a k. (Bounded a, Enum a, Ord k) => (a -> k) -> k -> Maybe a Source #
inverseMap f
creates a function that is the inverse of a given function
f
. It does so by constructing Map
internally for each value f a
. The
implementation makes sure that the Map
is constructed only once and then
shared for every call.
Memory usage note: don't inverse functions that have types like Int
as their result. In this case the created Map
will have huge size.
The complexity of reversed mapping is \(\mathcal{O}(\log n)\).
Performance note: make sure to specialize monomorphic type of your functions
that use inverseMap
to avoid Map
reconstruction.
One of the common inverseMap
use-case is inverting the show
or a show
-like
function.
>>>
data Color = Red | Green | Blue deriving (Show, Enum, Bounded)
>>>
parse = inverseMap show :: String -> Maybe Color
>>>
parse "Red"
Just Red>>>
parse "Black"
Nothing
Correctness note: inverseMap
expects injective function as its argument,
i.e. the function must map distinct arguments to distinct values.
Typical usage of this function looks like this:
data GhcVer = Ghc802 | Ghc822 | Ghc844 | Ghc865 | Ghc881 deriving (Eq
,Ord
,Show
,Enum
,Bounded
) showGhcVer :: GhcVer ->Text
showGhcVer = \case Ghc802 -> "8.0.2" Ghc822 -> "8.2.2" Ghc844 -> "8.4.4" Ghc865 -> "8.6.5" Ghc881 -> "8.8.1" parseGhcVer ::Text
->Maybe
GhcVer parseGhcVer =inverseMap
showGhcVer
Since: 0.1.1
Base reexports
The Bounded
class is used to name the upper and lower limits of a
type. Ord
is not a superclass of Bounded
since types that are not
totally ordered may also have upper and lower bounds.
The Bounded
class may be derived for any enumeration type;
minBound
is the first constructor listed in the data
declaration
and maxBound
is the last.
Bounded
may also be derived for single-constructor datatypes whose
constituent types are in Bounded
.
Instances
Bounded Bool | Since: base-2.1 |
Bounded Char | Since: base-2.1 |
Bounded Int | Since: base-2.1 |
Bounded Int8 | Since: base-2.1 |
Bounded Int16 | Since: base-2.1 |
Bounded Int32 | Since: base-2.1 |
Bounded Int64 | Since: base-2.1 |
Bounded Ordering | Since: base-2.1 |
Bounded Word | Since: base-2.1 |
Bounded Word8 | Since: base-2.1 |
Bounded Word16 | Since: base-2.1 |
Bounded Word32 | Since: base-2.1 |
Bounded Word64 | Since: base-2.1 |
Bounded VecCount | Since: base-4.10.0.0 |
Bounded VecElem | Since: base-4.10.0.0 |
Bounded () | Since: base-2.1 |
Bounded All | Since: base-2.1 |
Bounded Any | Since: base-2.1 |
Bounded Associativity | Since: base-4.9.0.0 |
Defined in GHC.Generics | |
Bounded SourceUnpackedness | Since: base-4.9.0.0 |
Defined in GHC.Generics | |
Bounded SourceStrictness | Since: base-4.9.0.0 |
Defined in GHC.Generics | |
Bounded DecidedStrictness | Since: base-4.9.0.0 |
Defined in GHC.Generics | |
Bounded CChar | |
Bounded CSChar | |
Bounded CUChar | |
Bounded CShort | |
Bounded CUShort | |
Bounded CInt | |
Bounded CUInt | |
Bounded CLong | |
Bounded CULong | |
Bounded CLLong | |
Bounded CULLong | |
Bounded CBool | |
Bounded CPtrdiff | |
Bounded CSize | |
Bounded CWchar | |
Bounded CSigAtomic | |
Defined in Foreign.C.Types minBound :: CSigAtomic # maxBound :: CSigAtomic # | |
Bounded CIntPtr | |
Bounded CUIntPtr | |
Bounded CIntMax | |
Bounded CUIntMax | |
Bounded WordPtr | |
Bounded IntPtr | |
Bounded Extension | |
Bounded Undefined Source # | |
Bounded a => Bounded (Min a) | Since: base-4.9.0.0 |
Bounded a => Bounded (Max a) | Since: base-4.9.0.0 |
Bounded a => Bounded (First a) | Since: base-4.9.0.0 |
Bounded a => Bounded (Last a) | Since: base-4.9.0.0 |
Bounded m => Bounded (WrappedMonoid m) | Since: base-4.9.0.0 |
Defined in Data.Semigroup minBound :: WrappedMonoid m # maxBound :: WrappedMonoid m # | |
Bounded a => Bounded (Identity a) | Since: base-4.9.0.0 |
Bounded a => Bounded (Dual a) | Since: base-2.1 |
Bounded a => Bounded (Sum a) | Since: base-2.1 |
Bounded a => Bounded (Product a) | Since: base-2.1 |
Bounded a => Bounded (Down a) | Swaps Since: base-4.14.0.0 |
(Bounded a, Bounded b) => Bounded (a, b) | Since: base-2.1 |
Bounded (Proxy t) | Since: base-4.7.0.0 |
(Bounded a, Bounded b, Bounded c) => Bounded (a, b, c) | Since: base-2.1 |
Bounded a => Bounded (Const a b) | Since: base-4.9.0.0 |
(Applicative f, Bounded a) => Bounded (Ap f a) | Since: base-4.12.0.0 |
a ~ b => Bounded (a :~: b) | Since: base-4.7.0.0 |
(Bounded a, Bounded b, Bounded c, Bounded d) => Bounded (a, b, c, d) | Since: base-2.1 |
a ~~ b => Bounded (a :~~: b) | Since: base-4.10.0.0 |
(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e) => Bounded (a, b, c, d, e) | Since: base-2.1 |
(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f) => Bounded (a, b, c, d, e, f) | Since: base-2.1 |
(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g) => Bounded (a, b, c, d, e, f, g) | Since: base-2.1 |
(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g, Bounded h) => Bounded (a, b, c, d, e, f, g, h) | Since: base-2.1 |
(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g, Bounded h, Bounded i) => Bounded (a, b, c, d, e, f, g, h, i) | Since: base-2.1 |
(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g, Bounded h, Bounded i, Bounded j) => Bounded (a, b, c, d, e, f, g, h, i, j) | Since: base-2.1 |
(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g, Bounded h, Bounded i, Bounded j, Bounded k) => Bounded (a, b, c, d, e, f, g, h, i, j, k) | Since: base-2.1 |
(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g, Bounded h, Bounded i, Bounded j, Bounded k, Bounded l) => Bounded (a, b, c, d, e, f, g, h, i, j, k, l) | Since: base-2.1 |
(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g, Bounded h, Bounded i, Bounded j, Bounded k, Bounded l, Bounded m) => Bounded (a, b, c, d, e, f, g, h, i, j, k, l, m) | Since: base-2.1 |
(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g, Bounded h, Bounded i, Bounded j, Bounded k, Bounded l, Bounded m, Bounded n) => Bounded (a, b, c, d, e, f, g, h, i, j, k, l, m, n) | Since: base-2.1 |
(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g, Bounded h, Bounded i, Bounded j, Bounded k, Bounded l, Bounded m, Bounded n, Bounded o) => Bounded (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) | Since: base-2.1 |
Class Enum
defines operations on sequentially ordered types.
The enumFrom
... methods are used in Haskell's translation of
arithmetic sequences.
Instances of Enum
may be derived for any enumeration type (types
whose constructors have no fields). The nullary constructors are
assumed to be numbered left-to-right by fromEnum
from 0
through n-1
.
See Chapter 10 of the Haskell Report for more details.
For any type that is an instance of class Bounded
as well as Enum
,
the following should hold:
- The calls
andsucc
maxBound
should result in a runtime error.pred
minBound
fromEnum
andtoEnum
should give a runtime error if the result value is not representable in the result type. For example,
is an error.toEnum
7 ::Bool
enumFrom
andenumFromThen
should be defined with an implicit bound, thus:
enumFrom x = enumFromTo x maxBound enumFromThen x y = enumFromThenTo x y bound where bound | fromEnum y >= fromEnum x = maxBound | otherwise = minBound
the successor of a value. For numeric types, succ
adds 1.
the predecessor of a value. For numeric types, pred
subtracts 1.
Convert from an Int
.
Convert to an Int
.
It is implementation-dependent what fromEnum
returns when
applied to a value that is too large to fit in an Int
.
Used in Haskell's translation of [n..]
with [n..] = enumFrom n
,
a possible implementation being enumFrom n = n : enumFrom (succ n)
.
For example:
enumFrom 4 :: [Integer] = [4,5,6,7,...]
enumFrom 6 :: [Int] = [6,7,8,9,...,maxBound :: Int]
enumFromThen :: a -> a -> [a] #
Used in Haskell's translation of [n,n'..]
with [n,n'..] = enumFromThen n n'
, a possible implementation being
enumFromThen n n' = n : n' : worker (f x) (f x n')
,
worker s v = v : worker s (s v)
, x = fromEnum n' - fromEnum n
and
f n y
| n > 0 = f (n - 1) (succ y)
| n < 0 = f (n + 1) (pred y)
| otherwise = y
For example:
enumFromThen 4 6 :: [Integer] = [4,6,8,10...]
enumFromThen 6 2 :: [Int] = [6,2,-2,-6,...,minBound :: Int]
enumFromTo :: a -> a -> [a] #
Used in Haskell's translation of [n..m]
with
[n..m] = enumFromTo n m
, a possible implementation being
enumFromTo n m
| n <= m = n : enumFromTo (succ n) m
| otherwise = []
.
For example:
enumFromTo 6 10 :: [Int] = [6,7,8,9,10]
enumFromTo 42 1 :: [Integer] = []
enumFromThenTo :: a -> a -> a -> [a] #
Used in Haskell's translation of [n,n'..m]
with
[n,n'..m] = enumFromThenTo n n' m
, a possible implementation
being enumFromThenTo n n' m = worker (f x) (c x) n m
,
x = fromEnum n' - fromEnum n
, c x = bool (>=) ((x 0)
f n y
| n > 0 = f (n - 1) (succ y)
| n < 0 = f (n + 1) (pred y)
| otherwise = y
and
worker s c v m
| c v m = v : worker s c (s v) m
| otherwise = []
For example:
enumFromThenTo 4 2 -6 :: [Integer] = [4,2,0,-2,-4,-6]
enumFromThenTo 6 8 2 :: [Int] = []
Instances
boundedEnumFromThen :: (Enum a, Bounded a) => a -> a -> [a] #
boundedEnumFrom :: (Enum a, Bounded a) => a -> [a] #