| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Data.Enumerate.Types
Description
see the Enumerable class for documentation.
see Data.Enumerate.Example for examples.
can also help automatically derive QuickCheck instances:
newtype SmallNatural = ...
instance Enumerable SmallNatural where ...
newtype SmallString = ...
instance Enumerable SmallString where ...
data T = C0 | C1 () Bool SmallNatural SmallString | C2 ...
instance Arbitrary T where arbitrary = elements enumerated
background on Generics:
also provides instances for:
- sets
- modular integers
- vinyl records
related packages:
- emgm. allows infinite lists (by convention). too heavyweight.
- enumerable. no
Genericinstance. - testing-feat. too heavyweight (testing framework).
- smallcheck too heavyweight (testing framework). Series enumerates up to some depth and can enumerated infinitely-inhabited types.
- https://hackage.haskell.org/package/quickcheck quickcheck> too heavyweight (testing framework, randomness unnecessary).
- class Enumerable a where
- enumerated :: [a]
- cardinality :: proxy a -> Natural
- type Partial a b = forall m. MonadThrow m => a -> m b
- class GEnumerable f where
- genumerated :: [f x]
- gcardinality :: proxy f -> Natural
- data Jectivity
- newtype WrappedBoundedEnum a = WrappedBoundedEnum {
- unwrapBoundedEnum :: a
- boundedEnumerated :: (Bounded a, Enum a) => [a]
- boundedCardinality :: forall proxy a. (Bounded a, Enum a) => proxy a -> Natural
- enumEnumerated :: Enum a => [a]
- indexedEnumerated :: (Bounded a, Ix a) => [a]
- indexedCardinality :: forall proxy a. (Bounded a, Ix a) => proxy a -> Natural
- enumerateBelow :: forall a. Enumerable a => Natural -> Either Natural [a]
- enumerateTimeout :: (Enumerable a, NFData a) => Int -> IO (Maybe [a])
Documentation
class Enumerable a where Source
enumerate the set of all values in a (finitely enumerable) type. enumerates depth first.
generalizes Enums to any finite/discrete type. an Enumerable is either:
- an Enum
- a product of Enumerables
- a sum of Enumerables
can be implemented automatically via its Generic instance.
laws:
consistent:
so you can index the
enumeratedwith a nonnegative index below thecardinality.distinct:
(Eq a) =>
nubenumerated==enumerated
complete:
x `
elem'enumerated
coincides with
BoundedEnums:(
Enuma,Boundeda) =>enumerated==boundedEnumerated(
Enuma) =>enumerated==enumEnumerated
(Bounded constraint elided for convenience, but relevant.)
("inputs" a type, outputs a list of values).
Minimal complete definition
Nothing
Instances
| Enumerable Bool Source | |
| Enumerable Char Source | there are only a million (1,114,112) characters.
|
| Enumerable Int8 Source |
|
| Enumerable Int16 Source |
|
| Enumerable Ordering Source | |
| Enumerable Word8 Source | |
| Enumerable Word16 Source | |
| Enumerable () Source | |
| Enumerable Void Source | |
| Enumerable a => Enumerable (Maybe a) Source | |
| (Enumerable a, Ord a) => Enumerable (Set a) Source | the the |
| (Bounded a, Enum a) => Enumerable (WrappedBoundedEnum a) Source | |
| Enumerable a => Enumerable (Demo a) Source | |
| (Enumerable a, Enumerable b) => Enumerable (Either a b) Source | the sum type. the |
| (Enumerable a, Enumerable b) => Enumerable (a, b) Source | the product type. the |
| (Enumerable a, Enumerable b, Enumerable c) => Enumerable (a, b, c) Source | |
| Enumerable (Rec * f ([] *)) Source | the cardinality is 1. |
| (Enumerable (f a), Enumerable (Rec * f as)) => Enumerable (Rec * f ((:) * a as)) Source | the cardinality is product of cardinalities. |
| (Enumerable a, Enumerable b, Enumerable c, Enumerable d) => Enumerable (a, b, c, d) Source | |
| (Enumerable a, Enumerable b, Enumerable c, Enumerable d, Enumerable e) => Enumerable (a, b, c, d, e) Source | |
| (Enumerable a, Enumerable b, Enumerable c, Enumerable d, Enumerable e, Enumerable f) => Enumerable (a, b, c, d, e, f) Source | |
| (Enumerable a, Enumerable b, Enumerable c, Enumerable d, Enumerable e, Enumerable f, Enumerable g) => Enumerable (a, b, c, d, e, f, g) Source |
type Partial a b = forall m. MonadThrow m => a -> m b Source
a (safely-)partial function. i.e. a function that:
- fails only via the
throwMmethod ofMonadThrow - succeeds only via the
returnmethod ofMonad
class GEnumerable f where Source
"Generic Enumerable", lifted to unary type constructors.
Instances
| GEnumerable V1 Source | empty list |
| GEnumerable U1 Source | singleton list |
| Enumerable a => GEnumerable (K1 R a) Source | call |
| (GEnumerable f, GEnumerable g) => GEnumerable ((:+:) f g) Source | add lists with |
| (GEnumerable f, GEnumerable g) => GEnumerable ((:*:) f g) Source | multiply lists with |
| GEnumerable f => GEnumerable (M1 D t f) Source | ignore datatype metadata |
| GEnumerable f => GEnumerable (M1 C t f) Source | ignore constructor metadata |
| GEnumerable f => GEnumerable (M1 S t f) Source | ignore selector metadata |
see "Data.Enumerate.Reify.getJectivityM"
Constructors
| Injective | |
| Surjective | |
| Bijective |
newtype WrappedBoundedEnum a Source
wrap any (Bounded a, Enum a) to be a Enumerable via boundedEnumerated.
(avoids OverlappingInstances).
Constructors
| WrappedBoundedEnum | |
Fields
| |
Instances
| (Bounded a, Enum a) => Enumerable (WrappedBoundedEnum a) Source |
boundedEnumerated :: (Bounded a, Enum a) => [a] Source
for non-Generic Bounded Enums:
instance Enumerable _ whereenumerated= boundedEnumeratedcardinality=boundedCardinality
boundedCardinality :: forall proxy a. (Bounded a, Enum a) => proxy a -> Natural Source
for non-Generic Bounded Enums.
behavior may be undefined when the cardinality of a is larger than the cardinality of Int. this should be okay, as Int is at least as big as Int64, which is at least as big as all the monomorphic types in base that instantiate Bounded. you can double-check with:
>>>boundedCardinality (const(undefined::Int)) -- platform specific18446744073709551616
-- i.e. 1 + 9223372036854775807 - -9223372036854775808
works with non-zero-based Enum instances, like Int64 or a custom toEnum/fromEnum.
assumes the enumeration's numbering is contiguous, e.g. if fromEnum 0 and fromEnum 2
both exist, then fromEnum 1 should exist too.
enumEnumerated :: Enum a => [a] Source
for non-Generic Enums:
instance Enumerable ... where
enumerated = enumEnumerated
the enum should still be bounded.
indexedEnumerated :: (Bounded a, Ix a) => [a] Source
for non-Generic Bounded Indexed (Ix) types:
instance Enumerable _ whereenumerated= indexedEnumeratedcardinality=indexedCardinality
indexedCardinality :: forall proxy a. (Bounded a, Ix a) => proxy a -> Natural Source
enumerateBelow :: forall a. Enumerable a => Natural -> Either Natural [a] Source
enumerate only when the cardinality is small enough. returns the cardinality when too large.
>>>enumerateBelow 2 :: Either Natural [Bool]Left 2
>>>enumerateBelow 100 :: Either Natural [Bool]Right [False,True]
useful when you've established that traversing a list below some length and consuming its values is reasonable for your application. e.g. after benchmarking, you think you can process a billion entries within a minute.
enumerateTimeout :: (Enumerable a, NFData a) => Int -> IO (Maybe [a]) Source
enumerate only when completely evaluating the list doesn't timeout (before the given number of microseconds).
>>>enumerateTimeout (2 * 10^6) :: IO (Maybe [Bool]) -- two secondsJust [False,True]