fin-0.1.1: Nat and Fin: peano naturals and finite numbers

Safe HaskellNone
LanguageHaskell2010

Data.Fin.Enum

Contents

Description

This module is designed to be imported qualified:

import qualified Data.Fin.Enum as E
Synopsis

Documentation

class Enum a where Source #

Generic enumerations.

Examples:

>>> from ()
0
>>> to 0 :: ()
()
>>> to 0 :: Bool
False
>>> map to F.universe :: [Bool]
[False,True]
>>> map (to . (+1) . from) [LT, EQ, GT] :: [Ordering] -- Num Fin is modulo arithmetic
[EQ,GT,LT]

Minimal complete definition

Nothing

Associated Types

type EnumSize a :: Nat Source #

The size of an enumeration.

Methods

from :: a -> Fin (EnumSize a) Source #

Converts a value to its index.

from :: (Generic a, GFrom a, EnumSize a ~ GEnumSize a) => a -> Fin (EnumSize a) Source #

Converts a value to its index.

to :: Fin (EnumSize a) -> a Source #

Converts from index to the original value.

to :: (Generic a, GTo a, EnumSize a ~ GEnumSize a) => Fin (EnumSize a) -> a Source #

Converts from index to the original value.

Instances
Enum Bool Source #

Bool ~ 2

Instance details

Defined in Data.Fin.Enum

Associated Types

type EnumSize Bool :: Nat Source #

Enum Ordering Source #

Ordering ~ 3

Instance details

Defined in Data.Fin.Enum

Associated Types

type EnumSize Ordering :: Nat Source #

Enum () Source #

() ~ 1

Instance details

Defined in Data.Fin.Enum

Associated Types

type EnumSize () :: Nat Source #

Methods

from :: () -> Fin (EnumSize ()) Source #

to :: Fin (EnumSize ()) -> () Source #

Enum Void Source #

Void ~ 0

Instance details

Defined in Data.Fin.Enum

Associated Types

type EnumSize Void :: Nat Source #

(Enum a, Enum b, InlineInduction (EnumSize a)) => Enum (Either a b) Source #

Either ~ +

Instance details

Defined in Data.Fin.Enum

Associated Types

type EnumSize (Either a b) :: Nat Source #

Methods

from :: Either a b -> Fin (EnumSize (Either a b)) Source #

to :: Fin (EnumSize (Either a b)) -> Either a b Source #

Generic implementation

gfrom :: (Generic a, GFrom a) => a -> Fin (GEnumSize a) Source #

Generic version of from.

type GFrom a = GFromRep (Rep a) Source #

Constraint for the class that computes gfrom.

gto :: (Generic a, GTo a) => Fin (GEnumSize a) -> a Source #

Generic version of to.

type GTo a = GToRep (Rep a) Source #

Constraint for the class that computes gto.

type GEnumSize a = EnumSizeRep (Rep a) Nat0 Source #

Compute the size from the type.