posable-1.0.0.0: A product-of-sums generics library
Safe HaskellNone
LanguageHaskell2010

Generics.POSable.POSable

Description

Exports the POSable class, which has a generic implementation GPOSable. Also re-exports Generic.SOP, which is needed to derive POSable.

Synopsis

Documentation

class KnownNat (Choices x) => POSable x where Source #

POSable, the base of this library. Provide a compact memory representation for a type and a function to get back to the original type. This memory representation consist of choices, that represent all constructor choices in the type in a single Finite integer, and fields which represents all values in the type as a Product of Sums, which can be mapped to a struct-of-arrays representation for use in array-based languages like Accelerate.

Minimal complete definition

Nothing

Associated Types

type Choices x :: Nat Source #

type Choices x = GChoices (SOP I (Code x))

type Fields x :: [[Type]] Source #

type Fields x = GFields (SOP I (Code x))

Methods

choices :: x -> Finite (Choices x) Source #

default choices :: (Generic x, GPOSable (SOP I (Code x)), GChoices (SOP I (Code x)) ~ Choices x) => x -> Finite (Choices x) Source #

tags :: [Integer] Source #

The tags function returns the range of each constructor. A few examples: >>> tags Bool [1,1] >>> tags (Either Float Float) [1,1] >>> tags (Bool, Bool) [4] >>> tags (Either Bool Bool) [2,2]

default tags :: GPOSable (SOP I (Code x)) => [Integer] Source #

fromPOSable :: Finite (Choices x) -> Product (Fields x) -> x Source #

default fromPOSable :: (Generic x, GPOSable (SOP I (Code x)), Fields x ~ GFields (SOP I (Code x)), Choices x ~ GChoices (SOP I (Code x))) => Finite (Choices x) -> Product (Fields x) -> x Source #

fields :: x -> Product (Fields x) Source #

default fields :: (Generic x, Fields x ~ GFields (SOP I (Code x)), GPOSable (SOP I (Code x))) => x -> Product (Fields x) Source #

emptyFields :: ProductType (Fields x) Source #

default emptyFields :: (GPOSable (SOP I (Code x)), Fields x ~ GFields (SOP I (Code x))) => ProductType (Fields x) Source #

Instances

Instances details
POSable Bool Source # 
Instance details

Defined in Generics.POSable.Instances

Associated Types

type Choices Bool :: Nat Source #

type Fields Bool :: [[Type]] Source #

POSable Double Source # 
Instance details

Defined in Examples

Associated Types

type Choices Double :: Nat Source #

type Fields Double :: [[Type]] Source #

POSable Float Source # 
Instance details

Defined in Examples

Associated Types

type Choices Float :: Nat Source #

type Fields Float :: [[Type]] Source #

POSable Ordering Source # 
Instance details

Defined in Generics.POSable.Instances

Associated Types

type Choices Ordering :: Nat Source #

type Fields Ordering :: [[Type]] Source #

POSable () Source # 
Instance details

Defined in Generics.POSable.Instances

Associated Types

type Choices () :: Nat Source #

type Fields () :: [[Type]] Source #

POSable Undef Source # 
Instance details

Defined in Generics.POSable.Instances

Associated Types

type Choices Undef :: Nat Source #

type Fields Undef :: [[Type]] Source #

POSable x => POSable (Maybe x) Source # 
Instance details

Defined in Generics.POSable.Instances

Associated Types

type Choices (Maybe x) :: Nat Source #

type Fields (Maybe x) :: [[Type]] Source #

(POSable l, POSable r) => POSable (Either l r) Source # 
Instance details

Defined in Generics.POSable.Instances

Associated Types

type Choices (Either l r) :: Nat Source #

type Fields (Either l r) :: [[Type]] Source #

(POSable x0, POSable x1) => POSable (x0, x1) Source # 
Instance details

Defined in Generics.POSable.Instances

Associated Types

type Choices (x0, x1) :: Nat Source #

type Fields (x0, x1) :: [[Type]] Source #

Methods

choices :: (x0, x1) -> Finite (Choices (x0, x1)) Source #

tags :: [Integer] Source #

fromPOSable :: Finite (Choices (x0, x1)) -> Product (Fields (x0, x1)) -> (x0, x1) Source #

fields :: (x0, x1) -> Product (Fields (x0, x1)) Source #

emptyFields :: ProductType (Fields (x0, x1)) Source #

(POSable x0, POSable x1, POSable x2) => POSable (x0, x1, x2) Source # 
Instance details

Defined in Generics.POSable.Instances

Associated Types

type Choices (x0, x1, x2) :: Nat Source #

type Fields (x0, x1, x2) :: [[Type]] Source #

Methods

choices :: (x0, x1, x2) -> Finite (Choices (x0, x1, x2)) Source #

tags :: [Integer] Source #

fromPOSable :: Finite (Choices (x0, x1, x2)) -> Product (Fields (x0, x1, x2)) -> (x0, x1, x2) Source #

fields :: (x0, x1, x2) -> Product (Fields (x0, x1, x2)) Source #

emptyFields :: ProductType (Fields (x0, x1, x2)) Source #

(POSable x0, POSable x1, POSable x2, POSable x3) => POSable (x0, x1, x2, x3) Source # 
Instance details

Defined in Generics.POSable.Instances

Associated Types

type Choices (x0, x1, x2, x3) :: Nat Source #

type Fields (x0, x1, x2, x3) :: [[Type]] Source #

Methods

choices :: (x0, x1, x2, x3) -> Finite (Choices (x0, x1, x2, x3)) Source #

tags :: [Integer] Source #

fromPOSable :: Finite (Choices (x0, x1, x2, x3)) -> Product (Fields (x0, x1, x2, x3)) -> (x0, x1, x2, x3) Source #

fields :: (x0, x1, x2, x3) -> Product (Fields (x0, x1, x2, x3)) Source #

emptyFields :: ProductType (Fields (x0, x1, x2, x3)) Source #

(POSable x0, POSable x1, POSable x2, POSable x3, POSable x4) => POSable (x0, x1, x2, x3, x4) Source # 
Instance details

Defined in Generics.POSable.Instances

Associated Types

type Choices (x0, x1, x2, x3, x4) :: Nat Source #

type Fields (x0, x1, x2, x3, x4) :: [[Type]] Source #

Methods

choices :: (x0, x1, x2, x3, x4) -> Finite (Choices (x0, x1, x2, x3, x4)) Source #

tags :: [Integer] Source #

fromPOSable :: Finite (Choices (x0, x1, x2, x3, x4)) -> Product (Fields (x0, x1, x2, x3, x4)) -> (x0, x1, x2, x3, x4) Source #

fields :: (x0, x1, x2, x3, x4) -> Product (Fields (x0, x1, x2, x3, x4)) Source #

emptyFields :: ProductType (Fields (x0, x1, x2, x3, x4)) Source #

(POSable x0, POSable x1, POSable x2, POSable x3, POSable x4, POSable x5) => POSable (x0, x1, x2, x3, x4, x5) Source # 
Instance details

Defined in Generics.POSable.Instances

Associated Types

type Choices (x0, x1, x2, x3, x4, x5) :: Nat Source #

type Fields (x0, x1, x2, x3, x4, x5) :: [[Type]] Source #

Methods

choices :: (x0, x1, x2, x3, x4, x5) -> Finite (Choices (x0, x1, x2, x3, x4, x5)) Source #

tags :: [Integer] Source #

fromPOSable :: Finite (Choices (x0, x1, x2, x3, x4, x5)) -> Product (Fields (x0, x1, x2, x3, x4, x5)) -> (x0, x1, x2, x3, x4, x5) Source #

fields :: (x0, x1, x2, x3, x4, x5) -> Product (Fields (x0, x1, x2, x3, x4, x5)) Source #

emptyFields :: ProductType (Fields (x0, x1, x2, x3, x4, x5)) Source #

(POSable x0, POSable x1, POSable x2, POSable x3, POSable x4, POSable x5, POSable x6) => POSable (x0, x1, x2, x3, x4, x5, x6) Source # 
Instance details

Defined in Generics.POSable.Instances

Associated Types

type Choices (x0, x1, x2, x3, x4, x5, x6) :: Nat Source #

type Fields (x0, x1, x2, x3, x4, x5, x6) :: [[Type]] Source #

Methods

choices :: (x0, x1, x2, x3, x4, x5, x6) -> Finite (Choices (x0, x1, x2, x3, x4, x5, x6)) Source #

tags :: [Integer] Source #

fromPOSable :: Finite (Choices (x0, x1, x2, x3, x4, x5, x6)) -> Product (Fields (x0, x1, x2, x3, x4, x5, x6)) -> (x0, x1, x2, x3, x4, x5, x6) Source #

fields :: (x0, x1, x2, x3, x4, x5, x6) -> Product (Fields (x0, x1, x2, x3, x4, x5, x6)) Source #

emptyFields :: ProductType (Fields (x0, x1, x2, x3, x4, x5, x6)) Source #

(POSable x0, POSable x1, POSable x2, POSable x3, POSable x4, POSable x5, POSable x6, POSable x7) => POSable (x0, x1, x2, x3, x4, x5, x6, x7) Source # 
Instance details

Defined in Generics.POSable.Instances

Associated Types

type Choices (x0, x1, x2, x3, x4, x5, x6, x7) :: Nat Source #

type Fields (x0, x1, x2, x3, x4, x5, x6, x7) :: [[Type]] Source #

Methods

choices :: (x0, x1, x2, x3, x4, x5, x6, x7) -> Finite (Choices (x0, x1, x2, x3, x4, x5, x6, x7)) Source #

tags :: [Integer] Source #

fromPOSable :: Finite (Choices (x0, x1, x2, x3, x4, x5, x6, x7)) -> Product (Fields (x0, x1, x2, x3, x4, x5, x6, x7)) -> (x0, x1, x2, x3, x4, x5, x6, x7) Source #

fields :: (x0, x1, x2, x3, x4, x5, x6, x7) -> Product (Fields (x0, x1, x2, x3, x4, x5, x6, x7)) Source #

emptyFields :: ProductType (Fields (x0, x1, x2, x3, x4, x5, x6, x7)) Source #

(POSable x0, POSable x1, POSable x2, POSable x3, POSable x4, POSable x5, POSable x6, POSable x7, POSable x8) => POSable (x0, x1, x2, x3, x4, x5, x6, x7, x8) Source # 
Instance details

Defined in Generics.POSable.Instances

Associated Types

type Choices (x0, x1, x2, x3, x4, x5, x6, x7, x8) :: Nat Source #

type Fields (x0, x1, x2, x3, x4, x5, x6, x7, x8) :: [[Type]] Source #

Methods

choices :: (x0, x1, x2, x3, x4, x5, x6, x7, x8) -> Finite (Choices (x0, x1, x2, x3, x4, x5, x6, x7, x8)) Source #

tags :: [Integer] Source #

fromPOSable :: Finite (Choices (x0, x1, x2, x3, x4, x5, x6, x7, x8)) -> Product (Fields (x0, x1, x2, x3, x4, x5, x6, x7, x8)) -> (x0, x1, x2, x3, x4, x5, x6, x7, x8) Source #

fields :: (x0, x1, x2, x3, x4, x5, x6, x7, x8) -> Product (Fields (x0, x1, x2, x3, x4, x5, x6, x7, x8)) Source #

emptyFields :: ProductType (Fields (x0, x1, x2, x3, x4, x5, x6, x7, x8)) Source #

(POSable x0, POSable x1, POSable x2, POSable x3, POSable x4, POSable x5, POSable x6, POSable x7, POSable x8, POSable x9) => POSable (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9) Source # 
Instance details

Defined in Generics.POSable.Instances

Associated Types

type Choices (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9) :: Nat Source #

type Fields (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9) :: [[Type]] Source #

Methods

choices :: (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9) -> Finite (Choices (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9)) Source #

tags :: [Integer] Source #

fromPOSable :: Finite (Choices (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9)) -> Product (Fields (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9)) -> (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9) Source #

fields :: (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9) -> Product (Fields (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9)) Source #

emptyFields :: ProductType (Fields (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9)) Source #

(POSable x0, POSable x1, POSable x2, POSable x3, POSable x4, POSable x5, POSable x6, POSable x7, POSable x8, POSable x9, POSable x10) => POSable (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10) Source # 
Instance details

Defined in Generics.POSable.Instances

Associated Types

type Choices (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10) :: Nat Source #

type Fields (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10) :: [[Type]] Source #

Methods

choices :: (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10) -> Finite (Choices (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10)) Source #

tags :: [Integer] Source #

fromPOSable :: Finite (Choices (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10)) -> Product (Fields (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10)) -> (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10) Source #

fields :: (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10) -> Product (Fields (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10)) Source #

emptyFields :: ProductType (Fields (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10)) Source #

(POSable x0, POSable x1, POSable x2, POSable x3, POSable x4, POSable x5, POSable x6, POSable x7, POSable x8, POSable x9, POSable x10, POSable x11) => POSable (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11) Source # 
Instance details

Defined in Generics.POSable.Instances

Associated Types

type Choices (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11) :: Nat Source #

type Fields (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11) :: [[Type]] Source #

Methods

choices :: (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11) -> Finite (Choices (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11)) Source #

tags :: [Integer] Source #

fromPOSable :: Finite (Choices (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11)) -> Product (Fields (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11)) -> (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11) Source #

fields :: (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11) -> Product (Fields (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11)) Source #

emptyFields :: ProductType (Fields (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11)) Source #

(POSable x0, POSable x1, POSable x2, POSable x3, POSable x4, POSable x5, POSable x6, POSable x7, POSable x8, POSable x9, POSable x10, POSable x11, POSable x12) => POSable (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12) Source # 
Instance details

Defined in Generics.POSable.Instances

Associated Types

type Choices (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12) :: Nat Source #

type Fields (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12) :: [[Type]] Source #

Methods

choices :: (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12) -> Finite (Choices (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12)) Source #

tags :: [Integer] Source #

fromPOSable :: Finite (Choices (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12)) -> Product (Fields (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12)) -> (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12) Source #

fields :: (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12) -> Product (Fields (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12)) Source #

emptyFields :: ProductType (Fields (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12)) Source #

(POSable x0, POSable x1, POSable x2, POSable x3, POSable x4, POSable x5, POSable x6, POSable x7, POSable x8, POSable x9, POSable x10, POSable x11, POSable x12, POSable x13) => POSable (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13) Source # 
Instance details

Defined in Generics.POSable.Instances

Associated Types

type Choices (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13) :: Nat Source #

type Fields (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13) :: [[Type]] Source #

Methods

choices :: (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13) -> Finite (Choices (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13)) Source #

tags :: [Integer] Source #

fromPOSable :: Finite (Choices (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13)) -> Product (Fields (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13)) -> (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13) Source #

fields :: (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13) -> Product (Fields (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13)) Source #

emptyFields :: ProductType (Fields (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13)) Source #

(POSable x0, POSable x1, POSable x2, POSable x3, POSable x4, POSable x5, POSable x6, POSable x7, POSable x8, POSable x9, POSable x10, POSable x11, POSable x12, POSable x13, POSable x14) => POSable (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14) Source # 
Instance details

Defined in Generics.POSable.Instances

Associated Types

type Choices (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14) :: Nat Source #

type Fields (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14) :: [[Type]] Source #

Methods

choices :: (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14) -> Finite (Choices (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14)) Source #

tags :: [Integer] Source #

fromPOSable :: Finite (Choices (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14)) -> Product (Fields (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14)) -> (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14) Source #

fields :: (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14) -> Product (Fields (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14)) Source #

emptyFields :: ProductType (Fields (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14)) Source #

(POSable x0, POSable x1, POSable x2, POSable x3, POSable x4, POSable x5, POSable x6, POSable x7, POSable x8, POSable x9, POSable x10, POSable x11, POSable x12, POSable x13, POSable x14, POSable x15) => POSable (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15) Source # 
Instance details

Defined in Generics.POSable.Instances

Associated Types

type Choices (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15) :: Nat Source #

type Fields (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15) :: [[Type]] Source #

Methods

choices :: (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15) -> Finite (Choices (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15)) Source #

tags :: [Integer] Source #

fromPOSable :: Finite (Choices (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15)) -> Product (Fields (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15)) -> (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15) Source #

fields :: (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15) -> Product (Fields (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15)) Source #

emptyFields :: ProductType (Fields (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15)) Source #

class All (SListI :: [Type] -> Constraint) (Code a) => Generic a #

The class of representable datatypes.

The SOP approach to generic programming is based on viewing datatypes as a representation (Rep) built from the sum of products of its components. The components of a datatype are specified using the Code type family.

The isomorphism between the original Haskell datatype and its representation is witnessed by the methods of this class, from and to. So for instances of this class, the following laws should (in general) hold:

to . from === id :: a -> a
from . to === id :: Rep a -> Rep a

You typically don't define instances of this class by hand, but rather derive the class instance automatically.

Option 1: Derive via the built-in GHC-generics. For this, you need to use the DeriveGeneric extension to first derive an instance of the Generic class from module GHC.Generics. With this, you can then give an empty instance for Generic, and the default definitions will just work. The pattern looks as follows:

import qualified GHC.Generics as GHC
import Generics.SOP

...

data T = ... deriving (GHC.Generic, ...)

instance Generic T -- empty
instance HasDatatypeInfo T -- empty, if you want/need metadata

Option 2: Derive via Template Haskell. For this, you need to enable the TemplateHaskell extension. You can then use deriveGeneric from module Generics.SOP.TH to have the instance generated for you. The pattern looks as follows:

import Generics.SOP
import Generics.SOP.TH

...

data T = ...

deriveGeneric ''T -- derives HasDatatypeInfo as well

Tradeoffs: Whether to use Option 1 or 2 is mainly a matter of personal taste. The version based on Template Haskell probably has less run-time overhead.

Non-standard instances: It is possible to give Generic instances manually that deviate from the standard scheme, as long as at least

to . from === id :: a -> a

still holds.

Instances

Instances details
Generic Undef Source # 
Instance details

Defined in Generics.POSable.Representation

Associated Types

type Code Undef :: [[Type]] #

Methods

from :: Undef -> Rep Undef #

to :: Rep Undef -> Undef #

data Finite (n :: Nat) #

Finite number type. Finite n is inhabited by exactly n values. Invariants:

getFinite x < natVal x
getFinite x >= 0

Instances

Instances details
KnownNat n => Bounded (Finite n)

Throws an error for Finite 0

Instance details

Defined in Data.Finite.Internal

Methods

minBound :: Finite n #

maxBound :: Finite n #

KnownNat n => Enum (Finite n) 
Instance details

Defined in Data.Finite.Internal

Methods

succ :: Finite n -> Finite n #

pred :: Finite n -> Finite n #

toEnum :: Int -> Finite n #

fromEnum :: Finite n -> Int #

enumFrom :: Finite n -> [Finite n] #

enumFromThen :: Finite n -> Finite n -> [Finite n] #

enumFromTo :: Finite n -> Finite n -> [Finite n] #

enumFromThenTo :: Finite n -> Finite n -> Finite n -> [Finite n] #

Eq (Finite n) 
Instance details

Defined in Data.Finite.Internal

Methods

(==) :: Finite n -> Finite n -> Bool #

(/=) :: Finite n -> Finite n -> Bool #

KnownNat n => Integral (Finite n)

Not modular arithmetic.

Instance details

Defined in Data.Finite.Internal

Methods

quot :: Finite n -> Finite n -> Finite n #

rem :: Finite n -> Finite n -> Finite n #

div :: Finite n -> Finite n -> Finite n #

mod :: Finite n -> Finite n -> Finite n #

quotRem :: Finite n -> Finite n -> (Finite n, Finite n) #

divMod :: Finite n -> Finite n -> (Finite n, Finite n) #

toInteger :: Finite n -> Integer #

KnownNat n => Num (Finite n)

Modular arithmetic. Only the fromInteger function is supposed to be useful.

Instance details

Defined in Data.Finite.Internal

Methods

(+) :: Finite n -> Finite n -> Finite n #

(-) :: Finite n -> Finite n -> Finite n #

(*) :: Finite n -> Finite n -> Finite n #

negate :: Finite n -> Finite n #

abs :: Finite n -> Finite n #

signum :: Finite n -> Finite n #

fromInteger :: Integer -> Finite n #

Ord (Finite n) 
Instance details

Defined in Data.Finite.Internal

Methods

compare :: Finite n -> Finite n -> Ordering #

(<) :: Finite n -> Finite n -> Bool #

(<=) :: Finite n -> Finite n -> Bool #

(>) :: Finite n -> Finite n -> Bool #

(>=) :: Finite n -> Finite n -> Bool #

max :: Finite n -> Finite n -> Finite n #

min :: Finite n -> Finite n -> Finite n #

KnownNat n => Read (Finite n) 
Instance details

Defined in Data.Finite.Internal

KnownNat n => Real (Finite n) 
Instance details

Defined in Data.Finite.Internal

Methods

toRational :: Finite n -> Rational #

Show (Finite n) 
Instance details

Defined in Data.Finite.Internal

Methods

showsPrec :: Int -> Finite n -> ShowS #

show :: Finite n -> String #

showList :: [Finite n] -> ShowS #

Generic (Finite n) 
Instance details

Defined in Data.Finite.Internal

Associated Types

type Rep (Finite n) :: Type -> Type #

Methods

from :: Finite n -> Rep (Finite n) x #

to :: Rep (Finite n) x -> Finite n #

NFData (Finite n) 
Instance details

Defined in Data.Finite.Internal

Methods

rnf :: Finite n -> () #

type Rep (Finite n) 
Instance details

Defined in Data.Finite.Internal

type Rep (Finite n) = D1 ('MetaData "Finite" "Data.Finite.Internal" "finite-typelits-0.1.4.2-5H6I7DpI5LO7unHaqoEAep" 'True) (C1 ('MetaCons "Finite" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer)))