| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Data.Finite
Description
Provides a class of types isomorphic to some statically-known .Fin n
This comes with Generics-based generated instances, and can be used to
generate instances of Enum and Bounded (for which the stock deriving
only supports sum types with no fields).
Since this is all still represented by Int internally, things will start
raising errors if your type has more values than can fit in positive
Ints. It's not recommended to use this on large types, and there's not
much reason to want to anyway, as its main uses are to derive Enum (which
is also based on Int) and to make the type compatible with
Table (which would be impractically large for a key type
with too many values to represent as Int).
The most common way to get a Finite instance for a type is to tack on a
deriving Finite via clause, which results in an
automatically-generated instance based on the type's ADT structure.Wrapped Generic MyType
This also provides instances and
Enum (Wrapped Finite a), so some types that would otherwise not be
compatible with derived Bounded (Wrapped Finite a)Enum instances can get them by adding a
deriving (Enum, Bounded) via Wrapped Finite MyType clause.
Synopsis
- class Finite a where
- type Cardinality a :: Nat
- cardinality' :: SC a (Cardinality a)
- toFin :: a -> Fin (Cardinality a)
- fromFin :: Fin (Cardinality a) -> a
- cardinality :: forall a. Finite a => SInt (Cardinality a)
- enumerate :: forall a. Finite a => [a]
- asFin :: Finite a => Iso' a (Fin (Cardinality a))
- data SC a n
- class GFinite a where
- gcardinality :: SInt (GCardinality a)
- gtoFin :: a p -> Fin (GCardinality a)
- gfromFin :: Fin (GCardinality a) -> a p
- type family GCardinality a where ...
Finite Enumerations
A typeclass of finite enumerable types.
These allow constructing Representable Functors using a
simple Vec as the underlying storage, with constant-time
lookup and efficient traversals.
Note that since Fin is (currently) represented by Int, any type with
more values than Int can't have an instance. This means we can't have
instances for 32- and 64-bit arithmetic types, since Int is only required
to have 30 bits of precision.
Annoyingly, we also can't have an instance for Int and Word, because
Fin wastes one bit of the Int by forbidding negative values. The
cardinality of Int and Word would need to be twice as large as we can
actually represent in a Fin. Another obstacle is that their cardinality
varies between implementations and architectures; it's possible to work
around this by making their Cardinality an irreducible type family
application, and using 'Data.SInt.SI#' to plug in a value at runtime, but
this makes the Fins related to Int and Word annoying to work with,
since their bound is only known at runtime.
Fortunately, those instances are unlikely to be important, since a table of 2^32 elements is moderately impractical (32GiB of pointers alone), and a table of 2^64 elements is unrepresentable in current computer architectures.
toFin and fromFin shall be total functions and shall be the two sides of
an isomorphism.
Associated Types
type Cardinality a :: Nat Source #
Methods
cardinality' :: SC a (Cardinality a) Source #
A witness that the cardinality is known at runtime.
This isn't part of the class context because we can only perform
arithmetic on KnownNat instances in expression context; that is, we
can't convince GHC that an instance with
type Cardinality (Maybe a) = Cardinality a + 1 is valid if the
KnownNat is in the class context. Instead, we use SInt to allow
computing the cardinality at runtime.
toFin :: a -> Fin (Cardinality a) Source #
fromFin :: Fin (Cardinality a) -> a Source #
Instances
cardinality :: forall a. Finite a => SInt (Cardinality a) Source #
A witness that the cardinality of a is known at runtime.
Implementation Details
A wrapper type around to support DerivingVia on GHC 8.6.Cardinality a
Instance methods that don't mention the instance head outside of type families / aliases don't work with DerivingVia on GHC 8.6 because it uses type signatures rather than TypeApplications to choose the instance to call into.
class GFinite a where Source #
The derived Finite implementation of a generic representation type.
Methods
gcardinality :: SInt (GCardinality a) Source #
gtoFin :: a p -> Fin (GCardinality a) Source #
gfromFin :: Fin (GCardinality a) -> a p Source #
Instances
type family GCardinality a where ... Source #
The derived cardinality of a generic representation type.
Equations
| GCardinality V1 = 0 | |
| GCardinality U1 = 1 | |
| GCardinality (K1 i a) = Cardinality a | |
| GCardinality (M1 i c f) = GCardinality f | |
| GCardinality (f :+: g) = GCardinality f + GCardinality g | |
| GCardinality (f :*: g) = GCardinality f * GCardinality g |