Sunday, February 27, 2011

Binary Decision Trees

I posted before about decision tree induction in GEP. Unfortunately there is not much data to compare GEP's ability to do DTs as the original author made some changes to GEP to do her experiments that I don't want to do to RGEP. Instead I'm trying to replicate results from a GA called GATree, which is pretty much a Genetic Programming technique, where the authors create Binary Decision Trees.
Binary Decision Trees (BDTs) are like normal decision trees in that each internal node is a decision and each leaf is one of the possible classes for the decision variable. The difference is that the internal nodes always have two children (hence the name). Rather than choosing the sub-child corresponding to the value of the attribute associated with the node, the node is associated with a single possible value for a single attribute. These values can be names or ranges. The left sub-child is taken if the current piece of data being decided on has the given value for the given attribute and the right sub-child is taken if not.
It is very easy to model this situation in Haskell. Here is the algebraic data type for the trees:
data BDT a = Leaf a | Node a (BDT a) (BDT a) deriving (Show, Eq, Functor, Foldable, Traversable)

and the evaluator:

evaltree _ (Leaf a) = a
evaltree attrs (Node a l r) = evaltree attrs $ if a `elem` attrs then l else r

Where attrs is a list of values of type a. The result is a value of type a that the tree has giving as the class of the list of as. Notice that all nodes and leafs hold the name type- since we are doing only nominal attributes even ranges of integers can be described by a string, which is what I'm actually using.
You have to use the following pragma to get all those beautiful derives:
{-# LANGUAGE DeriveTraversable, DeriveFoldable, DeriveFunctor #-}

The last important bit here is the ability to get the number of training cases correctly classified:

evalcases tree = sum . map (\(cas, expected) -> fromEnum $ evaltree cas tree == expected)

In case this is confusing, notice that it is in point free style- it evaluates to a function that expects a list of training cases which are pairs of attribute lists and their correct class. The fromEnum just turns a boolean value into an Int.

I'm also going to look into using functions as binary classifiers to test the results in the GEP book a little and see if I can include them in my thesis.

Wednesday, February 23, 2011

Awesome Images

Robust Gene Expression Programming is an evolutionary algorithm using bit vectors to encode expression trees. I was playing around with the idea of a linear population where individuals can only cross with those next to them, which has been done in Genetic Algorithms with interesting results, when I realized something really neat- a bit vector population in a linear order viewed as a picture would be a box of black and white pixels where useful schemata would float around the population from where they originated, and it might be possible to view this if the population where made into a picture.

Since I don't really want to look into variations of RGEP at the moment, I just recorded the normal unordered population every 50 generations and made a picture out of it. Here is a population at generation 500 trying to learn f(x) = 3*(x+1)^3 + 2*(x+1)^2 + x + 1:

I reversed the image so the front is the part of the individual that is interesting, since we are technically using postfix notation and the back is what is most likely to effect the fitness. I was concerned about the lack of convergence here- I expected much more uniformity. To see what the effect of Tournament Selection was against Roulette Wheel, I did a run using Roulette Wheel, and after only 50 generation we have:

So the population converged almost immediately. This is really interesting- the selection mechanisms have a much bigger effect on the diversity than I realized. I really like Tournament Selection and it performs very nicely, but it really seems like they take different strategies, exploration vs exploitation. Strange how the front part converged and the rest didn't though.

Hurray for data visualization! Now to figure out what it means for RGEP.

Monday, February 21, 2011

Term : Type : Kind : Sort

I've been reading a really interesting paper called "Introduction to Generalized Type Systems" in which the system of the lambda cube are discussed. The lambda cube consists of 8 systems, one on each point of the cube, where the simplest system is our good friend the simply typed lambda calculus and the most complex system is the calculus of construction (which has an awesome name). They consider only fairly simple situations in this paper by not including some of the operators and rules that can be defined, but the resulting theory is still very rich and complex.

There are several really neat things about this material. One is that they define a hierarchy of types that goes like this- term:type:kind:sort, where ":" is pronounced "in". A term is the basic object of the lambda calculus and involves constants, variables, lambda abstraction and application. If we group terms into what are basically sets, we get the types, and we can extend the system with different type operators to model things in programming and logic. Not only can there be abstract on the term level, but we can abstract on the type level as well, giving a type constructor (like an array type in most languages). While all normal (monomorphic) types are in the same kind, *, the type constructors have kinds built from * and ->. This means that we can have *->*, which may create lists of some type for example, or even (*->*)->* which looks suspiciously like a fix point operators (indeed there are some really cool applications of the fixed point of a type in Haskell). So these kinds can not be described simply by the symbol *, so how do we classify them? We don't want to lead ourselves into a paradox by defining *:* (kind is of kind kind) so we have another layer on top of kinds. In this paper they use a square box that I can't produce with ascii characters. This last layer is called the "sort" of a kind.

It is interesting that the systems become more and more restricted as we go up in the hierarchy- terms are basically unrestricted except when we only take those terms which can be given types, which have several operators on them are can be very complex with things like universal and existential quantification, products and co-products if we want them. If we take the simply typed lambda calculus then all types have kind *, but if we consider a more complex calculus like System F then the kinds form a simply typed lambda calculus, and it is on the sort level that there is only one symbol, the box.

Another neat thing about the material is that the lambda cube corresponds to a logic cube- a series of systems of logic with the same inclusion relation and the corresponding features as those of the lambda cube. I haven't gotten that far yet, but I always found the relation to logic very interesting.

The last thing I want to say is that the proof technique they use is very interesting. The first time I tried to read this paper I had no idea what was going on- they defined 8 systems all at once and proceed to prove things in all 8 simultaneously. I've been reading about called "Categories for Types" in which they describe a way of defining algebraic systems that is similar to what is used in this paper, which has helped a lot.

Saturday, February 19, 2011

Decision Tree Induction

To show that GEP can be used to solve many types of problems its inventor, Candida Ferreira, presents many different tasks from symbolic regression, design of neural networks, block stacking, traveling salesman, and many others. Some of them require significant modification of the original algorithm but other problems can be solved by carefully chosen operators and terminals.

One problem that is fairly simple to set up with GEP is the creation of decision trees. These are what they sound like- tree structures that can make decisions. They consist of nodes each of which corresponds to an attribute, and for some given value of that attribute the node will return the value of the correct subtree corresponding to that value. This means that we can fill in the attribute values and ask the tree to give us an answer, and one of its leaves will ultimately be selected as the result.

To do this in GEP, or in my case RGEP, we just make the attributes into operators with n children where n is the number of values the attribute can have, and we have one terminal for each value of the decision variable. I'm only doing a simple example case, and Ferreira adds some additional complexity when creating decision trees with continuous valued attributes.

Since I'm only doing a proof of concept for my thesis, I am only going to try a simple example about whether or not to play tennis based on the weather. I have already written some very very basic code to create decision trees- I considered more complex schemes, but since this is a very minor part of my thesis I ended up adding the ability to create operators and terminals as well as a fitness evaluator for decision trees in 5 lines of code. Pretty simple!

Designing Multiplexers!

One problem used to test methods in AI is the multiplexer problem. It has been used as an example to test the ability of different methods such as decision trees, genetic programming, neural networks, and gene expression programming to correctly classify inputs. The idea is that for some k > 0 we want to design a multiplexer with k address lines and 2^k data lines, and we want the multiplexer's output to be the data line selected by the address lines. The way this has been done with GP and GEP is to have these methods evolve a boolean expression with all k+2^k variables, one for each input, whose result should match the correct data line input.

The fitness in this case can just be how many test cases the function/multiplexer works correctly for. In John Koza's work he used how many it misclassified instead, and then produced a scaling function to normalize the fitness' and make sure they could be used in roulette wheel selection. I'm going the simpler route and just finding how many cases (and you do try every possible case for every individual every generation) each solution gets correct. I am free to minimize or maximize with RGEP, and scaling would have absolutely no effect since the scaling function will be either isotone or antitone- either way tournament selection will only compare ordering not size.

I'm going to try this problem as a test for RGEP to show that it can evolve more then just functions, which is what most of my tests are doing. I plan on trying different size multiplexers, probably 3, 7, and 11 sized because that is what Koza tried in one of his works on GP. I want to also try doing decision tree evolution in RGEP for some variety, and it would be pretty simple to evolve a decision tree for this problem. I think it might even be easier then the boolean function approach as a completely correct tree could be very short.

I will try to post about decision trees when I get that far.

Tuesday, February 15, 2011

Agda

For my Artificial Intelligence 2 class I have to do a tool review of some piece of software related to AI. While my thesis is in the field of Evolutionary Algorithms, my main interest is really in functional programming and the related theory (the lambda calculi, type theories, intuitionistic logic, and category theory) so I'm planning on doing a review of a theorem prover or assistant like agda. The relation to AI here is that such tools come out of the symbolic AI community historically.

While reading an introduction to Agda, I came across a sentence about the features of the language that made me literally laugh out loud. In addition to an amazing type system they mention that "Agda’s logical framework also provides record types and a countable sequence of larger universes Set = Set0 , Set1 , Set2 , . . ..".
Both record types and an infinite number of universes? What a language!

Sunday, February 13, 2011

Functional Programming in Evolutionary Algorithms

FP and EAs are two of my main interests in computer science, so naturally I want to see how they can be combined. Genetic programming has a special connection to functional programming in that early genetic programs were lisp expressions. This of course makes sense- the abstract syntax tree is the subject of evolution in this case and lisp is a natural language for this as you program the syntax tree directly.
There are other connections however- many of the important additions to GP have come from functional programming. There have been variations taking imperative constructs as well, but that is not the subject of this post. Some examples are polymorphism, recursion, and the addition of a type system. Some GPs even evolve lambda expressions.
Logic programming has also been applied to GP to evolve statement from a "logic grammar".
Along with the type systems that have been used in GP literature, there has been work allowing a GP to evolve higher order functions.
The use of functions like fold and map is called implicit recursion in GP and gives a nice way to allow recursive structures without the need to evolve higher order functions directly, or add recursive semantics and check for termination, etc.

I would like some day to look into other functional programming techniques in the context of EAs. For example, laziness opens up some possible optimizations. Tournament selection does not necessarily check every individual's fitness (they can be skipped if they are not chosen for any tournaments). In this case we must either add a lazy evaluation strategy, or use a lazy language or one that includes some way of specifying laziness. This has been investigated before, but the language used was Java.
One thing that I thing would be really neat would be using categorical concepts (category theory is another favorite topic of mine, especially where it interacts with functional programming). For example- could we make a monadic GP? A comonadic GP? So far I haven't been able to come up with a reasonable problem to test this out on, but it seems interesting.

Stack Effects

In concatenative languages like Forth every function (called a word) operates on an implicit stack. This means that instead of specifying the type signature, Int -> Int -> Int for a function like +, we specify the stack effect, which in forth would be a comment of the form ( n m -- n+m ). Stack effects are necessary as a word can have more then one result, for example the word dup has the stack comment ( n -- n n ) duplicating the top of the stack.
In RGEP the postfix notation allows us to use words from Forth as operators, where in previous GEPs operators had to be simple functions. This means that they need to be aware of their stack effect and not just their arity (the number of arguments they take). Since RGEP operators must preserve the closure property, the stack effect is essentially just the number of items required on the stack to execute the word and the number of items left after execution. To hold this data as well as the function for the operator I am using this type:
data OP a = OP { eats::Int, leaves::Int, applyOp::[a] -> [a], name::String }
So an OP, an operator, eats an integer number of argument from the stack and leaves an integer number of arguments as well. The operator itself is the function [a] -> [a] acting on the stack. I don't know how to embed the stack effect in the type system, but I would not be surprised if it was doable (I think I've read about ways of doing this) but unfortunately that would not be enough- I really do need to know how arguments the operators take and leave for other reasons in my evolutionary algorithm library.
The name is what you might expect- its the name of the operator. I think it is reasonable that all operators be named, and it makes printing them must nicer if they know who they are.

The nicest thing about arbitrary stack effects is that I can include functions like dup, drop, over, tuck, nip, rot, and drop in any problem, as they are polymorphic in their type. I hope that this will prove an easy way of promoting the reuse of substructures in RGEP. Other methods of promoting substructure reuse are Ferriera's version of ADFs (automatically defined functions) and Xin Li's work on subexpression libraries. I really like Xin Li's work and I think that the subexpression library approach is probably a good thing, but in the spirit of RGEP I want to propose a much simpler way to reuse subexpressions. Using the postfix operators, especially dup, over, and tuck reorganizes the expression tree such that certain subexpressions will appear many times. This has the disadvantage that the subexpressions may have only one actual copy in the individual, and so are easy to disrupt, but on the other hand it is trivial to add this method to RGEP (In Heal, my library, you just have to add them to the operator list) and if they promote subexpressions at all then it is worth trying them out. This is much simpler than keeping track of common subexpressions and saving them in a library, adding additional terminals for each expression, and expanding and contracting those terminals.

Saturday, February 12, 2011

Tournament and Roulette Wheel Selection

There are many selection mechanisms available in GA literature, but the two most common seem to be roulette wheel and tournament selection. Roulette wheel involves (conceptually) creating a pie chart where the fitness value of each individual gives the size of the slice of the pie that that individual is assigned to. To create a new population, we can imagine a little arrow spinning around the middle of the chart, and the part of the chart it lands on is the individual that should be selected. Performing this computation n times for a population of n individuals yields a new population. In Heal, my Haskell Evolutionary Algorithm Library, roulette selection is implemented like this:
roulette :: (Linear p) => p (a, Double) -> EAMonad (p a) e
roulette pop = do
let sumfit = F.sum $ fmap snd pop
ds <- Tr.forM pop $ const (nextDouble sumfit)
return $ fmap (select pop) ds
select v !d | empty v = error $ "No selection, fitness remaining: " ++ show d
| remaining <= 0.00001 = i
| otherwise = select (rest v) remaining where
(i, f) = first v
remaining = d - f
where L is the qualified name of Data.Foldable, Tr is the qualified name of Data.Traversable, and Linear is a type class of finite linear structures (so the user can user whatever structure they like- I'm using the Seq sequence structure from Data.Sequence). EAMonad is basically the Random monad with some extra statefulness. Its second type argument e is the environment of the evolutionary algorithm, but in understanding the code one can safely ignore this.

Tournament selection on the other hand consists of small tournaments. To selection a single individual for the new population, we must selection k (normally k = 2. In fact, some definitions of tournaments selection describe it as having tournaments that are always size 2) and we have them compete against each other. The competition consists of choosing the more fitness individual (if k is greater than 2, chose the most fit) some percentage p (normally p = 75%) of the time, and the less fit otherwise. For k>2 this is slightly more complex, but basically the less fit the smaller chance of selection, and for the most part k=2, p=75%. Interestingly the fitness for tournament selection does not necessarily have to be a real number greater than 0 as with some other selection mechanisms, it just has to be of a type with a total order. In Heal, tournament selection is implemented like this:
tournament :: (Linear p, Ord b) => p (a, b) -> EAMonad (p a) e
tournament pop = do
pop' <- Tr.forM pop $ const $ selectPlayers pop >>= compete
return pop'
selectPlayers p = do
i <- nextInt $ count p
i' <- nextInt $ count p
return $ (index p i, index p i')
compete (a, a') = do
b <- test 0.75
return $ fst $ maxBy snd a a'
maxBy f a a' = if f a > f a' then a else a'
Notice the weaker condition on the second part of the pair, (the first part is the individual, the second the fitness) it is simply an Ord instance. Count gives the size of the linear structure (meaning that the structures should be finite) and index allows you to index into the structure. While roulette wheel is used in the original GEP, tournament selection is more common in GP literature, and apparently in GA literature as well. I personally prefer tournament selection and I've chosen it for RGEP.

Tuesday, February 8, 2011

Haskell Evolutionary Algorithm Library on Git

I've uploaded the Haskell Evolutionary Library to GitHub- https://github.com/noahryan/heal. Its come a long way from its humble beginnings- I starting writing it ss my first little Haskell program in order to understand how to use the state monad. It is not a framework, and it doesn't provide a lot of structure- I need it to be fairly loose and easy to modify in order to do my research.
One nice thing about it is that it is less than 400 lines of code (more counting imports, blanks, comments,. etc) and supports Genetic Algorithms, Prefix Gene Expression Programming, and of course it is the first ever implementation of Robust Gene Expression programming, complete with a postfix evaluator for (as far as I know) the first time in any GEP. Although there are things I want to change, I am pretty happy with it and I find it pleasant to work with.
While it is hardly required that a user actually use the main loop provided, there is a small function called ea and another called ga in the EA module. These are the main entry point and are intended to capture the notion of an evolutionary algorithm and a genetic algorithm respectively. The RGEP and PGEP modules export functions call rgep and pgep to help set up problems with those techniques.
The EAMonad module exports the monad in which all evolutionary computation takes place- it allows randomness (as these are stochastic meta-heuristics so randomness is an inherent quality) a generation count, the ability to write to a log at any time, and the ability to keep any additional state that you want. This is a bit of a kludge- there is a type parameter for EAMonad that is intended to be the "rest of the environment" not included in the generation count or population if such an environment is included. I really don't know how else to allow a user to set up a problem that keeps track of many different types of state that I don't know about as the designer. The PGEP symbolic regression sample uses this to keep track of a number used to scale the population.
I am making use of a beautiful data structure called a 2-3 finger tree- the paper on this data structure is very fun and a good read. Also, there is some heavy use of the Traversable class as found in the functional pearl "Clowns and Jokers - Clowns to the Left of me, Jokers to the Right" by Conor Mcbride (a paper I highly recommend).
There are no real tricks or advanced Haskell techniques in this library unless monad transformers are considered advanced. This type of computation is specified by the techniques involved and there is a sense in which there is not room for a huge amount of cleverness. Maybe it would be an interesting research topic to look into functional EAs that investigates the opportunities to modify and implement EAs using techniques known to the functional programming community.

Well, back to work on my thesis!

Monday, February 7, 2011

Java's Type System

Type systems are something that I find extremely interesting- some functional programming languages have the most beautiful type systems and their connection to logic and category theory is one of my favorite things in Computer Science. But what about imperative languages? At my university we are taught Java and object oriented programming in the imperative tradition, so I've been thinking about how to describe Java's type system. I am not an expert, and all of this has been studied before- there are extensions to the lambda calculus with order relationships and much more advanced methods of describing class based object oriented systems. These are just my idle thoughts.
First of all, there is a countably infinite set of possible types. Types can be related by a relation called sub-classing which gives us a partial order. We could describe this as saying that a class A is a sub-class of a class B iff either that fact is given by the subclass relation or there is a chain of classes c0 <= c1 <= ... <= cn such that A <= c0 and cn <= B. The ability to cast an object to another type indicates that the first type is a subclass of the second.
We also have predicates on types in the form of interfaces. For any type we can ask "does it implement some interface?". Notice that if any super class of a class implements an interface than that subclass is said to implement the interface.
For any two class, indeed any set of classes, there is a join defined as the "smallest" class that is a superclass of all classes in the set. Since there is a top element, Object, there is a join for all collections of classes. It is useful to use the ability to cast to describe the order relation rather then sub-classing, because want that x <= x, and it sounds a bit odd to say that a class is a sub-class of itself (though I don't really see anything wrong with saying that). It is certainly true however that a class A can be cast to itself, so the reflective property is obvious there. There is the problem that an object can be cast up and then cast down, but lets ignore objects and just think about types (classes).
There is no bottom class, but it is possible for a chain of classes to have an end for which no class is smaller than that bottom element of the chain- in the case that the smallest class is declared "final".
The only meets that exist are within a chain- so only the trivial meets. Many sets of types have no meet, and this captures the fact that there is only single class sub-classing- there is no multiple inheritance.
We have a universal quantifier on types in the form of generics and we can bound that type variable with the order relation ( forall A <= some class B) or by asking to to satisfy some predicate (A implements some interface B). Generic classes can be considered an indexed family of classes, with one class in the family for all Java types. Since we can have many generic parameters to a class which can be distinguished by their order we can have an indexed family(indexed by the natural numbers) of type parameters.
I'm not entirely sure what the effects of wildcards are- my understanding is that they are a little like existential types.
It seems like abstract classes have no special structure here except maybe that an abstract class with no subclasses can be see as an empty type and therefore false. The problem here is that can always make a subclass- the only way to force a class to have no subtypes is to make it final, which is not allowed for abstract class for exactly this reason.

So, that was fun! I've seen some literature about this but I've never actually looked into it yet- I'm currently more interested in languages that are more aware of their type systems like Haskell.

Sunday, February 6, 2011

RGEP Design Criteria

Robust Gene Expression Programming has the following as it primary design criteria:
1. It should be as simple as possible without losing generality. This includes simplicity in implementation.
2. It should make as few assumption as possible about the problems it is used to solve.
3. It should perform at least as well as its most immediate predecessor, Prefix Gene Expression Programming.

Instructions vs Expression Trees

There are many evolutionary algorithms that evolve programs- GP, LGP, GPM, GEP, and many variations of each. some of these are evolving general tree structures, while others are intended for evolving instructions or a compilable program. In particular it seems like LGP is often used to evolve instructions for some abstract machine, and the instructions take the form of an assembly-like language. DGP and GPM deal with the concept of compiling the result of editing an individuals genetic material, and is clearly intended to deal with the complexity of a programming language.
In contrast, techniques like GEP and sometimes GP evolve a tree structure, which often happens to encode the abstract syntax tree of an expression in some language (indeed GE can evolve an expression tree in any context free grammar supplied by the user). In RGEP I plan on making this distinction clear- RGEP individuals encode an expression tree whose result after evaluation is an object whose fitness can be determined. This object can be a compiled program, or a tree (build from evaluating the postfix expression), or a function f(x) = y for some y, or anything else. This distinction is important for several reasons: it allows RGEP to be used in a large class of possible problems (those whose answers are expressible as the result of evaluating a tree structure), it is in the spirit of "robustness" in that it does not assume very much about the problem to be solved, it allows us to use general stack operators (which appear to improve fitness and promote the reuse of subexpressions, and allows me to specify the evaluation operation for all possible RGEP implementation, saying that the result of the evaluation is generic but the way it is arrived at is always the same.
This is also part of the link between PGEP, RGEP, and functional programming. It is a loose connection, but I think there is some sense in which PGEP and RGEP are more in the traditional of function or even declarative programming in general in that they describe the computation that they want to perform, rather then give explicit instructions (as in the case of LGP especially) on how to perform that computation. The actual operators and terminals supplied to RGEP determine what computation is described.
GPM has more then one derivative method- there is DGPs and GE. It is interesting that GPM, DGP and GE are all fairly complex and often deal with imperative style programs, while GEP is intended to simplify GPM and it is more declarative. PGEP and now RGEP are both intended to simplify GEP as well, so it seems like this whole area of research is focused on simplicity as well as effectiveness, which gives RGEP a nice place in GEP literature- an explicit attempt at simplicity with nearly no other design criteria.

Saturday, February 5, 2011

Robustness and Redundancy

RGEP (Robust Gene Expression Programming) is intended to be robust in the sense that it does not make many assumptions about the problem that it solves. This means that instead of evolving a program it evolves an expression whose result (possibly another expression) can be evaluated for fitness. Instead of forcing the user to create a maximizing fitness function, fitness can be maximized or minimized. The encoding is simple bit vectors, and any operator can make any change to an individual- there are no constraints to evolution.
I've recently discovered another applicable meaning to the name robust- the fact that many bit vectors encode the same expression tree. Since RGEP has this feature, and no other GEP seems to have it (it was part of GPM that was removed for GEP by the head-tail method and later a restriction on genetic operators), it makes robust the perfect description of my technique.
My reason for adding this redundancy in encoding was to make implementation of RGEP easier, but it seems to have a significant positive effect on performance. I started noticing that RGEP's initial populations were better than PGEP's in my experiments so I performed some extra tests to isolate the first population. I found that indeed RGEP performed better than PGEP on randomly generated populations. This can only be accounted for by the redundant encoding- the bit vector representation has no way of expressing itself yet, and the genetic operators are not given the chance to act.
This increase in performance is not small either- for one test function RGEP is 57% better, and for the other it is 91.5% better!
I am trying to find some other mechanism to account for this, but as far as I can tell the redundant, unrestricted encoding is a huge gain in the fitness of random individuals.

Tuesday, February 1, 2011

The Name RGEP

I chose the name "Robust Gene Expression Programming" for my thesis because my professor once called a neural network technique that made few assumptions about its problem space "robust". I liked the idea, and I incorporated it into my thesis, giving a better name to my variation of GEP then the original BPGEP (as it was originally a union of Binary and Prefix Gene Expression Programming).


While going through some Developmental Genetic Programming papers (DGP is related to GPM, which is a close relative to GEP and therefore relevant to my thesis) I found a reference to a paper about natural genetics in which the author refers to the RNA "secondary structures" as being robust because there are many mappings of genetic code to each RNA structure. It turns out that, as far as I know, RGEP is the first GEP method to map the genotype of symbol lists redundantly into the phenotype of expression trees. This means that among GEP techniques one of the main distinguishing factors is that it is robust in exactly this sense! I didn't at all intend for the name to make sense on this level, but now I think it is the perfect description of what I'm doing.
How odd.