generic-data-0.9.0.0: Deriving instances with GHC.Generics and related utilities

Safe HaskellNone
LanguageHaskell2010

Generic.Data.Internal.Enum

Description

Generic deriving for Enum, Bounded and Ix.

Warning

This is an internal module: it is not subject to any versioning policy, breaking changes can happen at any time.

If something here seems useful, please report it or create a pull request to export it from an external module.

Synopsis

Documentation

gfromEnum :: (Generic a, GEnum StandardEnum (Rep a)) => a -> Int Source #

Generic fromEnum generated with the StandardEnum option.

See also gtoEnum.

genumFrom :: (Generic a, GEnum StandardEnum (Rep a)) => a -> [a] Source #

Generic enumFrom generated with the StandardEnum option.

See also gtoEnum.

genumFromThen :: (Generic a, GEnum StandardEnum (Rep a)) => a -> a -> [a] Source #

Generic enumFromThen generated with the StandardEnum option.

See also gtoEnum.

genumFromTo :: (Generic a, GEnum StandardEnum (Rep a)) => a -> a -> [a] Source #

Generic enumFromTo generated with the StandardEnum option.

See also gtoEnum.

genumFromThenTo :: (Generic a, GEnum StandardEnum (Rep a)) => a -> a -> a -> [a] Source #

Generic enumFromThenTo generated with the StandardEnum option.

See also gtoEnum.

gfromFiniteEnum :: (Generic a, GEnum FiniteEnum (Rep a)) => a -> Int Source #

Generic fromEnum generated with the FiniteEnum option.

See also gtoFiniteEnum.

gfiniteEnumFrom :: (Generic a, GEnum FiniteEnum (Rep a)) => a -> [a] Source #

Generic enumFrom generated with the FiniteEnum option.

See also gtoFiniteEnum.

gfiniteEnumFromThen :: (Generic a, GEnum FiniteEnum (Rep a)) => a -> a -> [a] Source #

Generic enumFromThen generated with the FiniteEnum option.

See also gtoFiniteEnum.

gfiniteEnumFromTo :: (Generic a, GEnum FiniteEnum (Rep a)) => a -> a -> [a] Source #

Generic enumFromTo generated with the FiniteEnum option.

See also gtoFiniteEnum.

gfiniteEnumFromThenTo :: (Generic a, GEnum FiniteEnum (Rep a)) => a -> a -> a -> [a] Source #

Generic enumFromThenTo generated with the FiniteEnum option.

See also gtoFiniteEnum.

gtoEnumRaw' :: forall opts a. (Generic a, GEnum opts (Rep a)) => Int -> a Source #

Unsafe generic toEnum. Does not check whether the argument is within valid bounds. Use gtoEnum or gtoFiniteEnum instead.

gtoEnum' :: forall opts a. (Generic a, GEnum opts (Rep a)) => String -> Int -> a Source #

Generic toEnum. Use gfromEnum or gfromFiniteEnum instead.

gfromEnum' :: forall opts a. (Generic a, GEnum opts (Rep a)) => a -> Int Source #

Generic fromEnum. Use gfromEnum or gfromFiniteEnum instead.

genumMin :: Int Source #

genumMin == gfromEnum gminBound

genumMax :: forall opts a. (Generic a, GEnum opts (Rep a)) => Int Source #

genumMax == gfromEnum gmaxBound

genumFrom' :: forall opts a. (Generic a, GEnum opts (Rep a)) => a -> [a] Source #

Generic enumFrom. Use genumFrom or gfiniteEnumFrom instead.

genumFromThen' :: forall opts a. (Generic a, GEnum opts (Rep a)) => a -> a -> [a] Source #

genumFromTo' :: forall opts a. (Generic a, GEnum opts (Rep a)) => a -> a -> [a] Source #

Generic enumFromTo. Use genumFromTo or gfiniteEnumFromTo instead.

genumFromThenTo' :: forall opts a. (Generic a, GEnum opts (Rep a)) => a -> a -> a -> [a] Source #

gminBound :: (Generic a, GBounded (Rep a)) => a Source #

Generic minBound.

instance Bounded MyType where
  minBound = gminBound
  maxBound = gmaxBound

gmaxBound :: (Generic a, GBounded (Rep a)) => a Source #

Generic maxBound.

See also gminBound.

grange :: (Generic a, GIx (Rep a)) => (a, a) -> [a] Source #

Generic range.

import Data.Ix
instance Ix MyType where
  range = grange
  index = gindex
  inRange = ginRange

gindex :: (Generic a, GIx (Rep a)) => (a, a) -> a -> Int Source #

Generic index.

See also grange.

gunsafeIndex :: (Generic a, GIx (Rep a)) => (a, a) -> a -> Int Source #

Generic unsafeIndex.

Details

Expand

The functions unsafeIndex and unsafeRangeSize belong to Ix but are internal to GHC and hence not exported from the module Data.Ix. However they are exported from the module GHC.Arr. See grange for how to define an instance of Ix such that it does not depend on the stability of GHCs internal API. Unfortunately this results in additional (unnecessary) bound checks. With the danger of having no stability guarantees for GHC's internal API one can alternatively define an instance of Ix as

import GHC.Arr
instance Ix MyType where
  range = grange
  unsafeIndex = gunsafeIndex
  inRange = ginRange

ginRange :: (Generic a, GIx (Rep a)) => (a, a) -> a -> Bool Source #

Generic inRange.

See also grange.

class GEnum opts f where Source #

Generic representation of Enum types.

The opts parameter is a type-level option to select different implementations.

Methods

gCardinality :: Int Source #

gFromEnum :: f p -> Int Source #

gToEnum :: Int -> f p Source #

Instances
GEnum opts (U1 :: Type -> Type) Source # 
Instance details

Defined in Generic.Data.Internal.Enum

(GEnum opts f, GEnum opts g) => GEnum opts (f :+: g) Source # 
Instance details

Defined in Generic.Data.Internal.Enum

Methods

gCardinality :: Int Source #

gFromEnum :: (f :+: g) p -> Int Source #

gToEnum :: Int -> (f :+: g) p Source #

(Bounded c, Enum c) => GEnum FiniteEnum (K1 i c :: Type -> Type) Source # 
Instance details

Defined in Generic.Data.Internal.Enum

Methods

gCardinality :: Int Source #

gFromEnum :: K1 i c p -> Int Source #

gToEnum :: Int -> K1 i c p Source #

(GEnum FiniteEnum f, GEnum FiniteEnum g) => GEnum FiniteEnum (f :*: g) Source # 
Instance details

Defined in Generic.Data.Internal.Enum

Methods

gCardinality :: Int Source #

gFromEnum :: (f :*: g) p -> Int Source #

gToEnum :: Int -> (f :*: g) p Source #

GEnum opts f => GEnum opts (M1 i c f) Source # 
Instance details

Defined in Generic.Data.Internal.Enum

Methods

gCardinality :: Int Source #

gFromEnum :: M1 i c f p -> Int Source #

gToEnum :: Int -> M1 i c f p Source #

data StandardEnum Source #

Standard option for GEnum: derive Enum for types with only nullary constructors (the same restrictions as in the Haskell 2010 report).

data FiniteEnum Source #

Extends the StandardEnum option for GEnum to allow all constructors to have arbitrary many fields. Each field type must be an instance of both Enum and Bounded.

Details

Expand

Two restrictions require the user's caution:

  • The Enum instances of the field types need to start enumerating from 0. Particularly Int is an unfit field type, because the enumeration of the negative values starts before 0.
  • There can only be up to maxBound :: Int values (because the implementation represents the cardinality explicitly as an Int). This restriction makes Word an invalid field type. Notably, it is insufficient for each individual field types to stay below this limit. Instead it applies to the generic type as a whole.

The resulting GEnum instance starts enumerating from 0 up to (cardinality - 1) and respects the generic Ord instance (defined by gcompare). The values from different constructors are enumerated sequentially; they are not interleaved.

data Example = C0 Bool Bool | C1 Bool
  deriving (Eq, Ord, Show, Generic)

cardinality = 6  -- 2    * 2    + 2
                 -- Bool * Bool | Bool

enumeration =
    [ C0 False False
    , C0 False  True
    , C0  True False
    , C0  True  True
    , C1 False
    , C1 True
    ]

enumeration == map gtoFiniteEnum [0 .. 5]
[0 .. 5] == map gfromFiniteEnum enumeration
Instances
(Bounded c, Enum c) => GEnum FiniteEnum (K1 i c :: Type -> Type) Source # 
Instance details

Defined in Generic.Data.Internal.Enum

Methods

gCardinality :: Int Source #

gFromEnum :: K1 i c p -> Int Source #

gToEnum :: Int -> K1 i c p Source #

(GEnum FiniteEnum f, GEnum FiniteEnum g) => GEnum FiniteEnum (f :*: g) Source # 
Instance details

Defined in Generic.Data.Internal.Enum

Methods

gCardinality :: Int Source #

gFromEnum :: (f :*: g) p -> Int Source #

gToEnum :: Int -> (f :*: g) p Source #

class GBounded f where Source #

Generic representation of Bounded types.

Methods

gMinBound :: f p Source #

gMaxBound :: f p Source #

Instances
GBounded (U1 :: Type -> Type) Source # 
Instance details

Defined in Generic.Data.Internal.Enum

Bounded c => GBounded (K1 i c :: Type -> Type) Source # 
Instance details

Defined in Generic.Data.Internal.Enum

Methods

gMinBound :: K1 i c p Source #

gMaxBound :: K1 i c p Source #

(GBounded f, GBounded g) => GBounded (f :+: g) Source # 
Instance details

Defined in Generic.Data.Internal.Enum

Methods

gMinBound :: (f :+: g) p Source #

gMaxBound :: (f :+: g) p Source #

(GBounded f, GBounded g) => GBounded (f :*: g) Source # 
Instance details

Defined in Generic.Data.Internal.Enum

Methods

gMinBound :: (f :*: g) p Source #

gMaxBound :: (f :*: g) p Source #

GBounded f => GBounded (M1 i c f) Source # 
Instance details

Defined in Generic.Data.Internal.Enum

Methods

gMinBound :: M1 i c f p Source #

gMaxBound :: M1 i c f p Source #

class GIx f where Source #

Generic representation of Ix types.

Methods

gRange :: (f p, f p) -> [f p] Source #

gUnsafeIndex :: (f p, f p) -> f p -> Int Source #

gInRange :: (f p, f p) -> f p -> Bool Source #

Instances
GIx (U1 :: Type -> Type) Source # 
Instance details

Defined in Generic.Data.Internal.Enum

Methods

gRange :: (U1 p, U1 p) -> [U1 p] Source #

gUnsafeIndex :: (U1 p, U1 p) -> U1 p -> Int Source #

gInRange :: (U1 p, U1 p) -> U1 p -> Bool Source #

Ix c => GIx (K1 i c :: Type -> Type) Source # 
Instance details

Defined in Generic.Data.Internal.Enum

Methods

gRange :: (K1 i c p, K1 i c p) -> [K1 i c p] Source #

gUnsafeIndex :: (K1 i c p, K1 i c p) -> K1 i c p -> Int Source #

gInRange :: (K1 i c p, K1 i c p) -> K1 i c p -> Bool Source #

(GEnum StandardEnum f, GEnum StandardEnum g) => GIx (f :+: g) Source # 
Instance details

Defined in Generic.Data.Internal.Enum

Methods

gRange :: ((f :+: g) p, (f :+: g) p) -> [(f :+: g) p] Source #

gUnsafeIndex :: ((f :+: g) p, (f :+: g) p) -> (f :+: g) p -> Int Source #

gInRange :: ((f :+: g) p, (f :+: g) p) -> (f :+: g) p -> Bool Source #

(GIx f, GIx g) => GIx (f :*: g) Source # 
Instance details

Defined in Generic.Data.Internal.Enum

Methods

gRange :: ((f :*: g) p, (f :*: g) p) -> [(f :*: g) p] Source #

gUnsafeIndex :: ((f :*: g) p, (f :*: g) p) -> (f :*: g) p -> Int Source #

gInRange :: ((f :*: g) p, (f :*: g) p) -> (f :*: g) p -> Bool Source #

GIx f => GIx (M1 i c f) Source # 
Instance details

Defined in Generic.Data.Internal.Enum

Methods

gRange :: (M1 i c f p, M1 i c f p) -> [M1 i c f p] Source #

gUnsafeIndex :: (M1 i c f p, M1 i c f p) -> M1 i c f p -> Int Source #

gInRange :: (M1 i c f p, M1 i c f p) -> M1 i c f p -> Bool Source #