PortabilityOS independent
Stabilityunstable
MaintainerStephen E.A. Britton (sbritton (at) cbu (dot) edu)
Safe HaskellSafe-Infered

LargeCardinalHierarchy

Description

The LargeCardinalHierarchy module defines a recursively enumerable, countably infinite subclass of the logically (consistent) maximal transfinite set-theoretic universe ZFC+Con(LargeCardinals) (Zermelo-Frankel Set Theory + Axiom of Choice + All known large cardinals consistent with ZFC) via data constructors for each large cardinal within the hierarchy and functions over them. The algebraic data type Card is a Haskell implementation of the set theoretic proper class of all cardinals, Card. Card has value constructors for a countably infinite (aleph-null sized) subset of every cardinal type of all known large cardinals consistent with ZFC (Zermelo-Frankel Set Theory + Axiom of Choice) or, equivalently, ZF+GCH (Zermelo-Frankel Set Theory + Generalized Continuum Hypothesis).

Synopsis

Documentation

apply :: (t -> t1) -> [t] -> [t1]Source

apply is a binary higher-order function that takes a function f and a list of type x values, [x], and returns a new list of values derived from the application of f to each of the x values within [x].

zero :: CardSource

zero is the unique nullary function within the LargeCardinalHierarchy module that returns the additive identity element (and multiplicative absorbing element within the class of all cardinals), cardinal 0, via the Card constructor.

one :: CardSource

one is the unique nullary function within the LargeCardinalHierarchy module that returns the multiplicative identity element within the class of all cardinals, cardinal 1, via the Card constructor.

absolute :: CardSource

absolute is a type synonym (nullary function) for AbsoluteInfinity; the supremum of the class of all cardinals, Card.

zeros :: [Card]Source

zeros is a nullary function that returns a countably-infinite (aleph-null sized) sequence (a stream) of cardinal zeros.

ones :: [Card]Source

ones is a nullary function that returns a countably-infinite (aleph-null sized) sequence (a stream) of cardinal ones.

alefz :: Int -> [Card]Source

alefz is a unary function that takes an Int n and returns an n-element list of the first n aleph numbers enumerating from aleph-null.

tavs :: [Card]Source

tavs is a nullary function that returns a countably-infinite (aleph-null sized) sequence (a stream) of TAVs; TAV being the symbol for the absolutely infinite supremum of the class of all cardinals, Card.

absolutes :: [Card]Source

absolutes is a nullary function that returns a countably-infinite (aleph-null sized) sequence (a stream) of AbsoluteInfinitys; AbsoluteInfinity being the cardinality the class of all cardinals, Card.

absoluteInfinities :: [Card]Source

absoluteInfinities is a type synonym (nullary function) for absolutes.

(#) :: Card -> Card -> CardSource

'(#)' is binary function from (Card, Card) to Card. '(#)' takes two cardinal numbers and returns their binary sum. Category-theoretically speaking, '(#)' is a coproduct in the class of all cardinals, Card.

(#.) :: [Card] -> CardSource

'(#.)' is a unary (or, multiary) function from [Card] to Card. '(#.)' takes a list of cardinal numbers and returns their multiary sum. Category-theoretically speaking, '(#.)' is a coproduct in the class of all cardinals, Card.

(*.) :: Card -> Card -> CardSource

'(*.)' is a binary function from (Card, Card) to Card. '(*.)' takes two cardinal numbers and returns their binary product.

x :: [Card] -> CardSource

x is a unary (or, multiary) function from [Card] to Card. x takes a list of cardinal numbers and returns their multiary product.

(^.) :: Card -> Card -> CardSource

'(^.)' is a binary function from (Card,Card) to Card. '(^.)' take two cardinal numbers and returns the power of the zeroth cardinal number exponentiated to the first cardinal number.

cp :: [a] -> [b] -> [(a, b)]Source

cp is a binary function from [a] & [b] to [(a, b)]. cp takes two lists of elements and returns the list of all ordered pairs of elements between the two lists. cp is the Cartesian product operator.

cartesianProduct :: [a] -> [b] -> [(a, b)]Source

cartesianProduct is a binary function from [a] & [b] to [(a, b)]. cartesianProduct takes two lists of elements and returns the list of all ordered pairs of elements between the two lists cartesianProduct is the Cartesian product operator.

powerList :: [a] -> [[a]]Source

powerList is a unary function from [a] -> [[a]]. powerList takes a list of elements and returns the list of all sublists of that list. powerList is a canonical example of Haskell's facilitation in expressing functions elegantly.

ascend :: Integer -> [Card]Source

ascend is a unary function from Integer to [Card]. ascend takes a natural number n and returns a list of aleph cardinals from aleph 0 to aleph n.

descend :: Integer -> [Card]Source

descend is a unary function from Integer to [Card]. descend takes a natural number n and returns a list of aleph cardinals from aleph n to aleph 0.

level :: Int -> (Card -> Card) -> Integer -> CardSource

level is a ternary function from (Int, Card, Integer) to Card. level takes an Int n, a Card value constructor cons, and an Integer m and returns a Card equal to cons $ cons $ cons $ ... $ Card m.

ascent :: Int -> (Card -> Card) -> Integer -> Integer -> [Card]Source

ascent is a quaternary function from (Int, Card, Integer, Integer) to [Card]. ascent takes an Int x, a Card value constructor cons, and two Integers y and z and returns a list of level x type cons Card values from y to z, where y <= z. ascent is a generalization of ascend over all data constructors in Card.

descent :: Int -> (Card -> Card) -> Integer -> Integer -> [Card]Source

descent is a quaternary function from (Int, Card, Integer, Integer) to [Card]. descent takes an Int x, a Card value constructor cons, and two Integers y and z and returns a list of level x type cons Card values from y to z, where y >= z. descent is a generalization of descend over all data constructors in Card.

c :: Integer -> CardSource

c is a unary function that takes an Integer n and returns a finite cardinal number, Card n.

alef :: Integer -> CardSource

alef is a unary function that takes an Integer n and returns a tranfinite aleph number subscripted by cardinal n, Aleph n.

aleph :: Int -> Integer -> CardSource

aleph is a binary function from (Int, Integer) to Card. aleph takes an Int m and an Integer n and returns an m level Aleph whose deepest subscript is n.

beth :: Int -> Integer -> CardSource

beth is a binary function from (Int, Integer) to Card. beth takes an Int m and an Integer n and returns an m level Aleph whose deepest subscript is n.

wInac :: Int -> Integer -> CardSource

wInac is a binary function from (Int, Integer) to Card. wInac takes an Int m and an Integer n and returns an m level WeaklyInaccessible whose deepest subscript is n.

weaklyInaccessible :: Int -> Integer -> CardSource

weaklyInaccessible is a function synonym for wInac.

sInac :: Int -> Integer -> CardSource

sInac is a binary function from (Int, Integer) to Card. sInac takes an Int m and an Integer n and returns an m level StronglyInaccessible whose deepest subscript is n.

stronglyInaccessible :: Int -> Integer -> CardSource

stronglyInaccessible is a function synonym for sInac.

theta :: Int -> Integer -> CardSource

theta is a binary function from (Int, Integer) to Card. theta takes an Int m and an Integer n and returns an m level StronglyInaccessible cardinal whose deepest subscript is n. theta is a function synonym for sInac.

aInac :: Int -> Integer -> CardSource

aInac is a binary function from (Int, Integer) to Card. aInac takes an Int m and an Integer n and returns an m level AlphaInaccessible whose deepest subscript is n.

alphaInaccessible :: Int -> Integer -> CardSource

alphaInaccessible is a binary function from (Int, Integer) to Card. alphaInaccessible takes an Int m and an Integer n and returns an m level AlphaInaccessible whose deepest subscript is n. alphaInaccessible is a function synonym for aInac.

hInac :: Int -> Integer -> CardSource

hInac is a binary function from (Int, Integer) to Card. hInac takes an Int m and an Integer n and returns an m level HyperInaccessible whose deepest subscript is n.

hyperInaccessible :: Int -> Integer -> CardSource

hyperInaccessible is a binary function from (Int, Integer) to Card. hyperInaccessible takes an Int m and an Integer n and returns an m level HyperInaccessible whose deepest subscript is n. hyperInaccessible is a function synonym for hInac.

nu :: Int -> Integer -> CardSource

nu is a binary function from (Int, Integer) to Card. nu takes an Int m and an Integer n and returns an m level HyperInaccessible whose deepest subscript is n. nu is a function synonym for hInac.

h2Inac :: Int -> Integer -> CardSource

h2Inac is a binary function from (Int, Integer) to Card. h2Inac takes an Int m and an Integer n and returns an m level Hyper2Inaccessible whose deepest subscript is n.

hyper2Inaccessible :: Int -> Integer -> CardSource

hyper2Inaccessible is a binary function from (Int, Integer) to Card. hyper2Inaccessible takes an Int m and an Integer n and returns an m level Hyper2Inaccessible whose deepest subscript is n. hyper2Inaccessible is a function synonym for h2Inac.

mu :: Int -> Integer -> CardSource

mu is a binary function from (Int, Integer) to Card. mu takes an Int m and an Integer n and returns an m level Hyper2Inaccessible whose deepest subscript is n. mu is a function synonym for h2Inac.

wMahlo :: Int -> Integer -> CardSource

wMahlo is a binary function from (Int, Integer) to Card. wMahlo takes an Int m and an Integer n and returns an m level WeaklyMahlo whose deepest subscript is n.

weaklyMahlo :: Int -> Integer -> CardSource

weaklyMahlo is a binary function from (Int, Integer) to Card. weaklyMahlo takes an Int m and an Integer n and returns an m level WeaklyMahlo whose deepest subscript is n. weaklyMahlo is a function synonym for wMahlo.

sMahlo :: Int -> Integer -> CardSource

sMahlo is a binary function from (Int, Integer) to Card. sMahlo takes an Int m and an Integer n and returns an m level StronglyMahlo whose deepest subscript is n.

stronglyMahlo :: Int -> Integer -> CardSource

stronglyMahlo is a binary function from (Int, Integer) to Card. stronglyMahlo takes an Int m and an Integer n and returns an m level StronglyMahlo whose deepest subscript is n. stronglyMahlo is a function synonym for sMahlo.

rho :: Int -> Integer -> CardSource

rho is a binary function from (Int, Integer) to Card. rho takes an Int m and an Integer n and returns an m level StronglyMahlo cardinal whose deepest subscript is n.

aMahlo :: Int -> Integer -> CardSource

aMahlo is a binary function from (Int, Integer) to Card. aMahlo takes an Int m and an Integer n and returns an m level AlphaMahlo whose deepest subscript is n.

alphaMahlo :: Int -> Integer -> CardSource

alphaMahlo is a binary function from (Int, Integer) to Card. alphaMahlo takes an Int m and an Integer n and returns an m level AlphaMahlo whose deepest subscript is n. alphaMahlo is a function synonym for aMahlo.

hMahlo :: Int -> Integer -> CardSource

hMahlo is a binary function from (Int, Integer) to Card. hMahlo takes an Int m and an Integer n and returns an m level HyperMahlo whose deepest subscript is n.

hyperMahlo :: Int -> Integer -> CardSource

hyperMahlo is a binary function from (Int, Integer) to Card. hyperMahlo takes an Int m and an Integer n and returns an m level HyperMahlo whose deepest subscript is n.

reflect :: Int -> Integer -> CardSource

Binary function from (Int, Integer) to Card reflect takes an Int m and an Integer n and returns an m level reflecting cardinal whose deepest subscript is n

reflecting :: Int -> Integer -> CardSource

pii :: Int -> Int -> Int -> Integer -> CardSource

Binary function from (Int, Int, Int, Integer) to Card pii takes an Int x, an Int y, an Int m, and an Integer n and returns the m level pi-(x, y)-indescribable cardinal whose deepest subscript is n

piIndesc :: Int -> Int -> Int -> Integer -> CardSource

piIndescribable :: Int -> Int -> Int -> Integer -> CardSource

ti :: Int -> Integer -> CardSource

totalIndesc :: Int -> Integer -> CardSource

totallyIndescribable :: Int -> Integer -> CardSource

ni :: Int -> Integer -> CardSource

nuIndesc :: Int -> Integer -> CardSource

nuIndescribable :: Int -> Integer -> CardSource

lambdaUnfold :: Int -> Integer -> CardSource

lambdaUnfoldable :: Int -> Integer -> CardSource

unfold :: Int -> Integer -> CardSource

unfoldable :: Int -> Integer -> CardSource

lambdaShrewd :: Int -> Integer -> CardSource

shrewd :: Int -> Integer -> CardSource

ether :: Int -> Integer -> CardSource

Binary function from (Int, Integer) to Card ether takes an Int m and an Integer n and returns an m level ethereal cardinal whose deepest subscript is n

ethereal :: Int -> Integer -> CardSource

subtle :: Int -> Integer -> CardSource

Binary function from (Int, Integer) to Card subtle takes an Int m and an Integer n and returns an m level subtle cardinal whose deepest subscript is n

almostIneff :: Int -> Integer -> CardSource

almostIneffable :: Int -> Integer -> CardSource

ineff :: Int -> Integer -> CardSource

ineffable :: Int -> Integer -> CardSource

nIneff :: Int -> Integer -> CardSource

nIneffable :: Int -> Integer -> CardSource

totalIneff :: Int -> Integer -> CardSource

totallyIneffable :: Int -> Integer -> CardSource

remark :: Int -> Integer -> CardSource

remarkable :: Int -> Integer -> CardSource

aErdos :: Int -> Integer -> CardSource

alphaErdos :: Int -> Integer -> CardSource

gamma :: Int -> Integer -> CardSource

gErdos :: Int -> Integer -> CardSource

gammaErdos :: Int -> Integer -> CardSource

aRamsey :: Int -> Integer -> CardSource

almostRamsey :: Int -> Integer -> CardSource

jonsson :: Int -> Integer -> CardSource

rowbottom :: Int -> Integer -> CardSource

ramsey :: Int -> Integer -> CardSource

iRamsey :: Int -> Integer -> CardSource

ineffablyRamsey :: Int -> Integer -> CardSource

measure :: Int -> Integer -> CardSource

measurable :: Int -> Integer -> CardSource

kappa :: Int -> Integer -> CardSource

Binary function from (Int, Integer) to Card kappa takes an Int m and an Integer n and returns an m level measurable cardinal whose deepest subscript is n

zeroDag :: Int -> Integer -> CardSource

zeroDagger :: Int -> Integer -> CardSource

lambdaStrong :: Int -> Integer -> CardSource

strong :: Int -> Integer -> CardSource

woodin :: Int -> Integer -> CardSource

whWoodin :: Int -> Integer -> CardSource

weaklyHyperWoodin :: Int -> Integer -> CardSource

shelah :: Int -> Integer -> CardSource

hWoodin :: Int -> Integer -> CardSource

hyperWoodin :: Int -> Integer -> CardSource

ss :: Int -> Integer -> CardSource

supStrong :: Int -> Integer -> CardSource

superstrong :: Int -> Integer -> CardSource

superStrong :: Int -> Integer -> CardSource

subcompact :: Int -> Integer -> CardSource

stronglyCompact :: Int -> Integer -> CardSource

supCompact :: Int -> Integer -> CardSource

superCompact :: Int -> Integer -> CardSource

eta :: Int -> Integer -> CardSource

etaExtend :: Int -> Integer -> CardSource

etaExtendible :: Int -> Integer -> CardSource

ex :: Int -> Integer -> CardSource

extend :: Int -> Integer -> CardSource

extendible :: Int -> Integer -> CardSource

vopenka :: Int -> Integer -> CardSource

nss :: Int -> Integer -> CardSource

nSuperstrong :: Int -> Integer -> CardSource

nah :: Int -> Integer -> CardSource

nAlmostHuge :: Int -> Integer -> CardSource

nsah :: Int -> Integer -> CardSource

nSuperAlmostHuge :: Int -> Integer -> CardSource

nh :: Int -> Integer -> CardSource

nHuge :: Int -> Integer -> CardSource

nsh :: Int -> Integer -> CardSource

nSuperHuge :: Int -> Integer -> CardSource

rank :: Int -> Integer -> CardSource

lambda :: Int -> Integer -> CardSource

Binary function from (Int, Integer) to Card lambda takes an Int m and an Integer n and returns an m level rank-into-rank cardinal whose deepest subscript is n

rankIntoRank :: Int -> Integer -> CardSource

reinhardt :: Int -> Integer -> CardSource

order :: Int -> (Card -> Card) -> [Card]Source

Binary function from Int x Card to Card order takes an Int m and a Card card and returns the countably infinite list of level m card(s) indexed over the natural numbers [0..]. That is, order returns [(card m 0), (card m 1), (card m 2), (card m 3), . . .]

order increases linearly over its second argument keeping its first argument constant. order indexes in a zero order manner over the natural numbers. order m card = [(card m 0), (card m 1), (card m 2), (card m 3), . . .]

fixedpoints increases hierarchly over its first argument keeping its second argument constant. fixedpoints indexes in a higher order manner over its own arguments. fixedpoints m card = [(card 1 m), (card 2 m), (card 3 m), (card 4 m), . . .]

zeroOrder :: Int -> (Card -> Card) -> [Card]Source

Binary function from Int x Card to Card zeroOrder takes an Int m and a Card card and returns the countably infinite list of level m card(s) indexed over the natural numbers [0..]. That is, zeroOrder returns [(card m 0), (card m 1), (card m 2), (card m 3), . . .]

zeroOrder increases linearly over its second argument keeping its first argument constant. zeroOrder indexes in a zero order manner over the natural numbers. zeroOrder m card = [(card m 0), (card m 1), (card m 2), (card m 3), . . .]

zeroOrder 1 Aleph = [Aleph(0), Aleph(1), Aleph(2), Aleph(3), . . .]

higherOrder increases hierarchly over its first argument keeping its second argument constant. higherOrder indexes in a higher order manner over its own arguments. higherOrder m card = [(card 1 m), (card 2 m), (card 3 m), (card 4 m), . . .]

higherOrder 1 Aleph = [(1), Aleph(1), Aleph(Aleph(1)), Aleph(Aleph(Aleph(1))), . . .]

orderClass :: Int -> (Card -> Card) -> [Card]Source

Binary function from Int x Card to Card orderClass takes an Int m and a Card card and returns the countably infinite list of level m card(s) indexed over the natural numbers [0..]. That is, orderClass returns [(card m 0), (card m 1), (card m 2), (card m 3), . . .] orderClass is identical to order

club :: (Card -> Card) -> [Card]Source

Unary function from Card to Card club takes a Card value constructor card and returns the countably infinite list of type card Card fixed points indexed over the natural numbers [0..]. That is, club returns [(card 1 0), (card 2 0), (card 3 0), . . .] club is an implementation of the normal function f: Ordinals -> Ordinals that defines a closed and unbounded (club) class of ordinal fixed points according to the Fixed point lemma for normal functions

fixedpoints :: Integer -> (Card -> Card) -> [Card]Source

Binary function from Int x Card to Card fixedpoints takes an Int m and a Card value constructor card and returns the countably infinite list of type card Card fixed points indexed over the natural number m. That is, fixedpoints returns [(card 1 m), (card 2 m), (card 3 m), . . .] fixedpoints is an implementation of the normal function f: Ordinals -> Ordinals that defines a closed and unbounded (club) class of ordinal fixed points according to the Fixed point lemma for normal functions

fixedpoints increases hierarchly over its first argument keeping its second argument constant. fixedpoints indexes in a higher order manner over its own arguments. fixedpoints m card = [(card 1 m), (card 2 m), (card 3 m), (card 4 m), . . .]

order increases linearly over its second argument keeping its first argument constant. order indexes in a zero order manner over the natural numbers. order m card = [(card m 0), (card m 1), (card m 2), (card m 3), . . .]

higherOrder :: Integer -> (Card -> Card) -> [Card]Source

Binary function from Int x Card to Card higherOrder takes an Int m and a Card value constructor card and returns the countably infinite list of type card Card fixed points indexed over the natural number m. That is, higherOrder returns [(card 1 m), (card 2 m), (card 3 m), . . .] higherOrder is an implementation of the normal function f: Ordinals -> Ordinals that defines a closed and unbounded (club) class of ordinal fixed points according to the Fixed point lemma for normal functions

higherOrder increases hierarchly over its first argument keeping its second argument constant. higherOrder indexes in a higher order manner over its own arguments. higherOrder m card = [(card 1 m), (card 2 m), (card 3 m), (card 4 m), . . .]

higherOrder 1 Aleph = [(1), Aleph(1), Aleph(Aleph(1)), Aleph(Aleph(Aleph(1))), . . .]

zeroOrder increases linearly over its second argument keeping its first argument constant. zeroOrder indexes in a zero order manner over the natural numbers. zeroOrder m card = [(card m 0), (card m 1), (card m 2), (card m 3), . . .]

zeroOrder 1 Aleph = [Aleph(0), Aleph(1), Aleph(2), Aleph(3), . . .]

fromTo :: Int -> (Card -> Card) -> Int -> Int -> [Card]Source

Quaternary function from Int x Card x Int x Int to [Card] fromTo takes an Int ord, a Card value constructor cons, an Int m, and an Int n and returns the list of type cons Card(s) of order ord indexed from m to n. That is, fromTo returns [(cons ord m), . . . , (cons ord n)] fromTo ord cons m n = descent ord cons m n

alephs :: Int -> [Card]Source

alefs :: Integer -> [Card]Source

wInacs :: Int -> [Card]Source

wInacz :: Integer -> [Card]Source

sInacs :: Int -> [Card]Source

sInacz :: Integer -> [Card]Source

aInacs :: Int -> [Card]Source

aInacz :: Integer -> [Card]Source

hInacs :: Int -> [Card]Source

hInacz :: Integer -> [Card]Source

h2Inacs :: Int -> [Card]Source

h2Inacz :: Integer -> [Card]Source

wMahlos :: Int -> [Card]Source

wMahloz :: Integer -> [Card]Source

weaklyMahloz :: Integer -> [Card]Source

sMahlos :: Int -> [Card]Source

sMahloz :: Integer -> [Card]Source

stronglyMahloz :: Integer -> [Card]Source

aMahlos :: Int -> [Card]Source

aMahloz :: Integer -> [Card]Source

alphaMahloz :: Integer -> [Card]Source

hMahlos :: Int -> [Card]Source

hMahloz :: Integer -> [Card]Source

hyperMahloz :: Integer -> [Card]Source

reflexions :: Integer -> [Card]Source

piis :: Int -> Int -> Int -> [Card]Source

piIndescribables :: Int -> Int -> Int -> [Card]Source

piiz :: Int -> Int -> Integer -> [Card]Source

piIndescribablez :: Int -> Int -> Integer -> [Card]Source

tis :: Int -> [Card]Source

tiz :: Integer -> [Card]Source

nis :: Int -> [Card]Source

niz :: Integer -> [Card]Source

lambdaUnfoldz :: Integer -> [Card]Source

unfolds :: Int -> [Card]Source

unfoldz :: Integer -> [Card]Source

unfoldablez :: Integer -> [Card]Source

lambdaShrewdz :: Integer -> [Card]Source

shrewds :: Int -> [Card]Source

shrewdz :: Integer -> [Card]Source

ethers :: Int -> [Card]Source

ethereals :: Int -> [Card]Source

etherz :: Integer -> [Card]Source

etherealz :: Integer -> [Card]Source

subtles :: Int -> [Card]Source

subtlez :: Integer -> [Card]Source

almostIneffz :: Integer -> [Card]Source

ineffs :: Int -> [Card]Source

ineffz :: Integer -> [Card]Source

ineffablez :: Integer -> [Card]Source

nIneffs :: Int -> [Card]Source

nIneffz :: Integer -> [Card]Source

nIneffablez :: Integer -> [Card]Source

totalIneffz :: Integer -> [Card]Source

remarkablez :: Integer -> [Card]Source

aErdoss :: Int -> [Card]Source

aErdosz :: Integer -> [Card]Source

alphaErdosz :: Integer -> [Card]Source

gErdoss :: Int -> [Card]Source

gErdosz :: Integer -> [Card]Source

gammaErdosz :: Integer -> [Card]Source

aRamseys :: Int -> [Card]Source

aRamseyz :: Integer -> [Card]Source

almostRamseyz :: Integer -> [Card]Source

jonssons :: Int -> [Card]Source

jonssonz :: Integer -> [Card]Source

rowbottomz :: Integer -> [Card]Source

ramseys :: Int -> [Card]Source

ramseyz :: Integer -> [Card]Source

iRamseys :: Int -> [Card]Source

iRamseyz :: Integer -> [Card]Source

measures :: Int -> [Card]Source

measurez :: Integer -> [Card]Source

measurablez :: Integer -> [Card]Source

zeroDags :: Int -> [Card]Source

zeroDagz :: Integer -> [Card]Source

zeroDaggerz :: Integer -> [Card]Source

lambdaStrongz :: Integer -> [Card]Source

strongs :: Int -> [Card]Source

strongz :: Integer -> [Card]Source

woodins :: Int -> [Card]Source

woodinz :: Integer -> [Card]Source

whWoodins :: Int -> [Card]Source

whWoodinz :: Integer -> [Card]Source

shelahs :: Int -> [Card]Source

shelahz :: Integer -> [Card]Source

hWoodins :: Int -> [Card]Source

hWoodinz :: Integer -> [Card]Source

hyperWoodinz :: Integer -> [Card]Source

sss :: Int -> [Card]Source

ssz :: Integer -> [Card]Source

superstrongz :: Integer -> [Card]Source

scs :: Int -> [Card]Source

scz :: Integer -> [Card]Source

subcompactz :: Integer -> [Card]Source

supercompactz :: Integer -> [Card]Source

etas :: Int -> [Card]Source

etaz :: Integer -> [Card]Source

etaExtendiblez :: Integer -> [Card]Source

extends :: Int -> [Card]Source

extendz :: Integer -> [Card]Source

extendiblez :: Integer -> [Card]Source

vopenkas :: Int -> [Card]Source

vopenkaz :: Integer -> [Card]Source

nsss :: Int -> [Card]Source

nssz :: Integer -> [Card]Source

nSuperstrongz :: Integer -> [Card]Source

nahs :: Int -> [Card]Source

nahz :: Integer -> [Card]Source

nAlmostHugez :: Integer -> [Card]Source

nsahs :: Int -> [Card]Source

nsahz :: Integer -> [Card]Source

nHuges :: Int -> [Card]Source

nHugez :: Integer -> [Card]Source

nshs :: Int -> [Card]Source

nshz :: Integer -> [Card]Source

nSuperHugez :: Integer -> [Card]Source

ranks :: Int -> [Card]Source

rankz :: Integer -> [Card]Source

rankIntoRankz :: Integer -> [Card]Source

reinhardtz :: Integer -> [Card]Source