Stability | experimental |
---|---|
Maintainer | byorgey@cis.upenn.edu |
Various data structures representing reified combinatorial species expressions. See also Math.Combinatorics.Species.AST.Instances.
- data SpeciesAST where
- Zero :: SpeciesAST
- One :: SpeciesAST
- N :: Integer -> SpeciesAST
- X :: SpeciesAST
- E :: SpeciesAST
- C :: SpeciesAST
- L :: SpeciesAST
- Subset :: SpeciesAST
- KSubset :: Integer -> SpeciesAST
- Elt :: SpeciesAST
- :+: :: SpeciesAST -> SpeciesAST -> SpeciesAST
- :*: :: SpeciesAST -> SpeciesAST -> SpeciesAST
- :.: :: SpeciesAST -> SpeciesAST -> SpeciesAST
- :><: :: SpeciesAST -> SpeciesAST -> SpeciesAST
- :@: :: SpeciesAST -> SpeciesAST -> SpeciesAST
- Der :: SpeciesAST -> SpeciesAST
- OfSize :: SpeciesAST -> (Integer -> Bool) -> SpeciesAST
- OfSizeExactly :: SpeciesAST -> Integer -> SpeciesAST
- NonEmpty :: SpeciesAST -> SpeciesAST
- Rec :: ASTFunctor f => f -> SpeciesAST
- Omega :: SpeciesAST
- data TSpeciesAST s where
- TZero :: TSpeciesAST Void
- TOne :: TSpeciesAST Unit
- TN :: Integer -> TSpeciesAST (Const Integer)
- TX :: TSpeciesAST Id
- TE :: TSpeciesAST Set
- TC :: TSpeciesAST Cycle
- TL :: TSpeciesAST []
- TSubset :: TSpeciesAST Set
- TKSubset :: Integer -> TSpeciesAST Set
- TElt :: TSpeciesAST Id
- :+:: :: SizedSpeciesAST f -> SizedSpeciesAST g -> TSpeciesAST (Sum f g)
- :*:: :: SizedSpeciesAST f -> SizedSpeciesAST g -> TSpeciesAST (Prod f g)
- :.:: :: SizedSpeciesAST f -> SizedSpeciesAST g -> TSpeciesAST (Comp f g)
- :><:: :: SizedSpeciesAST f -> SizedSpeciesAST g -> TSpeciesAST (Prod f g)
- :@:: :: SizedSpeciesAST f -> SizedSpeciesAST g -> TSpeciesAST (Comp f g)
- TDer :: SizedSpeciesAST f -> TSpeciesAST (Comp f Star)
- TOfSize :: SizedSpeciesAST f -> (Integer -> Bool) -> TSpeciesAST f
- TOfSizeExactly :: SizedSpeciesAST f -> Integer -> TSpeciesAST f
- TNonEmpty :: SizedSpeciesAST f -> TSpeciesAST f
- TRec :: ASTFunctor f => f -> TSpeciesAST (Mu f)
- TOmega :: TSpeciesAST Void
- data SizedSpeciesAST s where
- Sized :: Interval -> TSpeciesAST s -> SizedSpeciesAST s
- interval :: TSpeciesAST s -> Interval
- annI :: TSpeciesAST s -> SizedSpeciesAST s
- getI :: SizedSpeciesAST s -> Interval
- stripI :: SizedSpeciesAST s -> TSpeciesAST s
- data ESpeciesAST where
- Wrap :: Typeable1 s => SizedSpeciesAST s -> ESpeciesAST
- wrap :: Typeable1 s => TSpeciesAST s -> ESpeciesAST
- unwrap :: Typeable1 s => ESpeciesAST -> TSpeciesAST s
- erase :: ESpeciesAST -> SpeciesAST
- erase' :: TSpeciesAST f -> SpeciesAST
- unerase :: SpeciesAST -> ESpeciesAST
- class (Typeable f, Show f, Typeable1 (Interp f (Mu f))) => ASTFunctor f where
- apply :: Typeable1 g => f -> TSpeciesAST g -> TSpeciesAST (Interp f g)
- needsCI :: SpeciesAST -> Bool
- substRec :: ASTFunctor f => f -> SpeciesAST -> SpeciesAST -> SpeciesAST
Basic species expression AST
data SpeciesAST whereSource
A basic, untyped AST type for species expressions, for easily
doing things like analysis, simplification, deriving isomorphisms,
and so on. Converting between SpeciesAST
and the typed variant
ESpeciesAST
can be done with unerase
and erase
.
Zero :: SpeciesAST | |
One :: SpeciesAST | |
N :: Integer -> SpeciesAST | |
X :: SpeciesAST | |
E :: SpeciesAST | |
C :: SpeciesAST | |
L :: SpeciesAST | |
Subset :: SpeciesAST | |
KSubset :: Integer -> SpeciesAST | |
Elt :: SpeciesAST | |
:+: :: SpeciesAST -> SpeciesAST -> SpeciesAST | |
:*: :: SpeciesAST -> SpeciesAST -> SpeciesAST | |
:.: :: SpeciesAST -> SpeciesAST -> SpeciesAST | |
:><: :: SpeciesAST -> SpeciesAST -> SpeciesAST | |
:@: :: SpeciesAST -> SpeciesAST -> SpeciesAST | |
Der :: SpeciesAST -> SpeciesAST | |
OfSize :: SpeciesAST -> (Integer -> Bool) -> SpeciesAST | |
OfSizeExactly :: SpeciesAST -> Integer -> SpeciesAST | |
NonEmpty :: SpeciesAST -> SpeciesAST | |
Rec :: ASTFunctor f => f -> SpeciesAST | |
Omega :: SpeciesAST |
Eq SpeciesAST | Species expressions can be compared for structural equality.
(Note that if Note, however, that species containing an |
Ord SpeciesAST | An (arbitrary) |
Show SpeciesAST | Display species expressions in a nice human-readable form. Note that we commit the unforgivable sin of omitting a corresponding Read instance. This will hopefully be remedied in a future version. |
C SpeciesAST | Species expressions are differentiable. |
C SpeciesAST | Species expressions form a ring. Well, sort of. Of course the ring laws actually only hold up to isomorphism of species, not up to structural equality. |
C SpeciesAST | Species expressions are additive. |
Species SpeciesAST | Species expressions are an instance of the |
Typed, sized species expression AST
data TSpeciesAST s whereSource
A variant of SpeciesAST
with a phantom type parameter which
also reflects the structure, so we can write
quasi-dependently-typed functions over species, in particular for
species enumeration.
Of course, the non-uniform type parameter means that
TSpeciesAST
cannot be an instance of the Species
class; for
that purpose the existential wrapper ESpeciesAST
is provided.
TSpeciesAST
is defined via mutual recursion with
SizedSpeciesAST
, which pairs a TSpeciesAST
with an interval
annotation indicating (a conservative approximation of) the label
set sizes for which the species actually yields any structures;
this information makes enumeration faster and also prevents it
from getting stuck in infinite recursion in some cases. A value
of SizedSpeciesAST
is thus an annotated species expression tree
with interval annotations at every node.
TZero :: TSpeciesAST Void | |
TOne :: TSpeciesAST Unit | |
TN :: Integer -> TSpeciesAST (Const Integer) | |
TX :: TSpeciesAST Id | |
TE :: TSpeciesAST Set | |
TC :: TSpeciesAST Cycle | |
TL :: TSpeciesAST [] | |
TSubset :: TSpeciesAST Set | |
TKSubset :: Integer -> TSpeciesAST Set | |
TElt :: TSpeciesAST Id | |
:+:: :: SizedSpeciesAST f -> SizedSpeciesAST g -> TSpeciesAST (Sum f g) | |
:*:: :: SizedSpeciesAST f -> SizedSpeciesAST g -> TSpeciesAST (Prod f g) | |
:.:: :: SizedSpeciesAST f -> SizedSpeciesAST g -> TSpeciesAST (Comp f g) | |
:><:: :: SizedSpeciesAST f -> SizedSpeciesAST g -> TSpeciesAST (Prod f g) | |
:@:: :: SizedSpeciesAST f -> SizedSpeciesAST g -> TSpeciesAST (Comp f g) | |
TDer :: SizedSpeciesAST f -> TSpeciesAST (Comp f Star) | |
TOfSize :: SizedSpeciesAST f -> (Integer -> Bool) -> TSpeciesAST f | |
TOfSizeExactly :: SizedSpeciesAST f -> Integer -> TSpeciesAST f | |
TNonEmpty :: SizedSpeciesAST f -> TSpeciesAST f | |
TRec :: ASTFunctor f => f -> TSpeciesAST (Mu f) | |
TOmega :: TSpeciesAST Void |
Show (TSpeciesAST s) |
Size annotations
data SizedSpeciesAST s whereSource
Sized :: Interval -> TSpeciesAST s -> SizedSpeciesAST s |
interval :: TSpeciesAST s -> IntervalSource
Given a TSpeciesAST
, compute (a conservative approximation of)
the interval of label set sizes on which the species yields any
structures.
annI :: TSpeciesAST s -> SizedSpeciesAST sSource
Annotate a TSpeciesAST
with the interval of label set sizes for
which it yields structures.
getI :: SizedSpeciesAST s -> IntervalSource
Retrieve the interval annotation from a SizedSpeciesAST
.
stripI :: SizedSpeciesAST s -> TSpeciesAST sSource
Strip the interval annotation from a SizedSpeciesAST
.
Existentially wrapped AST
data ESpeciesAST whereSource
An existential wrapper to hide the phantom type parameter to
SizedSpeciesAST
, so we can make it an instance of Species
.
Wrap :: Typeable1 s => SizedSpeciesAST s -> ESpeciesAST |
wrap :: Typeable1 s => TSpeciesAST s -> ESpeciesASTSource
Construct an ESpeciesAST
from a TSpeciesAST
by adding an
appropriate interval annotation and hiding the type.
unwrap :: Typeable1 s => ESpeciesAST -> TSpeciesAST sSource
Unwrap an existential wrapper to get out a typed AST. You can get out any type you like as long as it is the right one.
CAUTION: Don't try this at home!
erase :: ESpeciesAST -> SpeciesASTSource
Erase the type and interval information from an existentially wrapped species AST.
erase' :: TSpeciesAST f -> SpeciesASTSource
Erase the type and interval information from a typed species AST.
unerase :: SpeciesAST -> ESpeciesASTSource
Reconstruct the type and interval annotations on a species AST.
ASTFunctor class (codes for higher-order functors)
class (Typeable f, Show f, Typeable1 (Interp f (Mu f))) => ASTFunctor f whereSource
ASTFunctor
is a type class for codes which can be interpreted
(via the Interp
type family) as higher-order functors over
species expressions. The apply
method allows such codes to be
applied to a species AST. The indirection is needed to implement
recursive species.
apply :: Typeable1 g => f -> TSpeciesAST g -> TSpeciesAST (Interp f g)Source
Miscellaneous AST operations
needsCI :: SpeciesAST -> BoolSource
needsCI
is a predicate which checks whether a species expression
uses any of the operations which are not supported directly by
ordinary generating functions (composition, differentiation,
cartesian product, and functor composition), and hence need cycle
index series.
substRec :: ASTFunctor f => f -> SpeciesAST -> SpeciesAST -> SpeciesASTSource
Substitute an expression for recursive occurrences.