species-0.2: Computational combinatorial speciesSource codeContentsIndex
Math.Combinatorics.Species.Generate
Description
Generation of species: given a species and an underlying set of labels, generate a list of all structures built from the underlying set.
Synopsis
generateF :: SpeciesTypedAST s -> [a] -> [StructureF s a]
data Structure a where
Structure :: (ShowF f, Typeable1 f, Functor f) => f a -> Structure a
generate :: SpeciesAST -> [a] -> [Structure a]
generateTyped :: forall f a. (Typeable1 f, Typeable a) => SpeciesAST -> [a] -> [f a]
structureType :: SpeciesAST -> String
Documentation
generateF :: SpeciesTypedAST s -> [a] -> [StructureF s a]Source

Given an AST describing a species, with a phantom type parameter describing the species at the type level, and an underlying set, generate a list of all possible structures built over the underlying set; the type of the output list is a function of the species structure. (Of course, it would be really nice to have a real dependently-typed language for this!)

Unfortunately, SpeciesTypedAST cannot be made an instance of Species, so if we want to be able to generate structures given an expression of the Species DSL as input, we must take SpeciesAST as input, which existentially wraps the phantom structure type---but this means that the output list type must be existentially quantified as well; see generate and generateTyped below.

data Structure a whereSource
An existential wrapper for structures, ensuring that the structure functor results in something Showable and Typeable (when applied to a Showable and Typeable argument type).
Constructors
Structure :: (ShowF f, Typeable1 f, Functor f) => f a -> Structure a
show/hide Instances
generate :: SpeciesAST -> [a] -> [Structure a]Source

generate s ls generates a complete list of all s-structures over the underlying set of labels ls. For example:

 > generate octopi ([1,2,3] :: [Int])
 [<<*,1,2,3>>,<<*,1,3,2>>,<<*,2,1,3>>,<<*,2,3,1>>,<<*,3,1,2>>,<<*,3,2,1>>,
  <<*,1,2>,<*,3>>,<<*,2,1>,<*,3>>,<<*,1,3>,<*,2>>,<<*,3,1>,<*,2>>,<<*,1>,
  <*,2,3>>,<<*,1>,<*,3,2>>,<<*,1>,<*,2>,<*,3>>,<<*,1>,<*,3>,<*,2>>]

 > generate subsets "abc"
 [{'a','b','c'},{'a','b'},{'a','c'},{'a'},{'b','c'},{'b'},{'c'},{}]
 > generate simpleGraphs ([1,2,3] :: [Int])
 [{{1,2},{1,3},{2,3}},{{1,2},{1,3}},{{1,2},{2,3}},{{1,2}},{{1,3},{2,3}},
  {{1,3}},{{2,3}},{}]

There is one caveat: since the type of the generated structures is different for each species, it must be existentially quantified! The output of generate can always be Shown, but not much else.

However! All is not lost. It's possible, by the magic of Data.Typeable, to yank the type information (kicking and screaming) back into the open, so that you can then manipulate the generated structures to your heart's content. To see how, consult structureType and generateTyped.

generateTyped :: forall f a. (Typeable1 f, Typeable a) => SpeciesAST -> [a] -> [f a]Source

generateTyped s ls generates a complete list of all s-structures over the underlying set of labels ls, where the type of the generated structures is known (structureType may be used to compute this type). For example:

 > structureType subsets
 "Set"
 > generateTyped subsets ([1,2,3] :: [Int]) :: [Set Int]
 [{1,2,3},{1,2},{1,3},{1},{2,3},{2},{3},{}]
 > map (sum . getSet) $ it
 [6,3,4,1,5,2,3,0]

Although the output from generate appears the same, trying to compute the subset sums fails spectacularly if we use generate instead of generateTyped:

 > generate subsets ([1..3] :: [Int])
 [{1,2,3},{1,2},{1,3},{1},{2,3},{2},{3},{}]
 > map (sum . getSet) $ it
 <interactive>:1:21:
     Couldn't match expected type `Set a'
            against inferred type `Math.Combinatorics.Species.Generate.Structure
                                     Int'
       Expected type: [Set a]
       Inferred type: [Math.Combinatorics.Species.Generate.Structure Int]
     In the second argument of `($)', namely `it'
     In the expression: map (sum . getSet) $ it

If we use the wrong type, we get a nice error message:

 > generateTyped octopi ([1..3] :: [Int]) :: [Set Int]
 *** Exception: structure type mismatch.
   Expected: Set Int
   Inferred: Comp Cycle (Comp Cycle Star) Int
structureType :: SpeciesAST -> StringSource

structureType s returns a String representation of the functor type which represents the structure of the species s. In particular, if structureType s prints "T", then you can safely use generateTyped by writing

 generateTyped s ls :: [T L]

where ls :: [L].

Produced by Haddock version 2.6.0