Copyright | 2012--2021 wren gayle romano |
---|---|
License | BSD3 |
Maintainer | wren@cpan.org |
Stability | provisional |
Portability | Haskell98 + CPP (+ MagicHash) |
Safe Haskell | Trustworthy |
Language | Haskell2010 |
A redefinition of the Prelude's Enum
class in order
to render it safe. That is, the Haskell Language Report defines
pred
, succ
, fromEnum
and
toEnum
to be partial functions when the type is
Bounded
[1], but this is unacceptable. So these classes are
offered as a replacement, correcting the types of those functions.
We intentionally clash with the names of the Prelude's class;
if you wish to use both in the same file, then import this module
(or the Prelude) qualified.
While we're at it, we also generalize the notion of enumeration.
Rather than requiring that the type is linearly enumerable, we
distinguish between forward enumeration (which allows for multiple
predecessors) and backward enumeration (which allows for multiple
successors). Moreover, we do not require that the enumeration
order coincides with the Ord
ordering (if one exists), though
it's advisable that they do (for your sanity). However, we also
ensure that the notion of enumeration (in either direction) is
well-defined, which rules out instances for Float
and Double
,
and renders instances for Ratio
problematic.
Ratio
instances can be provided so long as the
base type is integral and enumerable; but they must be done in
an obscure order[2] that does not coincide with Ord
. Since
this is not what people may expect, we only provide an instance
for the newtype CalkinWilf
, not for
Ratio
itself.
The MagicHash
extension is only actually required if on GHC.
This extension is used only so that the implementation of the
instances for Char
match those of the Prelude's Enum
.
I have not benchmarked to determine whether this low-level hackery
is actually still necessary.
- 1
- http://www.haskell.org/onlinereport/haskell2010/haskellch6.html#x13-1310006.3.4
- 2
- Jeremy Gibbons, David Lester, and Richard Bird (2006). Enumerating the Rationals. JFP 16(3):281--291. DOI:10.1017/S0956796806005880 http://www.cs.ox.ac.uk/jeremy.gibbons/publications/rationals.pdf
Synopsis
- class UpwardEnum a where
- class DownwardEnum a where
- pred :: a -> Maybe a
- precedes :: a -> a -> Bool
- enumDownFrom :: a -> [a]
- enumDownFromTo :: a -> a -> [a]
- class (UpwardEnum a, DownwardEnum a) => Enum a where
- toEnum :: Int -> Maybe a
- fromEnum :: a -> Maybe Int
- enumFromThen :: a -> a -> [a]
- enumFromThenTo :: a -> a -> a -> [a]
Documentation
class UpwardEnum a where Source #
A class for upward enumerable types. That is, we can enumerate
larger and larger values, eventually getting every one of them;
i.e., given any x
, for all y
such that y `succeeds` x
,
it must be the case that y
occurs within some finite prefix
of enumFrom x
.
We require that succeeds
forms a strict partial order. That
is, it must obey the following laws (N.B., if the first two laws
hold, then the third one follows for free):
if x `succeeds` y && y `succeeds` z then x `succeeds` z if x `succeeds` y then not (y `succeeds` x) not (x `succeeds` x)
Moreover, we require that succeeds
agrees with succ
, and
that succ
is exhaustive for succeeds
(assuming Eq a
, by
magic if need be):
if succ x == Just y then y `succeeds` x if x `succeeds` y then x `elem` enumFrom y
The successor of a value, or Nothing
is there isn't one.
For the numeric types in the Prelude, succ
adds 1.
succeeds :: a -> a -> Bool infix 4 Source #
A variant of (
with regards to the enumeration order.>
)
Return x
followed by all it's successors, in order. The
resulting list is always non-empty, since it includes x
.
If the resulting list is always finite, then the succeeds
ordering is converse well-founded. In GHC, the default
implementation is a "good producer" for list fusion.
enumFromTo :: a -> a -> [a] Source #
Return the elements of
, filtering out
everything that succeeds enumFrom
xz
. If x
succeeds z
, then the
resulting list is empty; otherwise, it is non-empty, since
it includes x
. In GHC, the default implementation is a
"good producer" for list fusion.
Instances
UpwardEnum Bool Source # | |
UpwardEnum Char Source # | |
UpwardEnum Int Source # | |
UpwardEnum Integer Source # | |
UpwardEnum Ordering Source # | |
UpwardEnum () Source # | |
Integral a => UpwardEnum (CalkinWilf a) Source # | |
Defined in Data.Number.CalkinWilf succ :: CalkinWilf a -> Maybe (CalkinWilf a) Source # succeeds :: CalkinWilf a -> CalkinWilf a -> Bool Source # enumFrom :: CalkinWilf a -> [CalkinWilf a] Source # enumFromTo :: CalkinWilf a -> CalkinWilf a -> [CalkinWilf a] Source # |
class DownwardEnum a where Source #
A class for downward enumerable types. That is, we can enumerate
smaller and smaller values, eventually getting every one of them;
i.e., given any x
, for all y
such that y `precedes` x
,
it must be the case that y
occurs within some finite prefix
of enumDownFrom x
.
We require that precedes
forms a strict partial order. That
is, it must obey the following laws (N.B., if the first two laws
hold, then the third one follows for free):
if x `precedes` y && y `precedes` z then x `precedes` z if x `precedes` y then not (y `precedes` x) not (x `precedes` x)
Moreover, we require that precedes
agrees with pred
, and
that pred
is exhaustive for precedes
(assuming Eq a
, by
magic if need be):
if pred x == Just y then y `precedes` x if x `precedes` y then x `elem` enumDownFrom y
The predecessor of a value, or Nothing
is there isn't one.
For the numeric types in the Prelude, pred
subtracts 1.
precedes :: a -> a -> Bool infix 4 Source #
A variant of (
with regards to the enumeration order.<
)
enumDownFrom :: a -> [a] Source #
Return x
followed by all it's predecessors, in (reverse)
order. The resulting list is always non-empty, since it
includes x
. If the resulting list is always finite, then
the precedes
ordering is well-founded. In GHC, the default
implementation is a "good producer" for list fusion.
enumDownFromTo :: a -> a -> [a] Source #
Return the elements of
, filtering out
everything that precedes enumDownFrom
xz
. If x
precedes z
, then the
resulting list is empty; otherwise, it is non-empty, since
it includes x
. In GHC, the default implementation is a
"good producer" for list fusion.
Instances
DownwardEnum Bool Source # | |
DownwardEnum Char Source # | |
DownwardEnum Int Source # | |
DownwardEnum Integer Source # | |
DownwardEnum Ordering Source # | |
DownwardEnum () Source # | |
Defined in Prelude.SafeEnum | |
Integral a => DownwardEnum (CalkinWilf a) Source # | |
Defined in Data.Number.CalkinWilf pred :: CalkinWilf a -> Maybe (CalkinWilf a) Source # precedes :: CalkinWilf a -> CalkinWilf a -> Bool Source # enumDownFrom :: CalkinWilf a -> [CalkinWilf a] Source # enumDownFromTo :: CalkinWilf a -> CalkinWilf a -> [CalkinWilf a] Source # |
class (UpwardEnum a, DownwardEnum a) => Enum a where Source #
A class for types with a linear enumeration order. We require that the partial orders of the superclasses agree:
x `succeeds` y == y `precedes` x
That the enumeration order is preserved/reflected:
i `succeeds` j == toEnum i `succeeds` toEnum j x `succeeds` y == fromEnum x `succeeds` fromEnum y
And that toEnum
and fromEnum
form a weak isomorphism; i.e.,
for some p
and q
, the following must hold:
fromEnum <=< toEnum == (\i -> if p i then Just i else Nothing) toEnum <=< fromEnum == (\x -> if q x then Just x else Nothing)
In other words, the following type-restricted functions form an isomorphism of linear orderings.
toEnum' :: {i :: Int | toEnum i == Just _} -> a fromEnum' :: {x :: a | fromEnum x == Just _} -> Int
Minimal complete definition: toEnum
, fromEnum
. N.B., the
default definitions for enumFromThen
and enumFromThenTo
only
make sense when the type a
is "smaller" than Int
(i.e.,
fromEnum
always succeeds); if fromEnum
ever fails, then you
must override the defaults in order to correctly infer the stride
for values which cannot be converted to Int
.
toEnum :: Int -> Maybe a Source #
Convert from an Int
.
fromEnum :: a -> Maybe Int Source #
Convert to an Int
.
enumFromThen :: a -> a -> [a] Source #
Enumerate values with an inferred stride. The resulting
list is always non-empty, since it includes x
. Naturally,
this should agree with enumFrom
and enumDownFrom
(assuming
Eq a
, by magic if need be):
if succ x == Just y then enumFromThen x y == enumFrom x if pred x == Just y then enumFromThen x y == enumDownFrom x
In the default implementation: if fromEnum
fails on either
argument, then the result is exactly [x]
; and if toEnum
fails on any of the enumerated integers, then the first
failure terminates the enumeration. If either of these
properties is inappropriate, then you should override the
default. In GHC, the default implementation is a "good
producer" for list fusion.
enumFromThenTo :: a -> a -> a -> [a] Source #
Enumerate values with an inferred stride and a given limit.
If x
precedes y
(and therefore we're enumerating forward)
but x
succeeds z
(and therefore is past the limit), then
the result is empty. Similarly, if x
succeeds y
(and
therefore we're enumerating backward) but x
precedes z
(and therefore is past the limit), then the result is empty.
Otherwise the result is non-empty since it contains x
.
Naturally, this should agree with enumFromTo
and
enumDownFromTo
(assuming Eq a
, by magic if need be):
if succ x == Just y then enumFromThenTo x y z == enumFromTo x z if pred x == Just y then enumFromThenTo x y z == enumDownFromTo x z
In the default implementation: if fromEnum
fails on any
argument, then the result is either []
or [x]
(as
appropriate); and if toEnum
fails on any of the enumerated
integers, then the first failure terminates the enumeration.
If either of these properties is inappropriate, then you
should override the default. In GHC, the default implementation
is a "good producer" for list fusion.
Instances
Enum Bool Source # | |
Enum Char Source # | |
Enum Int Source # | |
Enum Integer Source # | |
Enum Ordering Source # | |
Enum () Source # | |
Integral a => Enum (CalkinWilf a) Source # | |
Defined in Data.Number.CalkinWilf toEnum :: Int -> Maybe (CalkinWilf a) Source # fromEnum :: CalkinWilf a -> Maybe Int Source # enumFromThen :: CalkinWilf a -> CalkinWilf a -> [CalkinWilf a] Source # enumFromThenTo :: CalkinWilf a -> CalkinWilf a -> CalkinWilf a -> [CalkinWilf a] Source # |