species-0.2: Computational combinatorial speciesSource codeContentsIndex
Math.Combinatorics.Species.Types
Contents
Miscellaneous
Lazy multiplication
Series types
Higher-order Show
Structure functors
Type-level species
Description
Some common types used by the species library, along with some utility functions.
Synopsis
type CycleType = [(Integer, Integer)]
newtype LazyRing a = LR {
unLR :: a
}
type LazyQ = LazyRing Rational
type LazyZ = LazyRing Integer
newtype EGF = EGF (T LazyQ)
egfFromCoeffs :: [LazyQ] -> EGF
liftEGF :: (T LazyQ -> T LazyQ) -> EGF -> EGF
liftEGF2 :: (T LazyQ -> T LazyQ -> T LazyQ) -> EGF -> EGF -> EGF
newtype GF = GF (T Integer)
gfFromCoeffs :: [Integer] -> GF
liftGF :: (T Integer -> T Integer) -> GF -> GF
liftGF2 :: (T Integer -> T Integer -> T Integer) -> GF -> GF -> GF
newtype CycleIndex = CI (T Rational)
ciFromMonomials :: [T Rational] -> CycleIndex
liftCI :: (T Rational -> T Rational) -> CycleIndex -> CycleIndex
liftCI2 :: (T Rational -> T Rational -> T Rational) -> CycleIndex -> CycleIndex -> CycleIndex
filterCoeffs :: C a => (Integer -> Bool) -> [a] -> [a]
selectIndex :: (C a, Eq a) => Integer -> [a] -> [a]
class Functor f => ShowF f where
showF :: Show a => f a -> String
newtype RawString = RawString String
newtype Const x a = Const x
newtype Identity a = Identity a
newtype Sum f g a = Sum {
unSum :: Either (f a) (g a)
}
newtype Prod f g a = Prod {
unProd :: (f a, g a)
}
data Comp f g a = Comp {
unComp :: f (g a)
}
newtype Cycle a = Cycle {
getCycle :: [a]
}
newtype Set a = Set {
getSet :: [a]
}
data Star a
= Star
| Original a
data Z
data S n
data X
data E
data C
data Sub
data Elt
data f :+: g
data f :*: g
data f :.: g
data f :><: g
data f :@: g
data Der f
type family StructureF t :: * -> *
Miscellaneous
type CycleType = [(Integer, Integer)]Source
A representation of the cycle type of a permutation. If c :: CycleType and (k,n) elem c, then the permutation has n cycles of size k.
Lazy multiplication
newtype LazyRing a Source
If T is an instance of Ring, then LazyRing T is isomorphic to T but with a lazy multiplication: 0 * undefined = undefined * 0 = 0.
Constructors
LR
unLR :: a
show/hide Instances
Eq a => Eq (LazyRing a)
Ord a => Ord (LazyRing a)
Show a => Show (LazyRing a)
HasLub (LazyRing a)
(Eq a, C a) => C (LazyRing a)
C a => C (LazyRing a)
(Eq a, C a) => C (LazyRing a)
C a => C (LazyRing a)
type LazyQ = LazyRing RationalSource
type LazyZ = LazyRing IntegerSource
Series types
newtype EGF Source
Exponential generating functions, for counting labelled species.
Constructors
EGF (T LazyQ)
show/hide Instances
egfFromCoeffs :: [LazyQ] -> EGFSource
liftEGF :: (T LazyQ -> T LazyQ) -> EGF -> EGFSource
liftEGF2 :: (T LazyQ -> T LazyQ -> T LazyQ) -> EGF -> EGF -> EGFSource
newtype GF Source
Ordinary generating functions, for counting unlabelled species.
Constructors
GF (T Integer)
show/hide Instances
gfFromCoeffs :: [Integer] -> GFSource
liftGF :: (T Integer -> T Integer) -> GF -> GFSource
liftGF2 :: (T Integer -> T Integer -> T Integer) -> GF -> GF -> GFSource
newtype CycleIndex Source
Cycle index series.
Constructors
CI (T Rational)
show/hide Instances
ciFromMonomials :: [T Rational] -> CycleIndexSource
liftCI :: (T Rational -> T Rational) -> CycleIndex -> CycleIndexSource
liftCI2 :: (T Rational -> T Rational -> T Rational) -> CycleIndex -> CycleIndex -> CycleIndexSource
filterCoeffs :: C a => (Integer -> Bool) -> [a] -> [a]Source
Filter the coefficients of a series according to a predicate.
selectIndex :: (C a, Eq a) => Integer -> [a] -> [a]Source
Set every coefficient of a series to 0 except the selected index. Truncate any trailing zeroes.
Higher-order Show
class Functor f => ShowF f whereSource
When generating species, we build up a functor representing structures of that species; in order to display generated structures, we need to know that applying the computed functor to a Showable type will also yield something Showable.
Methods
showF :: Show a => f a -> StringSource
show/hide Instances
newtype RawString Source
RawString is like String, but with a Show instance that doesn't add quotes or do any escaping. This is a (somewhat silly) hack needed to implement a ShowF instance for Comp.
Constructors
RawString String
show/hide Instances
Structure functors
Functors used in building up structures for species generation. Many of these functors are already defined elsewhere, in other packages; but to avoid a plethora of imports, inconsistent naming/instance schemes, etc., we just redefine them here.
newtype Const x a Source
The constant functor.
Constructors
Const x
show/hide Instances
newtype Identity a Source
The identity functor.
Constructors
Identity a
show/hide Instances
newtype Sum f g a Source
Functor coproduct.
Constructors
Sum
unSum :: Either (f a) (g a)
show/hide Instances
(Functor f, Functor g) => Functor (Sum f g)
(Typeable1 f, Typeable1 g) => Typeable1 (Sum f g)
(ShowF f, ShowF g) => ShowF (Sum f g)
(Show (f a), Show (g a)) => Show (Sum f g a)
newtype Prod f g a Source
Functor product.
Constructors
Prod
unProd :: (f a, g a)
show/hide Instances
(Functor f, Functor g) => Functor (Prod f g)
(Typeable1 f, Typeable1 g) => Typeable1 (Prod f g)
(ShowF f, ShowF g) => ShowF (Prod f g)
(Show (f a), Show (g a)) => Show (Prod f g a)
data Comp f g a Source
Functor composition.
Constructors
Comp
unComp :: f (g a)
show/hide Instances
(Functor f, Functor g) => Functor (Comp f g)
(Typeable1 f, Typeable1 g) => Typeable1 (Comp f g)
(ShowF f, ShowF g) => ShowF (Comp f g)
Show (f (g a)) => Show (Comp f g a)
newtype Cycle a Source
Cycle structure. A value of type 'Cycle a' is implemented as '[a]', but thought of as a directed cycle.
Constructors
Cycle
getCycle :: [a]
show/hide Instances
newtype Set a Source
Set structure. A value of type 'Set a' is implemented as '[a]', but thought of as an unordered set.
Constructors
Set
getSet :: [a]
show/hide Instances
data Star a Source
Star is isomorphic to Maybe, but with a more useful Show instance for our purposes. Used to implement species differentiation.
Constructors
Star
Original a
show/hide Instances
Type-level species
Some constructor-less data types used as indices to SpeciesTypedAST to reflect the species structure at the type level. This is the point at which we wish we were doing this in a dependently typed language.
data Z Source
data S n Source
data X Source
data E Source
data C Source
data Sub Source
data Elt Source
data f :+: g Source
data f :*: g Source
data f :.: g Source
data f :><: g Source
data f :@: g Source
data Der f Source
type family StructureF t :: * -> *Source
StructureF is a type function which maps type-level species descriptions to structure functors. That is, a structure of the species with type-level representation s, on the underlying set a, has type StructureF s a.
Produced by Haddock version 2.6.0