Safe Haskell | None |
---|---|
Language | Haskell2010 |
Cantor
Description
Cantor pairing gives us an isomorphism between a single natural number and pairs of natural numbers. This package provides a modern API to this functionality using GHC generics, allowing the encoding of arbitrary combinations of finite or countably infinite types in natural number form.
As a user, all you need to do is derive generic and get the instances for free.
Example
import GHC.Generics import Cantor data MyType = MyType { value1 :: [ Maybe Bool ] , value2 :: Integer } deriving (Generic) instance Cantor MyType
A warning: this package will work with recursive types, but you *must* manually specify the cardinality. This unfortunately is necessary due to GHC generics marking all fields as recursive, regardless of whether or not they actually are. Still, it's straightforward to manually specify the cardinality:
Recursive example
data Tree a = Leaf | Branch (Tree a) a (Tree a) deriving (Generic) instance Cantor a => Cantor (Tree a) where cardinality = Countable
If your type is finite, you can specify this by deriving the Finite
typeclass, which is a subclass of Cantor
:
Finite example
data Color = Red | Green | Blue deriving (Generic) instance Cantor Color instance Finite Color
Synopsis
- cantorEnumeration :: Cantor a => [a]
- data Cardinality
- class Cantor a where
- cardinality :: Cardinality
- toCantor :: Integer -> a
- fromCantor :: a -> Integer
- class Cantor a => Finite a where
Documentation
cantorEnumeration :: Cantor a => [a] Source #
Enumerates all values of a type by mapping toCantor
over the naturals.
data Cardinality Source #
Cardinality
can be either Finite
or Countable
. Countable
cardinality entails that a type has the same cardinality as the natural numbers. Note that not all infinite types are countable: for example, Natural -> Natural
is an infinite type, but it is not countably infinite; the basic intuition is that there is no possible way to enumerate all values of type Natural -> Natural
without "skipping" almost all of them. This is in contrast to the naturals, where despite their being infinite, we can trivially (by definition, in fact!) enumerate all of them without skipping any.
Instances
Eq Cardinality Source # | |
Defined in Cantor | |
Ord Cardinality Source # | |
Defined in Cantor Methods compare :: Cardinality -> Cardinality -> Ordering # (<) :: Cardinality -> Cardinality -> Bool # (<=) :: Cardinality -> Cardinality -> Bool # (>) :: Cardinality -> Cardinality -> Bool # (>=) :: Cardinality -> Cardinality -> Bool # max :: Cardinality -> Cardinality -> Cardinality # min :: Cardinality -> Cardinality -> Cardinality # | |
Show Cardinality Source # | |
Defined in Cantor Methods showsPrec :: Int -> Cardinality -> ShowS # show :: Cardinality -> String # showList :: [Cardinality] -> ShowS # | |
Generic Cardinality Source # | |
type Rep Cardinality Source # | |
Defined in Cantor type Rep Cardinality = D1 (MetaData "Cardinality" "Cantor" "cantor-pairing-0.1.0.0-9psbWPZlnGKBdY6UCFstnv" False) (C1 (MetaCons "Finite" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Integer)) :+: C1 (MetaCons "Countable" PrefixI False) (U1 :: Type -> Type)) |
The Cantor
class gives a way to convert a type to and from the natural numbers, as well as specifies the cardinality of the type.
Minimal complete definition
Nothing
Methods
cardinality :: Cardinality Source #
cardinality :: GCantor (Rep a) => Cardinality Source #
toCantor :: Integer -> a Source #
toCantor :: (Generic a, GCantor (Rep a)) => Integer -> a Source #
fromCantor :: a -> Integer Source #
fromCantor :: (Generic a, GCantor (Rep a)) => a -> Integer Source #
Instances
class Cantor a => Finite a where Source #
The Finite
typeclass simply entails that the Cardinality
of the set is finite.
Minimal complete definition
Nothing
Methods
Instances
Finite Bool Source # | |
Defined in Cantor Methods | |
Finite Char Source # | |
Defined in Cantor Methods | |
Finite Int Source # | |
Defined in Cantor Methods | |
Finite Int8 Source # | |
Defined in Cantor Methods | |
Finite Int16 Source # | |
Defined in Cantor Methods | |
Finite Int32 Source # | |
Defined in Cantor Methods | |
Finite Int64 Source # | |
Defined in Cantor Methods | |
Finite Word8 Source # | |
Defined in Cantor Methods | |
Finite Word16 Source # | |
Defined in Cantor Methods | |
Finite Word32 Source # | |
Defined in Cantor Methods | |
Finite Word64 Source # | |
Defined in Cantor Methods | |
Finite () Source # | |
Defined in Cantor Methods | |
Finite Void Source # | |
Defined in Cantor Methods | |
Finite a => Finite (Maybe a) Source # | |
Defined in Cantor Methods | |
Finite a => Finite (Min a) Source # | |
Defined in Cantor Methods | |
Finite a => Finite (Max a) Source # | |
Defined in Cantor Methods | |
Finite a => Finite (First a) Source # | |
Defined in Cantor Methods | |
Finite a => Finite (Last a) Source # | |
Defined in Cantor Methods | |
Finite a => Finite (Option a) Source # | |
Defined in Cantor Methods | |
Finite a => Finite (Identity a) Source # | |
Defined in Cantor Methods | |
Finite a => Finite (Sum a) Source # | |
Defined in Cantor Methods | |
Finite a => Finite (Product a) Source # | |
Defined in Cantor Methods | |
(Finite a, Finite b) => Finite (a -> b) Source # | |
Defined in Cantor Methods | |
(Finite a, Finite b) => Finite (Either a b) Source # | |
Defined in Cantor Methods | |
(Finite a, Finite b) => Finite (a, b) Source # | |
Defined in Cantor Methods | |
(Finite a, Finite b) => Finite (Arg a b) Source # | |
Defined in Cantor Methods | |
Finite (Proxy a) Source # | |
Defined in Cantor Methods | |
(Finite a, Finite b, Finite c) => Finite (a, b, c) Source # | |
Defined in Cantor Methods | |
Finite a => Finite (Const a b) Source # | |
Defined in Cantor Methods | |
(Finite a, Finite b, Finite c, Finite d) => Finite (a, b, c, d) Source # | |
Defined in Cantor Methods | |
(Finite a, Finite b, Finite c, Finite d, Finite e) => Finite (a, b, c, d, e) Source # | |
Defined in Cantor Methods | |
(Finite a, Finite b, Finite c, Finite d, Finite e, Finite f) => Finite (a, b, c, d, e, f) Source # | |
Defined in Cantor Methods | |
(Finite a, Finite b, Finite c, Finite d, Finite e, Finite f, Finite g) => Finite (a, b, c, d, e, f, g) Source # | |
Defined in Cantor Methods |