Dear All, I am using Haskell (via ASDL) to write a translator (target language = java) and have designed an AST for Java. I want to be able to do fairly powerful source to source manipulations on this java tree and as such would value any constructive criticism of the way I have put together the data structrures. Sort of (..."Wouldn't it be easier to manipulate if you had represented X as "... sort of thing) Many thanks in advance Chris note for Haskellers x = FOO(x,x*,x?) | BAR => data X = FOO X [X] (Maybe X) | BAR x = (y) => type X = Y module Java { typeSpecifier = (typeName,dims?) typeName = PrimType(primitiveType) | QualType(qualifiedName) classNameList = (qualifiedName*) primitiveType = BOOLEAN | CHAR | BYTE | SHORT | INT | LONG | FLOAT | DOUBLE | VOID compilationUnit = (programFile) programFile = (packageStatement?,importStatements,typeDeclarations) packageStatement = PACKAGE(qualifiedName) typeDeclarations = (typeDeclaration*) importStatements = (importStatement*) importStatement = IMPORT (qualifiedName,star) boolean = JTrue | JFalse star = (boolean) ident = (string) qualifiedName = (ident*) typeDeclaration = (classHeader,fieldDeclarations) classHeader = (modifiers,classWord,ident,extends,interfaces) modifiers = (modifier*) final = (boolean) modifier = ABSTRACT | FINAL | PUBLIC | PROTECTED | PRIVATE | STATIC | TRANSIENT | VOLATILE | NATIVE | SYNCHRONIZED classWord = CLASS | INTERFACE interfaces = (classNameList) fieldDeclarations = (fieldDeclaration*) fieldDeclaration = FieldVariableDeclaration (fieldVariableDeclaration) | MethodDeclaration (methodDeclaration) | ConstructorDeclaration (constructorDeclaration) | StaticNonStaticInitializer (boolean,block) | TypeDeclaration (typeDeclaration) fieldVariableDeclaration = (modifiers,typeSpecifier,variableDeclarators) variableDeclarators = (variableDeclarator*) variableDeclarator = (declaratorName,variableInitializer?) variableInitializer = Expression(expression) | ArrayInitializers(arrayInitializers) arrayInitializers = (variableInitializer*) methodDeclaration = (modifiers,typeSpecifier,methodDeclarator,throws,methodBody) methodDeclarator = (declaratorName,parameterList,op_dim?) parameterList = (parameter*) parameter = (final,typeSpecifier,declaratorName) declaratorName = (ident,op_dim?) throws = (classNameList) methodBody = (block) constructorDeclaration = (modifiers,constructorDeclarator,throws,block) constructorDeclarator = (ident,parameterList) extends = (typeName*) block = (localVariableDeclarationsAndStatements) localVariableDeclarationsAndStatements = (localVariableDeclarationOrStatement*) localVariableDeclarationOrStatement = LocalVariableDeclaration( localVariableDeclaration) | Statement( statement) localVariableDeclaration = (final,typeSpecifier,variableDeclarators) statement = EmptyStatement | LabelStatement (labelStatement) | ExpressionStatement (expressionStatement) | SelectionStatement (selectionStatement) | IterationStatement (iterationStatement) | JumpStatement (jumpStatement) | GuardingStatement (guardingStatement) | Block (block) labelStatement = ID (ident ) | CASE (expression) | DEFAULT expressionStatement = (expression) selectionStatement = IF(expression,statement,statement?) | SWITCH (expression,block) iterationStatement = WHILE ( expression , statement ) | DO (statement, expression ) | FOR ( forInit?, forExpr?, forIncr?, statement) forInit = ExpressionStatements (expressionStatements) | LocalVariableDecl(localVariableDeclaration) forExpr = (expression) forIncr = (expressionStatements) expressionStatements = (expressionStatement*) jumpStatement = BREAK (ident?) | CONTINUE (ident?) | RETURN (expression?) | THROW (expression) guardingStatement = SYNCH ( expression,statement) | TRY (block,catches,finally?) catches = (catch*) catch = (catchHeader, block) catchHeader = CATCH ( typeSpecifier, ident? ) finally = ( block) primaryExpression = QualifiedName (qualifiedName) | SpecialName (specialName) | NewAllocationExpression (newAllocationExpression) | ComplexPrimaryParens (expression) | ComplexPrimaryNoParens (complexPrimaryNoParenthesis) | NOT_IMPLEMENTED complexPrimaryNoParenthesis = LITERAL (typeSpecifier,string) | BOOLLIT (boolean) | ArrayAccess (arrayAccess) | FieldAccess (fieldAccess) | MethodCall (methodCall) arrayAccess = QNE (qualifiedName, expression) | CPParens (expression, expression) | CPNoParens (complexPrimaryNoParenthesis, expression) fieldAccess = RPE (expression,ident) | QualNameThis (qualifiedName) | QualNameClass (qualifiedName) | PrimTyClass (primitiveType) methodCall = (methodAccess , argumentList ) methodAccess = SN (specialName) | QN (callObject?,ident) | CN (qualifiedName,ident) callObject = (expression) specialName = THIS | SUPER | JNULL argumentList = (expression*) newAllocationExpression = (qualifiedName?,plainNewAllocationExpression) plainNewAllocationExpression = AAE(arrayAllocationExpression,arrayInitializers ) | CAE(classAllocationExpression,fieldDeclarations ) classAllocationExpression = (typeName,argumentList ) arrayAllocationExpression = (typeName, dimExprs, dims) dimExprs = (dimExpr*) dimExpr = (expression ) dims = (op_dim*) op_dim = OP_DIM inc_dec = OP_INC | OP_DEC unaryOperator = UPLUS | UMINUS | UTWIDDLE | UPLING primitiveTypeExpression = (primitiveType,dims?) classTypeExpression = (qualifiedName,dims) binop = OP_LOR | OP_LAND | OP_INC_OR | OP_EXC_OR | OP_AND | OP_EQ | OP_NE | OP_LT | OP_GT | OP_LE | OP_GE | OP_SHRR | OP_SHL | OP_SHR | OP_ADD | OP_MINUS | OP_TIMES | OP_DIV | OP_PERCENT expression = PrimExp (primaryExpression) | PostfixExp (expression,inc_dec) | PrefixExp(inc_dec, expression) | UnaryOp(unaryOperator,expression) | PrimTyExp( primitiveTypeExpression , expression) | ClassTyExp( classTypeExpression , expression) | EXP( expression , expression) | QUESTION (expression, expression , expression) | BINOP(expression,binop,expression) | InstanceOf(expression,typeSpecifier) | ASGT (expression,assignmentOperator,expression) assignmentOperator = ASS_EQ | ASS_MUL | ASS_DIV | ASS_MOD | ASS_ADD | ASS_SUB | ASS_SHL | ASS_SHR | ASS_SHRR | ASS_AND | ASS_XOR | ASS_OR }