enumerate-0.2.1: enumerate all the values in a finite type (automatically)

Safe HaskellNone
LanguageHaskell2010

Enumerate.Types

Contents

Description

enumerate all values in a finite type.

e.g.

data A
  = A0 Bool
  | A1 (Either Bool) (Maybe Bool)
  | A2 (Bool, Bool)
  | A3 (Set Bool)
  deriving (Show,Generic,Enumerable)

> enumerate
A0 False
A0 True
A1 ...

> cardinality ([]::[A])

see the Enumerable class for documentation.

see Enumerate.Example for examples.

can also help automatically derive QuickCheck instances:

newtype ValidString = ValidString String
 deriving (Show)
validStrings :: [String]
makeValidString :: String -> Maybe ValidString
makeValidString s = if s member validStrings then Just (ValidString s) else Nothing
instance Enumerable ValidString where enumerated = ValidString <$> validStrings ... -- manually (since normal String's are infinite)
instance Arbitrary ValidString where arbitrary = elements enumerated

data ValidName = ValidName ValidString ValidString | CoolValidName [ValidString]
 deriving (Show,Generic)
instance Enumerable ValidName -- automatically

instance Arbitrary ValidName where arbitrary = elements enumerated

Provides instances for all base types (whenever possible):

  • under Data. / Control. / System. / Text., and even GHC.
  • even non-Enums
  • except when too large (like Int) (see Enumerate.Large)

background on Generics:

also provides instances for:

  • sets
  • vinyl records

related packages:

  • enumerable. no Generic instance.
  • universe no Generic instance.
  • SafeEnum only Enums
  • emgm. allows infinite lists (by convention). too heavyweight.
  • testing-feat. too heavyweight (testing framework).
  • smallcheck too heavyweight (testing framework). Series enumerates up to some depth and can enumerated infinitely-inhabited types.
  • quickcheck too heavyweight (testing framework, randomness unnecessary).

Synopsis

modular integers

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:

(Bounded constraint elided for convenience, but relevant.)

("inputs" a type, outputs a list of values).

Every type in base (that can be an instance) is an instance.

Minimal complete definition

Nothing

Methods

enumerated :: [a] Source

cardinality :: proxy a -> Natural Source

Instances

Enumerable Bool Source 
Enumerable Char Source

there are only a million (1,114,112) characters.

>>> import Data.Char (ord,chr)  -- 'ord', 'chr'
>>> ord minBound
0
>>> ord maxBound
1114111
>>> length [chr 0 ..]
1114112
Enumerable Int8 Source
-- (toInteger prevents overflow)
>>> 1 + toInteger (maxBound::Int8) - toInteger (minBound::Int8)
256
Enumerable Int16 Source
>>> 1 + toInteger (maxBound::Int16) - toInteger (minBound::Int16)
65536
Enumerable Ordering Source 
Enumerable Word8 Source 
Enumerable Word16 Source 
Enumerable () Source 
Enumerable FormatAdjustment Source 
Enumerable FormatSign Source 
Enumerable Void Source 
Enumerable SpecConstrAnnotation Source 
Enumerable GiveGCStats Source 
Enumerable DoCostCentres Source 
Enumerable DoHeapProfile Source 
Enumerable DoTrace Source 
Enumerable IOMode Source 
Enumerable NonTermination Source 
Enumerable NestedAtomically Source 
Enumerable CodingFailureMode Source 
Enumerable CIno Source 
Enumerable CMode Source 
Enumerable BlockedIndefinitelyOnMVar Source 
Enumerable BlockedIndefinitelyOnSTM Source 
Enumerable Deadlock Source 
Enumerable AllocationLimitExceeded Source 
Enumerable AsyncException Source 
Enumerable Newline Source 
Enumerable NewlineMode Source 
Enumerable IODeviceType Source 
Enumerable SeekMode Source 
Enumerable CodingProgress Source 
Enumerable BufferState Source 
Enumerable CChar Source 
Enumerable CSChar Source 
Enumerable CUChar Source 
Enumerable CShort Source 
Enumerable CUShort Source 
Enumerable CWchar Source 
Enumerable ArithException Source 
Enumerable All Source 
Enumerable Any Source 
Enumerable Associativity Source 
Enumerable GeneralCategory Source 
Enumerable a => Enumerable (Identity a) Source 
Enumerable a => Enumerable (Complex a) Source 
Enumerable a => Enumerable (Dual a) Source 
Enumerable (a -> a) => Enumerable (Endo a) Source 
Enumerable a => Enumerable (Sum a) Source 
Enumerable a => Enumerable (Product a) Source 
Enumerable a => Enumerable (First a) Source 
Enumerable a => Enumerable (Last a) Source 
Enumerable a => Enumerable (Down a) Source

(a can be any Enumerable, unlike the Enum instance where a is an Integral).

Enumerable a => Enumerable (Maybe a) Source 
(Enumerable a, Ord a) => Enumerable (Set a) Source

the cardinality is the cardinality of the powerSet of a, i.e. 2^|a|. warning: it grows quickly. don't try to take the power set of Char! or even Word8.

the cardinality call is efficient (depending on the efficiency of the base type's call). you should be able to safely call enumerateBelow, unless the arithmetic itself becomes too large.

>>> enumerated :: [Set Bool]
[fromList [],fromList [False],fromList [False,True],fromList [True]]
(Bounded a, Enum a) => Enumerable (WrappedBoundedEnum a) Source 
(Ord a, Enumerable a) => Enumerable (A a) Source 
Enumerable a => Enumerable (Demo a) Source 
(Enumerable a, Enumerable b) => Enumerable (Either a b) Source

the sum type.

the cardinality is the sum of the cardinalities of a and b.

>>> cardinality ([] :: [Either Bool Ordering])
5
(Enumerable a, Enumerable b) => Enumerable (a, b) Source

the product type.

the cardinality is the product of the cardinalities of a and b.

>>> cardinality ([] :: [(Bool,Ordering)])
6
Enumerable a => Enumerable (Const a b) Source 
Enumerable (Proxy * a) Source

(phantom in a)

(Enumerable a, Enumerable b, Enumerable c) => Enumerable (a, b, c) Source

3

Enumerable (f a) => Enumerable (Alt * f a) Source 
Coercible * a b => Enumerable (Coercion * a b) Source 
(~) * a b => Enumerable ((:~:) * a b) Source 
Enumerable (Rec * f ([] *)) Source 
(Enumerable (f a), Enumerable (Rec * f as)) => Enumerable (Rec * f ((:) * a as)) Source

the cardinality is a product of cardinalities.

(Enumerable a, Enumerable b, Enumerable c, Enumerable d) => Enumerable (a, b, c, d) Source

4

(Enumerable a, Enumerable b, Enumerable c, Enumerable d, Enumerable e) => Enumerable (a, b, c, d, e) Source

5

(Enumerable a, Enumerable b, Enumerable c, Enumerable d, Enumerable e, Enumerable f) => Enumerable (a, b, c, d, e, f) Source

6

(Enumerable a, Enumerable b, Enumerable c, Enumerable d, Enumerable e, Enumerable f, Enumerable g) => Enumerable (a, b, c, d, e, f, g) Source

7

newtype WrappedBoundedEnum a Source

wrap any (Bounded a, Enum a) to be a Enumerable via boundedEnumerated.

(avoids OverlappingInstances).

Constructors

WrappedBoundedEnum 

Fields

unwrapBoundedEnum :: a
 

class GEnumerable f where Source

"Generic Enumerable", lifted to unary type constructors.

Methods

genumerated :: [f x] Source

gcardinality :: proxy f -> Natural Source

Instances

GEnumerable V1 Source

empty list

GEnumerable U1 Source

singleton list

Enumerable a => GEnumerable (K1 R a) Source

call enumerated

(GEnumerable f, GEnumerable g) => GEnumerable ((:+:) f g) Source

add lists with (<>)

(GEnumerable f, GEnumerable g) => GEnumerable ((:*:) f g) Source

multiply lists with concatMap

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

boundedEnumerated :: (Bounded a, Enum a) => [a] Source

for non-Generic Bounded Enums:

instance Enumerable _ where
 enumerated = boundedEnumerated
 cardinality = boundedCardinality

boundedCardinality :: forall proxy a. (Bounded a, Enum a) => proxy a -> Natural Source

for non-Generic Bounded Enums.

Assuming Bounded is correct, safely stop the enumeration (and know where to start).

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 specific
18446744073709551616
-- 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 _ where
 enumerated = indexedEnumerated
 cardinality = indexedCardinality

indexedCardinality :: forall proxy a. (Bounded a, Ix a) => proxy a -> Natural Source

for non-Generic Bounded Indexed (Ix) types.

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 seconds
Just [False,True]