diff -uNr gdc-0.17/d/asmstmt.cc gdc-0.18/d/asmstmt.cc --- gdc-0.17/d/asmstmt.cc 2005-10-25 04:13:26.000000000 +0200 +++ gdc-0.18/d/asmstmt.cc 2006-04-19 05:39:29.000000000 +0200 @@ -71,9 +71,35 @@ return a_s; } -void AsmStatement::toCBuffer(OutBuffer *buf) +void AsmStatement::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { - buf->printf("AsmStatement::toCBuffer()"); + bool sep = 0, nsep = 0; + buf->writestring("asm { "); + + for (Token * t = tokens; t; t = t->next) { + switch (t->value) { + case TOKlparen: + case TOKrparen: + case TOKlbracket: + case TOKrbracket: + case TOKcolon: + case TOKsemicolon: + case TOKcomma: + case TOKstring: + case TOKcharv: + case TOKwcharv: + case TOKdcharv: + nsep = 0; + break; + default: + nsep = 1; + } + if (sep + nsep == 2) + buf->writeByte(' '); + sep = nsep; + buf->writestring(t->toChars()); + } + buf->writestring("; }"); buf->writenl(); } @@ -226,6 +252,8 @@ arg_val = ((VarExp *) arg->expr)->var->toSymbol()->Stree; else arg_val = arg->expr->toElem(irs); + if (DECL_P( arg_val )) + TREE_ADDRESSABLE( arg_val ) = 1; switch (arg->mode) { case Mode_Input: cns = m_cns; break; case Mode_Output: cns = mw_cns; is_input = false; break; diff -uNr gdc-0.17/d/d-asm-i386.h gdc-0.18/d/d-asm-i386.h --- gdc-0.17/d/d-asm-i386.h 2005-10-25 04:13:26.000000000 +0200 +++ gdc-0.18/d/d-asm-i386.h 2006-04-26 05:23:05.000000000 +0200 @@ -238,6 +238,7 @@ Op_movsX, Op_movsx, Op_movzx, + Op_mul, Op_out, Op_outs, Op_outsX, @@ -465,6 +466,7 @@ /* Op_movsX */ { 0, 0, 0, 0, Clb_DI|Clb_SI }, /* Op_movsx */ { reg, mr, 0, 1 }, // type suffix is special case /* Op_movzx */ { reg, mr, 0, 1 }, // type suffix is special case + /* Op_mul */ { U|ax, mr, 0, 1, Clb_SizeDXAX|Clb_Flags, Next_Form, Op_Src_DXAXF }, /* Op_out */ { N|port,ax, 0, 1 }, /* Op_outs */ { N|dx, mem, 0, 1, Clb_SI }, /* Op_outsX */ { 0, 0, 0, 0, Clb_SI }, @@ -757,7 +759,7 @@ { "insb", Op_insX }, { "insd", Op_insX }, { "insw", Op_insX }, - { "int", Op_Src }, // imm only + { "int", Op_SrcImm }, { "into", Op_0 }, { "invd", Op_0 }, { "invlpg", Op_0 }, @@ -870,7 +872,7 @@ { "movupd",Op_DstSrcSSE }, { "movups",Op_DstSrcSSE }, { "movzx", Op_movzx }, - { "mul", Op_Src_DXAXF }, + { "mul", Op_mul }, { "mulpd", Op_DstSrcSSE }, { "mulps", Op_DstSrcSSE }, { "mulsd", Op_DstSrcSSE }, @@ -1257,6 +1259,10 @@ nextToken(); opIdent = Id::___in; return Op_in; + case TOKint32: // "int" + nextToken(); + opIdent = Id::__int; + return Op_SrcImm; case TOKout: nextToken(); opIdent = Id::___out; @@ -1688,7 +1694,21 @@ if (opInfo->implicitClobbers & Clb_SP) stmt->regs |= (1 << Reg_ESP); if (opInfo->implicitClobbers & Clb_ST) + { + /* Can't figure out how to tell GCC that an + asm statement leaves an arg pushed on the stack. + Maybe if the statment had and input or output + operand it would work... In any case, clobbering + all FP prevents incorrect code generation. */ stmt->regs |= (1 << Reg_ST); + stmt->regs |= (1 << Reg_ST1); + stmt->regs |= (1 << Reg_ST2); + stmt->regs |= (1 << Reg_ST3); + stmt->regs |= (1 << Reg_ST4); + stmt->regs |= (1 << Reg_ST5); + stmt->regs |= (1 << Reg_ST6); + stmt->regs |= (1 << Reg_ST7); + } if (opInfo->implicitClobbers & Clb_Flags) asmcode->moreRegs |= (1 << (Reg_EFLAGS - 32)); @@ -1701,9 +1721,13 @@ fmt = "%"; switch (op) { + case Op_mul: + // gas won't accept the two-operand form; skip to the source operand + i__ = 1; + // drop through case Op_bound: case Op_enter: - i = i; + i = i__; break; default: i = nOperands - 1 - i__; // operand = & operands[ nOperands - 1 - i ]; @@ -1766,7 +1790,7 @@ break; case Opr_Mem: // better: use output operands for simple variable references - if (opInfo->operands[i] & Opr_Update) { + if ( (opInfo->operands[i] & Opr_Update) == Opr_Update) { mode = Mode_Update; } else if (opInfo->operands[i] & Opr_Dest) { mode = Mode_Output; diff -uNr gdc-0.17/d/d-builtins2.cc gdc-0.18/d/d-builtins2.cc --- gdc-0.17/d/d-builtins2.cc 2005-10-02 16:17:55.000000000 +0200 +++ gdc-0.18/d/d-builtins2.cc 2006-05-21 23:37:42.000000000 +0200 @@ -221,8 +221,8 @@ } FuncDeclaration * func = new FuncDeclaration(0, 0, Lexer::idPool(name), STCextern, df); - func->csym = new Symbol; - func->csym->Stree = decl; + func->isym = new Symbol; + func->isym->Stree = decl; d_bi_funcs.data[bi] = func; } diff -uNr gdc-0.17/d/d-codegen.cc gdc-0.18/d/d-codegen.cc --- gdc-0.17/d/d-codegen.cc 2005-12-02 02:00:23.000000000 +0100 +++ gdc-0.18/d/d-codegen.cc 2006-05-21 23:37:42.000000000 +0200 @@ -32,6 +32,8 @@ IRState gen; Array IRState::stmtExprList; TemplateEmission IRState::emitTemplates; +bool IRState::splitDynArrayVarArgs; +bool IRState::useBuiltins; bool IRState::warnSignCompare = false; bool IRState::originalOmitFramePointer; @@ -131,6 +133,46 @@ } tree +IRState::exprVar(tree t_type) +{ + tree t_decl = build_decl(VAR_DECL, NULL_TREE, t_type); + DECL_CONTEXT( t_decl ) = getLocalContext(); + DECL_ARTIFICIAL( t_decl ) = 1; + return t_decl; +} + +static bool +needs_expr_var(tree exp) +{ + switch (TREE_CODE(exp)) { + case VAR_DECL: + case FUNCTION_DECL: + case PARM_DECL: + case CONST_DECL: + case INDIRECT_REF: + case ARRAY_REF: + return false; + case COMPONENT_REF: + return needs_expr_var(TREE_OPERAND(exp,0)); + default: + return true; + } +} + +tree +IRState::maybeExprVar(tree exp, tree * out_var) +{ + if ( needs_expr_var(exp) ) { + *out_var = exprVar(TREE_TYPE(exp)); + DECL_INITIAL( *out_var ) = exp; + return *out_var; + } else { + *out_var = NULL_TREE; + return exp; + } +} + +tree IRState::declContext(Dsymbol * d_sym) { Dsymbol * orig_sym = d_sym; @@ -266,10 +308,8 @@ break; case Tsarray: { - // %% TODO: stuffing types ok? if (target_type->ty == Tpointer) { - result = addressOf( exp ); - TREE_TYPE(result) = target_type->toCtype(); + result = nop( addressOf( exp ), target_type->toCtype() ); } else if (target_type->ty == Tarray) { TypeSArray * a_type = (TypeSArray*) exp_type; @@ -289,8 +329,8 @@ } else if (sz_a != sz_b) { array_len = array_len * sz_a / sz_b; } - tree pointer_value = addressOf( exp ); - TREE_TYPE(pointer_value) = target_type->next->pointerTo()->toCtype(); + tree pointer_value = nop( addressOf( exp ), + target_type->next->pointerTo()->toCtype() ); // Assumes casting to dynamic array of same type or void return darrayVal(target_type, array_len, pointer_value); @@ -440,7 +480,25 @@ else return exp_tree; } else { - return convertForAssignment( exp->toElem(this), exp->type, arg->type ); + /* + Type * et = exp->type->toBasetype(); + Type * at = arg->type->toBasetype(); + if (et != at) { + if ((et->ty == Taarray && at == Type::tvoid->arrayOf()) || + (et->ty == Tarray && at == Type::tvoid->arrayOf()) || + (et->ty == Tdelegate && at->ty == Tdelegate) || + (et->ty == Tclass && at->ty == Tpointer) || + (et->ty == Tpointer && at->ty == Tpointer) + ) { + } else { + g.ofile->setLoc(exp->loc); + ::warning("ackthpbpt: must convert %s to %s\n", + exp->type->toChars(), arg->type->toChars()); + } + } + else + */ + return exp->toElem(this); } } @@ -459,11 +517,7 @@ result = convertForAssignment(in_exp_tree, in_exp_type, target_decl->type); } - // We can't init static storage with a VAR_DECL (probably can't - // do it with an auto variable, either -- but can just use - // MODIFY_EXPR in that case). Also applies to fields of - // record in static storage - + // Cannot initialize static storage with a VAR_DECL // %%TODO: Are these all the cases? if (! target_decl->type->isscalar() && @@ -594,23 +648,6 @@ return d_truthvalue_conversion( result ); } - - -tree -IRState::convertForVarArg(Expression * exp) -{ - // The conversions are already done by the front end - // This just handles stuff we build. - - if (exp->type) { - exp = exp->integralPromotions(); - // %% figure out why I needed this... - if (exp->type->toBasetype()->ty == Tsarray) - exp = exp->castTo( exp->type->toBasetype()->next->arrayOf() ); - } - return exp->toElem( this ); -} - /* Convert to void[] without changing the length */ tree IRState::rawArray(Expression * exp) @@ -718,7 +755,7 @@ } tree -IRState::floatConstant( real_t value, TypeBasic * target_type ) +IRState::floatConstant(const real_t & value, TypeBasic * target_type ) { REAL_VALUE_TYPE converted_val; @@ -733,13 +770,16 @@ IRState::binding(tree var_chain, tree body) { // BIND_EXPR/DECL_INITIAL not supported in 4.0? - assert(TREE_CHAIN(var_chain) == NULL_TREE); // TODO + gcc_assert(TREE_CHAIN(var_chain) == NULL_TREE); // TODO: only handles one var - tree ini = build2(MODIFY_EXPR, void_type_node, var_chain, DECL_INITIAL(var_chain)); - DECL_INITIAL(var_chain) = NULL_TREE; + if ( DECL_INITIAL(var_chain) ) + { + tree ini = build2(MODIFY_EXPR, void_type_node, var_chain, DECL_INITIAL(var_chain)); + DECL_INITIAL(var_chain) = NULL_TREE; + body = compound(ini, body); + } - return build3(BIND_EXPR, TREE_TYPE(body), var_chain, - compound(ini, body), NULL_TREE); + return build3(BIND_EXPR, TREE_TYPE(body), var_chain, body, NULL_TREE); } #endif @@ -860,16 +900,36 @@ Argument * formal_arg = (Argument *) formal_args->data[i + fa_adj]; actual_arg_tree = convertForArgument(actual_arg_exp, formal_arg); - } else if (func_type->linkage != LINKd) { - // Vararg arguments - actual_arg_tree = convertForVarArg(actual_arg_exp); + + // from c-typeck.c: convert_arguments, default_conversion, ... + if (INTEGRAL_TYPE_P (TREE_TYPE(actual_arg_tree)) + && (TYPE_PRECISION (TREE_TYPE(actual_arg_tree)) < + TYPE_PRECISION (integer_type_node))) { + + actual_arg_tree = d_convert_basic(integer_type_node, actual_arg_tree); + } } else { - actual_arg_tree = actual_arg_exp->toElem(this); + if (splitDynArrayVarArgs && actual_arg_exp->type->toBasetype()->ty == Tarray) + { + tree da_exp = maybeMakeTemp( actual_arg_exp->toElem(this) ); + actual_arg_list.cons( darrayLenRef( da_exp ) ); + actual_arg_list.cons( darrayPtrRef( da_exp ) ); + continue; + } + else + { + actual_arg_tree = actual_arg_exp->toElem( this ); + + /* Not all targets support passing unpromoted types, so + promote anyway. */ + tree prom_type = d_type_promotes_to( TREE_TYPE( actual_arg_tree )); + if (prom_type != TREE_TYPE( actual_arg_tree )) + actual_arg_tree = d_convert_basic(prom_type, actual_arg_tree); + } } } //TREE_USED( actual_arg_tree ) = 1; // needed ? - actual_arg_list.cons( actual_arg_tree ); } @@ -907,17 +967,18 @@ static const char * libcall_ids[LIBCALL_count] = { "_d_assert", "_d_array_bounds", "_d_switch_error", "_D9invariant12_d_invariantFC6ObjectZv", - "_d_newclass", "_d_new", "_d_newarrayi", "_d_newarrayip", "_d_newbitarray", + "_d_newclass", "_d_new", /*"_d_newarrayi", */"_d_newarrayip", "_d_newbitarray", "_d_delclass", "_d_delarray", "_d_delmemory", "_d_callfinalizer", "_d_arraysetlength", "_d_arraysetlengthb", "_d_dynamic_cast", "_d_interface_cast", "_adEq", "_adEqBit", "_adCmp", "_adCmpChar", "_adCmpBit", - "_aaIn", "_aaGet", "_aaGetRvalue", "_aaDel", + //"_aaIn", "_aaGet", "_aaGetRvalue", "_aaDel", + "_aaInp", "_aaGetp", "_aaGetRvaluep", "_aaDelp", "_d_arraycast", "_d_arraycast_frombit", "_d_arraycopy", "_d_arraycopybit", "_d_arraycat", "_d_arraycatb", "_d_arraycatn", "_d_arrayappend", "_d_arrayappendb", - "_d_arrayappendc", "_d_arrayappendcb", + /*"_d_arrayappendc", */"_d_arrayappendcp", "_d_arrayappendcb", "_d_arraysetbit", "_d_arraysetbit2", "_d_monitorenter", "_d_monitorexit", "_d_criticalenter", "_d_criticalexit", @@ -983,24 +1044,19 @@ return_type = getObjectType(); break; case LIBCALL_NEW: - arg_types.push( Type::tuns32 ); - arg_types.push( Type::tuns32 ); - return_type = Type::tvoid->arrayOf(); - break; - case LIBCALL_NEWARRAYI: - arg_types.push( Type::tuns32 ); - arg_types.push( Type::tuns32 ); - varargs = true; + arg_types.push( Type::tsize_t ); + arg_types.push( Type::tsize_t ); return_type = Type::tvoid->arrayOf(); break; + //case LIBCALL_NEWARRAYI: case LIBCALL_NEWARRAYIP: - arg_types.push( Type::tuns32 ); - arg_types.push( Type::tuns32 ); - arg_types.push(Type::tvoid->pointerTo()); + arg_types.push( Type::tsize_t ); + arg_types.push( Type::tsize_t ); + arg_types.push( Type::tvoid->pointerTo() ); //varargs = true; return_type = Type::tvoid->arrayOf(); break; case LIBCALL_NEWBITARRAY: - arg_types.push( Type::tuns32 ); + arg_types.push( Type::tsize_t ); arg_types.push( Type::tbit ); return_type = Type::tbit->arrayOf(); break; @@ -1018,9 +1074,9 @@ break; case LIBCALL_ARRAYSETLENGTH: case LIBCALL_ARRAYSETLENGTH_B: - arg_types.push( Type::tuns32 ); + arg_types.push( Type::tsize_t ); if (lib_call == LIBCALL_ARRAYSETLENGTH) - arg_types.push( Type::tuns32 ); + arg_types.push( Type::tsize_t ); arg_types.push( Type::tvoid->arrayOf()->pointerTo() ); return_type = Type::tvoid->arrayOf(); break; @@ -1051,30 +1107,34 @@ arg_types.push(Type::tbit->arrayOf()); return_type = Type::tint32; break; - case LIBCALL_AAIN: - case LIBCALL_AAGET: - case LIBCALL_AAGETRVALUE: - case LIBCALL_AADEL: +// case LIBCALL_AAIN: +// case LIBCALL_AAGET: +// case LIBCALL_AAGETRVALUE: +// case LIBCALL_AADEL: + case LIBCALL_AAINP: + case LIBCALL_AAGETP: + case LIBCALL_AAGETRVALUEP: + case LIBCALL_AADELP: { Type * aa_type = Type::tvoid->pointerTo()->arrayOf(); // associated arrays are dynamic arrays of pointers - if (lib_call == LIBCALL_AAGET) + if (lib_call == LIBCALL_AAGETP) aa_type = aa_type->pointerTo(); arg_types.reserve(3); arg_types.push(aa_type); arg_types.push(Type::typeinfo->type); // typeinfo reference - if ( lib_call == LIBCALL_AAGET || lib_call == LIBCALL_AAGETRVALUE) - arg_types.push(Type::tint32); // %% + if ( lib_call == LIBCALL_AAGETP || lib_call == LIBCALL_AAGETRVALUEP) + arg_types.push(Type::tsize_t); - varargs = true; + arg_types.push(Type::tvoid->pointerTo()); //varargs = true; switch (lib_call) { - case LIBCALL_AAIN: - case LIBCALL_AAGET: - case LIBCALL_AAGETRVALUE: + case LIBCALL_AAINP: + case LIBCALL_AAGETP: + case LIBCALL_AAGETRVALUEP: return_type = Type::tvoid->pointerTo(); break; - case LIBCALL_AADEL: + case LIBCALL_AADELP: return_type = Type::tvoid; break; default: @@ -1113,7 +1173,7 @@ t = Type::tvoid->arrayOf(); arg_types.push(t); arg_types.push(t); - arg_types.push(Type::tuns32); + arg_types.push(Type::tsize_t); return_type = t; break; case LIBCALL_ARRAYCATN: @@ -1126,7 +1186,7 @@ t = Type::tuns8->arrayOf(); arg_types.push(t->pointerTo()); arg_types.push(t); - arg_types.push(Type::tuns32); + arg_types.push(Type::tsize_t); return_type = Type::tvoid->arrayOf(); break; case LIBCALL_ARRAYAPPENDB: @@ -1135,11 +1195,12 @@ arg_types.push(t); return_type = t; break; - case LIBCALL_ARRAYAPPENDC: +// case LIBCALL_ARRAYAPPENDC: + case LIBCALL_ARRAYAPPENDCP: t = Type::tuns8->arrayOf()->pointerTo(); arg_types.push(t->pointerTo()); - arg_types.push(Type::tuns32); - varargs = true; + arg_types.push(Type::tsize_t); + arg_types.push(Type::tvoid->pointerTo()); // varargs = true; return_type = Type::tvoid->arrayOf(); break; case LIBCALL_ARRAYAPPENDCB: @@ -1190,7 +1251,6 @@ abort(); } decl = FuncDeclaration::genCfunc(return_type, (char *) libcall_ids[lib_call]); - // %% have to do this because we don't declare arguments { TypeFunction * tf = (TypeFunction *) decl->type; tf->varargs = varargs ? 1 : 0; @@ -1206,19 +1266,6 @@ return decl; } -tree -IRState::libCall(LibCall lib_call, Array * args, tree result_type) -{ - FuncDeclaration * func_decl = getLibCallDecl(lib_call); - - tree result = call(func_decl, args); - if (result_type != NULL_TREE) { - // %% assumes caller knows what it is doing - TREE_TYPE( result ) = result_type; - } - return result; -} - tree IRState::maybeExpandSpecialCall(tree call_exp) { // More code duplication from C @@ -1253,6 +1300,8 @@ } } else if (DECL_BUILT_IN_CLASS(callee) == BUILT_IN_FRONTEND) { Intrinsic intrinsic = (Intrinsic) DECL_FUNCTION_CODE(callee); + tree type; + Type *d_type; switch (intrinsic) { case INTRINSIC_C_VA_ARG: // %% should_check c_promotes_to as in va_arg now @@ -1271,7 +1320,32 @@ t = build1(INDIRECT_REF, TREE_TYPE(TREE_TYPE(t)), t); } } - return build1(VA_ARG_EXPR, TREE_TYPE(TREE_TYPE(callee)), t); + type = TREE_TYPE(TREE_TYPE(callee)); + if (splitDynArrayVarArgs && (d_type = getDType(type)) && + d_type->toBasetype()->ty == Tarray) + { + // should create a temp var of type TYPE and move the binding + // to outside this expression. + t = stabilize_reference(t); + tree ltype = TREE_TYPE( TYPE_FIELDS( type )); + tree ptype = TREE_TYPE( TREE_CHAIN( TYPE_FIELDS( type ))); + tree lvar = exprVar(ltype); + tree pvar = exprVar(ptype); + tree e1 = vmodify(lvar, build1(VA_ARG_EXPR, ltype, t)); + tree e2 = vmodify(pvar, build1(VA_ARG_EXPR, ptype, t)); + tree b = compound( compound( e1, e2 ), darrayVal(type, lvar, pvar) ); + return binding(lvar, binding(pvar, b)); + } + else + { + tree type2 = d_type_promotes_to(type); + t = build1(VA_ARG_EXPR, type2, t); + if (type != type2) + // silently convert promoted type... + t = d_convert_basic(type, t); + return t; + } + break; case INTRINSIC_C_VA_START: /* t = TREE_VALUE(); @@ -1478,8 +1552,8 @@ ptr_exp = pvoidOkay( ptr_exp ); else ptr_exp = d_convert_basic(bitConfig.elemType->pointerTo()->toCtype(), ptr_exp); - elem_ref = build1(INDIRECT_REF, TREE_TYPE(TREE_TYPE(ptr_exp)), - pointerIntSum( ptr_exp, subscript_expr)); + elem_ref = indirect(pointerIntSum( ptr_exp, subscript_expr), + TREE_TYPE(TREE_TYPE(ptr_exp))); if (is_bit) { tree t; @@ -1877,16 +1951,15 @@ vtbl_ref = TREE_OPERAND(this_expr, 0); else //#endif - vtbl_ref = build1( INDIRECT_REF, TREE_TYPE(TREE_TYPE( this_expr )), - this_expr ); // dereference the pointer to the object + vtbl_ref = indirect(this_expr); + tree field = TYPE_FIELDS( TREE_TYPE( vtbl_ref )); // the vtbl is the first field //vtbl_ref = build( COMPONENT_REF, TREE_TYPE( field ), vtbl_ref, field ); // vtbl field (a pointer) vtbl_ref = component( vtbl_ref, field ); // vtbl field (a pointer) // %% better to do with array ref? vtbl_ref = build( PLUS_EXPR, TREE_TYPE(vtbl_ref), vtbl_ref, size_int( getPointerSize() * func->vtblIndex )); - vtbl_ref = build1( INDIRECT_REF, TREE_TYPE( functionPointer(func) ), - vtbl_ref ); + vtbl_ref = indirect(vtbl_ref, TREE_TYPE( functionPointer(func) )); return methodCallExpr(vtbl_ref, this_expr, d_type); } @@ -2012,13 +2085,6 @@ return save_expr(t); else return stabilize_reference(t); - /* Can't make a SAVE_EXPR of an lvalue, or else a copy is made. (?) - Just save the address of the array, and indirect that. - - Needed for SliceExp and ForeEachStatement. - */ - return build1(INDIRECT_REF, TREE_TYPE(t), - save_expr( addressOf( t ) )); } else return t; } @@ -2218,8 +2284,11 @@ # else # error Fix This # endif - if (type) + if (type) { TREE_TYPE( tree_value ) = type; + // May not to call force_fit_type for 3.3.x and 3.4.x, but being safe. + force_fit_type(tree_value, 0); + } #else # if HOST_BITS_PER_WIDE_INT == 32 tree tree_value = build_int_cst_wide(type, @@ -2229,6 +2298,10 @@ # else # error Fix This # endif + /* VALUE may be an incorrect representation for TYPE. Example: + uint x = cast(uint) -3; // becomes "-3u" -- value=0xfffffffffffffd type=Tuns32 + Constant folding will not work correctly unless this is done. */ + tree_value = force_fit_type(tree_value, 0, 0, 0); #endif return tree_value; } @@ -2380,13 +2453,16 @@ if (array_type->ty == Taarray) { Type * key_type = ((TypeAArray *) array_type)->key->toBasetype(); + AddrOfExpr aoe; + tree args[4]; args[0] = this->addressOf( e1->toElem(this) ); args[1] = this->typeinfoReference(key_type); - args[2] = this->integerConstant( array_type->next->size(), Type::tuns32 ); - args[3] = this->convertTo( e2, key_type ); // %% vararg issues + args[2] = this->integerConstant( array_type->next->size(), Type::tsize_t ); + args[3] = aoe.set(this, this->convertTo( e2, key_type )); return build1(INDIRECT_REF, type->toCtype(), - this->libCall(LIBCALL_AAGET, 4, args, type->pointerTo()->toCtype())); + aoe.finish(this, + this->libCall(LIBCALL_AAGETP, 4, args, type->pointerTo()->toCtype()))); } } return e->toElem(this); @@ -2913,40 +2989,6 @@ } } -ArrayMaker::ArrayMaker(Type * elem_type, int storage_class) -{ - elemType = elem_type; - storageClass = storage_class; - - elemList = NULL_TREE; - count = 0; -} - -ArrayMaker & -ArrayMaker::add(tree value) -{ - // GCC 4.0: the TREE_PURPOSE field is required - elemList = tree_cons(size_int(count), value, elemList); - count++; - return *this; -} - -tree -ArrayMaker::finish() -{ - tree ctor = make_node(CONSTRUCTOR); - tree type = gen.arrayType(elemType->toCtype(), count); - TREE_TYPE( ctor ) = type; - CONSTRUCTOR_ELTS( ctor ) = nreverse( elemList ); - if (storageClass & STCstatic) - TREE_STATIC( ctor ) = 1; - if (storageClass & STCconst) - TREE_CONSTANT( ctor ) = 1; - TREE_READONLY( ctor ) = 1; - return ctor; - -} - ArrayScope::ArrayScope(IRState * ini_irs, VarDeclaration * ini_v, const Loc & loc) : v(ini_v), irs(ini_irs) { diff -uNr gdc-0.17/d/d-codegen.h gdc-0.18/d/d-codegen.h --- gdc-0.17/d/d-codegen.h 2005-11-27 16:59:45.000000000 +0100 +++ gdc-0.18/d/d-codegen.h 2006-05-21 23:37:42.000000000 +0200 @@ -32,7 +32,7 @@ LIBCALL_INVARIANT, LIBCALL_NEWCLASS, LIBCALL_NEW, - LIBCALL_NEWARRAYI, + //LIBCALL_NEWARRAYI, LIBCALL_NEWARRAYIP, LIBCALL_NEWBITARRAY, LIBCALL_DELCLASS, @@ -48,10 +48,14 @@ LIBCALL_ADCMP, LIBCALL_ADCMPCHAR, LIBCALL_ADCMPBIT, - LIBCALL_AAIN, + /*LIBCALL_AAIN, LIBCALL_AAGET, LIBCALL_AAGETRVALUE, - LIBCALL_AADEL, + LIBCALL_AADEL,*/ + LIBCALL_AAINP, + LIBCALL_AAGETP, + LIBCALL_AAGETRVALUEP, + LIBCALL_AADELP, LIBCALL_ARRAYCAST, LIBCALL_ARRAYCAST_FROMBIT, LIBCALL_ARRAYCOPY, @@ -61,7 +65,8 @@ LIBCALL_ARRAYCATN, LIBCALL_ARRAYAPPEND, LIBCALL_ARRAYAPPENDB, - LIBCALL_ARRAYAPPENDC, + //LIBCALL_ARRAYAPPENDC, + LIBCALL_ARRAYAPPENDCP, LIBCALL_ARRAYAPPENDCB, LIBCALL_ARRAYSETBIT, LIBCALL_ARRAYSETBIT2, @@ -110,6 +115,8 @@ void emitLocalVar(VarDeclaration * v, bool no_init = false); tree localVar(tree t_type); tree localVar(Type * e_type) { return localVar(e_type->toCtype()); } + tree exprVar(tree t_type); + tree maybeExprVar(tree exp, tree * out_var); void expandDecl(tree t_decl); // ** Type conversion @@ -130,7 +137,6 @@ tree convertForCondition(Expression * exp) { return convertForCondition(exp->toElem(this), exp->type); } tree convertForCondition(tree exp_tree, Type * exp_type); - tree convertForVarArg(Expression * exp); tree rawArray(Expression * exp); @@ -146,7 +152,7 @@ } static Type * getObjectType() { - return ClassDeclaration::classinfo->baseClass->type; + return ClassDeclaration::object->type; } // Routines to handle variables that are references. @@ -175,7 +181,7 @@ return integerConstant(value, type->toCtype()); } - static tree floatConstant( real_t value, TypeBasic * target_type ); + static tree floatConstant(const real_t & value, TypeBasic * target_type ); // ** Routines for built in structured types @@ -231,8 +237,16 @@ tree toElemLvalue(Expression * e); static tree addressOf(tree exp) { + tree t; + d_mark_addressable(exp); - tree t = build1(ADDR_EXPR, build_pointer_type(TREE_TYPE(exp)), exp); +#if ENABLE_CHECKING + // Gimplify doesn't like &(*(ptr-to-array-type)) with static arrays + if (TREE_CODE(exp) == INDIRECT_REF) + t = nop(TREE_OPERAND(exp, 0), build_pointer_type(TREE_TYPE(exp))); + else +#endif + t = build1(ADDR_EXPR, build_pointer_type(TREE_TYPE(exp)), exp); #if D_NO_TRAMPOLINES if (TREE_CODE( exp ) == FUNCTION_DECL) TREE_STATIC( t ) = 1; @@ -240,20 +254,25 @@ return t; } static tree addressOf(Dsymbol *d) { - return addressOf( d->toSymbol()->Stree ); - } + return addressOf( d->toSymbol()->Stree ); } + /* Cast exp (which should be a pointer) to TYPE* and then indirect. The + back-end requires this cast in many cases. */ static tree indirect(tree exp, tree type) { - return build1(INDIRECT_REF, type, exp); - } - static tree indirect(tree exp) - { - return indirect(exp, TREE_TYPE(TREE_TYPE(exp))); + return build1(INDIRECT_REF, type, + nop(exp, build_pointer_type(type))); } + static tree indirect(tree exp) { + return build1(INDIRECT_REF, TREE_TYPE(TREE_TYPE(exp)), exp); } + static tree vmodify(tree dst, tree src) { + return build2(MODIFY_EXPR, void_type_node, dst, src); } - tree pointerIntSum(Expression * ptr_exp, Expression * idx_exp) - { return pointerIntSum(ptr_exp->toElem(this), idx_exp->toElem(this)); } + tree pointerIntSum(Expression * ptr_exp, Expression * idx_exp) { + return pointerIntSum(ptr_exp->toElem(this), idx_exp->toElem(this)); } tree pointerIntSum(tree ptr_node, tree idx_exp); + static tree nop(tree e, tree t) { + return build1(NOP_EXPR, t, e); } + // DMD allows { void[] a; & a[3]; } static tree pvoidOkay(tree t) { @@ -286,7 +305,7 @@ bool isBitArrayAccess(Expression * e) { if (e->op == TOKindex) { - Type * e1_basetype = e1_basetype = ((IndexExp *) e)->e1->type->toBasetype(); + Type * e1_basetype = ((IndexExp *) e)->e1->type->toBasetype(); // assuming != Taarray is good enough for == Tarray,Tsarray,Tpointer return e1_basetype->ty != Taarray && e1_basetype->next->isbit(); } else { @@ -324,22 +343,12 @@ return build3(COMPONENT_REF, TREE_TYPE(f), v, f, NULL_TREE); #endif } - static tree component(tree t, tree v, tree f) - { - // shouldn't need this... -#if D_GCC_VER < 40 - return build(COMPONENT_REF, t, v, f); -#else - return build3(COMPONENT_REF, t, v, f, NULL_TREE); -#endif - } // ** Function calls tree call(FuncDeclaration * func_decl, Array * args); tree call(Expression * expr, Array * arguments); tree call(tree callable, tree object, Array * arguments); - tree libCall(LibCall lib_call, Array * args, tree result_type = 0); tree assertCall(Loc loc, LibCall libcall = LIBCALL_ASSERT); static FuncDeclaration * getLibCallDecl(LibCall lib_call); static void replaceLibCallDecl(FuncDeclaration * d_decl); @@ -364,6 +373,8 @@ } static TemplateEmission emitTemplates; + static bool splitDynArrayVarArgs; + static bool useBuiltins; // Warnings static bool warnSignCompare; @@ -372,8 +383,7 @@ static bool originalOmitFramePointer; protected: - // This can't be static because - static tree maybeExpandSpecialCall(tree call_exp); + tree maybeExpandSpecialCall(tree call_exp); public: tree floatMod(tree a, tree b, Type * d_type); @@ -415,8 +425,6 @@ static bool functionNeedsChain(FuncDeclaration *f); // ** Instruction stream manipulation - - // want to inline gcc3 versions... void startCond(Statement * stmt, Expression * e_cond); void startElse(); void endCond(); @@ -531,18 +539,6 @@ void finish(); }; -class ArrayMaker { - Type * elemType; - int storageClass; - tree elemList; - unsigned count; -public: - ArrayMaker(Type * elem_type, int storage_class); - ArrayMaker & add(tree value); - tree finish(); - -}; - class ArrayScope { VarDeclaration * v; IRState * irs; @@ -552,7 +548,17 @@ tree finish(tree e); }; - +class AddrOfExpr { +public: + tree var; + AddrOfExpr() { var = NULL_TREE; } + tree set(IRState * irs, tree exp) { + return irs->addressOf( irs->maybeExprVar(exp, & var) ); + } + tree finish(IRState * irs, tree e2) { + return var ? irs->binding(var, e2) : e2; + } +}; #endif diff -uNr gdc-0.17/d/d-decls.cc gdc-0.18/d/d-decls.cc --- gdc-0.17/d/d-decls.cc 2005-11-05 15:12:01.000000000 +0100 +++ gdc-0.18/d/d-decls.cc 2006-05-21 23:37:42.000000000 +0200 @@ -318,179 +318,182 @@ // returns a FUNCTION_DECL tree Symbol *FuncDeclaration::toSymbol() { - if (! csym) { - tree id; - //struct prod_token_parm_item* parm; - //tree type_node; - tree fn_decl; - char * mangled_ident_str = 0; - AggregateDeclaration * agg_decl; + if (! csym) { + csym = new Symbol(); + + if (! isym) { + tree id; + //struct prod_token_parm_item* parm; + //tree type_node; + Type * func_type = tintro ? tintro : type; + tree fn_decl; + char * mangled_ident_str = 0; + AggregateDeclaration * agg_decl; - if (ident) { - id = get_identifier(ident->string); - } else { - // This happens for assoc array foreach bodies - - // Not sure if idents are strictly necc., but announce_function - // dies without them. + if (ident) { + id = get_identifier(ident->string); + } else { + // This happens for assoc array foreach bodies - // %% better: use parent name - - static unsigned unamed_seq = 0; - char buf[64]; - sprintf(buf, "___unamed_%u", ++unamed_seq);//%% sprintf - id = get_identifier(buf); - } + // Not sure if idents are strictly necc., but announce_function + // dies without them. - tree fn_type = type->toCtype(); - dkeep(fn_type); /* TODO: fix this. we need to keep the type because - the creation of a method type below leaves this fn_type - unreferenced. maybe lang_specific.based_on */ - - tree vindex = NULL_TREE; - if (isNested()) { - // Nested functions take an extra argument to be compatible with delegates. - // The stack frame will come from a trampoline. (unless D_NO_TRAMPOLINES is - // in effect.) - fn_type = build_function_type(TREE_TYPE(fn_type), - tree_cons(NULL_TREE, ptr_type_node, TYPE_ARG_TYPES(fn_type))); - tree t = fn_type; - while ( (t = TYPE_NEXT_VARIANT(t)) ) - if (D_TYPE_IS_NESTED(t) && gen.getDType(t) == (Type *) this) - break; - if (t) - fn_type = t; - else { -#if GCC_VER < 40 - fn_type = build_type_copy(fn_type); -#else - fn_type = build_variant_type_copy(fn_type); -#endif - TYPE_LANG_SPECIFIC( fn_type ) = build_d_type_lang_specific(type); - D_TYPE_IS_NESTED( fn_type ) = 1; + // %% better: use parent name + + static unsigned unamed_seq = 0; + char buf[64]; + sprintf(buf, "___unamed_%u", ++unamed_seq);//%% sprintf + id = get_identifier(buf); } - } - else if ( ( agg_decl = isMember() ) ) { - // Do this even if there is no debug info. It is needed to maker - // sure member functions are not called statically - if (isThis()) { - tree method_type = build_method_type(TREE_TYPE(agg_decl->handle->toCtype()), fn_type); - TYPE_ATTRIBUTES( method_type ) = TYPE_ATTRIBUTES( fn_type ); - fn_type = method_type; - - /* hopefully, this->type->toCtype()->lang_specific->dtype != this->type - won't be a problem */ - TYPE_LANG_SPECIFIC( fn_type ) = build_d_type_lang_specific(this->type); - if (isVirtual()) - vindex = size_int(vtblIndex); + tree fn_type = func_type->toCtype(); + dkeep(fn_type); /* TODO: fix this. we need to keep the type because + the creation of a method type below leaves this fn_type + unreferenced. maybe lang_specific.based_on */ + + tree vindex = NULL_TREE; + if (isNested()) { + // Nested functions take an extra argument to be compatible with delegates. + // The stack frame will come from a trampoline. (unless D_NO_TRAMPOLINES is + // in effect.) + fn_type = build_function_type(TREE_TYPE(fn_type), + tree_cons(NULL_TREE, ptr_type_node, TYPE_ARG_TYPES(fn_type))); + tree t = fn_type; + while ( (t = TYPE_NEXT_VARIANT(t)) ) + if (D_TYPE_IS_NESTED(t) && gen.getDType(t) == (Type *) this) + break; + if (t) + fn_type = t; + else { + fn_type = build_type_copy(fn_type); + TYPE_LANG_SPECIFIC( fn_type ) = build_d_type_lang_specific(func_type); + D_TYPE_IS_NESTED( fn_type ) = 1; + } + } else if ( ( agg_decl = isMember() ) ) { + // Do this even if there is no debug info. It is needed to maker + // sure member functions are not called statically + if (isThis()) { + tree method_type = build_method_type(TREE_TYPE(agg_decl->handle->toCtype()), fn_type); + TYPE_ATTRIBUTES( method_type ) = TYPE_ATTRIBUTES( fn_type ); + fn_type = method_type; + + /* hopefully, this->type->toCtype()->lang_specific->dtype != func_type + won't be a problem */ + TYPE_LANG_SPECIFIC( fn_type ) = build_d_type_lang_specific(func_type); + + if (isVirtual()) + vindex = size_int(vtblIndex); + } + } else if (isMain() && func_type->next->toBasetype()->ty == Tvoid) { + fn_type = build_function_type(integer_type_node, TYPE_ARG_TYPES(fn_type)); } - } - // %%CHECK: is it okay for static nested functions to have a FUNC_DECL context? - // seems okay so far... - - fn_decl = build_decl( FUNCTION_DECL, id, fn_type ); - dkeep(fn_decl); - if (ident) { - mangled_ident_str = mangle(); - uniqueName(this, fn_decl, mangled_ident_str); - } - if (c_ident) - SET_DECL_ASSEMBLER_NAME(fn_decl, get_identifier(c_ident->string)); - // %% What about DECL_SECTION_NAME ? - //DECL_ARGUMENTS(fn_decl) = NULL_TREE; // Probably don't need to do this until toObjFile - DECL_CONTEXT (fn_decl) = gen.declContext(this); //context; - if (vindex) { - DECL_VINDEX (fn_decl) = vindex; - DECL_VIRTUAL_P (fn_decl) = 1; - } - if (! gen.functionNeedsChain(this) -#if D_GCC_VER >= 40 - // gcc 4.0: seems to be an error to set DECL_NO_STATIC_CHAIN on a toplevel function - // (tree-nest.c:1282:convert_all_function_calls) - && decl_function_context(fn_decl) -#endif - ) { - // Prevent backend from thinking this is a nested function. - DECL_NO_STATIC_CHAIN( fn_decl ) = 1; - } + // %%CHECK: is it okay for static nested functions to have a FUNC_DECL context? + // seems okay so far... - /* For now, inline asm means we can't inline (stack wouldn't be - what was expected and LDASM labels aren't unique.) - TODO: If the asm consists entirely - of extended asm, we can allow inlining. */ - if (inlineAsm) { - DECL_UNINLINABLE(fn_decl) = 1; - } else { + fn_decl = build_decl( FUNCTION_DECL, id, fn_type ); + dkeep(fn_decl); + if (ident) { + mangled_ident_str = mangle(); + uniqueName(this, fn_decl, mangled_ident_str); + } + if (c_ident) + SET_DECL_ASSEMBLER_NAME(fn_decl, get_identifier(c_ident->string)); + // %% What about DECL_SECTION_NAME ? + //DECL_ARGUMENTS(fn_decl) = NULL_TREE; // Probably don't need to do this until toObjFile + DECL_CONTEXT (fn_decl) = gen.declContext(this); //context; + if (vindex) { + DECL_VINDEX (fn_decl) = vindex; + DECL_VIRTUAL_P (fn_decl) = 1; + } + if (! gen.functionNeedsChain(this) + #if D_GCC_VER >= 40 + // gcc 4.0: seems to be an error to set DECL_NO_STATIC_CHAIN on a toplevel function + // (tree-nest.c:1282:convert_all_function_calls) + && decl_function_context(fn_decl) + #endif + ) { + // Prevent backend from thinking this is a nested function. + DECL_NO_STATIC_CHAIN( fn_decl ) = 1; + } + + /* For now, inline asm means we can't inline (stack wouldn't be + what was expected and LDASM labels aren't unique.) + TODO: If the asm consists entirely + of extended asm, we can allow inlining. */ + if (inlineAsm) { + DECL_UNINLINABLE(fn_decl) = 1; + } else { #if D_GCC_VER >= 40 - // see grokdeclarator in c-decl.c - if (flag_inline_trees == 2 && fbody /* && should_emit? */) - DECL_INLINE (fn_decl) = 1; + // see grokdeclarator in c-decl.c + if (flag_inline_trees == 2 && fbody /* && should_emit? */) + DECL_INLINE (fn_decl) = 1; #endif - } + } - if (naked) { - D_DECL_NO_FRAME_POINTER( fn_decl ) = 1; - DECL_NO_INSTRUMENT_FUNCTION_ENTRY_EXIT( fn_decl ) = 1; - - /* Need to do this or GCC will set up a frame pointer with -finline-functions. - Must have something to do with defered processing -- after we turn - flag_omit_frame_pointer back on. */ - DECL_UNINLINABLE( fn_decl ) = 1; - } + if (naked) { + D_DECL_NO_FRAME_POINTER( fn_decl ) = 1; + DECL_NO_INSTRUMENT_FUNCTION_ENTRY_EXIT( fn_decl ) = 1; + + /* Need to do this or GCC will set up a frame pointer with -finline-functions. + Must have something to do with defered processing -- after we turn + flag_omit_frame_pointer back on. */ + DECL_UNINLINABLE( fn_decl ) = 1; + } #ifdef TARGET_DLLIMPORT_DECL_ATTRIBUTES - // Have to test for import first - if (isImportedSymbol()) - gen.addDeclAttribute( fn_decl, "dllimport" ); - else if (isExport()) - gen.addDeclAttribute( fn_decl, "dllexport" ); + // Have to test for import first + if (isImportedSymbol()) + gen.addDeclAttribute( fn_decl, "dllimport" ); + else if (isExport()) + gen.addDeclAttribute( fn_decl, "dllexport" ); #endif + + g.ofile->setDeclLoc(fn_decl, this); + g.ofile->setupSymbolStorage(this, fn_decl); + if (! ident) + TREE_PUBLIC( fn_decl ) = 0; + + TREE_USED (fn_decl) = 1; // %% Probably should be a little more intelligent about this + + // if -mrtd is passed, how to handle this? handle in parsing or do + // we go back and find out if linkage was specified + switch (linkage) + { + case LINKwindows: + gen.addDeclAttribute(fn_decl, "stdcall"); + // The stdcall attribute also needs to be set on the function type. + assert( ((TypeFunction *) func_type)->linkage == LINKwindows ); + break; + case LINKpascal: + // stdcall and reverse params? + break; + case LINKc: + // %% hack: on darwin (at least) using a DECL_EXTERNAL (IRState::getLibCallDecl) + // and TREE_STATIC FUNCTION_DECLs causes the stub label to be output twice. This + // is a work around. This doesn't handle the case in which the normal + // getLibCallDecl has already bee created and used. Note that the problem only + // occurs with function inlining is used. + gen.replaceLibCallDecl(this); + break; + case LINKd: + // %% If x86, regparm(1) + // not sure if reg struct return + break; + case LINKcpp: + break; + default: + fprintf(stderr, "linkage = %d\n", linkage); + assert(0); + } - g.ofile->setDeclLoc(fn_decl, this); - g.ofile->setupSymbolStorage(this, fn_decl); - if (! ident) - TREE_PUBLIC( fn_decl ) = 0; - - TREE_USED (fn_decl) = 1; // %% Probably should be a little more intelligent about this + csym->Sident = mangled_ident_str; // save for making thunks + csym->Stree = fn_decl; - // if -mrtd is passed, how to handle this? handle in parsing or do - // we go back and find out if linkage was specified - switch (linkage) - { - case LINKwindows: - gen.addDeclAttribute(fn_decl, "stdcall"); - // The stdcall attribute also needs to be set on the function type. - assert( ((TypeFunction *) type)->linkage == LINKwindows ); - break; - case LINKpascal: - // stdcall and reverse params? - break; - case LINKc: - // %% hack: on darwin (at least) using a DECL_EXTERNAL (IRState::getLibCallDecl) - // and TREE_STATIC FUNCTION_DECLs causes the stub label to be output twice. This - // is a work around. This doesn't handle the case in which the normal - // getLibCallDecl has already bee created and used. Note that the problem only - // occurs with function inlining is used. - gen.replaceLibCallDecl(this); - break; - case LINKd: - // %% If x86, regparm(1) - // not sure if reg struct return - break; - case LINKcpp: - break; - default: - fprintf(stderr, "linkage = %d\n", linkage); - assert(0); + gen.maybeSetUpBuiltin(this); + } else { + csym->Stree = isym->Stree; } - - csym = new Symbol(); - csym->Sident = mangled_ident_str; // save for making thunks - csym->Stree = fn_decl; - - gen.maybeSetUpBuiltin(this); } return csym; } diff -uNr gdc-0.17/d/d-gcc-complex_t.h gdc-0.18/d/d-gcc-complex_t.h --- gdc-0.17/d/d-gcc-complex_t.h 2004-10-26 02:41:27.000000000 +0200 +++ gdc-0.18/d/d-gcc-complex_t.h 2006-03-12 15:16:26.000000000 +0100 @@ -56,6 +56,9 @@ } operator bool () { return !re.isZero() || !im.isZero(); } + + int operator == (complex_t y) { return re == y.re && im == y.im; } + int operator != (complex_t y) { return re != y.re || im != y.im; } }; inline complex_t operator * (real_t x, complex_t y) { return complex_t(x) * y; } diff -uNr gdc-0.17/d/d-gcc-includes.h gdc-0.18/d/d-gcc-includes.h --- gdc-0.17/d/d-gcc-includes.h 2005-08-12 04:32:44.000000000 +0200 +++ gdc-0.18/d/d-gcc-includes.h 2005-12-25 18:45:12.000000000 +0100 @@ -25,7 +25,7 @@ // which defines some inline functions that use C prototypes.... #define GCC_INSN_FLAGS_H -// Confliction definition getween stdio.h and libiberty.h over the throw() +// Conflicting definitions between stdio.h and libiberty.h over the throw() #define HAVE_DECL_ASPRINTF 1 #include "config.h" @@ -39,7 +39,7 @@ #define bool unsigned char #endif -// coretypes.h and tm.h is not present in gcc < 3.4 (so it seems) +// coretypes.h and tm.h is not present in gcc < 3.4 #if D_GCC_VER == 33 /* nothing */ #else @@ -48,6 +48,7 @@ #include "tm.h" #endif +#include "cppdefault.h" #include "tree.h" #include "real.h" #include "langhooks.h" diff -uNr gdc-0.17/d/d-gcc-real.cc gdc-0.18/d/d-gcc-real.cc --- gdc-0.17/d/d-gcc-real.cc 2005-11-28 05:17:52.000000000 +0100 +++ gdc-0.18/d/d-gcc-real.cc 2006-03-12 15:16:26.000000000 +0100 @@ -23,8 +23,12 @@ #include "mars.h" #include "lexer.h" +#include "mtype.h" #include "d-gcc-real.h" +#include "d-lang.h" +#include "d-codegen.h" + static enum machine_mode max_float_mode() { @@ -328,6 +332,16 @@ return real_to_integer(& rv()); } +d_uns64 +real_t::toInt(Type * real_type, Type * int_type) +{ + tree t = fold( build1(FIX_TRUNC_EXPR, int_type->toCtype(), + gen.floatConstant(rv(), real_type->toBasetype()->isTypeBasic())) ); + // can't use tree_low_cst as it asserts !TREE_OVERFLOW + // %% HOST_WIDE_INT + return TREE_INT_CST_LOW(t); +} + bool real_t::isZero() { @@ -362,10 +376,22 @@ return real_compare(out, & rv(), & r.rv()); } +bool +real_t::isIdenticalTo(const real_t & r) const +{ + return REAL_VALUES_IDENTICAL(rv(), r.rv()); +} + +void +real_t::format(char * buf, unsigned buf_size) const +{ + real_to_decimal(buf, & rv(), buf_size, 0, 1); +} + void -real_t::format(char * buf, unsigned buf_size) +real_t::formatHex(char * buf, unsigned buf_size) const { - real_to_decimal(buf, & rv(), buf_size, 0, 0); + real_to_hexadecimal(buf, & rv(), buf_size, 0, 1); } bool diff -uNr gdc-0.17/d/d-gcc-real.h gdc-0.18/d/d-gcc-real.h --- gdc-0.17/d/d-gcc-real.h 2005-11-28 05:17:52.000000000 +0100 +++ gdc-0.18/d/d-gcc-real.h 2006-03-12 15:16:26.000000000 +0100 @@ -2,6 +2,7 @@ #define GCC_DCMPLR_D_REAL_H struct real_value; +struct Type; struct real_t { // Including gcc/real.h presents too many problems, so @@ -53,10 +54,13 @@ bool operator!= (const real_t & r); //operator d_uns64(); // avoid bugs, but maybe allow operator bool() d_uns64 toInt(); + d_uns64 toInt(Type * real_type, Type * int_type); bool isZero(); bool isNegative(); bool floatCompare(int op, const real_t & r); - void format(char * buf, unsigned buf_size); + bool isIdenticalTo(const real_t & r) const; + void format(char * buf, unsigned buf_size) const; + void formatHex(char * buf, unsigned buf_size) const; // for debugging: bool isInf(); bool isNan(); diff -uNr gdc-0.17/d/d-glue.cc gdc-0.18/d/d-glue.cc --- gdc-0.17/d/d-glue.cc 2005-11-28 05:17:52.000000000 +0100 +++ gdc-0.18/d/d-glue.cc 2006-05-21 23:37:42.000000000 +0200 @@ -85,7 +85,8 @@ case TOKidentity: // fall through case TOKequal: is_compare = true; - out_code = EQ_EXPR; break; + out_code = EQ_EXPR; + break; case TOKnotidentity: // fall through case TOKnotequal: is_compare = true; @@ -247,8 +248,17 @@ if (is_compare) signed_compare_check(& e1, & e2); - return build(out_code, boolean_type_node, // exp->type->toCtype(), + tree t = build(out_code, boolean_type_node, // exp->type->toCtype(), e1, e2); +#if D_GCC_VER >= 40 + /* Need to use fold(). Otherwise, complex-var == complex-cst is not + gimplified correctly. */ + + if (COMPLEX_FLOAT_TYPE_P( TREE_TYPE( e1 )) || + COMPLEX_FLOAT_TYPE_P( TREE_TYPE( e2 ))) + t = fold(t); +#endif + return t; } static tree @@ -308,7 +318,10 @@ // _adCmp compares each element. If bitwise comparison is ok, // use memcmp. - if (elem_type->isfloating() || elem_type->isClassHandle()) { + if (elem_type->isfloating() || elem_type->isClassHandle() || + elem_type->ty == Tsarray || elem_type->ty == Tarray || + elem_type->ty == Tstruct) + { tree args[3] = { irs->rawArray(e1), irs->rawArray(e2), @@ -362,13 +375,13 @@ return convert(type->toCtype(), result); } else { - Array args; - args.push(e1); - args.push(e2); - tree result = irs->libCall(LIBCALL_ADEQBIT, & args); + tree args[2]; + args[0] = e1->implicitCastTo(Type::tbit->arrayOf())->toElem(irs); + args[1] = e2->implicitCastTo(Type::tbit->arrayOf())->toElem(irs); + tree result = irs->libCall(LIBCALL_ADEQBIT, 2, args); if (op == TOKnotequal) - result = build1(TRUTH_NOT_EXPR, type->toCtype(), result); - return result; + result = build1(TRUTH_NOT_EXPR, boolean_type_node, result); + return convert(type->toCtype(), result); } } else { // Taarray case not defined in spec, probably a library call %% really should assert again tgus @@ -380,14 +393,16 @@ InExp::toElem(IRState * irs) { Type * e2_base_type = e2->type->toBasetype(); + AddrOfExpr aoe; assert( e2_base_type->ty == Taarray ); tree args[3]; Type * key_type = ((TypeAArray *) e2_base_type)->key->toBasetype(); args[0] = irs->rawArray(e2); args[1] = irs->typeinfoReference(key_type); - args[2] = irs->convertTo( e1, key_type ); // %% vararg issues - return d_convert_basic(type->toCtype(), irs->libCall(LIBCALL_AAIN, 3, args)); + args[2] = aoe.set(irs, irs->convertTo( e1, key_type ) ); + return d_convert_basic(type->toCtype(), + aoe.finish(irs, irs->libCall(LIBCALL_AAINP, 3, args) )); } elem * @@ -410,19 +425,22 @@ switch (elem_type->ty) { case Tvoid: - case Tchar: - case Tuns8: lib_call = LIBCALL_ADCMPCHAR; break; case Tbit: lib_call = LIBCALL_ADCMPBIT; break; default: + // Tuns8, Tchar, Tbool + if (elem_type->size() == 1 && elem_type->isscalar() && + elem_type->isunsigned()) + lib_call = LIBCALL_ADCMPCHAR; + else { args[2] = irs->typeinfoReference(elem_type); n_args = 3; + lib_call = LIBCALL_ADCMP; } - lib_call = LIBCALL_ADCMP; break; } @@ -462,7 +480,7 @@ } } -tree +static tree make_math_op(TOK op, tree e1, Type * e1_type, tree e2, Type * e2_type, Type * exp_type, IRState * irs) { // Integral promotions have already been done in the front end @@ -591,17 +609,7 @@ static tree one_elem_array(IRState * irs, Expression * value, tree & var_decl_out) { - // don't want pushdecl - // var_decl_out = irs->localVar(elem->type); - - tree v = build_decl(VAR_DECL, NULL_TREE, value->type->toCtype()); - - DECL_CONTEXT( v ) = irs->getLocalContext(); - DECL_ARTIFICIAL( v ) = 1; - DECL_INITIAL( v ) = value->toElem(irs); - - var_decl_out = v; - + tree v = irs->maybeExprVar(value->toElem(irs), & var_decl_out); return irs->darrayVal(value->type->arrayOf(), 1, irs->addressOf(v)); } @@ -612,7 +620,7 @@ Type * tb2 = e2->type->toBasetype(); Type * elem_type; - tree args[4]; + tree args[6]; tree array_exp[2] = { NULL_TREE, NULL_TREE }; tree elem_var = NULL_TREE; tree result; @@ -643,11 +651,26 @@ array_exp[1] = irs->rawArray(e2); if (elem_type->ty != Tbit) { - args[0] = irs->integerConstant(elem_type->size(), Type::tuns32); // new IntegerExp(loc, e1->type->next->size(), Type::tuns32); - args[1] = irs->integerConstant(2, Type::tuns32); // new IntegerExp(loc, 2, Type::tuns32); - args[2] = array_exp[0]; - args[3] = array_exp[1]; - result = irs->libCall(LIBCALL_ARRAYCATN, 4, args, type->toCtype()); + unsigned n_args; + args[0] = irs->integerConstant(elem_type->size(), Type::tsize_t); + args[1] = irs->integerConstant(2, Type::tsize_t); + if (irs->splitDynArrayVarArgs) + { + n_args = 6; + array_exp[0] = irs->maybeMakeTemp(array_exp[0]); + array_exp[1] = irs->maybeMakeTemp(array_exp[1]); + args[2] = irs->darrayLenRef(array_exp[0]); + args[3] = irs->darrayPtrRef(array_exp[0]); + args[4] = irs->darrayLenRef(array_exp[1]); + args[5] = irs->darrayPtrRef(array_exp[1]); + } + else + { + n_args = 4; + args[2] = array_exp[0]; + args[3] = array_exp[1]; + } + result = irs->libCall(LIBCALL_ARRAYCATN, n_args, args, type->toCtype()); } else { args[0] = array_exp[0]; args[1] = array_exp[1]; @@ -803,6 +826,12 @@ tree lhs = chain_cvt(tgt, e1_to_use->type, lhs_casts, irs); Type * src_type = lhs_type; + { + /* Determined the correct combined type from BinExp::typeCombine. */ + TY ty = (TY) Type::impcnvResult[lhs_type->toBasetype()->ty][exp->e2->type->toBasetype()->ty]; + if (ty != Terror) + src_type = Type::basic[ty]; + } tree src = make_math_op(out_code, lhs, lhs_type, exp->e2->toElem(irs), exp->e2->type, src_type, irs); @@ -836,9 +865,10 @@ tree args[3]; Type * elem_type = e1->type->toBasetype()->next->toBasetype(); //Expression * size_exp = new IntegerExp(loc, elem_type->size(), Type::tuns32); - tree size_exp = irs->integerConstant(elem_type->size(), Type::tuns32); + tree size_exp = irs->integerConstant(elem_type->size(), Type::tsize_t); LibCall lib_call; int n_args; + AddrOfExpr aoe; args[0] = irs->addressOf( irs->toElemLvalue(e1) ); if (elem_type->ty != Tbit) { @@ -846,8 +876,8 @@ if (elem_type->equals(e2->type->toBasetype())) { // append an element args[1] = size_exp; - args[2] = e2->toElem(irs); - lib_call = LIBCALL_ARRAYAPPENDC; + args[2] = aoe.set(irs, e2->toElem(irs) ); + lib_call = LIBCALL_ARRAYAPPENDCP; } else { // append an array args[1] = irs->rawArray(e2); @@ -864,7 +894,7 @@ lib_call = LIBCALL_ARRAYAPPENDB; } } - return irs->libCall(lib_call, n_args, args, type->toCtype()); + return aoe.finish(irs, irs->libCall(lib_call, n_args, args, type->toCtype())); } elem * @@ -907,9 +937,7 @@ // build(NE_EXPR, boolean_type_node, integer_zero_node, count_var)); irs->exitIfFalse( build(NE_EXPR, boolean_type_node, integer_zero_node, count_var) ); - irs->doExp( build(MODIFY_EXPR, void_type_node, - build1(INDIRECT_REF, TREE_TYPE(TREE_TYPE(ptr_var)), ptr_var), - in_val) ); + irs->doExp( build(MODIFY_EXPR, void_type_node, irs->indirect(ptr_var), in_val) ); irs->doExp( build(MODIFY_EXPR, void_type_node, ptr_var, build(PLUS_EXPR, TREE_TYPE(ptr_var), ptr_var, TYPE_SIZE_UNIT(TREE_TYPE(TREE_TYPE(ptr_var))))) ); @@ -926,27 +954,30 @@ // First, handle special assignment semantics if (e1->op == TOKarraylength) { // Assignment to an array's length property; resize the array. - - Expression * array_exp_1 = ((ArrayLengthExp *) e1)->e1; - Expression * array_exp = new AddrExp(loc, array_exp_1); - array_exp->type = array_exp_1->type->pointerTo(); + + tree array_exp; + Type * array_type; + Type * elem_type; + { + Expression * ae = ((ArrayLengthExp *) e1)->e1; + array_type = ae->type; + elem_type = ae->type->toBasetype()->next->toBasetype(); + array_exp = irs->addressOf( ae->toElem( irs )); + } - Type * elem_type = array_exp_1->type->toBasetype()->next; - Array args; + tree args[3]; tree result; if (! elem_type->isbit()) { - args.setDim(3); - args.data[0] = e2; - args.data[1] = new IntegerExp(loc, elem_type->size(), Type::tuns32); - args.data[2] = array_exp; - result = irs->libCall(LIBCALL_ARRAYSETLENGTH, & args, - array_exp_1->type->toCtype()); - } else { - args.setDim(2); - args.data[0] = e2; - args.data[1] = array_exp; - result = irs->libCall(LIBCALL_ARRAYSETLENGTH_B, & args); + args[0] = irs->convertTo(e2, Type::tsize_t); + args[1] = irs->integerConstant(elem_type->size(), Type::tsize_t); + args[2] = array_exp; + + result = irs->libCall(LIBCALL_ARRAYSETLENGTH, 3, args); + } else { + args[0] = irs->convertTo(e2, Type::tsize_t); + args[1] = array_exp; + result = irs->libCall(LIBCALL_ARRAYSETLENGTH_B, 2, args); } // the libcall actually returns a whole new dynamic array.., but also // modifies the array.. @@ -1108,19 +1139,21 @@ return aryscp.finish( irs->arrayElemRef( this, & aryscp ) ); } else { Type * key_type = ((TypeAArray *) array_type)->key->toBasetype(); + AddrOfExpr aoe; tree args[4]; tree t; args[0] = e1->toElem(irs); args[1] = irs->typeinfoReference(key_type); - args[2] = irs->integerConstant( array_type->next->size(), Type::tuns32 ); - args[3] = irs->convertTo( e2, key_type ); // %% vararg issues - t = irs->libCall(LIBCALL_AAGETRVALUE, 4, args, type->pointerTo()->toCtype()); + args[2] = irs->integerConstant( array_type->next->size(), Type::tsize_t ); + args[3] = aoe.set(irs, irs->convertTo( e2, key_type ) ); + t = irs->libCall(LIBCALL_AAGETRVALUEP, 4, args, type->pointerTo()->toCtype()); + t = aoe.finish(irs, t); if (global.params.useArrayBounds) { t = save_expr(t); t = build(COND_EXPR, TREE_TYPE(t), t, t, irs->assertCall(loc, LIBCALL_ARRAY_BOUNDS)); } - t = build1(INDIRECT_REF, type->toCtype(), t); + t = irs->indirect(t, type->toCtype()); return t; } } @@ -1182,7 +1215,7 @@ orig_array_expr = irs->maybeMakeTemp( orig_array_expr ); // specs don't say bounds if are checked for error or clipped to current size - // This line allow non-Tarray types + // Get the data pointer for static and dynamic arrays orig_pointer_expr = irs->convertTo(orig_array_expr, orig_array_type, orig_array_type->next->pointerTo()); @@ -1249,7 +1282,7 @@ } final_ptr_expr = irs->pointerIntSum(irs->pvoidOkay(final_ptr_expr), lwr_tree); - TREE_TYPE( final_ptr_expr ) = TREE_TYPE( orig_pointer_expr ); + final_ptr_expr = irs->nop(final_ptr_expr, TREE_TYPE( orig_pointer_expr )); } return aryscp.finish( irs->darrayVal(type->toCtype(), final_len_expr, final_ptr_expr) ); @@ -1261,35 +1294,35 @@ return irs->convertTo(e1, to); } +static tree +make_aa_del(IRState * irs, Expression * e_array, Expression * e_index) +{ + tree args[3]; + Type * key_type = ((TypeAArray *) e_array->type->toBasetype())->key->toBasetype(); + AddrOfExpr aoe; + + args[0] = e_array->toElem(irs); // %% no rawArray since the type should already be correct + args[1] = irs->typeinfoReference(key_type); + args[2] = aoe.set(irs, irs->convertTo( e_index, key_type )); + return aoe.finish(irs, irs->libCall(LIBCALL_AADELP, 3, args) ); +} + elem * DeleteExp::toElem(IRState* irs) { // Does this look like an associative array delete? - if (e1->op == TOKindex) { - switch (e1->type->toBasetype()->ty) { - /* - // DMD 0.126 allows these... - case Tclass: break; - case Tarray: break; - case Tpointer: break; - */ - default: - if (! global.params.useDeprecated) - error("delete aa[key] deprecated, use aa.remove(key)", e1->toChars()); - } + if (e1->op == TOKindex && + ((IndexExp*)e1)->e1->type->toBasetype()->ty == Taarray) { + + if (! global.params.useDeprecated) + error("delete aa[key] deprecated, use aa.remove(key)", e1->toChars()); Expression * e_array = ((BinExp *) e1)->e1; Expression * e_index = ((BinExp *) e1)->e2; + // Check that the array is actually an associative array - if (e_array->type->toBasetype()->ty == Taarray) { - // %% convert to void or cast void... and elesewhere - tree args[3]; - Type * key_type = ((TypeAArray *) e_array->type->toBasetype())->key->toBasetype(); - args[0] = e_array->toElem(irs); // %% no rawArray since the type should already be correct - args[1] = irs->typeinfoReference(key_type); - args[2] = irs->convertTo( e_index, key_type ); // %% vararg issues - return irs->libCall(LIBCALL_AADEL, 3, args); - } + if (e_array->type->toBasetype()->ty == Taarray) + return make_aa_del(irs, e_array, e_index); } // Otherwise, this is normal delete @@ -1313,15 +1346,10 @@ { Expression * e_array = e1; Expression * e_index = e2; + // Check that the array is actually an associative array if (e_array->type->toBasetype()->ty == Taarray) { - // %% convert to void or cast void... and elesewhere - tree args[3]; - Type * key_type = ((TypeAArray *) e_array->type->toBasetype())->key->toBasetype(); - args[0] = e_array->toElem(irs); // %% no rawArray since the type should already be correct - args[1] = irs->typeinfoReference(key_type); - args[2] = irs->convertTo( e_index, key_type ); // %% vararg issues - return irs->libCall(LIBCALL_AADEL, 3, args); + return make_aa_del(irs, e_array, e_index); } else { error("%s is not an associative array", e_array->toChars()); return error_mark_node; @@ -1401,18 +1429,15 @@ field->type->equals(this->type)) { if (rec_tree == error_mark_node) return error_mark_node; // backend will ICE otherwise - - //return build(COMPONENT_REF, type->toCtype(), - // rec_tree, field->toSymbol()->Stree); - return irs->component(type->toCtype(), - rec_tree, field->toSymbol()->Stree); + return irs->nop(irs->component(rec_tree, field->toSymbol()->Stree), + type->toCtype()); } else if (field->offset > the_offset) { break; } } } - tree e = build1(INDIRECT_REF, type->toCtype(), e1->toElem(irs)); + tree e = irs->indirect(e1->toElem(irs), type->toCtype()); if (irs->inVolatile()) TREE_THIS_VOLATILE( e ) = 1; return e; @@ -1421,11 +1446,7 @@ elem * AddrExp::toElem(IRState * irs) { - // %% check for &array[index] -> array + index ? - - tree t = irs->addressOf(e1->toElem(irs)); - TREE_TYPE(t) = type->toCtype(); // %% is this ever needed? - return t; + return irs->nop(irs->addressOf(e1->toElem(irs)), type->toCtype()); } elem * @@ -1446,7 +1467,7 @@ } elem * -DotTypeExp::toElem(IRState* irs) +DotTypeExp::toElem(IRState*) { // The only case in which this seems to be a valid expression is when // it is used to specify a non-virtual call ( SomeClass.func(...) ). @@ -1505,10 +1526,11 @@ } else if ( (var_decl = var->isVarDeclaration()) ) { tree this_tree = e1->toElem(irs); if ( obj_basetype_ty != Tstruct ) - this_tree = build1(INDIRECT_REF, TREE_TYPE(TREE_TYPE(this_tree)), this_tree); + this_tree = irs->indirect(this_tree); //return build(COMPONENT_REF, type->toCtype(), this_tree, var_decl->toSymbol()->Stree); - return irs->component(type->toCtype(), this_tree, var_decl->toSymbol()->Stree); + return irs->nop(irs->component(this_tree, var_decl->toSymbol()->Stree), + type->toCtype()); } else { // error below } @@ -1598,9 +1620,6 @@ Type * func_type = type->toBasetype(); - if (func_type->ty == Tpointer) - func_type = func_type->next; - switch (func_type->toBasetype()->ty) { case Tfunction: return irs->addressOf(fd); @@ -1638,7 +1657,7 @@ VarExp::toElem(IRState* irs) { if (var->storage_class & STCfield) { - error("Need 'this' to access member %s", var->ident->string); + /*::*/error("Need 'this' to access member %s", var->ident->string); return error_mark_node; } @@ -1647,7 +1666,7 @@ tree e = var->toSymbol()->Stree; if ( irs->isDeclarationReferenceType(var) ) { - e = build1(INDIRECT_REF, var->type->toCtype(), e); + e = irs->indirect(e, var->type->toCtype()); if (irs->inVolatile()) { TREE_THIS_VOLATILE(e) = 1; } @@ -1655,7 +1674,7 @@ if (irs->inVolatile()) { e = irs->addressOf(e); TREE_THIS_VOLATILE(e) = 1; - e = build1(INDIRECT_REF, TREE_TYPE(TREE_TYPE(e)), e); + e = irs->indirect(e); TREE_THIS_VOLATILE(e) = 1; } } @@ -1702,7 +1721,7 @@ new_call = save_expr( new_call ); // copy memory... setup_exp = build(MODIFY_EXPR, rec_type, - build1(INDIRECT_REF, rec_type, new_call ), + irs->indirect(new_call, rec_type), class_type->sym->toInitializer()->Stree); } else { tree arg = irs->addressOf( class_type->sym->toSymbol()->Stree ); @@ -1730,17 +1749,9 @@ new_call = save_expr( new_call ); setup_exp = irs->maybeCompound(setup_exp, build(MODIFY_EXPR, TREE_TYPE(vthis_field), - irs->component( build1(INDIRECT_REF, rec_type, new_call ), + irs->component( irs->indirect(new_call, rec_type), vthis_field ), vthis_value)); - /* - setup_exp = irs->maybeCompound(setup_exp, - build(MODIFY_EXPR, TREE_TYPE(vthis_field), - build(COMPONENT_REF, TREE_TYPE(vthis_field), - build1(INDIRECT_REF, rec_type, new_call ), - vthis_field), - vthis_value)); - */ } new_call = irs->maybeCompound(setup_exp, new_call); @@ -1767,8 +1778,8 @@ tree final_length = orig_length; tree final_size = NULL_TREE; tree final_init = NULL_TREE; - tree init_var = NULL_TREE; - unsigned multiple = 1; + AddrOfExpr aoe; + uhwint multiple = 1; if (elem_type->ty != Tbit) { if (elem_init_type->isZeroInit()) { @@ -1792,15 +1803,7 @@ } final_init = irs->convertForAssignment(elem_init_type->defaultInit(), elem_type); - if (TREE_CODE(final_init) != VAR_DECL) { - init_var = build_decl(VAR_DECL, NULL_TREE, elem_type->toCtype()); - DECL_CONTEXT(init_var) = irs->getLocalContext(); - DECL_ARTIFICIAL(init_var) = 1; - DECL_INITIAL(init_var) = final_init; - final_init = irs->addressOf(init_var); - } else { - final_init = irs->addressOf(final_init); - } + final_init = aoe.set(irs, final_init); lib_call = LIBCALL_NEWARRAYIP; } @@ -1829,10 +1832,7 @@ irs->darrayPtrRef(result)); } - if (init_var) - result = irs->binding(init_var, result); - - return result; + return aoe.finish(irs, result); } break; case Tpointer: @@ -1843,24 +1843,20 @@ if (allocator) { new_call = irs->call(allocator, newargs); } else { - Array built_new_args; - // there doesn't seem to be any simple allocation call... - // just need a wrapper around gc.alloc - built_new_args.reserve(2); - built_new_args.push( new IntegerExp( 1 )); - built_new_args.push( new IntegerExp(loc, object_type->size(), Type::tuns32 )); - new_call = irs->libCall(LIBCALL_NEW, & built_new_args); + tree args[2]; + args[0] = irs->integerConstant(1, Type::tsize_t); + args[1] = irs->integerConstant(object_type->size(), Type::tsize_t); + new_call = irs->libCall(LIBCALL_NEW, 2, args); new_call = irs->darrayPtrRef(new_call); } - new_call = build1(NOP_EXPR, base_type->toCtype(), new_call); + new_call = irs->nop(new_call, base_type->toCtype()); if ( ! object_type->isZeroInit() ) { // Save the result allocation call. new_call = save_expr( new_call ); - t = build1(INDIRECT_REF, TREE_TYPE(TREE_TYPE( new_call )), new_call); + t = irs->indirect(new_call); t = build(MODIFY_EXPR, TREE_TYPE(t), t, irs->convertForAssignment(object_type->defaultInit(), object_type) ); - //new_call = build1(ADDR_EXPR, type->toCtype(), new_call); - new_call = build(COMPOUND_EXPR, TREE_TYPE(new_call), t, new_call); + new_call = irs->compound(t, new_call); } return new_call; } @@ -2012,7 +2008,9 @@ { FILE *dump_file; int local_dump_flags; +#if 0 struct cgraph_node *cgn; +#endif /* Dump the C-specific tree IR. */ dump_file = dump_begin (TDI_original, &local_dump_flags); @@ -2079,7 +2077,7 @@ tree param_list; tree result_decl; - tree parm_decl; + tree parm_decl = NULL_TREE; tree block; #if D_NO_TRAMPOLINES tree static_chain_expr = NULL_TREE; @@ -2106,7 +2104,13 @@ TREE_STATIC( fn_decl ) = 1; - result_decl = build_decl( RESULT_DECL, NULL_TREE, type->next->toCtype() ); + { + Type * func_type = tintro ? tintro : type; + Type * ret_type = func_type->next->toBasetype(); + if (isMain() && ret_type->ty == Tvoid) + ret_type = Type::tint32; + result_decl = build_decl( RESULT_DECL, NULL_TREE, ret_type->toCtype() ); + } g.ofile->setDeclLoc(result_decl, this); DECL_RESULT( fn_decl ) = result_decl; DECL_CONTEXT( result_decl ) = fn_decl; @@ -2195,10 +2199,7 @@ Dsymbol * d = cd->toParent(); tree vthis_field = cd->vthis->toSymbol()->Stree; - t = irs->component( - build1(INDIRECT_REF, TREE_TYPE(TREE_TYPE(t)), t), - vthis_field); - + t = irs->component(irs->indirect(t), vthis_field); if (d->isFuncDeclaration()) { static_chain_expr = t; break; @@ -2390,6 +2391,12 @@ tree sl = alloc_stmt_list(); append_to_statement_list_force(t, & sl); TREE_OPERAND(body, 1) = sl; + } else if (! STATEMENT_LIST_HEAD(t)) { + /* For empty functions: Without this, there is a + segfault when inlined. Seen on build=ppc-linux but + not others (why?). */ + append_to_statement_list_force( + build1(RETURN_EXPR,void_type_node,NULL_TREE), & t); } } @@ -2405,8 +2412,9 @@ #else genericize_function (fn_decl); #endif - - g.ofile->outputFunction(this); + + if (! errorcount && ! global.errors) + g.ofile->outputFunction(this); #if D_GCC_VER < 40 //rest_of_compilation( fn_decl ); @@ -2483,12 +2491,15 @@ case Tcomplex32: return complex_float_type_node; case Tcomplex64: return complex_double_type_node; case Tcomplex80: return complex_long_double_type_node; - /* The following types copy an existing type so that they can have - unique names. Also need to change TYPE_MAIN_VARIANT so tree.c - functions don't use the original types for arrays, etc. */ + case Tbool: + if (int_size_in_bytes( boolean_type_node ) == 1) + return boolean_type_node; + // else, drop through case Tbit: - //ctype = copy_node(unsigned_intQI_type_node); // This is what DMD does - ctype = build_type_copy( unsigned_intQI_type_node ); + ctype = make_unsigned_type(1); + TREE_SET_CODE(ctype, BOOLEAN_TYPE); + assert(int_size_in_bytes( ctype ) == 1); + dkeep(ctype); return ctype; case Tchar: ctype = build_type_copy( unsigned_intQI_type_node ); @@ -2789,8 +2800,6 @@ BINFO_OFFSET (binfo) = size_zero_node; // %% type?, otherwize, integer_zero_node if (cls->baseClass) { - tree prot_tree; - #if D_GCC_VER < 40 BINFO_BASETYPES(binfo) = make_tree_vec(1); BINFO_BASETYPE(binfo, 0) = binfo_for(binfo, cls->baseClass); @@ -2801,6 +2810,8 @@ #if D_GCC_VER >= 40 #error update vector stuff #endif + tree prot_tree; + BINFO_BASEACCESSES(binfo) = make_tree_vec(1); switch ( ((BaseClass *) cls->baseclasses.data[0])->protection ) { case PROTpublic: @@ -2838,7 +2849,6 @@ make_tree_binfo(iface->baseclasses.dim) #endif ; - tree prot_tree; TREE_TYPE (binfo) = TREE_TYPE( iface->type->toCtype() ); // RECORD_TYPE, not REFERENCE_TYPE BINFO_INHERITANCE_CHAIN(binfo) = tgt_binfo; BINFO_OFFSET (binfo) = size_int(inout_offset * PTRSIZE); @@ -2863,6 +2873,7 @@ BINFO_BASE_APPEND(binfo, intfc_binfo_for(binfo, bc->base, inout_offset)); #endif #ifdef BINFO_BASEACCESSES + tree prot_tree; switch ( bc->protection ) { case PROTpublic: prot_tree = access_public_node; @@ -3114,6 +3125,12 @@ } void +OnScopeStatement::toIR(IRState *) +{ + // nothing (?) +} + +void WithStatement::toIR(IRState * irs) { if (wthis) { @@ -3239,7 +3256,12 @@ if (exp) { if (exp->type->toBasetype()->ty != Tvoid) { // %% == Type::tvoid ? FuncDeclaration * func = irs->func; - Type * ret_type = func->type->next; + Type * ret_type = func->tintro ? + func->tintro->next : func->type->next; + + if (func->isMain() && ret_type->toBasetype()->ty == Tvoid) + ret_type = Type::tint32; + tree result_decl = DECL_RESULT( irs->func->toSymbol()->Stree ); tree result_assign = build ( MODIFY_EXPR, TREE_TYPE( result_decl ), result_decl, @@ -3355,6 +3377,10 @@ void IfStatement::toIR(IRState * irs) { + if (match) { + irs->startScope(); + irs->emitLocalVar(match); + } irs->startCond(this, condition); if (ifbody) ifbody->toIR( irs ); @@ -3363,6 +3389,8 @@ elsebody->toIR ( irs ); } irs->endCond(); + if (match) + irs->endScope(); } void @@ -3422,7 +3450,8 @@ iter_init_expr = irs->addressOf( aggr_expr ); // Type needs to be pointer-to-element to get pointerIntSum // to work - TREE_TYPE(iter_init_expr) = agg_type->next->pointerTo()->toCtype(); + iter_init_expr = irs->nop(iter_init_expr, + agg_type->next->pointerTo()->toCtype()); } else { bound_expr = irs->darrayLenRef( aggr_expr ); iter_init_expr = irs->darrayPtrRef( aggr_expr ); @@ -3441,7 +3470,7 @@ if ( iter_decl != value->toSymbol()->Stree ) { // %% check.. irs->doExp( build(MODIFY_EXPR, void_type_node, value->toSymbol()->Stree, - build1(INDIRECT_REF, TREE_TYPE(TREE_TYPE(iter_decl)), iter_decl)) ); + irs->indirect(iter_decl)) ); } if (body) body->toIR( irs ); diff -uNr gdc-0.17/d/d-lang.cc gdc-0.18/d/d-lang.cc --- gdc-0.17/d/d-lang.cc 2005-11-27 17:28:26.000000000 +0100 +++ gdc-0.18/d/d-lang.cc 2006-05-21 23:37:42.000000000 +0200 @@ -128,6 +128,7 @@ */ +static const char * iprefix; static bool std_inc; // %%FIX: find a place for this static const char * fonly_arg; @@ -171,7 +172,9 @@ flag_exceptions = 1; // extra D-specific options + gen.splitDynArrayVarArgs = true; gen.emitTemplates = TEauto; + gen.useBuiltins = true; std_inc = true; #if D_GCC_VER >= 34 @@ -233,6 +236,16 @@ } } +static char * +prefixed_path(const char * path) +{ + // based on c-incpath.c + size_t len = cpp_GCC_INCLUDE_DIR_len; + if (iprefix && len != 0 && ! strncmp(path, cpp_GCC_INCLUDE_DIR, len)) + return concat(iprefix, path + len, NULL); + else + return xstrdup(path); +} #if D_GCC_VER == 33 static const char * @@ -245,6 +258,7 @@ Type::init(); Id::initialize(); Module::init(); + initPrecedence(); gcc_d_backend_init(); real_t::init(); @@ -285,16 +299,30 @@ VersionCondition::addPredefinedGlobalIdent("GNU_LongDouble128"); #endif - if (d_have_inline_asm()) + if (d_have_inline_asm() && strcmp(D_CPU_VERSYM, "X86") == 0) + { VersionCondition::addPredefinedGlobalIdent("D_InlineAsm"); + VersionCondition::addPredefinedGlobalIdent("D_InlineAsm_X86"); + } + + /* Setting global.params.cov forces module info generation which is + not needed for thee GCC coverage implementation. Instead, just + test flag_test_coverage while leaving global.params.cov unset. */ + //if (global.params.cov) + if (flag_test_coverage) + VersionCondition::addPredefinedGlobalIdent("D_Coverage"); VersionCondition::addPredefinedGlobalIdent("all"); // %%TODO: front or back? if (std_inc) { - global.params.imppath->insert(0, xstrdup(D_PHOBOS_DIR)); - global.params.imppath->insert(0, xstrdup(D_PHOBOS_TARGET_DIR)); + global.params.imppath->insert(0, prefixed_path(D_PHOBOS_DIR)); + global.params.imppath->insert(0, prefixed_path(D_PHOBOS_TARGET_DIR)); + /* + global.params.imppath->insert(0, D_PHOBOS_DIR); + global.params.imppath->insert(0, D_PHOBOS_TARGET_DIR); + */ } if (global.params.imppath) @@ -370,6 +398,9 @@ OPT_fdebug, OPT_fdebug_, OPT_fdebug_c, + OPT_fintfc, + OPT_fintfc_dir_, + OPT_fintfc_file_, OPT_fdoc, OPT_fdoc_dir_, OPT_fdoc_file_, @@ -379,8 +410,10 @@ OPT_fonly_, OPT_nostdinc, OPT_fdump_source, + OPT_fbuiltin, OPT_fsigned_char, OPT_funsigned_char, + OPT_iprefix, OPT_Wall, OPT_Wsign_compare }; @@ -459,6 +492,19 @@ case OPT_fdebug_c: strcpy(lang_name, value ? "GNU C" : "GNU D"); break; +#ifdef _DH + case OPT_fintfc: + global.params.doHdrGeneration = value; + break; + case OPT_fintfc_dir_: + global.params.doHdrGeneration = 1; + global.params.hdrdir = xstrdup(arg); + break; + case OPT_fintfc_file_: + global.params.doHdrGeneration = 1; + global.params.hdrname = xstrdup(arg); + break; +#endif case OPT_fdoc: global.params.doDocComments = value; break; @@ -494,7 +540,10 @@ } break; case OPT_fonly_: - fonly_arg = arg; + fonly_arg = xstrdup(arg); + break; + case OPT_iprefix: + iprefix = xstrdup(arg); break; case OPT_nostdinc: std_inc = false; @@ -502,6 +551,9 @@ case OPT_fdump_source: global.params.dump_source = value; break; + case OPT_fbuiltin: + gen.useBuiltins = value; + break; case OPT_fsigned_char: case OPT_funsigned_char: // ignored @@ -561,6 +613,12 @@ d_handle_option(OPT_fdebug_, p_arg + 6, value); else if (strcmp(p_arg, "debug") == 0) d_handle_option(OPT_fdebug, p_arg + 5, value); + else if (strcmp(p_arg, "intfc") == 0) + d_handle_option(OPT_fintfc, NULL, value); + else if (strncmp(p_arg, "intfc-dir=", 10) == 0) + d_handle_option(OPT_fintfc_dir_, p_arg + 10, value); + else if (strncmp(p_arg, "intfc-file=", 11) == 0) + d_handle_option(OPT_fintfc_file_, p_arg + 11, value); else if (strcmp(p_arg, "doc") == 0) d_handle_option(OPT_fdoc, NULL, value); else if (strncmp(p_arg, "doc-dir=", 8) == 0) @@ -584,9 +642,17 @@ d_handle_option(OPT_fonly_, p_arg + 5, value); else if (strcmp(p_arg, "dump-source") == 0) d_handle_option(OPT_fdump_source, NULL, value); + else if (strcmp(p_arg, "builtin") == 0) + d_handle_option(OPT_fbuiltin, NULL, value); else return 0; return 1; + } else if (strcmp(p_arg, "-iprefix") == 0) { + d_handle_option(OPT_iprefix, argv[1], 0); + return 2; + } else if (strcmp(p_arg, "-isystem") == 0) { + /* ignored */ + return 2; } else if (strcmp(p_arg, "-nostdinc") == 0) { d_handle_option(OPT_nostdinc, NULL, 0); return 1; @@ -713,7 +779,7 @@ gen.emitTemplates = (supports_one_only()) ? TEnormal : TEprivate; } global.params.symdebug = write_symbols != NO_DEBUG; - global.params.useInline = flag_inline_functions; + //global.params.useInline = flag_inline_functions; global.params.obj = ! flag_syntax_only; global.params.pic = flag_pic != 0; // Has no effect yet. gen.originalOmitFramePointer = flag_omit_frame_pointer; @@ -741,6 +807,7 @@ /* hack... */ Type::tbit->toCtype(); + Type::tbool->toCtype(); Type::tchar->toCtype(); Type::twchar->toCtype(); Type::tdchar->toCtype(); @@ -822,7 +889,7 @@ } id = new Identifier(name, 0); - Module * m = new Module(the_fname, id, global.params.doDocComments); + Module * m = new Module(the_fname, id, global.params.doDocComments, global.params.doHdrGeneration); if (! strcmp(in_fnames[i], input_filename)) an_output_module = m; modules.push(m); @@ -864,6 +931,26 @@ if (global.errors) goto had_errors; +#ifdef _DH + if (global.params.doHdrGeneration) + { + /* Generate 'header' import files. + * Since 'header' import files must be independent of command + * line switches and what else is imported, they are generated + * before any semantic analysis. + */ + for (i = 0; i < modules.dim; i++) + { + m = (Module *)modules.data[i]; + if (global.params.verbose) + fprintf(stderr, "import %s\n", m->toChars()); + m->genhdrfile(); + } + } + if (global.errors) + fatal(); +#endif + // Do semantic analysis for (i = 0; i < modules.dim; i++) { @@ -919,21 +1006,20 @@ g.irs = & gen; // needed for FuncDeclaration::toObjFile shouldDefer check // Generate output files - if (! flag_syntax_only) - for (i = 0; i < modules.dim; i++) - { - m = (Module *)modules.data[i]; - if (fonly_arg && m != an_output_module) - continue; - if (global.params.verbose) - fprintf(stderr, "code %s\n", m->toChars()); + for (i = 0; i < modules.dim; i++) + { + m = (Module *)modules.data[i]; + if (fonly_arg && m != an_output_module) + continue; + if (global.params.verbose) + fprintf(stderr, "code %s\n", m->toChars()); + if (! flag_syntax_only) m->genobjfile(); + if (! global.errors && ! errorcount) + { + if (global.params.doDocComments) + m->gendocfile(); } - if (! global.errors && ! errorcount) - { - //m->gensymfile(); - if (global.params.doDocComments) - m->gendocfile(); } #if D_GCC_VER == 33 @@ -1331,11 +1417,31 @@ return type; } +#if D_GCC_VER < 40 +#define TYPE_UNSIGNED TREE_UNSIGNED +#endif + /* Type promotion for variable arguments. */ tree d_type_promotes_to (tree type) { - return type; + /* Almost the same as c_type_promotes_to. This is needed varargs to work on + certain targets. */ + if (TYPE_MAIN_VARIANT (type) == float_type_node) + return double_type_node; + + // not quite the same as... if (c_promoting_integer_type_p (type)) + if (INTEGRAL_TYPE_P (type) && + (TYPE_PRECISION (type) < TYPE_PRECISION (integer_type_node)) ) + { + /* Preserve unsignedness if not really getting any wider. */ + if (TYPE_UNSIGNED (type) + && (TYPE_PRECISION (type) == TYPE_PRECISION (integer_type_node))) + return unsigned_type_node; + return integer_type_node; + } + + return type; } diff -uNr gdc-0.17/d/d-lang.h gdc-0.18/d/d-lang.h --- gdc-0.17/d/d-lang.h 2005-11-05 15:12:01.000000000 +0100 +++ gdc-0.18/d/d-lang.h 2006-05-13 15:24:34.000000000 +0200 @@ -151,6 +151,8 @@ extern tree d_unsigned_type(tree); extern tree d_signed_type(tree); +extern tree d_type_promotes_to(tree); + #if D_GCC_VER == 33 extern rtx d_expand_expr(tree, rtx, enum machine_mode, int); #else @@ -212,4 +214,11 @@ #define build_type_copy build_variant_type_copy #endif +typedef HOST_WIDE_INT hwint; +typedef unsigned HOST_WIDE_INT uhwint; + +#if D_GCC_VER < 40 +static inline tree build2(enum tree_code c, tree t, tree a, tree b) { return build(c, t, a, b); } +#endif + #endif diff -uNr gdc-0.17/d/dmd/access.c gdc-0.18/d/dmd/access.c --- gdc-0.17/d/dmd/access.c 2005-10-02 16:17:55.000000000 +0200 +++ gdc-0.18/d/dmd/access.c 2006-03-12 23:08:56.000000000 +0100 @@ -1,5 +1,5 @@ -// Copyright (c) 1999-2005 by Digital Mars +// Copyright (c) 1999-2006 by Digital Mars // All Rights Reserved // written by Walter Bright // www.digitalmars.com @@ -267,7 +267,8 @@ return 1; // Friends if both are in the same module - if (cd && toParent() == cd->toParent()) + //if (toParent() == cd->toParent()) + if (cd && getModule() == cd->getModule()) { #if LOG printf("\tin same module\n"); @@ -275,15 +276,6 @@ return 1; } - if (cd && cd->toParent() == this) - { -#if LOG - printf("\tcd is nested in this\n"); -#endif - return 1; - } - - #if LOG printf("\tnot friend\n"); #endif @@ -366,6 +358,13 @@ #endif return 1; } + if (!cd && getModule() == smember->getModule()) + { +#if LOG + printf("\tyes 3\n"); +#endif + return 1; + } } #if LOG printf("\tno\n"); diff -uNr gdc-0.17/d/dmd/aggregate.h gdc-0.18/d/dmd/aggregate.h --- gdc-0.17/d/dmd/aggregate.h 2005-10-13 03:06:51.000000000 +0200 +++ gdc-0.18/d/dmd/aggregate.h 2006-05-14 03:05:56.000000000 +0200 @@ -1,5 +1,5 @@ -// Copyright (c) 1999-2002 by Digital Mars +// Copyright (c) 1999-2005 by Digital Mars // All Rights Reserved // written by Walter Bright // www.digitalmars.com @@ -7,12 +7,6 @@ // in artistic.txt, or the GNU General Public License in gnu.txt. // See the included readme.txt for details. -/* NOTE: This file has been patched from the original DMD distribution to - work with the GDC compiler. - - Modified by David Friedman, October 2004 -*/ - #ifndef DMD_AGGREGATE_H #define DMD_AGGREGATE_H @@ -60,12 +54,11 @@ InvariantDeclaration *inv; // invariant NewDeclaration *aggNew; // allocator DeleteDeclaration *aggDelete; // deallocator -#ifdef IN_GCC +#ifdef IN_GCC Array methods; // flat list of all methods for debug information #endif - AggregateDeclaration(Loc loc, Identifier *id); void semantic2(Scope *sc); void semantic3(Scope *sc); @@ -113,7 +106,7 @@ StructDeclaration(Loc loc, Identifier *id); Dsymbol *syntaxCopy(Dsymbol *s); void semantic(Scope *sc); - void toCBuffer(OutBuffer *buf); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); char *mangle(); char *kind(); @@ -153,13 +146,14 @@ BaseClass(Type *type, enum PROT protection); int fillVtbl(ClassDeclaration *cd, Array *vtbl, int newinstance); - void copyBaseInterfaces(Array *); + void copyBaseInterfaces(BaseClasses *); }; #define CLASSINFO_SIZE 0x3C // value of ClassInfo.size struct ClassDeclaration : AggregateDeclaration { + static ClassDeclaration *object; static ClassDeclaration *classinfo; ClassDeclaration *baseClass; // NULL only if this is Object @@ -169,14 +163,14 @@ FuncDeclaration *staticDtor; Array vtbl; // Array of FuncDeclaration's making up the vtbl[] - Array baseclasses; // Array of BaseClass's; first is super, + BaseClasses baseclasses; // Array of BaseClass's; first is super, // rest are Interface's int interfaces_dim; BaseClass **interfaces; // interfaces[interfaces_dim] for this class // (does not include baseClass) - Array *vtblInterfaces; // array of base interfaces that have + BaseClasses *vtblInterfaces; // array of base interfaces that have // their own vtbl[] ClassInfoDeclaration *vclassinfo; // the ClassInfo object for this ClassDeclaration @@ -187,10 +181,10 @@ int isnested; // !=0 if is nested VarDeclaration *vthis; // 'this' parameter if this class is nested - ClassDeclaration(Loc loc, Identifier *id, Array *baseclasses); + ClassDeclaration(Loc loc, Identifier *id, BaseClasses *baseclasses); Dsymbol *syntaxCopy(Dsymbol *s); void semantic(Scope *sc); - void toCBuffer(OutBuffer *buf); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); int isBaseOf2(ClassDeclaration *cd); #define OFFSET_RUNTIME 0x76543210 @@ -209,7 +203,7 @@ PROT getAccess(Dsymbol *smember); // determine access to smember - void addLocalClass(Array *); + void addLocalClass(ClassDeclarations *); // Back end void toObjFile(); // compile to .obj file @@ -227,7 +221,7 @@ struct InterfaceDeclaration : ClassDeclaration { - InterfaceDeclaration(Loc loc, Identifier *id, Array *baseclasses); + InterfaceDeclaration(Loc loc, Identifier *id, BaseClasses *baseclasses); Dsymbol *syntaxCopy(Dsymbol *s); void semantic(Scope *sc); int isBaseOf(ClassDeclaration *cd, int *poffset); diff -uNr gdc-0.17/d/dmd/array.c gdc-0.18/d/dmd/array.c --- gdc-0.17/d/dmd/array.c 2005-05-29 23:09:19.000000000 +0200 +++ gdc-0.18/d/dmd/array.c 2006-03-12 23:08:56.000000000 +0100 @@ -1,5 +1,5 @@ -// Copyright (c) 1999-2003 by Digital Mars +// Copyright (c) 1999-2006 by Digital Mars // All Rights Reserved // written by Walter Bright // www.digitalmars.com @@ -7,12 +7,6 @@ // in artistic.txt, or the GNU General Public License in gnu.txt. // See the included readme.txt for details. -/* NOTE: This file has been patched from the original DMD distribution to - work with the GDC compiler. - - Modified by David Friedman, September 2004 -*/ - #include #include #include @@ -23,7 +17,9 @@ #include #endif +#if IN_GCC #include "gdc_alloca.h" +#endif #if _WIN32 #include diff -uNr gdc-0.17/d/dmd/arraytypes.h gdc-0.18/d/dmd/arraytypes.h --- gdc-0.17/d/dmd/arraytypes.h 1970-01-01 01:00:00.000000000 +0100 +++ gdc-0.18/d/dmd/arraytypes.h 2006-05-13 18:58:32.000000000 +0200 @@ -0,0 +1,38 @@ +// Copyright (c) 2006 by Digital Mars +// All Rights Reserved +// written by Walter Bright +// www.digitalmars.com +// License for redistribution is by either the Artistic License +// in artistic.txt, or the GNU General Public License in gnu.txt. +// See the included readme.txt for details. + +#ifndef DMD_ARRAYTYPES_H +#define DMD_ARRAYTYPES_H + +#ifdef __DMC__ +#pragma once +#endif /* __DMC__ */ + + +#include "root.h" + +struct Expression; +struct Statement; +struct BaseClass; +struct TemplateParameter; + +struct TemplateParameters : Array { }; + +struct Expressions : Array { }; + +struct Statements : Array { }; + +struct BaseClasses : Array { }; + +struct ClassDeclarations : Array { }; + +struct Dsymbols : Array { }; + +struct Objects : Array { }; + +#endif diff -uNr gdc-0.17/d/dmd/attrib.c gdc-0.18/d/dmd/attrib.c --- gdc-0.17/d/dmd/attrib.c 2005-11-28 05:17:52.000000000 +0100 +++ gdc-0.18/d/dmd/attrib.c 2006-05-14 04:21:51.000000000 +0200 @@ -1,5 +1,5 @@ -// Copyright (c) 1999-2005 by Digital Mars +// Copyright (c) 1999-2006 by Digital Mars // All Rights Reserved // written by Walter Bright // www.digitalmars.com @@ -7,12 +7,6 @@ // in artistic.txt, or the GNU General Public License in gnu.txt. // See the included readme.txt for details. -/* NOTE: This file has been patched from the original DMD distribution to - work with the GDC compiler. - - Modified by David Friedman, May 2005 -*/ - #include #include #include @@ -49,9 +43,10 @@ return decl; } -void AttribDeclaration::addMember(Scope *sc, ScopeDsymbol *sd) +int AttribDeclaration::addMember(Scope *sc, ScopeDsymbol *sd, int memnum) { unsigned i; + int m = 0; Array *d = include(sc, sd); if (d) @@ -60,9 +55,10 @@ { Dsymbol *s; s = (Dsymbol *)d->data[i]; - s->addMember(sc, sd); + m |= s->addMember(sc, sd, m | memnum); } } + return m; } void AttribDeclaration::semantic(Scope *sc) @@ -152,6 +148,8 @@ void AttribDeclaration::emitComment(Scope *sc) { + //printf("AttribDeclaration::emitComment(sc = %p)\n", sc); + /* If generating doc comment, skip this because if we're inside * a template, then include(NULL, NULL) will fail. */ @@ -216,16 +214,11 @@ return "attribute"; } -Dsymbol *AttribDeclaration::oneMember() +int AttribDeclaration::oneMember(Dsymbol **ps) { - Dsymbol *s; Array *d = include(NULL, NULL); - if (d && d->dim == 1) - { s = (Dsymbol *)d->data[0]; - return s->oneMember(); - } - return NULL; + return Dsymbol::oneMembers(d, ps); } void AttribDeclaration::checkCtorConstInit() @@ -247,7 +240,7 @@ /**************************************** */ -void AttribDeclaration::addLocalClass(Array *aclasses) +void AttribDeclaration::addLocalClass(ClassDeclarations *aclasses) { unsigned i; Array *d = include(NULL, NULL); @@ -263,7 +256,7 @@ } -void AttribDeclaration::toCBuffer(OutBuffer *buf) +void AttribDeclaration::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { if (decl) { @@ -275,7 +268,7 @@ Dsymbol *s = (Dsymbol *)decl->data[i]; buf->writestring(" "); - s->toCBuffer(buf); + s->toCBuffer(buf, hgs); } buf->writeByte('}'); } @@ -321,10 +314,40 @@ sc->stc = stc; } -void StorageClassDeclaration::toCBuffer(OutBuffer *buf) +void StorageClassDeclaration::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { - buf->writestring("BUG: storage class goes here"); // BUG - AttribDeclaration::toCBuffer(buf); + struct SCstring + { + int stc; + enum TOK tok; + }; + + static SCstring table[] = + { + { STCauto, TOKauto }, + { STCstatic, TOKstatic }, + { STCextern, TOKextern }, + { STCconst, TOKconst }, + { STCfinal, TOKfinal }, + { STCabstract, TOKabstract }, + { STCsynchronized, TOKsynchronized }, + { STCdeprecated, TOKdeprecated }, + { STCoverride, TOKoverride }, + }; + + int written = 0; + for (int i = 0; i < sizeof(table)/sizeof(table[0]); i++) + { + if (stc & table[i].stc) + { + if (written) + buf->writeByte(' '); + written = 1; + buf->writestring(Token::toChars(table[i].tok)); + } + } + + AttribDeclaration::toCBuffer(buf, hgs); } /********************************* LinkDeclaration ****************************/ @@ -387,7 +410,7 @@ } } -void LinkDeclaration::toCBuffer(OutBuffer *buf) +void LinkDeclaration::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { char *p; switch (linkage) @@ -401,9 +424,10 @@ assert(0); break; } - buf->writestring("extern "); + buf->writestring("extern ("); buf->writestring(p); - AttribDeclaration::toCBuffer(buf); + buf->writestring(") "); + AttribDeclaration::toCBuffer(buf, hgs); } char *LinkDeclaration::toChars() @@ -447,7 +471,7 @@ sc->protection = protection; } -void ProtDeclaration::toCBuffer(OutBuffer *buf) +void ProtDeclaration::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { char *p; switch (protection) @@ -462,7 +486,7 @@ break; } buf->writestring(p); - AttribDeclaration::toCBuffer(buf); + AttribDeclaration::toCBuffer(buf, hgs); } /********************************* AlignDeclaration ****************************/ @@ -502,10 +526,10 @@ } -void AlignDeclaration::toCBuffer(OutBuffer *buf) +void AlignDeclaration::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { - buf->printf("align %d", salign); - AttribDeclaration::toCBuffer(buf); + buf->printf("align (%d)", salign); + AttribDeclaration::toCBuffer(buf, hgs); } /********************************* AnonDeclaration ****************************/ @@ -611,10 +635,21 @@ } -void AnonDeclaration::toCBuffer(OutBuffer *buf) +void AnonDeclaration::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { buf->printf(isunion ? "union" : "struct"); - AttribDeclaration::toCBuffer(buf); + buf->writestring("\n{\n"); + if (decl) + { + for (unsigned i = 0; i < decl->dim; i++) + { + Dsymbol *s = (Dsymbol *)decl->data[i]; + + //buf->writestring(" "); + s->toCBuffer(buf, hgs); + } + } + buf->writestring("}\n"); } char *AnonDeclaration::kind() @@ -624,7 +659,7 @@ /********************************* PragmaDeclaration ****************************/ -PragmaDeclaration::PragmaDeclaration(Loc loc, Identifier *ident, Array *args, Array *decl) +PragmaDeclaration::PragmaDeclaration(Loc loc, Identifier *ident, Expressions *args, Array *decl) : AttribDeclaration(decl) { this->loc = loc; @@ -658,12 +693,12 @@ if (e->op == TOKstring) { StringExp *se = (StringExp *)e; - fprintf(stderr, "%.*s", se->len, se->string); + fprintf(stdmsg, "%.*s", se->len, se->string); } else error("string expected for message, not '%s'", e->toChars()); } - fprintf(stderr, "\n"); + fprintf(stdmsg, "\n"); } } else if (ident == Id::lib) @@ -680,6 +715,7 @@ error("string expected for library name, not '%s'", e->toChars()); } } +#if IN_GCC else if (ident == Id::GNU_asm) { if (! args || args->dim != 2) @@ -713,6 +749,7 @@ d->c_ident = Lexer::idPool((char*) s->string); } } +#endif else error("unrecognized pragma(%s)", ident->toChars()); @@ -727,6 +764,12 @@ } } +int PragmaDeclaration::oneMember(Dsymbol **ps) +{ + *ps = NULL; + return TRUE; +} + char *PragmaDeclaration::kind() { return "pragma"; @@ -750,7 +793,7 @@ } } -void PragmaDeclaration::toCBuffer(OutBuffer *buf) +void PragmaDeclaration::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { buf->printf("pragma(%s", ident->toChars()); if (args) @@ -759,11 +802,12 @@ { Expression *e = (Expression *)args->data[i]; - buf->printf(", %s", e->toChars()); + buf->writestring(", "); + e->toCBuffer(buf, hgs); } } buf->writestring(")"); - AttribDeclaration::toCBuffer(buf); + AttribDeclaration::toCBuffer(buf, hgs); } @@ -789,23 +833,32 @@ } -Dsymbol *ConditionalDeclaration::oneMember() +int ConditionalDeclaration::oneMember(Dsymbol **ps) { + //printf("ConditionalDeclaration::oneMember(), inc = %d\n", condition->inc); if (condition->inc) { Array *d = condition->include(NULL, NULL) ? decl : elsedecl; - if (d && d->dim == 1) - { Dsymbol *s = (Dsymbol *)d->data[0]; - return s->oneMember(); - } + return Dsymbol::oneMembers(d, ps); + } + *ps = NULL; + return TRUE; +} + +void ConditionalDeclaration::emitComment(Scope *sc) +{ + //printf("ConditionalDeclaration::emitComment(sc = %p)\n", sc); + if (condition->inc) + { + AttribDeclaration::emitComment(sc); } - return NULL; } // Decide if 'then' or 'else' code should be included Array *ConditionalDeclaration::include(Scope *sc, ScopeDsymbol *sd) { + //printf("ConditionalDeclaration::include()\n"); assert(condition); return condition->include(sc, sd) ? decl : elsedecl; } @@ -840,9 +893,9 @@ } } -void ConditionalDeclaration::toCBuffer(OutBuffer *buf) +void ConditionalDeclaration::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { - condition->toCBuffer(buf); + condition->toCBuffer(buf, hgs); if (decl || elsedecl) { buf->writenl(); @@ -855,7 +908,7 @@ Dsymbol *s = (Dsymbol *)decl->data[i]; buf->writestring(" "); - s->toCBuffer(buf); + s->toCBuffer(buf, hgs); } } buf->writeByte('}'); @@ -871,7 +924,7 @@ Dsymbol *s = (Dsymbol *)elsedecl->data[i]; buf->writestring(" "); - s->toCBuffer(buf); + s->toCBuffer(buf, hgs); } buf->writeByte('}'); } @@ -881,4 +934,78 @@ buf->writenl(); } +/***************************** StaticIfDeclaration ****************************/ + +StaticIfDeclaration::StaticIfDeclaration(Condition *condition, + Array *decl, Array *elsedecl) + : ConditionalDeclaration(condition, decl, elsedecl) +{ + //printf("StaticIfDeclaration::StaticIfDeclaration()\n"); + sd = NULL; + addisdone = 0; +} + + +Dsymbol *StaticIfDeclaration::syntaxCopy(Dsymbol *s) +{ + StaticIfDeclaration *dd; + + assert(!s); + dd = new StaticIfDeclaration(condition->syntaxCopy(), + Dsymbol::arraySyntaxCopy(decl), + Dsymbol::arraySyntaxCopy(elsedecl)); + return dd; +} + + +int StaticIfDeclaration::addMember(Scope *sc, ScopeDsymbol *sd, int memnum) +{ + /* This is deferred until semantic(), so that + * expressions in the condition can refer to declarations + * in the same scope, such as: + * + * template Foo(int i) + * { + * const int j = i + 1; + * static if (j == 3) + * const int k; + * } + */ + this->sd = sd; + int m = 0; + + if (memnum == 0) + { m = AttribDeclaration::addMember(sc, sd, memnum); + addisdone = 1; + } + return m; +} + + +void StaticIfDeclaration::semantic(Scope *sc) +{ + Array *d = include(sc, sd); + + //printf("\tStaticIfDeclaration::semantic '%s'\n",toChars()); + if (d) + { + if (!addisdone) + { AttribDeclaration::addMember(sc, sd, 1); + addisdone = 1; + } + + for (unsigned i = 0; i < d->dim; i++) + { + Dsymbol *s = (Dsymbol *)d->data[i]; + + s->semantic(sc); + } + } +} + +char *StaticIfDeclaration::kind() +{ + return "static if"; +} + diff -uNr gdc-0.17/d/dmd/attrib.h gdc-0.18/d/dmd/attrib.h --- gdc-0.17/d/dmd/attrib.h 2005-10-26 03:33:56.000000000 +0200 +++ gdc-0.18/d/dmd/attrib.h 2006-05-14 04:21:51.000000000 +0200 @@ -1,5 +1,5 @@ -// Copyright (c) 1999-2002 by Digital Mars +// Copyright (c) 1999-2006 by Digital Mars // All Rights Reserved // written by Walter Bright // www.digitalmars.com @@ -22,6 +22,9 @@ struct Initializer; struct Module; struct Condition; +#ifdef _DH +struct HdrGenState; +#endif /**************************************************************/ @@ -31,7 +34,7 @@ AttribDeclaration(Array *decl); virtual Array *include(Scope *sc, ScopeDsymbol *s); - void addMember(Scope *sc, ScopeDsymbol *s); + int addMember(Scope *sc, ScopeDsymbol *s, int memnum); void semantic(Scope *sc); void semantic2(Scope *sc); void semantic3(Scope *sc); @@ -39,10 +42,10 @@ void addComment(unsigned char *comment); void emitComment(Scope *sc); char *kind(); - Dsymbol *oneMember(); + int oneMember(Dsymbol **ps); void checkCtorConstInit(); - void addLocalClass(Array *); - void toCBuffer(OutBuffer *buf); + void addLocalClass(ClassDeclarations *); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); AttribDeclaration *isAttribDeclaration() { return this; } void toObjFile(); // compile to .obj file @@ -56,7 +59,7 @@ StorageClassDeclaration(unsigned stc, Array *decl); Dsymbol *syntaxCopy(Dsymbol *s); void semantic(Scope *sc); - void toCBuffer(OutBuffer *buf); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); }; struct LinkDeclaration : AttribDeclaration @@ -67,7 +70,7 @@ Dsymbol *syntaxCopy(Dsymbol *s); void semantic(Scope *sc); void semantic3(Scope *sc); - void toCBuffer(OutBuffer *buf); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); char *toChars(); }; @@ -78,7 +81,7 @@ ProtDeclaration(enum PROT p, Array *decl); Dsymbol *syntaxCopy(Dsymbol *s); void semantic(Scope *sc); - void toCBuffer(OutBuffer *buf); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); }; struct AlignDeclaration : AttribDeclaration @@ -88,7 +91,7 @@ AlignDeclaration(unsigned sa, Array *decl); Dsymbol *syntaxCopy(Dsymbol *s); void semantic(Scope *sc); - void toCBuffer(OutBuffer *buf); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); }; struct AnonDeclaration : AttribDeclaration @@ -98,18 +101,19 @@ AnonDeclaration(Loc loc, int isunion, Array *decl); Dsymbol *syntaxCopy(Dsymbol *s); void semantic(Scope *sc); - void toCBuffer(OutBuffer *buf); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); char *kind(); }; struct PragmaDeclaration : AttribDeclaration { - Array *args; // array of Expression's + Expressions *args; // array of Expression's - PragmaDeclaration(Loc loc, Identifier *ident, Array *args, Array *decl); + PragmaDeclaration(Loc loc, Identifier *ident, Expressions *args, Array *decl); Dsymbol *syntaxCopy(Dsymbol *s); void semantic(Scope *sc); - void toCBuffer(OutBuffer *buf); + int oneMember(Dsymbol **ps); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); char *kind(); void toObjFile(); // compile to .obj file }; @@ -121,10 +125,23 @@ ConditionalDeclaration(Condition *condition, Array *decl, Array *elsedecl); Dsymbol *syntaxCopy(Dsymbol *s); - Dsymbol *oneMember(); + int oneMember(Dsymbol **ps); + void emitComment(Scope *sc); Array *include(Scope *sc, ScopeDsymbol *s); void addComment(unsigned char *comment); - void toCBuffer(OutBuffer *buf); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); +}; + +struct StaticIfDeclaration : ConditionalDeclaration +{ + ScopeDsymbol *sd; + int addisdone; + + StaticIfDeclaration(Condition *condition, Array *decl, Array *elsedecl); + Dsymbol *syntaxCopy(Dsymbol *s); + int addMember(Scope *sc, ScopeDsymbol *s, int memnum); + void semantic(Scope *sc); + char *kind(); }; #endif /* DMD_ATTRIB_H */ diff -uNr gdc-0.17/d/dmd/cast.c gdc-0.18/d/dmd/cast.c --- gdc-0.17/d/dmd/cast.c 2005-11-28 05:17:52.000000000 +0100 +++ gdc-0.18/d/dmd/cast.c 2006-05-14 03:05:56.000000000 +0200 @@ -1,5 +1,5 @@ -// Copyright (c) 1999-2004 by Digital Mars +// Copyright (c) 1999-2006 by Digital Mars // All Rights Reserved // written by Walter Bright // www.digitalmars.com @@ -7,12 +7,6 @@ // in artistic.txt, or the GNU General Public License in gnu.txt. // See the included readme.txt for details. -/* NOTE: This file has been patched from the original DMD distribution to - work with the GDC compiler. - - Modified by David Friedman, September 2004 -*/ - #include #include @@ -49,7 +43,7 @@ if (e->op == TOKint64) return e->implicitCastTo(t); - fprintf(stderr, "warning - "); + fprintf(stdmsg, "warning - "); error("implicit conversion of expression (%s) of type %s to %s can cause loss of data", toChars(), type->toChars(), t->toChars()); } @@ -109,6 +103,7 @@ switch (ty) { case Tbit: + case Tbool: value &= 1; ty = Tint32; break; @@ -154,7 +149,8 @@ switch (toty) { case Tbit: - if (value & ~1) + case Tbool: + if ((value & 1) != value) goto Lno; goto Lyes; @@ -368,6 +364,35 @@ return result; } +int SymOffExp::implicitConvTo(Type *t) +{ +#if 0 + printf("SymOffExp::implicitConvTo(this=%s, type=%s, t=%s)\n", + toChars(), type->toChars(), t->toChars()); +#endif + int result; + + result = type->implicitConvTo(t); + //printf("\tresult = %d\n", result); + + if (result == MATCHnomatch) + { + // Look for pointers to functions where the functions are overloaded. + FuncDeclaration *f; + + t = t->toBasetype(); + if (type->ty == Tpointer && type->next->ty == Tfunction && + t->ty == Tpointer && t->next->ty == Tfunction) + { + f = var->isFuncDeclaration(); + if (f && f->overloadExactMatch(t->next)) + result = MATCHexact; + } + } + //printf("\tresult = %d\n", result); + return result; +} + int DelegateExp::implicitConvTo(Type *t) { #if 0 @@ -448,6 +473,29 @@ return e; } + +Expression *RealExp::castTo(Type *t) +{ + if (type->isreal() && t->isreal()) + type = t; + else if (type->isimaginary() && t->isimaginary()) + type = t; + else + return Expression::castTo(t); + return this; +} + + +Expression *ComplexExp::castTo(Type *t) +{ + if (type->iscomplex() && t->iscomplex()) + type = t; + else + return Expression::castTo(t); + return this; +} + + Expression *NullExp::castTo(Type *t) { Expression *e; Type *tb; @@ -479,7 +527,7 @@ Type *tb; int unique; - //printf("StringExp::castTo('%s')\n", string); + //printf("StringExp::castTo(%s) '%s'\n", t->toChars(), string); //if (((char*)string)[0] == 'd') *(char*)0=0; if (!committed && t->ty == Tpointer && t->next->ty == Tvoid) { @@ -620,6 +668,10 @@ break; default: + if (se->type->next->size() == tb->next->size()) + { se->type = t; + return se; + } goto Lcast; } } @@ -711,6 +763,44 @@ return e; } +Expression *SymOffExp::castTo(Type *t) +{ + Type *tb; + +#if 0 + printf("SymOffExp::castTo(this=%s, type=%s, t=%s)\n", + toChars(), type->toChars(), t->toChars()); +#endif + Expression *e = this; + + tb = t->toBasetype(); + type = type->toBasetype(); + if (tb != type) + { + // Look for pointers to functions where the functions are overloaded. + FuncDeclaration *f; + + if (type->ty == Tpointer && type->next->ty == Tfunction && + tb->ty == Tpointer && tb->next->ty == Tfunction) + { + f = var->isFuncDeclaration(); + if (f) + { + f = f->overloadExactMatch(tb->next); + if (f) + { + e = new SymOffExp(loc, f, 0); + e->type = t; + return e; + } + } + } + e = Expression::castTo(t); + } + e->type = t; + return e; +} + Expression *DelegateExp::castTo(Type *t) { Type *tb; @@ -719,6 +809,7 @@ toChars(), type->toChars(), t->toChars()); #endif Expression *e = this; + static char msg[] = "cannot form delegate due to covariant return type"; tb = t->toBasetype(); type = type->toBasetype(); @@ -734,15 +825,25 @@ { f = func->overloadExactMatch(tb->next); if (f) - { + { int offset; + if (f->tintro && f->tintro->next->isBaseOf(f->type->next, &offset) && offset) + error(msg); e = new DelegateExp(loc, e1, f); e->type = t; return e; } + if (func->tintro) + error(msg); } } e = Expression::castTo(t); } + else + { int offset; + + if (func->tintro && func->tintro->next->isBaseOf(func->type->next, &offset) && offset) + error(msg); + } e->type = t; return e; } @@ -1014,9 +1115,7 @@ else { Lincompatible: - error("incompatible types for ((%s) %s (%s)): '%s' and '%s'", - e1->toChars(), Token::toChars(op), e2->toChars(), - t1->toChars(), t2->toChars()); + incompatibleTypes(); } Lret: if (!type) @@ -1056,6 +1155,7 @@ case Tint16: case Tuns16: case Tbit: + case Tbool: case Tchar: case Twchar: e = e->castTo(Type::tint32); diff -uNr gdc-0.17/d/dmd/class.c gdc-0.18/d/dmd/class.c --- gdc-0.17/d/dmd/class.c 2005-10-13 03:06:51.000000000 +0200 +++ gdc-0.18/d/dmd/class.c 2006-05-14 04:21:51.000000000 +0200 @@ -1,6 +1,5 @@ - -// Copyright (c) 1999-2004 by Digital Mars +// Copyright (c) 1999-2006 by Digital Mars // All Rights Reserved // written by Walter Bright // www.digitalmars.com @@ -30,10 +29,13 @@ /********************************* ClassDeclaration ****************************/ ClassDeclaration *ClassDeclaration::classinfo; +ClassDeclaration *ClassDeclaration::object; -ClassDeclaration::ClassDeclaration(Loc loc, Identifier *id, Array *baseclasses) +ClassDeclaration::ClassDeclaration(Loc loc, Identifier *id, BaseClasses *baseclasses) : AggregateDeclaration(loc, id) { + static char msg[] = "only object.d can define this reserved class name"; + if (baseclasses) this->baseclasses = *baseclasses; baseClass = NULL; @@ -57,52 +59,99 @@ vtblsym = NULL; vclassinfo = NULL; - if (id == Id::__sizeof || id == Id::alignof) - error("illegal class name"); + if (id) + { // Look for special class names - // BUG: What if this is the wrong ClassInfo, i.e. it is nested? - if (!classinfo && id == Id::ClassInfo) - classinfo = this; + if (id == Id::__sizeof || id == Id::alignof || id == Id::mangleof) + error("illegal class name"); - // BUG: What if this is the wrong ModuleInfo, i.e. it is nested? - if (!Module::moduleinfo && id == Id::ModuleInfo) - Module::moduleinfo = this; + // BUG: What if this is the wrong TypeInfo, i.e. it is nested? + if (id->toChars()[0] == 'T') + { + if (id == Id::TypeInfo) + { if (Type::typeinfo) + Type::typeinfo->error(msg); + Type::typeinfo = this; + } - // BUG: What if this is the wrong TypeInfo, i.e. it is nested? - if (id && id->toChars()[0] == 'T') - { - if (!Type::typeinfo && id == Id::TypeInfo) - Type::typeinfo = this; + if (id == Id::TypeInfo_Class) + { if (Type::typeinfoclass) + Type::typeinfoclass->error(msg); + Type::typeinfoclass = this; + } - if (!Type::typeinfoclass && id == Id::TypeInfo_Class) - Type::typeinfoclass = this; + if (id == Id::TypeInfo_Struct) + { if (Type::typeinfostruct) + Type::typeinfostruct->error(msg); + Type::typeinfostruct = this; + } - if (!Type::typeinfostruct && id == Id::TypeInfo_Struct) - Type::typeinfostruct = this; + if (id == Id::TypeInfo_Typedef) + { if (Type::typeinfotypedef) + Type::typeinfotypedef->error(msg); + Type::typeinfotypedef = this; + } - if (!Type::typeinfotypedef && id == Id::TypeInfo_Typedef) - Type::typeinfotypedef = this; + if (id == Id::TypeInfo_Pointer) + { if (Type::typeinfopointer) + Type::typeinfopointer->error(msg); + Type::typeinfopointer = this; + } - if (!Type::typeinfopointer && id == Id::TypeInfo_Pointer) - Type::typeinfopointer = this; + if (id == Id::TypeInfo_Array) + { if (Type::typeinfoarray) + Type::typeinfoarray->error(msg); + Type::typeinfoarray = this; + } - if (!Type::typeinfoarray && id == Id::TypeInfo_Array) - Type::typeinfoarray = this; + if (id == Id::TypeInfo_StaticArray) + { //if (Type::typeinfostaticarray) + //Type::typeinfostaticarray->error(msg); + Type::typeinfostaticarray = this; + } - if (!Type::typeinfostaticarray && id == Id::TypeInfo_StaticArray) - Type::typeinfostaticarray = this; + if (id == Id::TypeInfo_AssociativeArray) + { if (Type::typeinfoassociativearray) + Type::typeinfoassociativearray->error(msg); + Type::typeinfoassociativearray = this; + } - if (!Type::typeinfoassociativearray && id == Id::TypeInfo_AssociativeArray) - Type::typeinfoassociativearray = this; + if (id == Id::TypeInfo_Enum) + { if (Type::typeinfoenum) + Type::typeinfoenum->error(msg); + Type::typeinfoenum = this; + } - if (!Type::typeinfoenum && id == Id::TypeInfo_Enum) - Type::typeinfoenum = this; + if (id == Id::TypeInfo_Function) + { if (Type::typeinfofunction) + Type::typeinfofunction->error(msg); + Type::typeinfofunction = this; + } - if (!Type::typeinfofunction && id == Id::TypeInfo_Function) - Type::typeinfofunction = this; + if (id == Id::TypeInfo_Delegate) + { if (Type::typeinfodelegate) + Type::typeinfodelegate->error(msg); + Type::typeinfodelegate = this; + } + } - if (!Type::typeinfodelegate && id == Id::TypeInfo_Delegate) - Type::typeinfodelegate = this; + if (id == Id::Object) + { if (object) + object->error(msg); + object = this; + } + + if (id == Id::ClassInfo) + { if (classinfo) + classinfo->error(msg); + classinfo = this; + } + + if (id == Id::ModuleInfo) + { if (Module::moduleinfo) + Module::moduleinfo->error(msg); + Module::moduleinfo = this; + } } com = 0; @@ -145,7 +194,7 @@ unsigned offset; //printf("ClassDeclaration::semantic(%s), type = %p, sizeok = %d, this = %p\n", toChars(), type, sizeok, this); - //printf("parent = %p, '%s'\n", sc->parent, sc->parent ? sc->parent->toChars() : ""); + //printf("\tparent = %p, '%s'\n", sc->parent, sc->parent ? sc->parent->toChars() : ""); //printf("sc->stc = %x\n", sc->stc); //{ static int n; if (++n == 20) *(char*)0=0; } @@ -281,6 +330,11 @@ TypeClass *tc; Type *bt; + if (!object) + { + error("missing or corrupt object.d"); + fatal(); + } bt = tbase->semantic(loc, sc)->toBasetype(); b = new BaseClass(bt, PROTpublic); baseclasses.shift(b); @@ -326,7 +380,7 @@ for (i = 0; i < members->dim; i++) { Dsymbol *s = (Dsymbol *)members->data[i]; - s->addMember(sc, this); + s->addMember(sc, this, 1); } /* If this is a nested class, add the hidden 'this' @@ -375,7 +429,7 @@ isdeprecated = 1; sc = sc->push(this); - sc->stc &= ~(STCauto | STCstatic | STCabstract); + sc->stc &= ~(STCauto | STCstatic | STCabstract | STCdeprecated); sc->parent = this; sc->inunion = 0; @@ -451,9 +505,9 @@ { //printf("Creating default this(){} for class %s\n", toChars()); ctor = new CtorDeclaration(0, 0, NULL, 0); - ctor->fbody = new CompoundStatement(0, new Array()); + ctor->fbody = new CompoundStatement(0, new Statements()); members->push(ctor); - ctor->addMember(sc, this); + ctor->addMember(sc, this, 1); *sc = scsave; sc->offset = structsize; ctor->semantic(sc); @@ -506,34 +560,33 @@ //printf("-ClassDeclaration::semantic(%s), type = %p\n", toChars(), type); } -void ClassDeclaration::toCBuffer(OutBuffer *buf) -{ int i; - int needcomma; - - buf->printf("%s %s", kind(), toChars()); - needcomma = 0; - if (baseClass) - { buf->printf(" : %s", baseClass->toChars()); - needcomma = 1; +void ClassDeclaration::toCBuffer(OutBuffer *buf, HdrGenState *hgs) +{ + if (!isAnonymous()) + { + buf->printf("%s ", kind()); + buf->writestring(toChars()); + if (baseclasses.dim) + buf->writestring(" : "); } - for (i = 0; i < baseclasses.dim; i++) + for (int i = 0; i < baseclasses.dim; i++) { BaseClass *b = (BaseClass *)baseclasses.data[i]; - if (needcomma) + if (i) buf->writeByte(','); - needcomma = 1; - buf->writestring(b->base->ident->toChars()); + //buf->writestring(b->base->ident->toChars()); + b->type->toCBuffer(buf, NULL, hgs); } buf->writenl(); buf->writeByte('{'); buf->writenl(); - for (i = 0; i < members->dim; i++) + for (int i = 0; i < members->dim; i++) { Dsymbol *s = (Dsymbol *)members->data[i]; buf->writestring(" "); - s->toCBuffer(buf); + s->toCBuffer(buf, hgs); } buf->writestring("}"); buf->writenl(); @@ -560,7 +613,7 @@ { if (!cd) return 0; - //printf("ClassDeclaration::isBaseOf(this = '%s', cd = '%s')\n", toChars(), cd->toChars()); + //printf("ClassDeclaration::isBaseOf2(this = '%s', cd = '%s')\n", toChars(), cd->toChars()); for (int i = 0; i < cd->baseclasses.dim; i++) { BaseClass *b = (BaseClass *)cd->baseclasses.data[i]; @@ -646,15 +699,21 @@ FuncDeclaration *ClassDeclaration::findFunc(Identifier *ident, TypeFunction *tf) { - unsigned i; + //printf("ClassDeclaration::findFunc(%s, %s) %s\n", ident->toChars(), tf->toChars(), toChars()); - for (i = 0; i < vtbl.dim; i++) + for (size_t i = 0; i < vtbl.dim; i++) { FuncDeclaration *fd = (FuncDeclaration *)vtbl.data[i]; + //printf("\t[%d] = %s\n", i, fd->toChars()); if (ident == fd->ident && - tf->equals(fd->type)) + //tf->equals(fd->type) + fd->type->covariant(tf) == 1 + ) + { //printf("\t\tfound\n"); return fd; + } + //else printf("\t\t%d\n", fd->type->covariant(tf)); } return NULL; @@ -663,7 +722,7 @@ void ClassDeclaration::interfaceSemantic(Scope *sc) { int i; - vtblInterfaces = new Array(); + vtblInterfaces = new BaseClasses(); vtblInterfaces->reserve(interfaces_dim); for (i = 0; i < interfaces_dim; i++) @@ -743,14 +802,14 @@ /**************************************** */ -void ClassDeclaration::addLocalClass(Array *aclasses) +void ClassDeclaration::addLocalClass(ClassDeclarations *aclasses) { aclasses->push(this); } /********************************* InterfaceDeclaration ****************************/ -InterfaceDeclaration::InterfaceDeclaration(Loc loc, Identifier *id, Array *baseclasses) +InterfaceDeclaration::InterfaceDeclaration(Loc loc, Identifier *id, BaseClasses *baseclasses) : ClassDeclaration(loc, id, baseclasses) { com = 0; @@ -880,7 +939,7 @@ for (i = 0; i < members->dim; i++) { Dsymbol *s = (Dsymbol *)members->data[i]; - s->addMember(sc, this); + s->addMember(sc, this, 1); } sc = sc->push(this); @@ -1082,7 +1141,7 @@ return result; } -void BaseClass::copyBaseInterfaces(Array *vtblInterfaces) +void BaseClass::copyBaseInterfaces(BaseClasses *vtblInterfaces) { //printf("+copyBaseInterfaces(), %s\n", base->toChars()); // if (baseInterfaces_dim) diff -uNr gdc-0.17/d/dmd/complex_t.h gdc-0.18/d/dmd/complex_t.h --- gdc-0.17/d/dmd/complex_t.h 2004-10-26 02:41:27.000000000 +0200 +++ gdc-0.18/d/dmd/complex_t.h 2006-03-12 15:16:26.000000000 +0100 @@ -46,6 +46,9 @@ } operator bool () { return re || im; } + + int operator == (complex_t y) { return re == y.re && im == y.im; } + int operator != (complex_t y) { return re != y.re || im != y.im; } }; inline complex_t operator * (long double x, complex_t y) { return complex_t(x) * y; } diff -uNr gdc-0.17/d/dmd/cond.c gdc-0.18/d/dmd/cond.c --- gdc-0.17/d/dmd/cond.c 2005-10-24 23:48:04.000000000 +0200 +++ gdc-0.18/d/dmd/cond.c 2006-05-13 21:05:42.000000000 +0200 @@ -19,6 +19,10 @@ #include "module.h" #include "template.h" #include "lexer.h" +#ifdef _DH +#include "mtype.h" +#include "scope.h" +#endif int findCondition(Array *ids, Identifier *ident) { @@ -103,7 +107,7 @@ return (inc == 1); } -void DebugCondition::toCBuffer(OutBuffer *buf) +void DebugCondition::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { if (ident) buf->printf("debug (%s)", ident->toChars()); @@ -190,7 +194,7 @@ return (inc == 1); } -void VersionCondition::toCBuffer(OutBuffer *buf) +void VersionCondition::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { if (ident) buf->printf("version (%s)", ident->toChars()); @@ -214,7 +218,13 @@ int StaticIfCondition::include(Scope *sc, ScopeDsymbol *s) { - //printf("StaticIfCondition::include()\n"); +#if 0 + printf("StaticIfCondition::include(sc = %p, s = %p)\n", sc, s); + if (s) + { + printf("\ts = '%s', kind = %s\n", s->toChars(), s->kind()); + } +#endif if (inc == 0) { if (!sc) @@ -225,7 +235,7 @@ } sc = sc->push(sc->scopesym); - sc->sd = s; + sc->sd = s; // s gets any addMember() sc->flags |= SCOPEstaticif; Expression *e = exp->semantic(sc); sc->pop(); @@ -243,10 +253,10 @@ return (inc == 1); } -void StaticIfCondition::toCBuffer(OutBuffer *buf) +void StaticIfCondition::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { buf->writestring("static if("); - exp->toCBuffer(buf); + exp->toCBuffer(buf, hgs); buf->writeByte(')'); } @@ -299,14 +309,14 @@ MATCH m; TemplateTypeParameter tp(loc, id, NULL, NULL); - Array parameters; + TemplateParameters parameters; parameters.setDim(1); parameters.data[0] = (void *)&tp; Array dedtypes; dedtypes.setDim(1); - m = targ->deduceType(tspec, ¶meters, &dedtypes); + m = targ->deduceType(NULL, tspec, ¶meters, &dedtypes); if (m == MATCHnomatch || (m != MATCHexact && tok == TOKequal)) inc = 2; @@ -320,7 +330,7 @@ s->semantic(sc); sc->insert(s); if (sd) - s->addMember(sc, sd); + s->addMember(sc, sd, 1); } } else if (id) @@ -331,7 +341,7 @@ s->semantic(sc); sc->insert(s); if (sd) - s->addMember(sc, sd); + s->addMember(sc, sd, 1); inc = 1; } else if (tspec) @@ -361,17 +371,17 @@ return (inc == 1); } -void IftypeCondition::toCBuffer(OutBuffer *buf) +void IftypeCondition::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { buf->writestring("iftype("); - targ->toCBuffer(buf, id); + targ->toCBuffer(buf, id, hgs); if (tspec) { if (tok == TOKcolon) buf->writestring(" : "); else buf->writestring(" == "); - tspec->toCBuffer(buf, NULL); + tspec->toCBuffer(buf, NULL, hgs); } buf->writeByte(')'); } diff -uNr gdc-0.17/d/dmd/cond.h gdc-0.18/d/dmd/cond.h --- gdc-0.17/d/dmd/cond.h 2005-10-13 03:06:51.000000000 +0200 +++ gdc-0.18/d/dmd/cond.h 2006-03-12 15:16:26.000000000 +0100 @@ -16,7 +16,13 @@ struct Module; struct Scope; struct ScopeDsymbol; +#ifdef _DH +#include "lexer.h" // dmdhg +#endif enum TOK; +#ifdef _DH +struct HdrGenState; +#endif int findCondition(Array *ids, Identifier *ident); @@ -31,7 +37,7 @@ virtual Condition *syntaxCopy() = 0; virtual int include(Scope *sc, ScopeDsymbol *s) = 0; - virtual void toCBuffer(OutBuffer *buf) = 0; + virtual void toCBuffer(OutBuffer *buf, HdrGenState *hgs) = 0; }; struct DVCondition : Condition @@ -54,7 +60,7 @@ DebugCondition(Module *mod, unsigned level, Identifier *ident); int include(Scope *sc, ScopeDsymbol *s); - void toCBuffer(OutBuffer *buf); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); }; struct VersionCondition : DVCondition @@ -67,7 +73,7 @@ VersionCondition(Module *mod, unsigned level, Identifier *ident); int include(Scope *sc, ScopeDsymbol *s); - void toCBuffer(OutBuffer *buf); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); }; struct StaticIfCondition : Condition @@ -77,7 +83,7 @@ StaticIfCondition(Loc loc, Expression *exp); Condition *syntaxCopy(); int include(Scope *sc, ScopeDsymbol *s); - void toCBuffer(OutBuffer *buf); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); }; struct IftypeCondition : Condition @@ -92,7 +98,7 @@ IftypeCondition(Loc loc, Type *targ, Identifier *id, enum TOK tok, Type *tspec); Condition *syntaxCopy(); int include(Scope *sc, ScopeDsymbol *s); - void toCBuffer(OutBuffer *buf); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); }; diff -uNr gdc-0.17/d/dmd/constfold.c gdc-0.18/d/dmd/constfold.c --- gdc-0.17/d/dmd/constfold.c 2005-11-28 05:17:52.000000000 +0100 +++ gdc-0.18/d/dmd/constfold.c 2006-05-14 03:05:56.000000000 +0200 @@ -30,10 +30,8 @@ /* %% fix? */ extern "C" bool real_isnan (const real_t *); - #endif - static real_t zero; // work around DMC bug for now @@ -118,20 +116,54 @@ Expression *CastExp::constFold() { //printf("CastExp::constFold(%s)\n", toChars()); + //printf("from %s to %s\n", type->toChars(), to->toChars()); + //printf("type = %p\n", type); + assert(type); e1 = e1->constFold(); - if (e1->op == TOKsymoff && type->size() == e1->type->size() && - type->toBasetype()->ty != Tsarray) + if (e1->op == TOKsymoff) { - e1->type = type; - return e1; + if (type->size() == e1->type->size() && + type->toBasetype()->ty != Tsarray) + { + e1->type = type; + return e1; + } + return this; } Type *tb = to->toBasetype(); - if (tb->ty == Tbit) + if (tb->ty == Tbit || tb->ty == Tbool) return new IntegerExp(loc, e1->toInteger() != 0, type); if (type->isintegral()) { + if (e1->type->isfloating()) + { integer_t result; +#ifdef IN_GCC + d_int64 r = e1->toReal().toInt(e1->type, type); +#else + real_t r = e1->toReal(); +#endif + + switch (type->toBasetype()->ty) + { + case Tint8: result = (d_int8)r; break; + case Tchar: + case Tuns8: result = (d_uns8)r; break; + case Tint16: result = (d_int16)r; break; + case Twchar: + case Tuns16: result = (d_uns16)r; break; + case Tint32: result = (d_int32)r; break; + case Tdchar: + case Tuns32: result = (d_uns32)r; break; + case Tint64: result = (d_int64)r; break; + case Tuns64: result = (d_uns64)r; break; + default: + assert(0); + } + + return new IntegerExp(loc, result, type); + } if (type->isunsigned()) return new IntegerExp(loc, e1->toUInteger(), type); else @@ -208,7 +240,70 @@ } else if (type->iscomplex()) { - e = new ComplexExp(loc, e1->toComplex() + e2->toComplex(), type); + // This rigamarole is necessary so that -0.0 doesn't get + // converted to +0.0 by doing an extraneous add with +0.0 + complex_t c1; + real_t r1; + real_t i1; + + complex_t c2; + real_t r2; + real_t i2; + + complex_t v; + int x; + + if (e1->type->isreal()) + { r1 = e1->toReal(); + x = 0; + } + else if (e1->type->isimaginary()) + { i1 = e1->toImaginary(); + x = 3; + } + else + { c1 = e1->toComplex(); + x = 6; + } + + if (e2->type->isreal()) + { r2 = e2->toReal(); + } + else if (e2->type->isimaginary()) + { i2 = e2->toImaginary(); + x += 1; + } + else + { c2 = e2->toComplex(); + x += 2; + } + + switch (x) + { +#if __DMC__ + case 0+0: v = (complex_t) (r1 + r2); break; + case 0+1: v = r1 + i2 * I; break; + case 0+2: v = r1 + c2; break; + case 3+0: v = i1 * I + r2; break; + case 3+1: v = (complex_t) ((i1 + i2) * I); break; + case 3+2: v = i1 * I + c2; break; + case 6+0: v = c1 + r2; break; + case 6+1: v = c1 + i2 * I; break; + case 6+2: v = c1 + c2; break; +#else + case 0+0: v = complex_t(r1 + r2, 0); break; + case 0+1: v = complex_t(r1, i2); break; + case 0+2: v = complex_t(r1 + creall(c2), cimagl(c2)); break; + case 3+0: v = complex_t(r2, i1); break; + case 3+1: v = complex_t(0, i1 + i2); break; + case 3+2: v = complex_t(creall(c2), i1 + cimagl(c2)); break; + case 6+0: v = complex_t(creall(c1) + r2, cimagl(c2)); break; + case 6+1: v = complex_t(creall(c1), cimagl(c1) + i2); break; + case 6+2: v = c1 + c2; break; +#endif + default: assert(0); + } + e = new ComplexExp(loc, v, type); } else if (e1->op == TOKsymoff) { @@ -245,7 +340,70 @@ } else if (type->iscomplex()) { - e = new ComplexExp(loc, e1->toComplex() - e2->toComplex(), type); + // This rigamarole is necessary so that -0.0 doesn't get + // converted to +0.0 by doing an extraneous add with +0.0 + complex_t c1; + real_t r1; + real_t i1; + + complex_t c2; + real_t r2; + real_t i2; + + complex_t v; + int x; + + if (e1->type->isreal()) + { r1 = e1->toReal(); + x = 0; + } + else if (e1->type->isimaginary()) + { i1 = e1->toImaginary(); + x = 3; + } + else + { c1 = e1->toComplex(); + x = 6; + } + + if (e2->type->isreal()) + { r2 = e2->toReal(); + } + else if (e2->type->isimaginary()) + { i2 = e2->toImaginary(); + x += 1; + } + else + { c2 = e2->toComplex(); + x += 2; + } + + switch (x) + { +#if __DMC__ + case 0+0: v = (complex_t) (r1 - r2); break; + case 0+1: v = r1 - i2 * I; break; + case 0+2: v = r1 - c2; break; + case 3+0: v = i1 * I - r2; break; + case 3+1: v = (complex_t) ((i1 - i2) * I); break; + case 3+2: v = i1 * I - c2; break; + case 6+0: v = c1 - r2; break; + case 6+1: v = c1 - i2 * I; break; + case 6+2: v = c1 - c2; break; +#else + case 0+0: v = complex_t(r1 - r2, 0); break; + case 0+1: v = complex_t(r1, -i2); break; + case 0+2: v = complex_t(r1 - creall(c2), -cimagl(c2)); break; + case 3+0: v = complex_t(-r2, i1); break; + case 3+1: v = complex_t(0, i1 - i2); break; + case 3+2: v = complex_t(-creall(c2), i1 - cimagl(c2)); break; + case 6+0: v = complex_t(creall(c1) - r2, cimagl(c1)); break; + case 6+1: v = complex_t(creall(c1), cimagl(c1) - i2); break; + case 6+2: v = c1 - c2; break; +#endif + default: assert(0); + } + e = new ComplexExp(loc, v, type); } else if (e1->op == TOKsymoff) { @@ -454,8 +612,8 @@ e = new RealExp(loc, creall(c), type); else if (type->isimaginary()) e = new RealExp(loc, cimagl(c), type); - else if (type->iscomplex()) - e = new ComplexExp(loc, c, type); + //else if (type->iscomplex()) + //e = new ComplexExp(loc, c, type); else assert(0); } @@ -538,6 +696,7 @@ Expression *UshrExp::constFold() { + //printf("UshrExp::constFold() %s\n", toChars()); unsigned count; integer_t value; @@ -549,11 +708,13 @@ { case Tint8: case Tuns8: + assert(0); // no way to trigger this value = (value & 0xFF) >> count; break; case Tint16: case Tuns16: + assert(0); // no way to trigger this value = (value & 0xFFFF) >> count; break; @@ -595,27 +756,35 @@ } Expression *AndAndExp::constFold() -{ integer_t n; +{ int n1, n2; e1 = e1->constFold(); e2 = e2->constFold(); - if (e1->type->isfloating()) - n = e1->toComplex() && e2->toComplex(); + + n1 = e1->isBool(1); + if (n1) + { n2 = e2->isBool(1); + assert(n2 || e2->isBool(0)); + } else - n = e1->toInteger() && e2->toInteger(); - return new IntegerExp(loc, n, type); + assert(e1->isBool(0)); + return new IntegerExp(loc, n1 && n2, type); } Expression *OrOrExp::constFold() -{ integer_t n; +{ int n1, n2; e1 = e1->constFold(); e2 = e2->constFold(); - if (e1->type->isfloating()) - n = e1->toComplex() || e2->toComplex(); - else - n = e1->toInteger() || e2->toInteger(); - return new IntegerExp(loc, n, type); + + n1 = e1->isBool(1); + if (!n1) + { + assert(e1->isBool(0)); + n2 = e2->isBool(1); + assert(n2 || e2->isBool(0)); + } + return new IntegerExp(loc, n1 || n2, type); } Expression *CmpExp::constFold() @@ -623,7 +792,7 @@ real_t r1; real_t r2; - //printf("CmpExp::constFold()\n"); + //printf("CmpExp::constFold() %s\n", toChars()); e1 = e1->constFold(); e2 = e2->constFold(); if (e1->type->isreal()) @@ -661,7 +830,11 @@ } #else // Don't rely on compiler, handle NAN arguments separately +#if IN_GCC if (real_isnan(&r1) || real_isnan(&r2)) // if unordered +#else + if (isnan(r1) || isnan(r2)) // if unordered +#endif { switch (op) { @@ -813,6 +986,7 @@ Expression *IdentityExp::constFold() { int cmp; + //printf("IdentityExp::constFold() %s\n", toChars()); e1 = e1->constFold(); e2 = e2->constFold(); if (e1->type->isfloating()) @@ -845,10 +1019,8 @@ int n; econd = econd->constFold(); - if (econd->type->isfloating()) - n = econd->toComplex() != 0; - else - n = econd->toInteger() != 0; + n = econd->isBool(1); + assert(n || econd->isBool(0)); return n ? e1->constFold() : e2->constFold(); } diff -uNr gdc-0.17/d/dmd/dchar.c gdc-0.18/d/dmd/dchar.c --- gdc-0.17/d/dmd/dchar.c 2005-04-28 23:12:43.000000000 +0200 +++ gdc-0.18/d/dmd/dchar.c 2006-04-16 17:13:30.000000000 +0200 @@ -1,5 +1,5 @@ -// Copyright (c) 1999-2002 by Digital Mars +// Copyright (c) 1999-2006 by Digital Mars // All Rights Reserved // written by Walter Bright // www.digitalmars.com @@ -332,18 +332,30 @@ case 2: hash *= 37; +#if __I86__ hash += *(unsigned short *)str; +#else + hash += str[0] * 256 + str[1]; +#endif return hash; case 3: hash *= 37; +#if __I86__ hash += (*(unsigned short *)str << 8) + ((unsigned char *)str)[2]; +#else + hash += (str[0] * 256 + str[1]) * 256 + str[2]; +#endif return hash; default: hash *= 37; +#if __I86__ hash += *(long *)str; +#else + hash += ((str[0] * 256 + str[1]) * 256 + str[2]) * 256 + str[3]; +#endif str += 4; len -= 4; break; diff -uNr gdc-0.17/d/dmd/dchar.h gdc-0.18/d/dmd/dchar.h --- gdc-0.17/d/dmd/dchar.h 2005-05-29 23:09:19.000000000 +0200 +++ gdc-0.18/d/dmd/dchar.h 2006-04-16 17:13:30.000000000 +0200 @@ -1,5 +1,5 @@ -// Copyright (c) 1999-2002 by Digital Mars +// Copyright (c) 1999-2006 by Digital Mars // All Rights Reserved // written by Walter Bright // www.digitalmars.com @@ -7,17 +7,11 @@ // in artistic.txt, or the GNU General Public License in gnu.txt. // See the included readme.txt for details. -/* NOTE: This file has been patched from the original DMD distribution to - work with the GDC compiler. - - Modified by David Friedman, September 2004 -*/ - #ifndef DCHAR_H #define DCHAR_H -#if __GNUC__ && ! _WIN32 +#if __GNUC__ && !_WIN32 #include "gnuc.h" #endif @@ -144,6 +138,7 @@ #else #include + #ifndef GCC_SAFE_DMD #include #endif diff -uNr gdc-0.17/d/dmd/declaration.c gdc-0.18/d/dmd/declaration.c --- gdc-0.17/d/dmd/declaration.c 2005-10-26 03:33:56.000000000 +0200 +++ gdc-0.18/d/dmd/declaration.c 2006-05-13 21:05:42.000000000 +0200 @@ -1,5 +1,5 @@ -// Copyright (c) 1999-2005 by Digital Mars +// Copyright (c) 1999-2006 by Digital Mars // All Rights Reserved // written by Walter Bright // www.digitalmars.com @@ -20,6 +20,7 @@ #include "module.h" #include "id.h" #include "expression.h" +#include "hdrgen.h" /********************************* Declaration ****************************/ @@ -85,6 +86,10 @@ this->type = new TypeTypedef(this); this->basetype = basetype->toBasetype(); this->init = init; +#ifdef _DH + this->htype = NULL; + this->hbasetype = NULL; +#endif this->sem = 0; this->loc = loc; } @@ -100,6 +105,25 @@ assert(!s); TypedefDeclaration *st; st = new TypedefDeclaration(loc, ident, basetype, init); +#ifdef _DH + // Syntax copy for header file + if (!htype) // Don't overwrite original + { if (type) // Make copy for both old and new instances + { htype = type->syntaxCopy(); + st->htype = type->syntaxCopy(); + } + } + else // Make copy of original for new instance + st->htype = htype->syntaxCopy(); + if (!hbasetype) + { if (basetype) + { hbasetype = basetype->syntaxCopy(); + st->hbasetype = basetype->syntaxCopy(); + } + } + else + st->hbasetype = hbasetype->syntaxCopy(); +#endif return st; } @@ -148,10 +172,15 @@ return type; } -void TypedefDeclaration::toCBuffer(OutBuffer *buf) +void TypedefDeclaration::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { buf->writestring("typedef "); - basetype->toCBuffer(buf, ident); + basetype->toCBuffer(buf, ident, hgs); + if (init) + { + buf->writestring(" = "); + init->toCBuffer(buf, hgs); + } buf->writeByte(';'); buf->writenl(); } @@ -166,6 +195,10 @@ this->loc = loc; this->type = type; this->aliassym = NULL; +#ifdef _DH + this->htype = NULL; + this->haliassym = NULL; +#endif this->overnext = NULL; this->inSemantic = 0; assert(type); @@ -179,6 +212,10 @@ this->loc = loc; this->type = NULL; this->aliassym = s; +#ifdef _DH + this->htype = NULL; + this->haliassym = NULL; +#endif this->overnext = NULL; this->inSemantic = 0; assert(s); @@ -192,6 +229,25 @@ sa = new AliasDeclaration(loc, ident, type->syntaxCopy()); else sa = new AliasDeclaration(loc, ident, aliassym->syntaxCopy(NULL)); +#ifdef _DH + // Syntax copy for header file + if (!htype) // Don't overwrite original + { if (type) // Make copy for both old and new instances + { htype = type->syntaxCopy(); + sa->htype = type->syntaxCopy(); + } + } + else // Make copy of original for new instance + sa->htype = htype->syntaxCopy(); + if (!haliassym) + { if (aliassym) + { haliassym = aliassym->syntaxCopy(s); + sa->haliassym = aliassym->syntaxCopy(s); + } + } + else + sa->haliassym = haliassym->syntaxCopy(s); +#endif return sa; } @@ -331,22 +387,40 @@ assert(this != aliassym); //static int count; if (++count == 10) *(char*)0=0; if (inSemantic) - error("recursive alias declaration"); + { error("recursive alias declaration"); +// return this; + } Dsymbol *s = aliassym ? aliassym->toAlias() : this; return s; } -void AliasDeclaration::toCBuffer(OutBuffer *buf) +void AliasDeclaration::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { buf->writestring("alias "); - if (aliassym) +#if 0 && _DH + if (hgs->hdrgen) { - aliassym->toCBuffer(buf); - buf->writeByte(' '); - buf->writestring(ident->toChars()); + if (haliassym) + { + haliassym->toCBuffer(buf, hgs); + buf->writeByte(' '); + buf->writestring(ident->toChars()); + } + else + htype->toCBuffer(buf, ident, hgs); } else - type->toCBuffer(buf, ident); +#endif + { + if (aliassym) + { + aliassym->toCBuffer(buf, hgs); + buf->writeByte(' '); + buf->writestring(ident->toChars()); + } + else + type->toCBuffer(buf, ident, hgs); + } buf->writeByte(';'); buf->writenl(); } @@ -359,12 +433,16 @@ #ifdef DEBUG if (!type && !init) { printf("VarDeclaration('%s')\n", id->toChars()); - *(char*)0=0; + //*(char*)0=0; } #endif assert(type || init); this->type = type; this->init = init; +#ifdef _DH + this->htype = NULL; + this->hinit = NULL; +#endif this->loc = loc; offset = 0; noauto = 0; @@ -393,6 +471,25 @@ sv = new VarDeclaration(loc, type ? type->syntaxCopy() : NULL, ident, init); sv->storage_class = storage_class; } +#ifdef _DH + // Syntax copy for header file + if (!htype) // Don't overwrite original + { if (type) // Make copy for both old and new instances + { htype = type->syntaxCopy(); + sv->htype = type->syntaxCopy(); + } + } + else // Make copy of original for new instance + sv->htype = htype->syntaxCopy(); + if (!hinit) + { if (init) + { hinit = init->syntaxCopy(); + sv->hinit = init->syntaxCopy(); + } + } + else + sv->hinit = hinit->syntaxCopy(); +#endif return sv; } @@ -406,8 +503,12 @@ /* If auto type inference, do the inference */ + int inferred = 0; if (!type) - { type = init->inferType(sc); + { inuse++; + type = init->inferType(sc); + inuse--; + inferred = 1; /* This is a kludge to support the existing syntax for RAII * declarations. @@ -593,6 +694,42 @@ } } } + else if (isConst() and init) + { + /* Because we may need the results of a const declaration in a + * subsequent type, such as an array dimension, before semantic2() + * gets ordinarilly run, try to run semantic2() now. + * Ignore failure. + */ + + ExpInitializer *ei = init->isExpInitializer(); + if (ei && !global.errors && !inferred) + { + unsigned errors = global.errors; + global.gag++; + //printf("+gag\n"); + Expression *e = ei->exp->syntaxCopy(); + inuse++; + e = e->semantic(sc); + inuse--; + e = e->implicitCastTo(type); + global.gag--; + //printf("-gag\n"); + if (errors != global.errors) // if errors happened + { + if (global.gag == 0) + global.errors = errors; // act as if nothing happened + } + else + { + e = e->optimize(WANTvalue); + if (e->op == TOKint64 || e->op == TOKstring) + { + ei->exp = e; // no errors, keep result + } + } + } + } } ExpInitializer *VarDeclaration::getExpInitializer() @@ -616,9 +753,17 @@ { //printf("VarDeclaration::semantic2('%s')\n", toChars()); if (init && !sc->parent->isFuncDeclaration()) - { inuse = 1; + { inuse++; +#if 0 + ExpInitializer *ei = init->isExpInitializer(); + if (ei) + { + ei->exp->dump(0); + printf("type = %p\n", ei->exp->type); + } +#endif init = init->semantic(sc, type); - inuse = 0; + inuse--; } } @@ -627,12 +772,19 @@ return "variable"; } -void VarDeclaration::toCBuffer(OutBuffer *buf) +void VarDeclaration::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { - type->toCBuffer(buf, ident); + if (storage_class & STCconst) + buf->writestring("const "); + if (storage_class & STCstatic) + buf->writestring("static "); + if (type) + type->toCBuffer(buf, ident, hgs); + else + buf->writestring(ident->toChars()); if (init) { buf->writestring(" = "); - init->toCBuffer(buf); + init->toCBuffer(buf, hgs); } buf->writeByte(';'); buf->writenl(); @@ -691,12 +843,15 @@ { FuncDeclaration *fd; Expression *efd; Expression *ec; - Array *arguments; + Expressions *arguments; + /* Generate: + * _d_callfinalizer(this) + */ fd = FuncDeclaration::genCfunc(Type::tvoid, "_d_callfinalizer"); efd = new VarExp(loc, fd); ec = new VarExp(loc, this); - arguments = new Array(); + arguments = new Expressions(); arguments->push(ec); e = new CallExp(loc, efd, arguments); e->type = fd->type->next; @@ -707,6 +862,7 @@ return e; } + /********************************* ClassInfoDeclaration ****************************/ ClassInfoDeclaration::ClassInfoDeclaration(ClassDeclaration *cd) diff -uNr gdc-0.17/d/dmd/declaration.h gdc-0.18/d/dmd/declaration.h --- gdc-0.17/d/dmd/declaration.h 2005-10-02 16:17:55.000000000 +0200 +++ gdc-0.18/d/dmd/declaration.h 2006-05-13 21:05:42.000000000 +0200 @@ -7,12 +7,6 @@ // in artistic.txt, or the GNU General Public License in gnu.txt. // See the included readme.txt for details. -/* NOTE: This file has been patched from the original DMD distribution to - work with the GDC compiler. - - Modified by David Friedman, September 2004 -*/ - #ifndef DMD_DECLARATION_H #define DMD_DECLARATION_H @@ -21,6 +15,8 @@ #endif /* __DMC__ */ #include "dsymbol.h" +#include "lexer.h" +#include "mtype.h" struct Expression; struct Statement; @@ -69,7 +65,7 @@ FuncDeclaration *anyf; // pick a func, any func, to use for error recovery }; -void overloadResolveX(Match *m, FuncDeclaration *f, Array *arguments); +void overloadResolveX(Match *m, FuncDeclaration *f, Expressions *arguments); /**************************************************************/ @@ -130,7 +126,11 @@ char *mangle(); char *kind(); Type *getType(); - void toCBuffer(OutBuffer *buf); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); +#ifdef _DH + Type *htype; + Type *hbasetype; +#endif void toDocBuffer(OutBuffer *buf); @@ -155,7 +155,11 @@ char *kind(); Type *getType(); Dsymbol *toAlias(); - void toCBuffer(OutBuffer *buf); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); +#ifdef _DH + Type *htype; + Dsymbol *haliassym; +#endif void toDocBuffer(OutBuffer *buf); @@ -176,7 +180,11 @@ void semantic(Scope *sc); void semantic2(Scope *sc); char *kind(); - void toCBuffer(OutBuffer *buf); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); +#ifdef _DH + Type *htype; + Initializer *hinit; +#endif int needThis(); int isImportedSymbol(); int isDataseg(); @@ -333,19 +341,22 @@ struct FuncDeclaration : Declaration { - Array *fthrows; // Array of Type's of exceptions + Array *fthrows; // Array of Type's of exceptions (not used) Statement *frequire; + Statement *fensure; + Statement *fbody; + Identifier *outId; // identifier for out statement VarDeclaration *vresult; // variable corresponding to outId LabelDsymbol *returnLabel; // where the return goes - Statement *fensure; - Statement *fbody; DsymbolTable *localsymtab; // used to prevent symbols in different // scopes from having the same name VarDeclaration *vthis; // 'this' parameter VarDeclaration *v_arguments; // '_arguments' parameter +#if IN_GCC VarDeclaration *v_argptr; // '_argptr' variable +#endif Array *parameters; // Array of Argument's for parameters DsymbolTable *labtab; // statement label symbol table Declaration *overnext; // next in overload list @@ -357,8 +368,11 @@ int inlineNest; // !=0 if nested inline int semanticRun; // !=0 if semantic3() had been run int nestedFrameRef; // !=0 if nested variables referenced frame ptr - int introducing; // !=0 if 'introducing' function ForeachStatement *fes; // if foreach body, this is the foreach + int introducing; // !=0 if 'introducing' function + Type *tintro; // if !=NULL, then this is the type + // of the 'introducing' function + // this one is overriding // Things that should really go into Scope int hasReturnExp; // if there's a return exp; statement @@ -367,12 +381,12 @@ Dsymbol *syntaxCopy(Dsymbol *); void semantic(Scope *sc); void semantic3(Scope *sc); - void toHBuffer(OutBuffer *buf); - void toCBuffer(OutBuffer *buf); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); + void bodyToCBuffer(OutBuffer *buf, HdrGenState *hgs); int overrides(FuncDeclaration *fd); int overloadInsert(Dsymbol *s); FuncDeclaration *overloadExactMatch(Type *t); - FuncDeclaration *overloadResolve(Loc loc, Array *arguments); + FuncDeclaration *overloadResolve(Loc loc, Expressions *arguments); LabelDsymbol *searchLabel(Identifier *ident); AggregateDeclaration *isThis(); AggregateDeclaration *isMember2(); @@ -393,11 +407,12 @@ virtual int addPreInvariant(); virtual int addPostInvariant(); void inlineScan(); - int canInline(int hasthis); + int canInline(int hasthis, int hdrscan = 0); Expression *doInline(InlineScanState *iss, Expression *ethis, Array *arguments); char *kind(); - static FuncDeclaration *genCfunc(Type *treturn, char *name); + static FuncDeclaration *genCfunc(Type *treturn, char *name, + Type *t1 = 0, Type *t2 = 0, Type *t3 = 0); Symbol *toSymbol(); Symbol *toThunkSymbol(int offset); // thunk version @@ -423,6 +438,7 @@ FuncLiteralDeclaration(Loc loc, Loc endloc, Type *type, enum TOK tok, ForeachStatement *fes); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); Dsymbol *syntaxCopy(Dsymbol *); int isNested(); @@ -437,6 +453,7 @@ CtorDeclaration(Loc loc, Loc endloc, Array *arguments, int varargs); Dsymbol *syntaxCopy(Dsymbol *); void semantic(Scope *sc); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); char *kind(); char *toChars(); int isVirtual(); @@ -452,6 +469,7 @@ DtorDeclaration(Loc loc, Loc endloc); Dsymbol *syntaxCopy(Dsymbol *); void semantic(Scope *sc); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); int addPreInvariant(); int addPostInvariant(); int overloadInsert(Dsymbol *s); @@ -471,6 +489,7 @@ int addPreInvariant(); int addPostInvariant(); void emitComment(Scope *sc); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); StaticCtorDeclaration *isStaticCtorDeclaration() { return this; } }; @@ -486,6 +505,7 @@ int addPreInvariant(); int addPostInvariant(); void emitComment(Scope *sc); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); StaticDtorDeclaration *isStaticDtorDeclaration() { return this; } }; @@ -499,6 +519,7 @@ int addPreInvariant(); int addPostInvariant(); void emitComment(Scope *sc); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); InvariantDeclaration *isInvariantDeclaration() { return this; } }; @@ -513,6 +534,7 @@ int isVirtual(); int addPreInvariant(); int addPostInvariant(); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); UnitTestDeclaration *isUnitTestDeclaration() { return this; } }; @@ -524,6 +546,7 @@ NewDeclaration(Loc loc, Loc endloc, Array *arguments, int varargs); Dsymbol *syntaxCopy(Dsymbol *); void semantic(Scope *sc); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); char *kind(); int isVirtual(); int addPreInvariant(); @@ -539,11 +562,15 @@ DeleteDeclaration(Loc loc, Loc endloc, Array *arguments); Dsymbol *syntaxCopy(Dsymbol *); void semantic(Scope *sc); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); char *kind(); int isDelete(); int isVirtual(); int addPreInvariant(); int addPostInvariant(); +#ifdef _DH + DeleteDeclaration *isDeleteDeclaration() { return this; } +#endif }; #endif /* DMD_DECLARATION_H */ diff -uNr gdc-0.17/d/dmd/doc.c gdc-0.18/d/dmd/doc.c --- gdc-0.17/d/dmd/doc.c 2005-11-27 17:28:26.000000000 +0100 +++ gdc-0.18/d/dmd/doc.c 2006-05-13 21:05:42.000000000 +0200 @@ -7,17 +7,11 @@ // in artistic.txt, or the GNU General Public License in gnu.txt. // See the included readme.txt for details. -/* NOTE: This file has been patched from the original DMD distribution to - work with the GDC compiler. - - Modified by David Friedman, September 2005 -*/ - - #include #include #include #include +#include #ifdef IN_GCC #include "mem.h" @@ -38,7 +32,15 @@ #include "macro.h" #include "template.h" #include "lexer.h" +#include "aggregate.h" +#include "declaration.h" +#include "enum.h" +#include "id.h" +#include "module.h" +#include "scope.h" +#include "hdrgen.h" #include "doc.h" +#include "mtype.h" struct Section { @@ -416,6 +418,7 @@ void Declaration::emitComment(Scope *sc) { //printf("Declaration::emitComment(%p '%s'), comment = '%s'\n", this, toChars(), comment); + //printf("type = %p\n", type); if (protection == PROTprivate || !ident || (!type && !isCtorDeclaration())) @@ -590,11 +593,14 @@ void Dsymbol::toDocBuffer(OutBuffer *buf) { - toCBuffer(buf); + HdrGenState hgs; + + toCBuffer(buf, &hgs); } void Declaration::toDocBuffer(OutBuffer *buf) { + //printf("Declaration::toDocbuffer()\n"); if (ident) { if (isDeprecated()) @@ -610,7 +616,12 @@ if (isSynchronized()) buf->writestring("synchronized "); if (type) - type->toCBuffer(buf, ident); + { HdrGenState hgs; + hgs.ddoc = 1; + type->toCBuffer(buf, ident, &hgs); + } + else + buf->writestring(ident->toChars()); buf->writestring(";\n"); } } @@ -648,14 +659,10 @@ void CtorDeclaration::toDocBuffer(OutBuffer *buf) { - TypeFunction *tf = (TypeFunction *)type; + HdrGenState hgs; buf->writestring("this"); - if (!tf) - { // Need to create one - tf = new TypeFunction(arguments, Type::tvoid, varargs, LINKd); - } - tf->argsToCBuffer(buf); + Argument::argsToCBuffer(buf, &hgs, arguments, varargs); buf->writestring(";\n"); } @@ -712,7 +719,8 @@ } else { - bc->type->toCBuffer(buf, NULL); + HdrGenState hgs; + bc->type->toCBuffer(buf, NULL, &hgs); } } buf->writestring(";\n"); @@ -1022,13 +1030,13 @@ L1: //printf("param '%.*s' = '%.*s'\n", namelen, namestart, textlen, textstart); - + HdrGenState hgs; buf->writestring("$(DDOC_PARAM_ROW "); buf->writestring("$(DDOC_PARAM_ID "); o = buf->offset; arg = isFunctionParameter(s, namestart, namelen); if (arg && arg->type && arg->ident) - arg->type->toCBuffer(buf, arg->ident); + arg->type->toCBuffer(buf, arg->ident, &hgs); else buf->write(namestart, namelen); highlightCode(sc, s, buf, o); diff -uNr gdc-0.17/d/dmd/dsymbol.c gdc-0.18/d/dmd/dsymbol.c --- gdc-0.17/d/dmd/dsymbol.c 2005-10-13 03:06:51.000000000 +0200 +++ gdc-0.18/d/dmd/dsymbol.c 2006-04-16 17:13:30.000000000 +0200 @@ -7,12 +7,6 @@ // in artistic.txt, or the GNU General Public License in gnu.txt. // See the included readme.txt for details. -/* NOTE: This file has been patched from the original DMD distribution to - work with the GDC compiler. - - Modified by David Friedman, May 2005 -*/ - #include #include #include @@ -30,6 +24,7 @@ #include "declaration.h" #include "id.h" #include "scope.h" +#include "init.h" /****************************** Dsymbol ******************************/ @@ -77,11 +72,64 @@ Dsymbol *Dsymbol::syntaxCopy(Dsymbol *s) { print(); - fprintf(stderr, "%s %s\n", kind(), toChars()); + printf("%s %s\n", kind(), toChars()); assert(0); return NULL; } +/************************************** + * Determine if this symbol is only one. + * Returns: + * FALSE, *ps = NULL: There are 2 or more symbols + * TRUE, *ps = NULL: There are zero symbols + * TRUE, *ps = symbol: The one and only one symbol + */ + +int Dsymbol::oneMember(Dsymbol **ps) +{ + //printf("Dsymbol::oneMember()\n"); + *ps = this; + return TRUE; +} + +/***************************************** + * Same as Dsymbol::oneMember(), but look at an array of Dsymbols. + */ + +int Dsymbol::oneMembers(Array *members, Dsymbol **ps) +{ + //printf("Dsymbol::oneMembers() %d\n", members ? members->dim : 0); + Dsymbol *s = NULL; + + if (members) + { + for (int i = 0; i < members->dim; i++) + { Dsymbol *sx = (Dsymbol *)members->data[i]; + + int x = sx->oneMember(ps); + //printf("\t[%d] kind %s = %d, s = %p\n", i, sx->kind(), x, *ps); + if (!x) + { + //printf("\tfalse 1\n"); + assert(*ps == NULL); + return FALSE; + } + if (*ps) + { + if (s) // more than one symbol + { *ps = NULL; + //printf("\tfalse 2\n"); + return FALSE; + } + s = *ps; + } + } + } + *ps = s; // s is the one symbol, NULL if none + //printf("\ttrue\n"); + return TRUE; +} + char *Dsymbol::toChars() { return ident ? ident->toChars() : (char *)"__anonymous"; @@ -93,6 +141,7 @@ char *q; size_t len; + //printf("Dsymbol::toPrettyChars() '%s'\n", toChars()); if (!parent) return toChars(); @@ -103,7 +152,7 @@ s = (char *)mem.malloc(len); q = s + len - 1; *q = 0; - for (p = this; 1; p = p->parent) + for (p = this; p; p = p->parent) { char *t = p->toChars(); len = strlen(t); @@ -197,10 +246,9 @@ return FALSE; } -void Dsymbol::toCBuffer(OutBuffer *buf) +void Dsymbol::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { - buf->printf("Dsymbol '%s' to C file", toChars()); - buf->writenl(); + buf->writestring(toChars()); } unsigned Dsymbol::size(Loc loc) @@ -268,8 +316,9 @@ return FALSE; } -void Dsymbol::addMember(Scope *sc, ScopeDsymbol *sd) +int Dsymbol::addMember(Scope *sc, ScopeDsymbol *sd, int memnum) { + //printf("Dsymbol::addMember('%s')\n", toChars()); //printf("Dsymbol::addMember(this = %p, '%s' scopesym = '%s')\n", this, toChars(), sd->toChars()); //printf("Dsymbol::addMember(this = %p, '%s' sd = %p, sd->symtab = %p)\n", this, toChars(), sd, sd->symtab); parent = sd; @@ -287,38 +336,38 @@ } if (sd->isAggregateDeclaration() || sd->isEnumDeclaration()) { - if (ident == Id::__sizeof || ident == Id::alignof) + if (ident == Id::__sizeof || ident == Id::alignof || ident == Id::mangleof) error(".%s property cannot be redefined", ident->toChars()); } + return 1; } + return 0; } void Dsymbol::error(const char *format, ...) { //printf("Dsymbol::error()\n"); - char *p = locToChars(); - if (!global.gag) { char *p = locToChars(); + if (*p) - fprintf(stderr, "%s: ", p); + fprintf(stdmsg, "%s: ", p); mem.free(p); if (isAnonymous()) - fprintf(stderr, "%s ", kind()); + fprintf(stdmsg, "%s ", kind()); else - fprintf(stderr, "%s %s ", kind(), toPrettyChars()); + fprintf(stdmsg, "%s %s ", kind(), toPrettyChars()); va_list ap; va_start(ap, format); - vfprintf(stderr, format, ap); + vfprintf(stdmsg, format, ap); va_end(ap); - fprintf(stderr, "\n"); - fflush(stderr); + fprintf(stdmsg, "\n"); + fflush(stdmsg); } - global.errors++; //fatal(); @@ -333,18 +382,18 @@ p = locToChars(); if (*p) - fprintf(stderr, "%s: ", p); + fprintf(stdmsg, "%s: ", p); mem.free(p); - fprintf(stderr, "%s %s ", kind(), toPrettyChars()); + fprintf(stdmsg, "%s %s ", kind(), toPrettyChars()); va_list ap; va_start(ap, format); - vfprintf(stderr, format, ap); + vfprintf(stdmsg, format, ap); va_end(ap); - fprintf(stderr, "\n"); - fflush(stderr); + fprintf(stdmsg, "\n"); + fflush(stdmsg); } global.errors++; @@ -636,18 +685,21 @@ { if (ident == Id::length || ident == Id::dollar) { VarDeclaration **pvar; + Expression *ce; if (exp->op == TOKindex) { IndexExp *ie = (IndexExp *)exp; pvar = &ie->lengthVar; + ce = ie->e1; } else if (exp->op == TOKslice) { SliceExp *se = (SliceExp *)exp; pvar = &se->lengthVar; + ce = se->e1; } else return NULL; @@ -655,6 +707,14 @@ { VarDeclaration *v = new VarDeclaration(0, Type::tsize_t, Id::dollar, NULL); + if (ce->op == TOKstring) + { /* It is for a string literal, so the + * length will be a const. + */ + Expression *e = new IntegerExp(0, ((StringExp *)ce)->len, Type::tsize_t); + v->init = new ExpInitializer(0, e); + v->storage_class |= STCconst; + } *pvar = v; } return (*pvar); diff -uNr gdc-0.17/d/dmd/dsymbol.h gdc-0.18/d/dmd/dsymbol.h --- gdc-0.17/d/dmd/dsymbol.h 2005-10-26 03:33:56.000000000 +0200 +++ gdc-0.18/d/dmd/dsymbol.h 2006-05-13 21:05:42.000000000 +0200 @@ -1,5 +1,5 @@ -// Copyright (c) 1999-2004 by Digital Mars +// Copyright (c) 1999-2006 by Digital Mars // All Rights Reserved // written by Walter Bright // www.digitalmars.com @@ -7,12 +7,6 @@ // in artistic.txt, or the GNU General Public License in gnu.txt. // See the included readme.txt for details. -/* NOTE: This file has been patched from the original DMD distribution to - work with the GDC compiler. - - Modified by David Friedman, September 2004 -*/ - #ifndef DMD_DSYMBOL_H #define DMD_DSYMBOL_H @@ -24,6 +18,7 @@ #include "stringtable.h" #include "mars.h" +#include "arraytypes.h" struct Identifier; struct Scope; @@ -66,8 +61,15 @@ struct ArrayScopeSymbol; struct SymbolDeclaration; struct Expression; +struct DeleteDeclaration; +struct HdrGenState; -union tree_node; typedef union tree_node TYPE; +#if IN_GCC +union tree_node; +typedef union tree_node TYPE; +#else +struct TYPE; +#endif enum PROT { @@ -111,14 +113,18 @@ virtual char *kind(); virtual Dsymbol *toAlias(); // resolve real symbol - virtual void addMember(Scope *sc, ScopeDsymbol *s); + virtual int addMember(Scope *sc, ScopeDsymbol *s, int memnum); virtual void semantic(Scope *sc); virtual void semantic2(Scope *sc); virtual void semantic3(Scope *sc); virtual void inlineScan(); virtual Dsymbol *search(Identifier *ident, int flags); virtual int overloadInsert(Dsymbol *s); - virtual void toCBuffer(OutBuffer *buf); +#ifdef _DH + char *toHChars(); + virtual void toHBuffer(OutBuffer *buf, HdrGenState *hgs); +#endif + virtual void toCBuffer(OutBuffer *buf, HdrGenState *hgs); virtual void toDocBuffer(OutBuffer *buf); virtual unsigned size(Loc loc); virtual int isforwardRef(); @@ -135,8 +141,9 @@ virtual int needThis(); // need a 'this' pointer? virtual enum PROT prot(); virtual Dsymbol *syntaxCopy(Dsymbol *s); // copy only syntax trees - virtual Dsymbol *oneMember() { return this; } - virtual void addLocalClass(Array *) { } + virtual int oneMember(Dsymbol **ps); + static int oneMembers(Array *members, Dsymbol **ps); + virtual void addLocalClass(ClassDeclarations *) { } virtual void checkCtorConstInit() { } virtual void addComment(unsigned char *comment); @@ -185,6 +192,9 @@ virtual ArrayScopeSymbol *isArrayScopeSymbol() { return NULL; } virtual Import *isImport() { return NULL; } virtual EnumDeclaration *isEnumDeclaration() { return NULL; } +#ifdef _DH + virtual DeleteDeclaration *isDeleteDeclaration() { return NULL; } +#endif virtual SymbolDeclaration *isSymbolDeclaration() { return NULL; } virtual AttribDeclaration *isAttribDeclaration() { return NULL; } }; diff -uNr gdc-0.17/d/dmd/entity.c gdc-0.18/d/dmd/entity.c --- gdc-0.17/d/dmd/entity.c 2005-04-28 23:12:43.000000000 +0200 +++ gdc-0.18/d/dmd/entity.c 2006-04-16 17:13:30.000000000 +0200 @@ -1,5 +1,5 @@ -// Copyright (c) 1999-2005 by Digital Mars +// Copyright (c) 1999-2006 by Digital Mars // All Rights Reserved // written by Walter Bright // www.digitalmars.com @@ -7,13 +7,6 @@ // in artistic.txt, or the GNU General Public License in gnu.txt. // See the included readme.txt for details. -/* NOTE: This file has been patched from the original DMD distribution to - work with the GDC compiler. - - Modified by David Friedman, April 2005 - Changes from Thomas Kuehne, November 2004 -*/ - #include @@ -30,455 +23,174 @@ unsigned short value; }; -#if 0 -//TODO: Merge Walter's list with Thomas' +#if IN_GCC +static NameId namesA[]={ + "Aacgr", 0x0386, + "aacgr", 0x03AC, + "Aacute", 0x00C1, + "aacute", 0x00E1, + "Abreve", 0x0102, + "abreve", 0x0103, + "Acirc", 0x00C2, + "acirc", 0x00E2, + "acute", 0x00B4, + "Acy", 0x0410, + "acy", 0x0430, + "AElig", 0x00C6, + "aelig", 0x00E6, + "Agr", 0x0391, + "agr", 0x03B1, + "Agrave", 0x00C0, + "agrave", 0x00E0, + "aleph", 0x2135, + "alpha", 0x03B1, + "Amacr", 0x0100, + "amacr", 0x0101, + "amalg", 0x2210, + "amp", 0x0026, + "and", 0x2227, + "ang", 0x2220, + "ang90", 0x221F, + "angmsd", 0x2221, + "angsph", 0x2222, + "angst", 0x212B, + "Aogon", 0x0104, + "aogon", 0x0105, + "ap", 0x2248, + "ape", 0x224A, + "apos", 0x0027, + "Aring", 0x00C5, + "aring", 0x00E5, + "ast", 0x002A, + "asymp", 0x224D, + "Atilde", 0x00C3, + "atilde", 0x00E3, + "Auml", 0x00C4, + "auml", 0x00E4, + NULL, 0 +}; -static NameId names[] = -{ - // Entities - "quot", 34, - "amp", 38, - "lt", 60, - "gt", 62, +static NameId namesB[]={ + "barwed", 0x22BC, + "Barwed", 0x2306, + "bcong", 0x224C, + "Bcy", 0x0411, + "bcy", 0x0431, + "becaus", 0x2235, + "bepsi", 0x220D, + "bernou", 0x212C, + "beta", 0x03B2, + "beth", 0x2136, + "Bgr", 0x0392, + "bgr", 0x03B2, + "blank", 0x2423, + "blk12", 0x2592, + "blk14", 0x2591, + "blk34", 0x2593, + "block", 0x2588, + "bottom", 0x22A5, + "bowtie", 0x22C8, + "boxdl", 0x2510, + "boxDL", 0x2555, + "boxdL", 0x2556, + "boxDl", 0x2557, + "boxdr", 0x250C, + "boxDR", 0x2552, + "boxDr", 0x2553, + "boxdR", 0x2554, + "boxh", 0x2500, + "boxH", 0x2550, + "boxhd", 0x252C, + "boxhD", 0x2564, + "boxHD", 0x2565, + "boxHd", 0x2566, + "boxhu", 0x2534, + "boxhU", 0x2567, + "boxHU", 0x2568, + "boxHu", 0x2569, + "boxul", 0x2518, + "boxUL", 0x255B, + "boxUl", 0x255C, + "boxuL", 0x255D, + "boxur", 0x2514, + "boxUR", 0x2558, + "boxuR", 0x2559, + "boxUr", 0x255A, + "boxv", 0x2502, + "boxV", 0x2551, + "boxvh", 0x253C, + "boxvH", 0x256A, + "boxVH", 0x256B, + "boxVh", 0x256C, + "boxvl", 0x2524, + "boxvL", 0x2561, + "boxVL", 0x2562, + "boxVl", 0x2563, + "boxvr", 0x251C, + "boxvR", 0x255E, + "boxVR", 0x255F, + "boxVr", 0x2560, + "bprime", 0x2035, + "breve", 0x02D8, + "brvbar", 0x00A6, + "bsim", 0x223D, + "bsime", 0x22CD, + "bsol", 0x005C, + "bull", 0x2022, + "bump", 0x224E, + "bumpe", 0x224F, + NULL, 0 +}; - "OElig", 338, - "oelig", 339, - "Scaron", 352, - "scaron", 353, - "Yuml", 376, - "circ", 710, - "tilde", 732, - "ensp", 8194, - "emsp", 8195, - "thinsp", 8201, - "zwnj", 8204, - "zwj", 8205, - "lrm", 8206, - "rlm", 8207, - "ndash", 8211, - "mdash", 8212, - "lsquo", 8216, - "rsquo", 8217, - "sbquo", 8218, - "ldquo", 8220, - "rdquo", 8221, - "bdquo", 8222, - "dagger", 8224, - "Dagger", 8225, - "permil", 8240, - "lsaquo", 8249, - "rsaquo", 8250, - "euro", 8364, - - // Latin-1 (ISO-8859-1) Entities - "nbsp", 160, - "iexcl", 161, - "cent", 162, - "pound", 163, - "curren", 164, - "yen", 165, - "brvbar", 166, - "sect", 167, - "uml", 168, - "copy", 169, - "ordf", 170, - "laquo", 171, - "not", 172, - "shy", 173, - "reg", 174, - "macr", 175, - "deg", 176, - "plusmn", 177, - "sup2", 178, - "sup3", 179, - "acute", 180, - "micro", 181, - "para", 182, - "middot", 183, - "cedil", 184, - "sup1", 185, - "ordm", 186, - "raquo", 187, - "frac14", 188, - "frac12", 189, - "frac34", 190, - "iquest", 191, - "Agrave", 192, - "Aacute", 193, - "Acirc", 194, - "Atilde", 195, - "Auml", 196, - "Aring", 197, - "AElig", 198, - "Ccedil", 199, - "Egrave", 200, - "Eacute", 201, - "Ecirc", 202, - "Euml", 203, - "Igrave", 204, - "Iacute", 205, - "Icirc", 206, - "Iuml", 207, - "ETH", 208, - "Ntilde", 209, - "Ograve", 210, - "Oacute", 211, - "Ocirc", 212, - "Otilde", 213, - "Ouml", 214, - "times", 215, - "Oslash", 216, - "Ugrave", 217, - "Uacute", 218, - "Ucirc", 219, - "Uuml", 220, - "Yacute", 221, - "THORN", 222, - "szlig", 223, - "agrave", 224, - "aacute", 225, - "acirc", 226, - "atilde", 227, - "auml", 228, - "aring", 229, - "aelig", 230, - "ccedil", 231, - "egrave", 232, - "eacute", 233, - "ecirc", 234, - "euml", 235, - "igrave", 236, - "iacute", 237, - "icirc", 238, - "iuml", 239, - "eth", 240, - "ntilde", 241, - "ograve", 242, - "oacute", 243, - "ocirc", 244, - "otilde", 245, - "ouml", 246, - "divide", 247, - "oslash", 248, - "ugrave", 249, - "uacute", 250, - "ucirc", 251, - "uuml", 252, - "yacute", 253, - "thorn", 254, - "yuml", 255, - - // Symbols and Greek letter entities - "fnof", 402, - "Alpha", 913, - "Beta", 914, - "Gamma", 915, - "Delta", 916, - "Epsilon", 917, - "Zeta", 918, - "Eta", 919, - "Theta", 920, - "Iota", 921, - "Kappa", 922, - "Lambda", 923, - "Mu", 924, - "Nu", 925, - "Xi", 926, - "Omicron", 927, - "Pi", 928, - "Rho", 929, - "Sigma", 931, - "Tau", 932, - "Upsilon", 933, - "Phi", 934, - "Chi", 935, - "Psi", 936, - "Omega", 937, - "alpha", 945, - "beta", 946, - "gamma", 947, - "delta", 948, - "epsilon", 949, - "zeta", 950, - "eta", 951, - "theta", 952, - "iota", 953, - "kappa", 954, - "lambda", 955, - "mu", 956, - "nu", 957, - "xi", 958, - "omicron", 959, - "pi", 960, - "rho", 961, - "sigmaf", 962, - "sigma", 963, - "tau", 964, - "upsilon", 965, - "phi", 966, - "chi", 967, - "psi", 968, - "omega", 969, - "thetasym", 977, - "upsih", 978, - "piv", 982, - "bull", 8226, - "hellip", 8230, - "prime", 8242, - "Prime", 8243, - "oline", 8254, - "frasl", 8260, - "weierp", 8472, - "image", 8465, - "real", 8476, - "trade", 8482, - "alefsym", 8501, - "larr", 8592, - "uarr", 8593, - "rarr", 8594, - "darr", 8595, - "harr", 8596, - "crarr", 8629, - "lArr", 8656, - "uArr", 8657, - "rArr", 8658, - "dArr", 8659, - "hArr", 8660, - "forall", 8704, - "part", 8706, - "exist", 8707, - "empty", 8709, - "nabla", 8711, - "isin", 8712, - "notin", 8713, - "ni", 8715, - "prod", 8719, - "sum", 8721, - "minus", 8722, - "lowast", 8727, - "radic", 8730, - "prop", 8733, - "infin", 8734, - "ang", 8736, - "and", 8743, - "or", 8744, - "cap", 8745, - "cup", 8746, - "int", 8747, - "there4", 8756, - "sim", 8764, - "cong", 8773, - "asymp", 8776, - "ne", 8800, - "equiv", 8801, - "le", 8804, - "ge", 8805, - "sub", 8834, - "sup", 8835, - "nsub", 8836, - "sube", 8838, - "supe", 8839, - "oplus", 8853, - "otimes", 8855, - "perp", 8869, - "sdot", 8901, - "lceil", 8968, - "rceil", 8969, - "lfloor", 8970, - "rfloor", 8971, - "lang", 9001, - "rang", 9002, - "loz", 9674, - "spades", 9824, - "clubs", 9827, - "hearts", 9829, - "diams", 9830, -}; - -int HtmlNamedEntity(unsigned char *p, int length) -{ - int i; - - // BUG: this is a dumb, slow linear search - for (i = 0; i < sizeof(names) / sizeof(names[0]); i++) - { - // Entries are case sensitive - if (memcmp(names[i].name, (char *)p, length) == 0 && - !names[i].name[length]) - return names[i].value; - } - return -1; -} - -#endif - -static NameId namesA[]={ - "Aacgr", 0x0386, - "aacgr", 0x03AC, - "Aacute", 0x00C1, - "aacute", 0x00E1, - "Abreve", 0x0102, - "abreve", 0x0103, - "Acirc", 0x00C2, - "acirc", 0x00E2, - "acute", 0x00B4, - "Acy", 0x0410, - "acy", 0x0430, - "AElig", 0x00C6, - "aelig", 0x00E6, - "Agr", 0x0391, - "agr", 0x03B1, - "Agrave", 0x00C0, - "agrave", 0x00E0, - "aleph", 0x2135, - "alpha", 0x03B1, - "Amacr", 0x0100, - "amacr", 0x0101, - "amalg", 0x2210, - "amp", 0x0026, - "and", 0x2227, - "ang", 0x2220, - "ang90", 0x221F, - "angmsd", 0x2221, - "angsph", 0x2222, - "angst", 0x212B, - "Aogon", 0x0104, - "aogon", 0x0105, - "ap", 0x2248, - "ape", 0x224A, - "apos", 0x0027, - "Aring", 0x00C5, - "aring", 0x00E5, - "ast", 0x002A, - "asymp", 0x224D, - "Atilde", 0x00C3, - "atilde", 0x00E3, - "Auml", 0x00C4, - "auml", 0x00E4, - NULL, 0 -}; - -static NameId namesB[]={ - "barwed", 0x22BC, - "Barwed", 0x2306, - "bcong", 0x224C, - "Bcy", 0x0411, - "bcy", 0x0431, - "becaus", 0x2235, - "bepsi", 0x220D, - "bernou", 0x212C, - "beta", 0x03B2, - "beth", 0x2136, - "Bgr", 0x0392, - "bgr", 0x03B2, - "blank", 0x2423, - "blk12", 0x2592, - "blk14", 0x2591, - "blk34", 0x2593, - "block", 0x2588, - "bottom", 0x22A5, - "bowtie", 0x22C8, - "boxdl", 0x2510, - "boxDL", 0x2555, - "boxdL", 0x2556, - "boxDl", 0x2557, - "boxdr", 0x250C, - "boxDR", 0x2552, - "boxDr", 0x2553, - "boxdR", 0x2554, - "boxh", 0x2500, - "boxH", 0x2550, - "boxhd", 0x252C, - "boxhD", 0x2564, - "boxHD", 0x2565, - "boxHd", 0x2566, - "boxhu", 0x2534, - "boxhU", 0x2567, - "boxHU", 0x2568, - "boxHu", 0x2569, - "boxul", 0x2518, - "boxUL", 0x255B, - "boxUl", 0x255C, - "boxuL", 0x255D, - "boxur", 0x2514, - "boxUR", 0x2558, - "boxuR", 0x2559, - "boxUr", 0x255A, - "boxv", 0x2502, - "boxV", 0x2551, - "boxvh", 0x253C, - "boxvH", 0x256A, - "boxVH", 0x256B, - "boxVh", 0x256C, - "boxvl", 0x2524, - "boxvL", 0x2561, - "boxVL", 0x2562, - "boxVl", 0x2563, - "boxvr", 0x251C, - "boxvR", 0x255E, - "boxVR", 0x255F, - "boxVr", 0x2560, - "bprime", 0x2035, - "breve", 0x02D8, - "brvbar", 0x00A6, - "bsim", 0x223D, - "bsime", 0x22CD, - "bsol", 0x005C, - "bull", 0x2022, - "bump", 0x224E, - "bumpe", 0x224F, - NULL, 0 -}; - -static NameId namesC[]={ - "Cacute", 0x0106, - "cacute", 0x0107, - "cap", 0x2229, - "Cap", 0x22D2, - "caret", 0x2041, - "caron", 0x02C7, - "Ccaron", 0x010C, - "ccaron", 0x010D, - "Ccedil", 0x00C7, - "ccedil", 0x00E7, - "Ccirc", 0x0108, - "ccirc", 0x0109, - "Cdot", 0x010A, - "cdot", 0x010B, - "cedil", 0x00B8, - "cent", 0x00A2, - "CHcy", 0x0427, - "chcy", 0x0447, - "check", 0x2713, - "chi", 0x03C7, - "cir", 0x25CB, - "circ", 0x005E, - "cire", 0x2257, - "clubs", 0x2663, - "colon", 0x003A, - "colone", 0x2254, - "comma", 0x002C, - "commat", 0x0040, - "comp", 0x2201, - "compfn", 0x2218, - "cong", 0x2245, - "conint", 0x222E, - "coprod", 0x2210, - "copy", 0x00A9, - "copysr", 0x2117, - "cross", 0x2717, - "cuepr", 0x22DE, - "cuesc", 0x22DF, - "cularr", 0x21B6, - "cup", 0x222A, - "Cup", 0x22D3, - "cupre", 0x227C, - "curarr", 0x21B7, - "curren", 0x00A4, - "cuvee", 0x22CE, - "cuwed", 0x22CF, - NULL, 0 -}; +static NameId namesC[]={ + "Cacute", 0x0106, + "cacute", 0x0107, + "cap", 0x2229, + "Cap", 0x22D2, + "caret", 0x2041, + "caron", 0x02C7, + "Ccaron", 0x010C, + "ccaron", 0x010D, + "Ccedil", 0x00C7, + "ccedil", 0x00E7, + "Ccirc", 0x0108, + "ccirc", 0x0109, + "Cdot", 0x010A, + "cdot", 0x010B, + "cedil", 0x00B8, + "cent", 0x00A2, + "CHcy", 0x0427, + "chcy", 0x0447, + "check", 0x2713, + "chi", 0x03C7, + "cir", 0x25CB, + "circ", 0x005E, + "cire", 0x2257, + "clubs", 0x2663, + "colon", 0x003A, + "colone", 0x2254, + "comma", 0x002C, + "commat", 0x0040, + "comp", 0x2201, + "compfn", 0x2218, + "cong", 0x2245, + "conint", 0x222E, + "coprod", 0x2210, + "copy", 0x00A9, + "copysr", 0x2117, + "cross", 0x2717, + "cuepr", 0x22DE, + "cuesc", 0x22DF, + "cularr", 0x21B6, + "cup", 0x222A, + "Cup", 0x22D3, + "cupre", 0x227C, + "curarr", 0x21B7, + "curren", 0x00A4, + "cuvee", 0x22CE, + "cuwed", 0x22CF, + NULL, 0 +}; static NameId namesD[]={ "dagger", 0x2020, @@ -1348,26 +1060,307 @@ NULL, 0 }; -// @todo@ order namesTable and names? by frequency -static NameId* namesTable[] = { - namesA, namesB, namesC, namesD, namesE, namesF, namesG, namesH, namesI, - namesJ, namesK, namesL, namesM, namesN, namesO, namesP, namesQ, namesR, - namesS, namesT, namesU, namesV, namesW, namesX, namesY, namesZ, NULL +// @todo@ order namesTable and names? by frequency +static NameId* namesTable[] = { + namesA, namesB, namesC, namesD, namesE, namesF, namesG, namesH, namesI, + namesJ, namesK, namesL, namesM, namesN, namesO, namesP, namesQ, namesR, + namesS, namesT, namesU, namesV, namesW, namesX, namesY, namesZ, NULL +}; + +int HtmlNamedEntity(unsigned char *p, int length) +{ + int tableIndex = tolower(*p) - 'a'; + if (tableIndex >= 0 && tableIndex < 26) { + NameId* names = namesTable[tableIndex]; + int i; + + for (i = 0; names[i].name; i++){ + if (strncmp(names[i].name, (char *)p, length) == 0){ + return names[i].value; + } + } + } + error("unrecognized character entity \"%.*s\"", length, p); + return -1; +} + +#else //TODO: Merge Walter's list with Thomas' + +static NameId names[] = +{ + // Entities + "quot", 34, + "amp", 38, + "lt", 60, + "gt", 62, + + "OElig", 338, + "oelig", 339, + "Scaron", 352, + "scaron", 353, + "Yuml", 376, + "circ", 710, + "tilde", 732, + "ensp", 8194, + "emsp", 8195, + "thinsp", 8201, + "zwnj", 8204, + "zwj", 8205, + "lrm", 8206, + "rlm", 8207, + "ndash", 8211, + "mdash", 8212, + "lsquo", 8216, + "rsquo", 8217, + "sbquo", 8218, + "ldquo", 8220, + "rdquo", 8221, + "bdquo", 8222, + "dagger", 8224, + "Dagger", 8225, + "permil", 8240, + "lsaquo", 8249, + "rsaquo", 8250, + "euro", 8364, + + // Latin-1 (ISO-8859-1) Entities + "nbsp", 160, + "iexcl", 161, + "cent", 162, + "pound", 163, + "curren", 164, + "yen", 165, + "brvbar", 166, + "sect", 167, + "uml", 168, + "copy", 169, + "ordf", 170, + "laquo", 171, + "not", 172, + "shy", 173, + "reg", 174, + "macr", 175, + "deg", 176, + "plusmn", 177, + "sup2", 178, + "sup3", 179, + "acute", 180, + "micro", 181, + "para", 182, + "middot", 183, + "cedil", 184, + "sup1", 185, + "ordm", 186, + "raquo", 187, + "frac14", 188, + "frac12", 189, + "frac34", 190, + "iquest", 191, + "Agrave", 192, + "Aacute", 193, + "Acirc", 194, + "Atilde", 195, + "Auml", 196, + "Aring", 197, + "AElig", 198, + "Ccedil", 199, + "Egrave", 200, + "Eacute", 201, + "Ecirc", 202, + "Euml", 203, + "Igrave", 204, + "Iacute", 205, + "Icirc", 206, + "Iuml", 207, + "ETH", 208, + "Ntilde", 209, + "Ograve", 210, + "Oacute", 211, + "Ocirc", 212, + "Otilde", 213, + "Ouml", 214, + "times", 215, + "Oslash", 216, + "Ugrave", 217, + "Uacute", 218, + "Ucirc", 219, + "Uuml", 220, + "Yacute", 221, + "THORN", 222, + "szlig", 223, + "agrave", 224, + "aacute", 225, + "acirc", 226, + "atilde", 227, + "auml", 228, + "aring", 229, + "aelig", 230, + "ccedil", 231, + "egrave", 232, + "eacute", 233, + "ecirc", 234, + "euml", 235, + "igrave", 236, + "iacute", 237, + "icirc", 238, + "iuml", 239, + "eth", 240, + "ntilde", 241, + "ograve", 242, + "oacute", 243, + "ocirc", 244, + "otilde", 245, + "ouml", 246, + "divide", 247, + "oslash", 248, + "ugrave", 249, + "uacute", 250, + "ucirc", 251, + "uuml", 252, + "yacute", 253, + "thorn", 254, + "yuml", 255, + + // Symbols and Greek letter entities + "fnof", 402, + "Alpha", 913, + "Beta", 914, + "Gamma", 915, + "Delta", 916, + "Epsilon", 917, + "Zeta", 918, + "Eta", 919, + "Theta", 920, + "Iota", 921, + "Kappa", 922, + "Lambda", 923, + "Mu", 924, + "Nu", 925, + "Xi", 926, + "Omicron", 927, + "Pi", 928, + "Rho", 929, + "Sigma", 931, + "Tau", 932, + "Upsilon", 933, + "Phi", 934, + "Chi", 935, + "Psi", 936, + "Omega", 937, + "alpha", 945, + "beta", 946, + "gamma", 947, + "delta", 948, + "epsilon", 949, + "zeta", 950, + "eta", 951, + "theta", 952, + "iota", 953, + "kappa", 954, + "lambda", 955, + "mu", 956, + "nu", 957, + "xi", 958, + "omicron", 959, + "pi", 960, + "rho", 961, + "sigmaf", 962, + "sigma", 963, + "tau", 964, + "upsilon", 965, + "phi", 966, + "chi", 967, + "psi", 968, + "omega", 969, + "thetasym", 977, + "upsih", 978, + "piv", 982, + "bull", 8226, + "hellip", 8230, + "prime", 8242, + "Prime", 8243, + "oline", 8254, + "frasl", 8260, + "weierp", 8472, + "image", 8465, + "real", 8476, + "trade", 8482, + "alefsym", 8501, + "larr", 8592, + "uarr", 8593, + "rarr", 8594, + "darr", 8595, + "harr", 8596, + "crarr", 8629, + "lArr", 8656, + "uArr", 8657, + "rArr", 8658, + "dArr", 8659, + "hArr", 8660, + "forall", 8704, + "part", 8706, + "exist", 8707, + "empty", 8709, + "nabla", 8711, + "isin", 8712, + "notin", 8713, + "ni", 8715, + "prod", 8719, + "sum", 8721, + "minus", 8722, + "lowast", 8727, + "radic", 8730, + "prop", 8733, + "infin", 8734, + "ang", 8736, + "and", 8743, + "or", 8744, + "cap", 8745, + "cup", 8746, + "int", 8747, + "there4", 8756, + "sim", 8764, + "cong", 8773, + "asymp", 8776, + "ne", 8800, + "equiv", 8801, + "le", 8804, + "ge", 8805, + "sub", 8834, + "sup", 8835, + "nsub", 8836, + "sube", 8838, + "supe", 8839, + "oplus", 8853, + "otimes", 8855, + "perp", 8869, + "sdot", 8901, + "lceil", 8968, + "rceil", 8969, + "lfloor", 8970, + "rfloor", 8971, + "lang", 9001, + "rang", 9002, + "loz", 9674, + "spades", 9824, + "clubs", 9827, + "hearts", 9829, + "diams", 9830, }; int HtmlNamedEntity(unsigned char *p, int length) { - int tableIndex = tolower(*p) - 'a'; - if (tableIndex >= 0 && tableIndex < 26) { - NameId* names = namesTable[tableIndex]; - int i; + int i; - for (i = 0; names[i].name; i++){ - if (strncmp(names[i].name, (char *)p, length) == 0){ - return names[i].value; - } - } + // BUG: this is a dumb, slow linear search + for (i = 0; i < sizeof(names) / sizeof(names[0]); i++) + { + // Entries are case sensitive + if (memcmp(names[i].name, (char *)p, length) == 0 && + !names[i].name[length]) + return names[i].value; } - error("unrecognized character entity \"%.*s\"", length, p); return -1; } + +#endif diff -uNr gdc-0.17/d/dmd/enum.c gdc-0.18/d/dmd/enum.c --- gdc-0.17/d/dmd/enum.c 2005-08-13 01:51:59.000000000 +0200 +++ gdc-0.18/d/dmd/enum.c 2006-03-12 23:08:56.000000000 +0100 @@ -109,13 +109,13 @@ { if (!scx->scopesym->symtab) scx->scopesym->symtab = new DsymbolTable(); - em->addMember(sce, scx->scopesym); + em->addMember(sce, scx->scopesym, 1); break; } } } else - em->addMember(sc, this); + em->addMember(sc, this, 1); if (first) { first = 0; @@ -146,29 +146,14 @@ //members->print(); } -Dsymbol *EnumDeclaration::oneMember() +int EnumDeclaration::oneMember(Dsymbol **ps) { - if (isAnonymous() && members && members->dim) - { - Dsymbol *s = (Dsymbol *)members->data[0]; - s = s->oneMember(); - - // Ignore any additional template instance symbols - for (int j = 1; j < members->dim; j++) - { Dsymbol *sx = (Dsymbol *)members->data[j]; - if (sx->isTemplateInstance()) - continue; - s = NULL; - break; - } - - if (s) - return s; - } - return this; + if (isAnonymous()) + return Dsymbol::oneMembers(members, ps); + return Dsymbol::oneMember(ps); } -void EnumDeclaration::toCBuffer(OutBuffer *buf) +void EnumDeclaration::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { int i; buf->writestring("enum "); @@ -179,7 +164,7 @@ if (memtype) { buf->writestring(": "); - memtype->toCBuffer(buf, NULL); + memtype->toCBuffer(buf, NULL, hgs); } if (!members) { @@ -195,8 +180,8 @@ EnumMember *em = ((Dsymbol *)members->data[i])->isEnumMember(); if (!em) continue; - buf->writestring(" "); - em->toCBuffer(buf); + //buf->writestring(" "); + em->toCBuffer(buf, hgs); buf->writeByte(','); buf->writenl(); } @@ -240,13 +225,13 @@ return em; } -void EnumMember::toCBuffer(OutBuffer *buf) +void EnumMember::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { buf->writestring(ident->toChars()); if (value) { buf->writestring(" = "); - value->toCBuffer(buf); + value->toCBuffer(buf, hgs); } } diff -uNr gdc-0.17/d/dmd/enum.h gdc-0.18/d/dmd/enum.h --- gdc-0.17/d/dmd/enum.h 2005-10-02 16:17:55.000000000 +0200 +++ gdc-0.18/d/dmd/enum.h 2006-03-12 23:08:56.000000000 +0100 @@ -20,6 +20,9 @@ struct Identifier; struct Type; struct Expression; +#ifdef _DH +struct HdrGenState; +#endif struct EnumDeclaration : ScopeDsymbol { @@ -32,8 +35,8 @@ EnumDeclaration(Loc loc, Identifier *id, Type *memtype); Dsymbol *syntaxCopy(Dsymbol *s); void semantic(Scope *sc); - Dsymbol *oneMember(); - void toCBuffer(OutBuffer *buf); + int oneMember(Dsymbol **ps); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); Type *getType(); char *kind(); @@ -54,7 +57,7 @@ EnumMember(Loc loc, Identifier *id, Expression *value); Dsymbol *syntaxCopy(Dsymbol *s); - void toCBuffer(OutBuffer *buf); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); char *kind(); void emitComment(Scope *sc); diff -uNr gdc-0.17/d/dmd/expression.c gdc-0.18/d/dmd/expression.c --- gdc-0.17/d/dmd/expression.c 2005-11-28 05:17:52.000000000 +0100 +++ gdc-0.18/d/dmd/expression.c 2006-05-14 05:13:10.000000000 +0200 @@ -1,5 +1,5 @@ -// Copyright (c) 1999-2005 by Digital Mars +// Copyright (c) 1999-2006 by Digital Mars // All Rights Reserved // written by Walter Bright // www.digitalmars.com @@ -26,6 +26,14 @@ #define integer_t dmd_integer_t #endif +#if __GNUC__ +extern "C" long double strtold(const char *p,char **endp); +#endif + +#if _WIN32 && __DMC__ +extern "C" char * __cdecl __locale_decpoint; +#endif + #if IN_GCC #include "mem.h" #elif _WIN32 @@ -49,11 +57,137 @@ #include "dsymbol.h" #include "module.h" #include "attrib.h" +#include "hdrgen.h" Expression *createTypeInfoArray(Scope *sc, Expression *args[], int dim); #define LOGSEMANTIC 0 +/********************************** + * Set operator precedence for each operator. + */ + +// Operator precedence - greater values are higher precedence + +enum PREC +{ + PREC_zero, + PREC_expr, + PREC_assign, + PREC_cond, + PREC_oror, + PREC_andand, + PREC_or, + PREC_xor, + PREC_and, + PREC_equal, + PREC_rel, + PREC_shift, + PREC_add, + PREC_mul, + PREC_unary, + PREC_primary, +}; + +enum PREC precedence[TOKMAX]; + +void initPrecedence() +{ + precedence[TOKimport] = PREC_primary; + precedence[TOKidentifier] = PREC_primary; + precedence[TOKthis] = PREC_primary; + precedence[TOKsuper] = PREC_primary; + precedence[TOKint64] = PREC_primary; + precedence[TOKfloat64] = PREC_primary; + precedence[TOKnull] = PREC_primary; + precedence[TOKstring] = PREC_primary; + precedence[TOKtypedot] = PREC_primary; + precedence[TOKtypeid] = PREC_primary; + precedence[TOKis] = PREC_primary; + precedence[TOKassert] = PREC_primary; + precedence[TOKfunction] = PREC_primary; + + // post + precedence[TOKdotti] = PREC_primary; + precedence[TOKdot] = PREC_primary; +// precedence[TOKarrow] = PREC_primary; + precedence[TOKplusplus] = PREC_primary; + precedence[TOKminusminus] = PREC_primary; + precedence[TOKcall] = PREC_primary; + precedence[TOKslice] = PREC_primary; + precedence[TOKarray] = PREC_primary; + + precedence[TOKaddress] = PREC_unary; + precedence[TOKstar] = PREC_unary; + precedence[TOKneg] = PREC_unary; + precedence[TOKuadd] = PREC_unary; + precedence[TOKnot] = PREC_unary; + precedence[TOKtobool] = PREC_add; + precedence[TOKtilde] = PREC_unary; + precedence[TOKdelete] = PREC_unary; + precedence[TOKnew] = PREC_unary; + precedence[TOKcast] = PREC_unary; + + precedence[TOKmul] = PREC_mul; + precedence[TOKdiv] = PREC_mul; + precedence[TOKmod] = PREC_mul; + + precedence[TOKadd] = PREC_add; + precedence[TOKmin] = PREC_add; + precedence[TOKcat] = PREC_add; + + precedence[TOKshl] = PREC_shift; + precedence[TOKshr] = PREC_shift; + precedence[TOKushr] = PREC_shift; + + precedence[TOKlt] = PREC_rel; + precedence[TOKle] = PREC_rel; + precedence[TOKgt] = PREC_rel; + precedence[TOKge] = PREC_rel; + precedence[TOKunord] = PREC_rel; + precedence[TOKlg] = PREC_rel; + precedence[TOKleg] = PREC_rel; + precedence[TOKule] = PREC_rel; + precedence[TOKul] = PREC_rel; + precedence[TOKuge] = PREC_rel; + precedence[TOKug] = PREC_rel; + precedence[TOKue] = PREC_rel; + precedence[TOKin] = PREC_rel; + + precedence[TOKequal] = PREC_equal; + precedence[TOKnotequal] = PREC_equal; + precedence[TOKidentity] = PREC_equal; + precedence[TOKnotidentity] = PREC_equal; + + precedence[TOKand] = PREC_and; + + precedence[TOKxor] = PREC_xor; + + precedence[TOKor] = PREC_or; + + precedence[TOKandand] = PREC_andand; + + precedence[TOKoror] = PREC_oror; + + precedence[TOKquestion] = PREC_cond; + + precedence[TOKassign] = PREC_assign; + precedence[TOKaddass] = PREC_assign; + precedence[TOKminass] = PREC_assign; + precedence[TOKcatass] = PREC_assign; + precedence[TOKmulass] = PREC_assign; + precedence[TOKdivass] = PREC_assign; + precedence[TOKmodass] = PREC_assign; + precedence[TOKshlass] = PREC_assign; + precedence[TOKshrass] = PREC_assign; + precedence[TOKushrass] = PREC_assign; + precedence[TOKandass] = PREC_assign; + precedence[TOKorass] = PREC_assign; + precedence[TOKxorass] = PREC_assign; + + precedence[TOKcomma] = PREC_expr; +} + /***************************************** * Determine if 'this' is available. * If it is, return the FuncDeclaration that has it. @@ -127,7 +261,7 @@ * Perform semantic() on an array of Expressions. */ -void arrayExpressionSemantic(Array *a, Scope *sc) +void arrayExpressionSemantic(Expressions *a, Scope *sc) { if (a) { @@ -144,7 +278,7 @@ * Preprocess arguments to function. */ -void preFunctionArguments(Loc loc, Scope *sc, Array *arguments) +void preFunctionArguments(Loc loc, Scope *sc, Expressions *arguments) { if (arguments) { @@ -153,6 +287,10 @@ if (!arg->type) { +#ifdef DEBUG + if (!global.gag) + printf("1: \n"); +#endif arg->error("%s is not an expression", arg->toChars()); arg = new IntegerExp(arg->loc, 0, Type::tint32); } @@ -183,7 +321,7 @@ * 4) add hidden _arguments[] argument */ -void functionArguments(Loc loc, Scope *sc, TypeFunction *tf, Array *arguments) +void functionArguments(Loc loc, Scope *sc, TypeFunction *tf, Expressions *arguments) { unsigned nargs; unsigned nproto; @@ -290,7 +428,7 @@ { /* Set arg to be: * new Tclass(arg0, arg1, ..., argn) */ - Array *args = new Array(); + Expressions *args = new Expressions(); args->setDim(nargs - i); for (int u = i; u < nargs; u++) args->data[u - i] = arguments->data[u]; @@ -378,7 +516,28 @@ } } -void argsToCBuffer(OutBuffer *buf, Array *arguments) +/************************************************** + * Write expression out to buf, but wrap it + * in ( ) if its precedence is less than pr. + */ + +void expToCBuffer(OutBuffer *buf, HdrGenState *hgs, Expression *e, enum PREC pr) +{ + if (precedence[e->op] < pr) + { + buf->writeByte('('); + e->toCBuffer(buf, hgs); + buf->writeByte(')'); + } + else + e->toCBuffer(buf, hgs); +} + +/************************************************** + * Write out argument list to buf. + */ + +void argsToCBuffer(OutBuffer *buf, Expressions *arguments, HdrGenState *hgs) { int i; if (arguments) @@ -388,7 +547,28 @@ if (i) buf->writeByte(','); - arg->toCBuffer(buf); + expToCBuffer(buf, hgs, arg, PREC_assign); + } + } +} + +/************************************************** + * Write out argument types to buf. + */ + +void argExpTypesToCBuffer(OutBuffer *buf, Expressions *arguments, HdrGenState *hgs) +{ + if (arguments) + { OutBuffer argbuf; + + for (size_t i = 0; i < arguments->dim; i++) + { Expression *arg = (Expression *)arguments->data[i]; + + if (i) + buf->writeByte(','); + argbuf.reset(); + arg->type->toCBuffer2(&argbuf, NULL, hgs); + buf->write(&argbuf); } } } @@ -419,7 +599,7 @@ { Expression *e; if (!size) - fprintf(stderr, "No expression copy for: %s\n", toChars()); + fprintf(stdmsg, "No expression copy for: %s\n", toChars()); e = (Expression *)mem.malloc(size); return (Expression *)memcpy(e, this, size); } @@ -443,15 +623,17 @@ void Expression::print() { - fprintf(stderr, "%s\n", toChars()); - fflush(stderr); + fprintf(stdmsg, "%s\n", toChars()); + fflush(stdmsg); } char *Expression::toChars() { OutBuffer *buf; + HdrGenState hgs; + memset(&hgs, 0, sizeof(hgs)); buf = new OutBuffer(); - toCBuffer(buf); + toCBuffer(buf, &hgs); return buf->toChars(); } @@ -462,16 +644,16 @@ char *p = loc.toChars(); if (*p) - fprintf(stderr, "%s: ", p); + fprintf(stdmsg, "%s: ", p); mem.free(p); va_list ap; va_start(ap, format); - vfprintf(stderr, format, ap); + vfprintf(stdmsg, format, ap); va_end(ap); - fprintf(stderr, "\n"); - fflush(stderr); + fprintf(stdmsg, "\n"); + fflush(stdmsg); } global.errors++; @@ -534,13 +716,15 @@ #endif } -void Expression::toCBuffer(OutBuffer *buf) +void Expression::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { buf->writestring(Token::toChars(op)); } void Expression::toMangleBuffer(OutBuffer *buf) { + fprintf(stdmsg, "global.errors = %d, gag = %d\n", global.errors, global.gag); + dump(0); assert(0); } @@ -580,6 +764,12 @@ error("'%s' is not a scalar, it is a %s", toChars(), type->toChars()); } +void Expression::checkNoBool() +{ + if (type->toBasetype()->ty == Tbool) + error("operation not allowed on bool '%s'", toChars()); +} + Expression *Expression::checkIntegral() { if (!type->isintegral()) @@ -600,6 +790,19 @@ s->checkDeprecated(loc, sc); } +/******************************** + * Check for expressions that have no use. + * Input: + * flag !=0 means we want the result + */ + +void Expression::checkSideEffect(int flag) +{ + if (!flag) + error("%s has no effect in expression (%s)", + Token::toChars(op), toChars()); +} + /***************************** * Check that expression can be tested for true or false. */ @@ -614,7 +817,9 @@ #endif if (!type->checkBoolean()) + { error("expression %s of type %s does not have a boolean value", toChars(), type->toChars()); + } return this; } @@ -689,12 +894,12 @@ return FALSE; } -Array *Expression::arraySyntaxCopy(Array *exps) -{ Array *a = NULL; +Expressions *Expression::arraySyntaxCopy(Expressions *exps) +{ Expressions *a = NULL; if (exps) { - a = new Array(); + a = new Expressions(); a->setDim(exps->dim); for (int i = 0; i < a->dim; i++) { Expression *e = (Expression *)exps->data[i]; @@ -711,6 +916,7 @@ IntegerExp::IntegerExp(Loc loc, integer_t value, Type *type) : Expression(loc, TOKint64, sizeof(IntegerExp)) { + //printf("IntegerExp(value = %lld, type = '%s')\n", value, type ? type->toChars() : ""); if (type && !type->isscalar()) { error("integral constant must be scalar type, not %s", type->toChars()); @@ -754,7 +960,8 @@ { switch (t->ty) { - case Tbit: value = (value != 0); break; + case Tbit: + case Tbool: value = (value != 0); break; case Tint8: value = (d_int8) value; break; case Tchar: case Tuns8: value = (d_uns8) value; break; @@ -850,20 +1057,91 @@ return this; } -void IntegerExp::toCBuffer(OutBuffer *buf) +void IntegerExp::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { + integer_t v = toInteger(); + if (type) - { - if (type->ty == Tenum) - { TypeEnum *te = (TypeEnum *)type; + { Type *t = type; + + L1: + switch (t->ty) + { + case Tenum: + { TypeEnum *te = (TypeEnum *)t; + buf->printf("cast(%s)", te->sym->toChars()); + t = te->sym->memtype; + goto L1; + } - buf->printf("cast(%s)", te->sym->toChars()); + case Ttypedef: + { TypeTypedef *tt = (TypeTypedef *)t; + buf->printf("cast(%s)", tt->sym->toChars()); + t = tt->sym->basetype; + goto L1; + } + + case Twchar: // BUG: need to cast(wchar) + case Tdchar: // BUG: need to cast(dchar) + if ((uinteger_t)v > 0xFF) + { + buf->printf("'\\U%08x'", v); + break; + } + case Tchar: + if (isprint(v) && v != '\\') + buf->printf("'%c'", (int)v); + else + buf->printf("'\\x%02x'", (int)v); + break; + + case Tint8: + buf->writestring("cast(byte)"); + goto L2; + + case Tint16: + buf->writestring("cast(short)"); + goto L2; + + case Tint32: + L2: + buf->printf("%ld", (int)v); + break; + + case Tuns8: + buf->writestring("cast(ubyte)"); + goto L3; + + case Tuns16: + buf->writestring("cast(ushort)"); + goto L3; + + case Tuns32: + L3: + buf->printf("%ldu", (unsigned)v); + break; + + case Tint64: + buf->printf("%lldL", v); + break; + + case Tuns64: + buf->printf("%lldLU", v); + break; + + case Tbit: + case Tbool: + buf->writestring((char *)(v ? "true" : "false")); + break; + + default: + assert(0); } } - if (value & 0x8000000000000000LL) - buf->printf("0x%llx", value); + else if (v & 0x8000000000000000LL) + buf->printf("0x%llx", v); else - buf->printf("%lld", value); + buf->printf("%lld", v); } void IntegerExp::toMangleBuffer(OutBuffer *buf) @@ -936,6 +1214,22 @@ #endif } +int RealExp::equals(Object *o) +{ RealExp *ne; + + if (this == o || + (((Expression *)o)->op == TOKfloat64 && + ((ne = (RealExp *)o), type->equals(ne->type)) && +#ifdef IN_GCC + value.isIdenticalTo(ne->value) +#else + memcmp(&value, &ne->value, sizeof(value)) == 0 +#endif + )) + return 1; + return 0; +} + Expression *RealExp::semantic(Scope *sc) { if (!type) @@ -955,19 +1249,72 @@ #endif } -void RealExp::toCBuffer(OutBuffer *buf) +void floatToBuffer(OutBuffer *buf, Type *type, const real_t & value) { + /* In order to get an exact representation, try converting it + * to decimal then back again. If it matches, use it. + * If it doesn't, fall back to hex, which is + * always exact. + */ + char buffer[48]; #ifdef IN_GCC - char buffer[8 + 3 * sizeof(value) + 1]; + real_t parsed_value; + value.format(buffer, sizeof(buffer)); - buf->writestring(buffer); + parsed_value = real_t::parse(buffer, real_t::LongDouble); + if (parsed_value.isIdenticalTo( value )) + buf->writestring(buffer); + else + { + value.formatHex(buffer, sizeof(buffer)); + buf->writestring(buffer); + } +#else + sprintf(buffer, "%Lg", value); + assert(strlen(buffer) < sizeof(buffer)); +#if _WIN32 && __DMC__ + char *save = __locale_decpoint; + __locale_decpoint = "."; + real_t r = strtold(buffer, NULL); + __locale_decpoint = save; #else - buf->printf("%Lg", value); + real_t r = strtold(buffer, NULL); #endif - if (type->isimaginary()) - buf->writeByte('i'); + if (r == value) // if exact duplication + buf->writestring(buffer); + else + buf->printf("%La", value); // ensure exact duplication +#endif + + if (type) + { + Type *t = type->toBasetype(); + switch (t->ty) + { + case Tfloat32: + case Timaginary32: + case Tcomplex32: + buf->writeByte('F'); + break; + + case Tfloat80: + case Timaginary80: + case Tcomplex80: + buf->writeByte('L'); + break; + + default: + break; + } + if (t->isimaginary()) + buf->writeByte('i'); + } } +void RealExp::toCBuffer(OutBuffer *buf, HdrGenState *hgs) +{ + floatToBuffer(buf, type, value); +} void RealExp::toMangleBuffer(OutBuffer *buf) { @@ -1012,12 +1359,20 @@ integer_t ComplexExp::toInteger() { +#ifdef IN_GCC return (sinteger_t) toReal().toInt(); +#else + return (sinteger_t) toReal(); +#endif } uinteger_t ComplexExp::toUInteger() { +#ifdef IN_GCC return (uinteger_t) toReal().toInt(); +#else + return (uinteger_t) toReal(); +#endif } real_t ComplexExp::toReal() @@ -1035,6 +1390,23 @@ return value; } +int ComplexExp::equals(Object *o) +{ ComplexExp *ne; + + if (this == o || + (((Expression *)o)->op == TOKcomplex80 && + ((ne = (ComplexExp *)o), type->equals(ne->type)) && +#ifdef IN_GCC + (value.re.isIdenticalTo(ne->value.re) && + value.im.isIdenticalTo(ne->value.im)) +#else + memcmp(&value, &ne->value, sizeof(value)) == 0 +#endif + )) + return 1; + return 0; +} + Expression *ComplexExp::semantic(Scope *sc) { if (!type) @@ -1046,12 +1418,17 @@ int ComplexExp::isBool(int result) { - return result ? (value != 0) - : (value == 0); + if (result) + return (bool)(value); + else + return !value; } -void ComplexExp::toCBuffer(OutBuffer *buf) +void ComplexExp::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { + /* Print as: + * (re+imi) + */ #ifdef IN_GCC char buf1[sizeof(value) * 3 + 8 + 1]; char buf2[sizeof(value) * 3 + 8 + 1]; @@ -1059,7 +1436,11 @@ cimagl(value).format(buf2, sizeof(buf2)); buf->printf("(%s+%si)", buf1, buf2); #else - buf->printf("(%Lg+%Lgi)", creall(value), cimagl(value)); + buf->writeByte('('); + floatToBuffer(buf, type, creall(value)); + buf->writeByte('+'); + floatToBuffer(buf, type, cimagl(value)); + buf->writestring("i)"); #endif } @@ -1131,9 +1512,12 @@ return ident->toChars(); } -void IdentifierExp::toCBuffer(OutBuffer *buf) +void IdentifierExp::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { - buf->writestring(ident->toChars()); + if (hgs->hdrgen) + buf->writestring(ident->toHChars2()); + else + buf->writestring(ident->toChars()); } Expression *IdentifierExp::toLvalue(Expression *e) @@ -1189,7 +1573,7 @@ if (!s->isFuncDeclaration()) // functions are checked after overloading checkDeprecated(sc, s); s = s->toAlias(); - //printf("s = '%s', s->kind = '%s'\n", s->toChars(), s->kind()); + //printf("s = '%s', s->kind = '%s', s->needThis() = %p\n", s->toChars(), s->kind(), s->needThis()); if (!s->isFuncDeclaration()) checkDeprecated(sc, s); @@ -1197,15 +1581,18 @@ thiscd = sc->func->parent->isClassDeclaration(); // BUG: This should happen after overload resolution for functions, not before - if (s->needThis() && hasThis(sc) /*&& !s->isFuncDeclaration()*/) + if (s->needThis()) { - // Supply an implicit 'this', as in - // this.ident + if (hasThis(sc) /*&& !s->isFuncDeclaration()*/) + { + // Supply an implicit 'this', as in + // this.ident - DotVarExp *de; + DotVarExp *de; - de = new DotVarExp(loc, new ThisExp(loc), s->isDeclaration()); - return de->semantic(sc); + de = new DotVarExp(loc, new ThisExp(loc), s->isDeclaration()); + return de->semantic(sc); + } } em = s->isEnumMember(); @@ -1311,7 +1698,7 @@ } TemplateInstance *ti = s->isTemplateInstance(); - if (ti) + if (ti && !global.errors) { ti->semantic(sc); s = ti->inst->toAlias(); if (!s->isTemplateInstance()) @@ -1321,6 +1708,14 @@ return e; } + TemplateDeclaration *td = s->isTemplateDeclaration(); + if (td) + { + e = new TemplateExp(loc, td); + e = e->semantic(sc); + return e; + } + error("%s '%s' is not a variable", s->kind(), s->toChars()); type = Type::terror; return this; @@ -1331,7 +1726,7 @@ return s->toChars(); } -void DsymbolExp::toCBuffer(OutBuffer *buf) +void DsymbolExp::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { buf->writestring(s->toChars()); } @@ -1399,7 +1794,7 @@ return result ? TRUE : FALSE; } -void ThisExp::toCBuffer(OutBuffer *buf) +void ThisExp::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { buf->writestring("this"); } @@ -1472,7 +1867,7 @@ return this; } -void SuperExp::toCBuffer(OutBuffer *buf) +void SuperExp::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { buf->writestring("super"); } @@ -1501,7 +1896,7 @@ return result ? FALSE : TRUE; } -void NullExp::toCBuffer(OutBuffer *buf) +void NullExp::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { buf->writestring("null"); } @@ -1550,9 +1945,12 @@ char *StringExp::toChars() { OutBuffer buf; + HdrGenState hgs; char *p; - toCBuffer(&buf); + memset(&hgs, 0, sizeof(hgs)); + toCBuffer(&buf, &hgs); + buf.writeByte(0); p = (char *)buf.data; buf.data = NULL; return p; @@ -1604,6 +2002,8 @@ else { buffer.writeUTF16(c); newlen++; + if (c >= 0x10000) + newlen++; } } buffer.writeUTF16(0); @@ -1684,7 +2084,7 @@ return result ? TRUE : FALSE; } -void StringExp::toCBuffer(OutBuffer *buf) +void StringExp::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { unsigned i; buf->writeByte('"'); @@ -1714,6 +2114,7 @@ break; case '"': + case '\\': buf->writeByte('\\'); default: if (isprint(c)) @@ -1813,20 +2214,15 @@ #if LOGSEMANTIC printf("TypeDotIdExp::semantic()\n"); #endif -#if 0 - type = type->semantic(loc, sc); - e = type->getProperty(loc, ident); -#else e = new DotIdExp(loc, new TypeExp(loc, type), ident); -#endif e = e->semantic(sc); return e; } -void TypeDotIdExp::toCBuffer(OutBuffer *buf) +void TypeDotIdExp::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { buf->writeByte('('); - type->toCBuffer(buf, NULL); + type->toCBuffer(buf, NULL, hgs); buf->writeByte(')'); buf->writeByte('.'); buf->writestring(ident->toChars()); @@ -1843,9 +2239,9 @@ this->type = type; } -void TypeExp::toCBuffer(OutBuffer *buf) +void TypeExp::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { - type->toCBuffer(buf, NULL); + type->toCBuffer(buf, NULL, hgs); } /************************************************************/ @@ -1874,20 +2270,23 @@ #endif Lagain: ti = sds->isTemplateInstance(); - if (ti) -#if 0 - { ti->semantic(sc); - sds = ti->inst; - } -#else + if (ti && !global.errors) { Dsymbol *s; ti->semantic(sc); s = ti->inst->toAlias(); sds2 = s->isScopeDsymbol(); if (!sds2) - { + { Expression *e; + //printf("s = %s, '%s'\n", s->kind(), s->toChars()); - Expression *e = new DsymbolExp(loc, s); + if (ti->withsym) + { + // Same as wthis.s + e = new VarExp(loc, ti->withsym->withstate->wthis); + e = new DotVarExp(loc, e, s->isDeclaration()); + } + else + e = new DsymbolExp(loc, s); e = e->semantic(sc); //printf("-1ScopeExp::semantic()\n"); return e; @@ -1902,28 +2301,51 @@ else { //printf("sds = %s, '%s'\n", sds->kind(), sds->toChars()); + //printf("\tparent = '%s'\n", sds->parent->toChars()); sds->semantic(sc); } -#endif type = Type::tvoid; //printf("-2ScopeExp::semantic()\n"); return this; } -void ScopeExp::toCBuffer(OutBuffer *buf) +void ScopeExp::toCBuffer(OutBuffer *buf, HdrGenState *hgs) +{ + if (sds->isTemplateInstance()) + { + sds->toCBuffer(buf, hgs); + } + else + { + buf->writestring(sds->kind()); + buf->writestring(" "); + buf->writestring(sds->toChars()); + } +} + +/********************** TemplateExp **************************************/ + +// Mainly just a placeholder + +TemplateExp::TemplateExp(Loc loc, TemplateDeclaration *td) + : Expression(loc, TOKtemplate, sizeof(TemplateExp)) +{ + //printf("TemplateExp(): %s\n", td->toChars()); + this->td = td; +} + +void TemplateExp::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { - buf->writestring(sds->kind()); - buf->writestring(" "); - buf->writestring(sds->toChars()); + buf->writestring(td->toChars()); } /********************** NewExp **************************************/ -NewExp::NewExp(Loc loc, Array *newargs, Type *type, Array *arguments) +NewExp::NewExp(Loc loc, Expressions *newargs, Type *newtype, Expressions *arguments) : Expression(loc, TOKnew, sizeof(NewExp)) { this->newargs = newargs; - this->type = type; + this->newtype = newtype; this->arguments = arguments; member = NULL; allocator = NULL; @@ -1932,7 +2354,7 @@ Expression *NewExp::syntaxCopy() { return new NewExp(loc, arraySyntaxCopy(newargs), - type->syntaxCopy(), arraySyntaxCopy(arguments)); + newtype->syntaxCopy(), arraySyntaxCopy(arguments)); } @@ -1942,9 +2364,11 @@ #if LOGSEMANTIC printf("NewExp::semantic() %s\n", toChars()); - printf("type: %s\n", type->toChars()); + printf("newtype: %s\n", newtype->toChars()); #endif - type = type->semantic(loc, sc); + if (type) + return this; + type = newtype->semantic(loc, sc); tb = type->toBasetype(); //printf("tb: %s, deco = %s\n", tb->toChars(), tb->deco); @@ -1994,7 +2418,7 @@ type = tf->next; if (!arguments) - arguments = new Array(); + arguments = new Expressions(); functionArguments(loc, sc, tf, arguments); } else @@ -2011,7 +2435,7 @@ // Prepend the uint size argument to newargs[] e = new IntegerExp(loc, cd->size(loc), Type::tuns32); if (!newargs) - newargs = new Array(); + newargs = new Expressions(); newargs->shift(e); f = f->overloadResolve(loc, newargs); @@ -2045,7 +2469,7 @@ // Prepend the uint size argument to newargs[] e = new IntegerExp(loc, sd->size(loc), Type::tuns32); if (!newargs) - newargs = new Array(); + newargs = new Expressions(); newargs->shift(e); f = f->overloadResolve(loc, newargs); @@ -2093,28 +2517,32 @@ return this; } -void NewExp::toCBuffer(OutBuffer *buf) +void NewExp::checkSideEffect(int flag) +{ +} + +void NewExp::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { int i; buf->writestring("new "); if (newargs && newargs->dim) { buf->writeByte('('); - argsToCBuffer(buf, newargs); + argsToCBuffer(buf, newargs, hgs); buf->writeByte(')'); } - type->toCBuffer(buf, NULL); + newtype->toCBuffer(buf, NULL, hgs); if (arguments && arguments->dim) { buf->writeByte('('); - argsToCBuffer(buf, arguments); + argsToCBuffer(buf, arguments, hgs); buf->writeByte(')'); } } /********************** NewAnonClassExp **************************************/ -NewAnonClassExp::NewAnonClassExp(Loc loc, Array *newargs, ClassDeclaration *cd, Array *arguments) +NewAnonClassExp::NewAnonClassExp(Loc loc, Expressions *newargs, ClassDeclaration *cd, Expressions *arguments) : Expression(loc, TOKnewanonclass, sizeof(NewAnonClassExp)) { this->newargs = newargs; @@ -2147,24 +2575,32 @@ return c->semantic(sc); } -void NewAnonClassExp::toCBuffer(OutBuffer *buf) +void NewAnonClassExp::checkSideEffect(int flag) +{ +} + +void NewAnonClassExp::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { int i; buf->writestring("new"); if (newargs && newargs->dim) { buf->writeByte('('); - argsToCBuffer(buf, newargs); + argsToCBuffer(buf, newargs, hgs); buf->writeByte(')'); } - buf->writestring(" class"); + buf->writestring(" class "); if (arguments && arguments->dim) { buf->writeByte('('); - argsToCBuffer(buf, arguments); + argsToCBuffer(buf, arguments, hgs); buf->writeByte(')'); } - buf->writestring(" { }"); + //buf->writestring(" { }"); + if (cd) + { + cd->toCBuffer(buf, hgs); + } } /********************** SymOffExp **************************************/ @@ -2202,12 +2638,12 @@ } } -void SymOffExp::toCBuffer(OutBuffer *buf) +void SymOffExp::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { if (offset) - buf->printf("(&%s+%u)", var->toChars(), offset); + buf->printf("(& %s+%u)", var->toChars(), offset); else - buf->printf("&%s", var->toChars()); + buf->printf("& %s", var->toChars()); } /******************************** VarExp **************************/ @@ -2252,9 +2688,9 @@ return ei->exp->implicitCastTo(type); } } - if (!v->isDataseg() && v->parent != sc->parent) + if (!v->isDataseg() && v->parent != sc->parent && v->parent) { - FuncDeclaration *fdv = v->parent->isFuncDeclaration(); + FuncDeclaration *fdv = v->toParent()->isFuncDeclaration(); FuncDeclaration *fdthis = sc->parent->isFuncDeclaration(); if (fdv && fdthis) @@ -2281,7 +2717,7 @@ return var->toChars(); } -void VarExp::toCBuffer(OutBuffer *buf) +void VarExp::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { buf->writestring(var->toChars()); } @@ -2398,7 +2834,7 @@ return fd->toChars(); } -void FuncExp::toCBuffer(OutBuffer *buf) +void FuncExp::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { buf->writestring(fd->toChars()); } @@ -2458,7 +2894,8 @@ error("declaration %s is already defined", s->toPrettyChars()); } if (!s->isVarDeclaration()) - { declaration->semantic(sc); + { + declaration->semantic(sc); s->parent = sc->parent; } if (!global.errors) @@ -2477,9 +2914,13 @@ return this; } -void DeclarationExp::toCBuffer(OutBuffer *buf) +void DeclarationExp::checkSideEffect(int flag) +{ +} + +void DeclarationExp::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { - declaration->toCBuffer(buf); + declaration->toCBuffer(buf, hgs); } @@ -2513,10 +2954,10 @@ return e; } -void TypeidExp::toCBuffer(OutBuffer *buf) +void TypeidExp::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { buf->writestring("typeid("); - typeidType->toCBuffer(buf, NULL); + typeidType->toCBuffer(buf, NULL, hgs); buf->writeByte(')'); } @@ -2536,7 +2977,11 @@ return this; } -void HaltExp::toCBuffer(OutBuffer *buf) +void HaltExp::checkSideEffect(int flag) +{ +} + +void HaltExp::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { buf->writestring("halt"); } @@ -2567,6 +3012,7 @@ Expression *IftypeExp::semantic(Scope *sc) { Type *tded; + //printf("IftypeExp::semantic()\n"); if (id && !(sc->flags & SCOPEstaticif)) error("can only declare type aliases within static if conditionals"); @@ -2653,7 +3099,7 @@ MATCH m; TemplateTypeParameter tp(loc, id, NULL, NULL); - Array parameters; + TemplateParameters parameters; parameters.setDim(1); parameters.data[0] = (void *)&tp; @@ -2661,7 +3107,7 @@ dedtypes.setDim(1); dedtypes.data[0] = NULL; - m = targ->deduceType(tspec, ¶meters, &dedtypes); + m = targ->deduceType(NULL, tspec, ¶meters, &dedtypes); if (m == MATCHnomatch || (m != MATCHexact && tok == TOKequal)) goto Lno; @@ -2709,7 +3155,7 @@ s->semantic(sc); sc->insert(s); if (sc->sd) - s->addMember(sc, sc->sd); + s->addMember(sc, sc->sd, 1); } return new IntegerExp(1); @@ -2717,17 +3163,17 @@ return new IntegerExp(0); } -void IftypeExp::toCBuffer(OutBuffer *buf) +void IftypeExp::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { buf->writestring("is("); - targ->toCBuffer(buf, id); + targ->toCBuffer(buf, id, hgs); if (tspec) { if (tok == TOKcolon) buf->writestring(" : "); else buf->writestring(" == "); - tspec->toCBuffer(buf, NULL); + tspec->toCBuffer(buf, NULL, hgs); } buf->writeByte(')'); } @@ -2760,10 +3206,10 @@ return this; } -void UnaExp::toCBuffer(OutBuffer *buf) +void UnaExp::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { buf->writestring(Token::toChars(op)); - e1->toCBuffer(buf); + expToCBuffer(buf, hgs, e1, precedence[op]); } /************************************************************/ @@ -2832,12 +3278,18 @@ e1 = e1->modifiableLvalue(sc, NULL); e1->checkScalar(); type = e1->type; + if (type->toBasetype()->ty == Tbool) + { + error("operator not allowed on bool expression %s", toChars()); + } typeCombine(); e1->checkArithmetic(); e2->checkArithmetic(); if (op == TOKmodass && e2->type->iscomplex()) - error("cannot perform modulo complex arithmetic"); + { error("cannot perform modulo complex arithmetic"); + return new IntegerExp(0); + } } return this; } @@ -2857,6 +3309,11 @@ e1 = e1->modifiableLvalue(sc, NULL); e1->checkScalar(); type = e1->type; + if (type->toBasetype()->ty == Tbool) + { + e2 = e2->implicitCastTo(type); + } + typeCombine(); e1->checkIntegral(); e2->checkIntegral(); @@ -2864,14 +3321,38 @@ return this; } +void BinExp::checkSideEffect(int flag) +{ + if (op == TOKplusplus || + op == TOKminusminus || + op == TOKassign || + op == TOKaddass || + op == TOKminass || + op == TOKcatass || + op == TOKmulass || + op == TOKdivass || + op == TOKmodass || + op == TOKshlass || + op == TOKshrass || + op == TOKushrass || + op == TOKandass || + op == TOKorass || + op == TOKxorass || + op == TOKoror || + op == TOKandand || + op == TOKin || + op == TOKremove) + return; + Expression::checkSideEffect(flag); +} -void BinExp::toCBuffer(OutBuffer *buf) +void BinExp::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { - e1->toCBuffer(buf); + expToCBuffer(buf, hgs, e1, precedence[op]); buf->writeByte(' '); buf->writestring(Token::toChars(op)); buf->writeByte(' '); - e2->toCBuffer(buf); + expToCBuffer(buf, hgs, e2, (enum PREC)(precedence[op] + 1)); } int BinExp::isunsigned() @@ -2879,6 +3360,13 @@ return e1->type->isunsigned() || e2->type->isunsigned(); } +void BinExp::incompatibleTypes() +{ + error("incompatible types for ((%s) %s (%s)): '%s' and '%s'", + e1->toChars(), Token::toChars(op), e2->toChars(), + e1->type->toChars(), e2->type->toChars()); +} + /************************************************************/ AssertExp::AssertExp(Loc loc, Expression *e) @@ -2894,6 +3382,7 @@ UnaExp::semantic(sc); e1 = resolveProperties(sc, e1); // BUG: see if we can do compile time elimination of the Assert + e1 = e1->optimize(WANTvalue); e1 = e1->checkToBoolean(); if (!global.params.useAssert && e1->isBool(FALSE)) { Expression *e = new HaltExp(loc); @@ -2904,10 +3393,14 @@ return this; } -void AssertExp::toCBuffer(OutBuffer *buf) +void AssertExp::checkSideEffect(int flag) +{ +} + +void AssertExp::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { buf->writestring("assert("); - e1->toCBuffer(buf); + expToCBuffer(buf, hgs, e1, PREC_assign); buf->writeByte(')'); } @@ -3010,6 +3503,12 @@ if (v) { //printf("DotIdExp:: Identifier '%s' is a variable, type '%s'\n", toChars(), v->type->toChars()); + if (v->inuse) + { + error("circular reference to '%s'", v->toChars()); + type = Type::tint32; + return this; + } type = v->type; if (v->isConst()) { @@ -3113,7 +3612,8 @@ } else if (e1->type->ty == Tpointer && ident != Id::init && ident != Id::__sizeof && - ident != Id::alignof && ident != Id::offsetof) + ident != Id::alignof && ident != Id::offsetof && + ident != Id::mangleof) { e = new PtrExp(loc, e1); e->type = e1->type->next; @@ -3127,10 +3627,10 @@ } } -void DotIdExp::toCBuffer(OutBuffer *buf) +void DotIdExp::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { //printf("DotIdExp::toCBuffer()\n"); - e1->toCBuffer(buf); + expToCBuffer(buf, hgs, e1, PREC_primary); buf->writeByte('.'); buf->writestring(ident->toChars()); } @@ -3165,6 +3665,9 @@ if (ad && !(t->ty == Tpointer && t->next->ty == Tstruct && ((TypeStruct *)t->next)->sym == ad) + && + !(t->ty == Tstruct && + ((TypeStruct *)t)->sym == ad) ) { ClassDeclaration *cd = ad->isClassDeclaration(); @@ -3233,9 +3736,9 @@ return this; } -void DotVarExp::toCBuffer(OutBuffer *buf) +void DotVarExp::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { - e1->toCBuffer(buf); + expToCBuffer(buf, hgs, e1, PREC_primary); buf->writeByte('.'); buf->writestring(var->toChars()); } @@ -3326,6 +3829,9 @@ error("%s is not a template", id->toChars()); goto Lerr; } + if (global.errors) + goto Lerr; + ti->tempdecl = td; if (eleft) @@ -3353,11 +3859,11 @@ return new IntegerExp(0); } -void DotTemplateInstanceExp::toCBuffer(OutBuffer *buf) +void DotTemplateInstanceExp::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { - e1->toCBuffer(buf); + expToCBuffer(buf, hgs, e1, PREC_primary); buf->writeByte('.'); - ti->toCBuffer(buf); + ti->toCBuffer(buf, hgs); } /************************************************************/ @@ -3382,11 +3888,12 @@ return this; } -void DelegateExp::toCBuffer(OutBuffer *buf) +void DelegateExp::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { buf->writeByte('&'); if (!func->isNested()) - { e1->toCBuffer(buf); + { + expToCBuffer(buf, hgs, e1, PREC_primary); buf->writeByte('.'); } buf->writestring(func->toChars()); @@ -3410,48 +3917,16 @@ return this; } -void DotTypeExp::toCBuffer(OutBuffer *buf) +void DotTypeExp::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { - e1->toCBuffer(buf); + expToCBuffer(buf, hgs, e1, PREC_primary); buf->writeByte('.'); buf->writestring(sym->toChars()); } /************************************************************/ -ArrowExp::ArrowExp(Loc loc, Expression *e, Identifier *ident) - : UnaExp(loc, TOKarrow, sizeof(ArrowExp), e) -{ - this->ident = ident; -} - -Expression *ArrowExp::semantic(Scope *sc) -{ Expression *e; - -#if LOGSEMANTIC - printf("ArrowExp::semantic('%s')\n", toChars()); -#endif - UnaExp::semantic(sc); - e1 = resolveProperties(sc, e1); - e1 = e1->checkToPointer(); - if (e1->type->ty != Tpointer) - error("pointer expected before ->, not '%s'", e1->type->toChars()); - e = new PtrExp(loc, e1); - e = new DotIdExp(loc, e, ident); - e = e->semantic(sc); - return e; -} - -void ArrowExp::toCBuffer(OutBuffer *buf) -{ - e1->toCBuffer(buf); - buf->writestring("->"); - buf->writestring(ident->toChars()); -} - -/************************************************************/ - -CallExp::CallExp(Loc loc, Expression *e, Array *arguments) +CallExp::CallExp(Loc loc, Expression *e, Expressions *arguments) : UnaExp(loc, TOKcall, sizeof(CallExp), e) { this->arguments = arguments; @@ -3466,7 +3941,7 @@ CallExp::CallExp(Loc loc, Expression *e, Expression *earg1) : UnaExp(loc, TOKcall, sizeof(CallExp), e) { - Array *arguments = new Array(); + Expressions *arguments = new Expressions(); arguments->setDim(1); arguments->data[0] = (void *)earg1; @@ -3476,7 +3951,7 @@ CallExp::CallExp(Loc loc, Expression *e, Expression *earg1, Expression *earg2) : UnaExp(loc, TOKcall, sizeof(CallExp), e) { - Array *arguments = new Array(); + Expressions *arguments = new Expressions(); arguments->setDim(2); arguments->data[0] = (void *)earg1; arguments->data[1] = (void *)earg2; @@ -3503,12 +3978,12 @@ if (type) return this; // semantic() already run #if 0 -if (arguments && arguments->dim) -{ - Expression *earg = (Expression *)arguments->data[0]; - earg->print(); - if (earg->type) earg->type->print(); -} + if (arguments && arguments->dim) + { + Expression *earg = (Expression *)arguments->data[0]; + earg->print(); + if (earg->type) earg->type->print(); + } #endif /* Transform: @@ -3545,7 +4020,7 @@ else if (e1ty == Tarray || e1ty == Tsarray || e1ty == Taarray) { if (!arguments) - arguments = new Array(); + arguments = new Expressions(); arguments->shift(dotid->e1); e1 = new IdentifierExp(dotid->loc, dotid->ident); } @@ -3553,6 +4028,7 @@ } Lagain: + f = NULL; if (e1->op == TOKthis || e1->op == TOKsuper) { // semantic() run later for these @@ -3597,8 +4073,8 @@ { ad = ((TypeStruct *)t1)->sym; L1: - fd = search_function(ad, Id::call); - if (fd) +// fd = search_function(ad, Id::call); +// if (fd) { // Rewrite as e1.call(arguments) Expression *e = new DotIdExp(loc, e1, Id::call); @@ -3781,6 +4257,17 @@ e->type = t1; e1 = e; } + else if (e1->op == TOKtemplate) + { + TemplateExp *te = (TemplateExp *)e1; + f = te->td->deduce(sc, loc, NULL, arguments); + if (!f) + { type = Type::terror; + return this; + } + e1 = new VarExp(loc, f); + goto Lagain; + } else { error("function expected before (), not %s of type %s", e1->toChars(), e1->type->toChars()); type = Type::terror; @@ -3818,19 +4305,36 @@ type = tf->next; if (!arguments) - arguments = new Array(); + arguments = new Expressions(); functionArguments(loc, sc, tf, arguments); assert(type); + + if (f && f->tintro) + { + Type *t = type; + int offset = 0; + + if (f->tintro->next->isBaseOf(t, &offset) && offset) + { + type = f->tintro->next; + return castTo(t); + } + } + return this; } -void CallExp::toCBuffer(OutBuffer *buf) +void CallExp::checkSideEffect(int flag) +{ +} + +void CallExp::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { int i; - e1->toCBuffer(buf); + expToCBuffer(buf, hgs, e1, precedence[op]); buf->writeByte('('); - argsToCBuffer(buf, arguments); + argsToCBuffer(buf, arguments, hgs); buf->writeByte(')'); } @@ -3891,6 +4395,7 @@ if (e1->type->toBasetype()->ty == Tbit) error("cannot take address of bit in array"); } + return optimize(WANTvalue); } return this; } @@ -3963,12 +4468,10 @@ return this; } -void PtrExp::toCBuffer(OutBuffer *buf) +void PtrExp::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { buf->writeByte('*'); - buf->writeByte('('); - e1->toCBuffer(buf); - buf->writeByte(')'); + expToCBuffer(buf, hgs, e1, precedence[op]); } /************************************************************/ @@ -3992,6 +4495,7 @@ if (e) return e; + e1->checkNoBool(); e1->checkArithmetic(); type = e1->type; } @@ -4017,6 +4521,7 @@ e = op_overload(sc); if (e) return e; + e1->checkNoBool(); e1->checkArithmetic(); return e1; } @@ -4039,6 +4544,7 @@ if (e) return e; + e1->checkNoBool(); e1 = e1->checkIntegral(); type = e1->type; } @@ -4071,7 +4577,7 @@ /************************************************************/ BoolExp::BoolExp(Loc loc, Expression *e, Type *t) - : UnaExp(loc, TOKnot, sizeof(BoolExp), e) + : UnaExp(loc, TOKtobool, sizeof(BoolExp), e) { type = t; } @@ -4167,12 +4673,21 @@ return this; } +void DeleteExp::checkSideEffect(int flag) +{ +} + Expression *DeleteExp::checkToBoolean() { error("delete does not give a boolean result"); return this; } +void DeleteExp::toCBuffer(OutBuffer *buf, HdrGenState *hgs) +{ + buf->writestring("delete "); + expToCBuffer(buf, hgs, e1, precedence[op]); +} /************************************************************/ @@ -4213,13 +4728,19 @@ return e1->castTo(to); } -void CastExp::toCBuffer(OutBuffer *buf) +void CastExp::checkSideEffect(int flag) +{ + if (!to->equals(Type::tvoid) && + !(to->ty == Tclass && e1->op == TOKcall && e1->type->ty == Tclass)) + Expression::checkSideEffect(flag); +} + +void CastExp::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { buf->writestring("cast("); - to->toCBuffer(buf, NULL); - buf->writestring(")("); - e1->toCBuffer(buf); + to->toCBuffer(buf, NULL, hgs); buf->writeByte(')'); + expToCBuffer(buf, hgs, e1, precedence[op]); } @@ -4359,19 +4880,19 @@ return this; } -void SliceExp::toCBuffer(OutBuffer *buf) +void SliceExp::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { - e1->toCBuffer(buf); + expToCBuffer(buf, hgs, e1, precedence[op]); buf->writeByte('['); if (upr || lwr) { if (lwr) - lwr->toCBuffer(buf); + expToCBuffer(buf, hgs, lwr, PREC_assign); else buf->writeByte('0'); buf->writestring(".."); if (upr) - upr->toCBuffer(buf); + expToCBuffer(buf, hgs, upr, PREC_assign); else buf->writestring("length"); // BUG: should be array.length } @@ -4401,9 +4922,9 @@ return this; } -void ArrayLengthExp::toCBuffer(OutBuffer *buf) +void ArrayLengthExp::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { - e1->toCBuffer(buf); + expToCBuffer(buf, hgs, e1, PREC_primary); buf->writestring(".length"); } @@ -4411,7 +4932,7 @@ // e1 [ i1, i2, i3, ... ] -ArrayExp::ArrayExp(Loc loc, Expression *e1, Array *args) +ArrayExp::ArrayExp(Loc loc, Expression *e1, Expressions *args) : UnaExp(loc, TOKarray, sizeof(ArrayExp), e1) { arguments = args; @@ -4469,12 +4990,12 @@ } -void ArrayExp::toCBuffer(OutBuffer *buf) +void ArrayExp::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { int i; - e1->toCBuffer(buf); + expToCBuffer(buf, hgs, e1, PREC_primary); buf->writeByte('['); - argsToCBuffer(buf, arguments); + argsToCBuffer(buf, arguments, hgs); buf->writeByte(']'); } @@ -4534,6 +5055,12 @@ return e2->isBool(result); } +void CommaExp::checkSideEffect(int flag) +{ + /* Don't check e1 until we cast(void) the a,b code generation */ + e2->checkSideEffect(flag); +} + /************************** IndexExp **********************************/ // e1 [ e2 ] @@ -4601,6 +5128,7 @@ TypeSArray *tsa = (TypeSArray *)t1; +#if 0 // Don't do now, because it might be short-circuit evaluated // Do compile time array bounds checking if possible e2 = e2->optimize(WANTvalue); if (e2->op == TOKint64) @@ -4611,6 +5139,7 @@ error("array index [%lld] is outside array bounds [0 .. %lld]", index, length); } +#endif e->type = t1->next; break; } @@ -4648,14 +5177,15 @@ return toLvalue(e); } -void IndexExp::toCBuffer(OutBuffer *buf) +void IndexExp::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { - e1->toCBuffer(buf); + expToCBuffer(buf, hgs, e1, PREC_primary); buf->writeByte('['); - e2->toCBuffer(buf); + expToCBuffer(buf, hgs, e2, PREC_assign); buf->writeByte(']'); } + /************************* PostIncExp ***********************************/ PostIncExp::PostIncExp(Loc loc, Expression *e) @@ -4678,6 +5208,7 @@ e = this; e1 = e1->modifiableLvalue(sc, NULL); e1->checkScalar(); + e1->checkNoBool(); if (e1->type->ty == Tpointer) e = scaleFactor(); else @@ -4687,9 +5218,9 @@ return e; } -void PostIncExp::toCBuffer(OutBuffer *buf) +void PostIncExp::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { - e1->toCBuffer(buf); + expToCBuffer(buf, hgs, e1, precedence[op]); buf->writestring("++"); } @@ -4714,6 +5245,7 @@ e = this; e1 = e1->modifiableLvalue(sc, NULL); e1->checkScalar(); + e1->checkNoBool(); if (e1->type->ty == Tpointer) e = scaleFactor(); else @@ -4723,9 +5255,9 @@ return e; } -void PostDecExp::toCBuffer(OutBuffer *buf) +void PostDecExp::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { - e1->toCBuffer(buf); + expToCBuffer(buf, hgs, e1, precedence[op]); buf->writestring("--"); } @@ -4745,8 +5277,8 @@ #endif //printf("e1->op = %d, '%s'\n", e1->op, Token::toChars(e1->op)); - /* Look for operator overloading of a[]=value. - * Do it before semantic() otherwise the a[] will have been + /* Look for operator overloading of a[i]=value. + * Do it before semantic() otherwise the a[i] will have been * converted to a.opIndex() already. */ if (e1->op == TOKarray) @@ -4771,7 +5303,7 @@ fd = search_function(ad, Id::indexass); if (fd) { Expression *e = new DotIdExp(loc, ae->e1, Id::indexass); - Array *a = ae->arguments->copy(); + Expressions *a = (Expressions *)ae->arguments->copy(); a->insert(0, e2); e = new CallExp(loc, e, a); @@ -4795,6 +5327,48 @@ } } } + /* Look for operator overloading of a[i..j]=value. + * Do it before semantic() otherwise the a[i..j] will have been + * converted to a.opSlice() already. + */ + if (e1->op == TOKslice) + { Type *t1; + SliceExp *ae = (SliceExp *)e1; + AggregateDeclaration *ad; + Identifier *id = Id::index; + FuncDeclaration *fd; + + ae->e1 = ae->e1->semantic(sc); + t1 = ae->e1->type->toBasetype(); + if (t1->ty == Tstruct) + { + ad = ((TypeStruct *)t1)->sym; + goto L2; + } + else if (t1->ty == Tclass) + { + ad = ((TypeClass *)t1)->sym; + L2: + // Rewrite (a[i..j] = value) to (a.opIndexAssign(value, i, j)) + fd = search_function(ad, Id::sliceass); + if (fd) + { Expression *e = new DotIdExp(loc, ae->e1, Id::sliceass); + Expressions *a = new Expressions(); + + a->push(e2); + if (ae->lwr) + { a->push(ae->lwr); + assert(ae->upr); + a->push(ae->upr); + } + else + assert(!ae->upr); + e = new CallExp(loc, e, a); + e = e->semantic(sc); + return e; + } + } + } BinExp::semantic(sc); e2 = resolveProperties(sc, e2); @@ -4901,9 +5475,10 @@ else { e1->checkScalar(); + e1->checkNoBool(); if (tb1->ty == Tpointer && tb2->isintegral()) e = scaleFactor(); - else if (tb1->ty == Tbit) + else if (tb1->ty == Tbit || tb1->ty == Tbool) { #if 0 // Need to rethink this @@ -4986,6 +5561,7 @@ e1 = e1->modifiableLvalue(sc, NULL); e1->checkScalar(); + e1->checkNoBool(); if (e1->type->ty == Tpointer && e2->type->isintegral()) e = scaleFactor(); else @@ -5079,6 +5655,7 @@ e1 = e1->modifiableLvalue(sc, NULL); e1->checkScalar(); + e1->checkNoBool(); type = e1->type; typeCombine(); e1->checkArithmetic(); @@ -5134,6 +5711,7 @@ e1 = e1->modifiableLvalue(sc, NULL); e1->checkScalar(); + e1->checkNoBool(); type = e1->type; typeCombine(); e1->checkArithmetic(); @@ -5204,6 +5782,7 @@ e1 = e1->modifiableLvalue(sc, NULL); e1->checkScalar(); + e1->checkNoBool(); type = e1->type; typeCombine(); e1->checkIntegral(); @@ -5231,6 +5810,7 @@ e1 = e1->modifiableLvalue(sc, NULL); e1->checkScalar(); + e1->checkNoBool(); type = e1->type; typeCombine(); e1->checkIntegral(); @@ -5258,6 +5838,7 @@ e1 = e1->modifiableLvalue(sc, NULL); e1->checkScalar(); + e1->checkNoBool(); type = e1->type; typeCombine(); e1->checkIntegral(); @@ -5337,6 +5918,12 @@ else if (tb1->ty == Tpointer && e2->type->isintegral() || tb2->ty == Tpointer && e1->type->isintegral()) e = scaleFactor(); + else if (tb1->ty == Tpointer && tb2->ty == Tpointer) + { + incompatibleTypes(); + type = e1->type; + e = this; + } else { typeCombine(); @@ -5529,6 +6116,7 @@ type = Type::tint32; e = this; } + e->type = e->type->semantic(loc, sc); return e; } return this; @@ -5687,7 +6275,9 @@ if (type->isfloating()) { type = e1->type; if (e2->type->iscomplex()) - error("cannot perform modulo complex arithmetic"); + { error("cannot perform modulo complex arithmetic"); + return new IntegerExp(0); + } } return this; } @@ -5780,9 +6370,18 @@ e = op_overload(sc); if (e) return e; - typeCombine(); - e1->checkIntegral(); - e2->checkIntegral(); + if (e1->type->toBasetype()->ty == Tbool && + e2->type->toBasetype()->ty == Tbool) + { + type = e1->type; + e = this; + } + else + { + typeCombine(); + e1->checkIntegral(); + e2->checkIntegral(); + } } return this; } @@ -5802,9 +6401,18 @@ e = op_overload(sc); if (e) return e; - typeCombine(); - e1->checkIntegral(); - e2->checkIntegral(); + if (e1->type->toBasetype()->ty == Tbool && + e2->type->toBasetype()->ty == Tbool) + { + type = e1->type; + e = this; + } + else + { + typeCombine(); + e1->checkIntegral(); + e2->checkIntegral(); + } } return this; } @@ -5824,9 +6432,18 @@ e = op_overload(sc); if (e) return e; - typeCombine(); - e1->checkIntegral(); - e2->checkIntegral(); + if (e1->type->toBasetype()->ty == Tbool && + e2->type->toBasetype()->ty == Tbool) + { + type = e1->type; + e = this; + } + else + { + typeCombine(); + e1->checkIntegral(); + e2->checkIntegral(); + } } return this; } @@ -5858,6 +6475,8 @@ type = Type::tboolean; if (e1->type->ty == Tvoid) type = Type::tvoid; + if (e2->op == TOKtype || e2->op == TOKimport) + error("%s is not an expression", e2->toChars()); return this; } @@ -5872,6 +6491,10 @@ return TRUE; } +void OrOrExp::checkSideEffect(int flag) +{ + e2->checkSideEffect(flag); +} /************************************************************/ @@ -5899,6 +6522,8 @@ type = Type::tboolean; if (e1->type->ty == Tvoid) type = Type::tvoid; + if (e2->op == TOKtype || e2->op == TOKimport) + error("%s is not an expression", e2->toChars()); return this; } @@ -5913,6 +6538,10 @@ return TRUE; } +void AndAndExp::checkSideEffect(int flag) +{ + e2->checkSideEffect(flag); +} /************************************************************/ @@ -6063,7 +6692,7 @@ if (ve1->var == ve2->var /*|| ve1->var->toSymbol() == ve2->var->toSymbol()*/) { // They are the same, result is 'true' - e = new IntegerExp(loc, 1, Type::tbit); + e = new IntegerExp(loc, 1, Type::tboolean); return e; } } @@ -6236,13 +6865,20 @@ return this; } -void CondExp::toCBuffer(OutBuffer *buf) +void CondExp::checkSideEffect(int flag) +{ + econd->checkSideEffect(TRUE); + e1->checkSideEffect(flag); + e2->checkSideEffect(flag); +} + +void CondExp::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { - econd->toCBuffer(buf); + expToCBuffer(buf, hgs, econd, PREC_oror); buf->writestring(" ? "); - e1->toCBuffer(buf); + expToCBuffer(buf, hgs, e1, PREC_expr); buf->writestring(" : "); - e2->toCBuffer(buf); + expToCBuffer(buf, hgs, e2, PREC_cond); } diff -uNr gdc-0.17/d/dmd/expression.h gdc-0.18/d/dmd/expression.h --- gdc-0.17/d/dmd/expression.h 2005-11-28 05:17:52.000000000 +0100 +++ gdc-0.18/d/dmd/expression.h 2006-05-14 04:21:51.000000000 +0200 @@ -1,5 +1,5 @@ -// Copyright (c) 1999-2005 by Digital Mars +// Copyright (c) 1999-2006 by Digital Mars // All Rights Reserved // written by Walter Bright // www.digitalmars.com @@ -19,6 +19,7 @@ #include "mars.h" #include "identifier.h" #include "lexer.h" +#include "arraytypes.h" struct Type; struct Scope; @@ -39,16 +40,28 @@ struct Declaration; struct AggregateDeclaration; struct TemplateInstance; +struct TemplateDeclaration; struct ClassDeclaration; +struct HdrGenState; +struct BinExp; // Back end struct IRState; -union tree_node; typedef union tree_node elem; struct dt_t; +#ifdef IN_GCC +union tree_node; typedef union tree_node elem; +#else +struct elem; +#endif + +void initPrecedence(); + Expression *resolveProperties(Scope *sc, Expression *e); void accessCheck(Loc loc, Scope *sc, Expression *e, Declaration *d); FuncDeclaration *search_function(AggregateDeclaration *ad, Identifier *funcid); +void inferApplyArgTypes(Array *arguments, Type *taggr); +void argExpTypesToCBuffer(OutBuffer *buf, Expressions *arguments, HdrGenState *hgs); struct Expression : Object { @@ -71,14 +84,14 @@ void rvalue(); static Expression *combine(Expression *e1, Expression *e2); - static Array *arraySyntaxCopy(Array *exps); + static Expressions *arraySyntaxCopy(Expressions *exps); virtual integer_t toInteger(); virtual uinteger_t toUInteger(); virtual real_t toReal(); virtual real_t toImaginary(); virtual complex_t toComplex(); - virtual void toCBuffer(OutBuffer *buf); + virtual void toCBuffer(OutBuffer *buf, HdrGenState *hgs); virtual void toMangleBuffer(OutBuffer *buf); virtual Expression *toLvalue(Expression *e); virtual Expression *modifiableLvalue(Scope *sc, Expression *e); @@ -87,6 +100,7 @@ virtual Expression *castTo(Type *t); virtual void checkEscape(); void checkScalar(); + void checkNoBool(); Expression *checkIntegral(); void checkArithmetic(); void checkDeprecated(Scope *sc, Dsymbol *s); @@ -104,6 +118,7 @@ virtual int isConst(); virtual int isBool(int result); virtual int isBit(); + virtual void checkSideEffect(int flag); virtual int inlineCost(InlineCostState *ics); virtual Expression *doInline(InlineDoState *ids); @@ -136,7 +151,7 @@ int isConst(); int isBool(int result); int implicitConvTo(Type *t); - void toCBuffer(OutBuffer *buf); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); void toMangleBuffer(OutBuffer *buf); Expression *toLvalue(Expression *e); elem *toElem(IRState *irs); @@ -148,6 +163,7 @@ real_t value; RealExp(Loc loc, real_t value, Type *type); + int equals(Object *o); Expression *semantic(Scope *sc); char *toChars(); integer_t toInteger(); @@ -155,9 +171,10 @@ real_t toReal(); real_t toImaginary(); complex_t toComplex(); + Expression *castTo(Type *t); int isConst(); int isBool(int result); - void toCBuffer(OutBuffer *buf); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); void toMangleBuffer(OutBuffer *buf); elem *toElem(IRState *irs); dt_t **toDt(dt_t **pdt); @@ -168,6 +185,7 @@ complex_t value; ComplexExp(Loc loc, complex_t value, Type *type); + int equals(Object *o); Expression *semantic(Scope *sc); char *toChars(); integer_t toInteger(); @@ -175,10 +193,14 @@ real_t toReal(); real_t toImaginary(); complex_t toComplex(); + Expression *castTo(Type *t); int isConst(); int isBool(int result); - void toCBuffer(OutBuffer *buf); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); void toMangleBuffer(OutBuffer *buf); +#ifdef _DH + OutBuffer hexp; +#endif elem *toElem(IRState *irs); dt_t **toDt(dt_t **pdt); }; @@ -193,7 +215,7 @@ Expression *semantic(Scope *sc); char *toChars(); void dump(int indent); - void toCBuffer(OutBuffer *buf); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); Expression *toLvalue(Expression *e); }; @@ -210,7 +232,7 @@ Expression *semantic(Scope *sc); char *toChars(); void dump(int indent); - void toCBuffer(OutBuffer *buf); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); Expression *toLvalue(Expression *e); }; @@ -221,7 +243,7 @@ ThisExp(Loc loc); Expression *semantic(Scope *sc); int isBool(int result); - void toCBuffer(OutBuffer *buf); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); Expression *toLvalue(Expression *e); int inlineCost(InlineCostState *ics); @@ -235,7 +257,7 @@ { SuperExp(Loc loc); Expression *semantic(Scope *sc); - void toCBuffer(OutBuffer *buf); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); int inlineCost(InlineCostState *ics); Expression *doInline(InlineDoState *ids); @@ -247,7 +269,7 @@ NullExp(Loc loc); Expression *semantic(Scope *sc); int isBool(int result); - void toCBuffer(OutBuffer *buf); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); void toMangleBuffer(OutBuffer *buf); int implicitConvTo(Type *t); Expression *castTo(Type *t); @@ -272,7 +294,7 @@ Expression *castTo(Type *t); int compare(Object *obj); int isBool(int result); - void toCBuffer(OutBuffer *buf); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); void toMangleBuffer(OutBuffer *buf); elem *toElem(IRState *irs); dt_t **toDt(dt_t **pdt); @@ -285,14 +307,14 @@ TypeDotIdExp(Loc loc, Type *type, Identifier *ident); Expression *syntaxCopy(); Expression *semantic(Scope *sc); - void toCBuffer(OutBuffer *buf); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); elem *toElem(IRState *irs); }; struct TypeExp : Expression { TypeExp(Loc loc, Type *type); - void toCBuffer(OutBuffer *buf); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); elem *toElem(IRState *irs); }; @@ -304,21 +326,31 @@ Expression *syntaxCopy(); Expression *semantic(Scope *sc); elem *toElem(IRState *irs); - void toCBuffer(OutBuffer *buf); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); +}; + +struct TemplateExp : Expression +{ + TemplateDeclaration *td; + + TemplateExp(Loc loc, TemplateDeclaration *td); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); }; struct NewExp : Expression { - Array *newargs; // Array of Expression's to call new operator - Array *arguments; // Array of Expression's + Type *newtype; + Expressions *newargs; // Array of Expression's to call new operator + Expressions *arguments; // Array of Expression's CtorDeclaration *member; // constructor function NewDeclaration *allocator; // allocator function - NewExp(Loc loc, Array *newargs, Type *type, Array *arguments); + NewExp(Loc loc, Expressions *newargs, Type *newtype, Expressions *arguments); Expression *syntaxCopy(); Expression *semantic(Scope *sc); elem *toElem(IRState *irs); - void toCBuffer(OutBuffer *buf); + void checkSideEffect(int flag); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); //int inlineCost(InlineCostState *ics); Expression *doInline(InlineDoState *ids); @@ -327,14 +359,15 @@ struct NewAnonClassExp : Expression { - Array *newargs; // Array of Expression's to call new operator - Array *arguments; // Array of Expression's to call class constructor + Expressions *newargs; // Array of Expression's to call new operator + Expressions *arguments; // Array of Expression's to call class constructor ClassDeclaration *cd; // class being instantiated - NewAnonClassExp(Loc loc, Array *newargs, ClassDeclaration *cd, Array *arguments); + NewAnonClassExp(Loc loc, Expressions *newargs, ClassDeclaration *cd, Expressions *arguments); Expression *syntaxCopy(); Expression *semantic(Scope *sc); - void toCBuffer(OutBuffer *buf); + void checkSideEffect(int flag); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); }; // Offset from symbol @@ -347,10 +380,12 @@ SymOffExp(Loc loc, Declaration *var, unsigned offset); Expression *semantic(Scope *sc); void checkEscape(); - void toCBuffer(OutBuffer *buf); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); int isConst(); int isBool(int result); Expression *doInline(InlineDoState *ids); + int implicitConvTo(Type *t); + Expression *castTo(Type *t); elem *toElem(IRState *irs); dt_t **toDt(dt_t **pdt); @@ -367,7 +402,7 @@ Expression *semantic(Scope *sc); void dump(int indent); char *toChars(); - void toCBuffer(OutBuffer *buf); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); void checkEscape(); Expression *toLvalue(Expression *e); Expression *modifiableLvalue(Scope *sc, Expression *e); @@ -389,7 +424,7 @@ Expression *syntaxCopy(); Expression *semantic(Scope *sc); char *toChars(); - void toCBuffer(OutBuffer *buf); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); elem *toElem(IRState *irs); int inlineCost(InlineCostState *ics); @@ -406,7 +441,8 @@ DeclarationExp(Loc loc, Dsymbol *declaration); Expression *syntaxCopy(); Expression *semantic(Scope *sc); - void toCBuffer(OutBuffer *buf); + void checkSideEffect(int flag); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); elem *toElem(IRState *irs); int inlineCost(InlineCostState *ics); @@ -421,14 +457,15 @@ TypeidExp(Loc loc, Type *typeidType); Expression *syntaxCopy(); Expression *semantic(Scope *sc); - void toCBuffer(OutBuffer *buf); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); }; struct HaltExp : Expression { HaltExp(Loc loc); Expression *semantic(Scope *sc); - void toCBuffer(OutBuffer *buf); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); + void checkSideEffect(int flag); elem *toElem(IRState *irs); }; @@ -447,7 +484,7 @@ IftypeExp(Loc loc, Type *targ, Identifier *id, enum TOK tok, Type *tspec, enum TOK tok2); Expression *syntaxCopy(); Expression *semantic(Scope *sc); - void toCBuffer(OutBuffer *buf); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); }; /****************************************************************/ @@ -459,7 +496,7 @@ UnaExp(Loc loc, enum TOK op, int size, Expression *e1); Expression *syntaxCopy(); Expression *semantic(Scope *sc); - void toCBuffer(OutBuffer *buf); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); Expression *optimize(int result); void dump(int indent); @@ -481,11 +518,13 @@ Expression *semanticp(Scope *sc); Expression *commonSemanticAssign(Scope *sc); Expression *commonSemanticAssignIntegral(Scope *sc); - void toCBuffer(OutBuffer *buf); + void checkSideEffect(int flag); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); Expression *scaleFactor(); Expression *typeCombine(); Expression *optimize(int result); int isunsigned(); + void incompatibleTypes(); void dump(int indent); int inlineCost(InlineCostState *ics); @@ -497,13 +536,20 @@ elem *toElemBin(IRState *irs, int op); }; +struct BinAssignExp : BinExp +{ + BinAssignExp(Loc loc, enum TOK op, int size, Expression *e1, Expression *e2); + void checkSideEffect(int flag); +}; + /****************************************************************/ struct AssertExp : UnaExp { AssertExp(Loc loc, Expression *e); Expression *semantic(Scope *sc); - void toCBuffer(OutBuffer *buf); + void checkSideEffect(int flag); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); elem *toElem(IRState *irs); }; @@ -513,7 +559,7 @@ DotIdExp(Loc loc, Expression *e, Identifier *ident); Expression *semantic(Scope *sc); - void toCBuffer(OutBuffer *buf); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); void dump(int i); }; @@ -525,7 +571,7 @@ Expression *semantic(Scope *sc); Expression *toLvalue(Expression *e); Expression *modifiableLvalue(Scope *sc, Expression *e); - void toCBuffer(OutBuffer *buf); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); void dump(int indent); elem *toElem(IRState *irs); }; @@ -537,7 +583,7 @@ DotTemplateInstanceExp(Loc loc, Expression *e, TemplateInstance *ti); Expression *syntaxCopy(); Expression *semantic(Scope *sc); - void toCBuffer(OutBuffer *buf); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); void dump(int indent); }; @@ -549,7 +595,7 @@ Expression *semantic(Scope *sc); int implicitConvTo(Type *t); Expression *castTo(Type *t); - void toCBuffer(OutBuffer *buf); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); void dump(int indent); int inlineCost(InlineCostState *ics); @@ -562,31 +608,23 @@ DotTypeExp(Loc loc, Expression *e, Dsymbol *sym); Expression *semantic(Scope *sc); - void toCBuffer(OutBuffer *buf); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); elem *toElem(IRState *irs); }; -struct ArrowExp : UnaExp -{ - Identifier *ident; - - ArrowExp(Loc loc, Expression *e, Identifier *ident); - Expression *semantic(Scope *sc); - void toCBuffer(OutBuffer *buf); -}; - struct CallExp : UnaExp { - Array *arguments; // Array of Expression's + Expressions *arguments; // Array of Expression's - CallExp(Loc loc, Expression *e, Array *arguments); + CallExp(Loc loc, Expression *e, Expressions *arguments); CallExp(Loc loc, Expression *e); CallExp(Loc loc, Expression *e, Expression *earg1); CallExp(Loc loc, Expression *e, Expression *earg1, Expression *earg2); Expression *syntaxCopy(); Expression *semantic(Scope *sc); - void toCBuffer(OutBuffer *buf); + void checkSideEffect(int flag); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); elem *toElem(IRState *irs); int inlineCost(InlineCostState *ics); @@ -610,7 +648,7 @@ PtrExp(Loc loc, Expression *e, Type *t); Expression *semantic(Scope *sc); Expression *toLvalue(Expression *e); - void toCBuffer(OutBuffer *buf); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); elem *toElem(IRState *irs); Expression *optimize(int result); }; @@ -671,6 +709,8 @@ DeleteExp(Loc loc, Expression *e); Expression *semantic(Scope *sc); Expression *checkToBoolean(); + void checkSideEffect(int flag); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); elem *toElem(IRState *irs); }; @@ -683,7 +723,8 @@ Expression *syntaxCopy(); Expression *semantic(Scope *sc); Expression *optimize(int result); - void toCBuffer(OutBuffer *buf); + void checkSideEffect(int flag); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); Expression *constFold(); elem *toElem(IRState *irs); @@ -704,7 +745,7 @@ void checkEscape(); Expression *toLvalue(Expression *e); Expression *modifiableLvalue(Scope *sc, Expression *e); - void toCBuffer(OutBuffer *buf); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); Expression *optimize(int result); void dump(int indent); elem *toElem(IRState *irs); @@ -718,7 +759,8 @@ { ArrayLengthExp(Loc loc, Expression *e1); Expression *semantic(Scope *sc); - void toCBuffer(OutBuffer *buf); + Expression *optimize(int result); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); elem *toElem(IRState *irs); }; @@ -726,13 +768,13 @@ struct ArrayExp : UnaExp { - Array *arguments; // Array of Expression's + Expressions *arguments; // Array of Expression's - ArrayExp(Loc loc, Expression *e1, Array *arguments); + ArrayExp(Loc loc, Expression *e1, Expressions *arguments); Expression *syntaxCopy(); Expression *semantic(Scope *sc); Expression *toLvalue(Expression *e); - void toCBuffer(OutBuffer *buf); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); // For operator overloading Identifier *opId(); @@ -758,6 +800,7 @@ Expression *toLvalue(Expression *e); Expression *modifiableLvalue(Scope *sc, Expression *e); int isBool(int result); + void checkSideEffect(int flag); Expression *optimize(int result); elem *toElem(IRState *irs); }; @@ -771,7 +814,7 @@ Expression *semantic(Scope *sc); Expression *toLvalue(Expression *e); Expression *modifiableLvalue(Scope *sc, Expression *e); - void toCBuffer(OutBuffer *buf); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); Expression *optimize(int result); Expression *doInline(InlineDoState *ids); @@ -782,7 +825,7 @@ { PostIncExp(Loc loc, Expression *e); Expression *semantic(Scope *sc); - void toCBuffer(OutBuffer *buf); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); Identifier *opId(); // For operator overloading elem *toElem(IRState *irs); }; @@ -791,7 +834,7 @@ { PostDecExp(Loc loc, Expression *e); Expression *semantic(Scope *sc); - void toCBuffer(OutBuffer *buf); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); Identifier *opId(); // For operator overloading elem *toElem(IRState *irs); }; @@ -1106,6 +1149,7 @@ int isBit(); Expression *constFold(); Expression *optimize(int result); + void checkSideEffect(int flag); elem *toElem(IRState *irs); }; @@ -1117,6 +1161,7 @@ int isBit(); Expression *constFold(); Expression *optimize(int result); + void checkSideEffect(int flag); elem *toElem(IRState *irs); }; @@ -1155,6 +1200,7 @@ EqualExp(enum TOK op, Loc loc, Expression *e1, Expression *e2); Expression *semantic(Scope *sc); Expression *constFold(); + Expression *optimize(int result); int isBit(); // For operator overloading @@ -1190,7 +1236,8 @@ Expression *toLvalue(Expression *e); Expression *modifiableLvalue(Scope *sc, Expression *e); Expression *checkToBoolean(); - void toCBuffer(OutBuffer *buf); + void checkSideEffect(int flag); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); int implicitConvTo(Type *t); Expression *castTo(Type *t); diff -uNr gdc-0.17/d/dmd/func.c gdc-0.18/d/dmd/func.c --- gdc-0.17/d/dmd/func.c 2005-10-24 23:48:04.000000000 +0200 +++ gdc-0.18/d/dmd/func.c 2006-05-14 04:21:51.000000000 +0200 @@ -1,5 +1,5 @@ -// Copyright (c) 1999-2005 by Digital Mars +// Copyright (c) 1999-2006 by Digital Mars // All Rights Reserved // written by Walter Bright // www.digitalmars.com @@ -7,12 +7,6 @@ // in artistic.txt, or the GNU General Public License in gnu.txt. // See the included readme.txt for details. -/* NOTE: This file has been patched from the original DMD distribution to - work with the GDC compiler. - - Modified by David Friedman, September 2004 -*/ - #include #include @@ -29,12 +23,12 @@ #include "module.h" #include "statement.h" #include "template.h" +#include "hdrgen.h" #ifdef IN_GCC #include "d-dmd-gcc.h" #endif - /********************************* FuncDeclaration ****************************/ FuncDeclaration::FuncDeclaration(Loc loc, Loc endloc, Identifier *id, enum STC storage_class, Type *type) @@ -54,7 +48,9 @@ localsymtab = NULL; vthis = NULL; v_arguments = NULL; +#if IN_GCC v_argptr = NULL; +#endif parameters = NULL; labtab = NULL; overnext = NULL; @@ -66,8 +62,9 @@ inlineAsm = 0; semanticRun = 0; nestedFrameRef = 0; - introducing = 0; fes = NULL; + introducing = 0; + tintro = NULL; } Dsymbol *FuncDeclaration::syntaxCopy(Dsymbol *s) @@ -115,7 +112,7 @@ parent = sc->parent; protection = sc->protection; storage_class |= sc->stc; - //printf("storage_class = x%x\n", storage_class); + //printf("function storage_class = x%x\n", storage_class); Dsymbol *parent = toParent(); if (isConst() || isAuto()) @@ -250,10 +247,11 @@ // BUG: should give error if argument types match, // but return type does not? - //printf("\tvtbl[%d]\n", vi); + //printf("\tvtbl[%d] = '%s'\n", vi, fdv ? fdv->ident->toChars() : ""); if (fdv && fdv->ident == ident) { int cov = type->covariant(fdv->type); + //printf("\tcov = %d\n", cov); if (cov) { // Override @@ -280,6 +278,28 @@ } cd->vtbl.data[vi] = (void *)this; vtblIndex = vi; + + /* This works by whenever this function is called, + * it actually returns tintro, which gets dynamically + * cast to type. But we know that tintro is a base + * of type, so we could optimize it by not doing a + * dynamic cast, but just subtracting the isBaseOf() + * offset if the value is != null. + */ + + if (fdv->tintro) + tintro = fdv->tintro; + else if (!type->equals(fdv->type)) + { + /* Only need to have a tintro if the vptr + * offsets differ + */ + int offset; + if (fdv->type->next->isBaseOf(type->next, &offset)) + { + tintro = fdv->type; + } + } goto L1; } } @@ -300,6 +320,60 @@ } L1: ; + + /* Go through all the interface bases. + * If this function is covariant with any members of those interface + * functions, set the tintro. + */ + for (int i = 0; i < cd->interfaces_dim; i++) + { + BaseClass *b = cd->interfaces[i]; + for (vi = 0; vi < b->base->vtbl.dim; vi++) + { + Dsymbol *s = (Dsymbol *)b->base->vtbl.data[vi]; + //printf("[%d] %p %s\n", vi, s, s->toChars()); + FuncDeclaration *fdv = s->isFuncDeclaration(); + if (fdv && fdv->ident == ident) + { + int cov = type->covariant(fdv->type); + //printf("\tcov = %d\n", cov); + if (cov == 2) + { + //type->print(); + //fdv->type->print(); + //printf("%s %s\n", type->deco, fdv->type->deco); + error("of type %s overrides but is not covariant with %s of type %s", + type->toChars(), fdv->toPrettyChars(), fdv->type->toChars()); + } + if (cov == 1) + { Type *ti = NULL; + + if (fdv->tintro) + ti = fdv->tintro; + else if (!type->equals(fdv->type)) + { + /* Only need to have a tintro if the vptr + * offsets differ + */ + int offset; + if (fdv->type->next->isBaseOf(type->next, &offset) && offset) + { + ti = fdv->type; + } + } + if (ti) + { + if (tintro && !tintro->equals(ti)) + { + error("incompatible covariant types %s and %s", tintro->toChars(), ti->toChars()); + } + tintro = ti; + } + } + } + } + } + } else if (isOverride() && !parent->isTemplateInstance()) error("override only applies to class member functions"); @@ -354,6 +428,8 @@ goto Lmainerr; } } + if (f->next->ty != Tint32 && f->next->ty != Tvoid) + error("must return int or void, not %s", f->next->toChars()); if (f->varargs) { Lmainerr: @@ -421,6 +497,9 @@ sc2->sw = NULL; sc2->fes = fes; sc2->linkage = LINKd; + sc2->stc &= ~(STCauto | STCstatic | STCabstract | STCdeprecated); + sc2->protection = PROTpublic; + sc2->structalign = 8; // Declare 'this' ad = isThis(); @@ -473,10 +552,10 @@ } if (f->linkage == LINKd || (parameters && parameters->dim)) { // Declare _argptr -#ifndef IN_GCC - t = Type::tvoid->pointerTo(); -#else +#if IN_GCC t = d_gcc_builtin_va_list_d_type; +#else + t = Type::tvoid->pointerTo(); #endif argptr = new VarDeclaration(0, t, Id::_argptr, NULL); argptr->semantic(sc2); @@ -689,7 +768,14 @@ // Insert implicit super() at start of fbody Expression *e1 = new SuperExp(0); Expression *e = new CallExp(0, e1); + + unsigned errors = global.errors; + global.gag++; e = e->semantic(sc2); + global.gag--; + if (errors != global.errors) + error("no match for implicit super() call in constructor"); + Statement *s = new ExpStatement(0, e); fbody = new CompoundStatement(0, s, fbody); } @@ -703,35 +789,46 @@ } // else if (!hasReturnExp && type->next->ty != Tvoid) // error("expected to return a value of type %s", type->next->toChars()); - else if (type->next->ty != Tvoid && !inlineAsm) + else if (!inlineAsm) { - if (offend) - { Expression *e; - - if (global.params.warnings) - { fprintf(stderr, "warning - "); - error("no return at end of function"); + if (type->next->ty == Tvoid) + { + if (offend && isMain()) + { // Add a return 0; statement + Statement *s = new ReturnStatement(0, new IntegerExp(0)); + fbody = new CompoundStatement(0, fbody, s); } + } + else + { + if (offend) + { Expression *e; - if (global.params.useAssert && - !global.params.useInline) - { /* Add an assert(0); where the missing return - * should be. - */ - e = new AssertExp(endloc, new IntegerExp(0, 0, Type::tint32)); + if (global.params.warnings) + { fprintf(stdmsg, "warning - "); + error("no return at end of function"); + } + + if (global.params.useAssert && + !global.params.useInline) + { /* Add an assert(0); where the missing return + * should be. + */ + e = new AssertExp(endloc, new IntegerExp(0, 0, Type::tint32)); + } + else + e = new HaltExp(endloc); + e = new CommaExp(0, e, type->next->defaultInit()); + e = e->semantic(sc2); + Statement *s = new ExpStatement(0, e); + fbody = new CompoundStatement(0, fbody, s); } - else - e = new HaltExp(endloc); - e = new CommaExp(0, e, type->next->defaultInit()); - e = e->semantic(sc2); - Statement *s = new ExpStatement(0, e); - fbody = new CompoundStatement(0, fbody, s); } } } { - Array *a = new Array(); + Statements *a = new Statements(); // Merge in initialization of 'out' parameters if (parameters) @@ -751,7 +848,11 @@ if (argptr) { // Initialize _argptr to point past non-variadic arg -#ifndef IN_GCC +#if IN_GCC + // Handled in FuncDeclaration::toObjFile + v_argptr = argptr; + v_argptr->init = new VoidInitializer(loc); +#else Expression *e1; Expression *e; Type *t = argptr->type; @@ -769,18 +870,20 @@ e = new AssignExp(0, e1, e); e->type = t; a->push(new ExpStatement(0, e)); -#else - // Handled in FuncDeclaration::toObjFile - v_argptr = argptr; - v_argptr->init = new VoidInitializer(loc); #endif } - // Merge contracts together with body into one compound statement +#ifdef _DH + if (frequire && global.params.useIn) + { frequire->incontract = 1; + a->push(frequire); + } +#else if (frequire && global.params.useIn) a->push(frequire); +#endif // Precondition invariant if (addPreInvariant()) @@ -831,6 +934,10 @@ // Create: return vresult; assert(vresult); Expression *e = new VarExp(0, vresult); + if (tintro) + { e = e->implicitCastTo(tintro->next); + e = e->semantic(sc); + } ReturnStatement *s = new ReturnStatement(0, e); a->push(s); } @@ -843,19 +950,51 @@ } } -void FuncDeclaration::toHBuffer(OutBuffer *buf) +void FuncDeclaration::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { - type->toCBuffer(buf, ident); - buf->writeByte(';'); - buf->writenl(); + //printf("FuncDeclaration::toCBuffer() '%s'\n", toChars()); + + type->toCBuffer(buf, ident, hgs); + bodyToCBuffer(buf, hgs); } -void FuncDeclaration::toCBuffer(OutBuffer *buf) + +void FuncDeclaration::bodyToCBuffer(OutBuffer *buf, HdrGenState *hgs) { - type->toCBuffer(buf, ident); - if (fbody) + if (fbody && + (!hgs->hdrgen || hgs->tpltMember || canInline(1,1)) + ) { buf->writenl(); - fbody->toCBuffer(buf); + + // in{} + if (frequire) + { buf->writestring("in"); + buf->writenl(); + frequire->toCBuffer(buf, hgs); + } + + // out{} + if (fensure) + { buf->writestring("out"); + if (outId) + { buf->writebyte('('); + buf->writestring(outId->toChars()); + buf->writebyte(')'); + } + buf->writenl(); + fensure->toCBuffer(buf, hgs); + } + + if (frequire || fensure) + { buf->writestring("body"); + buf->writenl(); + } + + buf->writebyte('{'); + buf->writenl(); + fbody->toCBuffer(buf, hgs); + buf->writebyte('}'); + buf->writenl(); } else { buf->writeByte(';'); @@ -980,7 +1119,7 @@ // Recursive helper function -void overloadResolveX(Match *m, FuncDeclaration *fstart, Array *arguments) +void overloadResolveX(Match *m, FuncDeclaration *fstart, Expressions *arguments) { MATCH match; Declaration *d; @@ -1058,7 +1197,7 @@ } } -FuncDeclaration *FuncDeclaration::overloadResolve(Loc loc, Array *arguments) +FuncDeclaration *FuncDeclaration::overloadResolve(Loc loc, Expressions *arguments) { TypeFunction *tf; Match m; @@ -1092,26 +1231,17 @@ OutBuffer buf; if (arguments) - { int i; - OutBuffer argbuf; - - for (i = 0; i < arguments->dim; i++) - { Expression *arg; + { + HdrGenState hgs; - arg = (Expression *)arguments->data[i]; - argbuf.reset(); - assert(arg->type); - arg->type->toCBuffer2(&argbuf, NULL); - if (i) - buf.writeByte(','); - buf.write(&argbuf); - } + argExpTypesToCBuffer(&buf, arguments, &hgs); } if (m.last == MATCHnomatch) { tf = (TypeFunction *)type; + //printf("tf = %s, args = %s\n", tf->deco, ((Expression *)arguments->data[0])->type->deco); error(loc, "%s does not match argument types (%s)", Argument::argsTypesToChars(tf->arguments, tf->varargs), buf.toChars()); @@ -1254,9 +1384,9 @@ { CompoundStatement *cs; if (!fbody) - { Array *a; + { Statements *a; - a = new Array(); + a = new Statements(); fbody = new CompoundStatement(0, a); } cs = fbody->isCompoundStatement(); @@ -1362,7 +1492,8 @@ * Generate a FuncDeclaration for a runtime library function. */ -FuncDeclaration *FuncDeclaration::genCfunc(Type *treturn, char *name) +FuncDeclaration *FuncDeclaration::genCfunc(Type *treturn, char *name, + Type *t1, Type *t2, Type *t3) { FuncDeclaration *fd; TypeFunction *tf; @@ -1387,7 +1518,19 @@ } else { - tf = new TypeFunction(NULL, treturn, 0, LINKc); + Array * args = 0; + if (t1) { + args = new Array; + args->push(new Argument(In,t1,0,0)); + if (t2) + { + args->push(new Argument(In,t2,0,0)); + if (t3) + args->push(new Argument(In,t3,0,0)); + } + } + + tf = new TypeFunction(args, treturn, 0, LINKc); fd = new FuncDeclaration(0, 0, id, STCstatic, tf); fd->protection = PROTpublic; fd->linkage = LINKc; @@ -1465,6 +1608,20 @@ return (tok == TOKdelegate) ? (char*)"delegate" : (char*)"function"; } +void FuncLiteralDeclaration::toCBuffer(OutBuffer *buf, HdrGenState *hgs) +{ + static Identifier *idfunc; + static Identifier *iddel; + + if (!idfunc) + idfunc = new Identifier("function", 0); + if (!iddel) + iddel = new Identifier("delegate", 0); + + type->toCBuffer(buf, ((tok == TOKdelegate) ? iddel : idfunc), hgs); + bodyToCBuffer(buf, hgs); +} + /********************************* CtorDeclaration ****************************/ @@ -1488,7 +1645,6 @@ assert(!fthrows); // deprecated f->arguments = Argument::arraySyntaxCopy(arguments); - return f; } @@ -1562,6 +1718,13 @@ } +void CtorDeclaration::toCBuffer(OutBuffer *buf, HdrGenState *hgs) +{ + buf->writestring("this"); + Argument::argsToCBuffer(buf, hgs, arguments, varargs); + bodyToCBuffer(buf, hgs); +} + /********************************* DtorDeclaration ****************************/ DtorDeclaration::DtorDeclaration(Loc loc, Loc endloc) @@ -1616,6 +1779,14 @@ return FALSE; } +void DtorDeclaration::toCBuffer(OutBuffer *buf, HdrGenState *hgs) +{ + if (hgs->hdrgen) + return; + buf->writestring("~this()"); + bodyToCBuffer(buf, hgs); +} + /********************************* StaticCtorDeclaration ****************************/ StaticCtorDeclaration::StaticCtorDeclaration(Loc loc, Loc endloc) @@ -1678,6 +1849,14 @@ return FALSE; } +void StaticCtorDeclaration::toCBuffer(OutBuffer *buf, HdrGenState *hgs) +{ + if (hgs->hdrgen) + return; + buf->writestring("static this()"); + bodyToCBuffer(buf, hgs); +} + /********************************* StaticDtorDeclaration ****************************/ StaticDtorDeclaration::StaticDtorDeclaration(Loc loc, Loc endloc) @@ -1745,6 +1924,14 @@ return FALSE; } +void StaticDtorDeclaration::toCBuffer(OutBuffer *buf, HdrGenState *hgs) +{ + if (hgs->hdrgen) + return; + buf->writestring("static ~this()"); + bodyToCBuffer(buf, hgs); +} + /********************************* InvariantDeclaration ****************************/ InvariantDeclaration::InvariantDeclaration(Loc loc, Loc endloc) @@ -1803,6 +1990,14 @@ return FALSE; } +void InvariantDeclaration::toCBuffer(OutBuffer *buf, HdrGenState *hgs) +{ + if (hgs->hdrgen) + return; + buf->writestring("invariant"); + bodyToCBuffer(buf, hgs); +} + /********************************* UnitTestDeclaration ****************************/ @@ -1876,6 +2071,13 @@ return FALSE; } +void UnitTestDeclaration::toCBuffer(OutBuffer *buf, HdrGenState *hgs) +{ + if (hgs->hdrgen) + return; + buf->writestring("unittest"); + bodyToCBuffer(buf, hgs); +} /********************************* NewDeclaration ****************************/ @@ -1955,6 +2157,12 @@ return FALSE; } +void NewDeclaration::toCBuffer(OutBuffer *buf, HdrGenState *hgs) +{ + buf->writestring("new"); + Argument::argsToCBuffer(buf, hgs, arguments, varargs); + bodyToCBuffer(buf, hgs); +} /********************************* DeleteDeclaration ****************************/ @@ -2037,6 +2245,13 @@ return FALSE; } +void DeleteDeclaration::toCBuffer(OutBuffer *buf, HdrGenState *hgs) +{ + buf->writestring("delete"); + Argument::argsToCBuffer(buf, hgs, arguments, 0); + bodyToCBuffer(buf, hgs); +} + diff -uNr gdc-0.17/d/dmd/hdrgen.c gdc-0.18/d/dmd/hdrgen.c --- gdc-0.17/d/dmd/hdrgen.c 1970-01-01 01:00:00.000000000 +0100 +++ gdc-0.18/d/dmd/hdrgen.c 2006-03-12 15:16:26.000000000 +0100 @@ -0,0 +1,97 @@ + +// Copyright (c) 1999-2005 by Digital Mars +// All Rights Reserved +// Initial header generation implementation by Dave Fladebo +// www.digitalmars.com +// License for redistribution is by either the Artistic License +// in artistic.txt, or the GNU General Public License in gnu.txt. +// See the included readme.txt for details. + +// Routines to emit header files + +#ifdef _DH + +#define PRETTY_PRINT +#define TEST_EMIT_ALL 0 // For Testing + +#define LOG 0 + +#include +#include +#include +#if __DMC__ +#include +#endif + +#include "id.h" +#include "init.h" + +#include "attrib.h" +#include "cond.h" +#include "enum.h" +#include "import.h" +#include "module.h" +#include "mtype.h" +#include "scope.h" +#include "staticassert.h" +#include "template.h" +#include "utf.h" +#include "version.h" + +#include "declaration.h" +#include "aggregate.h" +#include "expression.h" +#include "statement.h" +#include "mtype.h" +#include "hdrgen.h" + +void argsToCBuffer(OutBuffer *buf, Array *arguments, HdrGenState *hgs); + +void Module::genhdrfile() +{ + OutBuffer hdrbufr; + + hdrbufr.printf("// D import file generated from '%s'", srcfile->toChars()); + hdrbufr.writenl(); + + HdrGenState hgs; + memset(&hgs, 0, sizeof(hgs)); + hgs.hdrgen = 1; + + toCBuffer(&hdrbufr, &hgs); + + // Transfer image to file + hdrfile->setbuffer(hdrbufr.data, hdrbufr.offset); + hdrbufr.data = NULL; + + hdrfile->writev(); +} + + +void Module::toCBuffer(OutBuffer *buf, HdrGenState *hgs) +{ + if (md) + { + buf->writestring("module "); + buf->writestring(md->toChars()); + buf->writebyte(';'); + buf->writenl(); + } + + for (int i = 0; i < members->dim; i++) + { Dsymbol *s = (Dsymbol *)members->data[i]; + + s->toHBuffer(buf, hgs); + } +} + + +void Dsymbol::toHBuffer(OutBuffer *buf, HdrGenState *hgs) +{ + toCBuffer(buf, hgs); +} + + +/*************************************/ + +#endif // #ifdef _DH diff -uNr gdc-0.17/d/dmd/hdrgen.h gdc-0.18/d/dmd/hdrgen.h --- gdc-0.17/d/dmd/hdrgen.h 1970-01-01 01:00:00.000000000 +0100 +++ gdc-0.18/d/dmd/hdrgen.h 2006-05-13 21:05:42.000000000 +0200 @@ -0,0 +1,32 @@ + +// Copyright (c) 1999-2005 by Digital Mars +// All Rights Reserved +// initial header generation implementation by Dave Fladebo +// www.digitalmars.com +// License for redistribution is by either the Artistic License +// in artistic.txt, or the GNU General Public License in gnu.txt. +// See the included readme.txt for details. + + +struct HdrGenState +{ + int hdrgen; // 1 if generating header file + int ddoc; // 1 if generating Ddoc file + int tpltMember; + int inCallExp; + int inPtrExp; + int inSlcExp; + int inDotExp; + int inBinExp; + int inArrExp; + int emitInst; + struct + { + int init; + int decl; + } FLinit; + + HdrGenState() { memset(this, 0, sizeof(HdrGenState)); } +}; + + diff -uNr gdc-0.17/d/dmd/html.c gdc-0.18/d/dmd/html.c --- gdc-0.17/d/dmd/html.c 2005-11-27 16:59:45.000000000 +0100 +++ gdc-0.18/d/dmd/html.c 2005-12-10 03:31:59.000000000 +0100 @@ -22,7 +22,7 @@ #include #include #include -#include +//#include #include "mars.h" #include "html.h" diff -uNr gdc-0.17/d/dmd/identifier.c gdc-0.18/d/dmd/identifier.c --- gdc-0.17/d/dmd/identifier.c 2005-05-29 23:09:19.000000000 +0200 +++ gdc-0.18/d/dmd/identifier.c 2006-04-16 17:13:30.000000000 +0200 @@ -1,5 +1,5 @@ -// Copyright (c) 1999-2004 by Digital Mars +// Copyright (c) 1999-2005 by Digital Mars // All Rights Reserved // written by Walter Bright // www.digitalmars.com @@ -49,9 +49,29 @@ return (char *)string; } +char *Identifier::toHChars2() +{ + char *p = NULL; + + if (this == Id::ctor) p = "this"; + else if (this == Id::dtor) p = "~this"; + else if (this == Id::classInvariant) p = "invariant"; + else if (this == Id::unitTest) p = "unittest"; + else if (this == Id::staticCtor) p = "static this"; + else if (this == Id::staticDtor) p = "static ~this"; + else if (this == Id::dollar) p = "$"; + else if (this == Id::withSym) p = "with"; + else if (this == Id::result) p = "result"; + else if (this == Id::returnLabel) p = "return"; + else + p = toChars(); + + return p; +} + void Identifier::print() { - fprintf(stderr, "%s",string); + fprintf(stdmsg, "%s",string); } int Identifier::dyncast() diff -uNr gdc-0.17/d/dmd/identifier.h gdc-0.18/d/dmd/identifier.h --- gdc-0.17/d/dmd/identifier.h 2005-01-10 04:30:55.000000000 +0100 +++ gdc-0.18/d/dmd/identifier.h 2006-03-12 15:16:26.000000000 +0100 @@ -1,5 +1,5 @@ -// Copyright (c) 1999-2004 by Digital Mars +// Copyright (c) 1999-2005 by Digital Mars // All Rights Reserved // written by Walter Bright // www.digitalmars.com @@ -28,6 +28,10 @@ int compare(Object *o); void print(); char *toChars(); +#ifdef _DH + char *toHChars(); +#endif + char *toHChars2(); int dyncast(); static Identifier *generateId(char *prefix); diff -uNr gdc-0.17/d/dmd/idgen.c gdc-0.18/d/dmd/idgen.c --- gdc-0.17/d/dmd/idgen.c 2005-09-09 23:27:05.000000000 +0200 +++ gdc-0.18/d/dmd/idgen.c 2006-04-16 17:13:30.000000000 +0200 @@ -43,6 +43,7 @@ { "size" }, { "__sizeof", "sizeof" }, { "alignof" }, + { "mangleof" }, { "length" }, { "remove" }, { "ptr" }, @@ -61,6 +62,7 @@ { "line" }, { "empty", "" }, { "p" }, + { "coverage", "__coverage" }, { "TypeInfo" }, { "TypeInfo_Class" }, @@ -75,6 +77,7 @@ { "TypeInfo_Delegate" }, { "_arguments" }, { "_argptr" }, + { "_match" }, { "LINE", "__LINE__" }, { "FILE", "__FILE__" }, @@ -99,6 +102,10 @@ { "Windows" }, { "Pascal" }, + { "exit" }, + { "success" }, + { "failure" }, + { "keys" }, { "values" }, { "rehash" }, @@ -161,8 +168,11 @@ { "index", "opIndex" }, { "indexass", "opIndexAssign" }, { "slice", "opSlice" }, + { "sliceass", "opSliceAssign" }, { "call", "opCall" }, { "cast", "opCast" }, + { "match", "opMatch" }, + { "next", "opNext" }, { "classNew", "new" }, { "classDelete", "delete" }, diff -uNr gdc-0.17/d/dmd/impcnvgen.c gdc-0.18/d/dmd/impcnvgen.c --- gdc-0.17/d/dmd/impcnvgen.c 2005-04-28 23:12:43.000000000 +0200 +++ gdc-0.18/d/dmd/impcnvgen.c 2006-04-16 17:13:30.000000000 +0200 @@ -1,5 +1,5 @@ -// Copyright (c) 1999-2002 by Digital Mars +// Copyright (c) 1999-2006 by Digital Mars // All Rights Reserved // written by Walter Bright // www.digitalmars.com @@ -24,6 +24,7 @@ case Tchar: case Twchar: case Tbit: + case Tbool: case Tint8: case Tuns8: case Tint16: @@ -74,6 +75,28 @@ /* ======================= */ + X(Tbool,Tbool, Tbool,Tbool, Tbool) + X(Tbool,Tint8, Tint32,Tint32, Tint32) + X(Tbool,Tuns8, Tint32,Tint32, Tint32) + X(Tbool,Tint16, Tint32,Tint32, Tint32) + X(Tbool,Tuns16, Tint32,Tint32, Tint32) + X(Tbool,Tint32, Tint32,Tint32, Tint32) + X(Tbool,Tuns32, Tuns32,Tuns32, Tuns32) + X(Tbool,Tint64, Tint64,Tint64, Tint64) + X(Tbool,Tuns64, Tuns64,Tuns64, Tuns64) + + X(Tbool,Tfloat32, Tfloat32,Tfloat32, Tfloat32) + X(Tbool,Tfloat64, Tfloat64,Tfloat64, Tfloat64) + X(Tbool,Tfloat80, Tfloat80,Tfloat80, Tfloat80) + X(Tbool,Timaginary32, Tfloat32,Timaginary32, Tfloat32) + X(Tbool,Timaginary64, Tfloat64,Timaginary64, Tfloat64) + X(Tbool,Timaginary80, Tfloat80,Timaginary80, Tfloat80) + X(Tbool,Tcomplex32, Tfloat32,Tcomplex32, Tcomplex32) + X(Tbool,Tcomplex64, Tfloat64,Tcomplex64, Tcomplex64) + X(Tbool,Tcomplex80, Tfloat80,Tcomplex80, Tcomplex80) + + /* ======================= */ + X(Tint8,Tint8, Tint32,Tint32, Tint32) X(Tint8,Tuns8, Tint32,Tint32, Tint32) X(Tint8,Tint16, Tint32,Tint32, Tint32) diff -uNr gdc-0.17/d/dmd/import.c gdc-0.18/d/dmd/import.c --- gdc-0.17/d/dmd/import.c 2005-05-29 23:09:19.000000000 +0200 +++ gdc-0.18/d/dmd/import.c 2006-03-12 15:16:26.000000000 +0100 @@ -1,5 +1,5 @@ -// Copyright (c) 1999-2002 by Digital Mars +// Copyright (c) 1999-2005 by Digital Mars // All Rights Reserved // written by Walter Bright // www.digitalmars.com @@ -16,6 +16,7 @@ #include "identifier.h" #include "module.h" #include "scope.h" +#include "hdrgen.h" /********************************* Import ****************************/ @@ -132,8 +133,11 @@ return s->isImport() != NULL; } -void Import::toCBuffer(OutBuffer *buf) +void Import::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { + if (hgs->hdrgen && id == Id::object) + return; // object is imported by default + buf->writestring("import "); if (packages && packages->dim) { int i; diff -uNr gdc-0.17/d/dmd/import.h gdc-0.18/d/dmd/import.h --- gdc-0.17/d/dmd/import.h 2005-05-29 23:09:19.000000000 +0200 +++ gdc-0.18/d/dmd/import.h 2006-03-12 15:16:26.000000000 +0100 @@ -1,5 +1,5 @@ -// Copyright (c) 1999-2002 by Digital Mars +// Copyright (c) 1999-2005 by Digital Mars // All Rights Reserved // written by Walter Bright // www.digitalmars.com @@ -22,6 +22,9 @@ struct OutBuffer; struct Module; struct Package; +#ifdef _DH +struct HdrGenState; +#endif struct Import : Dsymbol { @@ -38,7 +41,7 @@ void semantic2(Scope *sc); Dsymbol *search(Identifier *ident, int flags); int overloadInsert(Dsymbol *s); - void toCBuffer(OutBuffer *buf); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); Import *isImport() { return this; } }; diff -uNr gdc-0.17/d/dmd/init.c gdc-0.18/d/dmd/init.c --- gdc-0.17/d/dmd/init.c 2005-10-26 03:33:56.000000000 +0200 +++ gdc-0.18/d/dmd/init.c 2006-03-12 15:16:26.000000000 +0100 @@ -89,7 +89,7 @@ } -void VoidInitializer::toCBuffer(OutBuffer *buf) +void VoidInitializer::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { buf->writestring("void"); } @@ -214,8 +214,24 @@ } -void StructInitializer::toCBuffer(OutBuffer *buf) +void StructInitializer::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { + buf->writebyte('{'); + for (int i = 0; i < field.dim; i++) + { + if (i > 0) + buf->writebyte(','); + Identifier *id = (Identifier *)field.data[i]; + if (id) + { + buf->writestring(id->toChars()); + buf->writebyte(':'); + } + Initializer *iz = (Initializer *)value.data[i]; + if (iz) + iz->toCBuffer(buf, hgs); + } + buf->writebyte('}'); } /********************************** ArrayInitializer ************************************/ @@ -316,8 +332,24 @@ } -void ArrayInitializer::toCBuffer(OutBuffer *buf) +void ArrayInitializer::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { + buf->writebyte('['); + for (int i = 0; i < index.dim; i++) + { + if (i > 0) + buf->writebyte(','); + Expression *ex = (Expression *)index.data[i]; + if (ex) + { + ex->toCBuffer(buf, hgs); + buf->writebyte(':'); + } + Initializer *iz = (Initializer *)value.data[i]; + if (iz) + iz->toCBuffer(buf, hgs); + } + buf->writebyte(']'); } @@ -387,9 +419,9 @@ } -void ExpInitializer::toCBuffer(OutBuffer *buf) +void ExpInitializer::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { - exp->toCBuffer(buf); + exp->toCBuffer(buf, hgs); } diff -uNr gdc-0.17/d/dmd/init.h gdc-0.18/d/dmd/init.h --- gdc-0.17/d/dmd/init.h 2005-10-26 03:33:56.000000000 +0200 +++ gdc-0.18/d/dmd/init.h 2006-03-12 15:16:26.000000000 +0100 @@ -22,6 +22,9 @@ struct AggregateDeclaration; struct VoidInitializer; struct ExpInitializer; +#ifdef _DH +struct HdrGenState; +#endif struct Initializer : Object { @@ -32,7 +35,7 @@ virtual Initializer *semantic(Scope *sc, Type *t); virtual Type *inferType(Scope *sc); virtual Expression *toExpression() = 0; - virtual void toCBuffer(OutBuffer *buf) = 0; + virtual void toCBuffer(OutBuffer *buf, HdrGenState *hgs) = 0; static Array *arraySyntaxCopy(Array *ai); @@ -50,7 +53,7 @@ Initializer *syntaxCopy(); Initializer *semantic(Scope *sc, Type *t); Expression *toExpression(); - void toCBuffer(OutBuffer *buf); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); dt_t *toDt(); @@ -68,7 +71,7 @@ void addInit(Identifier *field, Initializer *value); Initializer *semantic(Scope *sc, Type *t); Expression *toExpression(); - void toCBuffer(OutBuffer *buf); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); dt_t *toDt(); }; @@ -86,7 +89,7 @@ void addInit(Expression *index, Initializer *value); Initializer *semantic(Scope *sc, Type *t); Expression *toExpression(); - void toCBuffer(OutBuffer *buf); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); dt_t *toDt(); dt_t *toDtBit(); // for bit arrays @@ -101,7 +104,7 @@ Initializer *semantic(Scope *sc, Type *t); Type *inferType(Scope *sc); Expression *toExpression(); - void toCBuffer(OutBuffer *buf); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); dt_t *toDt(); diff -uNr gdc-0.17/d/dmd/inline.c gdc-0.18/d/dmd/inline.c --- gdc-0.17/d/dmd/inline.c 2005-10-24 23:48:04.000000000 +0200 +++ gdc-0.18/d/dmd/inline.c 2006-05-14 01:38:32.000000000 +0200 @@ -1,5 +1,5 @@ -// Copyright (c) 1999-2005 by Digital Mars +// Copyright (c) 1999-2006 by Digital Mars // All Rights Reserved // written by Walter Bright // www.digitalmars.com @@ -33,6 +33,7 @@ { int nested; int hasthis; + int hdrscan; // !=0 if inline scan for 'header' content FuncDeclaration *fd; }; @@ -117,7 +118,8 @@ for (int i = 0; i < arguments->dim; i++) { Expression *e = (Expression *)arguments->data[i]; - cost += e->inlineCost(ics); + if (e) + cost += e->inlineCost(ics); } } return cost; @@ -131,16 +133,18 @@ int ThisExp::inlineCost(InlineCostState *ics) { FuncDeclaration *fd = ics->fd; - if (fd->isNested() || !ics->hasthis) - return COST_MAX; + if (!ics->hdrscan) + if (fd->isNested() || !ics->hasthis) + return COST_MAX; return 1; } int SuperExp::inlineCost(InlineCostState *ics) { FuncDeclaration *fd = ics->fd; - if (fd->isNested() || !ics->hasthis) - return COST_MAX; + if (!ics->hdrscan) + if (fd->isNested() || !ics->hasthis) + return COST_MAX; return 1; } @@ -159,10 +163,11 @@ { int cost = 0; VarDeclaration *vd; + //printf("DeclarationExp::inlineCost()\n"); vd = declaration->isVarDeclaration(); if (vd) { - if (vd->isDataseg()) + if (!ics->hdrscan && vd->isDataseg()) return COST_MAX; cost += 1; @@ -332,19 +337,22 @@ * Perform doInline() on an array of Expressions. */ -Array *arrayExpressiondoInline(Array *a, InlineDoState *ids) -{ Array *newa = NULL; +Expressions *arrayExpressiondoInline(Expressions *a, InlineDoState *ids) +{ Expressions *newa = NULL; if (a) { - newa = new Array(); + newa = new Expressions(); newa->setDim(a->dim); for (int i = 0; i < a->dim; i++) { Expression *e = (Expression *)a->data[i]; - e = e->doInline(ids); - newa->data[i] = (void *)e; + if (e) + { + e = e->doInline(ids); + newa->data[i] = (void *)e; + } } } return newa; @@ -592,7 +600,7 @@ } -/* ========== Walk the parse trees, and inline expand functions =============== */ +/* ========== Walk the parse trees, and inline expand functions ============= */ /* Walk the trees, looking for functions to inline. * Inline any that can be. @@ -810,8 +818,11 @@ for (int i = 0; i < arguments->dim; i++) { Expression *e = (Expression *)arguments->data[i]; - e = e->inlineScan(iss); - arguments->data[i] = (void *)e; + if (e) + { + e = e->inlineScan(iss); + arguments->data[i] = (void *)e; + } } } } @@ -823,7 +834,23 @@ Expression *DeclarationExp::inlineScan(InlineScanState *iss) { - // Should scan variable initializers + VarDeclaration *vd; + + //printf("DeclarationExp::inlineScan()\n"); + vd = declaration->isVarDeclaration(); + if (vd) + { + // Scan initializer (vd->init) + if (vd->init) + { + ExpInitializer *ie = vd->init->isExpInitializer(); + + if (ie) + { + ie->exp = ie->exp->inlineScan(iss); + } + } + } return this; } @@ -933,7 +960,7 @@ } } -int FuncDeclaration::canInline(int hasthis) +int FuncDeclaration::canInline(int hasthis, int hdrscan) { InlineCostState ics; int cost; @@ -944,7 +971,7 @@ printf("FuncDeclaration::canInline('%s')\n", toChars()); #endif - if (inlineNest || !semanticRun) + if (inlineNest || (!semanticRun && !hdrscan)) { #if CANINLINE_LOG printf("\t1: no, inlineNest = %d, semanticRun = %d\n", inlineNest, semanticRun); @@ -973,10 +1000,23 @@ assert(0); } - assert(type->ty == Tfunction); - TypeFunction *tf = (TypeFunction *)(type); + if (type) + { assert(type->ty == Tfunction); + TypeFunction *tf = (TypeFunction *)(type); + if (tf->varargs == 1) // no variadic parameter lists + goto Lno; + } + else + { CtorDeclaration *ctor = isCtorDeclaration(); + + if (ctor && ctor->varargs == 1) + goto Lno; + } if ( + !fbody || + !hdrscan && + ( #if 0 isCtorDeclaration() || // cannot because need to convert: // return; @@ -985,11 +1025,9 @@ #endif isSynchronized() || isImportedSymbol() || - !fbody || - tf->varargs == 1 || // no variadic parameter lists nestedFrameRef || // no nested references to this frame (isVirtual() && !isFinal()) - ) + )) { goto Lno; } @@ -1010,6 +1048,7 @@ memset(&ics, 0, sizeof(ics)); ics.hasthis = hasthis; ics.fd = this; + ics.hdrscan = hdrscan; cost = fbody->inlineCost(&ics); #if CANINLINE_LOG printf("cost = %d\n", cost); @@ -1017,17 +1056,20 @@ if (cost >= COST_MAX) goto Lno; - inlineScan(); + if (!hdrscan) // Don't scan recursively for header content scan + inlineScan(); Lyes: - inlineStatus = ILSyes; + if (!hdrscan) // Don't modify inlineStatus for header content scan + inlineStatus = ILSyes; #if CANINLINE_LOG printf("\tyes\n"); #endif return 1; Lno: - inlineStatus = ILSno; + if (!hdrscan) // Don't modify inlineStatus for header content scan + inlineStatus = ILSno; #if CANINLINE_LOG printf("\tno\n"); #endif diff -uNr gdc-0.17/d/dmd/lexer.c gdc-0.18/d/dmd/lexer.c --- gdc-0.17/d/dmd/lexer.c 2005-10-26 03:33:56.000000000 +0200 +++ gdc-0.18/d/dmd/lexer.c 2006-05-14 04:21:51.000000000 +0200 @@ -1,5 +1,5 @@ -// Copyright (c) 1999-2005 by Digital Mars +// Copyright (c) 1999-2006 by Digital Mars // All Rights Reserved // written by Walter Bright // www.digitalmars.com @@ -20,7 +20,7 @@ #include #include #include -#include +//#include #include #include #include @@ -39,12 +39,9 @@ #if _WIN32 #include "..\root\mem.h" -#elif ! defined(_WIN32) -#include "../root/mem.h" #else -#error "fix this" +#include "../root/mem.h" #endif - #endif #include "stringtable.h" @@ -111,10 +108,12 @@ return ::operator new(size); } +#ifdef DEBUG void Token::print() { - fprintf(stderr, "%s\n", toChars()); + fprintf(stdmsg, "%s\n", toChars()); } +#endif char *Token::toChars() { char *p; @@ -124,14 +123,22 @@ switch (value) { case TOKint32v: +#if IN_GCC sprintf(buffer,"%ld",(d_int32)int64value); +#else + sprintf(buffer,"%ld",int32value); +#endif break; case TOKuns32v: case TOKcharv: case TOKwcharv: case TOKdcharv: +#if IN_GCC sprintf(buffer,"%luU",(d_uns32)uns64value); +#else + sprintf(buffer,"%luU",uns32value); +#endif break; case TOKint64v: @@ -186,7 +193,40 @@ #if CSTRINGS p = string; #else - p = (char *)ustring; + { OutBuffer buf; + + buf.writeByte('"'); + for (unsigned i = 0; i < len; ) + { unsigned c; + + utf_decodeChar((unsigned char *)ustring, len, &i, &c); + switch (c) + { + case 0: + break; + + case '"': + case '\\': + buf.writeByte('\\'); + default: + if (isprint(c)) + buf.writeByte(c); + else if (c <= 0x7F) + buf.printf("\\x%02x", c); + else if (c <= 0xFFFF) + buf.printf("\\u%04x", c); + else + buf.printf("\\U%08x", c); + continue; + } + break; + } + buf.writeByte('"'); + if (postfix) + buf.writeByte('"'); + buf.writeByte(0); + p = (char *)buf.extractData(); + } #endif break; @@ -239,23 +279,46 @@ this->anyToken = 0; this->commentToken = commentToken; //initKeywords(); -} -#if 0 -unsigned Lexer::locToLine(Loc loc) -{ - unsigned linnum = 1; - unsigned char *s; - unsigned char *p = base + loc; + /* If first line starts with '#!', ignore the line + */ - for (s = base; s != p; s++) + if (p[0] == '#' && p[1] =='!') { - if (*s == '\n') - linnum++; + p += 2; + while (1) + { unsigned char c = *p; + switch (c) + { + case '\n': + p++; + break; + + case '\r': + p++; + if (*p == '\n') + p++; + break; + + case 0: + case 0x1A: + break; + + default: + if (c & 0x80) + { unsigned u = decodeUTF(); + if (u == PS || u == LS) + break; + } + p++; + continue; + } + break; + } + loc.linnum = 2; } - return linnum; } -#endif + void Lexer::error(const char *format, ...) { @@ -263,18 +326,18 @@ { char *p = loc.toChars(); if (*p) - fprintf(stderr, "%s: ", p); + fprintf(stdmsg, "%s: ", p); mem.free(p); va_list ap; va_start(ap, format); - vfprintf(stderr, format, ap); + vfprintf(stdmsg, format, ap); va_end(ap); - fprintf(stderr, "\n"); - fflush(stderr); + fprintf(stdmsg, "\n"); + fflush(stdmsg); - if (global.errors > 20) // moderate blizzard of cascading messages + if (global.errors >= 20) // moderate blizzard of cascading messages fatal(); } global.errors++; @@ -286,18 +349,18 @@ { char *p = loc.toChars(); if (*p) - fprintf(stderr, "%s: ", p); + fprintf(stdmsg, "%s: ", p); mem.free(p); va_list ap; va_start(ap, format); - vfprintf(stderr, format, ap); + vfprintf(stdmsg, format, ap); va_end(ap); - fprintf(stderr, "\n"); - fflush(stderr); + fprintf(stdmsg, "\n"); + fflush(stdmsg); - if (global.errors > 20) // moderate blizzard of cascading messages + if (global.errors >= 20) // moderate blizzard of cascading messages fatal(); } global.errors++; @@ -924,6 +987,16 @@ t->value = TOKassign; // = return; + case '~': + p++; + if (*p == '=') + { p++; + t->value = TOKcatass; // ~= + } + else + t->value = TOKtilde; // ~ + return; + #define SINGLE(c,tok) case c: p++; t->value = tok; return; SINGLE('(', TOKlparen) @@ -954,7 +1027,6 @@ DOUBLE('*', TOKmul, '=', TOKmulass) DOUBLE('%', TOKmod, '=', TOKmodass) DOUBLE('^', TOKxor, '=', TOKxorass) - DOUBLE('~', TOKtilde, '=', TOKcatass) #undef DOUBLE @@ -1426,6 +1498,7 @@ * u 'u' or 'U' */ +#if 0 unsigned Lexer::wchar(unsigned u) { unsigned value; @@ -1456,6 +1529,7 @@ } return value; } +#endif /************************************** * Read in a number. @@ -1700,7 +1774,7 @@ uinteger_t n; // unsigned >=64 bit integer type - if (stringbuffer.offset == 1 && (state == STATE_decimal || state == STATE_0)) + if (stringbuffer.offset == 2 && (state == STATE_decimal || state == STATE_0)) n = stringbuffer.data[0] - '0'; else { @@ -1762,8 +1836,11 @@ case 'u': f = FLAGS_unsigned; goto L1; - case 'L': + case 'l': + if (!global.params.useDeprecated) + error("'l' suffix is deprecated, use 'L' instead"); + case 'L': f = FLAGS_long; L1: p++; @@ -1780,6 +1857,9 @@ switch (flags) { case 0: + /* Octal or Hexadecimal constant. + * First that fits: int, uint, long, ulong + */ if (n & 0x8000000000000000LL) result = TOKuns64v; else if (n & 0xFFFFFFFF00000000LL) @@ -1791,6 +1871,8 @@ break; case FLAGS_decimal: + /* First that fits: int, long, long long + */ if (n & 0x8000000000000000LL) { error("signed integer overflow"); result = TOKuns64v; @@ -1803,6 +1885,8 @@ case FLAGS_unsigned: case FLAGS_decimal | FLAGS_unsigned: + /* First that fits: uint, ulong + */ if (n & 0xFFFFFFFF00000000LL) result = TOKuns64v; else @@ -1987,14 +2071,18 @@ result = TOKfloat64v; break; - case 'L': case 'l': + if (!global.params.useDeprecated) + error("'l' suffix is deprecated, use 'L' instead"); + case 'L': result = TOKfloat80v; p++; break; } if (*p == 'i' || *p == 'I') { + if (!global.params.useDeprecated && *p == 'I') + error("'I' suffix is deprecated, use 'i' instead"); p++; switch (result) { @@ -2144,8 +2232,7 @@ char *msg; c = *s; - if (!(c & 0x80)) - return c; + assert(c & 0x80); // Check length of remaining string up to 6 UTF-8 characters for (len = 1; len < 6 && s[len]; len++) @@ -2349,7 +2436,6 @@ { "iftype", TOKiftype }, { "template", TOKtemplate }, - { "instance", TOKinstance }, { "void", TOKvoid }, { "byte", TOKint8 }, @@ -2366,8 +2452,9 @@ { "double", TOKfloat64 }, { "real", TOKfloat80 }, - { "bit", TOKbit }, - { "char", TOKchar }, +/* { "bit", TOKbit }, */ + { "bool", TOKbool }, + { "char", TOKchar }, { "wchar", TOKwchar }, { "dchar", TOKdchar }, @@ -2402,6 +2489,10 @@ { "with", TOKwith }, { "asm", TOKasm }, { "foreach", TOKforeach }, + { "scope", TOKscope }, + { "on_scope_exit", TOKon_scope_exit }, + { "on_scope_failure", TOKon_scope_failure }, + { "on_scope_success", TOKon_scope_success }, { "struct", TOKstruct }, { "class", TOKclass }, @@ -2490,8 +2581,8 @@ Token::tochars[TOKge] = ">="; Token::tochars[TOKequal] = "=="; Token::tochars[TOKnotequal] = "!="; - Token::tochars[TOKidentity] = "==="; - Token::tochars[TOKnotidentity] = "!=="; + Token::tochars[TOKnotidentity] = "!is"; + Token::tochars[TOKtobool] = "!!"; Token::tochars[TOKunord] = "!<>="; Token::tochars[TOKue] = "!<>"; @@ -2503,6 +2594,7 @@ Token::tochars[TOKug] = "!<="; Token::tochars[TOKnot] = "!"; + Token::tochars[TOKtobool] = "!!"; Token::tochars[TOKshl] = "<<"; Token::tochars[TOKshr] = ">>"; Token::tochars[TOKushr] = ">>>"; @@ -2519,7 +2611,7 @@ Token::tochars[TOKoror] = "||"; Token::tochars[TOKarray] = "[]"; Token::tochars[TOKindex] = "[i]"; - Token::tochars[TOKaddress] = "#"; + Token::tochars[TOKaddress] = "&"; Token::tochars[TOKstar] = "*"; Token::tochars[TOKtilde] = "~"; Token::tochars[TOKdollar] = "$"; @@ -2544,6 +2636,8 @@ Token::tochars[TOKcatass] = "~="; Token::tochars[TOKcat] = "~"; Token::tochars[TOKcall] = "call"; + Token::tochars[TOKidentity] = "is"; + Token::tochars[TOKnotidentity] = "!is"; Token::tochars[TOKorass] = "|="; @@ -2556,4 +2650,5 @@ Token::tochars[TOKtypedot] = "typedot"; Token::tochars[TOKarraylength] = "arraylength"; Token::tochars[TOKstring] = "string"; + Token::tochars[TOKdsymbol] = "symbol"; } diff -uNr gdc-0.17/d/dmd/lexer.h gdc-0.18/d/dmd/lexer.h --- gdc-0.17/d/dmd/lexer.h 2005-10-13 03:06:51.000000000 +0200 +++ gdc-0.18/d/dmd/lexer.h 2006-04-16 17:13:30.000000000 +0200 @@ -1,6 +1,6 @@ -// Copyright (c) 1999-2002 by Digital Mars +// Copyright (c) 1999-2006 by Digital Mars // All Rights Reserved // written by Walter Bright // www.digitalmars.com @@ -8,12 +8,6 @@ // in artistic.txt, or the GNU General Public License in gnu.txt. // See the included readme.txt for details. -/* NOTE: This file has been patched from the original DMD distribution to - work with the GDC compiler. - - Modified by David Friedman, September 2004 -*/ - #ifndef DMD_LEXER_H #define DMD_LEXER_H @@ -66,7 +60,7 @@ TOKdottype, TOKslice, TOKarraylength, TOKversion, TOKmodule, TOKdollar, - TOKtemplate, TOKinstance, + TOKtemplate, TOKdeclaration, TOKtypeof, TOKpragma, TOKdsymbol, TOKtypeid, TOKuadd, @@ -79,6 +73,7 @@ TOKequal, TOKnotequal, TOKidentity, TOKnotidentity, TOKindex, TOKis, + TOKtobool, // NCEG floating point compares // !<>= <> <>= !> !>= !< !<= !<> @@ -121,7 +116,7 @@ TOKfloat32, TOKfloat64, TOKfloat80, TOKimaginary32, TOKimaginary64, TOKimaginary80, TOKcomplex32, TOKcomplex64, TOKcomplex80, - TOKchar, TOKwchar, TOKdchar, TOKbit, + TOKchar, TOKwchar, TOKdchar, TOKbit, TOKbool, TOKcent, TOKucent, // Aggregates @@ -139,6 +134,8 @@ TOKcase, TOKdefault, TOKbreak, TOKcontinue, TOKwith, TOKsynchronized, TOKreturn, TOKgoto, TOKtry, TOKcatch, TOKfinally, TOKasm, TOKforeach, + TOKscope, + TOKon_scope_exit, TOKon_scope_failure, TOKon_scope_success, // Contracts TOKbody, TOKinvariant, @@ -151,7 +148,7 @@ #define CASE_BASIC_TYPES \ case TOKwchar: case TOKdchar: \ - case TOKbit: case TOKchar: \ + case TOKbit: case TOKbool: case TOKchar: \ case TOKint8: case TOKuns8: \ case TOKint16: case TOKuns16: \ case TOKint32: case TOKuns32: \ @@ -181,6 +178,7 @@ case TOKcomplex64: t = Type::tcomplex64; goto LabelX; \ case TOKcomplex80: t = Type::tcomplex80; goto LabelX; \ case TOKbit: t = Type::tbit; goto LabelX; \ + case TOKbool: t = Type::tbool; goto LabelX; \ case TOKchar: t = Type::tchar; goto LabelX; \ case TOKwchar: t = Type::twchar; goto LabelX; \ case TOKdchar: t = Type::tdchar; goto LabelX; \ @@ -224,7 +222,7 @@ static void *operator new(size_t sz); int isKeyword(); - void print(); + void print(); char *toChars(); static char *toChars(enum TOK); }; diff -uNr gdc-0.17/d/dmd/link.c gdc-0.18/d/dmd/link.c --- gdc-0.17/d/dmd/link.c 2005-05-29 23:09:19.000000000 +0200 +++ gdc-0.18/d/dmd/link.c 2006-05-14 03:16:44.000000000 +0200 @@ -1,6 +1,6 @@ -// Copyright (c) 1999-2002 by Digital Mars +// Copyright (c) 1999-2006 by Digital Mars // All Rights Reserved // written by Walter Bright // www.digitalmars.com @@ -66,8 +66,19 @@ cmdbuf.writeByte(','); if (global.params.exefile) cmdbuf.writestring(global.params.exefile); + else + { // Generate exe file name from first obj name + char *n = (char *)global.params.objfiles->data[0]; + char *ex; + + n = FileName::name(n); + FileName *fn = FileName::forceExt(n, "exe"); + global.params.exefile = fn->toChars(); + } cmdbuf.writeByte(','); + if (global.params.run) + cmdbuf.writestring("nul"); // if (mapfile) // cmdbuf.writestring(output); cmdbuf.writeByte(','); @@ -137,7 +148,10 @@ // Build argv[] Array argv; - argv.push((void *)"gcc"); + char *cc = getenv("CC"); + if (!cc) + cc = "gcc"; + argv.push((void *)cc); argv.insert(1, global.params.objfiles); // None of that a.out stuff. Use explicit exe file name, or @@ -165,6 +179,7 @@ else ex = (char *)"a.out"; // no extension, so give up argv.push(ex); + global.params.exefile = ex; } argv.insert(argv.dim, global.params.libfiles); @@ -176,6 +191,21 @@ argv.push((void *)"-lpthread"); argv.push((void *)"-lm"); + if (0 && global.params.exefile) + { + /* This switch enables what is known as 'smart linking' + * in the Windows world, where unreferenced sections + * are removed from the executable. It eliminates unreferenced + * functions, essentially making a 'library' out of a module. + * Although it is documented to work with ld version 2.13, + * in practice it does not, but just seems to be ignored. + * Thomas Kuehne has verified that it works with ld 2.16.1. + * BUG: disabled because it causes exception handling to fail + */ + argv.push((void *)"-Xlinker"); + argv.push((void *)"--gc-sections"); + } + for (i = 0; i < global.params.linkswitches->dim; i++) { argv.push((void *)"-Xlinker"); @@ -212,6 +242,18 @@ #endif } +/********************************** + * Delete generated EXE file. + */ + +void deleteExeFile() +{ + if (global.params.exefile) + { + //printf("deleteExeFile() %s\n", global.params.exefile); + remove(global.params.exefile); + } +} /****************************** * Execute a rule. Return the status. @@ -227,9 +269,9 @@ char *buff; size_t len; -// if (global.params.verbose) + if (!global.params.quiet || global.params.verbose) { - printf("%s %s\n",cmd,args); + printf("%s %s\n", cmd, args); fflush(stdout); } @@ -259,8 +301,8 @@ if (status == -1) status = spawnlp(0,cmd,cmd,args,NULL); #endif - if (global.params.verbose) - printf("\n"); +// if (global.params.verbose) +// printf("\n"); if (status) { if (status == -1) @@ -318,3 +360,59 @@ } #endif +/*************************************** + * Run the compiled program. + * Return exit status. + */ + +int runProgram() +{ + //printf("runProgram()\n"); + if (global.params.verbose) + { + printf("%s", global.params.exefile); + for (size_t i = 0; i < global.params.runargs_length; i++) + printf(" %s", (char *)global.params.runargs[i]); + printf("\n"); + } + + // Build argv[] + Array argv; + + argv.push((void *)global.params.exefile); + for (size_t i = 0; i < global.params.runargs_length; i++) + argv.push((void *)global.params.runargs[i]); + argv.push(NULL); + +#if _WIN32 + char *ex = FileName::name(global.params.exefile); + if (ex == global.params.exefile) + ex = FileName::combine(".", ex); + else + ex = global.params.exefile; + return spawnv(0,ex,(char **)argv.data); +#elif linux + pid_t childpid; + int status; + + childpid = fork(); + if (childpid == 0) + { + char *fn = (char *)argv.data[0]; + if (!FileName::absolute(fn)) + { // Make it "./fn" + fn = FileName::combine(".", fn); + } + execv(fn, (char **)argv.data); + perror(fn); // failed to execute + return -1; + } + + waitpid(childpid, &status, 0); + + status = WEXITSTATUS(status); + return status; +#else + assert(0); +#endif +} diff -uNr gdc-0.17/d/dmd/macro.c gdc-0.18/d/dmd/macro.c --- gdc-0.17/d/dmd/macro.c 2005-10-24 23:48:04.000000000 +0200 +++ gdc-0.18/d/dmd/macro.c 2006-04-16 17:13:30.000000000 +0200 @@ -1,5 +1,5 @@ -// Copyright (c) 1999-2005 by Digital Mars +// Copyright (c) 1999-2006 by Digital Mars // All Rights Reserved // written by Walter Bright // www.digitalmars.com @@ -14,6 +14,7 @@ #include #include #include +#include #ifdef IN_GCC #include "mem.h" diff -uNr gdc-0.17/d/dmd/macro.h gdc-0.18/d/dmd/macro.h --- gdc-0.17/d/dmd/macro.h 2005-10-13 03:06:51.000000000 +0200 +++ gdc-0.18/d/dmd/macro.h 2006-05-08 12:41:19.000000000 +0200 @@ -30,7 +30,7 @@ int inuse; // macro is in use (don't expand) Macro(unsigned char *name, size_t namelen, unsigned char *text, size_t textlen); - Macro *Macro::search(unsigned char *name, size_t namelen); + Macro *search(unsigned char *name, size_t namelen); public: static Macro *define(Macro **ptable, unsigned char *name, size_t namelen, unsigned char *text, size_t textlen); diff -uNr gdc-0.17/d/dmd/mangle.c gdc-0.18/d/dmd/mangle.c --- gdc-0.17/d/dmd/mangle.c 2005-05-29 23:09:19.000000000 +0200 +++ gdc-0.18/d/dmd/mangle.c 2006-05-14 03:05:56.000000000 +0200 @@ -1,5 +1,5 @@ -// Copyright (c) 1999-2005 by Digital Mars +// Copyright (c) 1999-2006 by Digital Mars // All Rights Reserved // written by Walter Bright // www.digitalmars.com @@ -7,12 +7,6 @@ // in artistic.txt, or the GNU General Public License in gnu.txt. // See the included readme.txt for details. -/* NOTE: This file has been patched from the original DMD distribution to - work with the GDC compiler. - - Modified by David Friedman, May 2005 -*/ - #include #include #include @@ -68,7 +62,7 @@ return ident->toChars(); default: - fprintf(stderr, "'%s', linkage = %d\n", toChars(), linkage); + fprintf(stdmsg, "'%s', linkage = %d\n", toChars(), linkage); assert(0); } } @@ -154,9 +148,9 @@ ident == Id::TypeInfo_Class || ident == Id::TypeInfo_Typedef || ident == Id::Exception || - ident == Id::Object || - ident == Id::ClassInfo || - ident == Id::ModuleInfo || + this == object || + this == classinfo || + this == Module::moduleinfo || memcmp(ident->toChars(), "TypeInfo_", 9) == 0 ) parent = NULL; diff -uNr gdc-0.17/d/dmd/mars.c gdc-0.18/d/dmd/mars.c --- gdc-0.17/d/dmd/mars.c 2005-11-28 05:17:52.000000000 +0100 +++ gdc-0.18/d/dmd/mars.c 2006-05-18 02:05:55.000000000 +0200 @@ -1,5 +1,5 @@ -// Copyright (c) 1999-2005 by Digital Mars +// Copyright (c) 1999-2006 by Digital Mars // All Rights Reserved // written by Walter Bright // www.digitalmars.com @@ -13,6 +13,11 @@ #include #include +#if _WIN32 +#include +long __cdecl __ehfilter(LPEXCEPTION_POINTERS ep); +#endif + #if __DMC__ #include #endif @@ -29,6 +34,7 @@ #include "mtype.h" #include "id.h" #include "cond.h" +#include "expression.h" void getenv_setargv(const char *envvar, int *pargc, char** *pargv); @@ -38,6 +44,7 @@ { mars_ext = "d"; sym_ext = "d"; + hdr_ext = "di"; doc_ext = "html"; ddoc_ext = "ddoc"; @@ -49,9 +56,9 @@ #error "fix this" #endif - copyright = "Copyright (c) 1999-2005 by Digital Mars"; + copyright = "Copyright (c) 1999-2006 by Digital Mars"; written = "written by Walter Bright"; - version = "v0.140"; + version = "v0.157"; global.structalign = 8; memset(¶ms, 0, sizeof(Param)); @@ -90,16 +97,16 @@ char *p = loc.toChars(); if (*p) - printf("%s: ", p); + fprintf(stdmsg, "%s: ", p); mem.free(p); va_list ap; va_start(ap, format); - printf("Error: "); - vprintf(format, ap); + fprintf(stdmsg, "Error: "); + vfprintf(stdmsg, format, ap); va_end( ap ); - printf("\n"); - fflush(stdout); + fprintf(stdmsg, "\n"); + fflush(stdmsg); } global.errors++; } @@ -131,6 +138,7 @@ \n\ files.d D source files\n\ -c do not link\n\ + -cov do code coverage analysis\n\ -D generate documentation\n\ -Dddocdir write documentation file to docdir directory\n\ -Dffilename write documentation file to filename\n\ @@ -139,10 +147,14 @@ -debug=level compile in debug code <= level\n\ -debug=ident compile in debug code identified by ident\n\ -g add symbolic debug info\n\ + -H generate 'header' file\n\ + -Hdhdrdir write 'header' file to hdrdir directory\n\ + -Hffilename write 'header' file to filename\n\ --help print help\n\ -Ipath where to look for imports\n\ -inline do function inlining\n\ -Llinkerflag pass linkerflag to link\n\ + -nofloat do not emit reference to floating point\n\ -O optimize\n\ -o- do not write object file\n\ -odobjdir write object files to directory objdir\n\ @@ -151,6 +163,7 @@ -profile profile runtime performance of generated code\n\ -quiet suppress unnecessary messages\n\ -release compile release version\n\ + -run srcfile args... run resulting program, passing args\n\ -unittest compile in unit tests\n\ -v verbose\n\ -version=level compile in version code >= level\n\ @@ -166,11 +179,13 @@ char *p; Module *m; int status = EXIT_SUCCESS; + int argcstart = argc; // Initialization Type::init(); Id::initialize(); Module::init(); + initPrecedence(); backend_init(); @@ -210,7 +225,9 @@ #endif /* linux */ VersionCondition::addPredefinedGlobalIdent("X86"); VersionCondition::addPredefinedGlobalIdent("LittleEndian"); + //VersionCondition::addPredefinedGlobalIdent("D_Bits"); VersionCondition::addPredefinedGlobalIdent("D_InlineAsm"); + VersionCondition::addPredefinedGlobalIdent("D_InlineAsm_X86"); VersionCondition::addPredefinedGlobalIdent("all"); #if _WIN32 @@ -237,6 +254,8 @@ global.params.useDeprecated = 1; else if (strcmp(p + 1, "c") == 0) global.params.link = 0; + else if (strcmp(p + 1, "cov") == 0) + global.params.cov = 1; else if (strcmp(p + 1, "fPIC") == 0) global.params.pic = 1; else if (strcmp(p + 1, "g") == 0) @@ -311,8 +330,35 @@ goto Lerror; } } +#ifdef _DH + else if (p[1] == 'H') + { global.params.doHdrGeneration = 1; + switch (p[2]) + { + case 'd': + if (!p[3]) + goto Lnoarg; + global.params.hdrdir = p + 3; + break; + + case 'f': + if (!p[3]) + goto Lnoarg; + global.params.hdrname = p + 3; + break; + + case 0: + break; + + default: + goto Lerror; + } + } +#endif else if (strcmp(p + 1, "inline") == 0) global.params.useInline = 1; + else if (strcmp(p + 1, "nofloat") == 0) + global.params.nofloat = 1; else if (strcmp(p + 1, "quiet") == 0) global.params.quiet = 1; else if (strcmp(p + 1, "release") == 0) @@ -396,6 +442,21 @@ { global.params.linkswitches->push(p + 2); } + else if (strcmp(p + 1, "run") == 0) + { global.params.run = 1; + global.params.runargs_length = ((i >= argcstart) ? argc : argcstart) - i - 1; + if (global.params.runargs_length) + { + files.push(argv[i + 1]); + global.params.runargs = &argv[i + 2]; + i += global.params.runargs_length; + global.params.runargs_length--; + } + else + { global.params.run = 0; + goto Lnoarg; + } + } else { Lerror: @@ -428,6 +489,9 @@ global.params.useSwitchError = 0; } + if (global.params.run) + global.params.quiet = 1; + if (global.params.useUnitTests) global.params.useAssert = 1; @@ -439,6 +503,11 @@ global.params.exefile = global.params.objname; global.params.objname = NULL; } + else if (global.params.run) + { + error("flags conflict with -run"); + fatal(); + } else { if (global.params.objname && files.dim > 1) @@ -447,6 +516,9 @@ fatal(); } } + if (global.params.cov) + VersionCondition::addPredefinedGlobalIdent("D_Coverage"); + //printf("%d source files\n",files.dim); @@ -567,12 +639,16 @@ } id = new Identifier(name, 0); - m = new Module((char *) files.data[i], id, global.params.doDocComments); + m = new Module((char *) files.data[i], id, global.params.doDocComments, global.params.doHdrGeneration); modules.push(m); global.params.objfiles->push(m->objfile->name->str); } +#if _WIN32 + __try + { +#endif // Read files, parse them for (i = 0; i < modules.dim; i++) { @@ -606,6 +682,25 @@ } if (global.errors) fatal(); +#ifdef _DH + if (global.params.doHdrGeneration) + { + /* Generate 'header' import files. + * Since 'header' import files must be independent of command + * line switches and what else is imported, they are generated + * before any semantic analysis. + */ + for (i = 0; i < modules.dim; i++) + { + m = (Module *)modules.data[i]; + if (global.params.verbose) + printf("import %s\n", m->toChars()); + m->genhdrfile(); + } + } + if (global.errors) + fatal(); +#endif // Do semantic analysis for (i = 0; i < modules.dim; i++) @@ -643,6 +738,26 @@ // Scan for functions to inline if (global.params.useInline) { + /* The problem with useArrayBounds and useAssert is that the + * module being linked to may not have generated them, so if + * we inline functions from those modules, the symbols for them will + * not be found at link time. + */ + if (!global.params.useArrayBounds && !global.params.useAssert) + { + // Do pass 3 semantic analysis on all imported modules, + // since otherwise functions in them cannot be inlined + for (i = 0; i < Module::amodules.dim; i++) + { + m = (Module *)Module::amodules.data[i]; + if (global.params.verbose) + printf("semantic3 %s\n", m->toChars()); + m->semantic3(); + } + if (global.errors) + fatal(); + } + for (i = 0; i < modules.dim; i++) { m = (Module *)modules.data[i]; @@ -666,18 +781,49 @@ m->deleteObjFile(); else { - //m->gensymfile(); if (global.params.doDocComments) m->gendocfile(); } } - +#if _WIN32 + } + __except (__ehfilter(GetExceptionInformation())) + { + printf("Stack overflow\n"); + fatal(); + } +#endif backend_term(); if (global.errors) fatal(); - if (global.params.link) - status = runLINK(); + if (!global.params.objfiles->dim) + { + if (global.params.link) + error("no object files to link"); + } + else + { + if (global.params.link) + status = runLINK(); + + if (global.params.run) + { + if (!status) + { + status = runProgram(); + + /* Delete .obj files and .exe file + */ + for (i = 0; i < modules.dim; i++) + { + m = (Module *)modules.data[i]; + m->deleteObjFile(); + } + deleteExeFile(); + } + } + } return status; } @@ -701,6 +847,7 @@ int instring; int slash; char c; + int j; env = getenv(envvar); if (!env) @@ -715,6 +862,7 @@ for (int i = 0; i < argc; i++) argv->data[i] = (void *)(*pargv)[i]; + j = 1; // leave argv[0] alone while (1) { wildcard = 1; @@ -731,7 +879,9 @@ case '"': wildcard = 0; default: - argv->push(env); + argv->push(env); // append + //argv->insert(j, env); // insert at position j + j++; argc++; p = env; slash = 0; @@ -789,4 +939,18 @@ *pargv = (char **)argv->data; } +#if _WIN32 +long __cdecl __ehfilter(LPEXCEPTION_POINTERS ep) +{ + //printf("%x\n", ep->ExceptionRecord->ExceptionCode); + if (ep->ExceptionRecord->ExceptionCode == STATUS_STACK_OVERFLOW) + { +#ifndef DEBUG + return EXCEPTION_EXECUTE_HANDLER; +#endif + } + return EXCEPTION_CONTINUE_SEARCH; +} + +#endif diff -uNr gdc-0.17/d/dmd/mars.h gdc-0.18/d/dmd/mars.h --- gdc-0.17/d/dmd/mars.h 2005-11-27 17:28:26.000000000 +0100 +++ gdc-0.18/d/dmd/mars.h 2006-05-14 03:05:56.000000000 +0200 @@ -1,5 +1,5 @@ -// Copyright (c) 1999-2005 by Digital Mars +// Copyright (c) 1999-2006 by Digital Mars // All Rights Reserved // written by Walter Bright // www.digitalmars.com @@ -20,6 +20,10 @@ #pragma once #endif /* __DMC__ */ +#ifdef IN_GCC +/* Changes for the GDC compiler by David Friedman */ +#endif + struct Array; // Put command line switches in here @@ -49,6 +53,8 @@ char preservePaths; // !=0 means don't strip path from source file char warnings; // enable warnings char pic; // generate position-independent-code for shared libs + char cov; // generate code coverage data + char nofloat; // code should not pull in floating point support char *argv0; // program name Array *imppath; // array of char*'s of where to look for import modules @@ -60,6 +66,10 @@ char *docname; // write documentation file to docname Array *ddocfiles; // macro include files for Ddoc + char doHdrGeneration; // process embedded documentation comments + char *hdrdir; // write 'header' file to docdir directory + char *hdrname; // write 'header' file to docname + unsigned debuglevel; // debug level Array *debugids; // debug identifiers @@ -78,6 +88,10 @@ char debugx; char debugy; + char run; // run resulting executable + size_t runargs_length; + char** runargs; // arguments for executable + // Linker stuff Array *objfiles; Array *linkswitches; @@ -94,6 +108,7 @@ char *obj_ext; char *doc_ext; // for Ddoc generated files char *ddoc_ext; // for Ddoc macro include files + char *hdr_ext; // for D 'header' import files char *copyright; char *written; Array *path; // Array of char*'s which form the import lookup path @@ -117,13 +132,13 @@ #ifdef __DMC__ typedef _Complex long double complex_t; #else -#ifndef IN_GCC -#include "complex_t.h" +# ifndef IN_GCC +# include "complex_t.h" +# endif #endif + #ifdef __APPLE__ -//#include "complex.h"//This causes problems with include the c++ and not the C "complex.h" -#define integer_t dmd_integer_t -#endif +# define integer_t dmd_integer_t #endif // Be careful not to care about sign with integer_t @@ -133,7 +148,6 @@ typedef long long sinteger_t; typedef unsigned long long uinteger_t; - typedef signed char d_int8; typedef unsigned char d_uns8; typedef short d_int16; @@ -147,7 +161,6 @@ typedef double d_float64; typedef long double d_float80; -// Note: this will be 2 bytes on Win32 systems, and 4 bytes under linux. typedef d_uns8 d_char; typedef d_uns16 d_wchar; typedef d_uns32 d_dchar; @@ -160,10 +173,8 @@ // Modify OutBuffer::writewchar to write the correct size of wchar #if _WIN32 #define writewchar writeword -#endif - +#else // This needs a configuration test... -#ifndef _WIN32 #define writewchar write4 #endif @@ -230,6 +241,15 @@ void fatal(); void err_nomem(); int runLINK(); +void deleteExeFile(); +int runProgram(); void inifile(char *argv0, char *inifile); +/*** Where to send error messages ***/ +#if IN_GCC +#define stdmsg stderr +#else +#define stdmsg stdout +#endif + #endif /* DMD_MARS_H */ diff -uNr gdc-0.17/d/dmd/module.c gdc-0.18/d/dmd/module.c --- gdc-0.17/d/dmd/module.c 2005-10-24 23:48:04.000000000 +0200 +++ gdc-0.18/d/dmd/module.c 2006-05-14 01:38:32.000000000 +0200 @@ -1,5 +1,5 @@ -// Copyright (c) 1999-2004 by Digital Mars +// Copyright (c) 1999-2005 by Digital Mars // All Rights Reserved // written by Walter Bright // www.digitalmars.com @@ -7,17 +7,19 @@ // in artistic.txt, or the GNU General Public License in gnu.txt. // See the included readme.txt for details. -/* NOTE: This file has been patched from the original DMD distribution to - work with the GDC compiler. - - Modified by David Friedman, September 2004 -*/ - #include #include #include +#ifdef _MSC_VER +#include +#endif + +#if IN_GCC #include "gdc_alloca.h" +#endif + +#include "mem.h" #include "mars.h" #include "module.h" @@ -27,6 +29,7 @@ #include "id.h" #include "import.h" #include "dsymbol.h" +#include "hdrgen.h" #define MARS 1 #include "html.h" @@ -38,6 +41,7 @@ ClassDeclaration *Module::moduleinfo; DsymbolTable *Module::modules; +Array Module::amodules; Array Module::deferred; // deferred Dsymbol's needing semantic() run on them @@ -46,7 +50,7 @@ modules = new DsymbolTable(); } -Module::Module(char *filename, Identifier *ident, int doDocComment) +Module::Module(char *filename, Identifier *ident, int doDocComment, int doHdrGen) : Package(ident) { FileName *srcfilename; @@ -59,6 +63,7 @@ this->arg = filename; md = NULL; errors = 0; + numlines = 0; members = NULL; isHtml = 0; isDocFile = 0; @@ -91,6 +96,8 @@ versionidsNot = NULL; macrotable = NULL; + cov = NULL; + covb = NULL; srcfilename = FileName::defaultExt(filename, global.mars_ext); if (!srcfilename->equalsExt(global.mars_ext)) @@ -126,6 +133,11 @@ setDocfile(); } + if (doHdrGen) + { + setHdrfile(); + } + objfile = new File(objfilename); symfile = new File(symfilename); } @@ -156,6 +168,32 @@ docfile = new File(docfilename); } +void Module::setHdrfile() +{ + FileName *hdrfilename; + char *arghdr; + + if (global.params.hdrname) + arghdr = global.params.hdrname; + else if (global.params.preservePaths) + arghdr = (char *)arg; + else + arghdr = FileName::name((char *)arg); + if (!FileName::absolute(arghdr)) + arghdr = FileName::combine(global.params.hdrdir, arghdr); + if (global.params.hdrname) + hdrfilename = new FileName(arghdr, 0); + else + hdrfilename = FileName::forceExt(arghdr, global.hdr_ext); + + if (hdrfilename->equals(srcfile->name)) + { error("Source file and 'header' file have same name '%s'", srcfile->name->str); + fatal(); + } + + hdrfile = new File(hdrfilename); +} + void Module::deleteObjFile() { if (global.params.obj) @@ -204,18 +242,47 @@ filename = (char *)buf.extractData(); } - m = new Module(filename, ident, 0); + m = new Module(filename, ident, 0, 0); m->loc = loc; - // Find the sym file - char *s; - s = FileName::searchPath(global.path, m->symfile->toChars(), 1); - if (s) - m->symfile = new File(s); - - // BUG: the sym file is actually a source file that is - // parsed. Someday make it a real symbol table - m->srcfile = m->symfile; + /* Search along global.path for .di file, then .d file. + */ + char *result = NULL; + FileName *fdi = FileName::forceExt(filename, global.hdr_ext); + FileName *fd = FileName::forceExt(filename, global.mars_ext); + char *sdi = fdi->toChars(); + char *sd = fd->toChars(); + + if (FileName::exists(sdi)) + result = sdi; + else if (FileName::exists(sd)) + result =sd; + else if (FileName::absolute(filename)) + ; + else if (!global.path) + ; + else + { + for (size_t i = 0; i < global.path->dim; i++) + { + char *p = (char *)global.path->data[i]; + char *n = FileName::combine(p, sdi); + if (FileName::exists(n)) + { result = n; + break; + } + mem.free(n); + n = FileName::combine(p, sd); + if (FileName::exists(n)) + { result = n; + break; + } + mem.free(n); + } + } + if (result) + m->srcfile = new File(result); + m->read(loc); m->parse(); @@ -269,7 +336,11 @@ (((unsigned char *)p)[0] << 24); } +#if IN_GCC void Module::parse(bool dump_source) +#else +void Module::parse() +#endif { char *srcname; unsigned char *buf; unsigned buflen; @@ -441,12 +512,13 @@ } #ifdef IN_GCC - // dump utf-8 encoded source - if(dump_source){ - // %% srcname could contain a path ... - d_gcc_dump_source(srcname, "utf-8", buf, buflen); - } -#endif /* IN_GCC */ + // dump utf-8 encoded source + if (dump_source) + { // %% srcname could contain a path ... + d_gcc_dump_source(srcname, "utf-8", buf, buflen); + } +#endif + /* If it starts with the string "Ddoc", then it's a documentation * source file. */ @@ -467,14 +539,14 @@ buflen = dbuf->offset; #ifdef IN_GCC // dump extracted source - if(dump_source) { + if (dump_source) d_gcc_dump_source(srcname, "d.utf-8", buf, buflen); - } #endif } Parser p(this, buf, buflen, docfile != NULL); members = p.parseModule(); md = p.md; + numlines = p.loc.linnum; DsymbolTable *dst; @@ -503,6 +575,10 @@ else error(loc, "is in multiple defined"); } + else + { + amodules.push(this); + } } void Module::semantic() @@ -534,7 +610,7 @@ { Dsymbol *s; s = (Dsymbol *)members->data[i]; - s->addMember(NULL, sc->scopesym); + s->addMember(NULL, sc->scopesym, 1); } // Pass 1 semantic routines: do public side of the definition @@ -544,7 +620,6 @@ s = (Dsymbol *)members->data[i]; //printf("\tModule('%s'): '%s'.semantic()\n", toChars(), s->toChars()); s->semantic(sc); - runDeferredSemantic(); } @@ -649,6 +724,7 @@ void Module::gensymfile() { OutBuffer buf; + HdrGenState hgs; int i; //printf("Module::gensymfile()\n"); @@ -661,7 +737,7 @@ Dsymbol *s; s = (Dsymbol *)members->data[i]; - s->toCBuffer(&buf); + s->toCBuffer(&buf, &hgs); } // Transfer image to file @@ -678,7 +754,7 @@ int Module::needModuleInfo() { - return needmoduleinfo; + return needmoduleinfo || global.params.cov; } Dsymbol *Module::search(Identifier *ident, int flags) diff -uNr gdc-0.17/d/dmd/module.h gdc-0.18/d/dmd/module.h --- gdc-0.17/d/dmd/module.h 2005-10-24 23:48:04.000000000 +0200 +++ gdc-0.18/d/dmd/module.h 2006-05-14 01:38:32.000000000 +0200 @@ -7,12 +7,6 @@ // in artistic.txt, or the GNU General Public License in gnu.txt. // See the included readme.txt for details. -/* NOTE: This file has been patched from the original DMD distribution to - work with the GDC compiler. - - Modified by David Friedman, September 2004 -*/ - #ifndef DMD_MODULE_H #define DMD_MODULE_H @@ -27,9 +21,14 @@ struct ClassDeclaration; struct ModuleDeclaration; struct Macro; +struct VarDeclaration; // Back end +#if IN_GCC union tree_node; typedef union tree_node elem; +#else +struct elem; +#endif struct Package : ScopeDsymbol { @@ -45,7 +44,8 @@ struct Module : Package { - static DsymbolTable *modules; // All modules + static DsymbolTable *modules; // symbol table of all modules + static Array amodules; // array of all modules static Array deferred; // deferred Dsymbol's needing semantic() run on them static void init(); @@ -56,9 +56,11 @@ ModuleDeclaration *md; // if !NULL, the contents of the ModuleDeclaration declaration File *srcfile; // input source file File *objfile; // output .obj file + File *hdrfile; // 'header' file File *symfile; // output symbol file File *docfile; // output documentation file unsigned errors; // if any errors in file + unsigned numlines; // number of lines in source file int isHtml; // if it is an HTML file int isDocFile; // if it is a documentation input file, not D source int needmoduleinfo; @@ -92,19 +94,28 @@ Macro *macrotable; // document comment macros - Module(char *arg, Identifier *ident, int doDocComment); + Module(char *arg, Identifier *ident, int doDocComment, int doHdrGen); ~Module(); static Module *load(Loc loc, Array *packages, Identifier *ident); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); char *kind(); void setDocfile(); // set docfile member void read(Loc loc); // read file +#if IN_GCC void parse(bool dump_source = false); // syntactic parse +#else + void parse(); // syntactic parse +#endif void semantic(); // semantic analysis void semantic2(); // pass 2 semantic analysis void semantic3(); // pass 3 semantic analysis void inlineScan(); // scan for functions to inline + void setHdrfile(); // set hdrfile member +#ifdef _DH + void genhdrfile(); // generate D import file +#endif void genobjfile(); void gensymfile(); void gendocfile(); @@ -116,6 +127,9 @@ // Back end + Symbol *cov; // private uint[] __coverage; + unsigned *covb; // bit array of valid code line numbers + Symbol *sctor; // module constructor Symbol *sdtor; // module destructor Symbol *stest; // module unit test @@ -131,6 +145,7 @@ static Symbol *gencritsec(); elem *toEfilename(); + elem *toEmodulename(); Symbol *toSymbol(); void genmoduleinfo(); diff -uNr gdc-0.17/d/dmd/mtype.c gdc-0.18/d/dmd/mtype.c --- gdc-0.17/d/dmd/mtype.c 2005-11-28 05:17:52.000000000 +0100 +++ gdc-0.18/d/dmd/mtype.c 2006-05-14 04:21:51.000000000 +0200 @@ -16,8 +16,12 @@ // Issues with using -include total.h (defines integer_t) and then complex.h fails... #undef integer_t +#define __USE_ISOC99 1 // so signbit() gets defined +#include + #include #include +#include #include "gdc_alloca.h" @@ -25,16 +29,21 @@ #include #endif -#include // TODO%% this undefines signbit and includes is the wrong complex.h anyway // -- not sure why this is needed, anyway // don't need to worry about all this if the 'nan negative by default' issue is resolved -#ifndef __GNUC__ +#if _MSC_VER +#include +#include +#include +#elif __DMC__ // includes the wrong complex.h in C++ #include +#else +//#define signbit 56 #endif -#ifdef __APPLE__ +#if __APPLE__ #include static double zero = 0; #elif __GNUC__ @@ -61,6 +70,7 @@ #include "mem.h" +#include "dsymbol.h" #include "mtype.h" #include "scope.h" #include "init.h" @@ -72,6 +82,7 @@ #include "enum.h" #include "import.h" #include "aggregate.h" +#include "hdrgen.h" FuncDeclaration *hasThis(Scope *sc); @@ -108,6 +119,7 @@ ClassDeclaration *Type::typeinfofunction; ClassDeclaration *Type::typeinfodelegate; +Type *Type::tvoidptr; Type *Type::basic[TMAX]; unsigned char Type::mangleChar[TMAX]; StringTable Type::stringtable; @@ -128,7 +140,7 @@ Type *Type::syntaxCopy() { print(); - fprintf(stderr, "ty = %d\n", ty); + fprintf(stdmsg, "ty = %d\n", ty); assert(0); return this; } @@ -141,6 +153,7 @@ (t && deco == t->deco) && // deco strings are unique deco != NULL) // and semantic() has been run { + //printf("deco = '%s', t->deco = '%s'\n", deco, t->deco); return 1; } //if (deco && t && t->deco) printf("deco = '%s', t->deco = '%s'\n", deco, t->deco); @@ -189,6 +202,7 @@ mangleChar[Tcomplex80] = 'c'; mangleChar[Tbit] = 'b'; + mangleChar[Tbool] = 'x'; mangleChar[Tascii] = 'a'; mangleChar[Twchar] = 'u'; mangleChar[Tdchar] = 'w'; @@ -199,7 +213,7 @@ for (i = 0; i < TMAX; i++) { if (!mangleChar[i]) - fprintf(stderr, "ty = %d\n", i); + fprintf(stdmsg, "ty = %d\n", i); assert(mangleChar[i]); } @@ -209,13 +223,15 @@ Tfloat32, Tfloat64, Tfloat80, Timaginary32, Timaginary64, Timaginary80, Tcomplex32, Tcomplex64, Tcomplex80, - Tbit, + Tbit, Tbool, Tascii, Twchar, Tdchar }; for (i = 0; i < sizeof(basetab) / sizeof(basetab[0]); i++) basic[basetab[i]] = new TypeBasic(basetab[i]); basic[Terror] = basic[Tint32]; + tvoidptr = tvoid->pointerTo(); + if (global.params.isX86_64) { PTRSIZE = 8; @@ -343,21 +359,22 @@ char *Type::toChars() { OutBuffer *buf; + HdrGenState hgs; buf = new OutBuffer(); - toCBuffer2(buf, NULL); + toCBuffer2(buf, NULL, &hgs); return buf->toChars(); } -void Type::toCBuffer(OutBuffer *buf, Identifier *ident) +void Type::toCBuffer(OutBuffer *buf, Identifier *ident, HdrGenState *hgs) { OutBuffer tbuf; - toCBuffer2(&tbuf, ident); + toCBuffer2(&tbuf, ident, hgs); buf->write(&tbuf); } -void Type::toCBuffer2(OutBuffer *buf, Identifier *ident) +void Type::toCBuffer2(OutBuffer *buf, Identifier *ident, HdrGenState *hgs) { buf->prependstring(toChars()); if (ident) @@ -490,7 +507,7 @@ return 0; // assume not } -int Type::isBaseOf(Type *t) +int Type::isBaseOf(Type *t, int *poffset) { return 0; // assume not } @@ -545,6 +562,12 @@ e = defaultInit(); e->loc = loc; } + else if (ident == Id::mangleof) + { assert(deco); + e = new StringExp(loc, deco, strlen(deco), 'c'); + Scope sc; + e = e->semantic(&sc); + } else { error(loc, "no property '%s' for type '%s'", ident->toChars(), toChars()); @@ -613,16 +636,16 @@ { char *p = loc.toChars(); if (*p) - fprintf(stderr, "%s: ", p); + fprintf(stdmsg, "%s: ", p); mem.free(p); va_list ap; va_start(ap, format); - vfprintf(stderr, format, ap); + vfprintf(stdmsg, format, ap); va_end(ap); - fprintf(stderr, "\n"); - fflush(stderr); + fprintf(stdmsg, "\n"); + fflush(stdmsg); } global.errors++; //fatal(); @@ -781,6 +804,11 @@ flags |= TFLAGSintegral | TFLAGSunsigned; break; + case Tbool: d = "bool"; + c = d; + flags |= TFLAGSintegral | TFLAGSunsigned; + break; + case Tascii: d = Token::toChars(TOKchar); c = "char"; flags |= TFLAGSintegral | TFLAGSunsigned; @@ -816,7 +844,7 @@ return dstring; } -void TypeBasic::toCBuffer2(OutBuffer *buf, Identifier *ident) +void TypeBasic::toCBuffer2(OutBuffer *buf, Identifier *ident, HdrGenState *hgs) { buf->prependstring(cstring); if (ident) @@ -861,6 +889,7 @@ break; case Tbit: size = 1; break; + case Tbool: size = 1; break; case Tascii: size = 1; break; case Twchar: size = 2; break; case Tdchar: size = 4; break; @@ -916,7 +945,8 @@ case Tint64: ivalue = 0x7FFFFFFFFFFFFFFFLL; goto Livalue; case Tuns64: ivalue = 0xFFFFFFFFFFFFFFFFULL; goto Livalue; case Tbit: ivalue = 1; goto Livalue; - case Tascii: ivalue = 0xFF; goto Livalue; + case Tbool: ivalue = 1; goto Livalue; + case Tchar: ivalue = 0xFF; goto Livalue; case Twchar: ivalue = 0xFFFFUL; goto Livalue; case Tdchar: ivalue = 0x10FFFFUL; goto Livalue; @@ -976,7 +1006,8 @@ case Tint64: ivalue = (-9223372036854775807LL-1LL); goto Livalue; case Tuns64: ivalue = 0; goto Livalue; case Tbit: ivalue = 0; goto Livalue; - case Tascii: ivalue = 0; goto Livalue; + case Tbool: ivalue = 0; goto Livalue; + case Tchar: ivalue = 0; goto Livalue; case Twchar: ivalue = 0; goto Livalue; case Tdchar: ivalue = 0; goto Livalue; @@ -1004,24 +1035,27 @@ case Tfloat32: case Tfloat64: case Tfloat80: -#ifdef IN_GCC + { +#if IN_GCC // mode doesn't matter, will be converted in RealExp anyway fvalue = real_t::getnan(real_t::LongDouble); #elif __GNUC__ - { // gcc nan's have the sign bit set by default, so turn it off + // gcc nan's have the sign bit set by default, so turn it off // Need the volatile to prevent gcc from doing incorrect // constant folding. volatile d_float80 foo; foo = NAN; - // This doesn't seem to be the case on the systems I'm using %% - if ( signbit(foo) ) - foo = -foo; + if (signbit(foo)) // signbit sometimes, not always, set + foo = -foo; // turn off sign bit fvalue = foo; - } +#elif _MSC_VER + unsigned long nan[2]= { 0xFFFFFFFF, 0x7FFFFFFF }; + fvalue = *(double*)nan; #else fvalue = NAN; #endif goto Lfvalue; + } } } else if (ident == Id::infinity) @@ -1037,10 +1071,12 @@ case Tfloat32: case Tfloat64: case Tfloat80: -#ifdef IN_GCC +#if IN_GCC fvalue = real_t::getinfinity(); #elif __GNUC__ fvalue = 1 / zero; +#elif _MSC_VER + fvalue = std::numeric_limits::infinity(); #else fvalue = INFINITY; #endif @@ -1168,11 +1204,16 @@ complex_t cvalue; #if __DMC__ + //((real_t *)&cvalue)[0] = fvalue; + //((real_t *)&cvalue)[1] = fvalue; cvalue = fvalue + fvalue * I; #else cvalue.re = fvalue; cvalue.im = fvalue; #endif + //for (int i = 0; i < 20; i++) + // printf("%02x ", ((unsigned char *)&cvalue)[i]); + //printf("\n"); e = new ComplexExp(0, cvalue, this); } return e; @@ -1357,7 +1398,7 @@ return MATCHnomatch; if (ty == Tvoid /*|| to->ty == Tvoid*/) return MATCHnomatch; - if (to->ty == Tbit) + if (to->ty == Tbit || to->ty == Tbool) return MATCHnomatch; TypeBasic *tob = (TypeBasic *)to; if (flags & TFLAGSintegral) @@ -1377,10 +1418,10 @@ if (flags & TFLAGScomplex && !(tob->flags & TFLAGScomplex)) return MATCHnomatch; - // Allow implicit conversion of real or imaginary to complex + // Disallow implicit conversion of real or imaginary to complex if (flags & (TFLAGSreal | TFLAGSimaginary) && tob->flags & TFLAGScomplex) - return MATCHconvert; + return MATCHnomatch; // Disallow implicit conversion to-from real and imaginary if ((flags & (TFLAGSreal | TFLAGSimaginary)) != @@ -1413,15 +1454,15 @@ { Expression *ec; FuncDeclaration *fd; - Array *arguments; + Expressions *arguments; char *nm; static char *name[2] = { "_adReverseChar", "_adReverseWchar" }; nm = name[n->ty == Twchar]; - fd = FuncDeclaration::genCfunc(Type::tindex, nm); + fd = FuncDeclaration::genCfunc(Type::tindex, nm, Type::tvoid->arrayOf()); ec = new VarExp(0, fd); e = e->castTo(n->arrayOf()); // convert to dynamic array - arguments = new Array(); + arguments = new Expressions(); arguments->push(e); e = new CallExp(e->loc, ec, arguments); e->type = next->arrayOf(); @@ -1430,7 +1471,7 @@ { Expression *ec; FuncDeclaration *fd; - Array *arguments; + Expressions *arguments; int size = next->size(e->loc); char *nm; static char *name[2][2] = { { "_adReverse", "_adDup" }, @@ -1438,10 +1479,11 @@ assert(size); nm = name[n->ty == Tbit][ident == Id::dup]; - fd = FuncDeclaration::genCfunc(Type::tvoid->arrayOf(), nm); + fd = FuncDeclaration::genCfunc(Type::tvoid->arrayOf(), nm, + Type::tvoid->arrayOf(), next->ty != Tbit ? Type::tint32 : NULL); ec = new VarExp(0, fd); e = e->castTo(n->arrayOf()); // convert to dynamic array - arguments = new Array(); + arguments = new Expressions(); arguments->push(e); if (next->ty != Tbit) arguments->push(new IntegerExp(0, size, Type::tint32)); @@ -1452,13 +1494,15 @@ { Expression *ec; FuncDeclaration *fd; - Array *arguments; + Expressions *arguments; fd = FuncDeclaration::genCfunc(tint32->arrayOf(), - (char*)(n->ty == Tbit ? "_adSortBit" : "_adSort")); + (char*)(n->ty == Tbit ? "_adSortBit" : "_adSort"), + Type::tvoid->arrayOf(), + n->ty == Tbit ? NULL : Type::tvoid->pointerTo()); ec = new VarExp(0, fd); e = e->castTo(n->arrayOf()); // convert to dynamic array - arguments = new Array(); + arguments = new Expressions(); arguments->push(e); if (next->ty != Tbit) arguments->push(n->ty == Tsarray @@ -1474,18 +1518,18 @@ return e; } -void TypeArray::toCBuffer2(OutBuffer *buf, Identifier *ident) +void TypeArray::toCBuffer2(OutBuffer *buf, Identifier *ident, HdrGenState *hgs) { #if 1 OutBuffer buf2; - toPrettyBracket(&buf2); + toPrettyBracket(&buf2, hgs); buf->prependstring(buf2.toChars()); if (ident) { buf->writeByte(' '); buf->writestring(ident->toChars()); } - next->toCBuffer2(buf, NULL); + next->toCBuffer2(buf, NULL, hgs); #elif 1 // The D way Type *t; @@ -1496,14 +1540,14 @@ ta = dynamic_cast(t); if (!ta) break; - ta->toPrettyBracket(&buf2); + ta->toPrettyBracket(&buf2, hgs); } buf->prependstring(buf2.toChars()); if (ident) { buf2.writestring(ident->toChars()); } - t->toCBuffer2(buf, NULL); + t->toCBuffer2(buf, NULL, hgs); #else // The C way if (buf->offset) @@ -1522,7 +1566,7 @@ buf->writeByte(']'); t = t->next; } while (t->ty == Tsarray); - t->toCBuffer2(buf, NULL); + t->toCBuffer2(buf, NULL, hgs); #endif } @@ -1649,7 +1693,7 @@ next->toTypeInfoBuffer(buf); } -void TypeSArray::toPrettyBracket(OutBuffer *buf) +void TypeSArray::toPrettyBracket(OutBuffer *buf, HdrGenState *hgs) { buf->printf("[%s]", dim->toChars()); } @@ -1782,7 +1826,7 @@ next->toTypeInfoBuffer(buf); } -void TypeDArray::toPrettyBracket(OutBuffer *buf) +void TypeDArray::toPrettyBracket(OutBuffer *buf, HdrGenState *hgs) { buf->writestring("[]"); } @@ -1832,7 +1876,7 @@ } if (to->ty == Tarray) { - if (to->next->isBaseOf(next) || to->next->ty == Tvoid) + if (to->next->isBaseOf(next, NULL) || to->next->ty == Tvoid) return MATCHconvert; } return Type::implicitConvTo(to); @@ -1931,6 +1975,7 @@ break; #endif case Tbit: + case Tbool: case Tfunction: case Tvoid: case Tnone: @@ -1960,11 +2005,11 @@ { Expression *ec; FuncDeclaration *fd; - Array *arguments; + Expressions *arguments; - fd = FuncDeclaration::genCfunc(Type::tsize_t, "_aaLen"); + fd = FuncDeclaration::genCfunc(Type::tsize_t, "_aaLen", Type::tvoid->arrayOf()); ec = new VarExp(0, fd); - arguments = new Array(); + arguments = new Expressions(); arguments->push(e); e = new CallExp(e->loc, ec, arguments); e->type = fd->type->next; @@ -1973,7 +2018,7 @@ { Expression *ec; FuncDeclaration *fd; - Array *arguments; + Expressions *arguments; char aakeys[7+3*sizeof(int)+1]; int size = key->size(e->loc); @@ -1987,12 +2032,13 @@ else #endif strcpy(aakeys, "_aaKeys"); - fd = FuncDeclaration::genCfunc(Type::tvoid->arrayOf(), aakeys); + fd = FuncDeclaration::genCfunc(Type::tvoid->arrayOf(), aakeys, + Type::tvoid->arrayOf(), Type::tsize_t); ec = new VarExp(0, fd); - arguments = new Array(); + arguments = new Expressions(); arguments->push(e); if (size) - arguments->push(new IntegerExp(0, size, Type::tint32)); + arguments->push(new IntegerExp(0, size, Type::tsize_t)); e = new CallExp(e->loc, ec, arguments); e->type = index->arrayOf(); } @@ -2000,14 +2046,17 @@ { Expression *ec; FuncDeclaration *fd; - Array *arguments; + Expressions *arguments; - fd = FuncDeclaration::genCfunc(Type::tvoid->arrayOf(), "_aaValues"); + fd = FuncDeclaration::genCfunc(Type::tvoid->arrayOf(), "_aaValues", + Type::tvoid->arrayOf(), Type::tsize_t, Type::tsize_t); ec = new VarExp(0, fd); - arguments = new Array(); + arguments = new Expressions(); arguments->push(e); - arguments->push(new IntegerExp(0, key->size(e->loc), Type::tint32)); - arguments->push(new IntegerExp(0, next->size(e->loc), Type::tint32)); + size_t keysize = key->size(e->loc); + keysize = (keysize + 3) & ~3; // BUG: 64 bit pointers? + arguments->push(new IntegerExp(0, keysize, Type::tsize_t)); + arguments->push(new IntegerExp(0, next->size(e->loc), Type::tsize_t)); e = new CallExp(e->loc, ec, arguments); e->type = next->arrayOf(); } @@ -2015,11 +2064,11 @@ { Expression *ec; FuncDeclaration *fd; - Array *arguments; + Expressions *arguments; fd = FuncDeclaration::genCfunc(Type::tvoid->arrayOf(), "_aaRehash"); ec = new VarExp(0, fd); - arguments = new Array(); + arguments = new Expressions(); arguments->push(e->addressOf()); arguments->push(key->getInternalTypeInfo(sc)); e = new CallExp(e->loc, ec, arguments); @@ -2039,12 +2088,12 @@ next->toDecoBuffer(buf); } -void TypeAArray::toPrettyBracket(OutBuffer *buf) +void TypeAArray::toPrettyBracket(OutBuffer *buf, HdrGenState *hgs) { buf->writeByte('['); { OutBuffer ibuf; - index->toCBuffer2(&ibuf, NULL); + index->toCBuffer2(&ibuf, NULL, hgs); buf->write(&ibuf); } buf->writeByte(']'); @@ -2099,7 +2148,7 @@ return PTRSIZE; } -void TypePointer::toCBuffer2(OutBuffer *buf, Identifier *ident) +void TypePointer::toCBuffer2(OutBuffer *buf, Identifier *ident, HdrGenState *hgs) { //printf("TypePointer::toCBuffer2() next = %d\n", next->ty); buf->prependstring("*"); @@ -2108,7 +2157,7 @@ buf->writeByte(' '); buf->writestring(ident->toChars()); } - next->toCBuffer2(buf, NULL); + next->toCBuffer2(buf, NULL, hgs); } int TypePointer::implicitConvTo(Type *to) @@ -2188,14 +2237,14 @@ return PTRSIZE; } -void TypeReference::toCBuffer2(OutBuffer *buf, Identifier *ident) +void TypeReference::toCBuffer2(OutBuffer *buf, Identifier *ident, HdrGenState *hgs) { buf->prependstring("&"); if (ident) { buf->writestring(ident->toChars()); } - next->toCBuffer2(buf, NULL); + next->toCBuffer2(buf, NULL, hgs); } Expression *TypeReference::dotExp(Scope *sc, Expression *e, Identifier *ident) @@ -2230,6 +2279,8 @@ TypeFunction::TypeFunction(Array *arguments, Type *treturn, int varargs, enum LINK linkage) : Type(Tfunction, treturn) { +if (!treturn) *(char*)0=0; + assert(treturn); this->arguments = arguments; this->varargs = varargs; this->linkage = linkage; @@ -2237,6 +2288,7 @@ Type *TypeFunction::syntaxCopy() { + assert(next); Type *treturn = next->syntaxCopy(); Array *args = Argument::arraySyntaxCopy(arguments); Type *t = new TypeFunction(args, treturn, varargs, linkage); @@ -2253,6 +2305,12 @@ int Type::covariant(Type *t) { +#if 0 + printf("Type::covariant(t = %s) %s\n", t->toChars(), toChars()); + printf("deco = %p, %p\n", deco, t->deco); + printf("ty = %d\n", next->ty); +#endif + int inoutmismatch = 0; if (equals(t)) @@ -2304,12 +2362,15 @@ } Lcovariant: + //printf("\tcovaraint: 1\n"); return 1; Ldistinct: + //printf("\tcovaraint: 0\n"); return 0; Lnotcovariant: + //printf("\tcovaraint: 2\n"); return 2; } @@ -2354,75 +2415,43 @@ next->toDecoBuffer(buf); } -void TypeFunction::toCBuffer2(OutBuffer *buf, Identifier *ident) +void TypeFunction::toCBuffer2(OutBuffer *buf, Identifier *ident, HdrGenState *hgs) { - char *p; + char *p = NULL; - switch (linkage) + if (hgs->ddoc != 1) { - case LINKd: p = NULL; break; - case LINKc: p = "C "; break; - case LINKwindows: p = "Windows "; break; - case LINKpascal: p = "Pascal "; break; - case LINKcpp: p = "C++ "; break; - default: - assert(0); + switch (linkage) + { + case LINKd: p = NULL; break; + case LINKc: p = "C "; break; + case LINKwindows: p = "Windows "; break; + case LINKpascal: p = "Pascal "; break; + case LINKcpp: p = "C++ "; break; + default: + assert(0); + } } if (buf->offset) { - if (p) + if (!hgs->hdrgen && p) buf->prependstring(p); buf->bracket('(', ')'); assert(!ident); } else { - if (p) + if (!hgs->hdrgen && p) buf->writestring(p); if (ident) { buf->writeByte(' '); - buf->writestring(ident->toChars()); + buf->writestring(ident->toHChars2()); } } - argsToCBuffer(buf); - next->toCBuffer2(buf, NULL); -} - -void TypeFunction::argsToCBuffer(OutBuffer *buf) -{ - buf->writeByte('('); - if (arguments) - { int i; - OutBuffer argbuf; - - for (i = 0; i < arguments->dim; i++) - { Argument *arg; - - if (i) - buf->writestring(", "); - arg = (Argument *)arguments->data[i]; - if (arg->inout == Out) - buf->writestring("out "); - else if (arg->inout == InOut) - buf->writestring("inout "); - argbuf.reset(); - arg->type->toCBuffer2(&argbuf, arg->ident); - if (arg->defaultArg) - { - argbuf.writestring(" = "); - arg->defaultArg->toCBuffer(&argbuf); - } - buf->write(&argbuf); - } - if (varargs) - { - if (i && varargs == 1) - buf->writeByte(','); - buf->writestring("..."); - } - } - buf->writeByte(')'); + Argument::argsToCBuffer(buf, hgs, arguments, varargs); + if (!ident || ident->toHChars2() == ident->toChars()) + next->toCBuffer2(buf, NULL, hgs); } Type *TypeFunction::semantic(Loc loc, Scope *sc) @@ -2614,13 +2643,13 @@ return PTRSIZE * 2; } -void TypeDelegate::toCBuffer2(OutBuffer *buf, Identifier *ident) +void TypeDelegate::toCBuffer2(OutBuffer *buf, Identifier *ident, HdrGenState *hgs) { #if 1 OutBuffer args; TypeFunction *tf = (TypeFunction *)next; - tf->argsToCBuffer(&args); + Argument::argsToCBuffer(&args, hgs, tf->arguments, tf->varargs); buf->prependstring(args.toChars()); buf->prependstring(" delegate"); if (ident) @@ -2628,9 +2657,9 @@ buf->writeByte(' '); buf->writestring(ident->toChars()); } - next->next->toCBuffer2(buf, NULL); + next->next->toCBuffer2(buf, NULL, hgs); #else - next->toCBuffer2(buf, Id::delegate); + next->toCBuffer2(buf, Id::delegate, hgs); if (ident) { buf->writestring(ident->toChars()); @@ -2692,7 +2721,7 @@ idents.push(ident); } -void TypeQualified::toCBuffer2Helper(OutBuffer *buf, Identifier *ident) +void TypeQualified::toCBuffer2Helper(OutBuffer *buf, Identifier *ident, HdrGenState *hgs) { int i; @@ -2704,7 +2733,7 @@ if (id->dyncast() != DYNCAST_IDENTIFIER) { TemplateInstance *ti = (TemplateInstance *)id; - ti->toCBuffer(buf); + ti->toCBuffer(buf, hgs); } else buf->writestring(id->toChars()); @@ -2736,8 +2765,11 @@ Type *t; Expression *e; - //printf("TypeQualified::resolveHelper(sc = %p, idents = '%s')\n", sc, toChars()); - //printf("\tscopesym = '%s'\n", scopesym->toChars()); +#if 0 + printf("TypeQualified::resolveHelper(sc = %p, idents = '%s')\n", sc, toChars()); + if (scopesym) + printf("\tscopesym = '%s'\n", scopesym->toChars()); +#endif *pe = NULL; *pt = NULL; *ps = NULL; @@ -2775,8 +2807,8 @@ } else sm = s->search(id, 0); -//printf("s = '%s', kind = '%s'\n", s->toChars(), s->kind()); -//printf("getType = '%s'\n", s->getType()->toChars()); + //printf("\t3: s = '%s' %p, kind = '%s'\n",s->toChars(), s, s->kind()); + //printf("getType = '%s'\n", s->getType()->toChars()); if (!sm) { #if 0 @@ -2786,12 +2818,23 @@ return; } #endif + v = s->isVarDeclaration(); + if (v && id == Id::length) + { + if (v->isConst() && v->getExpInitializer()) + e = v->getExpInitializer()->exp; + else + e = new VarExp(loc, v); + t = e->type; + if (!t) + goto Lerror; + goto L3; + } t = s->getType(); if (!t && s->isDeclaration()) t = s->isDeclaration()->type; if (t) { -//<<>> sm = t->toDsymbol(sc); if (sm) { sm = sm->search(id, 0); @@ -2800,14 +2843,17 @@ } e = t->getProperty(loc, id); i++; + L3: for (; i < idents.dim; i++) { id = (Identifier *)idents.data[i]; + //printf("e: '%s', id: '%s', type = %p\n", e->toChars(), id->toChars(), e->type); e = e->type->dotExp(sc, e, id); } *pe = e; } else + Lerror: error(loc, "identifier '%s' of '%s' is not defined", id->toChars(), toChars()); return; } @@ -2869,20 +2915,33 @@ *ps = s; return; } - if (t->ty == Tident && t != this) - { - Scope *scx; + if (t->ty == Tinstance && t != this && !t->deco) + { error(loc, "forward reference to '%s'", t->toChars()); + return; + } - for (scx = sc; 1; scx = scx->enclosing) + if (t != this) + { Type *tx; + for (tx = t; tx; tx = tx->next) + { if (tx->ty == Tident) + break; + } + if (tx) { - if (!scx) - { error(loc, "forward reference to '%s'", t->toChars()); - return; + Scope *scx; + + for (scx = sc; 1; scx = scx->enclosing) + { + if (!scx) + { error(loc, "forward reference to '%s'", t->toChars()); + return; + } + if (scx->scopesym == scopesym) + break; } - if (scx->scopesym == scopesym) - break; + t = t->semantic(loc, scx); + //((TypeIdentifier *)t)->resolve(loc, scx, pe, &t, ps); } - ((TypeIdentifier *)t)->resolve(loc, scx, pe, &t, ps); } *pt = t->merge(); } @@ -2920,12 +2979,12 @@ buf->printf("%c%s", mangleChar[ty], name); } -void TypeIdentifier::toCBuffer2(OutBuffer *buf, Identifier *ident) +void TypeIdentifier::toCBuffer2(OutBuffer *buf, Identifier *ident, HdrGenState *hgs) { OutBuffer tmp; tmp.writestring(this->ident->toChars()); - toCBuffer2Helper(&tmp, NULL); + toCBuffer2Helper(&tmp, NULL, hgs); buf->prependstring(tmp.toChars()); if (ident) { buf->writeByte(' '); @@ -3019,6 +3078,8 @@ resolve(loc, sc, &e, &t, &s); if (t) { + //printf("\tit's a type %s, %s\n", t->toChars(), t->deco); + if (t->ty == Ttypedef) { TypeTypedef *tt = (TypeTypedef *)t; @@ -3061,12 +3122,12 @@ } -void TypeInstance::toCBuffer2(OutBuffer *buf, Identifier *ident) +void TypeInstance::toCBuffer2(OutBuffer *buf, Identifier *ident, HdrGenState *hgs) { OutBuffer tmp; - tempinst->toCBuffer(&tmp); - toCBuffer2Helper(&tmp, NULL); + tempinst->toCBuffer(&tmp, hgs); + toCBuffer2Helper(&tmp, NULL, hgs); buf->prependstring(tmp.toChars()); if (ident) { buf->writeByte(' '); @@ -3145,14 +3206,14 @@ return t->toDsymbol(sc); } -void TypeTypeof::toCBuffer2(OutBuffer *buf, Identifier *ident) +void TypeTypeof::toCBuffer2(OutBuffer *buf, Identifier *ident, HdrGenState *hgs) { OutBuffer tmp; tmp.writestring("typeof("); - exp->toCBuffer(&tmp); + exp->toCBuffer(&tmp, hgs); tmp.writeByte(')'); - toCBuffer2Helper(&tmp, NULL); + toCBuffer2Helper(&tmp, NULL, hgs); buf->prependstring(tmp.toChars()); if (ident) { buf->writeByte(' '); @@ -3308,7 +3369,7 @@ toBasetype()->toTypeInfoBuffer(buf); } -void TypeEnum::toCBuffer2(OutBuffer *buf, Identifier *ident) +void TypeEnum::toCBuffer2(OutBuffer *buf, Identifier *ident, HdrGenState *hgs) { buf->prependstring(sym->toChars()); if (ident) @@ -3342,22 +3403,33 @@ if (ident == Id::max) { + if (!sym->symtab) + goto Lfwd; e = new IntegerExp(0, sym->maxval, this); } else if (ident == Id::min) { + if (!sym->symtab) + goto Lfwd; e = new IntegerExp(0, sym->minval, this); } else if (ident == Id::init) { + if (!sym->symtab) + goto Lfwd; e = defaultInit(); } else { - assert(sym->memtype); + if (!sym->memtype) + goto Lfwd; e = sym->memtype->getProperty(loc, ident); } return e; + +Lfwd: + error(loc, "forward reference of %s.%s", toChars(), ident->toChars()); + return new IntegerExp(0, 0, this); } int TypeEnum::isintegral() @@ -3377,7 +3449,8 @@ int TypeEnum::isscalar() { - return sym->memtype->isscalar(); + return 1; + //return sym->memtype->isscalar(); } int TypeEnum::implicitConvTo(Type *to) @@ -3465,7 +3538,7 @@ sym->basetype->toTypeInfoBuffer(buf); } -void TypeTypedef::toCBuffer2(OutBuffer *buf, Identifier *ident) +void TypeTypedef::toCBuffer2(OutBuffer *buf, Identifier *ident, HdrGenState *hgs) { //printf("TypeTypedef::toCBuffer2() '%s'\n", sym->toChars()); buf->prependstring(sym->toChars()); @@ -3514,6 +3587,21 @@ return sym->basetype->isfloating(); } +int TypeTypedef::isreal() +{ + return sym->basetype->isreal(); +} + +int TypeTypedef::isimaginary() +{ + return sym->basetype->isimaginary(); +} + +int TypeTypedef::iscomplex() +{ + return sym->basetype->iscomplex(); +} + int TypeTypedef::isunsigned() { return sym->basetype->isunsigned(); @@ -3644,14 +3732,12 @@ } -void TypeStruct::toCBuffer2(OutBuffer *buf, Identifier *ident) +void TypeStruct::toCBuffer2(OutBuffer *buf, Identifier *ident, HdrGenState *hgs) { buf->prependbyte(' '); buf->prependstring(sym->toChars()); if (ident) - { buf->writeByte(' '); buf->writestring(ident->toChars()); - } } Expression *TypeStruct::dotExp(Scope *sc, Expression *e, Identifier *ident) @@ -3805,6 +3891,12 @@ return sym->zeroInit; } +int TypeStruct::checkBoolean() +{ + return FALSE; +} + + /***************************** TypeClass *****************************/ @@ -3853,7 +3945,7 @@ buf->printf("%c%s", mangleChar[ty], name); } -void TypeClass::toCBuffer2(OutBuffer *buf, Identifier *ident) +void TypeClass::toCBuffer2(OutBuffer *buf, Identifier *ident, HdrGenState *hgs) { buf->prependstring(sym->toChars()); if (ident) @@ -4055,13 +4147,13 @@ return sym->isauto; } -int TypeClass::isBaseOf(Type *t) +int TypeClass::isBaseOf(Type *t, int *poffset) { if (t->ty == Tclass) { ClassDeclaration *cd; cd = ((TypeClass *)t)->sym; - if (sym->isBaseOf(cd, NULL)) + if (sym->isBaseOf(cd, poffset)) return 1; } return 0; @@ -4124,7 +4216,7 @@ Argument *Argument::syntaxCopy() { Argument *a = new Argument(inout, - type->syntaxCopy(), + type ? type->syntaxCopy() : NULL, ident, defaultArg ? defaultArg->syntaxCopy() : NULL); return a; @@ -4156,6 +4248,7 @@ if (args) { int i; OutBuffer argbuf; + HdrGenState hgs; for (i = 0; i < args->dim; i++) { Argument *arg; @@ -4164,7 +4257,7 @@ buf->writeByte(','); arg = (Argument *)args->data[i]; argbuf.reset(); - arg->type->toCBuffer2(&argbuf, NULL); + arg->type->toCBuffer2(&argbuf, NULL, &hgs); buf->write(&argbuf); } if (varargs) @@ -4179,3 +4272,40 @@ return buf->toChars(); } +void Argument::argsToCBuffer(OutBuffer *buf, HdrGenState *hgs, Array *arguments, int varargs) +{ + buf->writeByte('('); + if (arguments) + { int i; + OutBuffer argbuf; + + for (i = 0; i < arguments->dim; i++) + { Argument *arg; + + if (i) + buf->writestring(", "); + arg = (Argument *)arguments->data[i]; + if (arg->inout == Out) + buf->writestring("out "); + else if (arg->inout == InOut) + buf->writestring("inout "); + argbuf.reset(); + arg->type->toCBuffer2(&argbuf, arg->ident, hgs); + if (arg->defaultArg) + { + argbuf.writestring(" = "); + arg->defaultArg->toCBuffer(&argbuf, hgs); + } + buf->write(&argbuf); + } + if (varargs) + { + if (i && varargs == 1) + buf->writeByte(','); + buf->writestring("..."); + } + } + buf->writeByte(')'); +} + + diff -uNr gdc-0.17/d/dmd/mtype.h gdc-0.18/d/dmd/mtype.h --- gdc-0.17/d/dmd/mtype.h 2005-11-28 05:17:52.000000000 +0100 +++ gdc-0.18/d/dmd/mtype.h 2006-05-13 21:05:42.000000000 +0200 @@ -1,5 +1,5 @@ -// Copyright (c) 1999-2005 by Digital Mars +// Copyright (c) 1999-2006 by Digital Mars // All Rights Reserved // written by Walter Bright // www.digitalmars.com @@ -23,6 +23,7 @@ #include "root.h" #include "stringtable.h" +#include "arraytypes.h" #include "expression.h" struct Scope; @@ -39,10 +40,15 @@ enum LINK; struct TypeBasic; +struct HdrGenState; // Back end +#if IN_GCC union tree_node; typedef union tree_node TYPE; typedef TYPE type; +#else +typedef struct TYPE type; +#endif struct Symbol; enum TY @@ -83,6 +89,7 @@ Tcomplex80, Tbit, + Tbool, Tchar, Twchar, Tdchar, @@ -140,15 +147,17 @@ #define tcomplex80 basic[Tcomplex80] #define tbit basic[Tbit] + #define tbool basic[Tbool] #define tchar basic[Tchar] #define twchar basic[Twchar] #define tdchar basic[Tdchar] // Some special types #define tshiftcnt tint32 // right side of shift expression - #define tboolean tint32 // result of boolean expression +// #define tboolean tint32 // result of boolean expression + #define tboolean tbool // result of boolean expression #define tindex tint32 // array/ptr index - #define tvoidptr tint32 // size for void* + static Type *tvoidptr; // void* #define terror basic[Terror] // for error recovery #define tsize_t basic[Tsize_t] // matches size_t alias @@ -193,8 +202,8 @@ virtual void toDecoBuffer(OutBuffer *buf); virtual void toTypeInfoBuffer(OutBuffer *buf); Type *merge(); - void toCBuffer(OutBuffer *buf, Identifier *ident); - virtual void toCBuffer2(OutBuffer *buf, Identifier *ident); + void toCBuffer(OutBuffer *buf, Identifier *ident, HdrGenState *hgs); + virtual void toCBuffer2(OutBuffer *buf, Identifier *ident, HdrGenState *hgs); virtual int isbit(); virtual int isintegral(); virtual int isfloating(); // real, imaginary, or complex @@ -212,7 +221,7 @@ Type *arrayOf(); virtual Dsymbol *toDsymbol(Scope *sc); virtual Type *toBasetype(); - virtual int isBaseOf(Type *t); + virtual int isBaseOf(Type *t, int *poffset); virtual int implicitConvTo(Type *to); virtual ClassDeclaration *isClassHandle(); virtual Expression *getProperty(Loc loc, Identifier *ident); @@ -222,7 +231,7 @@ virtual int isZeroInit(); // if initializer is 0 virtual dt_t **toDt(dt_t **pdt); Identifier *getTypeInfoIdent(int internal); - virtual MATCH deduceType(Type *tparam, Array *parameters, Array *atypes); + virtual MATCH deduceType(Scope *sc, Type *tparam, TemplateParameters *parameters, Array *atypes); virtual void resolve(Loc loc, Scope *sc, Expression **pe, Type **pt, Dsymbol **ps); Expression *getInternalTypeInfo(Scope *sc); Expression *getTypeInfo(Scope *sc); @@ -254,7 +263,7 @@ Expression *getProperty(Loc loc, Identifier *ident); Expression *dotExp(Scope *sc, Expression *e, Identifier *ident); char *toChars(); - void toCBuffer2(OutBuffer *buf, Identifier *ident); + void toCBuffer2(OutBuffer *buf, Identifier *ident, HdrGenState *hgs); int isintegral(); int isbit(); int isfloating(); @@ -275,8 +284,8 @@ struct TypeArray : Type { TypeArray(TY ty, Type *next); - virtual void toPrettyBracket(OutBuffer *buf) = 0; - void toCBuffer2(OutBuffer *buf, Identifier *ident); + virtual void toPrettyBracket(OutBuffer *buf, HdrGenState *hgs) = 0; + void toCBuffer2(OutBuffer *buf, Identifier *ident, HdrGenState *hgs); Expression *dotExp(Scope *sc, Expression *e, Identifier *ident); }; @@ -292,14 +301,14 @@ Type *semantic(Loc loc, Scope *sc); void toDecoBuffer(OutBuffer *buf); void toTypeInfoBuffer(OutBuffer *buf); - void toPrettyBracket(OutBuffer *buf); + void toPrettyBracket(OutBuffer *buf, HdrGenState *hgs); Expression *dotExp(Scope *sc, Expression *e, Identifier *ident); int isString(); unsigned memalign(unsigned salign); int implicitConvTo(Type *to); Expression *defaultInit(); dt_t **toDt(dt_t **pdt); - MATCH deduceType(Type *tparam, Array *parameters, Array *atypes); + MATCH deduceType(Scope *sc, Type *tparam, TemplateParameters *parameters, Array *atypes); TypeInfoDeclaration *getTypeInfoDeclaration(); type *toCtype(); @@ -316,7 +325,7 @@ Type *semantic(Loc loc, Scope *sc); void toDecoBuffer(OutBuffer *buf); void toTypeInfoBuffer(OutBuffer *buf); - void toPrettyBracket(OutBuffer *buf); + void toPrettyBracket(OutBuffer *buf, HdrGenState *hgs); Expression *dotExp(Scope *sc, Expression *e, Identifier *ident); int isString(); int checkBoolean(); @@ -338,10 +347,10 @@ d_uns64 size(Loc loc); Type *semantic(Loc loc, Scope *sc); void toDecoBuffer(OutBuffer *buf); - void toPrettyBracket(OutBuffer *buf); + void toPrettyBracket(OutBuffer *buf, HdrGenState *hgs); Expression *dotExp(Scope *sc, Expression *e, Identifier *ident); Expression *defaultInit(); - MATCH deduceType(Type *tparam, Array *parameters, Array *atypes); + MATCH deduceType(Scope *sc, Type *tparam, TemplateParameters *parameters, Array *atypes); int checkBoolean(); TypeInfoDeclaration *getTypeInfoDeclaration(); @@ -357,7 +366,7 @@ Type *syntaxCopy(); Type *semantic(Loc loc, Scope *sc); d_uns64 size(Loc loc); - void toCBuffer2(OutBuffer *buf, Identifier *ident); + void toCBuffer2(OutBuffer *buf, Identifier *ident, HdrGenState *hgs); int implicitConvTo(Type *to); int isscalar(); Expression *defaultInit(); @@ -372,7 +381,7 @@ TypeReference(Type *t); Type *syntaxCopy(); d_uns64 size(Loc loc); - void toCBuffer2(OutBuffer *buf, Identifier *ident); + void toCBuffer2(OutBuffer *buf, Identifier *ident, HdrGenState *hgs); Expression *dotExp(Scope *sc, Expression *e, Identifier *ident); Expression *defaultInit(); int isZeroInit(); @@ -395,9 +404,8 @@ Type *syntaxCopy(); Type *semantic(Loc loc, Scope *sc); void toDecoBuffer(OutBuffer *buf); - void toCBuffer2(OutBuffer *buf, Identifier *ident); - void argsToCBuffer(OutBuffer *buf); - MATCH deduceType(Type *tparam, Array *parameters, Array *atypes); + void toCBuffer2(OutBuffer *buf, Identifier *ident, HdrGenState *hgs); + MATCH deduceType(Scope *sc, Type *tparam, TemplateParameters *parameters, Array *atypes); TypeInfoDeclaration *getTypeInfoDeclaration(); int callMatch(Array *toargs); @@ -413,7 +421,7 @@ Type *syntaxCopy(); Type *semantic(Loc loc, Scope *sc); d_uns64 size(Loc loc); - void toCBuffer2(OutBuffer *buf, Identifier *ident); + void toCBuffer2(OutBuffer *buf, Identifier *ident, HdrGenState *hgs); Expression *defaultInit(); int isZeroInit(); int checkBoolean(); @@ -430,7 +438,7 @@ TypeQualified(TY ty, Loc loc); void syntaxCopyHelper(TypeQualified *t); void addIdent(Identifier *ident); - void toCBuffer2Helper(OutBuffer *buf, Identifier *ident); + void toCBuffer2Helper(OutBuffer *buf, Identifier *ident, HdrGenState *hgs); d_uns64 size(Loc loc); void resolveHelper(Loc loc, Scope *sc, Dsymbol *s, Dsymbol *scopesym, Expression **pe, Type **pt, Dsymbol **ps); @@ -444,11 +452,11 @@ Type *syntaxCopy(); //char *toChars(); void toDecoBuffer(OutBuffer *buf); - void toCBuffer2(OutBuffer *buf, Identifier *ident); + void toCBuffer2(OutBuffer *buf, Identifier *ident, HdrGenState *hgs); void resolve(Loc loc, Scope *sc, Expression **pe, Type **pt, Dsymbol **ps); Dsymbol *toDsymbol(Scope *sc); Type *semantic(Loc loc, Scope *sc); - MATCH deduceType(Type *tparam, Array *parameters, Array *atypes); + MATCH deduceType(Scope *sc, Type *tparam, TemplateParameters *parameters, Array *atypes); }; /* Similar to TypeIdentifier, but with a TemplateInstance as the root @@ -461,10 +469,10 @@ Type *syntaxCopy(); //char *toChars(); //void toDecoBuffer(OutBuffer *buf); - void toCBuffer2(OutBuffer *buf, Identifier *ident); + void toCBuffer2(OutBuffer *buf, Identifier *ident, HdrGenState *hgs); void resolve(Loc loc, Scope *sc, Expression **pe, Type **pt, Dsymbol **ps); Type *semantic(Loc loc, Scope *sc); - MATCH deduceType(Type *tparam, Array *parameters, Array *atypes); + MATCH deduceType(Scope *sc, Type *tparam, TemplateParameters *parameters, Array *atypes); }; struct TypeTypeof : TypeQualified @@ -474,7 +482,7 @@ TypeTypeof(Loc loc, Expression *exp); Type *syntaxCopy(); Dsymbol *toDsymbol(Scope *sc); - void toCBuffer2(OutBuffer *buf, Identifier *ident); + void toCBuffer2(OutBuffer *buf, Identifier *ident, HdrGenState *hgs); Type *semantic(Loc loc, Scope *sc); d_uns64 size(Loc loc); }; @@ -492,13 +500,14 @@ Dsymbol *toDsymbol(Scope *sc); void toDecoBuffer(OutBuffer *buf); void toTypeInfoBuffer(OutBuffer *buf); - void toCBuffer2(OutBuffer *buf, Identifier *ident); + void toCBuffer2(OutBuffer *buf, Identifier *ident, HdrGenState *hgs); Expression *dotExp(Scope *sc, Expression *e, Identifier *ident); unsigned memalign(unsigned salign); Expression *defaultInit(); int isZeroInit(); + int checkBoolean(); dt_t **toDt(dt_t **pdt); - MATCH deduceType(Type *tparam, Array *parameters, Array *atypes); + MATCH deduceType(Scope *sc, Type *tparam, TemplateParameters *parameters, Array *atypes); TypeInfoDeclaration *getTypeInfoDeclaration(); type *toCtype(); @@ -516,7 +525,7 @@ Dsymbol *toDsymbol(Scope *sc); void toDecoBuffer(OutBuffer *buf); void toTypeInfoBuffer(OutBuffer *buf); - void toCBuffer2(OutBuffer *buf, Identifier *ident); + void toCBuffer2(OutBuffer *buf, Identifier *ident, HdrGenState *hgs); Expression *dotExp(Scope *sc, Expression *e, Identifier *ident); Expression *getProperty(Loc loc, Identifier *ident); int isintegral(); @@ -527,7 +536,7 @@ Type *toBasetype(); Expression *defaultInit(); int isZeroInit(); - MATCH deduceType(Type *tparam, Array *parameters, Array *atypes); + MATCH deduceType(Scope *sc, Type *tparam, TemplateParameters *parameters, Array *atypes); TypeInfoDeclaration *getTypeInfoDeclaration(); type *toCtype(); @@ -546,11 +555,14 @@ Dsymbol *toDsymbol(Scope *sc); void toDecoBuffer(OutBuffer *buf); void toTypeInfoBuffer(OutBuffer *buf); - void toCBuffer2(OutBuffer *buf, Identifier *ident); + void toCBuffer2(OutBuffer *buf, Identifier *ident, HdrGenState *hgs); Expression *dotExp(Scope *sc, Expression *e, Identifier *ident); int isbit(); int isintegral(); int isfloating(); + int isreal(); + int isimaginary(); + int iscomplex(); int isscalar(); int isunsigned(); int checkBoolean(); @@ -559,7 +571,7 @@ Expression *defaultInit(); int isZeroInit(); dt_t **toDt(dt_t **pdt); - MATCH deduceType(Type *tparam, Array *parameters, Array *atypes); + MATCH deduceType(Scope *sc, Type *tparam, TemplateParameters *parameters, Array *atypes); TypeInfoDeclaration *getTypeInfoDeclaration(); type *toCtype(); @@ -577,14 +589,14 @@ Type *semantic(Loc loc, Scope *sc); Dsymbol *toDsymbol(Scope *sc); void toDecoBuffer(OutBuffer *buf); - void toCBuffer2(OutBuffer *buf, Identifier *ident); + void toCBuffer2(OutBuffer *buf, Identifier *ident, HdrGenState *hgs); Expression *dotExp(Scope *sc, Expression *e, Identifier *ident); ClassDeclaration *isClassHandle(); - int isBaseOf(Type *t); + int isBaseOf(Type *t, int *poffset); int implicitConvTo(Type *to); Expression *defaultInit(); int isZeroInit(); - MATCH deduceType(Type *tparam, Array *parameters, Array *atypes); + MATCH deduceType(Scope *sc, Type *tparam, TemplateParameters *parameters, Array *atypes); int isauto(); int checkBoolean(); TypeInfoDeclaration *getTypeInfoDeclaration(); @@ -594,7 +606,7 @@ Symbol *toSymbol(); }; -enum InOut { In, Out, InOut }; +enum InOut { None, In, Out, InOut }; struct Argument : Object { @@ -607,6 +619,7 @@ Argument *syntaxCopy(); static Array *arraySyntaxCopy(Array *args); static char *argsTypesToChars(Array *args, int varargs); + static void argsToCBuffer(OutBuffer *buf, HdrGenState *hgs, Array *arguments, int varargs); }; extern int PTRSIZE; diff -uNr gdc-0.17/d/dmd/opover.c gdc-0.18/d/dmd/opover.c --- gdc-0.17/d/dmd/opover.c 2005-05-29 23:09:19.000000000 +0200 +++ gdc-0.18/d/dmd/opover.c 2006-05-13 21:05:42.000000000 +0200 @@ -1,4 +1,4 @@ -// Copyright (c) 1999-2004 by Digital Mars +// Copyright (c) 1999-2006 by Digital Mars // All Rights Reserved // written by Walter Bright // www.digitalmars.com @@ -43,6 +43,7 @@ #include "aggregate.h" static Expression *build_overload(Loc loc, Scope *sc, Expression *ethis, Expression *earg, Identifier *id); +static void inferApplyArgTypesX(FuncDeclaration *fstart, Array *arguments); /******************************** Expression **************************/ @@ -212,8 +213,8 @@ Identifier *id_r = opId_r(); Match m; - Array args1; - Array args2; + Expressions args1; + Expressions args2; int argsset = 0; AggregateDeclaration *ad1; @@ -425,3 +426,178 @@ } return NULL; } + + +/***************************************** + * Given array of arguments and an aggregate type, + * if any of the argument types are missing, attempt to infer + * them from the aggregate type. + */ + +void inferApplyArgTypes(Array *arguments, Type *taggr) +{ + if (!arguments || !arguments->dim) + return; + + /* Return if no arguments need types. + */ + for (size_t u = 0; 1; u++) + { if (u == arguments->dim) + return; + Argument *arg = (Argument *)arguments->data[u]; + if (!arg->type) + break; + } + + AggregateDeclaration *ad; + FuncDeclaration *fd; + + Argument *arg = (Argument *)arguments->data[0]; + Type *tab = taggr->toBasetype(); + switch (tab->ty) + { + case Tarray: + case Tsarray: + if (arguments->dim == 2) + { + if (!arg->type) + arg->type = Type::tsize_t; // key type + arg = (Argument *)arguments->data[1]; + } + if (!arg->type) + arg->type = tab->next; // value type + break; + + case Taarray: + { TypeAArray *taa = (TypeAArray *)tab; + + if (arguments->dim == 2) + { + if (!arg->type) + arg->type = taa->index; // key type + arg = (Argument *)arguments->data[1]; + } + if (!arg->type) + arg->type = taa->next; // value type + break; + } + + case Tclass: + ad = ((TypeClass *)tab)->sym; + goto Laggr; + + case Tstruct: + ad = ((TypeStruct *)tab)->sym; + goto Laggr; + + Laggr: +#if 0 + if (arguments->dim == 1) + { + if (!arg->type) + { + /* Look for an opNext() overload + */ + fd = search_function(ad, Id::next); + if (!fd) + goto Lapply; + arg->type = fd->type->next; + } + break; + } +#endif + Lapply: + /* Look for an + * int opApply(int delegate(inout Type [, ...]) dg); + * overload + */ + fd = search_function(ad, Id::apply); + if (!fd) + break; + inferApplyArgTypesX(fd, arguments); + break; + + default: + break; // ignore error, caught later + } +} + +/******************************** + * Recursive helper function, + * analogous to func.overloadResolveX(). + */ + +static void inferApplyArgTypesX(FuncDeclaration *fstart, Array *arguments) +{ + Declaration *d; + Declaration *next; + + for (d = fstart; d; d = next) + { + FuncDeclaration *f; + FuncAliasDeclaration *fa; + AliasDeclaration *a; + + fa = d->isFuncAliasDeclaration(); + if (fa) + { + inferApplyArgTypesX(fa->funcalias, arguments); + next = fa->overnext; + } + else if ((f = d->isFuncDeclaration()) != NULL) + { + next = f->overnext; + + TypeFunction *tf = (TypeFunction *)f->type; + if (!tf->arguments || tf->arguments->dim != 1) + continue; + Argument *p = (Argument *)tf->arguments->data[0]; + if (p->type->ty != Tdelegate) + continue; + tf = (TypeFunction *)p->type->next; + assert(tf->ty == Tfunction); + + /* We now have tf, the type of the delegate. Match it against + * the arguments, filling in missing argument types. + */ + if (!tf->arguments || tf->varargs) + continue; // not enough parameters + unsigned nparams = tf->arguments->dim; + if (arguments->dim != nparams) + continue; // not enough parameters + + for (unsigned u = 0; u < nparams; u++) + { + p = (Argument *)arguments->data[u]; + Argument *tp = (Argument *)tf->arguments->data[u]; + if (p->type) + { if (!p->type->equals(tp->type)) + { + /* Cannot resolve argument types. Indicate an + * error by setting the number of arguments to 0. + */ + arguments->dim = 0; + return; + } + continue; + } + p->type = tp->type; + } + } + else if ((a = d->isAliasDeclaration()) != NULL) + { + Dsymbol *s = a->toAlias(); + next = s->isDeclaration(); + if (next == a) + break; + if (next == fstart) + break; + } + else + { d->error("is aliased to a function"); + break; + } + } +} + + diff -uNr gdc-0.17/d/dmd/optimize.c gdc-0.18/d/dmd/optimize.c --- gdc-0.17/d/dmd/optimize.c 2005-11-27 17:28:26.000000000 +0100 +++ gdc-0.18/d/dmd/optimize.c 2006-05-14 04:21:51.000000000 +0200 @@ -1,5 +1,5 @@ -// Copyright (c) 1999-2005 by Digital Mars +// Copyright (c) 1999-2006 by Digital Mars // All Rights Reserved // written by Walter Bright // www.digitalmars.com @@ -113,6 +113,7 @@ Expression *CastExp::optimize(int result) { + //printf("CastExp::optimize(result = %d) %s\n", result, toChars()); if (e1->op == TOKstring && (type->ty == Tpointer || type->ty == Tarray) && type->next->equals(e1->type->next) @@ -194,9 +195,10 @@ Expression *CommaExp::optimize(int result) { Expression *e; + //printf("CommaExp::optimize(result = %d) %s\n", result, toChars()); e1 = e1->optimize(0); e2 = e2->optimize(result); - if (!e1) + if (!e1 || e1->op == TOKint64 || e1->op == TOKfloat64) { e = e2; if (e) @@ -207,6 +209,47 @@ return e; } +Expression *ArrayLengthExp::optimize(int result) +{ Expression *e; + + //printf("ArrayLengthExp::optimize(result = %d) %s\n", result, toChars()); + e1 = e1->optimize(WANTvalue); + e = this; + if (e1->op == TOKstring) + { StringExp *es1 = (StringExp *)e1; + + e = new IntegerExp(loc, es1->len, type); + } + return e; +} + +Expression *EqualExp::optimize(int result) +{ Expression *e; + + //printf("EqualExp::optimize(result = %d) %s\n", result, toChars()); + e1 = e1->optimize(WANTvalue); + e2 = e2->optimize(WANTvalue); + e = this; + if (e1->op == TOKstring && e2->op == TOKstring) + { StringExp *es1 = (StringExp *)e1; + StringExp *es2 = (StringExp *)e2; + int value; + + assert(es1->sz == es2->sz); + if (es1->len == es2->len && + memcmp(es1->string, es2->string, es1->sz * es1->len) == 0) + value = 1; + else + value = 0; + if (op == TOKnotequal) + value ^= 1; + e = new IntegerExp(loc, value, type); + } + else if (e1->isConst() == 1 && e2->isConst() == 1) + e = constFold(); + return e; +} + Expression *IndexExp::optimize(int result) { Expression *e; @@ -219,7 +262,7 @@ uinteger_t i = e2->toInteger(); if (i >= es1->len) - error("string index %llu is out of bounds", i); + error("string index %llu is out of bounds [0 .. %u]", i, es1->len); else { integer_t value; @@ -244,6 +287,14 @@ e = new IntegerExp(loc, value, type); } } + else if (e1->type->toBasetype()->ty == Tsarray && e2->op == TOKint64) + { TypeSArray *tsa = (TypeSArray *)e1->type->toBasetype(); + uinteger_t length = tsa->dim->toInteger(); + uinteger_t i = e2->toInteger(); + + if (i >= length) + error("array index %llu is out of bounds [0 .. %llu]", i, length); + } return e; } @@ -288,17 +339,25 @@ Expression *AndAndExp::optimize(int result) { Expression *e; + //printf("AndAndExp::optimize(%d) %s\n", result, toChars()); e1 = e1->optimize(WANTflags); - e2 = e2->optimize(WANTflags); e = this; if (e1->isBool(FALSE)) - e = new IntegerExp(loc, 0, type); - else if (e1->isConst()) { - if (e2->isConst()) - e = constFold(); - else if (e1->isBool(TRUE)) - e = new BoolExp(loc, e2, type); + e = new CommaExp(loc, e1, new IntegerExp(loc, 0, type)); + e->type = type; + e = e->optimize(result); + } + else + { + e2 = e2->optimize(WANTflags); + if (e1->isConst()) + { + if (e2->isConst()) + e = constFold(); + else if (e1->isBool(TRUE)) + e = new BoolExp(loc, e2, type); + } } return e; } @@ -307,16 +366,23 @@ { Expression *e; e1 = e1->optimize(WANTflags); - e2 = e2->optimize(WANTflags); e = this; if (e1->isBool(TRUE)) - e = new IntegerExp(loc, 1, type); - else if (e1->isConst()) + { // Replace with (e1, 1) + e = new CommaExp(loc, e1, new IntegerExp(loc, 1, type)); + e->type = type; + e = e->optimize(result); + } + else { - if (e2->isConst()) - e = constFold(); - else if (e1->isBool(FALSE)) - e = new BoolExp(loc, e2, type); + e2 = e2->optimize(WANTflags); + if (e1->isConst()) + { + if (e2->isConst()) + e = constFold(); + else if (e1->isBool(FALSE)) + e = new BoolExp(loc, e2, type); + } } return e; } @@ -324,7 +390,7 @@ Expression *CatExp::optimize(int result) { Expression *e; - //printf("CatExp::optimize(%d)\n", result); + //printf("CatExp::optimize(%d) %s\n", result, toChars()); e1 = e1->optimize(result); e2 = e2->optimize(result); if (e1->op == TOKstring && e2->op == TOKstring) @@ -353,7 +419,77 @@ t = es1->type; else t = es2->type; - es->type = new TypeSArray(t->next, new IntegerExp(0, len, Type::tindex)); + //es->type = new TypeSArray(t->next, new IntegerExp(0, len, Type::tindex)); + //es->type = es->type->semantic(loc, NULL); + es->type = type; + e = es; + } + else if (e1->op == TOKstring && e2->op == TOKint64) + { + // Concatenate the strings + void *s; + void *sch; + StringExp *es1 = (StringExp *)e1; + StringExp *es; + Type *t; + size_t len = es1->len + 1; + int sz = es1->sz; + integer_t v = e2->toInteger(); + + s = mem.malloc((len + 1) * sz); + memcpy(s, es1->string, es1->len * sz); + sch = (unsigned char *)s + es1->len * sz; + switch (sz) + { + case 1: *(d_uns8*)sch = v; break; + case 2: *(d_uns16*)sch = v; break; + case 4: *(d_uns32*)sch = v; break; + default: assert(0); + } + + // Add terminating 0 + memset((unsigned char *)s + len * sz, 0, sz); + + es = new StringExp(loc, s, len); + es->sz = sz; + es->committed = es1->committed; + t = es1->type; + //es->type = new TypeSArray(t->next, new IntegerExp(0, len, Type::tindex)); + //es->type = es->type->semantic(loc, NULL); + es->type = type; + e = es; + } + else if (e1->op == TOKint64 && e2->op == TOKstring) + { + // Concatenate the strings + void *s; + StringExp *es2 = (StringExp *)e2; + StringExp *es; + Type *t; + size_t len = 1 + es2->len; + int sz = es2->sz; + integer_t v = e1->toInteger(); + + s = mem.malloc((len + 1) * sz); + switch (sz) + { + case 1: *(d_uns8*)s = v; break; + case 2: *(d_uns16*)s = v; break; + case 4: *(d_uns32*)s = v; break; + default: assert(0); + } + memcpy((unsigned char *)s + sz, es2->string, es2->len * sz); + + // Add terminating 0 + memset((unsigned char *)s + len * sz, 0, sz); + + es = new StringExp(loc, s, len); + es->sz = sz; + es->committed = es2->committed; + t = es2->type; + //es->type = new TypeSArray(t->next, new IntegerExp(0, len, Type::tindex)); + //es->type = es->type->semantic(loc, NULL); + es->type = type; e = es; } else @@ -366,14 +502,15 @@ { Expression *e; econd = econd->optimize(WANTflags); - e1 = e1->optimize(result); - e2 = e2->optimize(result); if (econd->isBool(TRUE)) - e = e1; + e = e1->optimize(result); else if (econd->isBool(FALSE)) - e = e2; + e = e2->optimize(result); else + { e1 = e1->optimize(result); + e2 = e2->optimize(result); e = this; + } return e; } diff -uNr gdc-0.17/d/dmd/parse.c gdc-0.18/d/dmd/parse.c --- gdc-0.17/d/dmd/parse.c 2005-11-28 05:17:52.000000000 +0100 +++ gdc-0.18/d/dmd/parse.c 2006-05-14 01:38:32.000000000 +0200 @@ -183,34 +183,6 @@ s = parseMixin(); break; - case TOKinstance: // Deprecated - if (isDeclaration(&token, 2, TOKreserved, NULL)) - { - //printf("it's a declaration\n"); - goto Ldeclaration; - } - else - { - // instance foo(bar) ident; - - TemplateInstance *ti; - - //printf("it's an alias\n"); - ti = parseTemplateInstance(); - s = (Dsymbol *)ti; - if (ti) - { - if (token.value == TOKidentifier) - { - s = (Dsymbol *)new AliasDeclaration(loc, token.ident, ti); - nextToken(); - } - } - if (token.value != TOKsemicolon) - error("';' expected after template instance"); - } - break; - CASE_BASIC_TYPES: case TOKalias: case TOKtypedef: @@ -218,7 +190,7 @@ case TOKtypeof: case TOKdot: Ldeclaration: - a = parseDeclaration(); + a = parseDeclarations(); decldefs->append(a); continue; @@ -260,7 +232,14 @@ s = parseStaticAssert(); else if (token.value == TOKif) { condition = parseStaticIfCondition(); - goto Lcondition; + a = parseBlock(); + aelse = NULL; + if (token.value == TOKelse) + { nextToken(); + aelse = parseBlock(); + } + s = new StaticIfDeclaration(condition, a, aelse); + break; } else { stc = STCstatic; @@ -307,6 +286,8 @@ s = v; if (token.value != TOKsemicolon) error("semicolon expected following auto declaration, not '%s'", token.toChars()); + else + nextToken(); } else { a = parseBlock(); @@ -366,7 +347,7 @@ case TOKpragma: { Identifier *ident; - Array *args = NULL; + Expressions *args = NULL; nextToken(); check(TOKlparen); @@ -670,6 +651,7 @@ /*********************************************** + * Deprecated. * iftype (type identifier : specialization) * body * else @@ -942,7 +924,7 @@ * at ai ... */ - if (inout != In) + if (inout == Out || inout == InOut) error("variadic argument cannot be out or inout"); varargs = 2; a = new Argument(inout, at, ai, ae); @@ -965,6 +947,7 @@ return arguments; } + /************************************* */ @@ -1007,6 +990,7 @@ Expression *value; Identifier *ident; + loc = this->loc; ident = token.ident; value = NULL; nextToken(); @@ -1041,7 +1025,7 @@ int anon = 0; enum TOK tok; Identifier *id; - Array *tpl = NULL; + TemplateParameters *tpl = NULL; //printf("Parser::parseAggregate()\n"); tok = token.value; @@ -1070,7 +1054,7 @@ error("anonymous classes not allowed"); // Collect base class(es) - Array *baseclasses = NULL; + BaseClasses *baseclasses = NULL; if (token.value == TOKcolon) { nextToken(); @@ -1148,17 +1132,16 @@ /******************************************* */ -Array *Parser::parseBaseClasses() +BaseClasses *Parser::parseBaseClasses() { enum PROT protection = PROTpublic; - Array *baseclasses = new Array(); + BaseClasses *baseclasses = new BaseClasses(); for (; 1; nextToken()) { switch (token.value) { case TOKidentifier: - case TOKinstance: break; case TOKprivate: protection = PROTprivate; @@ -1193,7 +1176,7 @@ { TemplateDeclaration *tempdecl; Identifier *id; - Array *tpl; + TemplateParameters *tpl; Array *decldefs; Loc loc = this->loc; @@ -1234,18 +1217,18 @@ * Parse template parameter list. */ -Array *Parser::parseTemplateParameterList() +TemplateParameters *Parser::parseTemplateParameterList() { - Array *tpl; + TemplateParameters *tpl; if (token.value != TOKlparen) { error("parenthesized TemplateParameterList expected following TemplateIdentifier"); goto Lerr; } - tpl = new Array(); + tpl = new TemplateParameters(); nextToken(); - // Get TemplateParameterList + // Get array of TemplateParameters if (token.value != TOKrparen) { while (1) @@ -1491,6 +1474,7 @@ Array *Parser::parseTemplateArgumentList() { + //printf("Parser::parseTemplateArgumentList()\n"); Array *tiargs = new Array(); if (token.value != TOKlparen) { error("!(TemplateArgumentList) expected following TemplateIdentifier"); @@ -1627,18 +1611,6 @@ id = Id::empty; goto Lident; - case TOKinstance: - { // Deprecated - tempinst = parseTemplateInstance(); - if (!tempinst) // if error - { t = Type::tvoid; - break; - } - - tid = new TypeInstance(loc, tempinst); - goto Lident2; - } - case TOKtypeof: { Expression *exp; @@ -1963,7 +1935,7 @@ * Return array of Declaration *'s. */ -Array *Parser::parseDeclaration() +Array *Parser::parseDeclarations() { enum STC storage_class; enum STC stc; @@ -1976,7 +1948,7 @@ unsigned char *comment = token.blockComment; enum LINK link = linkage; - //printf("parseDeclaration()\n"); + //printf("parseDeclarations()\n"); switch (token.value) { case TOKtypedef: @@ -2485,39 +2457,6 @@ break; } - case TOKinstance: // Deprecated - /* Three cases: - * 1) Declaration - * 2) Template Instance Alias - * 3) Expression - */ - if (isDeclaration(&token, 2, TOKreserved, NULL)) - { - //printf("it's a declaration\n"); - goto Ldeclaration; - } - else - { - if (isTemplateInstance(&token, &t) && t->value == TOKidentifier) - { // case 2 - TemplateInstance *ti; - AliasDeclaration *a; - - ti = parseTemplateInstance(); - assert(ti); - assert(token.value == TOKidentifier); - - a = new AliasDeclaration(loc, token.ident, ti); - s = new DeclarationStatement(loc, a); - nextToken(); - if (token.value != TOKsemicolon) - error("';' expected after template instance, not %s", token.toChars()); - } - else - goto Lexp; // case 3 - } - break; - case TOKstatic: { // Look ahead to see if it's static assert() or static if() Token *t; @@ -2548,10 +2487,10 @@ Ldeclaration: { Array *a; - a = parseDeclaration(); + a = parseDeclarations(); if (a->dim > 1) { - Array *as = new Array(); + Statements *as = new Statements(); as->reserve(a->dim); for (int i = 0; i < a->dim; i++) { @@ -2601,10 +2540,10 @@ } case TOKlcurly: - { Array *statements; + { Statements *statements; nextToken(); - statements = new Array(); + statements = new Statements(); while (token.value != TOKrcurly) { statements->push(parseStatement(PSsemi | PScurlyscope)); @@ -2716,10 +2655,21 @@ { inout = InOut; nextToken(); } + if (token.value == TOKidentifier) + { + Token *t = peek(&token); + if (t->value == TOKcomma || t->value == TOKsemicolon) + { ai = token.ident; + at = NULL; // infer argument type + nextToken(); + goto Larg; + } + } tb = parseBasicType(); at = parseDeclarator(tb, &ai); if (!ai) error("no identifier for declarator %s", at->toChars()); + Larg: a = new Argument(inout, at, ai, NULL); arguments->push(a); if (token.value == TOKcomma) @@ -2738,12 +2688,62 @@ } case TOKif: - { Expression *condition; + { Argument *arg = NULL; + Expression *condition; Statement *ifbody; Statement *elsebody; nextToken(); check(TOKlparen); + + if (token.value == TOKauto) + { + nextToken(); + if (token.value == TOKidentifier) + { + Token *t = peek(&token); + if (t->value == TOKassign) + { + arg = new Argument(In, NULL, token.ident, NULL); + nextToken(); + nextToken(); + } + else + { error("= expected following auto identifier"); + goto Lerror; + } + } + else + { error("identifier expected following auto"); + goto Lerror; + } + } + else if (isDeclaration(&token, 2, TOKassign, NULL)) + { + Type *tb; + Type *at; + Identifier *ai; + + tb = parseBasicType(); + at = parseDeclarator(tb, &ai); + check(TOKassign); + arg = new Argument(In, at, ai, NULL); + } + + // Check for " ident;" + else if (token.value == TOKidentifier) + { + Token *t = peek(&token); + if (t->value == TOKcomma || t->value == TOKsemicolon) + { + arg = new Argument(In, NULL, token.ident, NULL); + nextToken(); + nextToken(); + if (!global.params.useDeprecated) + error("if (v; e) is deprecated, use if (auto v = e)"); + } + } + condition = parseExpression(); check(TOKrparen); ifbody = parseStatement(PSscope); @@ -2754,7 +2754,46 @@ } else elsebody = NULL; - s = new IfStatement(loc, condition, ifbody, elsebody); + s = new IfStatement(loc, arg, condition, ifbody, elsebody); + break; + } + + case TOKscope: + nextToken(); + check(TOKlparen); + if (token.value != TOKidentifier) + { error("scope identifier expected"); + goto Lerror; + } + else + { TOK t = TOKon_scope_exit; + Identifier *id = token.ident; + + if (id == Id::exit) + t = TOKon_scope_exit; + else if (id == Id::failure) + t = TOKon_scope_failure; + else if (id == Id::success) + t = TOKon_scope_success; + else + error("valid scope identifiers are exit, failure, or success, not %s", id->toChars()); + nextToken(); + check(TOKrparen); + Statement *st = parseStatement(PScurlyscope); + s = new OnScopeStatement(loc, t, st); + break; + } + + case TOKon_scope_exit: + case TOKon_scope_failure: + case TOKon_scope_success: + { + TOK t = token.value; + if (!global.params.useDeprecated) + error("%s is deprecated, use scope", token.toChars()); + nextToken(); + Statement *st = parseStatement(PScurlyscope); + s = new OnScopeStatement(loc, t, st); break; } @@ -2785,7 +2824,7 @@ case TOKpragma: { Identifier *ident; - Array *args = NULL; + Expressions *args = NULL; Statement *body; nextToken(); @@ -2820,7 +2859,7 @@ case TOKcase: { Expression *exp; - Array *statements; + Statements *statements; Array cases; // array of Expression's while (1) @@ -2833,7 +2872,7 @@ } check(TOKcolon); - statements = new Array(); + statements = new Statements(); while (token.value != TOKcase && token.value != TOKdefault && token.value != TOKrcurly) @@ -2854,12 +2893,12 @@ case TOKdefault: { - Array *statements; + Statements *statements; nextToken(); check(TOKcolon); - statements = new Array(); + statements = new Statements(); while (token.value != TOKcase && token.value != TOKdefault && token.value != TOKrcurly) @@ -3045,12 +3084,12 @@ case TOKvolatile: nextToken(); - s = parseStatement(PSsemi | PSscope); + s = parseStatement(PSsemi | PScurlyscope); s = new VolatileStatement(loc, s); break; case TOKasm: - { Array *statements; + { Statements *statements; Identifier *label; Loc labelloc; Token *toklist; @@ -3066,7 +3105,7 @@ toklist = NULL; ptoklist = &toklist; label = NULL; - statements = new Array(); + statements = new Statements(); while (1) { switch (token.value) @@ -3236,18 +3275,6 @@ case TOKdot: goto Ldot; - case TOKinstance: // Deprecated - // Handle cases like: - // instance Foo(int).bar x; - // But remember that: - // instance Foo(int) x; - // is not a type, but is an AliasDeclaration declaration. - if (!isTemplateInstance(t, &t)) - goto Lfalse; // invalid syntax for template instance - if (t->value == TOKdot) - goto Ldot; - goto Lfalse; - case TOKtypeof: /* typeof(exp).identifier... */ @@ -3273,6 +3300,8 @@ Token *t = *pt; int parens; + //printf("Parser::isDeclarator()\n"); + //t->print(); if (t->value == TOKassign) return FALSE; @@ -3434,13 +3463,18 @@ if (!isBasicType(&t)) return FALSE; tmp = FALSE; - if (!isDeclarator(&t, &tmp, TOKreserved)) + if (t->value != TOKdotdotdot && + !isDeclarator(&t, &tmp, TOKreserved)) return FALSE; if (t->value == TOKassign) { t = peek(t); if (!isExpression(&t)) return FALSE; - continue; + } + if (t->value == TOKdotdotdot) + { + t = peek(t); + break; } if (t->value == TOKcomma) { t = peek(t); @@ -3464,24 +3498,38 @@ // is found. Token *t = *pt; - int nest = 0; + int brnest = 0; + int panest = 0; for (;; t = peek(t)) { switch (t->value) { case TOKlbracket: - nest++; + brnest++; continue; case TOKrbracket: - if (--nest >= 0) + if (--brnest >= 0) continue; break; + case TOKlparen: + panest++; + continue; + case TOKcomma: + if (brnest || panest) + continue; + break; + case TOKrparen: - if (nest) + if (--panest >= 0) + continue; + break; + + case TOKslice: + if (brnest) continue; break; @@ -3720,12 +3768,12 @@ break; case TOKtrue: - e = new IntegerExp(loc, 1, Type::tbit); + e = new IntegerExp(loc, 1, Type::tbool); nextToken(); break; case TOKfalse: - e = new IntegerExp(loc, 0, Type::tbit); + e = new IntegerExp(loc, 0, Type::tbool); nextToken(); break; @@ -3872,16 +3920,6 @@ e = new AssertExp(loc, e); break; - case TOKinstance: // Deprecated - { TemplateInstance *tempinst; - - tempinst = parseTemplateInstance(); - if (!tempinst) - goto Lerr; - e = new ScopeExp(loc, tempinst); - break; - } - case TOKfunction: case TOKdelegate: { @@ -3961,15 +3999,6 @@ else error("identifier expected following '.', not '%s'", token.toChars()); break; -#if 0 - case TOKarrow: - nextToken(); - if (token.value == TOKidentifier) - e = new ArrowExp(loc, e, token.ident); - else - error("identifier expected following '->', not '%s'", token.toChars()); - break; -#endif case TOKplusplus: e = new PostIncExp(loc, e); @@ -4009,7 +4038,7 @@ } else { // array[index, i2, i3, i4, ...] - Array *arguments = new Array(); + Expressions *arguments = new Expressions(); arguments->push(index); if (token.value == TOKcomma) { @@ -4543,12 +4572,12 @@ * Assume current token is '('. */ -Array *Parser::parseArguments() +Expressions *Parser::parseArguments() { // function call - Array *arguments; + Expressions *arguments; Expression *arg; - arguments = new Array(); + arguments = new Expressions(); //if (token.value == TOKlparen) { nextToken(); @@ -4573,8 +4602,8 @@ Expression *Parser::parseNewExp() { Type *t; - Array *newargs; - Array *arguments = NULL; + Expressions *newargs; + Expressions *arguments = NULL; Expression *e; Loc loc = this->loc; @@ -4592,7 +4621,7 @@ if (token.value == TOKlparen) arguments = parseArguments(); - Array *baseclasses = parseBaseClasses(); + BaseClasses *baseclasses = parseBaseClasses(); Identifier *id = NULL; ClassDeclaration *cd = new ClassDeclaration(loc, id, baseclasses); @@ -4636,7 +4665,7 @@ e = new DotIdExp(loc, e, id); } - arguments = new Array(); + arguments = new Expressions(); arguments->push(e); t = new TypeDArray(t->next); } @@ -4651,7 +4680,7 @@ TypeSArray *tsa = (TypeSArray *)t; Expression *e = tsa->dim; - arguments = new Array(); + arguments = new Expressions(); arguments->push(e); t = new TypeDArray(t->next); } diff -uNr gdc-0.17/d/dmd/parse.h gdc-0.18/d/dmd/parse.h --- gdc-0.17/d/dmd/parse.h 2005-10-26 03:33:56.000000000 +0200 +++ gdc-0.18/d/dmd/parse.h 2006-05-13 21:05:42.000000000 +0200 @@ -14,6 +14,7 @@ #pragma once #endif /* __DMC__ */ +#include "arraytypes.h" #include "lexer.h" #include "enum.h" @@ -53,7 +54,7 @@ Array *parseDeclDefs(int once); Array *parseBlock(); TemplateDeclaration *parseTemplateDeclaration(); - Array *parseTemplateParameterList(); + TemplateParameters *parseTemplateParameterList(); TemplateInstance *parseTemplateInstance(); Dsymbol *parseMixin(); Array *parseTemplateArgumentList(); @@ -74,12 +75,12 @@ Array *parseParameters(int *pvarargs); EnumDeclaration *parseEnum(); Dsymbol *parseAggregate(); - Array *parseBaseClasses(); + BaseClasses *parseBaseClasses(); Import *parseImport(Array *decldefs); Type *parseBasicType(); Type *parseBasicType2(Type *t); Type *parseDeclarator(Type *t, Identifier **pident); - Array *parseDeclaration(); + Array *parseDeclarations(); void parseContracts(FuncDeclaration *f); Statement *parseStatement(int flags); Initializer *parseInitializer(); @@ -110,7 +111,7 @@ Expression *parseCondExp(); Expression *parseAssignExp(); - Array *parseArguments(); + Expressions *parseArguments(); Expression *parseNewExp(); diff -uNr gdc-0.17/d/dmd/port.h gdc-0.18/d/dmd/port.h --- gdc-0.17/d/dmd/port.h 2004-10-26 02:41:27.000000000 +0200 +++ gdc-0.18/d/dmd/port.h 2005-12-10 03:31:59.000000000 +0100 @@ -13,7 +13,7 @@ #ifndef TYPEDEFS #define TYPEDEFS -#include +//#include #if _MSC_VER typedef __int64 longlong; @@ -45,14 +45,14 @@ static ulonglong strtoull(const char *p, char **pend, int base); static char *ull_to_string(char *buffer, ulonglong ull); - static wchar_t *ull_to_string(wchar_t *buffer, ulonglong ull); + // static wchar_t *ull_to_string(wchar_t *buffer, ulonglong ull); // Convert ulonglong to double static double ull_to_double(ulonglong ull); // Get locale-dependent list separator static char *list_separator(); - static wchar_t *wlist_separator(); + // static wchar_t *wlist_separator(); }; #endif diff -uNr gdc-0.17/d/dmd/root.c gdc-0.18/d/dmd/root.c --- gdc-0.17/d/dmd/root.c 2005-10-13 03:06:51.000000000 +0200 +++ gdc-0.18/d/dmd/root.c 2006-05-08 12:41:19.000000000 +0200 @@ -48,6 +48,7 @@ } #endif +#ifndef IN_GCC /************************************* * Convert wchar string to ascii string. */ @@ -84,6 +85,7 @@ } return 1; } +#endif /*********************************** @@ -1560,19 +1562,21 @@ char *p; unsigned psize; int count; + va_list args_copy; p = buffer; psize = sizeof(buffer); for (;;) { + va_copy(args_copy, args); #if _WIN32 - count = _vsnprintf(p,psize,format,args); + count = _vsnprintf(p,psize,format,args_copy); if (count != -1) break; psize *= 2; #endif #ifndef _WIN32 - count = vsnprintf(p,psize,format,args); + count = vsnprintf(p,psize,format,args_copy); if (count == -1) psize *= 2; else if (count >= psize) @@ -1592,19 +1596,20 @@ dchar *p; unsigned psize; int count; + va_list args_copy; p = buffer; psize = sizeof(buffer) / sizeof(buffer[0]); for (;;) { #if _WIN32 - count = _vsnwprintf(p,psize,format,args); + count = _vsnwprintf(p,psize,format,args_copy); if (count != -1) break; psize *= 2; #endif #ifndef _WIN32 - count = vsnwprintf(p,psize,format,args); + count = vsnwprintf(p,psize,format,args_copy); if (count == -1) psize *= 2; else if (count >= psize) diff -uNr gdc-0.17/d/dmd/root.h gdc-0.18/d/dmd/root.h --- gdc-0.17/d/dmd/root.h 2005-10-13 03:06:51.000000000 +0200 +++ gdc-0.18/d/dmd/root.h 2006-05-08 12:41:19.000000000 +0200 @@ -233,10 +233,10 @@ // Return <0 this < f // =0 this == f // >0 this > f - int File::compareTime(File *f); + int compareTime(File *f); // Read system file statistics - void File::stat(); + void stat(); /* Set buffer */ @@ -292,7 +292,7 @@ void printf(const unsigned short *format, ...); #endif void bracket(char left, char right); - unsigned OutBuffer::bracket(unsigned i, char *left, unsigned j, char *right); + unsigned bracket(unsigned i, char *left, unsigned j, char *right); void spread(unsigned offset, unsigned nbytes); unsigned insert(unsigned offset, const void *data, unsigned nbytes); void remove(unsigned offset, unsigned nbytes); diff -uNr gdc-0.17/d/dmd/scope.c gdc-0.18/d/dmd/scope.c --- gdc-0.17/d/dmd/scope.c 2005-10-02 16:17:55.000000000 +0200 +++ gdc-0.18/d/dmd/scope.c 2006-04-16 17:13:30.000000000 +0200 @@ -121,7 +121,7 @@ Dsymbol *m = module; while (m->parent) m = m->parent; - m->addMember(NULL, sc->scopesym); + m->addMember(NULL, sc->scopesym, 1); m->parent = NULL; // got changed by addMember() // Create the module scope underneath the global scope @@ -232,7 +232,7 @@ sc->enclosing && sc->enclosing->search(ident, NULL)) { - fprintf(stderr, "warning - "); + fprintf(stdmsg, "warning - "); error("array 'length' hides other 'length' name in outer scope"); } diff -uNr gdc-0.17/d/dmd/statement.c gdc-0.18/d/dmd/statement.c --- gdc-0.17/d/dmd/statement.c 2005-10-02 16:17:55.000000000 +0200 +++ gdc-0.18/d/dmd/statement.c 2006-05-14 04:21:51.000000000 +0200 @@ -1,5 +1,5 @@ -// Copyright (c) 1999-2004 by Digital Mars +// Copyright (c) 1999-2006 by Digital Mars // All Rights Reserved // written by Walter Bright // www.digitalmars.com @@ -29,13 +29,18 @@ #include "declaration.h" #include "aggregate.h" #include "id.h" - +#include "hdrgen.h" /******************************** Statement ***************************/ Statement::Statement(Loc loc) : loc(loc) { +#ifdef _DH + // If this is an in{} contract scope statement (skip for determining + // inlineStatus of a function body for header content) + incontract = 0; +#endif } Statement *Statement::syntaxCopy() @@ -46,19 +51,20 @@ void Statement::print() { - fprintf(stderr, "%s\n", toChars()); - fflush(stderr); + fprintf(stdmsg, "%s\n", toChars()); + fflush(stdmsg); } char *Statement::toChars() { OutBuffer *buf; + HdrGenState hgs; buf = new OutBuffer(); - toCBuffer(buf); + toCBuffer(buf, &hgs); return buf->toChars(); } -void Statement::toCBuffer(OutBuffer *buf) +void Statement::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { buf->printf("Statement::toCBuffer()"); buf->writenl(); @@ -91,16 +97,16 @@ { char *p = loc.toChars(); if (*p) - fprintf(stderr, "%s: ", p); + fprintf(stdmsg, "%s: ", p); mem.free(p); va_list ap; va_start(ap, format); - vfprintf(stderr, format, ap); + vfprintf(stdmsg, format, ap); va_end(ap); - fprintf(stderr, "\n"); - fflush(stderr); + fprintf(stdmsg, "\n"); + fflush(stdmsg); } global.errors++; } @@ -140,13 +146,19 @@ * If this statement has code that needs to run in a finally clause * at the end of the current scope, return that code in the form of * a Statement. + * Output: + * *sentry code executed upon entry to the scope + * *sexception code executed upon exit from the scope via exception + * *sfinally code executed in finally block */ -Statement *Statement::callAutoDtor() +void Statement::scopeCode(Statement **sentry, Statement **sexception, Statement **sfinally) { - //printf("Statement::callAutoDtor()\n"); + //printf("Statement::scopeCode()\n"); //print(); - return NULL; + *sentry = NULL; + *sexception = NULL; + *sfinally = NULL; } /********************************* @@ -155,7 +167,7 @@ * Returns NULL if no flattening necessary. */ -Array *Statement::flatten() +Statements *Statement::flatten() { return NULL; } @@ -175,18 +187,25 @@ return es; } -void ExpStatement::toCBuffer(OutBuffer *buf) +void ExpStatement::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { if (exp) - exp->toCBuffer(buf); + exp->toCBuffer(buf, hgs); buf->writeByte(';'); - buf->writenl(); + if (!hgs->FLinit.init) + buf->writenl(); } Statement *ExpStatement::semantic(Scope *sc) { if (exp) + { + //printf("ExpStatement::semantic() %s\n", exp->toChars()); exp = exp->semantic(sc); + exp = resolveProperties(sc, exp); + exp->checkSideEffect(0); + exp = exp->optimize(WANTvalue); + } return this; } @@ -219,11 +238,15 @@ return ds; } -Statement *DeclarationStatement::callAutoDtor() +void DeclarationStatement::scopeCode(Statement **sentry, Statement **sexception, Statement **sfinally) { - //printf("DeclarationStatement::callAutoDtor()\n"); + //printf("DeclarationStatement::scopeCode()\n"); //print(); + *sentry = NULL; + *sexception = NULL; + *sfinally = NULL; + if (exp) { if (exp->op == TOKdeclaration) @@ -237,24 +260,22 @@ if (e) { //printf("dtor is: "); e->print(); - return new ExpStatement(loc, e); + *sfinally = new ExpStatement(loc, e); } } } } - return NULL; } -void DeclarationStatement::toCBuffer(OutBuffer *buf) +void DeclarationStatement::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { - buf->printf("DeclarationStatement::toCBuffer()"); - buf->writenl(); + exp->toCBuffer(buf, hgs); } /******************************** CompoundStatement ***************************/ -CompoundStatement::CompoundStatement(Loc loc, Array *s) +CompoundStatement::CompoundStatement(Loc loc, Statements *s) : Statement(loc) { statements = s; @@ -263,7 +284,7 @@ CompoundStatement::CompoundStatement(Loc loc, Statement *s1, Statement *s2) : Statement(loc) { - statements = new Array(); + statements = new Statements(); statements->reserve(2); statements->push(s1); statements->push(s2); @@ -271,9 +292,9 @@ Statement *CompoundStatement::syntaxCopy() { - Array *a = new Array(); + Statements *a = new Statements(); a->setDim(statements->dim); - for (int i = 0; i < statements->dim; i++) + for (size_t i = 0; i < statements->dim; i++) { Statement *s = (Statement *)statements->data[i]; if (s) s = s->syntaxCopy(); @@ -288,12 +309,16 @@ { Statement *s; //printf("CompoundStatement::semantic(this = %p, sc = %p)\n", this, sc); - for (int i = 0; i < statements->dim; i++) + + /* Start by flattening it + */ + + for (size_t i = 0; i < statements->dim; i++) { L1: s = (Statement *) statements->data[i]; if (s) - { Array *a = s->flatten(); + { Statements *a = s->flatten(); if (a) { @@ -303,32 +328,100 @@ break; goto L1; } + } + } + for (size_t i = 0; i < statements->dim; i++) + { + s = (Statement *) statements->data[i]; + if (s) + { s = s->semantic(sc); statements->data[i] = s; if (s) { - Statement *finalbody; + Statement *sentry; + Statement *sexception; + Statement *sfinally; + + s->scopeCode(&sentry, &sexception, &sfinally); + if (sentry) + { + sentry = sentry->semantic(sc); + statements->data[i] = sentry; + } + if (sexception) + { + if (i + 1 == statements->dim) + { + statements->push(sexception); + if (sfinally) + // Assume sexception does not throw + statements->push(sfinally); + } + else + { + /* Rewrite: + * s; s1; s2; + * As: + * s; + * try { s1; s2; } + * catch (Object __o) + * { sexception; throw __o; } + */ + Statement *body; + Statements *a = new Statements(); + + for (int j = i + 1; j < statements->dim; j++) + { + a->push(statements->data[j]); + } + body = new CompoundStatement(0, a); + body = new ScopeStatement(0, body); - finalbody = s->callAutoDtor(); - if (finalbody) + char name[3 + sizeof(int) * 3 + 1]; + static int num; + sprintf(name, "__o%d", ++num); + Identifier *id = Lexer::idPool(name); + + Statement *handler = new ThrowStatement(0, new IdentifierExp(0, id)); + handler = new CompoundStatement(0, sexception, handler); + + Array *catches = new Array(); + Catch *ctch = new Catch(0, NULL, id, handler); + catches->push(ctch); + s = new TryCatchStatement(0, body, catches); + + if (sfinally) + s = new TryFinallyStatement(0, s, sfinally); + s = s->semantic(sc); + statements->data[i + 1] = s; + statements->setDim(i + 2); + break; + } + } + else if (sfinally) { if (i + 1 == statements->dim) { - statements->push(finalbody); + statements->push(sfinally); } else { - // The rest of the statements form the body of a try-finally + /* Rewrite: + * s; s1; s2; + * As: + * s; try { s1; s2; } finally { sfinally; } + */ Statement *body; - Array *a = new Array(); + Statements *a = new Statements(); for (int j = i + 1; j < statements->dim; j++) { a->push(statements->data[j]); } body = new CompoundStatement(0, a); - s = new TryFinallyStatement(0, body, finalbody); + s = new TryFinallyStatement(0, body, sfinally); s = s->semantic(sc); statements->data[i + 1] = s; statements->setDim(i + 2); @@ -343,7 +436,7 @@ return this; } -Array *CompoundStatement::flatten() +Statements *CompoundStatement::flatten() { return statements; } @@ -366,7 +459,7 @@ return rs; } -void CompoundStatement::toCBuffer(OutBuffer *buf) +void CompoundStatement::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { int i; for (i = 0; i < statements->dim; i++) @@ -374,7 +467,7 @@ s = (Statement *) statements->data[i]; if (s) - s->toCBuffer(buf); + s->toCBuffer(buf, hgs); } } @@ -402,7 +495,7 @@ if (!falloff && global.params.warnings && !s->comeFrom()) { - fprintf(stderr, "warning - "); + fprintf(stdmsg, "warning - "); s->error("statement is not reachable"); } falloff = s->fallOffEnd(); @@ -434,7 +527,7 @@ //printf("ScopeStatement::semantic(sc = %p)\n", sc); if (statement) - { Array *a; + { Statements *a; sym = new ScopeDsymbol(); sym->parent = sc->scopesym; @@ -449,12 +542,15 @@ statement = statement->semantic(sc); if (statement) { - Statement *finalbody; - finalbody = statement->callAutoDtor(); - if (finalbody) + Statement *sentry; + Statement *sexception; + Statement *sfinally; + + statement->scopeCode(&sentry, &sexception, &sfinally); + if (sfinally) { - //printf("adding finalbody\n"); - statement = new CompoundStatement(loc, statement, finalbody); + //printf("adding sfinally\n"); + statement = new CompoundStatement(loc, statement, sfinally); } } @@ -468,13 +564,13 @@ return statement ? statement->fallOffEnd() : TRUE; } -void ScopeStatement::toCBuffer(OutBuffer *buf) +void ScopeStatement::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { buf->writeByte('{'); buf->writenl(); if (statement) - statement->toCBuffer(buf); + statement->toCBuffer(buf, hgs); buf->writeByte('}'); buf->writenl(); @@ -498,12 +594,41 @@ Statement *WhileStatement::semantic(Scope *sc) { +#if 0 + if (condition->op == TOKmatch) + { + /* Rewrite while (condition) body as: + * if (condition) + * do + * body + * while ((_match = _match.opNext), _match); + */ + + Expression *ew = new IdentifierExp(0, Id::_match); + ew = new DotIdExp(0, ew, Id::next); + ew = new AssignExp(0, new IdentifierExp(0, Id::_match), ew); + ////ew = new EqualExp(TOKnotequal, 0, ew, new NullExp(0)); + Expression *ev = new IdentifierExp(0, Id::_match); + //ev = new CastExp(0, ev, Type::tvoidptr); + ew = new CommaExp(0, ew, ev); + Statement *sw = new DoStatement(loc, body, ew); + Statement *si = new IfStatement(loc, condition, sw, NULL); + return si->semantic(sc); + } +#endif + condition = condition->semantic(sc); condition = resolveProperties(sc, condition); condition = condition->checkToBoolean(); sc->noctor++; - body = body->semanticScope(sc, this, this); + + Scope *scd = sc->push(); + scd->sbreak = this; + scd->scontinue = this; + body = body->semantic(scd); + scd->pop(); + sc->noctor--; return this; @@ -530,6 +655,15 @@ return TRUE; } +void WhileStatement::toCBuffer(OutBuffer *buf, HdrGenState *hgs) +{ + buf->writestring("while ("); + condition->toCBuffer(buf, hgs); + buf->writebyte(')'); + buf->writenl(); + body->toCBuffer(buf, hgs); +} + /******************************** DoStatement ***************************/ DoStatement::DoStatement(Loc loc, Statement *b, Expression *c) @@ -553,7 +687,9 @@ sc->noctor--; condition = condition->semantic(sc); condition = resolveProperties(sc, condition); + condition = condition->checkToBoolean(); + return this; } @@ -578,6 +714,16 @@ return TRUE; } +void DoStatement::toCBuffer(OutBuffer *buf, HdrGenState *hgs) +{ + buf->writestring("do"); + buf->writenl(); + body->toCBuffer(buf, hgs); + buf->writestring("while ("); + condition->toCBuffer(buf, hgs); + buf->writebyte(')'); +} + /******************************** ForStatement ***************************/ ForStatement::ForStatement(Loc loc, Statement *init, Expression *condition, Expression *increment, Statement *body) @@ -653,6 +799,39 @@ return TRUE; } +void ForStatement::toCBuffer(OutBuffer *buf, HdrGenState *hgs) +{ + buf->writestring("for ("); + if (init) + { + hgs->FLinit.init++; + hgs->FLinit.decl = 0; + init->toCBuffer(buf, hgs); + if (hgs->FLinit.decl > 0) + buf->writebyte(';'); + hgs->FLinit.decl = 0; + hgs->FLinit.init--; + } + else + buf->writebyte(';'); + if (condition) + { buf->writebyte(' '); + condition->toCBuffer(buf, hgs); + } + buf->writebyte(';'); + if (increment) + { buf->writebyte(' '); + increment->toCBuffer(buf, hgs); + } + buf->writebyte(')'); + buf->writenl(); + buf->writebyte('{'); + buf->writenl(); + body->toCBuffer(buf, hgs); + buf->writebyte('}'); + buf->writenl(); +} + /******************************** ForeachStatement ***************************/ ForeachStatement::ForeachStatement(Loc loc, Array *arguments, @@ -665,6 +844,8 @@ this->key = NULL; this->value = NULL; + + this->func = NULL; } Statement *ForeachStatement::syntaxCopy() @@ -677,6 +858,7 @@ Statement *ForeachStatement::semantic(Scope *sc) { + //printf("ForeachStatement::semantic() %p\n", this); ScopeDsymbol *sym; Statement *s = this; int dim = arguments->dim; @@ -686,9 +868,32 @@ Type *tn = NULL; Type *tnv = NULL; + func = sc->func; + if (func->fes) + func = func->fes->func; + aggr = aggr->semantic(sc); aggr = resolveProperties(sc, aggr); + inferApplyArgTypes(arguments, aggr->type); + + /* Check for inference errors + */ + if (dim != arguments->dim) + { + //printf("dim = %d, arguments->dim = %d\n", dim, arguments->dim); + error("cannot uniquely infer foreach argument types"); + return this; + } + for (i = 0; i < dim; i++) + { Argument *arg = (Argument *)arguments->data[i]; + if (!arg->type) + { + error("cannot infer type for %s", arg->ident->toChars()); + return this; + } + } + sym = new ScopeDsymbol(); sym->parent = sc->scopesym; sc = sc->push(sym); @@ -742,6 +947,7 @@ { case In: var->storage_class |= STCin; break; case Out: var->storage_class |= STCout; break; case InOut: var->storage_class |= STCin | STCout; break; + default: assert(0); } var->semantic(sc); if (!sc->insert(var)) @@ -788,7 +994,7 @@ case Tstruct: Lapply: { FuncDeclaration *fdapply; - Array *args; + Expressions *args; Expression *ec; Expression *e; FuncLiteralDeclaration *fld; @@ -796,12 +1002,15 @@ Type *t; Expression *flde; Identifier *id; + Type *tret; + + tret = func->type->next; // Need a variable to hold value from any return statements in body. - if (!sc->func->vresult && sc->func->type->next != Type::tvoid) + if (!sc->func->vresult && tret != Type::tvoid) { VarDeclaration *v; - v = new VarDeclaration(loc, sc->func->type->next, Id::result, NULL); + v = new VarDeclaration(loc, tret, Id::result, NULL); v->noauto = 1; v->semantic(sc); if (!sc->insert(v)) @@ -813,7 +1022,7 @@ /* Turn body into the function literal: * int delegate(inout T arg) { body } */ - args = new Array(); + args = new Expressions(); for (i = 0; i < dim; i++) { Argument *arg = (Argument *)arguments->data[i]; @@ -876,13 +1085,17 @@ * _aaApply(aggr, keysize, flde) */ if (dim == 2) - fdapply = FuncDeclaration::genCfunc(Type::tindex, "_aaApply2"); + fdapply = FuncDeclaration::genCfunc(Type::tindex, "_aaApply2", + Type::tvoid->arrayOf(), Type::tsize_t, flde->type); // flde->type is not generic else - fdapply = FuncDeclaration::genCfunc(Type::tindex, "_aaApply"); + fdapply = FuncDeclaration::genCfunc(Type::tindex, "_aaApply", + Type::tvoid->arrayOf(), Type::tsize_t, flde->type); // flde->type is not generic); ec = new VarExp(0, fdapply); - args = new Array(); + args = new Expressions(); args->push(aggr); - args->push(new IntegerExp(0, taa->key->size(), Type::tint32)); + size_t keysize = taa->key->size(); + keysize = (keysize + 3) & ~3; + args->push(new IntegerExp(0, keysize, Type::tsize_t)); args->push(flde); e = new CallExp(loc, ec, args); e->type = Type::tindex; // don't run semantic() on e @@ -916,10 +1129,11 @@ } int j = sprintf(fdname, "_aApply%.*s%d", 2, fntab[flag], dim); assert(j < sizeof(fdname)); - fdapply = FuncDeclaration::genCfunc(Type::tindex, fdname); + fdapply = FuncDeclaration::genCfunc(Type::tindex, fdname, + Type::tvoid->arrayOf(), flde->type); // flde->type is not generic ec = new VarExp(0, fdapply); - args = new Array(); + args = new Expressions(); if (tab->ty == Tsarray) aggr = aggr->castTo(tn->arrayOf()); args->push(aggr); @@ -933,12 +1147,12 @@ * aggr.apply(flde) */ ec = new DotIdExp(loc, aggr, Id::apply); - args = new Array(); + args = new Expressions(); args->push(flde); e = new CallExp(loc, ec, args); e = e->semantic(sc); if (e->type != Type::tint32) - error("apply() function for %s must return an int", tab->toChars()); + error("opApply() function for %s must return an int", tab->toChars()); } if (!cases.dim) @@ -947,7 +1161,7 @@ else { // Construct a switch statement around the return value // of the apply function. - Array *a = new Array(); + Statements *a = new Statements(); // default: break; takes care of cases 0 and 1 s = new BreakStatement(0, NULL); @@ -1000,22 +1214,58 @@ return TRUE; } +void ForeachStatement::toCBuffer(OutBuffer *buf, HdrGenState *hgs) +{ + buf->writestring("foreach ("); + int i; + for (int i = 0; i < arguments->dim; i++) + { + Argument *a = (Argument *)arguments->data[i]; + if (i) + buf->writestring(", "); + if (a->inout == InOut) + buf->writestring("inout "); + if (a->type) + a->type->toCBuffer(buf, a->ident, hgs); + else + buf->writestring(a->ident->toChars()); + } + buf->writestring("; "); + aggr->toCBuffer(buf, hgs); + buf->writebyte(')'); + buf->writenl(); + buf->writebyte('{'); + buf->writenl(); + if (body) + body->toCBuffer(buf, hgs); + buf->writebyte('}'); + buf->writenl(); +} + /******************************** IfStatement ***************************/ -IfStatement::IfStatement(Loc loc, Expression *condition, Statement *ifbody, Statement *elsebody) +IfStatement::IfStatement(Loc loc, Argument *arg, Expression *condition, Statement *ifbody, Statement *elsebody) : Statement(loc) { + this->arg = arg; this->condition = condition; this->ifbody = ifbody; this->elsebody = elsebody; + this->match = NULL; } Statement *IfStatement::syntaxCopy() { + Statement *i = NULL; + if (ifbody) + i = ifbody->syntaxCopy(); + Statement *e = NULL; if (elsebody) e = elsebody->syntaxCopy(); - IfStatement *s = new IfStatement(loc, condition->syntaxCopy(), ifbody->syntaxCopy(), e); + + Argument *a = arg ? arg->syntaxCopy() : NULL; + IfStatement *s = new IfStatement(loc, a, condition->syntaxCopy(), i, e); return s; } @@ -1034,7 +1284,35 @@ unsigned cs0 = sc->callSuper; unsigned cs1; - ifbody = ifbody->semanticScope(sc, NULL, NULL); + Scope *scd; + if (arg) + { /* Declare arg, which we will set to be the + * result of condition. + */ + ScopeDsymbol *sym = new ScopeDsymbol(); + sym->parent = sc->scopesym; + scd = sc->push(sym); + + Type *t = arg->type ? arg->type : condition->type; + match = new VarDeclaration(loc, t, arg->ident, NULL); + match->noauto = 1; + match->semantic(scd); + if (!scd->insert(match)) + assert(0); + match->parent = sc->func; + + /* Generate: + * (arg = condition) + */ + VarExp *v = new VarExp(0, match); + condition = new AssignExp(loc, v, condition); + condition = condition->semantic(scd); + } + else + scd = sc->push(); + ifbody = ifbody->semantic(scd); + scd->pop(); + cs1 = sc->callSuper; sc->callSuper = cs0; if (elsebody) @@ -1058,10 +1336,26 @@ } -void IfStatement::toCBuffer(OutBuffer *buf) +void IfStatement::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { - buf->printf("IfStatement::toCBuffer()"); + buf->writestring("if ("); + if (arg) + { + if (arg->type) + arg->type->toCBuffer(buf, arg->ident, hgs); + else + buf->writestring(arg->ident->toChars()); + buf->writebyte(';'); + } + condition->toCBuffer(buf, hgs); + buf->writebyte(')'); buf->writenl(); + ifbody->toCBuffer(buf, hgs); + if (elsebody) + { buf->writestring("else"); + buf->writenl(); + elsebody->toCBuffer(buf, hgs); + } } /******************************** ConditionalStatement ***************************/ @@ -1109,18 +1403,25 @@ return (ifbody && ifbody->usesEH()) || (elsebody && elsebody->usesEH()); } -void ConditionalStatement::toCBuffer(OutBuffer *buf) +void ConditionalStatement::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { - condition->toCBuffer(buf); + condition->toCBuffer(buf, hgs); buf->writenl(); - buf->printf("ConditionalStatement::toCBuffer()"); + if (ifbody) + ifbody->toCBuffer(buf, hgs); + if (elsebody) + { + buf->writestring("else"); + buf->writenl(); + elsebody->toCBuffer(buf, hgs); + } buf->writenl(); } /******************************** PragmaStatement ***************************/ -PragmaStatement::PragmaStatement(Loc loc, Identifier *ident, Array *args, Statement *body) +PragmaStatement::PragmaStatement(Loc loc, Identifier *ident, Expressions *args, Statement *body) : Statement(loc) { this->ident = ident; @@ -1152,12 +1453,12 @@ if (e->op == TOKstring) { StringExp *se = (StringExp *)e; - fprintf(stderr, "%.*s", se->len, se->string); + fprintf(stdmsg, "%.*s", se->len, se->string); } else error("string expected for message, not '%s'", e->toChars()); } - fprintf(stderr, "\n"); + fprintf(stdmsg, "\n"); } } else if (ident == Id::lib) @@ -1196,7 +1497,7 @@ return TRUE; } -void PragmaStatement::toCBuffer(OutBuffer *buf) +void PragmaStatement::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { buf->printf("PragmaStatement::toCBuffer()"); buf->writenl(); @@ -1223,9 +1524,9 @@ return NULL; } -void StaticAssertStatement::toCBuffer(OutBuffer *buf) +void StaticAssertStatement::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { - sa->toCBuffer(buf); + sa->toCBuffer(buf, hgs); } @@ -1310,12 +1611,12 @@ if (!sc->sw->sdefault) { if (global.params.warnings) - { fprintf(stderr, "warning - "); + { fprintf(stdmsg, "warning - "); error("switch statement has no default"); } // Generate runtime error if the default is hit - Array *a = new Array(); + Statements *a = new Statements(); CompoundStatement *cs; Statement *s; @@ -1355,6 +1656,28 @@ return TRUE; } +void SwitchStatement::toCBuffer(OutBuffer *buf, HdrGenState *hgs) +{ + buf->writestring("switch ("); + condition->toCBuffer(buf, hgs); + buf->writebyte(')'); + buf->writenl(); + if (body) + { + if (!body->isScopeStatement()) + { buf->writebyte('{'); + buf->writenl(); + body->toCBuffer(buf, hgs); + buf->writebyte('}'); + buf->writenl(); + } + else + { + body->toCBuffer(buf, hgs); + } + } +} + /******************************** CaseStatement ***************************/ CaseStatement::CaseStatement(Loc loc, Expression *exp, Statement *s) @@ -1440,13 +1763,24 @@ return TRUE; } +void CaseStatement::toCBuffer(OutBuffer *buf, HdrGenState *hgs) +{ + buf->writestring("case "); + exp->toCBuffer(buf, hgs); + buf->writebyte(':'); + buf->writenl(); + statement->toCBuffer(buf, hgs); +} + /******************************** DefaultStatement ***************************/ DefaultStatement::DefaultStatement(Loc loc, Statement *s) : Statement(loc) { this->statement = s; +#if IN_GCC cblock = NULL; +#endif } Statement *DefaultStatement::syntaxCopy() @@ -1486,6 +1820,12 @@ return TRUE; } +void DefaultStatement::toCBuffer(OutBuffer *buf, HdrGenState *hgs) +{ + buf->writestring("default:\n"); + statement->toCBuffer(buf, hgs); +} + /******************************** GotoDefaultStatement ***************************/ GotoDefaultStatement::GotoDefaultStatement(Loc loc) @@ -1513,6 +1853,11 @@ return FALSE; } +void GotoDefaultStatement::toCBuffer(OutBuffer *buf, HdrGenState *hgs) +{ + buf->writestring("goto default;\n"); +} + /******************************** GotoCaseStatement ***************************/ GotoCaseStatement::GotoCaseStatement(Loc loc, Expression *exp) @@ -1553,6 +1898,17 @@ return FALSE; } +void GotoCaseStatement::toCBuffer(OutBuffer *buf, HdrGenState *hgs) +{ + buf->writestring("goto case"); + if (exp) + { buf->writebyte(' '); + exp->toCBuffer(buf, hgs); + } + buf->writebyte(';'); + buf->writenl(); +} + /******************************** SwitchErrorStatement ***************************/ SwitchErrorStatement::SwitchErrorStatement(Loc loc) @@ -1565,6 +1921,12 @@ return FALSE; } +void SwitchErrorStatement::toCBuffer(OutBuffer *buf, HdrGenState *hgs) +{ + buf->writestring("SwitchErrorStatement::toCBuffer()"); + buf->writenl(); +} + /******************************** ReturnStatement ***************************/ ReturnStatement::ReturnStatement(Loc loc, Expression *exp) @@ -1584,11 +1946,18 @@ Statement *ReturnStatement::semantic(Scope *sc) { + //printf("ReturnStatement::semantic()\n"); + FuncDeclaration *fd = sc->parent->isFuncDeclaration(); FuncDeclaration *fdx = fd; Type *tret = fd->type->next; + if (fd->tintro) + tret = fd->tintro->next; Type *tbret = tret->toBasetype(); + if (!exp && tbret->ty == Tvoid && fd->isMain()) + exp = new IntegerExp(0); + Scope *scx = sc; if (sc->fes) { @@ -1604,10 +1973,12 @@ } } + tret = fdx->type->next; + if (exp) { exp = exp->semantic(sc); exp = resolveProperties(sc, exp); - exp = exp->implicitCastTo(fdx->type->next); + exp = exp->implicitCastTo(tret); } if (!exp || exp->op == TOKint64 || exp->op == TOKfloat64 || exp->op == TOKimaginary80 || exp->op == TOKcomplex80 || @@ -1687,7 +2058,6 @@ if (tbret->ty != Tvoid) exp = exp->implicitCastTo(tret); } - exp = exp->optimize(WANTvalue); //exp->dump(0); //exp->print(); exp->checkEscape(); @@ -1717,16 +2087,17 @@ if (exp) { Statement *s; - s = new ExpStatement(loc, exp); + s = new ExpStatement(0, exp); return new CompoundStatement(loc, s, gs); } return gs; } - if (exp && tbret->ty == Tvoid) + if (exp && tbret->ty == Tvoid && !fd->isMain()) { Statement *s; s = new ExpStatement(loc, exp); + loc = 0; exp = NULL; return new CompoundStatement(loc, s, this); } @@ -1739,11 +2110,11 @@ return FALSE; } -void ReturnStatement::toCBuffer(OutBuffer *buf) +void ReturnStatement::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { buf->printf("return "); if (exp) - exp->toCBuffer(buf); + exp->toCBuffer(buf, hgs); buf->writeByte(';'); buf->writenl(); } @@ -1825,6 +2196,17 @@ return FALSE; } +void BreakStatement::toCBuffer(OutBuffer *buf, HdrGenState *hgs) +{ + buf->writestring("break"); + if (ident) + { buf->writebyte(' '); + buf->writestring(ident->toChars()); + } + buf->writebyte(';'); + buf->writenl(); +} + /******************************** ContinueStatement ***************************/ ContinueStatement::ContinueStatement(Loc loc, Identifier *ident) @@ -1841,6 +2223,7 @@ Statement *ContinueStatement::semantic(Scope *sc) { + //printf("ContinueStatement::semantic() %p\n", this); if (ident) { Scope *scx; @@ -1854,6 +2237,16 @@ { if (sc->fes) // if this is the body of a foreach { + for (; scx; scx = scx->enclosing) + { + ls = scx->slabel; + if (ls && ls->ident == ident && ls->statement == sc->fes) + { + // Replace continue ident; with return 0; + return new ReturnStatement(0, new IntegerExp(0)); + } + } + /* Post this statement to the fes, and replace * it with a return value that caller will put into * a switch. Caller will figure out where the break @@ -1902,6 +2295,17 @@ return FALSE; } +void ContinueStatement::toCBuffer(OutBuffer *buf, HdrGenState *hgs) +{ + buf->writestring("continue"); + if (ident) + { buf->writebyte(' '); + buf->writestring(ident->toChars()); + } + buf->writebyte(';'); + buf->writenl(); +} + /******************************** SynchronizedStatement ***************************/ SynchronizedStatement::SynchronizedStatement(Loc loc, Expression *exp, Statement *body) @@ -1969,6 +2373,21 @@ return body->fallOffEnd(); } +void SynchronizedStatement::toCBuffer(OutBuffer *buf, HdrGenState *hgs) +{ + buf->writestring("synchronized"); + if (exp) + { buf->writebyte('('); + exp->toCBuffer(buf, hgs); + buf->writebyte(')'); + } + if (body) + { + buf->writebyte(' '); + body->toCBuffer(buf, hgs); + } +} + /******************************** WithStatement ***************************/ WithStatement::WithStatement(Loc loc, Expression *exp, Statement *body) @@ -2033,13 +2452,12 @@ return this; } -void WithStatement::toCBuffer(OutBuffer *buf) +void WithStatement::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { buf->writestring("with ("); - exp->toCBuffer(buf); - buf->writestring(")\n{\n"); - body->toCBuffer(buf); - buf->writestring("\n}\n"); + exp->toCBuffer(buf, hgs); + buf->writestring(")\n"); + body->toCBuffer(buf, hgs); } int WithStatement::usesEH() @@ -2125,6 +2543,20 @@ return result; } +void TryCatchStatement::toCBuffer(OutBuffer *buf, HdrGenState *hgs) +{ + buf->writestring("try"); + buf->writenl(); + if (body) + body->toCBuffer(buf, hgs); + int i; + for (i = 0; i < catches->dim; i++) + { + Catch *c = (Catch *)catches->data[i]; + c->toCBuffer(buf, hgs); + } +} + /******************************** Catch ***************************/ Catch::Catch(Loc loc, Type *t, Identifier *id, Statement *handler) @@ -2184,7 +2616,23 @@ sc->pop(); } -/******************************** TryFinallyStatement ***************************/ +void Catch::toCBuffer(OutBuffer *buf, HdrGenState *hgs) +{ + buf->writestring("catch"); + if (type) + { buf->writebyte('('); + type->toCBuffer(buf, ident, hgs); + buf->writebyte(')'); + } + buf->writenl(); + buf->writebyte('{'); + buf->writenl(); + handler->toCBuffer(buf, hgs); + buf->writebyte('}'); + buf->writenl(); +} + +/****************************** TryFinallyStatement ***************************/ TryFinallyStatement::TryFinallyStatement(Loc loc, Statement *body, Statement *finalbody) : Statement(loc) @@ -2212,12 +2660,12 @@ return this; } -void TryFinallyStatement::toCBuffer(OutBuffer *buf) +void TryFinallyStatement::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { buf->printf("try\n{\n"); - body->toCBuffer(buf); + body->toCBuffer(buf, hgs); buf->printf("}\nfinally\n{\n"); - finalbody->toCBuffer(buf); + finalbody->toCBuffer(buf, hgs); buf->writeByte('}'); buf->writenl(); } @@ -2241,11 +2689,94 @@ { int result; result = body->fallOffEnd(); - if (finalbody) - result = finalbody->fallOffEnd(); +// if (finalbody) +// result = finalbody->fallOffEnd(); return result; } +/****************************** OnScopeStatement ***************************/ + +OnScopeStatement::OnScopeStatement(Loc loc, TOK tok, Statement *statement) + : Statement(loc) +{ + this->tok = tok; + this->statement = statement; +} + +Statement *OnScopeStatement::syntaxCopy() +{ + OnScopeStatement *s = new OnScopeStatement(loc, + tok, statement->syntaxCopy()); + return s; +} + +Statement *OnScopeStatement::semantic(Scope *sc) +{ + /* semantic is called on results of scopeCode() */ + return this; +} + +void OnScopeStatement::toCBuffer(OutBuffer *buf, HdrGenState *hgs) +{ + buf->writestring(Token::toChars(tok)); + buf->writebyte(' '); + statement->toCBuffer(buf, hgs); +} + +int OnScopeStatement::usesEH() +{ + return (tok != TOKon_scope_success); +} + +void OnScopeStatement::scopeCode(Statement **sentry, Statement **sexception, Statement **sfinally) +{ + //printf("OnScopeStatement::scopeCode()\n"); + //print(); + *sentry = NULL; + *sexception = NULL; + *sfinally = NULL; + switch (tok) + { + case TOKon_scope_exit: + *sfinally = statement; + break; + + case TOKon_scope_failure: + *sexception = statement; + break; + + case TOKon_scope_success: + { + /* Create: + * sentry: int x = 0; + * sexception: x = 1; + * sfinally: if (!x) statement; + */ + char name[5 + sizeof(int) * 3 + 1]; + static int num; + sprintf(name, "__osf%d", ++num); + Identifier *id = Lexer::idPool(name); + + ExpInitializer *ie = new ExpInitializer(loc, new IntegerExp(0)); + VarDeclaration *v = new VarDeclaration(loc, Type::tint32, id, ie); + *sentry = new DeclarationStatement(loc, v); + + Expression *e = new IntegerExp(1); + e = new AssignExp(0, new VarExp(0, v), e); + *sexception = new ExpStatement(0, e); + + e = new VarExp(0, v); + e = new NotExp(0, e); + *sfinally = new IfStatement(0, NULL, e, statement, NULL); + + break; + } + + default: + assert(0); + } +} + /******************************** ThrowStatement ***************************/ ThrowStatement::ThrowStatement(Loc loc, Expression *exp) @@ -2277,10 +2808,10 @@ return FALSE; } -void ThrowStatement::toCBuffer(OutBuffer *buf) +void ThrowStatement::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { buf->printf("throw "); - exp->toCBuffer(buf); + exp->toCBuffer(buf, hgs); buf->writeByte(';'); buf->writenl(); } @@ -2295,7 +2826,8 @@ Statement *VolatileStatement::syntaxCopy() { - VolatileStatement *s = new VolatileStatement(loc, statement); + VolatileStatement *s = new VolatileStatement(loc, + statement ? statement->syntaxCopy() : NULL); return s; } @@ -2305,9 +2837,9 @@ return this; } -Array *VolatileStatement::flatten() +Statements *VolatileStatement::flatten() { - Array *a; + Statements *a; a = statement->flatten(); if (a) @@ -2327,6 +2859,17 @@ return statement->fallOffEnd(); } +void VolatileStatement::toCBuffer(OutBuffer *buf, HdrGenState *hgs) +{ + buf->writestring("volatile"); + if (statement) + { if (statement->isScopeStatement()) + buf->writenl(); + else + buf->writebyte(' '); + statement->toCBuffer(buf, hgs); + } +} /******************************** GotoStatement ***************************/ @@ -2359,7 +2902,7 @@ * so we can patch it later, and add it to a 'look at this later' * list. */ - Array *a = new Array(); + Statements *a = new Statements(); Statement *s; a->push(this); @@ -2377,6 +2920,14 @@ return FALSE; } +void GotoStatement::toCBuffer(OutBuffer *buf, HdrGenState *hgs) +{ + buf->writestring("goto "); + buf->writestring(ident->toChars()); + buf->writebyte(';'); + buf->writenl(); +} + /******************************** LabelStatement ***************************/ LabelStatement::LabelStatement(Loc loc, Identifier *ident, Statement *statement) @@ -2415,9 +2966,9 @@ return this; } -Array *LabelStatement::flatten() +Statements *LabelStatement::flatten() { - Array *a; + Statements *a; a = statement->flatten(); if (a) @@ -2451,6 +3002,15 @@ return TRUE; } +void LabelStatement::toCBuffer(OutBuffer *buf, HdrGenState *hgs) +{ + buf->writestring(ident->toChars()); + buf->writebyte(':'); + buf->writenl(); + if (statement) + statement->toCBuffer(buf, hgs); +} + /******************************** LabelDsymbol ***************************/ @@ -2458,7 +3018,9 @@ : Dsymbol(ident) { statement = NULL; +#if IN_GCC asmLabelNum = 0; +#endif } LabelDsymbol *LabelDsymbol::isLabel() // is this a LabelDsymbol()? diff -uNr gdc-0.17/d/dmd/statement.h gdc-0.18/d/dmd/statement.h --- gdc-0.17/d/dmd/statement.h 2005-08-12 05:36:58.000000000 +0200 +++ gdc-0.18/d/dmd/statement.h 2006-05-13 21:05:42.000000000 +0200 @@ -1,5 +1,5 @@ -// Copyright (c) 1999-2002 by Digital Mars +// Copyright (c) 1999-2006 by Digital Mars // All Rights Reserved // written by Walter Bright // www.digitalmars.com @@ -7,12 +7,6 @@ // in artistic.txt, or the GNU General Public License in gnu.txt. // See the included readme.txt for details. -/* NOTE: This file has been patched from the original DMD distribution to - work with the GDC compiler. - - Modified by David Friedman, September 2004 -*/ - #ifndef DMD_STATEMENT_H #define DMD_STATEMENT_H @@ -22,6 +16,7 @@ #include "root.h" +#include "arraytypes.h" #include "dsymbol.h" struct OutBuffer; @@ -42,12 +37,22 @@ struct CompoundStatement; struct Argument; struct StaticAssert; +struct AsmStatement; +struct GotoStatement; +struct ScopeStatement; +struct TryCatchStatement; +struct HdrGenState; // Back end struct IRState; struct Blockx; +#if IN_GCC union tree_node; typedef union tree_node block; union tree_node; typedef union tree_node elem; +#else +struct block; +struct elem; +#endif struct code; struct Statement : Object @@ -61,7 +66,14 @@ char *toChars(); void error(const char *format, ...); - virtual void toCBuffer(OutBuffer *buf); + virtual void toCBuffer(OutBuffer *buf, HdrGenState *hgs); + virtual TryCatchStatement *isTryCatchStatement() { return NULL; } + virtual GotoStatement *isGotoStatement() { return NULL; } + virtual AsmStatement *isAsmStatement() { return NULL; } +#ifdef _DH + int incontract; +#endif + virtual ScopeStatement *isScopeStatement() { return NULL; } virtual Statement *semantic(Scope *sc); Statement *semanticScope(Scope *sc, Statement *sbreak, Statement *scontinue); virtual int hasBreak(); @@ -69,8 +81,8 @@ virtual int usesEH(); virtual int fallOffEnd(); virtual int comeFrom(); - virtual Statement *callAutoDtor(); - virtual Array *flatten(); + virtual void scopeCode(Statement **sentry, Statement **sexit, Statement **sfinally); + virtual Statements *flatten(); virtual int inlineCost(InlineCostState *ics); virtual Expression *doInline(InlineDoState *ids); @@ -91,7 +103,7 @@ ExpStatement(Loc loc, Expression *exp); Statement *syntaxCopy(); - void toCBuffer(OutBuffer *buf); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); Statement *semantic(Scope *sc); int fallOffEnd(); @@ -110,24 +122,24 @@ DeclarationStatement(Loc loc, Dsymbol *s); DeclarationStatement(Loc loc, Expression *exp); Statement *syntaxCopy(); - void toCBuffer(OutBuffer *buf); - Statement *callAutoDtor(); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); + void scopeCode(Statement **sentry, Statement **sexit, Statement **sfinally); DeclarationStatement *isDeclarationStatement() { return this; } }; struct CompoundStatement : Statement { - Array *statements; + Statements *statements; - CompoundStatement(Loc loc, Array *s); + CompoundStatement(Loc loc, Statements *s); CompoundStatement(Loc loc, Statement *s1, Statement *s2); Statement *syntaxCopy(); - void toCBuffer(OutBuffer *buf); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); Statement *semantic(Scope *sc); int usesEH(); int fallOffEnd(); - Array *flatten(); + Statements *flatten(); ReturnStatement *isReturnStatement(); int inlineCost(InlineCostState *ics); @@ -144,10 +156,10 @@ struct BlockStatement : CompoundStatement { - BlockStatement(Loc loc, Array *s); + BlockStatement(Loc loc, Statements *s); BlockStatement(Loc loc, Statement *s1, Statement *s2); Statement *syntaxCopy(); - void toCBuffer(OutBuffer *buf); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); Statement *semantic(Scope *sc); void toIR(IRState *irs); @@ -160,7 +172,8 @@ ScopeStatement(Loc loc, Statement *s); Statement *syntaxCopy(); - void toCBuffer(OutBuffer *buf); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); + ScopeStatement *isScopeStatement() { return this; } Statement *semantic(Scope *sc); int fallOffEnd(); @@ -181,6 +194,7 @@ int hasContinue(); int usesEH(); int fallOffEnd(); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); Statement *inlineScan(InlineScanState *iss); @@ -199,6 +213,7 @@ int hasContinue(); int usesEH(); int fallOffEnd(); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); Statement *inlineScan(InlineScanState *iss); @@ -219,6 +234,7 @@ int hasContinue(); int usesEH(); int fallOffEnd(); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); Statement *inlineScan(InlineScanState *iss); @@ -234,6 +250,8 @@ VarDeclaration *key; VarDeclaration *value; + FuncDeclaration *func; // function we're lexically in + Array cases; // put breaks, continues, gotos and returns here Array gotos; // forward referenced goto's go here @@ -244,6 +262,7 @@ int hasContinue(); int usesEH(); int fallOffEnd(); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); Statement *inlineScan(InlineScanState *iss); @@ -252,14 +271,17 @@ struct IfStatement : Statement { + Argument *arg; Expression *condition; Statement *ifbody; Statement *elsebody; - IfStatement(Loc loc, Expression *condition, Statement *ifbody, Statement *elsebody); + VarDeclaration *match; // for MatchExpression results + + IfStatement(Loc loc, Argument *arg, Expression *condition, Statement *ifbody, Statement *elsebody); Statement *syntaxCopy(); Statement *semantic(Scope *sc); - void toCBuffer(OutBuffer *buf); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); int usesEH(); int fallOffEnd(); @@ -281,22 +303,22 @@ Statement *semantic(Scope *sc); int usesEH(); - void toCBuffer(OutBuffer *buf); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); }; struct PragmaStatement : Statement { Identifier *ident; - Array *args; // array of Expression's + Expressions *args; // array of Expression's Statement *body; - PragmaStatement(Loc loc, Identifier *ident, Array *args, Statement *body); + PragmaStatement(Loc loc, Identifier *ident, Expressions *args, Statement *body); Statement *syntaxCopy(); Statement *semantic(Scope *sc); int usesEH(); int fallOffEnd(); - void toCBuffer(OutBuffer *buf); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); }; struct StaticAssertStatement : Statement @@ -307,7 +329,7 @@ Statement *syntaxCopy(); Statement *semantic(Scope *sc); - void toCBuffer(OutBuffer *buf); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); }; struct SwitchStatement : Statement @@ -325,6 +347,7 @@ int hasBreak(); int usesEH(); int fallOffEnd(); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); Statement *inlineScan(InlineScanState *iss); @@ -345,6 +368,7 @@ int usesEH(); int fallOffEnd(); int comeFrom(); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); Statement *inlineScan(InlineScanState *iss); @@ -354,7 +378,9 @@ struct DefaultStatement : Statement { Statement *statement; +#if IN_GCC block *cblock; // back end: label for the block +#endif DefaultStatement(Loc loc, Statement *s); Statement *syntaxCopy(); @@ -362,6 +388,7 @@ int usesEH(); int fallOffEnd(); int comeFrom(); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); Statement *inlineScan(InlineScanState *iss); @@ -376,6 +403,7 @@ Statement *syntaxCopy(); Statement *semantic(Scope *sc); int fallOffEnd(); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); void toIR(IRState *irs); }; @@ -389,6 +417,7 @@ Statement *syntaxCopy(); Statement *semantic(Scope *sc); int fallOffEnd(); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); void toIR(IRState *irs); }; @@ -397,6 +426,7 @@ { SwitchErrorStatement(Loc loc); int fallOffEnd(); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); void toIR(IRState *irs); }; @@ -407,7 +437,7 @@ ReturnStatement(Loc loc, Expression *exp); Statement *syntaxCopy(); - void toCBuffer(OutBuffer *buf); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); Statement *semantic(Scope *sc); int fallOffEnd(); @@ -428,6 +458,7 @@ Statement *syntaxCopy(); Statement *semantic(Scope *sc); int fallOffEnd(); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); void toIR(IRState *irs); }; @@ -440,6 +471,7 @@ Statement *syntaxCopy(); Statement *semantic(Scope *sc); int fallOffEnd(); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); void toIR(IRState *irs); }; @@ -456,6 +488,7 @@ int hasContinue(); int usesEH(); int fallOffEnd(); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); Statement *inlineScan(InlineScanState *iss); @@ -474,7 +507,7 @@ WithStatement(Loc loc, Expression *exp, Statement *body); Statement *syntaxCopy(); Statement *semantic(Scope *sc); - void toCBuffer(OutBuffer *buf); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); int usesEH(); int fallOffEnd(); @@ -498,6 +531,8 @@ Statement *inlineScan(InlineScanState *iss); void toIR(IRState *irs); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); + TryCatchStatement *isTryCatchStatement() { return this; } }; struct Catch : Object @@ -511,6 +546,7 @@ Catch(Loc loc, Type *t, Identifier *id, Statement *handler); Catch *syntaxCopy(); void semantic(Scope *sc); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); }; struct TryFinallyStatement : Statement @@ -520,7 +556,7 @@ TryFinallyStatement(Loc loc, Statement *body, Statement *finalbody); Statement *syntaxCopy(); - void toCBuffer(OutBuffer *buf); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); Statement *semantic(Scope *sc); int hasBreak(); int hasContinue(); @@ -532,6 +568,21 @@ void toIR(IRState *irs); }; +struct OnScopeStatement : Statement +{ + TOK tok; + Statement *statement; + + OnScopeStatement(Loc loc, TOK tok, Statement *statement); + Statement *syntaxCopy(); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); + Statement *semantic(Scope *sc); + int usesEH(); + void scopeCode(Statement **sentry, Statement **sexit, Statement **sfinally); + + void toIR(IRState *irs); +}; + struct ThrowStatement : Statement { Expression *exp; @@ -539,7 +590,7 @@ ThrowStatement(Loc loc, Expression *exp); Statement *syntaxCopy(); Statement *semantic(Scope *sc); - void toCBuffer(OutBuffer *buf); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); int fallOffEnd(); Statement *inlineScan(InlineScanState *iss); @@ -554,8 +605,9 @@ VolatileStatement(Loc loc, Statement *statement); Statement *syntaxCopy(); Statement *semantic(Scope *sc); - Array *flatten(); + Statements *flatten(); int fallOffEnd(); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); Statement *inlineScan(InlineScanState *iss); @@ -574,6 +626,8 @@ int fallOffEnd(); void toIR(IRState *irs); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); + GotoStatement *isGotoStatement() { return this; } }; struct LabelStatement : Statement @@ -587,10 +641,11 @@ LabelStatement(Loc loc, Identifier *ident, Statement *statement); Statement *syntaxCopy(); Statement *semantic(Scope *sc); - Array *flatten(); + Statements *flatten(); int usesEH(); int fallOffEnd(); int comeFrom(); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); Statement *inlineScan(InlineScanState *iss); @@ -600,7 +655,9 @@ struct LabelDsymbol : Dsymbol { LabelStatement *statement; +#if IN_GCC unsigned asmLabelNum; // GCC-specific +#endif LabelDsymbol(Identifier *ident); LabelDsymbol *isLabel(); @@ -620,7 +677,8 @@ Statement *semantic(Scope *sc); int comeFrom(); - void toCBuffer(OutBuffer *buf); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); + virtual AsmStatement *isAsmStatement() { return this; } void toIR(IRState *irs); }; diff -uNr gdc-0.17/d/dmd/staticassert.c gdc-0.18/d/dmd/staticassert.c --- gdc-0.17/d/dmd/staticassert.c 2005-05-29 23:09:19.000000000 +0200 +++ gdc-0.18/d/dmd/staticassert.c 2006-05-14 03:05:56.000000000 +0200 @@ -1,5 +1,5 @@ -// Copyright (c) 1999-2003 by Digital Mars +// Copyright (c) 1999-2006 by Digital Mars // All Rights Reserved // written by Walter Bright // www.digitalmars.com @@ -33,8 +33,9 @@ return sa; } -void StaticAssert::addMember(Scope *sc, ScopeDsymbol *sd) +int StaticAssert::addMember(Scope *sc, ScopeDsymbol *sd, int memnum) { + return 0; // we didn't add anything } void StaticAssert::semantic(Scope *sc) @@ -46,9 +47,21 @@ Expression *e; e = exp->semantic(sc); - e = e->constFold(); + e = e->optimize(WANTvalue); if (e->isBool(FALSE)) error("(%s) is false", exp->toChars()); + else if (!e->isBool(TRUE)) + { + error("(%s) is not evaluatable at compile time", exp->toChars()); +printf("%s\n", e->toChars()); + } +} + +int StaticAssert::oneMember(Dsymbol **ps) +{ + //printf("StaticAssert::oneMember())\n"); + *ps = NULL; + return TRUE; } void StaticAssert::inlineScan() @@ -64,11 +77,11 @@ return "static assert"; } -void StaticAssert::toCBuffer(OutBuffer *buf) +void StaticAssert::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { buf->writestring(kind()); buf->writeByte('('); - exp->toCBuffer(buf); + exp->toCBuffer(buf, hgs); buf->writestring(");"); buf->writenl(); } diff -uNr gdc-0.17/d/dmd/staticassert.h gdc-0.18/d/dmd/staticassert.h --- gdc-0.17/d/dmd/staticassert.h 2005-05-29 23:09:19.000000000 +0200 +++ gdc-0.18/d/dmd/staticassert.h 2006-04-16 17:13:30.000000000 +0200 @@ -1,5 +1,5 @@ -// Copyright (c) 1999-2003 by Digital Mars +// Copyright (c) 1999-2006 by Digital Mars // All Rights Reserved // written by Walter Bright // www.digitalmars.com @@ -17,6 +17,9 @@ #include "dsymbol.h" struct Expression; +#ifdef _DH +struct HdrGenState; +#endif struct StaticAssert : Dsymbol { @@ -25,13 +28,14 @@ StaticAssert(Loc loc, Expression *exp); Dsymbol *syntaxCopy(Dsymbol *s); - void addMember(Scope *sc, ScopeDsymbol *sd); + int addMember(Scope *sc, ScopeDsymbol *sd, int memnum); void semantic(Scope *sc); void semantic2(Scope *sc); void inlineScan(); + int oneMember(Dsymbol **ps); void toObjFile(); char *kind(); - void toCBuffer(OutBuffer *buf); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); }; #endif diff -uNr gdc-0.17/d/dmd/struct.c gdc-0.18/d/dmd/struct.c --- gdc-0.17/d/dmd/struct.c 2005-10-13 03:06:51.000000000 +0200 +++ gdc-0.18/d/dmd/struct.c 2006-05-13 21:05:42.000000000 +0200 @@ -254,7 +254,7 @@ { Dsymbol *s = (Dsymbol *)members->data[i]; //printf("adding member '%s' to '%s'\n", s->toChars(), this->toChars()); - s->addMember(sc, this); + s->addMember(sc, this, 1); } } @@ -317,7 +317,7 @@ FuncDeclaration *fdptr = new FuncDeclaration(loc, loc, fdx->ident, STCundefined, tfeqptr); Expression *e = new IdentifierExp(loc, Id::p); e = new PtrExp(loc, e); - Array *args = new Array(); + Expressions *args = new Expressions(); args->push(e); e = new IdentifierExp(loc, id); e = new CallExp(loc, e, args); @@ -325,7 +325,7 @@ ScopeDsymbol *s = fdx->parent->isScopeDsymbol(); assert(s); s->members->push(fdptr); - fdptr->addMember(sc, s); + fdptr->addMember(sc, s, 1); fdptr->semantic(sc2); } } @@ -405,10 +405,12 @@ } } -void StructDeclaration::toCBuffer(OutBuffer *buf) +void StructDeclaration::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { int i; - buf->printf("%s %s", kind(), toChars()); + buf->printf("%s ", kind()); + if (!isAnonymous()) + buf->writestring(toChars()); if (!members) { buf->writeByte(';'); @@ -423,7 +425,7 @@ Dsymbol *s = (Dsymbol *)members->data[i]; buf->writestring(" "); - s->toCBuffer(buf); + s->toCBuffer(buf, hgs); } buf->writeByte('}'); buf->writenl(); diff -uNr gdc-0.17/d/dmd/template.c gdc-0.18/d/dmd/template.c --- gdc-0.17/d/dmd/template.c 2005-11-28 05:17:52.000000000 +0100 +++ gdc-0.18/d/dmd/template.c 2006-05-13 21:05:42.000000000 +0200 @@ -1,5 +1,5 @@ -// Copyright (c) 1999-2005 by Digital Mars +// Copyright (c) 1999-2006 by Digital Mars // All Rights Reserved // written by Walter Bright // www.digitalmars.com @@ -34,6 +34,7 @@ #include "mars.h" #include "dsymbol.h" #include "identifier.h" +#include "hdrgen.h" #define LOG 0 @@ -68,7 +69,7 @@ /* ======================== TemplateDeclaration ============================= */ -TemplateDeclaration::TemplateDeclaration(Loc loc, Identifier *id, Array *parameters, Array *decldefs) +TemplateDeclaration::TemplateDeclaration(Loc loc, Identifier *id, TemplateParameters *parameters, Array *decldefs) : ScopeDsymbol(id) { #if LOG @@ -97,13 +98,13 @@ Dsymbol *TemplateDeclaration::syntaxCopy(Dsymbol *) { TemplateDeclaration *td; - Array *p; + TemplateParameters *p; Array *d; p = NULL; if (parameters) { - p = new Array(); + p = new TemplateParameters(); p->setDim(parameters->dim); for (int i = 0; i < p->dim; i++) { TemplateParameter *tp = (TemplateParameter *)parameters->data[i]; @@ -162,14 +163,16 @@ paramscope->pop(); - if (members && members->dim) + if (members) { - Dsymbol *s = (Dsymbol *)members->data[0]; - s = s->oneMember(); - if (s && s->ident && s->ident->equals(ident)) + Dsymbol *s; + if (Dsymbol::oneMembers(members, &s)) { - onemember = s; - s->parent = this; + if (s && s->ident && s->ident->equals(ident)) + { + onemember = s; + s->parent = this; + } } } @@ -257,16 +260,19 @@ dedtypes->zero(); -//printf("TemplateDeclaration::matchWithInstance(this = %p, ti = %p)\n", this, ti); -//printf("dim = %d, parameters->dim = %d\n", dim, parameters->dim); +//printf("dedtypes->dim = %d, parameters->dim = %d\n", dim, parameters->dim); //if (ti->tiargs->dim) //printf("ti->tiargs->dim = %d, [0] = %p\n", ti->tiargs->dim, ti->tiargs->data[0]); + // If more arguments than parameters, no match + if (ti->tiargs->dim > parameters->dim) + return MATCHnomatch; + assert(dim == parameters->dim); assert(dim >= ti->tiargs->dim); // Set up scope for parameters - assert(scope); + assert((size_t)scope > 0x10000); ScopeDsymbol *paramsym = new ScopeDsymbol(); paramsym->parent = scope->parent; Scope *paramscope = scope->push(paramsym); @@ -402,7 +408,8 @@ } // Temporary Array to hold deduced types - dedtypes.setDim(parameters->dim); + //dedtypes.setDim(parameters->dim); + dedtypes.setDim(td2->parameters->dim); // Attempt a type deduction if (td2->matchWithInstance(&ti, &dedtypes, 1)) @@ -418,10 +425,313 @@ return 0; } -void TemplateDeclaration::toCBuffer(OutBuffer *buf) + +/************************************************* + * Match function arguments against a specific template function. + * Input: + * targsi Expression/Type initial list of template arguments + * fargs arguments to function + * Output: + * dedargs Expression/Type deduced template arguments + */ + +MATCH TemplateDeclaration::deduceMatch(Array *targsi, Array *fargs, Array *dedargs) +{ + size_t i; + size_t nfparams; + size_t nfargs; + size_t nargsi; + MATCH match = MATCHexact; + FuncDeclaration *fd = onemember->toAlias()->isFuncDeclaration(); + TypeFunction *fdtype; + Array dedtypes; // for T:T*, the dedargs is the T*, dedtypes is the T + + assert((size_t)scope > 0x10000); + + dedargs->setDim(parameters->dim); + dedargs->zero(); + + dedtypes.setDim(parameters->dim); + dedtypes.zero(); + + // Set up scope for parameters + ScopeDsymbol *paramsym = new ScopeDsymbol(); + paramsym->parent = scope->parent; + Scope *paramscope = scope->push(paramsym); + + nargsi = 0; + if (targsi) + { // Set initial template arguments + + nargsi = targsi->dim; + if (nargsi > parameters->dim) + goto Lnomatch; + + memcpy(dedargs->data, targsi->data, nargsi * sizeof(*dedargs->data)); + + for (i = 0; i < nargsi; i++) + { Object *oarg = (Object *)dedargs->data[i]; + TemplateParameter *tp = (TemplateParameter *)parameters->data[i]; + MATCH m; + Declaration *sparam; + + m = tp->matchArg(paramscope, oarg, i, parameters, &dedtypes, &sparam); + if (m == MATCHnomatch) + goto Lnomatch; + if (m < match) + match = m; + + sparam->semantic(paramscope); + if (!paramscope->insert(sparam)) + goto Lnomatch; + } + } + + assert(fd->type->ty == Tfunction); + fdtype = (TypeFunction *)fd->type; + + nfparams = fdtype->arguments->dim; // number of function parameters + nfargs = fargs->dim; // number of function arguments + + if (nfparams == nfargs) + ; + else if (nfargs > nfparams) + { + if (fdtype->varargs == 0) + goto Lnomatch; // too many args, no match + match = MATCHconvert; // match ... with a conversion + } + + // Loop through the function parameters + for (i = 0; i < nfparams; i++) + { + Argument *fparam = (Argument *)fdtype->arguments->data[i]; + Expression *farg; + MATCH m; + + if (i >= nfargs) // if not enough arguments + { + if (fparam->defaultArg) + { /* Default arguments do not participate in template argument + * deduction. + */ + goto Lmatch; + } + } + else + { farg = (Expression *)fargs->data[i]; + m = farg->type->deduceType(scope, fparam->type, parameters, &dedtypes); + //printf("m = %d\n", m); + if (m) + { if (m < match) + match = m; // pick worst match + continue; + } + } + if (!(fdtype->varargs == 2 && i + 1 == nfparams)) + goto Lnomatch; + + /* Check for match with function parameter T... + */ + Type *t = fparam->type; + switch (t->ty) + { + // Perhaps we can do better with this, see TypeFunction::callMatch() + case Tsarray: + case Tarray: + case Tclass: + case Tident: + goto Lmatch; + + default: + goto Lnomatch; + } + } + +Lmatch: + + for (i = nargsi; i < dedargs->dim; i++) + { + TemplateParameter *tp = (TemplateParameter *)parameters->data[i]; + Object *oarg = (Object *)dedargs->data[i]; + if (!oarg) + { Object *o = (Object *)dedtypes.data[i]; + if (o) + { + if (tp->specialization()) + error("specialization not allowed for deduced parameter %s", tp->ident->toChars()); + } + else + { o = tp->defaultArg(paramscope); + if (!o) + goto Lnomatch; + } + declareParameter(paramscope, tp, o); + dedargs->data[i] = (void *)o; + } + } + + paramscope->pop(); + return match; + +Lnomatch: + paramscope->pop(); + return MATCHnomatch; +} + +/************************************************** + * Declare template parameter tp with value o. + */ + +void TemplateDeclaration::declareParameter(Scope *sc, TemplateParameter *tp, Object *o) +{ + //printf("TemplateDeclaration::declareParameter('%s')\n", tp->ident->toChars()); + + Type *targ = isType(o); + Expression *ea = isExpression(o); + Dsymbol *sa = isDsymbol(o); + Dsymbol *s; + + if (targ) + { + s = new AliasDeclaration(0, tp->ident, targ); + } + else if (sa) + { + //printf("Alias %s %s;\n", sa->ident->toChars(), tp->ident->toChars()); + s = new AliasDeclaration(0, tp->ident, sa); + } + else if (ea) + { + // tdtypes.data[i] always matches ea here + Initializer *init = new ExpInitializer(loc, ea); + TemplateValueParameter *tvp = tp->isTemplateValueParameter(); + assert(tvp); + + VarDeclaration *v = new VarDeclaration(0, tvp->valType, tp->ident, init); + v->storage_class = STCconst; + s = v; + } + else + assert(0); + if (!sc->insert(s)) + error("declaration %s is already defined", tp->ident->toChars()); + s->semantic(sc); +} + +/************************************************* + * Given function arguments, figure out which template function + * to expand, and return that function. + * If no match, give error message and return NULL. + * Input: + * targsi initial list of template arguments + * fargs arguments to function + */ + +FuncDeclaration *TemplateDeclaration::deduce(Scope *sc, Loc loc, Array *targsi, Expressions *fargs) +{ + MATCH m_best = MATCHnomatch; + TemplateDeclaration *td_ambig = NULL; + TemplateDeclaration *td_best = NULL; + Array *tdargs = new Array(); + TemplateInstance *ti; + FuncDeclaration *fd; + + for (TemplateDeclaration *td = this; td; td = td->overnext) + { + if (!td->scope) + { + error("forward reference to template"); + goto Lerror; + } + if (!td->onemember || !td->onemember->toAlias()->isFuncDeclaration()) + { + error("is not a function template"); + goto Lerror; + } + + MATCH m; + Array dedargs; + + m = td->deduceMatch(targsi, fargs, &dedargs); + if (!m) // if no match + continue; + + if (m < m_best) + goto Ltd_best; + if (m > m_best) + goto Ltd; + + { + // Disambiguate by picking the most specialized TemplateDeclaration + int c1 = td->leastAsSpecialized(td_best); + int c2 = td_best->leastAsSpecialized(td); + //printf("c1 = %d, c2 = %d\n", c1, c2); + + if (c1 && !c2) + goto Ltd; + else if (!c1 && c2) + goto Ltd_best; + else + goto Lambig; + } + + Lambig: // td_best and td are ambiguous + td_ambig = td; + continue; + + Ltd_best: // td_best is the best match so far + td_ambig = NULL; + continue; + + Ltd: // td is the new best match + td_ambig = NULL; + assert((size_t)td->scope > 0x10000); + td_best = td; + m_best = m; + tdargs->setDim(dedargs.dim); + memcpy(tdargs->data, dedargs.data, tdargs->dim * sizeof(void *)); + continue; + } + if (!td_best) + { + error(loc, "does not match any template declaration"); + goto Lerror; + } + if (td_ambig) + { + error(loc, "%s matches more than one template declaration, %s and %s", + toChars(), td_best->toChars(), td_ambig->toChars()); + } + + /* The best match is td_best with arguments tdargs. + * Now instantiate the template. + */ + assert((size_t)td_best->scope > 0x10000); + ti = new TemplateInstance(loc, td_best, tdargs); + ti->semantic(sc); + fd = ti->toAlias()->isFuncDeclaration(); + if (!fd) + goto Lerror; + return fd; + + Lerror: + { + OutBuffer buf; + HdrGenState hgs; + + argExpTypesToCBuffer(&buf, fargs, &hgs); + error(loc, "cannot deduce template function from argument types (%s)", + buf.toChars()); + return NULL; + } +} + +void TemplateDeclaration::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { int i; + buf->writestring(kind()); buf->writeByte(' '); buf->writestring(ident->toChars()); @@ -431,32 +741,65 @@ TemplateParameter *tp = (TemplateParameter *)parameters->data[i]; if (i) buf->writeByte(','); - tp->toCBuffer(buf); + tp->toCBuffer(buf, hgs); } buf->writeByte(')'); + + if (hgs->hdrgen) + { + hgs->tpltMember++; + buf->writenl(); + buf->writebyte('{'); + buf->writenl(); + for (i = 0; i < members->dim; i++) + { + Dsymbol *s = (Dsymbol *)members->data[i]; + s->toCBuffer(buf, hgs); + } + buf->writebyte('}'); + buf->writenl(); + hgs->tpltMember--; + } } char *TemplateDeclaration::toChars() -{ - OutBuffer buf; - char *s; +{ OutBuffer buf; + HdrGenState hgs; - toCBuffer(&buf); - s = buf.toChars(); - buf.data = NULL; - return s + strlen(kind()) + 1; // kludge to skip over 'template ' + memset(&hgs, 0, sizeof(hgs)); + buf.writestring(ident->toChars()); + buf.writeByte('('); + for (int i = 0; i < parameters->dim; i++) + { + TemplateParameter *tp = (TemplateParameter *)parameters->data[i]; + if (i) + buf.writeByte(','); + tp->toCBuffer(&buf, &hgs); + } + buf.writeByte(')'); + buf.writeByte(0); + return (char *)buf.extractData(); } /* ======================== Type ============================================ */ /* These form the heart of template argument deduction. - * Given 'this' being the argument to the template instance, + * Given 'this' being the type argument to the template instance, * it is matched against the template declaration parameter specialization * 'tparam' to determine the type to be used for the parameter. + * Example: + * template Foo(T:T*) // template declaration + * Foo!(int*) // template instantiation + * Input: + * this = int* + * tparam = T + * parameters = [ T:T* ] // Array of TemplateParameter's + * Output: + * dedtypes = [ int ] // Array of Expression/Type's */ -MATCH Type::deduceType(Type *tparam, Array *parameters, Array *dedtypes) +MATCH Type::deduceType(Scope *sc, Type *tparam, TemplateParameters *parameters, Array *dedtypes) { //printf("Type::deduceType()\n"); //printf("\tthis = %d, ", ty); print(); @@ -464,6 +807,7 @@ if (!tparam) goto Lnomatch; + Lagain: if (this == tparam) goto Lexact; @@ -473,7 +817,17 @@ //printf("\ttident = '%s'\n", tident->toChars()); if (tident->idents.dim > 0) - goto Lnomatch; + { + Llookup: + if (!sc) + goto Lnomatch; + /* BUG: what if tparam is a template instance, that + * has as an argument another Tident? + */ + tparam = tparam->semantic(0, sc); + assert(tparam->ty != Tident); + goto Lagain; + } // Determine which parameter tparam is Identifier *id = tident->ident; @@ -481,7 +835,7 @@ for (i = 0; 1; i++) { if (i == parameters->dim) - goto Lnomatch; + goto Llookup; TemplateParameter *tp = (TemplateParameter *)parameters->data[i]; if (tp->ident->equals(id)) @@ -504,7 +858,7 @@ goto Lnomatch; if (next) - return next->deduceType(tparam->next, parameters, dedtypes); + return next->deduceType(sc, tparam->next, parameters, dedtypes); Lexact: return MATCHexact; @@ -513,31 +867,78 @@ return MATCHnomatch; } -MATCH TypeSArray::deduceType(Type *tparam, Array *parameters, Array *dedtypes) +MATCH TypeSArray::deduceType(Scope *sc, Type *tparam, TemplateParameters *parameters, Array *dedtypes) { + //printf("TypeSArray::deduceType()\n"); + //printf("\tthis = %d, ", ty); print(); + //printf("\ttparam = %d, ", tparam->ty); tparam->print(); + // Extra check that array dimensions must match - if (tparam && tparam->ty == Tsarray) + if (tparam) { - TypeSArray *tp = (TypeSArray *)tparam; - if (dim->toInteger() != tp->dim->toInteger()) - return MATCHnomatch; + if (tparam->ty == Tsarray) + { + TypeSArray *tp = (TypeSArray *)tparam; + if (dim->toInteger() != tp->dim->toInteger()) + return MATCHnomatch; + } + else if (tparam->ty == Taarray) + { + TypeAArray *tp = (TypeAArray *)tparam; + if (tp->index->ty == Tident) + { TypeIdentifier *tident = (TypeIdentifier *)tp->index; + + if (tident->idents.dim == 0) + { Identifier *id = tident->ident; + + for (size_t i = 0; i < parameters->dim; i++) + { + TemplateParameter *tp = (TemplateParameter *)parameters->data[i]; + + if (tp->ident->equals(id)) + { // Found the corresponding template parameter + TemplateValueParameter *tvp = tp->isTemplateValueParameter(); + if (!tvp || !tvp->valType->isintegral()) + goto Lnomatch; + + if (dedtypes->data[i]) + { + if (!dim->equals((Object *)dedtypes->data[i])) + goto Lnomatch; + } + else + { dedtypes->data[i] = (void *)dim; + } + return next->deduceType(sc, tparam->next, parameters, dedtypes); + } + } + } + } + } } - return Type::deduceType(tparam, parameters, dedtypes); + return Type::deduceType(sc, tparam, parameters, dedtypes); + + Lnomatch: + return MATCHnomatch; } -MATCH TypeAArray::deduceType(Type *tparam, Array *parameters, Array *dedtypes) +MATCH TypeAArray::deduceType(Scope *sc, Type *tparam, TemplateParameters *parameters, Array *dedtypes) { + //printf("TypeAArray::deduceType()\n"); + //printf("\tthis = %d, ", ty); print(); + //printf("\ttparam = %d, ", tparam->ty); tparam->print(); + // Extra check that index type must match if (tparam && tparam->ty == Taarray) { TypeAArray *tp = (TypeAArray *)tparam; - if (!index->deduceType(tp->index, parameters, dedtypes)) + if (!index->deduceType(sc, tp->index, parameters, dedtypes)) return MATCHnomatch; } - return Type::deduceType(tparam, parameters, dedtypes); + return Type::deduceType(sc, tparam, parameters, dedtypes); } -MATCH TypeFunction::deduceType(Type *tparam, Array *parameters, Array *dedtypes) +MATCH TypeFunction::deduceType(Scope *sc, Type *tparam, TemplateParameters *parameters, Array *dedtypes) { // Extra check that function characteristics must match if (tparam && tparam->ty == Tfunction) @@ -552,14 +953,14 @@ Argument *a = (Argument *)arguments->data[i]; Argument *ap = (Argument *)tp->arguments->data[i]; if (a->inout != ap->inout || - !a->type->deduceType(ap->type, parameters, dedtypes)) + !a->type->deduceType(sc, ap->type, parameters, dedtypes)) return MATCHnomatch; } } - return Type::deduceType(tparam, parameters, dedtypes); + return Type::deduceType(sc, tparam, parameters, dedtypes); } -MATCH TypeIdentifier::deduceType(Type *tparam, Array *parameters, Array *dedtypes) +MATCH TypeIdentifier::deduceType(Scope *sc, Type *tparam, TemplateParameters *parameters, Array *dedtypes) { // Extra check if (tparam && tparam->ty == Tident) @@ -575,10 +976,10 @@ return MATCHnomatch; } } - return Type::deduceType(tparam, parameters, dedtypes); + return Type::deduceType(sc, tparam, parameters, dedtypes); } -MATCH TypeInstance::deduceType(Type *tparam, Array *parameters, Array *dedtypes) +MATCH TypeInstance::deduceType(Scope *sc, Type *tparam, TemplateParameters *parameters, Array *dedtypes) { // Extra check if (tparam && tparam->ty == Tinstance) @@ -599,15 +1000,19 @@ Type *t1 = (Type *)tempinst->tiargs->data[i]; Type *t2 = (Type *)tp->tempinst->tiargs->data[i]; - if (!t1->deduceType(t2, parameters, dedtypes)) + if (!t1->deduceType(sc, t2, parameters, dedtypes)) return MATCHnomatch; } } - return Type::deduceType(tparam, parameters, dedtypes); + return Type::deduceType(sc, tparam, parameters, dedtypes); } -MATCH TypeStruct::deduceType(Type *tparam, Array *parameters, Array *dedtypes) +MATCH TypeStruct::deduceType(Scope *sc, Type *tparam, TemplateParameters *parameters, Array *dedtypes) { + //printf("TypeStruct::deduceType()\n"); + //printf("\tthis->parent = %s, ", sym->parent->toChars()); print(); + //printf("\ttparam = %d, ", tparam->ty); tparam->print(); + // Extra check if (tparam && tparam->ty == Tstruct) { @@ -616,10 +1021,10 @@ if (sym != tp->sym) return MATCHnomatch; } - return Type::deduceType(tparam, parameters, dedtypes); + return Type::deduceType(sc, tparam, parameters, dedtypes); } -MATCH TypeEnum::deduceType(Type *tparam, Array *parameters, Array *dedtypes) +MATCH TypeEnum::deduceType(Scope *sc, Type *tparam, TemplateParameters *parameters, Array *dedtypes) { // Extra check if (tparam && tparam->ty == Tenum) @@ -629,10 +1034,10 @@ if (sym != tp->sym) return MATCHnomatch; } - return Type::deduceType(tparam, parameters, dedtypes); + return Type::deduceType(sc, tparam, parameters, dedtypes); } -MATCH TypeTypedef::deduceType(Type *tparam, Array *parameters, Array *dedtypes) +MATCH TypeTypedef::deduceType(Scope *sc, Type *tparam, TemplateParameters *parameters, Array *dedtypes) { // Extra check if (tparam && tparam->ty == Ttypedef) @@ -642,10 +1047,10 @@ if (sym != tp->sym) return MATCHnomatch; } - return Type::deduceType(tparam, parameters, dedtypes); + return Type::deduceType(sc, tparam, parameters, dedtypes); } -MATCH TypeClass::deduceType(Type *tparam, Array *parameters, Array *dedtypes) +MATCH TypeClass::deduceType(Scope *sc, Type *tparam, TemplateParameters *parameters, Array *dedtypes) { //printf("TypeClass::deduceType()\n"); @@ -654,15 +1059,10 @@ { TypeClass *tp = (TypeClass *)tparam; -#if 1 //printf("\t%d\n", (MATCH) implicitConvTo(tp)); return (MATCH) implicitConvTo(tp); -#else - if (sym != tp->sym) - return MATCHnomatch; -#endif } - return Type::deduceType(tparam, parameters, dedtypes); + return Type::deduceType(sc, tparam, parameters, dedtypes); } /* ======================== TemplateParameter =============================== */ @@ -757,7 +1157,7 @@ MATCH TemplateTypeParameter::matchArg(Scope *sc, Object *oarg, - int i, Array *parameters, Array *dedtypes, Declaration **psparam) + int i, TemplateParameters *parameters, Array *dedtypes, Declaration **psparam) { //printf("TemplateTypeParameter::matchArg()\n"); @@ -772,7 +1172,7 @@ if (specType) { //printf("\tcalling deduceType(), specType is %s\n", specType->toChars()); - MATCH m2 = ta->deduceType(specType, parameters, dedtypes); + MATCH m2 = ta->deduceType(sc, specType, parameters, dedtypes); if (m2 == MATCHnomatch) { //printf("\tfailed deduceType\n"); goto Lnomatch; @@ -782,11 +1182,15 @@ m = m2; t = (Type *)dedtypes->data[i]; } - else if (t) - { // Must match already deduced type + else + { + m = MATCHconvert; + if (t) + { // Must match already deduced type - if (!t->equals(ta)) - goto Lnomatch; + if (!t->equals(ta)) + goto Lnomatch; + } } if (!t) @@ -821,18 +1225,18 @@ } -void TemplateTypeParameter::toCBuffer(OutBuffer *buf) +void TemplateTypeParameter::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { buf->writestring(ident->toChars()); if (specType) { buf->writestring(" : "); - specType->toCBuffer(buf, NULL); + specType->toCBuffer(buf, NULL, hgs); } if (defaultType) { buf->writestring(" = "); - defaultType->toCBuffer(buf, NULL); + defaultType->toCBuffer(buf, NULL, hgs); } } @@ -850,6 +1254,12 @@ } +Object *TemplateTypeParameter::specialization() +{ + return specType; +} + + Object *TemplateTypeParameter::defaultArg(Scope *sc) { Type *t; @@ -930,7 +1340,7 @@ } MATCH TemplateAliasParameter::matchArg(Scope *sc, - Object *oarg, int i, Array *parameters, Array *dedtypes, Declaration **psparam) + Object *oarg, int i, TemplateParameters *parameters, Array *dedtypes, Declaration **psparam) { Dsymbol *sa; @@ -992,19 +1402,19 @@ fprintf(stderr, "\tArgument alias: %s\n", sa->toChars()); } -void TemplateAliasParameter::toCBuffer(OutBuffer *buf) +void TemplateAliasParameter::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { buf->writestring("alias "); buf->writestring(ident->toChars()); if (specAliasT) { buf->writestring(" : "); - specAliasT->toCBuffer(buf, NULL); + specAliasT->toCBuffer(buf, NULL, hgs); } if (defaultAlias) { buf->writestring(" = "); - defaultAlias->toCBuffer(buf, NULL); + defaultAlias->toCBuffer(buf, NULL, hgs); } } @@ -1023,6 +1433,12 @@ } +Object *TemplateAliasParameter::specialization() +{ + return specAliasT; +} + + Object *TemplateAliasParameter::defaultArg(Scope *sc) { Dsymbol *s = NULL; @@ -1131,11 +1547,14 @@ MATCH TemplateValueParameter::matchArg(Scope *sc, - Object *oarg, int i, Array *parameters, Array *dedtypes, Declaration **psparam) + Object *oarg, int i, TemplateParameters *parameters, Array *dedtypes, Declaration **psparam) { + //printf("TemplateValueParameter::matchArg()\n"); + Initializer *init; Declaration *sparam; Expression *ei = isExpression(oarg); + MATCH m = MATCHexact; if (!ei && oarg) goto Lnomatch; @@ -1145,9 +1564,16 @@ goto Lnomatch; Expression *e = specValue; + e = e->semantic(sc); e = e->implicitCastTo(valType); e = e->constFold(); + + ei = ei->syntaxCopy(); + ei = ei->semantic(sc); + ei = ei->constFold(); + //printf("ei: %s, %s\n", ei->toChars(), ei->type->toChars()); + //printf("e : %s, %s\n", e->toChars(), e->type->toChars()); if (!ei->equals(e)) goto Lnomatch; } @@ -1158,13 +1584,23 @@ if (!ei || !ei->equals(e)) goto Lnomatch; } +Lmatch: + //printf("valType: %s\n", valType->toChars()); + //printf("ei: %s, %s\n", ei->toChars(), ei->type->toChars()); + if (ei->type) + { + m = (MATCH)ei->implicitConvTo(valType); + //printf("m: %d\n", m); + if (!m) + goto Lnomatch; + } dedtypes->data[i] = ei; init = new ExpInitializer(loc, ei); sparam = new VarDeclaration(loc, valType, ident, init); sparam->storage_class = STCconst; *psparam = sparam; - return MATCHexact; + return m; Lnomatch: *psparam = NULL; @@ -1184,18 +1620,18 @@ } -void TemplateValueParameter::toCBuffer(OutBuffer *buf) +void TemplateValueParameter::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { - valType->toCBuffer(buf, ident); + valType->toCBuffer(buf, ident, hgs); if (specValue) { buf->writestring(" : "); - specValue->toCBuffer(buf); + specValue->toCBuffer(buf, hgs); } if (defaultValue) { buf->writestring(" = "); - defaultValue->toCBuffer(buf); + defaultValue->toCBuffer(buf, hgs); } } @@ -1215,6 +1651,12 @@ } +Object *TemplateValueParameter::specialization() +{ + return specValue; +} + + Object *TemplateValueParameter::defaultArg(Scope *sc) { Expression *e; @@ -1244,9 +1686,37 @@ this->argsym = NULL; this->aliasdecl = NULL; this->semanticdone = 0; + this->withsym = NULL; + this->nest = 0; #ifdef IN_GCC this->objFileModule = NULL; #endif + this->havetempdecl = 0; +} + + +TemplateInstance::TemplateInstance(Loc loc, TemplateDeclaration *td, Array *tiargs) + : ScopeDsymbol(NULL) +{ +#if LOG + printf("TemplateInstance(this = %p, tempdecl = '%s')\n", this, td->toChars()); +#endif + this->loc = loc; + this->idents.push(td->ident); + this->tiargs = tiargs; + this->tempdecl = td; + this->inst = NULL; + this->argsym = NULL; + this->aliasdecl = NULL; + this->semanticdone = 0; + this->withsym = NULL; + this->nest = 0; +#ifdef IN_GCC + this->objFileModule = NULL; +#endif + this->havetempdecl = 1; + + assert((size_t)tempdecl->scope > 0x10000); } @@ -1295,6 +1765,8 @@ void TemplateInstance::semantic(Scope *sc) { + if (global.errors) + return; #if LOG printf("+TemplateInstance::semantic('%s' (%p), this=%p)\n", toChars(), this, this); #endif @@ -1312,7 +1784,7 @@ if (inst) // if semantic() was already run { #if LOG - printf("-TemplateInstance::semantic('%s', this=%p)\n", inst->toChars(), inst); + printf("-TemplateInstance::semantic('%s', this=%p) already run\n", inst->toChars(), inst); #endif return; } @@ -1328,13 +1800,23 @@ #if LOG printf("\tdo semantic\n"); #endif - // Run semantic on each argument, place results in tiargs[] - semanticTiargs(sc); + if (havetempdecl) + { + assert((size_t)tempdecl->scope > 0x10000); + // Deduce tdtypes + tdtypes.setDim(tempdecl->parameters->dim); + tempdecl->matchWithInstance(this, &tdtypes, 0); + } + else + { + // Run semantic on each argument, place results in tiargs[] + semanticTiargs(sc); - tempdecl = findTemplateDeclaration(sc); - if (!tempdecl || global.errors) - { inst = this; - return; // error recovery + tempdecl = findTemplateDeclaration(sc); + if (!tempdecl || global.errors) + { inst = this; + return; // error recovery + } } /* See if there is an existing TemplateInstantiation that already @@ -1419,6 +1901,7 @@ #endif unsigned errorsave = global.errors; inst = this; + int tempdecl_instance_idx = tempdecl->instances.dim; tempdecl->instances.push(this); parent = tempdecl->parent; //printf("parent = '%s'\n", parent->kind()); @@ -1516,14 +1999,18 @@ // Add members of template instance to template instance symbol table // parent = scope->scopesym; symtab = new DsymbolTable(); + int memnum = 0; for (int i = 0; i < members->dim; i++) { Dsymbol *s = (Dsymbol *)members->data[i]; #if LOG - printf("\tadding member '%s' %p to '%s'\n", s->toChars(), s, this->toChars()); + printf("\t[%d] adding member '%s' %p to '%s', memnum = %d\n", i, s->toChars(), s, this->toChars(), memnum); #endif - s->addMember(scope, this); + memnum |= s->addMember(scope, this, memnum); } +#if LOG + printf("adding members done\n"); +#endif /* See if there is only one member of template instance, and that * member has the same name as the template instance. @@ -1532,19 +2019,8 @@ //printf("members->dim = %d\n", members->dim); if (members->dim) { - Dsymbol *s = (Dsymbol *)members->data[0]; - s = s->oneMember(); - - // Ignore any additional template instance symbols - for (int j = 1; j < members->dim; j++) - { Dsymbol *sx = (Dsymbol *)members->data[j]; - if (sx->isTemplateInstance()) - continue; - s = NULL; - break; - } - - if (s) + Dsymbol *s; + if (Dsymbol::oneMembers(members, &s) && s) { //printf("s->kind = '%s'\n", s->kind()); //s->print(); @@ -1590,7 +2066,11 @@ // Give additional context info if error occurred during instantiation if (global.errors != errorsave) + { error("error instantiating"); + if (global.gag) + tempdecl->instances.remove(tempdecl_instance_idx); + } #if LOG printf("-TemplateInstance::semantic('%s', this=%p)\n", toChars(), this); @@ -1601,6 +2081,7 @@ void TemplateInstance::semanticTiargs(Scope *sc) { // Run semantic on each argument, place results in tiargs[] + //printf("TemplateInstance::semanticTiargs()\n"); for (int j = 0; j < tiargs->dim; j++) { Type *ta = isType((Object *)tiargs->data[j]); Expression *ea; @@ -1611,7 +2092,11 @@ // It might really be an Expression or an Alias ta->resolve(loc, sc, &ea, &ta, &sa); if (ea) + { + ea = ea->semantic(sc); + ea = ea->constFold(); tiargs->data[j] = ea; + } else if (sa) tiargs->data[j] = sa; else if (ta) @@ -1627,7 +2112,8 @@ ea = isExpression((Object *)tiargs->data[j]); assert(ea); ea = ea->semantic(sc); - ea = ea->constFold(); + ea = ea->optimize(WANTvalue); + //ea = ea->constFold(); tiargs->data[j] = ea; } //printf("1: tiargs->data[%d] = %p\n", j, tiargs->data[j]); @@ -1640,6 +2126,7 @@ TemplateDeclaration *TemplateInstance::findTemplateDeclaration(Scope *sc) { + //printf("TemplateInstance::findTemplateDeclaration()\n"); if (!tempdecl) { /* Given: @@ -1656,8 +2143,10 @@ if (s) { #if LOG - printf("It's an instance of '%s'\n", s->toChars()); + printf("It's an instance of '%s' kind '%s'\n", s->toChars(), s->kind()); #endif + withsym = scopesym->isWithScopeSymbol(); + s = s->toAlias(); for (i = 1; i < idents.dim; i++) { Dsymbol *sm; @@ -1682,8 +2171,28 @@ tempdecl = s->isTemplateDeclaration(); if (!tempdecl) { - error("%s is not a template declaration, it is a %s", id->toChars(), s->kind()); - return NULL; + if (!s->parent && global.errors) + return NULL; + assert(s->parent); + TemplateInstance *ti = s->parent->isTemplateInstance(); + if (ti && + (ti->idents.data[ti->idents.dim - 1] == id || + ti->toAlias()->ident == id) + && + idents.dim == 1 && + ti->tempdecl) + { + /* This is so that one can refer to the enclosing + * template, even if it has the same name as a member + * of the template, if it has a !(arguments) + */ + tempdecl = ti->tempdecl; + } + else + { + error("%s is not a template declaration, it is a %s", id->toChars(), s->kind()); + return NULL; + } } } else @@ -1718,7 +2227,7 @@ if (!m) // no match at all continue; -#if 0 +#if 1 if (m < m_best) goto Ltd_best; if (m > m_best) @@ -1746,9 +2255,11 @@ continue; Ltd_best: // td_best is the best match so far + td_ambig = NULL; continue; Ltd: // td is the new best match + td_ambig = NULL; td_best = td; m_best = m; tdtypes.setDim(dedtypes.dim); @@ -1758,12 +2269,13 @@ if (!td_best) { - error("does not match any template declaration"); + error("%s does not match any template declaration", toChars()); return NULL; } if (td_ambig) { - error("matches more than one template declaration"); + error("%s matches more than one template declaration, %s and %s", + toChars(), td_best->toChars(), td_ambig->toChars()); } /* The best match is td_best @@ -1864,39 +2376,8 @@ TemplateParameter *tp = (TemplateParameter *)tempdecl->parameters->data[i]; //Object *o = (Object *)tiargs->data[i]; Object *o = (Object *)tdtypes.data[i]; - Type *targ = isType(o); - Expression *ea = isExpression(o); - Dsymbol *sa = isDsymbol(o); - Dsymbol *s; - - if (targ) - { - Type *tded = isType((Object *)tdtypes.data[i]); - assert(tded); - s = new AliasDeclaration(0, tp->ident, tded); - } - else if (sa) - { - //printf("Alias %s %s;\n", sa->ident->toChars(), tp->ident->toChars()); - s = new AliasDeclaration(0, tp->ident, sa); - } - else if (ea) - { - // tdtypes.data[i] always matches ea here - Initializer *init = new ExpInitializer(loc, ea); - TemplateValueParameter *tvp = tp->isTemplateValueParameter(); - assert(tvp); - - VarDeclaration *v = new VarDeclaration(0, tvp->valType, tp->ident, init); - v->storage_class = STCconst; - s = v; - } - else - assert(0); - if (!scope->insert(s)) - error("declaration %s is already defined", tp->ident->toChars()); - s->semantic(scope); + tempdecl->declareParameter(scope, tp, o); } } @@ -1989,7 +2470,7 @@ } } -void TemplateInstance::toCBuffer(OutBuffer *buf) +void TemplateInstance::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { int i; @@ -2015,9 +2496,9 @@ Expression *e = isExpression(oarg); Dsymbol *s = isDsymbol(oarg); if (t) - t->toCBuffer(buf, NULL); + t->toCBuffer(buf, NULL, hgs); else if (e) - e->toCBuffer(buf); + e->toCBuffer(buf, hgs); else if (s) { char *p = s->ident ? s->ident->toChars() : s->toChars(); @@ -2070,16 +2551,22 @@ return "template instance"; } +int TemplateInstance::oneMember(Dsymbol **ps) +{ + *ps = NULL; + return TRUE; +} + char *TemplateInstance::toChars() { OutBuffer buf; + HdrGenState hgs; char *s; - toCBuffer(&buf); + toCBuffer(&buf, &hgs); s = buf.toChars(); buf.data = NULL; return s; - //return s + 9; // kludge to skip over 'instance ' } /* ======================== TemplateMixin ================================ */ @@ -2299,7 +2786,7 @@ { Dsymbol *s; s = (Dsymbol *)members->data[i]; - s->addMember(scope, this); + s->addMember(scope, this, i); //sc->insert(s); //printf("sc->parent = %p, sc->scopesym = %p\n", sc->parent, sc->scopesym); //printf("s->parent = %s\n", s->parent->toChars()); @@ -2408,30 +2895,54 @@ return "mixin"; } -Dsymbol *TemplateMixin::oneMember() +int TemplateMixin::oneMember(Dsymbol **ps) { - return Dsymbol::oneMember(); + return Dsymbol::oneMember(ps); } -void TemplateMixin::toCBuffer(OutBuffer *buf) +void TemplateMixin::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { - //buf->writestring("mixin "); - if (tqual) - { tqual->toCBuffer(buf, NULL); - buf->writeByte('.'); - } - for (int i = 0; i + 1 < idents->dim; i++) - { Identifier *id = (Identifier *)idents->data[i]; + buf->writestring("mixin "); + int i; + for (i = 0; i < idents->dim; i++) + { Identifier *id = (Identifier *)idents->data[i]; + if (i) + buf->writeByte('.'); buf->writestring(id->toChars()); - buf->writeByte('.'); } - TemplateInstance::toCBuffer(buf); - if (ident) + buf->writestring("!("); + if (tiargs) { - buf->writeByte(' '); - buf->writestring(ident->toChars()); + for (i = 0; i < tiargs->dim; i++) + { if (i) + buf->writebyte(','); + Object *oarg = (Object *)tiargs->data[i]; + Type *t = isType(oarg); + Expression *e = isExpression(oarg); + Dsymbol *s = isDsymbol(oarg); + if (t) + t->toCBuffer(buf, NULL, hgs); + else if (e) + e->toCBuffer(buf, hgs); + else if (s) + { + char *p = s->ident ? s->ident->toChars() : s->toChars(); + buf->writestring(p); + } + else if (!oarg) + { + buf->writestring("NULL"); + } + else + { + assert(0); + } + } } + buf->writebyte(')'); + buf->writebyte(';'); + buf->writenl(); } diff -uNr gdc-0.17/d/dmd/template.h gdc-0.18/d/dmd/template.h --- gdc-0.17/d/dmd/template.h 2005-11-28 05:17:52.000000000 +0100 +++ gdc-0.18/d/dmd/template.h 2006-05-13 21:05:42.000000000 +0200 @@ -1,5 +1,5 @@ -// Copyright (c) 1999-2005 by Digital Mars +// Copyright (c) 1999-2006 by Digital Mars // All Rights Reserved // written by Walter Bright // www.digitalmars.com @@ -7,12 +7,6 @@ // in artistic.txt, or the GNU General Public License in gnu.txt. // See the included readme.txt for details. -/* NOTE: This file has been patched from the original DMD distribution to - work with the GDC compiler. - - Modified by David Friedman, May 2005 -*/ - #ifndef DMD_TEMPLATE_H #define DMD_TEMPLATE_H @@ -21,8 +15,10 @@ #endif /* __DMC__ */ #include "root.h" +#include "arraytypes.h" #include "dsymbol.h" + struct OutBuffer; struct Identifier; struct TemplateInstance; @@ -34,22 +30,24 @@ struct Scope; struct Expression; struct AliasDeclaration; +struct FuncDeclaration; +struct HdrGenState; enum MATCH; struct TemplateDeclaration : ScopeDsymbol { - Array *parameters; // array of TemplateParameter's + TemplateParameters *parameters; // array of TemplateParameter's Array instances; // array of TemplateInstance's TemplateDeclaration *overnext; // next overloaded TemplateDeclaration Scope *scope; Dsymbol *onemember; // if !=NULL then one member of this template - TemplateDeclaration(Loc loc, Identifier *id, Array *parameters, Array *decldefs); + TemplateDeclaration(Loc loc, Identifier *id, TemplateParameters *parameters, Array *decldefs); Dsymbol *syntaxCopy(Dsymbol *); void semantic(Scope *sc); int overloadInsert(Dsymbol *s); - void toCBuffer(OutBuffer *buf); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); char *kind(); char *toChars(); @@ -59,6 +57,10 @@ MATCH matchWithInstance(TemplateInstance *ti, Array *atypes, int flag); int leastAsSpecialized(TemplateDeclaration *td2); + MATCH deduceMatch(Array *targsi, Array *fargs, Array *dedargs); + FuncDeclaration *deduce(Scope *sc, Loc loc, Array *targsi, Expressions *fargs); + void declareParameter(Scope *sc, TemplateParameter *tp, Object *o); + TemplateDeclaration *isTemplateDeclaration() { return this; } }; @@ -86,7 +88,8 @@ virtual TemplateParameter *syntaxCopy() = 0; virtual void semantic(Scope *) = 0; virtual void print(Object *oarg, Object *oded) = 0; - virtual void toCBuffer(OutBuffer *buf) = 0; + virtual void toCBuffer(OutBuffer *buf, HdrGenState *hgs) = 0; + virtual Object *specialization() = 0; virtual Object *defaultArg(Scope *sc) = 0; /* If TemplateParameter's match as far as overloading goes. @@ -95,7 +98,7 @@ /* Match actual argument against parameter. */ - virtual MATCH matchArg(Scope *sc, Object *oarg, int i, Array *parameters, Array *dedtypes, Declaration **psparam) = 0; + virtual MATCH matchArg(Scope *sc, Object *oarg, int i, TemplateParameters *parameters, Array *dedtypes, Declaration **psparam) = 0; /* Create dummy argument based on parameter. */ @@ -116,10 +119,11 @@ TemplateParameter *syntaxCopy(); void semantic(Scope *); void print(Object *oarg, Object *oded); - void toCBuffer(OutBuffer *buf); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); + Object *specialization(); Object *defaultArg(Scope *sc); int overloadMatch(TemplateParameter *); - MATCH matchArg(Scope *sc, Object *oarg, int i, Array *parameters, Array *dedtypes, Declaration **psparam); + MATCH matchArg(Scope *sc, Object *oarg, int i, TemplateParameters *parameters, Array *dedtypes, Declaration **psparam); void *dummyArg(); }; @@ -141,10 +145,11 @@ TemplateParameter *syntaxCopy(); void semantic(Scope *); void print(Object *oarg, Object *oded); - void toCBuffer(OutBuffer *buf); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); + Object *specialization(); Object *defaultArg(Scope *sc); int overloadMatch(TemplateParameter *); - MATCH matchArg(Scope *sc, Object *oarg, int i, Array *parameters, Array *dedtypes, Declaration **psparam); + MATCH matchArg(Scope *sc, Object *oarg, int i, TemplateParameters *parameters, Array *dedtypes, Declaration **psparam); void *dummyArg(); }; @@ -167,29 +172,37 @@ TemplateParameter *syntaxCopy(); void semantic(Scope *); void print(Object *oarg, Object *oded); - void toCBuffer(OutBuffer *buf); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); + Object *specialization(); Object *defaultArg(Scope *sc); int overloadMatch(TemplateParameter *); - MATCH matchArg(Scope *sc, Object *oarg, int i, Array *parameters, Array *dedtypes, Declaration **psparam); + MATCH matchArg(Scope *sc, Object *oarg, int i, TemplateParameters *parameters, Array *dedtypes, Declaration **psparam); void *dummyArg(); }; struct TemplateInstance : ScopeDsymbol { /* Given: - * instance foo.bar.abc(int, char, 10*10) + * template abc(T:T*, S, int V) + * instance foo.bar.abc(int*, char, 10*10) */ Array idents; // Array of Identifiers [foo, bar, abc] - Array *tiargs; // Array of Types/Expressions of template instance arguments [int, char, 10*10] + Array *tiargs; // Array of Types/Expressions of template + // instance arguments [int*, char, 10*10] + + Array tdtypes; // Array of Types/Expressions corresponding + // to TemplateDeclaration.parameters + // [int, char, 100] TemplateDeclaration *tempdecl; // referenced by foo.bar.abc TemplateInstance *inst; // refer to existing instance - Array tdtypes; // types corresponding to TemplateDeclaration.parameters ScopeDsymbol *argsym; // argument symbol table AliasDeclaration *aliasdecl; // !=NULL if instance is an alias for its // sole member + WithScopeSymbol *withsym; // if a member of a with statement int semanticdone; // has semantic() been done? int nest; // for recursion detection + int havetempdecl; // 1 if used second constructor #ifdef IN_GCC /* On some targets, it is necessary to know whether a symbol will be emitted in the output or not before the symbol @@ -198,15 +211,17 @@ #endif TemplateInstance(Loc loc, Identifier *temp_id); + TemplateInstance(Loc loc, TemplateDeclaration *tempdecl, Array *tiargs); Dsymbol *syntaxCopy(Dsymbol *); void addIdent(Identifier *ident); void semantic(Scope *sc); void semantic2(Scope *sc); void semantic3(Scope *sc); void inlineScan(); - void toCBuffer(OutBuffer *buf); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); Dsymbol *toAlias(); // resolve real symbol char *kind(); + int oneMember(Dsymbol **ps); char *toChars(); char *mangle(); @@ -234,8 +249,8 @@ void semantic3(Scope *sc); void inlineScan(); char *kind(); - Dsymbol *oneMember(); - void toCBuffer(OutBuffer *buf); + int oneMember(Dsymbol **ps); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); void toObjFile(); // compile to .obj file diff -uNr gdc-0.17/d/dmd/tocsym.c gdc-0.18/d/dmd/tocsym.c --- gdc-0.17/d/dmd/tocsym.c 2005-06-22 05:13:40.000000000 +0200 +++ gdc-0.18/d/dmd/tocsym.c 2006-04-16 17:13:30.000000000 +0200 @@ -11,9 +11,7 @@ #include #include #include -#ifndef alloca -#include -#endif +#include "gdc_alloca.h" #include "mars.h" #include "module.h" @@ -70,6 +68,7 @@ char *n; n = mangle(); //ident->toChars(); + assert(n); id = (char *) alloca(strlen(prefix) + strlen(n) + 1); sprintf(id,"%s%s", prefix, n); s = symbol_name(id, sclass, t); @@ -302,6 +301,7 @@ break; case LINKpascal: + t->Tty = TYnpfunc; t->Tmangle = mTYman_pas; break; diff -uNr gdc-0.17/d/dmd/todt.c gdc-0.18/d/dmd/todt.c --- gdc-0.17/d/dmd/todt.c 2005-11-28 05:17:52.000000000 +0100 +++ gdc-0.18/d/dmd/todt.c 2006-03-12 15:56:29.000000000 +0100 @@ -465,6 +465,7 @@ dt_t **ComplexExp::toDt(dt_t **pdt) { + //printf("ComplexExp::toDt() '%s'\n", toChars()); d_float32 fvalue; d_float64 dvalue; d_float80 evalue; @@ -490,8 +491,8 @@ pdt = dtnbytes(pdt,REALSIZE - REALPAD,(char *)&evalue); pdt = dtnbytes(pdt,REALPAD,zeropad); evalue = cimagl(value); - pdt = dtnbytes(pdt,REALSIZE,(char *)&evalue); - pdt = dtnbytes(pdt,REALSIZE - REALPAD,zeropad); + pdt = dtnbytes(pdt,REALSIZE - REALPAD,(char *)&evalue); + pdt = dtnbytes(pdt,REALPAD,zeropad); break; default: @@ -821,7 +822,10 @@ for (i = 1; i < len; i++) { if (tbn->ty == Tstruct) - pdt = tnext->toDt(pdt); + { pdt = tnext->toDt(pdt); + while (*pdt) + pdt = &((*pdt)->DTnext); + } else pdt = e->toDt(pdt); } diff -uNr gdc-0.17/d/dmd/toobj.c gdc-0.18/d/dmd/toobj.c --- gdc-0.17/d/dmd/toobj.c 2005-10-26 03:33:56.000000000 +0200 +++ gdc-0.18/d/dmd/toobj.c 2006-05-13 21:05:42.000000000 +0200 @@ -134,7 +134,7 @@ dtdword(&dt, namelen); dtabytes(&dt, TYnptr, 0, namelen + 1, name); - Array aclasses; + ClassDeclarations aclasses; int i; //printf("members->dim = %d\n", members->dim); diff -uNr gdc-0.17/d/dmd/total.h gdc-0.18/d/dmd/total.h --- gdc-0.17/d/dmd/total.h 2005-05-29 23:09:19.000000000 +0200 +++ gdc-0.18/d/dmd/total.h 2006-05-13 21:05:42.000000000 +0200 @@ -1,5 +1,5 @@ -// Copyright (c) 1999-2002 by Digital Mars +// Copyright (c) 1999-2006 by Digital Mars // All Rights Reserved // written by Walter Bright // www.digitalmars.com @@ -18,11 +18,12 @@ #include #include #include -#include +//#include #include "root.h" #include "stringtable.h" +#include "arraytypes.h" #include "mars.h" #include "lexer.h" #include "parse.h" diff -uNr gdc-0.17/d/dmd/version.c gdc-0.18/d/dmd/version.c --- gdc-0.17/d/dmd/version.c 2005-06-23 02:52:34.000000000 +0200 +++ gdc-0.18/d/dmd/version.c 2006-04-16 17:13:30.000000000 +0200 @@ -8,6 +8,7 @@ // See the included readme.txt for details. #include +#include #include "root.h" @@ -45,7 +46,7 @@ return ds; } -void DebugSymbol::addMember(Scope *sc, ScopeDsymbol *sd) +int DebugSymbol::addMember(Scope *sc, ScopeDsymbol *sd, int memnum) { //printf("DebugSymbol::addMember('%s') %s\n", sd->toChars(), toChars()); Module *m; @@ -73,6 +74,7 @@ else m->debuglevel = level; } + return 0; } void DebugSymbol::semantic(Scope *sc) @@ -80,7 +82,7 @@ //printf("DebugSymbol::semantic() %s\n", toChars()); } -void DebugSymbol::toCBuffer(OutBuffer *buf) +void DebugSymbol::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { buf->writestring("debug = "); if (ident) @@ -124,7 +126,7 @@ return ds; } -void VersionSymbol::addMember(Scope *sc, ScopeDsymbol *sd) +int VersionSymbol::addMember(Scope *sc, ScopeDsymbol *sd, int memnum) { //printf("VersionSymbol::addMember('%s') %s\n", sd->toChars(), toChars()); Module *m; @@ -153,13 +155,14 @@ else m->versionlevel = level; } + return 0; } void VersionSymbol::semantic(Scope *sc) { } -void VersionSymbol::toCBuffer(OutBuffer *buf) +void VersionSymbol::toCBuffer(OutBuffer *buf, HdrGenState *hgs) { buf->writestring("version = "); if (ident) diff -uNr gdc-0.17/d/dmd/version.h gdc-0.18/d/dmd/version.h --- gdc-0.17/d/dmd/version.h 2005-05-29 23:09:19.000000000 +0200 +++ gdc-0.18/d/dmd/version.h 2006-04-16 17:13:30.000000000 +0200 @@ -1,5 +1,5 @@ -// Copyright (c) 1999-2002 by Digital Mars +// Copyright (c) 1999-2005 by Digital Mars // All Rights Reserved // written by Walter Bright // www.digitalmars.com @@ -17,6 +17,7 @@ #include "dsymbol.h" struct OutBuffer; +struct HdrGenState; struct DebugSymbol : Dsymbol { @@ -26,9 +27,9 @@ DebugSymbol(Loc loc, unsigned level); Dsymbol *syntaxCopy(Dsymbol *); - void addMember(Scope *sc, ScopeDsymbol *s); + int addMember(Scope *sc, ScopeDsymbol *s, int memnum); void semantic(Scope *sc); - void toCBuffer(OutBuffer *buf); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); char *kind(); }; @@ -40,9 +41,9 @@ VersionSymbol(Loc loc, unsigned level); Dsymbol *syntaxCopy(Dsymbol *); - void addMember(Scope *sc, ScopeDsymbol *s); + int addMember(Scope *sc, ScopeDsymbol *s, int memnum); void semantic(Scope *sc); - void toCBuffer(OutBuffer *buf); + void toCBuffer(OutBuffer *buf, HdrGenState *hgs); char *kind(); }; diff -uNr gdc-0.17/d/dmd-script gdc-0.18/d/dmd-script --- gdc-0.17/d/dmd-script 2005-11-27 17:28:26.000000000 +0100 +++ gdc-0.18/d/dmd-script 2006-05-26 02:06:43.000000000 +0200 @@ -33,6 +33,8 @@ my $output_parents; my $output_file; my $link = 1; +my $run = 0; +my $verbose = 0; my $show_commands = 0; my $seen_all_sources_flag = 0; my $first_input_file; @@ -43,6 +45,7 @@ my @out; my @link_out; +my @run_args; # Use the gdc executable in the same directory as this script and account # for the target prefix. @@ -70,7 +73,7 @@ sub printUsage() { print <> 8; + } +} + exit ($ok ? 0 : 1); diff -uNr gdc-0.17/d/d-spec.c gdc-0.18/d/d-spec.c --- gdc-0.17/d/d-spec.c 2005-08-12 04:32:44.000000000 +0200 +++ gdc-0.18/d/d-spec.c 2006-05-13 15:24:34.000000000 +0200 @@ -250,19 +250,8 @@ continue; } - /* If the filename ends in .[chi], put options around it. - But not if a specified -x option is currently active. */ len = strlen (argv[i]); if (len > 2 - && (argv[i][len - 1] == 'c' - || argv[i][len - 1] == 'i' - || argv[i][len - 1] == 'h') - && argv[i][len - 2] == '.') - { - args[i] |= LANGSPEC; - added += 2; - } - else if (len > 2 && (argv[i][len - 1] == 'd') && (argv[i][len - 2] == '.')) { @@ -338,29 +327,6 @@ saw_libc = argv[i]; } - /* Wrap foo.[chi] files in a language specification to - force the gcc compiler driver to run cc1plus on them. */ - if (args[i] & LANGSPEC) - { - int len = strlen (argv[i]); - switch (argv[i][len - 1]) - { - case 'c': - arglist[j++] = "-xc++"; - break; - case 'i': - arglist[j++] = "-xc++-cpp-output"; - break; - case 'h': - arglist[j++] = "-xc++-header"; - break; - default: - abort (); - } - arglist[j++] = argv[i]; - arglist[j] = "-xnone"; - } - if (args[i] & D_SOURCE_FILE) { if (all_d_sources) diff -uNr gdc-0.17/d/dt.h gdc-0.18/d/dt.h --- gdc-0.17/d/dt.h 2005-08-13 01:51:59.000000000 +0200 +++ gdc-0.18/d/dt.h 2006-05-08 12:41:19.000000000 +0200 @@ -58,7 +58,7 @@ return dtval(pdt, DT_nbytes, count, pbytes); } inline dt_t** -dtabytes(dt_t** pdt, TypeType ty, int, unsigned count, char * pbytes) { +dtabytes(dt_t** pdt, TypeType, int, unsigned count, char * pbytes) { return dtval(pdt, DT_abytes, count, pbytes); } inline dt_t** @@ -70,7 +70,7 @@ return dtval(pdt, DT_word, val, 0); } inline dt_t** -dtxoff(dt_t** pdt, Symbol * sym, unsigned offset, TypeType ty) { +dtxoff(dt_t** pdt, Symbol * sym, unsigned offset, TypeType) { return dtval(pdt, DT_xoff, offset, sym); } inline dt_t** diff -uNr gdc-0.17/d/gcc-mars.cc gdc-0.18/d/gcc-mars.cc --- gdc-0.17/d/gcc-mars.cc 2005-11-28 05:17:52.000000000 +0100 +++ gdc-0.18/d/gcc-mars.cc 2006-05-18 02:05:55.000000000 +0200 @@ -27,14 +27,15 @@ { mars_ext = "d"; sym_ext = "d"; + hdr_ext = "di"; doc_ext = "html"; ddoc_ext = "ddoc"; obj_ext = "o"; - copyright = "Copyright (c) 1999-2005 by Digital Mars"; + copyright = "Copyright (c) 1999-2006 by Digital Mars"; written = "written by Walter Bright"; - version = "v0.140"; + version = "v0.157"; global.structalign = 8; memset(¶ms, 0, sizeof(Param)); diff -uNr gdc-0.17/d/gdc_alloca.h gdc-0.18/d/gdc_alloca.h --- gdc-0.17/d/gdc_alloca.h 2005-05-29 23:09:19.000000000 +0200 +++ gdc-0.18/d/gdc_alloca.h 2006-03-12 15:16:26.000000000 +0100 @@ -6,6 +6,8 @@ # include # elif __sun__ # include +# elif SKYOS +# define alloca __builtin_alloca # else /* guess... */ # include diff -uNr gdc-0.17/d/gdc-version gdc-0.18/d/gdc-version --- gdc-0.17/d/gdc-version 2005-11-28 05:17:52.000000000 +0100 +++ gdc-0.18/d/gdc-version 2006-04-16 17:13:30.000000000 +0200 @@ -1 +1 @@ -gdc 0.17, using dmd 0.140 \ No newline at end of file +gdc 0.18, using dmd 0.149 diff -uNr gdc-0.17/d/INSTALL gdc-0.18/d/INSTALL --- gdc-0.17/d/INSTALL 2005-10-13 03:06:51.000000000 +0200 +++ gdc-0.18/d/INSTALL 2006-05-18 03:01:42.000000000 +0200 @@ -2,8 +2,6 @@ Required source packages * The core package of a recent GCC 3.3.x, 3.4.x, or 4.0.x release. - The C++ package is also required if you want to build the recls - package. * The gdc package from the main page. Required software @@ -31,9 +29,6 @@ 5. Build GCC using the normal install instructions. The only difference is that "d" is added to the --enable-languages option. - If you want to build the recls package, you also need to enable - the C++ compiler. - If you need to specify a compiler to build GCC other than the system's default, change the PATH, or use the "CC" and "CXX" environment variables. Example: @@ -84,8 +79,3 @@ expected. o On FreeBSD and Linux, the test of the "%A" format will fail due to a library bug. - * If you use recls, you need to add -lstdc++ to the link flags (or - run g++ and add -lphobos and -lpthread.) Also add /lib - to LD_LIBRARY_PATH or whatever is necessary for your system to - find shared libraries. OR build GCC and your programs with a - static libstdc++. diff -uNr gdc-0.17/d/INSTALL.html gdc-0.18/d/INSTALL.html --- gdc-0.17/d/INSTALL.html 2005-10-13 03:06:51.000000000 +0200 +++ gdc-0.18/d/INSTALL.html 2006-05-18 03:01:42.000000000 +0200 @@ -10,9 +10,7 @@

Required source packages

  • The core package of a recent GCC 3.3.x, 3.4.x, or 4.0.x -release.  The C++ -package -is also required if you want to build the recls package.
    +release.
  • The gdc package from the main page.
@@ -62,9 +60,6 @@ is added to the --enable-languages option.

-If you want to build the recls package, you also -need to enable the C++ compiler.
-
If you need to specify a compiler to build GCC other than the system's default, change the PATH, @@ -138,15 +133,6 @@ to a library bug.
-
  • If you use recls, you need to add -lstdc++ to the link -flags (or run g++ and add - -lphobos and -lpthread.)  Also add <prefix>/lib -to LD_LIBRARY_PATH or -whatever is necessary for your system to find shared libraries. OR -build GCC and your programs with a static libstdc++.
    diff -uNr gdc-0.17/d/lang.opt gdc-0.18/d/lang.opt --- gdc-0.17/d/lang.opt 2005-11-05 15:12:01.000000000 +0100 +++ gdc-0.18/d/lang.opt 2006-05-21 23:37:42.000000000 +0200 @@ -80,6 +80,17 @@ D Specify that the source file's parent directories should be appended to the object output directory. Note: this is actually a driver option; the backend ignores it. +fintfc +Generate D interface files + +fintfc-dir= +D Joined RejectNegative +-fintfc-dir= Write D interface files to directory + +fintfc-file= +D Joined RejectNegative +-fintfc-file= Write D interface file to + fdoc D Generate documentation @@ -104,6 +115,10 @@ D RejectNegative Dump decoded UTF-8 text and source from HTML +fbuiltin +D +Recognize built-in functions + funsigned-char D Make \"char\" unsigned by default (silently ignored in D) @@ -112,6 +127,18 @@ D Make \"char\" signed by default (silently ignored in D) +iprefix +D Joined Separate +-iprefix Specify as a prefix for next two options + +isysroot +D Joined Separate +-isysroot Set to be the system root directory + +isystem +D Joined Separate +-isystem Add to the start of the system include path + Wall D Enable most warning messages diff -uNr gdc-0.17/d/lang-specs.h gdc-0.18/d/lang-specs.h --- gdc-0.17/d/lang-specs.h 2005-08-12 04:32:44.000000000 +0200 +++ gdc-0.18/d/lang-specs.h 2005-12-25 18:45:12.000000000 +0100 @@ -39,13 +39,13 @@ {".d", "@d", D_D_SPEC_REST }, {".D", "@d", D_D_SPEC_REST }, {"@d", - "%{!E:cc1d %i %:d-all-sources() %(cc1_options) %{nostdinc*} %{+e*} %{I*}\ + "%{!E:cc1d %i %:d-all-sources() %(cc1_options) %I %{nostdinc*} %{+e*} %{I*}\ %{M} %{MM} %{!fsyntax-only:%(invoke_as)}}", D_D_SPEC_REST }, #else {".d", "@d", D_D_SPEC_REST }, {".D", "@d", D_D_SPEC_REST }, {"@d", - "%{!E:cc1d %i %(cc1_options) %{nostdinc*} %{+e*} %{I*}\ + "%{!E:cc1d %i %(cc1_options) %I %{nostdinc*} %{+e*} %{I*}\ %{M} %{MM} %{!fsyntax-only:%(invoke_as)}}", D_D_SPEC_REST }, #endif diff -uNr gdc-0.17/d/Make-lang.in gdc-0.18/d/Make-lang.in --- gdc-0.17/d/Make-lang.in 2005-10-02 16:17:55.000000000 +0200 +++ gdc-0.18/d/Make-lang.in 2006-03-12 15:16:26.000000000 +0100 @@ -22,6 +22,7 @@ # For various glibc, we need to define this to get NAN and FP_ constants D_EXTRA_DEFINES += -D_GNU_SOURCE=1 +D_EXTRA_DEFINES += -D_DH=1 # As with C++: (quote) OTOH, I think this means the g++ driver... # Note that it would be nice to move the dependency on g++ @@ -89,13 +90,17 @@ # need for Cygwin which does not have 3.4.x, x>1 yet... D_EXTRA_DEFINES += -DD_GCC_VER341=1 endif +ifeq ($(gcc_version),3.4.0) +# similar: needed for SkyOS which uses 3.4.0 +D_EXTRA_DEFINES += -DD_GCC_VER341=1 +endif D d: $(D_COMPILER_NAME)$(exeext) # Tell GNU make to ignore these if they exist. .PHONY: D d -D_BORROWED_C_OBJS=attribs.o +D_BORROWED_C_OBJS=attribs.o cppdefault.o D_INCLUDES = -I$(srcdir)/d -I$(srcdir)/d/dmd -Id # -Wno-long-double is for MacOS X -- needs to be configurated @@ -127,7 +132,7 @@ D_DMD_OBJS = \ d/access.dmd.o d/array.dmd.o d/attrib.dmd.o d/cast.dmd.o d/class.dmd.o d/cond.dmd.o d/constfold.dmd.o d/dchar.dmd.o d/declaration.dmd.o d/doc.dmd.o \ - d/dsymbol.dmd.o d/dump.dmd.o d/entity.dmd.o d/enum.dmd.o d/expression.dmd.o d/func.dmd.o d/gnuc.dmd.o d/html.dmd.o d/identifier.dmd.o d/import.dmd.o \ + d/dsymbol.dmd.o d/dump.dmd.o d/entity.dmd.o d/enum.dmd.o d/expression.dmd.o d/func.dmd.o d/gnuc.dmd.o d/hdrgen.dmd.o d/html.dmd.o d/identifier.dmd.o d/import.dmd.o \ d/init.dmd.o d/inline.dmd.o d/lexer.dmd.o d/lstring.dmd.o d/macro.dmd.o d/mangle.dmd.o d/mem.dmd.o d/mtype.dmd.o d/module.dmd.o d/opover.dmd.o d/optimize.dmd.o d/parse.dmd.o \ d/root.dmd.o d/scope.dmd.o d/statement.dmd.o d/staticassert.dmd.o d/stringtable.dmd.o d/struct.dmd.o d/template.dmd.o \ d/todt.dmd.o d/toobj.dmd.o d/typinf.dmd.o d/unialpha.dmd.o d/utf.dmd.o d/version.dmd.o diff -uNr gdc-0.17/d/patch-gcc-4.0.x gdc-0.18/d/patch-gcc-4.0.x --- gdc-0.17/d/patch-gcc-4.0.x 2005-11-05 15:12:01.000000000 +0100 +++ gdc-0.18/d/patch-gcc-4.0.x 2006-05-26 02:57:54.000000000 +0200 @@ -431,3 +431,17 @@ /* Specify a value to compute along with its corresponding cleanup. Operand 0 is the cleanup expression. The cleanup is executed by the first enclosing CLEANUP_POINT_EXPR, +diff -cr gcc-orig/real.c gcc/real.c +*** gcc-orig/real.c Mon Sep 19 12:56:24 2005 +--- gcc/real.c Tue Apr 25 21:18:32 2006 +*************** +*** 2205,2210 **** +--- 2205,2212 ---- + np2 = SIGNIFICAND_BITS - fmt->p * fmt->log2_b; + memset (r->sig, -1, SIGSZ * sizeof (unsigned long)); + clear_significand_below (r, np2); ++ if (REAL_MODE_FORMAT_COMPOSITE_P (mode)) ++ clear_significand_bit (r, SIGNIFICAND_BITS - fmt->pnan - 1); + } + + /* Fills R with 2**N. */ diff -uNr gdc-0.17/d/phobos/acinclude.m4 gdc-0.18/d/phobos/acinclude.m4 --- gdc-0.17/d/phobos/acinclude.m4 2005-05-29 23:09:19.000000000 +0200 +++ gdc-0.18/d/phobos/acinclude.m4 2006-05-18 03:01:42.000000000 +0200 @@ -43,8 +43,12 @@ fi LIBS="$LIBS $d_thread_lib" -dnl BSD socket configuration. Since there is only Windows vs. Unix -dnl configuration for std.socket... +dnl BSD socket configuration + +AC_CHECK_TYPES([socklen_t, siginfo_t],[],[],[ +#include +#include +#include ]) AC_MSG_CHECKING([for sa_len]) AC_TRY_COMPILE([ @@ -117,6 +121,9 @@ mach) DCFG_SEMAPHORE_IMPL="GNU_Semaphore_Mach" d_module_mach=1 ;; pthreads) DCFG_SEMAPHORE_IMPL="GNU_Sempahore_Pthreads" ;; + skyos) DCFG_SEMAPHORE_IMPL="GNU_Sempahore_Pthreads" + D_EXTRA_OBJS="$D_EXTRA_OBJS std/c/skyos/compat.o" + ;; *) AC_MSG_ERROR([No usable semaphore implementation]) ;; esac else @@ -135,10 +142,15 @@ AC_DEFINE(PHOBOS_USE_PTHREADS,1,[Define if using pthreads]) -RECLS_CXXFLAGS="$RECLS_CXXFLAGS -Dunix" -D_RECLS_OS=unix +AC_CHECK_FUNC(mmap,DCFG_MMAP="GNU_Unix_Have_MMap",[]) + +AC_CHECK_FUNC(getpwnam_r,DCFG_GETPWNAM_R="GNU_Unix_Have_getpwnam_r",[]) + D_EXTRA_OBJS="gcc/configunix.o gcc/cbridge_fdset.o std/c/unix/unix.o $D_EXTRA_OBJS" +# Add "linux" module for compatibility even if not Linux +D_EXTRA_OBJS="std/c/linux/linux.o $D_EXTRA_OBJS" +D_PREREQ_SRCS="$D_PREREQ_SRCS "'$(configunix_d_src)' DCFG_UNIX="Unix" ]) @@ -152,7 +164,7 @@ d_gc_stack= d_gc_data= -case "$target_os" in +case "$d_target_os" in aix*) d_gc_data="$d_gc_data GC_Use_Data_Fixed" ;; cygwin*) d_gc_data="$d_gc_data GC_Use_Data_Fixed" @@ -171,6 +183,8 @@ d_gc_data="$d_gc_data GC_Use_Data_Fixed" #have_proc_maps=1 ;; + skyos*) d_gc_data="$d_gc_data GC_Use_Data_Fixed" + ;; *) D_GC_MODULES=internal/gc/gcgcc.o ;; esac @@ -179,8 +193,15 @@ AC_CHECK_FUNC(mmap,d_gc_alloc=GC_Use_Alloc_MMap,[]) fi if test -z "$d_gc_alloc"; then - AC_MSG_ERROR([No usable memory allocation routine]) + AC_CHECK_FUNC(valloc,d_gc_alloc=GC_Use_Alloc_Valloc,[]) +fi +if test -z "$d_gc_alloc"; then + # Use malloc as a fallback + d_gc_alloc=GC_Use_Alloc_Malloc fi +#if test -z "$d_gc_alloc"; then +# AC_MSG_ERROR([No usable memory allocation routine]) +#fi if test -z "$d_gc_stack"; then AC_MSG_CHECKING([for __libc_stack_end]) @@ -223,4 +244,4 @@ for m in $d_gc_data; do f="$f -fversion=$m"; done D_GC_FLAGS=$f -]) \ No newline at end of file +]) diff -uNr gdc-0.17/d/phobos/aclocal.m4 gdc-0.18/d/phobos/aclocal.m4 --- gdc-0.17/d/phobos/aclocal.m4 2005-05-29 23:09:19.000000000 +0200 +++ gdc-0.18/d/phobos/aclocal.m4 2006-03-12 15:56:29.000000000 +0100 @@ -1,7 +1,7 @@ -# aclocal.m4 generated automatically by aclocal 1.6.3 -*- Autoconf -*- +# generated automatically by aclocal 1.9.5 -*- Autoconf -*- -# Copyright 1996, 1997, 1998, 1999, 2000, 2001, 2002 -# Free Software Foundation, Inc. +# Copyright (C) 1996, 1997, 1998, 1999, 2000, 2001, 2002, 2003, 2004, +# 2005 Free Software Foundation, Inc. # This file is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. @@ -11,229 +11,4 @@ # even the implied warranty of MERCHANTABILITY or FITNESS FOR A # PARTICULAR PURPOSE. -dnl Unix-specific configuration -AC_DEFUN(DPHOBOS_CONFIGURE_UNIX,[ - -AC_CHECK_HEADERS(pthread.h,:, - [AC_MSG_ERROR([can't find pthread.h. Pthreads is the only supported thread library.])]) - -AC_MSG_CHECKING([for recursive mutex name]) -AC_TRY_COMPILE([#include ],[ -pthread_mutexattr_t attr; -pthread_mutexattr_settype(&attr, PTHREAD_MUTEX_RECURSIVE);], - [AC_DEFINE(HAVE_PTHREAD_MUTEX_RECURSIVE,1,[Determines how to declared recursive mutexes]) - AC_MSG_RESULT([PTHREAD_MUTEX_RECURSIVE])], - [AC_MSG_RESULT([PTHREAD_MUTEX_RECURSIVE_NP])]) - -dnl -pthread doesn't work because, by putting it in specs, it is passed -dnl to the linker instead of being interpreted by the driver... -dnl -lc_r ins't quite right because there is also a -lc_r_p -# -pthread - -if test -z "$d_thread_lib"; then - AC_MSG_CHECKING([for thread library linker argument]) - d_thread_lib=error - for thrd_lib in "" -lc_r -lpthread -ldce; do - d_savelibs=$LIBS - LIBS="$LIBS $thrd_lib" - - AC_TRY_LINK([#include ],[ - pthread_create(0,0,0,0);], - [d_thread_lib=$thrd_lib], - :) - - LIBS=$d_savelibs - - if test "$d_thread_lib" != "error"; then - break - fi - done - case "$d_thread_lib" in - error) AC_MSG_ERROR([Not found! You may need to use --enable-thread-lib]) ;; - -*) AC_MSG_RESULT([$d_thread_lib]) ;; - *) AC_MSG_RESULT([none needed]) ;; - esac -fi -LIBS="$LIBS $d_thread_lib" - -dnl BSD socket configuration. Since there is only Windows vs. Unix -dnl configuration for std.socket... - -AC_MSG_CHECKING([for sa_len]) -AC_TRY_COMPILE([ -#include -#include ],[ -struct sockaddr s; s.sa_len = 0;], - [AC_MSG_RESULT([yes]) - DCFG_SA_LEN=GNU_BsdSockets_salen], - [AC_MSG_RESULT([no]) - DCFG_SA_LEN=""]) - -if test -n "$DCFG_SA_LEN"; then - AC_MSG_CHECKING([size of sa_len]) - AC_TRY_COMPILE([ -#include -#include ],[ - struct sockaddr s; - struct Test { - int x: sizeof(s.sa_len)==1; - };], - [AC_MSG_RESULT([one byte])], - [AC_MSG_RESULT([not one byte]) - AC_MSG_ERROR([Can not handle layout of sockaddr. Please report this so your system can be supported.])]) -else - AC_MSG_CHECKING([size of sa_family]) - AC_TRY_COMPILE([ -#include -#include ],[ - struct sockaddr s; - struct Test { - int x: sizeof(s.sa_family)==2; - };], - [AC_MSG_RESULT([two bytes])], - [AC_MSG_RESULT([not two bytes]) - AC_MSG_ERROR([Can not handle layout of sockaddr. Please report this so your system can be supported.])]) -fi - -AC_SEARCH_LIBS(sem_init, pthread rt posix4) - -DCFG_PTHREAD_SUSPEND= -AC_SUBST(DCFG_PTHREAD_SUSPEND) - -if true; then - AC_CHECK_HEADERS(semaphore.h) - AC_CHECK_FUNC(sem_init) - AC_CHECK_FUNC(semaphore_create) - AC_CHECK_FUNC(pthread_cond_wait) - - if test -z "$d_sem_impl"; then - # Probably need to test what actually works. sem_init is defined - # on AIX and Darwin but does not actually work. - # For now, test for Mach semaphores first so it overrides Posix. AIX - # is a special case. - if test "$ac_cv_func_semaphore_create" = "yes"; then - d_sem_impl="mach" - elif test "$ac_cv_func_sem_init" = "yes" && \ - test "$ac_cv_header_semaphore_h" = "yes" && \ - test -z "$d_is_aix"; then - d_sem_impl="posix" - elif test "$ac_cv_func_pthread_cond_wait" = "yes"; then - d_sem_impl="pthreads" - fi - fi - - dnl TODO: change this to using pthreads? if so, define usepthreads - dnl and configure semaphore - - case "$d_sem_impl" in - posix) DCFG_SEMAPHORE_IMPL="GNU_Semaphore_POSIX" ;; - mach) DCFG_SEMAPHORE_IMPL="GNU_Semaphore_Mach" - d_module_mach=1 ;; - pthreads) DCFG_SEMAPHORE_IMPL="GNU_Sempahore_Pthreads" ;; - *) AC_MSG_ERROR([No usable semaphore implementation]) ;; - esac -else - dnl Need to be able to query thread state for this method to be useful - AC_CHECK_FUNC(pthread_suspend_np) - AC_CHECK_FUNC(pthread_continue_np) - - if test "$ac_cv_func_pthread_suspend_np" = "yes" && \ - test "$ac_cv_func_pthread_continue_np" = "yes" ; then - # TODO: need to test that these actually work. - DCFG_PTHREAD_SUSPEND=GNU_pthread_suspend - else - AC_MSG_ERROR([TODO]) - fi -fi - -AC_DEFINE(PHOBOS_USE_PTHREADS,1,[Define if using pthreads]) - -RECLS_CXXFLAGS="$RECLS_CXXFLAGS -Dunix" -D_RECLS_OS=unix - -D_EXTRA_OBJS="gcc/configunix.o gcc/cbridge_fdset.o std/c/unix/unix.o $D_EXTRA_OBJS" -DCFG_UNIX="Unix" - -]) - -dnl Garbage collection configuration -AC_DEFUN(DPHOBOS_CONFIGURE_GC, [ - -D_GC_MODULES=internal/gc/gcgcc.o - -d_gc_alloc= -d_gc_stack= -d_gc_data= - -case "$target_os" in - aix*) d_gc_data="$d_gc_data GC_Use_Data_Fixed" - ;; - cygwin*) d_gc_data="$d_gc_data GC_Use_Data_Fixed" - ;; - darwin*) D_GC_MODULES="$D_GC_MODULES internal/gc/gc_dyld.o" - d_gc_stack=GC_Use_Stack_Fixed - d_gc_data="$d_gc_data GC_Use_Data_Dyld" - ;; - freebsd*) D_GC_MODULES="$D_GC_MODULES internal/gc/gc_freebsd.o" - d_gc_stack=GC_Use_Stack_FreeBSD - d_gc_data="$d_gc_data GC_Use_Data_Fixed" - dnl maybe just GC_Use_Stack_ExternC - ;; - linux*) - #d_gc_stack=GC_Use_Stack_Proc_Stat - d_gc_data="$d_gc_data GC_Use_Data_Fixed" - #have_proc_maps=1 - ;; - *) D_GC_MODULES=internal/gc/gcgcc.o - ;; -esac - -if test -z "$d_gc_alloc"; then - AC_CHECK_FUNC(mmap,d_gc_alloc=GC_Use_Alloc_MMap,[]) -fi -if test -z "$d_gc_alloc"; then - AC_MSG_ERROR([No usable memory allocation routine]) -fi - -if test -z "$d_gc_stack"; then - AC_MSG_CHECKING([for __libc_stack_end]) - AC_TRY_LINK([],[ - extern long __libc_stack_end; - return __libc_stack_end == 0;], - [AC_MSG_RESULT(yes) - d_gc_stack=GC_Use_Stack_GLibC], - [AC_MSG_RESULT(no)]) -fi -if test -z "$d_gc_stack"; then - d_gc_stack=GC_Use_Stack_Guess - D_GC_MODULES="$D_GC_MODULES internal/gc/gc_guess_stack.o" -fi -if test -z "$d_gc_stack"; then - AC_MSG_ERROR([No usable stack origin information]) -fi - -dnl if test -z "$d_gc_data"; then -dnl AC_MSG_CHECKING([for __data_start and _end]) -dnl AC_TRY_LINK([],[ -dnl extern int __data_start; -dnl extern int _end; -dnl return & _end - & __data_start;], -dnl [AC_MSG_RESULT(yes) -dnl d_gc_data="$d_gc_data GC_Use_Data_Data_Start_End"], -dnl [AC_MSG_RESULT(no)]) -dnl fi -if test -n "$have_proc_maps" && test "$enable_proc_maps" = auto; then - enable_proc_maps=yes -fi -if test "$enable_proc_maps" = yes; then - d_gc_data="$d_gc_data GC_Use_Data_Proc_Maps" -fi -if test -z "$d_gc_data"; then - AC_MSG_ERROR([No usable data segment information]) -fi - -f="-fversion=$d_gc_alloc -fversion=$d_gc_stack" -for m in $d_gc_data; do f="$f -fversion=$m"; done -D_GC_FLAGS=$f - -]) +m4_include([acinclude.m4]) diff -uNr gdc-0.17/d/phobos/crc32.d gdc-0.18/d/phobos/crc32.d --- gdc-0.17/d/phobos/crc32.d 2004-10-26 02:41:27.000000000 +0200 +++ gdc-0.18/d/phobos/crc32.d 2006-03-12 23:08:56.000000000 +0100 @@ -12,7 +12,7 @@ */ // CRC-32 calculation -module crc; +module crc32; private uint[256] crc32_table = [ diff -uNr gdc-0.17/d/phobos/etc/c/recls/linux.mak gdc-0.18/d/phobos/etc/c/recls/linux.mak --- gdc-0.17/d/phobos/etc/c/recls/linux.mak 2004-10-26 02:41:27.000000000 +0200 +++ gdc-0.18/d/phobos/etc/c/recls/linux.mak 1970-01-01 01:00:00.000000000 +0100 @@ -1,80 +0,0 @@ -# ############################################################################## -# File: makefile.unix -# -# Purpose: GCC 3.2+ makefile for the recls library (std.recls) -# -# Created: 24th November 2003 -# Updated: 24th November 2003 -# -# Copyright: Synesis Software Pty Ltd, (c) 2003. All rights reserved. -# -# Home: www.synesis.com.au/software -# -# ############################################################################## - -# ############################################################################## -# Macros - -CC = g++ -LD = g++ -AR = ar - -RECLS_INCLUDE = . -RECLS_LIBDIR = . -RECLS_SRCDIR = . - -STLSOFT_RECLS_PATCH_INCLUDE = #$(RECLS_INCLUDE) - -STLSOFT_INCLUDE = ../stlsoft - -F_WARN_ALL = -Wall -F_WARN_AS_ERR = # -F_OPT_SPEED = -O4 -F_TARG_PENTIUM = -mcpu=i686 -F_NOLOGO = - - -CCFLAGS = $(F_WARN_ALL) $(F_WARN_AS_ERR) $(F_OPT_SPEED) $(F_TARG_PENTIUM) $(F_NOLOGO) -CCDEFS = -DNDEBUG -DUNIX -D_M_IX86 - -CCARGS = $(CCFLAGS) $(CCDEFS) -c -I. -I$(STLSOFT_INCLUDE) - -################################################################################ -# Objects - -OBJS_C = \ - ./recls_api.o \ - ./recls_fileinfo.o \ - ./recls_internal.o \ - ./recls_util.o \ - ./recls_api_unix.o \ - ./recls_fileinfo_unix.o \ - ./recls_util_unix.o - - -################################################################################ -# Suffix rules - -.c.o: - $(CC) $(CCARGS) -o$@ $? - -.cpp.o: - $(CC) $(CCARGS) -o$@ $? - -################################################################################ -# Targets - -target: $(RECLS_LIBDIR)/librecls.a - -clean: - @echo Cleaning targets - @rm -f $(RECLS_LIBDIR)/librecls.a - @rm -f $(OBJS_C) - @rm -f *.map - -# executables - -$(RECLS_LIBDIR)/librecls.a: $(OBJS_C) - $(AR) -r $@ $(OBJS_C) - -################################################################################ diff -uNr gdc-0.17/d/phobos/etc/c/recls/recls_api.cpp gdc-0.18/d/phobos/etc/c/recls/recls_api.cpp --- gdc-0.17/d/phobos/etc/c/recls/recls_api.cpp 2004-10-26 02:41:27.000000000 +0200 +++ gdc-0.18/d/phobos/etc/c/recls/recls_api.cpp 1970-01-01 01:00:00.000000000 +0100 @@ -1,382 +0,0 @@ -/* ///////////////////////////////////////////////////////////////////////////// - * File: recls_api.cpp - * - * Purpose: Main (platform-independent) implementation file for the recls API. - * - * Created: 16th August 2003 - * Updated: 27th November 2003 - * - * License: (Licensed under the Synesis Software Standard Source License) - * - * Copyright (C) 2002-2003, Synesis Software Pty Ltd. - * - * All rights reserved. - * - * www: http://www.synesis.com.au/software - * http://www.recls.org/ - * - * email: submissions@recls.org for submissions - * admin@recls.org for other enquiries - * - * Redistribution and use in source and binary forms, with or - * without modification, are permitted provided that the following - * conditions are met: - * - * (i) Redistributions of source code must retain the above - * copyright notice and contact information, this list of - * conditions and the following disclaimer. - * - * (ii) Any derived versions of this software (howsoever modified) - * remain the sole property of Synesis Software. - * - * (iii) Any derived versions of this software (howsoever modified) - * remain subject to all these conditions. - * - * (iv) Neither the name of Synesis Software nor the names of any - * subdivisions, employees or agents of Synesis Software, nor the - * names of any other contributors to this software may be used to - * endorse or promote products derived from this software without - * specific prior written permission. - * - * This source code is provided by Synesis Software "as is" and any - * warranties, whether expressed or implied, including, but not - * limited to, the implied warranties of merchantability and - * fitness for a particular purpose are disclaimed. In no event - * shall the Synesis Software be liable for any direct, indirect, - * incidental, special, exemplary, or consequential damages - * (including, but not limited to, procurement of substitute goods - * or services; loss of use, data, or profits; or business - * interruption) however caused and on any theory of liability, - * whether in contract, strict liability, or tort (including - * negligence or otherwise) arising in any way out of the use of - * this software, even if advised of the possibility of such - * damage. - * - * ////////////////////////////////////////////////////////////////////////// */ - - -/* ///////////////////////////////////////////////////////////////////////////// - * Includes - */ - -#define RECLS_PURE_API - -#include "recls.h" -#include "recls_internal.h" -#include "recls_assert.h" - -#include - -#include "recls_debug.h" - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace - */ - -#if !defined(RECLS_NO_NAMESPACE) -namespace recls -{ -#endif /* !RECLS_NO_NAMESPACE */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Search control - */ - -/** Closes the given search */ -RECLS_FNDECL(void) Recls_SearchClose(hrecls_t hSrch) -{ - function_scope_trace("Recls_SearchClose"); - - ReclsSearchInfo *si = ReclsSearchInfo::FromHandle(hSrch); - - recls_assert(NULL != si); - - delete si; -} - -/* ///////////////////////////////////////////////////////////////////////////// - * Search enumeration - */ - -RECLS_FNDECL(recls_rc_t) Recls_SearchProcess( recls_char_t const *searchRoot - , recls_char_t const *pattern - , recls_uint32_t flags - , hrecls_process_fn_t pfn - , recls_process_fn_param_t param) -{ - function_scope_trace("Recls_SearchProcess"); - - recls_assert(NULL != pfn); - - hrecls_t hSrch; - recls_rc_t rc = Recls_Search(searchRoot, pattern, flags, &hSrch); - - if(RECLS_SUCCEEDED(rc)) - { - recls_info_t info; - - do - { - rc = Recls_GetDetails(hSrch, &info); - - if(RECLS_FAILED(rc)) - { - break; - } - else - { - int res = (*pfn)(info, param); - - Recls_CloseDetails(info); - - if(0 == res) - { - break; - } - } - } - while(RECLS_SUCCEEDED(rc = Recls_GetNext(hSrch))); - - Recls_SearchClose(hSrch); - } - - if(RECLS_RC_NO_MORE_DATA == rc) - { - rc = RECLS_RC_OK; - } - - return rc; -} - -RECLS_FNDECL(recls_rc_t) Recls_GetNext(hrecls_t hSrch) -{ - function_scope_trace("Recls_GetNext"); - - ReclsSearchInfo *si = ReclsSearchInfo::FromHandle(hSrch); - - recls_assert(NULL != si); - - return si->GetNext(); -} - -RECLS_FNDECL(recls_rc_t) Recls_GetDetails( hrecls_t hSrch - , recls_info_t *pinfo) -{ - function_scope_trace("Recls_GetDetails"); - - ReclsSearchInfo *si = ReclsSearchInfo::FromHandle(hSrch); - - recls_assert(NULL != si); - recls_assert(NULL != pinfo); - - return si->GetDetails(pinfo); -} - -RECLS_FNDECL(recls_rc_t) Recls_GetNextDetails( hrecls_t hSrch - , recls_info_t *pinfo) -{ - function_scope_trace("Recls_GetNextDetails"); - - ReclsSearchInfo *si = ReclsSearchInfo::FromHandle(hSrch); - - recls_assert(NULL != si); - - return si->GetNextDetails(pinfo); -} - -/*************************************** - * File entry info structure - */ - -RECLS_FNDECL(void) Recls_CloseDetails(recls_info_t fileInfo) -{ - function_scope_trace("Recls_CloseDetails"); - - recls_assert(NULL != fileInfo); - - FileInfo_Release(fileInfo); -} - -RECLS_FNDECL(recls_rc_t) Recls_CopyDetails( recls_info_t fileInfo - , recls_info_t *pinfo) -{ - function_scope_trace("Recls_CopyDetails"); - - recls_assert(NULL != fileInfo); - - return FileInfo_Copy(fileInfo, pinfo); -} - -RECLS_FNDECL(recls_rc_t) Recls_OutstandingDetails( hrecls_t hSrch - , recls_uint32_t *count) -{ - function_scope_trace("Recls_OutstandingDetails"); - - ReclsSearchInfo *si = ReclsSearchInfo::FromHandle(hSrch); - - recls_assert(NULL != si); - recls_assert(NULL != count); - STLSOFT_SUPPRESS_UNUSED(si); - - recls_sint32_t cCreated; - recls_sint32_t cShared; - - FileInfo_BlockCount(&cCreated, &cShared); - - *count = cCreated; - - return RECLS_RC_OK; -} - -/* ///////////////////////////////////////////////////////////////////////////// - * Error handling - */ - -RECLS_FNDECL(recls_rc_t) Recls_GetLastError(hrecls_t hSrch) -{ - function_scope_trace("Recls_GetLastError"); - - ReclsSearchInfo *si = ReclsSearchInfo::FromHandle(hSrch); - - recls_assert(NULL != si); - - return si->GetLastError(); -} - -RECLS_FNDECL(size_t) Recls_GetLastErrorString( hrecls_t hSrch - , recls_char_t *buffer - , size_t cchBuffer) -{ - function_scope_trace("Recls_GetLastErrorString"); - - return Recls_GetErrorString(Recls_GetLastError(hSrch), buffer, cchBuffer); -} - -/* ///////////////////////////////////////////////////////////////////////////// - * Property elicitation - */ - -RECLS_FNDECL(size_t) Recls_GetPathProperty( recls_info_t fileInfo - , recls_char_t *buffer - , size_t cchBuffer) -{ - function_scope_trace("Recls_GetPathProperty"); - - recls_assert(NULL != fileInfo); - - return Recls_GetStringProperty_(&fileInfo->path, buffer, cchBuffer); -} - -RECLS_FNDECL(size_t) Recls_GetDirectoryProperty( recls_info_t fileInfo - , recls_char_t *buffer - , size_t cchBuffer) -{ - function_scope_trace("Recls_GetDirectoryProperty"); - - recls_assert(NULL != fileInfo); - - return Recls_GetStringProperty_(&fileInfo->directory, buffer, cchBuffer); -} - -RECLS_FNDECL(size_t) Recls_GetFileProperty( recls_info_t fileInfo - , recls_char_t *buffer - , size_t cchBuffer) -{ - function_scope_trace("Recls_GetFileProperty"); - - recls_assert(NULL != fileInfo); - - struct recls_strptrs_t file = - { - fileInfo->fileName.begin /* File is defined by start of fileName ... */ - , fileInfo->fileExt.end /* ... to end of fileExt. */ - }; - - return Recls_GetStringProperty_(&file, buffer, cchBuffer); -} - -RECLS_FNDECL(size_t) Recls_GetFileNameProperty( recls_info_t fileInfo - , recls_char_t *buffer - , size_t cchBuffer) -{ - function_scope_trace("Recls_GetFileNameProperty"); - - recls_assert(NULL != fileInfo); - - return Recls_GetStringProperty_(&fileInfo->fileName, buffer, cchBuffer); -} - -RECLS_FNDECL(size_t) Recls_GetFileExtProperty( recls_info_t fileInfo - , recls_char_t *buffer - , size_t cchBuffer) -{ - function_scope_trace("Recls_GetFileExtProperty"); - - recls_assert(NULL != fileInfo); - - return Recls_GetStringProperty_(&fileInfo->fileExt, buffer, cchBuffer); -} - -RECLS_FNDECL(size_t) Recls_GetDirectoryPartProperty( recls_info_t fileInfo - , int part - , recls_char_t *buffer - , size_t cchBuffer) -{ - function_scope_trace("Recls_GetDirectoryPartProperty"); - - recls_assert(NULL != fileInfo); - - size_t cParts = fileInfo->directoryParts.end - fileInfo->directoryParts.begin; - -//debug_printf("%s: %u parts\n", fileInfo->path.begin, cParts); - - if(part < 0) - { - return cParts; - } - else - { - recls_assert(static_cast(part) < cParts); - - return Recls_GetStringProperty_(&fileInfo->directoryParts.begin[part], buffer, cchBuffer); - } -} - -RECLS_FNDECL(void) Recls_GetSizeProperty( recls_info_t fileInfo - , recls_filesize_t *size) -{ - function_scope_trace("Recls_GetSizeProperty"); - - recls_assert(NULL != fileInfo); - recls_assert(NULL != size); - - *size = fileInfo->size; -} - -RECLS_FNDECL(recls_time_t) Recls_GetModificationTime(recls_info_t fileInfo) -{ - function_scope_trace("Recls_GetModificationTime"); - - recls_assert(NULL != fileInfo); - - return fileInfo->modificationTime; -} - -RECLS_FNDECL(recls_time_t) Recls_GetLastAccessTime(recls_info_t fileInfo) -{ - function_scope_trace("Recls_GetLastAccessTime"); - - recls_assert(NULL != fileInfo); - - return fileInfo->lastAccessTime; -} - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace - */ - -#if !defined(RECLS_NO_NAMESPACE) -} /* namespace recls */ -#endif /* !RECLS_NO_NAMESPACE */ - -/* ////////////////////////////////////////////////////////////////////////// */ diff -uNr gdc-0.17/d/phobos/etc/c/recls/recls_api_unix.cpp gdc-0.18/d/phobos/etc/c/recls/recls_api_unix.cpp --- gdc-0.17/d/phobos/etc/c/recls/recls_api_unix.cpp 2004-10-26 02:41:27.000000000 +0200 +++ gdc-0.18/d/phobos/etc/c/recls/recls_api_unix.cpp 1970-01-01 01:00:00.000000000 +0100 @@ -1,1045 +0,0 @@ -/* ///////////////////////////////////////////////////////////////////////////// - * File: recls_api_unix.cpp - * - * Purpose: Win32 implementation file for the recls API. - * - * Created: 16th August 2003 - * Updated: 27th November 2003 - * - * License: (Licensed under the Synesis Software Standard Source License) - * - * Copyright (C) 2002-2003, Synesis Software Pty Ltd. - * - * All rights reserved. - * - * www: http://www.synesis.com.au/software - * http://www.recls.org/ - * - * email: submissions@recls.org for submissions - * admin@recls.org for other enquiries - * - * Redistribution and use in source and binary forms, with or - * without modification, are permitted provided that the following - * conditions are met: - * - * (i) Redistributions of source code must retain the above - * copyright notice and contact information, this list of - * conditions and the following disclaimer. - * - * (ii) Any derived versions of this software (howsoever modified) - * remain the sole property of Synesis Software. - * - * (iii) Any derived versions of this software (howsoever modified) - * remain subject to all these conditions. - * - * (iv) Neither the name of Synesis Software nor the names of any - * subdivisions, employees or agents of Synesis Software, nor the - * names of any other contributors to this software may be used to - * endorse or promote products derived from this software without - * specific prior written permission. - * - * This source code is provided by Synesis Software "as is" and any - * warranties, whether expressed or implied, including, but not - * limited to, the implied warranties of merchantability and - * fitness for a particular purpose are disclaimed. In no event - * shall the Synesis Software be liable for any direct, indirect, - * incidental, special, exemplary, or consequential damages - * (including, but not limited to, procurement of substitute goods - * or services; loss of use, data, or profits; or business - * interruption) however caused and on any theory of liability, - * whether in contract, strict liability, or tort (including - * negligence or otherwise) arising in any way out of the use of - * this software, even if advised of the possibility of such - * damage. - * - * ////////////////////////////////////////////////////////////////////////// */ - - -/* ///////////////////////////////////////////////////////////////////////////// - * Includes - */ - -#include "recls.h" -#include "recls_internal.h" -#include "recls_assert.h" -#include "recls_util.h" - -#include - -#include -#include - -# include -# include - -#include "recls_debug.h" - -#include - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace - */ - -#if !defined(RECLS_NO_NAMESPACE) -namespace recls -{ -#endif /* !RECLS_NO_NAMESPACE */ - -unixstl_ns_using(glob_sequence) - -typedef unixstl_ns_qual(filesystem_traits) traits_type; // We need to do this, because VC is a bit thick - -/* ///////////////////////////////////////////////////////////////////////////// - * Utility functions - */ - -#if defined(_DEBUG) && \ - defined(RECLS_PLATFORM_IS_WIN32) - -/* static */ tls_index function_scope::sm_index; - -#endif /* _DEBUG */ - -/* ////////////////////////////////////////////////////////////////////////// */ - -static recls_info_t create_entryinfo_from_psrecord(recls_char_t const * /* rootDir */, recls_uint32_t flags, recls_char_t const *entry) -{ - typedef recls_char_t char_type; - - recls_char_t rootDir[PATH_MAX]; - recls_char_t entryName[PATH_MAX]; - recls_char_t *name_start; - - traits_type::str_copy(rootDir, entry); - name_start = strrchr(rootDir, '/'); - traits_type::str_copy(entryName, ++name_start); - *name_start = '\0'; - - function_scope_trace("create_entryinfo_from_psrecord"); - - // size of structure is: - // - // offsetof(struct recls_fileinfo_t, data) - // + directory parts - // + full path (+ null) - // + short name (+ null) - - size_t cchRootDir = traits_type::str_len(rootDir); - -// recls_assert(cchRootDir > 0); -// recls_assert(rootDir[cchRootDir - 1] == traits_type::path_name_separator()); - - size_t cchFileName = traits_type::str_len(entryName); - size_t cDirParts = ((flags & RECLS_F_DIRECTORY_PARTS) == RECLS_F_DIRECTORY_PARTS) ? count_dir_parts(rootDir, rootDir + cchRootDir) : 0; - size_t cbPath = align_up_size(sizeof(char_type) * (1 + cchRootDir + cchFileName)); - size_t cb = offsetof(struct recls_fileinfo_t, data) - + cDirParts * sizeof(recls_strptrs_t) - + cbPath; - - struct recls_fileinfo_t *info = const_cast(FileInfo_Allocate(cb)); - - if(NULL != info) - { - char_type *fullPath = (char_type*)&info->data[cDirParts * sizeof(recls_strptrs_t)]; -// char_type *altName = (char_type*)&info->data[cDirParts * sizeof(recls_strptrs_t) + cbPath]; - - // full path - traits_type::str_copy(fullPath, rootDir); - traits_type::str_cat(fullPath, entryName); - info->path.begin = fullPath; - info->path.end = fullPath + cchRootDir + cchFileName; - - // directory, file (name + ext) - info->directory.begin = fullPath; - info->directory.end = fullPath + cchRootDir; - info->fileName.begin = info->directory.end; - info->fileName.end = strrchr(info->directory.end, '.'); - if(NULL != info->fileName.end) - { - info->fileExt.begin = info->fileName.end + 1; - info->fileExt.end = info->directory.end + cchFileName; - } - else - { - info->fileName.end = info->directory.end + cchFileName; - info->fileExt.begin = info->directory.end + cchFileName; - info->fileExt.end = info->directory.end + cchFileName; - } - - // determine the directory parts - char_type const *p = info->directory.begin; - char_type const *l = info->directory.end; - struct recls_strptrs_t *begin = (struct recls_strptrs_t*)&info->data[0]; - - info->directoryParts.begin = begin; - info->directoryParts.end = begin + cDirParts; - - if(info->directoryParts.begin != info->directoryParts.end) - { - recls_assert((flags & RECLS_F_DIRECTORY_PARTS) == RECLS_F_DIRECTORY_PARTS); - - begin->begin = p; - - for(; p != l; ++p) - { - if(*p == traits_type::path_name_separator()) - { - begin->end = p + 1; - - if(++begin != info->directoryParts.end) - { - begin->begin = p + 1; - } - } - } - } - - struct stat st; - - stat(fullPath, &st); - - // attributes - info->attributes = st.st_mode; - - // time, size - info->lastStatusChangeTime = st.st_ctime; - info->modificationTime = st.st_mtime; - info->lastAccessTime = st.st_atime; - info->size = st.st_size; - - // Checks - recls_assert(info->path.begin < info->path.end); - - recls_assert(info->directory.begin < info->directory.end); - recls_assert(info->path.begin <= info->directory.begin); - recls_assert(info->directory.end <= info->path.end); - - recls_assert(info->fileName.begin <= info->fileName.end); - - recls_assert(info->fileExt.begin <= info->fileExt.end); - - recls_assert(info->fileName.begin < info->fileExt.end); - recls_assert(info->fileName.end <= info->fileExt.begin); - } - - return info; -} - -/* ///////////////////////////////////////////////////////////////////////////// - * PlatformDirectoryNode - */ - -class PlatformDirectoryNode - : public ReclsDNode -{ -public: - typedef recls_char_t char_type; - typedef PlatformDirectoryNode class_type; -private: - typedef glob_sequence directory_sequence_t; - typedef glob_sequence entry_sequence_t; - -// Construction -private: - PlatformDirectoryNode(recls_uint32_t flags, char_type const *rootDir, char_type const *pattern); -public: - virtual ~PlatformDirectoryNode(); - - static PlatformDirectoryNode *FindAndCreate(recls_uint32_t flags, char_type const *rootDir, char_type const *pattern); - static PlatformDirectoryNode *FindAndCreate(recls_uint32_t flags, char_type const *rootDir, char_type const *subDir, char_type const *pattern); - -// ReclsDNode methods -private: - virtual recls_rc_t GetNext(); - virtual recls_rc_t GetDetails(recls_info_t *pinfo); - virtual recls_rc_t GetNextDetails(recls_info_t *pinfo); - -// Implementation -private: - recls_rc_t Initialise(); - - recls_bool_t _is_valid() const; - -#if defined(RECLS_COMPILER_IS_BORLAND) - static directory_sequence_t::const_iterator _select_iter(int b, directory_sequence_t::const_iterator trueVal, directory_sequence_t::const_iterator falseVal) - { - // I can't explain it, but Borland does not like the tertiary operator and the copy-ctors of the iterators - if(b) - { - return trueVal; - } - else - { - return falseVal; - } - } -#endif /* !RECLS_COMPILER_IS_BORLAND */ - static int _ssFlags_from_reclsFlags(recls_uint32_t flags) - { - recls_assert(0 == (flags & RECLS_F_LINKS)); // Doesn't work with links - recls_assert(0 == (flags & RECLS_F_DEVICES)); // Doesn't work with devices - - int ssFlags = 0; - - if(0 != (flags & RECLS_F_FILES)) - { - ssFlags |= entry_sequence_t::files; - } - if(0 != (flags & RECLS_F_DIRECTORIES)) - { - ssFlags |= entry_sequence_t::directories; - } - - return ssFlags; - } - -// Members -private: - recls_info_t m_current; - ReclsDNode *m_dnode; - recls_uint32_t const m_flags; - entry_sequence_t m_entries; - entry_sequence_t::const_iterator m_entriesBegin; - directory_sequence_t m_directories; - directory_sequence_t::const_iterator m_directoriesBegin; - char_type m_rootDir[RECLS_PATH_MAX]; - char_type m_pattern[RECLS_PATH_MAX]; -}; - -PlatformDirectoryNode::PlatformDirectoryNode(recls_uint32_t flags, PlatformDirectoryNode::char_type const *rootDir, PlatformDirectoryNode::char_type const *pattern) - : m_current(NULL) - , m_dnode(NULL) - , m_flags(flags) - , m_entries(rootDir, pattern, _ssFlags_from_reclsFlags(flags)) - , m_entriesBegin(m_entries.begin()) -#ifdef _MSC_VER // For testing - , m_directories(rootDir, "*.*", directory_sequence_t::directories) -#else /* ? _MSC_VER */ - , m_directories(rootDir, traits_type::pattern_all(), directory_sequence_t::directories) -#endif /* _MSC_VER */ -#if !defined(RECLS_COMPILER_IS_BORLAND) - , m_directoriesBegin((flags & RECLS_F_RECURSIVE) ? m_directories.begin() : m_directories.end()) -#else - , m_directoriesBegin(_select_iter((flags & RECLS_F_RECURSIVE), m_directories.begin(), m_directories.end())) -#endif /* !RECLS_COMPILER_IS_BORLAND */ -{ - function_scope_trace("PlatformDirectoryNode::PlatformDirectoryNode"); - -#if defined(RECLS_COMPILER_IS_BORLAND) -// m_directoriesBegin = ((flags & RECLS_F_RECURSIVE) ? m_directories.begin() : m_directories.end()); -#endif /* !RECLS_COMPILER_IS_BORLAND */ - - traits_type::str_copy(m_rootDir, rootDir); - traits_type::ensure_dir_end(m_rootDir); - traits_type::str_copy(m_pattern, pattern); - - recls_assert(stlsoft_raw_offsetof(PlatformDirectoryNode, m_entries) < stlsoft_raw_offsetof(PlatformDirectoryNode, m_entriesBegin)); - recls_assert(stlsoft_raw_offsetof(PlatformDirectoryNode, m_directories) < stlsoft_raw_offsetof(PlatformDirectoryNode, m_directoriesBegin)); -} - -inline /* static */ PlatformDirectoryNode *PlatformDirectoryNode::FindAndCreate(recls_uint32_t flags, PlatformDirectoryNode::char_type const *rootDir, PlatformDirectoryNode::char_type const *pattern) -{ - PlatformDirectoryNode *node; - - function_scope_trace("PlatformDirectoryNode::FindAndCreate"); - -#ifdef RECLS_COMPILER_THROWS_ON_NEW_FAIL - try - { -#endif /* RECLS_COMPILER_THROWS_ON_NEW_FAIL */ - node = new PlatformDirectoryNode(flags, rootDir, pattern); -#ifdef RECLS_COMPILER_THROWS_ON_NEW_FAIL - } - catch(std::bad_alloc &) - { - node = NULL; - } -#endif /* RECLS_COMPILER_THROWS_ON_NEW_FAIL */ - - if(NULL != node) - { - // Ensure that it, or one of its sub-nodes, has matching entries. - recls_rc_t rc = node->Initialise(); - - if(RECLS_FAILED(rc)) - { - delete node; - - node = NULL; - } - } - - recls_assert(NULL == node || node->_is_valid()); - - return node; -} - -inline /* static */ PlatformDirectoryNode *PlatformDirectoryNode::FindAndCreate(recls_uint32_t flags, PlatformDirectoryNode::char_type const *rootDir, PlatformDirectoryNode::char_type const *subDir, PlatformDirectoryNode::char_type const *pattern) -{ - char_type compositeDir[RECLS_PATH_MAX]; - - recls_assert(rootDir[traits_type::str_len(rootDir) - 1] == traits_type::path_name_separator()); - - // Only need subdir, since globbing provides partial path - traits_type::str_copy(compositeDir, subDir); - - return FindAndCreate(flags, compositeDir, pattern); -} - -PlatformDirectoryNode::~PlatformDirectoryNode() -{ - function_scope_trace("PlatformDirectoryNode::~PlatformDirectoryNode"); - - FileInfo_Release(m_current); - - delete m_dnode; -} - -recls_rc_t PlatformDirectoryNode::Initialise() -{ - function_scope_trace("PlatformDirectoryNode::Initialise"); - - recls_rc_t rc; - - recls_assert(NULL == m_current); - recls_assert(NULL == m_dnode); - - if(m_entriesBegin != m_entries.end()) - { - // (i) Try getting a file first, - m_current = create_entryinfo_from_psrecord(m_rootDir, m_flags, *m_entriesBegin); - - if(NULL == m_current) - { - rc = RECLS_RC_OUT_OF_MEMORY; - } - else - { - rc = RECLS_RC_OK; - } - } - else - { - if(m_directoriesBegin == m_directories.end()) - { - rc = RECLS_RC_NO_MORE_DATA; - } - else - { - do - { -#if 1 - // The way glob_sequence works - m_dnode = PlatformDirectoryNode::FindAndCreate(m_flags, m_rootDir, *m_directoriesBegin, m_pattern); -#else /* ? 0 */ -// m_dnode = PlatformDirectoryNode::FindAndCreate(m_flags, (*m_directoriesBegin).get_path(), m_pattern); -#endif /* 0 */ - - } while(NULL == m_dnode && ++m_directoriesBegin != m_directories.end()); - - rc = (NULL == m_dnode) ? RECLS_RC_NO_MORE_DATA : RECLS_RC_OK; - } - } - - if(RECLS_SUCCEEDED(rc)) - { - recls_assert(_is_valid()); - } - - return rc; -} - -recls_bool_t PlatformDirectoryNode::_is_valid() const -{ - function_scope_trace("PlatformDirectoryNode::_is_valid"); - - recls_rc_t rc = RECLS_RC_OK; - -#ifdef STLSOFT_CF_PRAGMA_MESSAGE_SUPPORT -# pragma message("Flesh these out") -#endif /* STLSOFT_CF_PRAGMA_MESSAGE_SUPPORT */ - if(RECLS_SUCCEEDED(rc)) - { - - } - - if(RECLS_SUCCEEDED(rc)) - { - } - - if(RECLS_SUCCEEDED(rc)) - { - } - - if(RECLS_SUCCEEDED(rc)) - { - } - - // (i) Either we are enumerating files (m_current != NULL) or directories (m_dnode != NULL), but not both - recls_assert(NULL == m_current || NULL == m_dnode); - // (ii) Either we are enumerating files (m_current != NULL) or there are no more files to enumerate - recls_assert(NULL != m_current || m_entriesBegin == m_entries.end()); - - return RECLS_SUCCEEDED(rc); -} - - -recls_rc_t PlatformDirectoryNode::GetNext() -{ - function_scope_trace("PlatformDirectoryNode::GetNext"); - - recls_assert(_is_valid()); - - /* Searching operates as follows: - * - * 1. Return all the contents of the files - * 2. Return the contents of the directories. - * - * Hence, if m_dnode is non-NULL, we've already searched - */ - - /* States: - * - * - Iterating files: m_entriesBegin != m_entries.end(), m_dnode is NULL, m_directoriesBegin != m_directories.end() - * - Iterating directories: m_directoriesBegin != m_directories.end(), m_dnode is non-NULL, m_current is NULL - * - */ - - // Invariants - - // (i) Either we are enumerating files (m_current != NULL) or directories (m_dnode != NULL), but not both - recls_assert(NULL == m_current || NULL == m_dnode); - // (ii) Either we are enumerating files (m_current != NULL) or there are no more files to enumerate - recls_assert(NULL != m_current || m_entriesBegin == m_entries.end()); - - recls_rc_t rc = RECLS_RC_NO_MORE_DATA; - - if(NULL != m_current) - { - // Currently enumerating through the files - - recls_assert(m_entriesBegin != m_entries.end()); - recls_assert(NULL == m_dnode); - - // Advance, and check for end of sequence - ++m_entriesBegin; - - FileInfo_Release(m_current); - if(m_entriesBegin != m_entries.end()) - { - // Still enumerating, so just update m_current - m_current = create_entryinfo_from_psrecord(m_rootDir, m_flags, *m_entriesBegin); - - rc = RECLS_RC_OK; - } - else - { - // No more left in the files sequence, so delete m_current - m_current = NULL; - - rc = RECLS_RC_NO_MORE_DATA; - } - } - - if(NULL == m_current) - { - // Now we are either enumerating the directories, or we've already done so - - if(NULL != m_dnode) - { - // Currently enumerating the directories - rc = m_dnode->GetNext(); - - if(RECLS_RC_NO_MORE_DATA == rc) - { - ++m_directoriesBegin; - - delete m_dnode; - - m_dnode = NULL; - } - } - - if(m_directoriesBegin == m_directories.end()) - { - // Enumeration is complete. - rc = RECLS_RC_NO_MORE_DATA; - } - else - { - if(NULL == m_dnode) - { - do - { - // Creation of the node will cause it to enter the first enumeration - // state. However, if there are no matching - - recls_assert(m_directoriesBegin != m_directories.end()); - -#if 1 - // The way glob_sequence works - m_dnode = PlatformDirectoryNode::FindAndCreate(m_flags, m_rootDir, *m_directoriesBegin, m_pattern); -#else /* ? 0 */ -// m_dnode = PlatformDirectoryNode::FindAndCreate(m_flags, (*m_directoriesBegin).get_path(), m_pattern); -#endif /* 0 */ - - if(NULL != m_dnode) - { - rc = RECLS_RC_OK; - } - else - { - ++m_directoriesBegin; - } - - } while(NULL == m_dnode && m_directoriesBegin != m_directories.end()); - } - } - } - - recls_assert(_is_valid()); - - return rc; -} - -recls_rc_t PlatformDirectoryNode::GetDetails(recls_info_t *pinfo) -{ - function_scope_trace("PlatformDirectoryNode::GetDetails"); - - recls_assert(_is_valid()); - - recls_rc_t rc; - - recls_assert(NULL != pinfo); - recls_assert(NULL == m_current || NULL == m_dnode); - - if(NULL != m_current) - { - // Currently searching for files from the current directory - - recls_assert(NULL == m_dnode); - - rc = FileInfo_Copy(m_current, pinfo); - -#if defined(_DEBUG) && \ - defined(RECLS_PLATFORM_IS_WIN32) - { - recls_char_t buffer[RECLS_PATH_MAX]; - - Recls_GetPathProperty(m_current, buffer, stlsoft_num_elements(buffer)); - - debug_printf(" [%s]\n", buffer); - } -#endif /* _DEBUG */ - } - else if(NULL != m_dnode) - { - recls_assert(NULL == m_current); - - // Sub-directory searching is active, so get from there. - - rc = m_dnode->GetDetails(pinfo); - } - else - { - // Enumeration has completed - rc = RECLS_RC_NO_MORE_DATA; - } - - recls_assert(_is_valid()); - - return rc; -} - -recls_rc_t PlatformDirectoryNode::GetNextDetails(recls_info_t *pinfo) -{ - function_scope_trace("PlatformDirectoryNode::GetNextDetails"); - - recls_assert(_is_valid()); - recls_assert(NULL != pinfo); - - recls_rc_t rc = GetNext(); - - if(RECLS_SUCCEEDED(rc)) - { - rc = GetDetails(pinfo); - } - - recls_assert(_is_valid()); - - return rc; -} - -/* ///////////////////////////////////////////////////////////////////////////// - * ReclsSearchInfo - */ - -void *ReclsSearchInfo::operator new(size_t cb, int cDirParts, size_t cbRootDir) -{ - function_scope_trace("ReclsSearchInfo::operator new"); - - cbRootDir = align_up_size(cbRootDir); - - recls_assert(cb > stlsoft_raw_offsetof(ReclsSearchInfo, data)); - - cb = stlsoft_raw_offsetof(ReclsSearchInfo, data) - + (cDirParts) * sizeof(recls_strptrs_t) - + cbRootDir; - - return malloc(cb); -} - -#if !defined(RECLS_COMPILER_IS_BORLAND) && \ - !defined(RECLS_COMPILER_IS_DMC) -void ReclsSearchInfo::operator delete(void *pv, int /* cDirParts */, size_t /* cbRootDir */) -{ - function_scope_trace("ReclsSearchInfo::operator delete"); - - free(pv); -} -#endif /* !RECLS_COMPILER_IS_BORLAND && !RECLS_COMPILER_IS_DMC */ - -void ReclsSearchInfo::operator delete(void *pv) -{ - function_scope_trace("ReclsSearchInfo::operator delete"); - - free(pv); -} - -inline /* static */ recls_rc_t ReclsSearchInfo::FindAndCreate(ReclsSearchInfo::char_type const *rootDir, ReclsSearchInfo::char_type const *pattern, recls_uint32_t flags, ReclsSearchInfo **ppsi) -{ - function_scope_trace("ReclsSearchInfo::FindAndCreate"); - - recls_rc_t rc; - ReclsSearchInfo *si; - char_type fullPath[RECLS_PATH_MAX]; - size_t cchFullPath; - - *ppsi = NULL; - - cchFullPath = traits_type::get_full_path_name(rootDir, RECLS_NUM_ELEMENTS(fullPath), fullPath); - if( 0 == cchFullPath || - !file_exists(fullPath)) - { - rc = RECLS_RC_INVALID_DIRECTORY; - } - else - { -#if defined(EMULATE_UNIX_ON_WIN32) - recls_char_t *_fullPath = fullPath; - recls_char_t *fullPath = _fullPath + 2; - - std::replace(fullPath, fullPath + cchFullPath, '\\', traits_type::path_name_separator()); -#endif /* EMULATE_UNIX_ON_WIN32 */ - - traits_type::ensure_dir_end(fullPath); - - size_t lenSearchRoot = traits_type::str_len(fullPath); - - recls_assert(0 < lenSearchRoot); - - rootDir = fullPath; - - // Count the directory parts. This is always done for the ReclsSearchInfo class, since it - // uses them to recurse. - char_type const *begin = rootDir; - char_type const *const end = rootDir + lenSearchRoot; - int cDirParts = count_dir_parts(begin, end); - -#ifdef RECLS_COMPILER_THROWS_ON_NEW_FAIL - try - { -#endif /* RECLS_COMPILER_THROWS_ON_NEW_FAIL */ - si = new(cDirParts, sizeof(char_type) * (1 + lenSearchRoot)) ReclsSearchInfo(cDirParts, rootDir, pattern, flags); -#ifdef RECLS_COMPILER_THROWS_ON_NEW_FAIL - } - catch(std::bad_alloc &) - { - si = NULL; - } -#endif /* RECLS_COMPILER_THROWS_ON_NEW_FAIL */ - - if(NULL == si) - { - rc = RECLS_RC_FAIL; - } - else - { - // This is a nasty hack. It's tantamount to ctor & create function, so - // should be made more elegant soon. - if(NULL == si->m_dnode) - { - delete si; - - si = NULL; - - rc = RECLS_RC_NO_MORE_DATA; - } - else - { - *ppsi = si; - - rc = RECLS_RC_OK; - } - } - } - - return rc; -} - -ReclsSearchInfo::char_type const *ReclsSearchInfo::_calc_rootDir(int cDirParts, ReclsSearchInfo::char_type const *rootDir) -{ - function_scope_trace("ReclsSearchInfo::_calc_rootDir"); - - // Root dir is located after file parts, and before pattern - return traits_type::str_copy((char_type*)&data[cDirParts * sizeof(recls_strptrs_t)], rootDir); -} - -ReclsSearchInfo::ReclsSearchInfo( int cDirParts - , ReclsSearchInfo::char_type const *rootDir - , ReclsSearchInfo::char_type const *pattern - , recls_uint32_t flags) - : m_flags(flags) - , m_lastError(RECLS_RC_OK) - , m_rootDir(_calc_rootDir(cDirParts, rootDir)) -{ - function_scope_trace("ReclsSearchInfo::ReclsSearchInfo"); - - recls_assert(NULL != rootDir); - recls_assert(NULL != pattern); - recls_assert(traits_type::str_len(rootDir) < RECLS_PATH_MAX); - recls_assert(traits_type::str_len(pattern) < RECLS_PATH_MAX); - - // Initialise the directory parts. - - recls_assert(rootDir[1] != ':'); - -// char_type const *p = rootDir; -// struct recls_strptrs_t *begin = (struct recls_strptrs_t*)&data[0]; - - // Now start the search - m_dnode = PlatformDirectoryNode::FindAndCreate(m_flags, rootDir, pattern); -} - -// Operations -recls_rc_t ReclsSearchInfo::GetNext() -{ - function_scope_trace("ReclsSearchInfo::GetNext"); - - recls_assert(NULL != m_dnode); - - m_lastError = m_dnode->GetNext(); - - if(RECLS_RC_NO_MORE_DATA == m_lastError) - { - delete m_dnode; - - m_dnode = NULL; - } - - return m_lastError; -} - -recls_rc_t ReclsSearchInfo::GetDetails(recls_info_t *pinfo) -{ - function_scope_trace("ReclsSearchInfo::GetDetails"); - - recls_assert(NULL != m_dnode); - - return (m_lastError = m_dnode->GetDetails(pinfo)); -} - -recls_rc_t ReclsSearchInfo::GetNextDetails(recls_info_t *pinfo) -{ - function_scope_trace("ReclsSearchInfo::GetNextDetails"); - - recls_assert(NULL != m_dnode); - - m_lastError = m_dnode->GetNextDetails(pinfo); - - if(RECLS_RC_NO_MORE_DATA == m_lastError) - { - delete m_dnode; - } - - return m_lastError; -} - -// Accessors - -recls_rc_t ReclsSearchInfo::GetLastError() const -{ - function_scope_trace("ReclsSearchInfo::GetLastError"); - - return m_lastError; -} - -/* ///////////////////////////////////////////////////////////////////////////// - * Search control - */ - -RECLS_FNDECL(recls_rc_t) Recls_Search( recls_char_t const *searchRoot - , recls_char_t const *pattern - , recls_uint32_t flags - , hrecls_t *phSrch) -{ - function_scope_trace("Recls_Search"); - - recls_assert(NULL != searchRoot); - recls_assert(NULL != pattern); - recls_assert(NULL != phSrch); - - *phSrch = ReclsSearchInfo::ToHandle(NULL); - - recls_rc_t rc; - - // Validate the search root - if( NULL == searchRoot || - 0 == *searchRoot) - { - searchRoot = "."; - } - - // Validate the flags - if(0 == (flags & RECLS_F_TYPEMASK)) - { - flags |= RECLS_F_FILES; - } - - // Since Win32 does not support all search types, we need to inform - // the caller if they ask to create a search that can never be - // satisfied. - if(0 == (flags & (RECLS_F_FILES | RECLS_F_DIRECTORIES))) - { - rc = RECLS_RC_INVALID_SEARCH_TYPE; - } - // Validate the pattern. - else if('\0' == *pattern) - { - rc = RECLS_RC_NO_MORE_DATA; - } - else - { - ReclsSearchInfo *si; - - rc = ReclsSearchInfo::FindAndCreate(searchRoot, pattern, flags, &si); - - if(RECLS_SUCCEEDED(rc)) - { - *phSrch = ReclsSearchInfo::ToHandle(si); - - rc = RECLS_RC_OK; - } - } - - return rc; -} - -/* ///////////////////////////////////////////////////////////////////////////// - * Error handling - */ - -RECLS_FNDECL(size_t) Recls_GetErrorString( recls_rc_t rc - , recls_char_t *buffer - , size_t cchBuffer) -{ - function_scope_trace("Recls_GetErrorString"); - - recls_assert(NULL != buffer); - - if(rc == RECLS_RC_SEARCH_NO_CURRENT) - { - strncpy(buffer, "Search has no current node", cchBuffer); - } - else if(rc == RECLS_RC_INVALID_DIRECTORY) - { - strncpy(buffer, "Invalid directory", cchBuffer); - } - else if(rc == RECLS_RC_NO_MORE_DATA) - { - strncpy(buffer, "No more data", cchBuffer); - } - else if(rc == RECLS_RC_OUT_OF_MEMORY) - { - strncpy(buffer, "No more memory", cchBuffer); - } - - return strlen(buffer); -} - -/* ///////////////////////////////////////////////////////////////////////////// - * Property elicitation - */ - -RECLS_FNDECL(size_t) Recls_GetDirectoryPathProperty( recls_info_t fileInfo - , recls_char_t *buffer - , size_t cchBuffer) -{ - function_scope_trace("Recls_GetDirectoryPathProperty"); - - recls_assert(NULL != fileInfo); - - struct recls_strptrs_t directoryPath = - { - fileInfo->path.begin /* Directory path is defined by start of path ... */ - , fileInfo->directory.end /* ... to end of directory. */ - }; - - return Recls_GetStringProperty_(&directoryPath, buffer, cchBuffer); -} - -RECLS_FNDECL(recls_bool_t) Recls_IsFileReadOnly(recls_info_t fileInfo) -{ - function_scope_trace("Recls_IsFileReadOnly"); - - recls_assert(NULL != fileInfo); - - return (fileInfo->attributes & S_IWRITE) == 0; -} - -RECLS_FNDECL(recls_bool_t) Recls_IsFileDirectory(recls_info_t fileInfo) -{ - function_scope_trace("Recls_IsFileDirectory"); - - recls_assert(NULL != fileInfo); - - return (fileInfo->attributes & S_IFMT) == S_IFDIR; -} - -RECLS_FNDECL(recls_bool_t) Recls_IsFileLink(recls_info_t fileInfo) -{ - function_scope_trace("Recls_IsFileLink"); - - recls_assert(NULL != fileInfo); - ((void)fileInfo); - - return false; -} - -RECLS_FNDECL(recls_time_t) Recls_GetCreationTime(recls_info_t fileInfo) -{ - function_scope_trace("Recls_GetCreationTime"); - - recls_assert(NULL != fileInfo); - - return fileInfo->modificationTime; -} - -RECLS_FNDECL(recls_time_t) Recls_GetLastStatusChangeTime(recls_info_t fileInfo) -{ - function_scope_trace("Recls_GetLastStatusChangeTime"); - - recls_assert(NULL != fileInfo); - - return fileInfo->lastStatusChangeTime; -} - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace - */ - -#if !defined(RECLS_NO_NAMESPACE) -} /* namespace recls */ -#endif /* !RECLS_NO_NAMESPACE */ - -/* ////////////////////////////////////////////////////////////////////////// */ diff -uNr gdc-0.17/d/phobos/etc/c/recls/recls_api_win32.cpp gdc-0.18/d/phobos/etc/c/recls/recls_api_win32.cpp --- gdc-0.17/d/phobos/etc/c/recls/recls_api_win32.cpp 2004-10-26 02:41:27.000000000 +0200 +++ gdc-0.18/d/phobos/etc/c/recls/recls_api_win32.cpp 1970-01-01 01:00:00.000000000 +0100 @@ -1,1053 +0,0 @@ -/* ///////////////////////////////////////////////////////////////////////////// - * File: recls_api_win32.cpp - * - * Purpose: Win32 implementation file for the recls API. - * - * Created: 16th August 2003 - * Updated: 28th November 2003 - * - * License: (Licensed under the Synesis Software Standard Source License) - * - * Copyright (C) 2002-2003, Synesis Software Pty Ltd. - * - * All rights reserved. - * - * www: http://www.synesis.com.au/software - * http://www.recls.org/ - * - * email: submissions@recls.org for submissions - * admin@recls.org for other enquiries - * - * Redistribution and use in source and binary forms, with or - * without modification, are permitted provided that the following - * conditions are met: - * - * (i) Redistributions of source code must retain the above - * copyright notice and contact information, this list of - * conditions and the following disclaimer. - * - * (ii) Any derived versions of this software (howsoever modified) - * remain the sole property of Synesis Software. - * - * (iii) Any derived versions of this software (howsoever modified) - * remain subject to all these conditions. - * - * (iv) Neither the name of Synesis Software nor the names of any - * subdivisions, employees or agents of Synesis Software, nor the - * names of any other contributors to this software may be used to - * endorse or promote products derived from this software without - * specific prior written permission. - * - * This source code is provided by Synesis Software "as is" and any - * warranties, whether expressed or implied, including, but not - * limited to, the implied warranties of merchantability and - * fitness for a particular purpose are disclaimed. In no event - * shall the Synesis Software be liable for any direct, indirect, - * incidental, special, exemplary, or consequential damages - * (including, but not limited to, procurement of substitute goods - * or services; loss of use, data, or profits; or business - * interruption) however caused and on any theory of liability, - * whether in contract, strict liability, or tort (including - * negligence or otherwise) arising in any way out of the use of - * this software, even if advised of the possibility of such - * damage. - * - * ////////////////////////////////////////////////////////////////////////// */ - - -/* ///////////////////////////////////////////////////////////////////////////// - * Includes - */ - -#include "recls.h" -#include "recls_internal.h" -#include "recls_assert.h" -#include "recls_util.h" - -#include - -#include -#include -#include - -#include -#include - -#include - -#include "recls_debug.h" - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace - */ - -#if !defined(RECLS_NO_NAMESPACE) -namespace recls -{ -#endif /* !RECLS_NO_NAMESPACE */ - -winstl_ns_using(basic_findfile_sequence) - -typedef winstl_ns_qual(filesystem_traits) traits_type; // We need to do this, because VC is a bit thick - -/* ///////////////////////////////////////////////////////////////////////////// - * Utility functions - */ - -#if defined(_DEBUG) - -/* static */ tls_index function_scope::sm_index; - -#endif /* _DEBUG */ - -/* ////////////////////////////////////////////////////////////////////////// */ - -static recls_info_t create_entryinfo_from_psrecord(recls_char_t const *rootDir, recls_uint32_t flags, WIN32_FIND_DATA const &findData) -{ - typedef recls_char_t char_type; - - function_scope_trace("create_entryinfo_from_psrecord"); - - // size of structure is: - // - // offsetof(struct recls_fileinfo_t, data) - // + directory parts - // + full path (+ null) - // + short name (+ null) - - size_t cchRootDir = traits_type::str_len(rootDir); - - recls_assert(cchRootDir > 0); - recls_assert(rootDir[cchRootDir - 1] == traits_type::path_name_separator()); - - size_t cchFileName = traits_type::str_len(findData.cFileName); - size_t cDirParts = ((flags & RECLS_F_DIRECTORY_PARTS) == RECLS_F_DIRECTORY_PARTS) ? count_dir_parts(rootDir + 2, rootDir + cchRootDir) : 0; - size_t cbPath = align_up_size(sizeof(char_type) * (1 + cchRootDir + cchFileName)); - size_t cbAlt = align_up_size(sizeof(char_type) * (1 + RECLS_NUM_ELEMENTS(findData.cAlternateFileName))); - size_t cb = offsetof(struct recls_fileinfo_t, data) - + cDirParts * sizeof(recls_strptrs_t) - + cbPath - + cbAlt; - - struct recls_fileinfo_t *info = const_cast(FileInfo_Allocate(cb)); - - if(NULL != info) - { - char_type *fullPath = (char_type*)&info->data[cDirParts * sizeof(recls_strptrs_t)]; - char_type *altName = (char_type*)&info->data[cDirParts * sizeof(recls_strptrs_t) + cbPath]; - - // full path - traits_type::str_copy(fullPath, rootDir); - traits_type::str_cat(fullPath, findData.cFileName); - info->path.begin = fullPath; - info->path.end = fullPath + cchRootDir + cchFileName; - - // drive, directory, file (name + ext) - info->drive = fullPath[0]; - info->directory.begin = fullPath + 2; - info->directory.end = fullPath + cchRootDir; - info->fileName.begin = info->directory.end; - info->fileName.end = strrchr(info->directory.end, '.'); - if(NULL != info->fileName.end) - { - info->fileExt.begin = info->fileName.end + 1; - info->fileExt.end = info->directory.end + cchFileName; - } - else - { - info->fileName.end = info->directory.end + cchFileName; - info->fileExt.begin = info->directory.end + cchFileName; - info->fileExt.end = info->directory.end + cchFileName; - } - - // determine the directory parts - char_type const *p = info->directory.begin; - char_type const *l = info->directory.end; - struct recls_strptrs_t *begin = (struct recls_strptrs_t*)&info->data[0]; - - info->directoryParts.begin = begin; - info->directoryParts.end = begin + cDirParts; - - if(info->directoryParts.begin != info->directoryParts.end) - { - recls_assert((flags & RECLS_F_DIRECTORY_PARTS) == RECLS_F_DIRECTORY_PARTS); - - begin->begin = p; - - for(; p != l; ++p) - { - if(*p == traits_type::path_name_separator()) - { - begin->end = p + 1; - - if(++begin != info->directoryParts.end) - { - begin->begin = p + 1; - } - } - } - } - - // alt name - traits_type::str_copy(altName, findData.cAlternateFileName); - info->shortFile.begin = altName; - info->shortFile.end = altName + traits_type::str_len(altName); - - // attributes - info->attributes = findData.dwFileAttributes; - - // time, size - info->creationTime = findData.ftCreationTime; - info->modificationTime = findData.ftLastWriteTime; - info->lastAccessTime = findData.ftLastAccessTime; - info->size.u.HighPart = findData.nFileSizeHigh; - info->size.u.LowPart = findData.nFileSizeLow; - - // Checks - recls_assert(info->path.begin < info->path.end); - - recls_assert(info->directory.begin < info->directory.end); - recls_assert(info->path.begin <= info->directory.begin); - recls_assert(info->directory.end <= info->path.end); - - recls_assert(info->fileName.begin <= info->fileName.end); - - recls_assert(info->fileExt.begin <= info->fileExt.end); - - recls_assert(info->fileName.begin < info->fileExt.end); - recls_assert(info->fileName.end <= info->fileExt.begin); - } - - return info; -} - -/* ///////////////////////////////////////////////////////////////////////////// - * PlatformDirectoryNode - */ - -class PlatformDirectoryNode - : public ReclsDNode -{ -public: - typedef recls_char_t char_type; - typedef PlatformDirectoryNode class_type; -private: - typedef basic_findfile_sequence directory_sequence_t; - typedef basic_findfile_sequence entry_sequence_t; - -// Construction -private: - PlatformDirectoryNode(recls_uint32_t flags, char_type const *rootDir, char_type const *pattern); -public: - virtual ~PlatformDirectoryNode(); - - static PlatformDirectoryNode *FindAndCreate(recls_uint32_t flags, char_type const *rootDir, char_type const *pattern); - static PlatformDirectoryNode *FindAndCreate(recls_uint32_t flags, char_type const *rootDir, char_type const *subDir, char_type const *pattern); - -// ReclsDNode methods -private: - virtual recls_rc_t GetNext(); - virtual recls_rc_t GetDetails(recls_info_t *pinfo); - virtual recls_rc_t GetNextDetails(recls_info_t *pinfo); - -// Implementation -private: - recls_rc_t Initialise(); - - recls_bool_t _is_valid() const; - -#if defined(RECLS_COMPILER_IS_BORLAND) - static directory_sequence_t::const_iterator _select_iter(int b, directory_sequence_t::const_iterator trueVal, directory_sequence_t::const_iterator falseVal) - { - // I can't explain it, but Borland does not like the tertiary operator and the copy-ctors of the iterators - if(b) - { - return trueVal; - } - else - { - return falseVal; - } - } -#endif /* !RECLS_COMPILER_IS_BORLAND */ - static int _ssFlags_from_reclsFlags(recls_uint32_t flags) - { - recls_assert(0 == (flags & RECLS_F_LINKS)); // Doesn't work with links - recls_assert(0 == (flags & RECLS_F_DEVICES)); // Doesn't work with devices - - int ssFlags = 0; - - if(0 != (flags & RECLS_F_FILES)) - { - ssFlags |= entry_sequence_t::files; - } - if(0 != (flags & RECLS_F_DIRECTORIES)) - { - ssFlags |= entry_sequence_t::directories; - } - - return ssFlags; - } - -// Members -private: - recls_info_t m_current; - ReclsDNode *m_dnode; - recls_uint32_t const m_flags; - entry_sequence_t m_entries; - entry_sequence_t::const_iterator m_entriesBegin; - directory_sequence_t m_directories; - directory_sequence_t::const_iterator m_directoriesBegin; - char_type m_rootDir[RECLS_PATH_MAX]; - char_type m_pattern[RECLS_PATH_MAX]; -}; - -PlatformDirectoryNode::PlatformDirectoryNode(recls_uint32_t flags, PlatformDirectoryNode::char_type const *rootDir, PlatformDirectoryNode::char_type const *pattern) - : m_current(NULL) - , m_dnode(NULL) - , m_flags(flags) - , m_entries(rootDir, pattern, _ssFlags_from_reclsFlags(flags)) - , m_entriesBegin(m_entries.begin()) - , m_directories(rootDir, traits_type::pattern_all(), directory_sequence_t::directories) -#if !defined(RECLS_COMPILER_IS_BORLAND) - , m_directoriesBegin((flags & RECLS_F_RECURSIVE) ? m_directories.begin() : m_directories.end()) -#else - , m_directoriesBegin(_select_iter((flags & RECLS_F_RECURSIVE), m_directories.begin(), m_directories.end())) -#endif /* !RECLS_COMPILER_IS_BORLAND */ -{ - function_scope_trace("PlatformDirectoryNode::PlatformDirectoryNode"); - -#if defined(RECLS_COMPILER_IS_BORLAND) -// m_directoriesBegin = ((flags & RECLS_F_RECURSIVE) ? m_directories.begin() : m_directories.end()); -#endif /* !RECLS_COMPILER_IS_BORLAND */ - - traits_type::str_copy(m_rootDir, rootDir); - traits_type::ensure_dir_end(m_rootDir); - traits_type::str_copy(m_pattern, pattern); - - recls_assert(stlsoft_raw_offsetof(PlatformDirectoryNode, m_entries) < stlsoft_raw_offsetof(PlatformDirectoryNode, m_entriesBegin)); - recls_assert(stlsoft_raw_offsetof(PlatformDirectoryNode, m_directories) < stlsoft_raw_offsetof(PlatformDirectoryNode, m_directoriesBegin)); -} - -inline /* static */ PlatformDirectoryNode *PlatformDirectoryNode::FindAndCreate(recls_uint32_t flags, PlatformDirectoryNode::char_type const *rootDir, PlatformDirectoryNode::char_type const *pattern) -{ - PlatformDirectoryNode *node; - - function_scope_trace("PlatformDirectoryNode::FindAndCreate"); - -#ifdef RECLS_COMPILER_THROWS_ON_NEW_FAIL - try - { -#endif /* RECLS_COMPILER_THROWS_ON_NEW_FAIL */ - node = new PlatformDirectoryNode(flags, rootDir, pattern); -#ifdef RECLS_COMPILER_THROWS_ON_NEW_FAIL - } - catch(std::bad_alloc &) - { - node = NULL; - } -#endif /* RECLS_COMPILER_THROWS_ON_NEW_FAIL */ - - if(NULL != node) - { - // Ensure that it, or one of its sub-nodes, has matching entries. - recls_rc_t rc = node->Initialise(); - - if(RECLS_FAILED(rc)) - { - delete node; - - node = NULL; - } - } - - recls_assert(NULL == node || node->_is_valid()); - - return node; -} - -inline /* static */ PlatformDirectoryNode *PlatformDirectoryNode::FindAndCreate(recls_uint32_t flags, PlatformDirectoryNode::char_type const *rootDir, PlatformDirectoryNode::char_type const *subDir, PlatformDirectoryNode::char_type const *pattern) -{ - char_type compositeDir[RECLS_PATH_MAX]; - - recls_assert(rootDir[traits_type::str_len(rootDir) - 1] == traits_type::path_name_separator()); - - traits_type::str_copy(compositeDir, rootDir); - traits_type::str_cat(compositeDir, subDir); - - return FindAndCreate(flags, compositeDir, pattern); -} - -PlatformDirectoryNode::~PlatformDirectoryNode() -{ - function_scope_trace("PlatformDirectoryNode::~PlatformDirectoryNode"); - - FileInfo_Release(m_current); - - delete m_dnode; -} - -recls_rc_t PlatformDirectoryNode::Initialise() -{ - function_scope_trace("PlatformDirectoryNode::Initialise"); - - recls_rc_t rc; - - recls_assert(NULL == m_current); - recls_assert(NULL == m_dnode); - - if(m_entriesBegin != m_entries.end()) - { - // (i) Try getting a file first, - m_current = create_entryinfo_from_psrecord(m_rootDir, m_flags, (*m_entriesBegin).get_find_data()); - - if(NULL == m_current) - { - rc = RECLS_RC_OUT_OF_MEMORY; - } - else - { - rc = RECLS_RC_OK; - } - } - else - { - if(m_directoriesBegin == m_directories.end()) - { - rc = RECLS_RC_NO_MORE_DATA; - } - else - { - do - { -#if 0 -// m_dnode = PlatformDirectoryNode::FindAndCreate(m_flags, m_rootDir, (*m_directoriesBegin, m_pattern); -#else /* ? 0 */ - // The way basic_findfile_sequence<> works - m_dnode = PlatformDirectoryNode::FindAndCreate(m_flags, (*m_directoriesBegin).get_path(), m_pattern); -#endif /* 0 */ - - } while(NULL == m_dnode && ++m_directoriesBegin != m_directories.end()); - - rc = (NULL == m_dnode) ? RECLS_RC_NO_MORE_DATA : RECLS_RC_OK; - } - } - - if(RECLS_SUCCEEDED(rc)) - { - recls_assert(_is_valid()); - } - - return rc; -} - -recls_bool_t PlatformDirectoryNode::_is_valid() const -{ - function_scope_trace("PlatformDirectoryNode::_is_valid"); - - recls_rc_t rc = RECLS_RC_OK; - -#ifdef STLSOFT_CF_PRAGMA_MESSAGE_SUPPORT -# pragma message("Flesh these out") -#endif /* STLSOFT_CF_PRAGMA_MESSAGE_SUPPORT */ - if(RECLS_SUCCEEDED(rc)) - { - - } - - if(RECLS_SUCCEEDED(rc)) - { - } - - if(RECLS_SUCCEEDED(rc)) - { - } - - if(RECLS_SUCCEEDED(rc)) - { - } - - // (i) Either we are enumerating files (m_current != NULL) or directories (m_dnode != NULL), but not both - recls_assert(NULL == m_current || NULL == m_dnode); - // (ii) Either we are enumerating files (m_current != NULL) or there are no more files to enumerate - recls_assert(NULL != m_current || m_entriesBegin == m_entries.end()); - - return RECLS_SUCCEEDED(rc); -} - - -recls_rc_t PlatformDirectoryNode::GetNext() -{ - function_scope_trace("PlatformDirectoryNode::GetNext"); - - recls_assert(_is_valid()); - - /* Searching operates as follows: - * - * 1. Return all the contents of the files - * 2. Return the contents of the directories. - * - * Hence, if m_dnode is non-NULL, we've already searched - */ - - /* States: - * - * - Iterating files: m_entriesBegin != m_entries.end(), m_dnode is NULL, m_directoriesBegin != m_directories.end() - * - Iterating directories: m_directoriesBegin != m_directories.end(), m_dnode is non-NULL, m_current is NULL - * - */ - - // Invariants - - // (i) Either we are enumerating files (m_current != NULL) or directories (m_dnode != NULL), but not both - recls_assert(NULL == m_current || NULL == m_dnode); - // (ii) Either we are enumerating files (m_current != NULL) or there are no more files to enumerate - recls_assert(NULL != m_current || m_entriesBegin == m_entries.end()); - - recls_rc_t rc = RECLS_RC_NO_MORE_DATA; - - if(NULL != m_current) - { - // Currently enumerating through the files - - recls_assert(m_entriesBegin != m_entries.end()); - recls_assert(NULL == m_dnode); - - // Advance, and check for end of sequence - ++m_entriesBegin; - - FileInfo_Release(m_current); - if(m_entriesBegin != m_entries.end()) - { - // Still enumerating, so just update m_current - m_current = create_entryinfo_from_psrecord(m_rootDir, m_flags, (*m_entriesBegin).get_find_data()); - - rc = RECLS_RC_OK; - } - else - { - // No more left in the files sequence, so delete m_current - m_current = NULL; - - rc = RECLS_RC_NO_MORE_DATA; - } - } - - if(NULL == m_current) - { - // Now we are either enumerating the directories, or we've already done so - - if(NULL != m_dnode) - { - // Currently enumerating the directories - rc = m_dnode->GetNext(); - - if(RECLS_RC_NO_MORE_DATA == rc) - { - ++m_directoriesBegin; - - delete m_dnode; - - m_dnode = NULL; - } - } - - if(m_directoriesBegin == m_directories.end()) - { - // Enumeration is complete. - rc = RECLS_RC_NO_MORE_DATA; - } - else - { - if(NULL == m_dnode) - { - do - { - // Creation of the node will cause it to enter the first enumeration - // state. However, if there are no matching - - recls_assert(m_directoriesBegin != m_directories.end()); - -#if 0 -// m_dnode = PlatformDirectoryNode::FindAndCreate(m_flags, m_rootDir, *m_directoriesBegin, m_pattern); -#else /* ? 0 */ - // The way basic_findfile_sequence<> works - m_dnode = PlatformDirectoryNode::FindAndCreate(m_flags, (*m_directoriesBegin).get_path(), m_pattern); -#endif /* 0 */ - - if(NULL != m_dnode) - { - rc = RECLS_RC_OK; - } - else - { - ++m_directoriesBegin; - } - - } while(NULL == m_dnode && m_directoriesBegin != m_directories.end()); - } - } - } - - recls_assert(_is_valid()); - - return rc; -} - -recls_rc_t PlatformDirectoryNode::GetDetails(recls_info_t *pinfo) -{ - function_scope_trace("PlatformDirectoryNode::GetDetails"); - - recls_assert(_is_valid()); - - recls_rc_t rc; - - recls_assert(NULL != pinfo); - recls_assert(NULL == m_current || NULL == m_dnode); - - if(NULL != m_current) - { - // Currently searching for files from the current directory - - recls_assert(NULL == m_dnode); - - rc = FileInfo_Copy(m_current, pinfo); - -#ifdef _DEBUG - { - recls_char_t buffer[RECLS_PATH_MAX]; - - Recls_GetPathProperty(m_current, buffer, stlsoft_num_elements(buffer)); - - debug_printf(" [%s]\n", buffer); - } -#endif /* _DEBUG */ - } - else if(NULL != m_dnode) - { - recls_assert(NULL == m_current); - - // Sub-directory searching is active, so get from there. - - rc = m_dnode->GetDetails(pinfo); - } - else - { - // Enumeration has completed - rc = RECLS_RC_NO_MORE_DATA; - } - - recls_assert(_is_valid()); - - return rc; -} - -recls_rc_t PlatformDirectoryNode::GetNextDetails(recls_info_t *pinfo) -{ - function_scope_trace("PlatformDirectoryNode::GetNextDetails"); - - recls_assert(_is_valid()); - recls_assert(NULL != pinfo); - - recls_rc_t rc = GetNext(); - - if(RECLS_SUCCEEDED(rc)) - { - rc = GetDetails(pinfo); - } - - recls_assert(_is_valid()); - - return rc; -} - -/* ///////////////////////////////////////////////////////////////////////////// - * ReclsSearchInfo - */ - -void *ReclsSearchInfo::operator new(size_t cb, int cDirParts, size_t cbRootDir) -{ - function_scope_trace("ReclsSearchInfo::operator new"); - - cbRootDir = align_up_size(cbRootDir); - - recls_assert(cb > stlsoft_raw_offsetof(ReclsSearchInfo, data)); - - cb = stlsoft_raw_offsetof(ReclsSearchInfo, data) - + (cDirParts) * sizeof(recls_strptrs_t) - + cbRootDir; - - return malloc(cb); -} - -#if !defined(RECLS_COMPILER_IS_BORLAND) && \ - !defined(RECLS_COMPILER_IS_DMC) && \ - !defined(RECLS_COMPILER_IS_INTEL) && \ - !defined(RECLS_COMPILER_IS_WATCOM) -void ReclsSearchInfo::operator delete(void *pv, int /* cDirParts */, size_t /* cbRootDir */) -{ - function_scope_trace("ReclsSearchInfo::operator delete"); - - free(pv); -} -#endif /* !RECLS_COMPILER_IS_BORLAND && !RECLS_COMPILER_IS_DMC */ - -void ReclsSearchInfo::operator delete(void *pv) -{ - function_scope_trace("ReclsSearchInfo::operator delete"); - - free(pv); -} - -inline /* static */ recls_rc_t ReclsSearchInfo::FindAndCreate(ReclsSearchInfo::char_type const *rootDir, ReclsSearchInfo::char_type const *pattern, recls_uint32_t flags, ReclsSearchInfo **ppsi) -{ - function_scope_trace("ReclsSearchInfo::FindAndCreate"); - - recls_rc_t rc; - ReclsSearchInfo *si; - char_type fullPath[RECLS_PATH_MAX]; - size_t cchFullPath; - - *ppsi = NULL; - - cchFullPath = traits_type::get_full_path_name(rootDir, RECLS_NUM_ELEMENTS(fullPath), fullPath); - if( 0 == cchFullPath || - !file_exists(fullPath)) - { - rc = RECLS_RC_INVALID_DIRECTORY; - } - else - { - traits_type::ensure_dir_end(fullPath); - - size_t lenSearchRoot = traits_type::str_len(fullPath); - - recls_assert(0 < lenSearchRoot); - - rootDir = fullPath; - - // Count the directory parts. This is always done for the ReclsSearchInfo class, since it - // uses them to recurse. - char_type const *begin = rootDir + 2; - char_type const *const end = rootDir + lenSearchRoot; - int cDirParts = count_dir_parts(begin, end); - -#ifdef RECLS_COMPILER_THROWS_ON_NEW_FAIL - try - { -#endif /* RECLS_COMPILER_THROWS_ON_NEW_FAIL */ - si = new(cDirParts, sizeof(char_type) * (1 + lenSearchRoot)) ReclsSearchInfo(cDirParts, rootDir, pattern, flags); -#ifdef RECLS_COMPILER_THROWS_ON_NEW_FAIL - } - catch(std::bad_alloc &) - { - si = NULL; - } -#endif /* RECLS_COMPILER_THROWS_ON_NEW_FAIL */ - - if(NULL == si) - { - rc = RECLS_RC_FAIL; - } - else - { - // This is a nasty hack. It's tantamount to ctor & create function, so - // should be made more elegant soon. - if(NULL == si->m_dnode) - { - delete si; - - si = NULL; - - rc = RECLS_RC_NO_MORE_DATA; - } - else - { - *ppsi = si; - - rc = RECLS_RC_OK; - } - } - } - - return rc; -} - -ReclsSearchInfo::char_type const *ReclsSearchInfo::_calc_rootDir(int cDirParts, ReclsSearchInfo::char_type const *rootDir) -{ - function_scope_trace("ReclsSearchInfo::_calc_rootDir"); - - // Root dir is located after file parts, and before pattern - return traits_type::str_copy((char_type*)&data[cDirParts * sizeof(recls_strptrs_t)], rootDir); -} - -ReclsSearchInfo::ReclsSearchInfo( int cDirParts - , ReclsSearchInfo::char_type const *rootDir - , ReclsSearchInfo::char_type const *pattern - , recls_uint32_t flags) - : m_flags(flags) - , m_lastError(RECLS_RC_OK) - , m_rootDir(_calc_rootDir(cDirParts, rootDir)) -{ - function_scope_trace("ReclsSearchInfo::ReclsSearchInfo"); - - recls_assert(NULL != rootDir); - recls_assert(NULL != pattern); - recls_assert(traits_type::str_len(rootDir) < RECLS_PATH_MAX); - recls_assert(traits_type::str_len(pattern) < RECLS_PATH_MAX); - - // Initialise the directory parts. - - recls_assert(rootDir[1] == ':'); - -// char_type const *p = rootDir + 2; -// struct recls_strptrs_t *begin = (struct recls_strptrs_t*)&data[0]; - - // Now start the search - m_dnode = PlatformDirectoryNode::FindAndCreate(m_flags, rootDir, pattern); -} - -// Operations -recls_rc_t ReclsSearchInfo::GetNext() -{ - function_scope_trace("ReclsSearchInfo::GetNext"); - - recls_assert(NULL != m_dnode); - - m_lastError = m_dnode->GetNext(); - - if(RECLS_RC_NO_MORE_DATA == m_lastError) - { - delete m_dnode; - - m_dnode = NULL; - } - - return m_lastError; -} - -recls_rc_t ReclsSearchInfo::GetDetails(recls_info_t *pinfo) -{ - function_scope_trace("ReclsSearchInfo::GetDetails"); - - recls_assert(NULL != m_dnode); - - return (m_lastError = m_dnode->GetDetails(pinfo)); -} - -recls_rc_t ReclsSearchInfo::GetNextDetails(recls_info_t *pinfo) -{ - function_scope_trace("ReclsSearchInfo::GetNextDetails"); - - recls_assert(NULL != m_dnode); - - m_lastError = m_dnode->GetNextDetails(pinfo); - - if(RECLS_RC_NO_MORE_DATA == m_lastError) - { - delete m_dnode; - } - - return m_lastError; -} - -// Accessors - -recls_rc_t ReclsSearchInfo::GetLastError() const -{ - function_scope_trace("ReclsSearchInfo::GetLastError"); - - return m_lastError; -} - -/* ///////////////////////////////////////////////////////////////////////////// - * Search control - */ - -RECLS_FNDECL(recls_rc_t) Recls_Search( recls_char_t const *searchRoot - , recls_char_t const *pattern - , recls_uint32_t flags - , hrecls_t *phSrch) -{ - function_scope_trace("Recls_Search"); - - recls_assert(NULL != searchRoot); - recls_assert(NULL != pattern); - recls_assert(NULL != phSrch); - - *phSrch = ReclsSearchInfo::ToHandle(NULL); - - recls_rc_t rc; - - // Validate the search root - if( NULL == searchRoot || - 0 == *searchRoot) - { - searchRoot = "."; - } - - // Validate the flags - if(0 == (flags & RECLS_F_TYPEMASK)) - { - flags |= RECLS_F_FILES; - } - - // Since Win32 does not support all search types, we need to inform - // the caller if they ask to create a search that can never be - // satisfied. - if(0 == (flags & (RECLS_F_FILES | RECLS_F_DIRECTORIES))) - { - rc = RECLS_RC_INVALID_SEARCH_TYPE; - } - // Validate the pattern. - else if('\0' == *pattern) - { - rc = RECLS_RC_NO_MORE_DATA; - } - else - { - ReclsSearchInfo *si; - - rc = ReclsSearchInfo::FindAndCreate(searchRoot, pattern, flags, &si); - - if(RECLS_SUCCEEDED(rc)) - { - *phSrch = ReclsSearchInfo::ToHandle(si); - - rc = RECLS_RC_OK; - } - } - - return rc; -} - -/* ///////////////////////////////////////////////////////////////////////////// - * Error handling - */ - -RECLS_FNDECL(size_t) Recls_GetErrorString( recls_rc_t rc - , recls_char_t *buffer - , size_t cchBuffer) -{ - function_scope_trace("Recls_GetErrorString"); - - recls_assert(NULL != buffer); - - if(rc == RECLS_RC_SEARCH_NO_CURRENT) - { - strncpy(buffer, "Search has no current node", cchBuffer); - } - else if(rc == RECLS_RC_INVALID_DIRECTORY) - { - strncpy(buffer, "Invalid directory", cchBuffer); - } - else if(rc == RECLS_RC_NO_MORE_DATA) - { - strncpy(buffer, "No more data", cchBuffer); - } - else if(rc == RECLS_RC_OUT_OF_MEMORY) - { - strncpy(buffer, "No more memory", cchBuffer); - } - - return strlen(buffer); -} - -/* ///////////////////////////////////////////////////////////////////////////// - * Property elicitation - */ - -RECLS_FNDECL(size_t) Recls_GetDirectoryPathProperty( recls_info_t fileInfo - , recls_char_t *buffer - , size_t cchBuffer) -{ - function_scope_trace("Recls_GetDirectoryPathProperty"); - - recls_assert(NULL != fileInfo); - - struct recls_strptrs_t directoryPath = - { - fileInfo->path.begin /* Directory path is defined by start of path ... */ - , fileInfo->directory.end /* ... to end of directory. */ - }; - - return Recls_GetStringProperty_(&directoryPath, buffer, cchBuffer); -} - -RECLS_FNDECL(size_t) Recls_GetShortFileProperty( recls_info_t fileInfo - , recls_char_t *buffer - , size_t cchBuffer) -{ - function_scope_trace("Recls_GetShortFileProperty"); - - recls_assert(NULL != fileInfo); - - return Recls_GetStringProperty_(&fileInfo->shortFile, buffer, cchBuffer); -} - -RECLS_FNDECL(void) Recls_GetDriveProperty( recls_info_t fileInfo - , recls_char_t *pchDrive) -{ - function_scope_trace("Recls_GetDriveProperty"); - - recls_assert(NULL != fileInfo); - recls_assert(NULL != pchDrive); - - *pchDrive = (recls_char_t)toupper(*fileInfo->path.begin); -} - -RECLS_FNDECL(recls_bool_t) Recls_IsFileReadOnly(recls_info_t fileInfo) -{ - function_scope_trace("Recls_IsFileReadOnly"); - - recls_assert(NULL != fileInfo); - - return fileInfo->attributes & FILE_ATTRIBUTE_READONLY; -} - -RECLS_FNDECL(recls_bool_t) Recls_IsFileDirectory(recls_info_t fileInfo) -{ - function_scope_trace("Recls_IsFileDirectory"); - - recls_assert(NULL != fileInfo); - - return fileInfo->attributes & FILE_ATTRIBUTE_DIRECTORY; -} - -RECLS_FNDECL(recls_bool_t) Recls_IsFileLink(recls_info_t fileInfo) -{ - function_scope_trace("Recls_IsFileLink"); - - recls_assert(NULL != fileInfo); - ((void)fileInfo); - - return false; -} - -RECLS_FNDECL(recls_time_t) Recls_GetCreationTime(recls_info_t fileInfo) -{ - function_scope_trace("Recls_GetCreationTime"); - - recls_assert(NULL != fileInfo); - - return fileInfo->creationTime; -} - -RECLS_FNDECL(recls_time_t) Recls_GetLastStatusChangeTime(recls_info_t fileInfo) -{ - function_scope_trace("Recls_GetLastStatusChangeTime"); - - recls_assert(NULL != fileInfo); - - return fileInfo->modificationTime; -} - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace - */ - -#if !defined(RECLS_NO_NAMESPACE) -} /* namespace recls */ -#endif /* !RECLS_NO_NAMESPACE */ - -/* ////////////////////////////////////////////////////////////////////////// */ diff -uNr gdc-0.17/d/phobos/etc/c/recls/recls_assert.h gdc-0.18/d/phobos/etc/c/recls/recls_assert.h --- gdc-0.17/d/phobos/etc/c/recls/recls_assert.h 2004-10-26 02:41:27.000000000 +0200 +++ gdc-0.18/d/phobos/etc/c/recls/recls_assert.h 1970-01-01 01:00:00.000000000 +0100 @@ -1,128 +0,0 @@ -/* ///////////////////////////////////////////////////////////////////////////// - * File: recls_assert.h - * - * Purpose: Compiler discrimination for the recls API. - * - * Created: 15th August 2003 - * Updated: 2nd November 2003 - * - * License: (Licensed under the Synesis Software Standard Source License) - * - * Copyright (C) 2002-2003, Synesis Software Pty Ltd. - * - * All rights reserved. - * - * www: http://www.synesis.com.au/software - * http://www.recls.org/ - * - * email: submissions@recls.org for submissions - * admin@recls.org for other enquiries - * - * Redistribution and use in source and binary forms, with or - * without modification, are permitted provided that the following - * conditions are met: - * - * (i) Redistributions of source code must retain the above - * copyright notice and contact information, this list of - * conditions and the following disclaimer. - * - * (ii) Any derived versions of this software (howsoever modified) - * remain the sole property of Synesis Software. - * - * (iii) Any derived versions of this software (howsoever modified) - * remain subject to all these conditions. - * - * (iv) Neither the name of Synesis Software nor the names of any - * subdivisions, employees or agents of Synesis Software, nor the - * names of any other contributors to this software may be used to - * endorse or promote products derived from this software without - * specific prior written permission. - * - * This source code is provided by Synesis Software "as is" and any - * warranties, whether expressed or implied, including, but not - * limited to, the implied warranties of merchantability and - * fitness for a particular purpose are disclaimed. In no event - * shall the Synesis Software be liable for any direct, indirect, - * incidental, special, exemplary, or consequential damages - * (including, but not limited to, procurement of substitute goods - * or services; loss of use, data, or profits; or business - * interruption) however caused and on any theory of liability, - * whether in contract, strict liability, or tort (including - * negligence or otherwise) arising in any way out of the use of - * this software, even if advised of the possibility of such - * damage. - * - * ////////////////////////////////////////////////////////////////////////// */ - - -#ifndef RECLS_INCL_H_RECLS_ASSERT -#define RECLS_INCL_H_RECLS_ASSERT - -/* File version */ -#ifndef RECLS_DOCUMENTATION_SKIP_SECTION -# define RECLS_VER_H_RECLS_ASSERT_MAJOR 1 -# define RECLS_VER_H_RECLS_ASSERT_MINOR 0 -# define RECLS_VER_H_RECLS_ASSERT_REVISION 6 -# define RECLS_VER_H_RECLS_ASSERT_EDIT 6 -#endif /* !RECLS_DOCUMENTATION_SKIP_SECTION */ - -/** \file recls_assert.h Assertions for the \ref group_recls API */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Includes - */ - -#include "recls.h" - -/** \def recls_assert Assert macro for the recls API - * - * \param x The expression that must evaluate to \c true - */ - -#if defined(RECLS_PLATFORM_IS_WIN32) && \ - defined(_MSC_VER) -# include // Prefer MSVCRT for VC++ and compatible compilers -# define recls_assert(x) _ASSERTE(x) -#else -# include -# define recls_assert(x) assert(x) -#endif /* compiler */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Macros - */ - -/** \def recls_message_assert Assert macro for the recls API - * - * \param m The literal string describing the failed condition - * \param x The expression that must evaluate to \c true - */ - -#if defined(__WATCOMC__) - #define recls_message_assert(m, ) recls_assert(x) -#else - #define recls_message_assert(m, x) recls_assert((m, x)) -#endif /* __WATCOMC__ */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace - */ - -#if !defined(RECLS_NO_NAMESPACE) -namespace recls -{ -#endif /* !RECLS_NO_NAMESPACE */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace - */ - -#if !defined(RECLS_NO_NAMESPACE) -} /* namespace recls */ -#endif /* !RECLS_NO_NAMESPACE */ - -/* ////////////////////////////////////////////////////////////////////////// */ - -#endif /* !RECLS_INCL_H_RECLS_ASSERT */ - -/* ////////////////////////////////////////////////////////////////////////// */ diff -uNr gdc-0.17/d/phobos/etc/c/recls/recls_compiler_dmc.h gdc-0.18/d/phobos/etc/c/recls/recls_compiler_dmc.h --- gdc-0.17/d/phobos/etc/c/recls/recls_compiler_dmc.h 2004-10-26 02:41:27.000000000 +0200 +++ gdc-0.18/d/phobos/etc/c/recls/recls_compiler_dmc.h 1970-01-01 01:00:00.000000000 +0100 @@ -1,137 +0,0 @@ -/* ///////////////////////////////////////////////////////////////////////////// - * File: recls_compiler_dmc.h - * - * Purpose: Digital Mars specific types and includes for the recls API. - * - * Created: 17th August 2003 - * Updated: 2nd November 2003 - * - * License: (Licensed under the Synesis Software Standard Source License) - * - * Copyright (C) 2002-2003, Synesis Software Pty Ltd. - * - * All rights reserved. - * - * www: http://www.synesis.com.au/software - * http://www.recls.org/ - * - * email: submissions@recls.org for submissions - * admin@recls.org for other enquiries - * - * Redistribution and use in source and binary forms, with or - * without modification, are permitted provided that the following - * conditions are met: - * - * (i) Redistributions of source code must retain the above - * copyright notice and contact information, this list of - * conditions and the following disclaimer. - * - * (ii) Any derived versions of this software (howsoever modified) - * remain the sole property of Synesis Software. - * - * (iii) Any derived versions of this software (howsoever modified) - * remain subject to all these conditions. - * - * (iv) Neither the name of Synesis Software nor the names of any - * subdivisions, employees or agents of Synesis Software, nor the - * names of any other contributors to this software may be used to - * endorse or promote products derived from this software without - * specific prior written permission. - * - * This source code is provided by Synesis Software "as is" and any - * warranties, whether expressed or implied, including, but not - * limited to, the implied warranties of merchantability and - * fitness for a particular purpose are disclaimed. In no event - * shall the Synesis Software be liable for any direct, indirect, - * incidental, special, exemplary, or consequential damages - * (including, but not limited to, procurement of substitute goods - * or services; loss of use, data, or profits; or business - * interruption) however caused and on any theory of liability, - * whether in contract, strict liability, or tort (including - * negligence or otherwise) arising in any way out of the use of - * this software, even if advised of the possibility of such - * damage. - * - * ////////////////////////////////////////////////////////////////////////// */ - - -#if !defined(RECLS_INCL_H_RECLS_COMPILER) && \ - !defined(RECLS_DOCUMENTATION_SKIP_SECTION) -# error recls_compiler_dmc.h cannot be included directly. Include recls.h -#else - -#ifndef RECLS_COMPILER_IS_DMC -# error recls_compiler_dmc.h can only be used for Digital Mars compiler builds -#endif /* !RECLS_COMPILER_IS_DMC */ - -/* File version */ -#ifndef RECLS_DOCUMENTATION_SKIP_SECTION -# define RECLS_VER_H_RECLS_COMPILER_DMC_MAJOR 1 -# define RECLS_VER_H_RECLS_COMPILER_DMC_MINOR 1 -# define RECLS_VER_H_RECLS_COMPILER_DMC_REVISION 1 -# define RECLS_VER_H_RECLS_COMPILER_DMC_EDIT 4 -#endif /* !RECLS_DOCUMENTATION_SKIP_SECTION */ - -/** \file recls_compiler_dmc.h Digital Mars C/C++-specific compiler definitions for the \ref group_recls API */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Includes - */ - -#include - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace - */ - -#if !defined(RECLS_NO_NAMESPACE) -namespace recls -{ -#endif /* !RECLS_NO_NAMESPACE */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Typedefs - */ - -/** \def recls_byte_t The byte type for the \ref group_recls API */ -/** \def recls_sint8_t The 8-bit signed integer type for the \ref group_recls API */ -/** \def recls_uint8_t The 8-bit unsigned integer type for the \ref group_recls API */ -/** \def recls_sint16_t The 16-bit signed integer type for the \ref group_recls API */ -/** \def recls_uint16_t The 16-bit unsigned integer type for the \ref group_recls API */ -/** \def recls_sint32_t The 32-bit signed integer type for the \ref group_recls API */ -/** \def recls_uint32_t The 32-bit unsigned integer type for the \ref group_recls API */ -/** \def recls_sint64_t The 64-bit signed integer type for the \ref group_recls API */ -/** \def recls_uint64_t The 64-bit unsigned integer type for the \ref group_recls API */ - -typedef unsigned char recls_byte_t; - -typedef signed char recls_sint8_t; -typedef unsigned char recls_uint8_t; - -typedef signed short recls_sint16_t; -typedef unsigned short recls_uint16_t; - -typedef signed long recls_sint32_t; -typedef unsigned long recls_uint32_t; - -typedef signed __int64 recls_sint64_t; -typedef unsigned __int64 recls_uint64_t; - -/** \def recls_char_a_t The ANSI character type for the \ref group_recls API */ -/** \def recls_char_w_t The Unicode character type for the \ref group_recls API */ -typedef char recls_char_a_t; -typedef wchar_t recls_char_w_t; - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace - */ - -#if !defined(RECLS_NO_NAMESPACE) -} /* namespace recls */ -#endif /* !RECLS_NO_NAMESPACE */ - -/* ////////////////////////////////////////////////////////////////////////// */ - -#endif /* RECLS_INCL_H_RECLS_COMPILER */ - -/* ////////////////////////////////////////////////////////////////////////// */ diff -uNr gdc-0.17/d/phobos/etc/c/recls/recls_compiler_gcc.h gdc-0.18/d/phobos/etc/c/recls/recls_compiler_gcc.h --- gdc-0.17/d/phobos/etc/c/recls/recls_compiler_gcc.h 2004-10-26 02:41:27.000000000 +0200 +++ gdc-0.18/d/phobos/etc/c/recls/recls_compiler_gcc.h 1970-01-01 01:00:00.000000000 +0100 @@ -1,137 +0,0 @@ -/* ///////////////////////////////////////////////////////////////////////////// - * File: recls_compiler_gcc.h - * - * Purpose: Digital Mars specific types and includes for the recls API. - * - * Created: 17th August 2003 - * Updated: 2nd November 2003 - * - * License: (Licensed under the Synesis Software Standard Source License) - * - * Copyright (C) 2002-2003, Synesis Software Pty Ltd. - * - * All rights reserved. - * - * www: http://www.synesis.com.au/software - * http://www.recls.org/ - * - * email: submissions@recls.org for submissions - * admin@recls.org for other enquiries - * - * Redistribution and use in source and binary forms, with or - * without modification, are permitted provided that the following - * conditions are met: - * - * (i) Redistributions of source code must retain the above - * copyright notice and contact information, this list of - * conditions and the following disclaimer. - * - * (ii) Any derived versions of this software (howsoever modified) - * remain the sole property of Synesis Software. - * - * (iii) Any derived versions of this software (howsoever modified) - * remain subject to all these conditions. - * - * (iv) Neither the name of Synesis Software nor the names of any - * subdivisions, employees or agents of Synesis Software, nor the - * names of any other contributors to this software may be used to - * endorse or promote products derived from this software without - * specific prior written permission. - * - * This source code is provided by Synesis Software "as is" and any - * warranties, whether expressed or implied, including, but not - * limited to, the implied warranties of merchantability and - * fitness for a particular purpose are disclaimed. In no event - * shall the Synesis Software be liable for any direct, indirect, - * incidental, special, exemplary, or consequential damages - * (including, but not limited to, procurement of substitute goods - * or services; loss of use, data, or profits; or business - * interruption) however caused and on any theory of liability, - * whether in contract, strict liability, or tort (including - * negligence or otherwise) arising in any way out of the use of - * this software, even if advised of the possibility of such - * damage. - * - * ////////////////////////////////////////////////////////////////////////// */ - - -#if !defined(RECLS_INCL_H_RECLS_COMPILER) && \ - !defined(RECLS_DOCUMENTATION_SKIP_SECTION) -# error recls_compiler_gcc.h cannot be included directly. Include recls.h -#else - -#ifndef RECLS_COMPILER_IS_GCC -# error recls_compiler_gcc.h can only be used for GCC compiler builds -#endif /* !RECLS_COMPILER_IS_GCC */ - -/* File version */ -#ifndef RECLS_DOCUMENTATION_SKIP_SECTION -# define RECLS_VER_H_RECLS_COMPILER_GCC_MAJOR 1 -# define RECLS_VER_H_RECLS_COMPILER_GCC_MINOR 1 -# define RECLS_VER_H_RECLS_COMPILER_GCC_REVISION 1 -# define RECLS_VER_H_RECLS_COMPILER_GCC_EDIT 4 -#endif /* !RECLS_DOCUMENTATION_SKIP_SECTION */ - -/** \file recls_compiler_gcc.h GCC-specific compiler definitions for the \ref group_recls API */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Includes - */ - -#include - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace - */ - -#if !defined(RECLS_NO_NAMESPACE) -namespace recls -{ -#endif /* !RECLS_NO_NAMESPACE */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Typedefs - */ - -/** \def recls_byte_t The byte type for the \ref group_recls API */ -/** \def recls_sint8_t The 8-bit signed integer type for the \ref group_recls API */ -/** \def recls_uint8_t The 8-bit unsigned integer type for the \ref group_recls API */ -/** \def recls_sint16_t The 16-bit signed integer type for the \ref group_recls API */ -/** \def recls_uint16_t The 16-bit unsigned integer type for the \ref group_recls API */ -/** \def recls_sint32_t The 32-bit signed integer type for the \ref group_recls API */ -/** \def recls_uint32_t The 32-bit unsigned integer type for the \ref group_recls API */ -/** \def recls_sint64_t The 64-bit signed integer type for the \ref group_recls API */ -/** \def recls_uint64_t The 64-bit unsigned integer type for the \ref group_recls API */ - -typedef unsigned char recls_byte_t; - -typedef signed char recls_sint8_t; -typedef unsigned char recls_uint8_t; - -typedef signed short recls_sint16_t; -typedef unsigned short recls_uint16_t; - -typedef signed long recls_sint32_t; -typedef unsigned long recls_uint32_t; - -typedef signed long long recls_sint64_t; -typedef unsigned long long recls_uint64_t; - -/** \def recls_char_a_t The ANSI character type for the \ref group_recls API */ -/** \def recls_char_w_t The Unicode character type for the \ref group_recls API */ -typedef char recls_char_a_t; -typedef wchar_t recls_char_w_t; - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace - */ - -#if !defined(RECLS_NO_NAMESPACE) -} /* namespace recls */ -#endif /* !RECLS_NO_NAMESPACE */ - -/* ////////////////////////////////////////////////////////////////////////// */ - -#endif /* RECLS_INCL_H_RECLS_COMPILER */ - -/* ////////////////////////////////////////////////////////////////////////// */ diff -uNr gdc-0.17/d/phobos/etc/c/recls/recls_compiler.h gdc-0.18/d/phobos/etc/c/recls/recls_compiler.h --- gdc-0.17/d/phobos/etc/c/recls/recls_compiler.h 2004-10-26 02:41:27.000000000 +0200 +++ gdc-0.18/d/phobos/etc/c/recls/recls_compiler.h 1970-01-01 01:00:00.000000000 +0100 @@ -1,202 +0,0 @@ -/* ///////////////////////////////////////////////////////////////////////////// - * File: recls_compiler.h - * - * Purpose: Compiler discrimination for the recls API. - * - * Created: 15th August 2003 - * Updated: 23rd September 2003 - * - * License: (Licensed under the Synesis Software Standard Source License) - * - * Copyright (C) 2002-2003, Synesis Software Pty Ltd. - * - * All rights reserved. - * - * www: http://www.synesis.com.au/software - * http://www.recls.org/ - * - * email: submissions@recls.org for submissions - * admin@recls.org for other enquiries - * - * Redistribution and use in source and binary forms, with or - * without modification, are permitted provided that the following - * conditions are met: - * - * (i) Redistributions of source code must retain the above - * copyright notice and contact information, this list of - * conditions and the following disclaimer. - * - * (ii) Any derived versions of this software (howsoever modified) - * remain the sole property of Synesis Software. - * - * (iii) Any derived versions of this software (howsoever modified) - * remain subject to all these conditions. - * - * (iv) Neither the name of Synesis Software nor the names of any - * subdivisions, employees or agents of Synesis Software, nor the - * names of any other contributors to this software may be used to - * endorse or promote products derived from this software without - * specific prior written permission. - * - * This source code is provided by Synesis Software "as is" and any - * warranties, whether expressed or implied, including, but not - * limited to, the implied warranties of merchantability and - * fitness for a particular purpose are disclaimed. In no event - * shall the Synesis Software be liable for any direct, indirect, - * incidental, special, exemplary, or consequential damages - * (including, but not limited to, procurement of substitute goods - * or services; loss of use, data, or profits; or business - * interruption) however caused and on any theory of liability, - * whether in contract, strict liability, or tort (including - * negligence or otherwise) arising in any way out of the use of - * this software, even if advised of the possibility of such - * damage. - * - * ////////////////////////////////////////////////////////////////////////// */ - - -#ifndef RECLS_INCL_H_RECLS_COMPILER -#define RECLS_INCL_H_RECLS_COMPILER - -/* File version */ -#ifndef RECLS_DOCUMENTATION_SKIP_SECTION -# define RECLS_VER_H_RECLS_COMPILER_MAJOR 1 -# define RECLS_VER_H_RECLS_COMPILER_MINOR 0 -# define RECLS_VER_H_RECLS_COMPILER_REVISION 6 -# define RECLS_VER_H_RECLS_COMPILER_EDIT 6 -#endif /* !RECLS_DOCUMENTATION_SKIP_SECTION */ - -/** \file recls_compiler.h Compiler detection for the \ref group_recls API */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Compiler detection - */ - -#if defined(__BORLANDC__) -# define RECLS_COMPILER_IS_BORLAND -#elif defined(__DMC__) -# define RECLS_COMPILER_IS_DMC -#elif defined(__GNUC__) -# define RECLS_COMPILER_IS_GCC -#elif defined(__INTEL_COMPILER) -# define RECLS_COMPILER_IS_INTEL -#elif defined(__MWERKS__) -# define RECLS_COMPILER_IS_MWERKS -#elif defined(__WATCOMC__) -# define RECLS_COMPILER_IS_WATCOM -#elif defined(_MSC_VER) -# define RECLS_COMPILER_IS_MSVC -#else -# error Compiler not recognised -#endif /* compiler */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Includes - */ - -#if defined(RECLS_COMPILER_IS_BORLAND) -# include "recls_compiler_borland.h" -#elif defined(RECLS_COMPILER_IS_DMC) -# include "recls_compiler_dmc.h" -#elif defined(RECLS_COMPILER_IS_GCC) -# include "recls_compiler_gcc.h" -#elif defined(RECLS_COMPILER_IS_INTEL) -# include "recls_compiler_intel.h" -#elif defined(RECLS_COMPILER_IS_MWERKS) -# include "recls_compiler_mwerks.h" -#elif defined(RECLS_COMPILER_IS_WATCOM) -# include "recls_compiler_watcom.h" -#elif defined(RECLS_COMPILER_IS_MSVC) -# include "recls_compiler_msvc.h" -#else -# error Compiler not recognised. recls recognises Borland, CodeWarrior, Digital Mars, GCC, Intel, Visual C++ and Watcom. -#endif /* compiler */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Calling convention - */ - -/** \def RECLS_CALLCONV_NULL Unspecified calling convention for the \c recls API */ -/** \def RECLS_CALLCONV_CDECL \c cdecl calling convention for the \c recls API */ -/** \def RECLS_CALLCONV_STDDECL \c stdcall calling convention for the \c recls API */ -/** \def RECLS_CALLCONV_FASTDECL \c fastcall calling convention for the \c recls API */ -/** \def RECLS_CALLCONV_DEFAULT Default calling convention for the \c recls API */ - -#define RECLS_CALLCONV_NULL -#ifdef RECLS_DOCUMENTATION_SKIP_SECTION -# define RECLS_CALLCONV_CDECL -# define RECLS_CALLCONV_STDDECL -# define RECLS_CALLCONV_FASTDECL -# define RECLS_CALLCONV_DEFAULT -#elif defined(RECLS_PLATFORM_IS_WIN32) -# define RECLS_CALLCONV_CDECL __cdecl -# define RECLS_CALLCONV_STDDECL __stdcall -# define RECLS_CALLCONV_FASTDECL __fastcall -# define RECLS_CALLCONV_DEFAULT __stdcall -#elif defined(RECLS_PLATFORM_IS_WIN16) -# define RECLS_CALLCONV_CDECL _cdecl -# define RECLS_CALLCONV_STDDECL _pascal -# define RECLS_CALLCONV_FASTDECL _pascal -# define RECLS_CALLCONV_DEFAULT _pascal -#elif defined(RECLS_PLATFORM_IS_UNIX) -# define RECLS_CALLCONV_CDECL -# define RECLS_CALLCONV_STDDECL -# define RECLS_CALLCONV_FASTDECL -# define RECLS_CALLCONV_DEFAULT -#else -# error Platform not recognised -#endif /* __SYNSOFT_VAL_OS_WIN16 */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace - */ - -#if !defined(RECLS_NO_NAMESPACE) -namespace recls -{ -#endif /* !RECLS_NO_NAMESPACE */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Typedefs - */ - -/** \def recls_bool_t The boolean type of the \c recls API */ -typedef unsigned int recls_bool_t; - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace typedefs - */ - -#if !defined(RECLS_NO_NAMESPACE) -typedef recls_sint8_t sint8_t; -typedef recls_uint8_t uint8_t; - -typedef recls_sint16_t sint16_t; -typedef recls_uint16_t uint16_t; - -typedef recls_sint32_t sint32_t; -typedef recls_uint32_t uint32_t; - -typedef recls_sint64_t sint64_t; -typedef recls_uint64_t uint64_t; - -typedef recls_bool_t bool_t; -#endif /* !RECLS_NO_NAMESPACE */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Constants and definitions - */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace - */ - -#if !defined(RECLS_NO_NAMESPACE) -} /* namespace recls */ -#endif /* !RECLS_NO_NAMESPACE */ - -/* ////////////////////////////////////////////////////////////////////////// */ - -#endif /* !RECLS_INCL_H_RECLS_COMPILER */ - -/* ////////////////////////////////////////////////////////////////////////// */ diff -uNr gdc-0.17/d/phobos/etc/c/recls/recls_debug.h gdc-0.18/d/phobos/etc/c/recls/recls_debug.h --- gdc-0.17/d/phobos/etc/c/recls/recls_debug.h 2004-10-26 02:41:27.000000000 +0200 +++ gdc-0.18/d/phobos/etc/c/recls/recls_debug.h 1970-01-01 01:00:00.000000000 +0100 @@ -1,183 +0,0 @@ -/* ///////////////////////////////////////////////////////////////////////////// - * File: recls_debug.h - * - * Purpose: Compiler discrimination for the recls API. - * - * Created: 30th September 2003 - * Updated: 24th November 2003 - * - * License: (Licensed under the Synesis Software Standard Source License) - * - * Copyright (C) 2002-2003, Synesis Software Pty Ltd. - * - * All rights reserved. - * - * www: http://www.synesis.com.au/software - * http://www.recls.org/ - * - * email: submissions@recls.org for submissions - * admin@recls.org for other enquiries - * - * Redistribution and use in source and binary forms, with or - * without modification, are permitted provided that the following - * conditions are met: - * - * (i) Redistributions of source code must retain the above - * copyright notice and contact information, this list of - * conditions and the following disclaimer. - * - * (ii) Any derived versions of this software (howsoever modified) - * remain the sole property of Synesis Software. - * - * (iii) Any derived versions of this software (howsoever modified) - * remain subject to all these conditions. - * - * (iv) Neither the name of Synesis Software nor the names of any - * subdivisions, employees or agents of Synesis Software, nor the - * names of any other contributors to this software may be used to - * endorse or promote products derived from this software without - * specific prior written permission. - * - * This source code is provided by Synesis Software "as is" and any - * warranties, whether expressed or implied, including, but not - * limited to, the implied warranties of merchantability and - * fitness for a particular purpose are disclaimed. In no event - * shall the Synesis Software be liable for any direct, indirect, - * incidental, special, exemplary, or consequential damages - * (including, but not limited to, procurement of substitute goods - * or services; loss of use, data, or profits; or business - * interruption) however caused and on any theory of liability, - * whether in contract, strict liability, or tort (including - * negligence or otherwise) arising in any way out of the use of - * this software, even if advised of the possibility of such - * damage. - * - * ////////////////////////////////////////////////////////////////////////// */ - - -#ifndef RECLS_INCL_H_RECLS_DEBUG -#define RECLS_INCL_H_RECLS_DEBUG - -/* File version */ -#ifndef RECLS_DOCUMENTATION_SKIP_SECTION -# define RECLS_VER_H_RECLS_DEBUG_MAJOR 1 -# define RECLS_VER_H_RECLS_DEBUG_MINOR 0 -# define RECLS_VER_H_RECLS_DEBUG_REVISION 6 -# define RECLS_VER_H_RECLS_DEBUG_EDIT 6 -#endif /* !RECLS_DOCUMENTATION_SKIP_SECTION */ - -/** \file recls_debug.h Debug infrastructure for the \ref group_recls API */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Includes - */ - -#include "recls.h" -#if defined(RECLS_PLATFORM_IS_WIN32) && \ - defined(_DEBUG) -# include -# include -#endif /* _DEBUG && RECLS_PLATFORM_IS_WIN32 */ -#include - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace - */ - -#if !defined(RECLS_NO_NAMESPACE) -namespace recls -{ -#endif /* !RECLS_NO_NAMESPACE */ - -#if defined(_DEBUG) && \ - defined(RECLS_PLATFORM_IS_WIN32) -winstl_ns_using(last_error_scope) -winstl_ns_using(tls_index) -#endif /* _DEBUG && RECLS_PLATFORM_IS_WIN32 */ - -/* ///////////////////////////////////////////////////////////////////////////// - * debug_printf - */ - -#if defined(_DEBUG) && \ - defined(RECLS_PLATFORM_IS_WIN32) - -inline void debug_printf(char const *fmt, ...) -{ - va_list args; - char _sz[2048]; - - va_start(args, fmt); - - _vsnprintf(_sz, stlsoft_num_elements(_sz), fmt, args); - OutputDebugStringA(_sz); - - va_end(args); -} - -class function_scope -{ -public: - function_scope(char const *fn) - { - last_error_scope error_scope; - - strncpy(m_fn, fn, stlsoft_num_elements(m_fn) - 1); - debug_printf("%*s>> %s()\n", _post_inc(), "", m_fn); - } - ~function_scope() - { - last_error_scope error_scope; - - debug_printf("%*s<< %s()\n", _pre_dec(), "", m_fn); - } - -private: - typedef stlsoft::sint32_t int32_t; - - static int32_t _post_inc() - { - int32_t i = reinterpret_cast(::TlsGetValue(sm_index)); - int32_t r = i++; - - ::TlsSetValue(sm_index, reinterpret_cast(i)); - - return r; - } - static int32_t _pre_dec() - { - int32_t i = reinterpret_cast(::TlsGetValue(sm_index)); - int32_t r = --i; - - ::TlsSetValue(sm_index, reinterpret_cast(i)); - - return r; - } - -private: - char m_fn[1024]; - static tls_index sm_index; -}; - -# define function_scope_trace(f) function_scope _scope_ ## __LINE__(f) - -#else /* ? _DEBUG && RECLS_PLATFORM_IS_WIN32 */ -inline void _debug_printf(char const *, ...) -{} -# define debug_printf (0) ? ((void)0) : _debug_printf -# define function_scope_trace(f) do { ; } while(0) -#endif /* _DEBUG && RECLS_PLATFORM_IS_WIN32 */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace - */ - -#if !defined(RECLS_NO_NAMESPACE) -} /* namespace recls */ -#endif /* !RECLS_NO_NAMESPACE */ - -/* ////////////////////////////////////////////////////////////////////////// */ - -#endif /* !RECLS_INCL_H_RECLS_DEBUG */ - -/* ////////////////////////////////////////////////////////////////////////// */ diff -uNr gdc-0.17/d/phobos/etc/c/recls/recls_defs.h gdc-0.18/d/phobos/etc/c/recls/recls_defs.h --- gdc-0.17/d/phobos/etc/c/recls/recls_defs.h 2004-10-26 02:41:27.000000000 +0200 +++ gdc-0.18/d/phobos/etc/c/recls/recls_defs.h 1970-01-01 01:00:00.000000000 +0100 @@ -1,79 +0,0 @@ -/* ///////////////////////////////////////////////////////////////////////////// - * File: recls_defs.h - * - * Purpose: Definitions for the recls API. - * - * Created: 15th August 2003 - * Updated: 27th November 2003 - * - * License: (Licensed under the Synesis Software Standard Source License) - * - * Copyright (C) 2002-2003, Synesis Software Pty Ltd. - * - * All rights reserved. - * - * www: http://www.synesis.com.au/software - * http://www.recls.org/ - * - * email: submissions@recls.org for submissions - * admin@recls.org for other enquiries - * - * Redistribution and use in source and binary forms, with or - * without modification, are permitted provided that the following - * conditions are met: - * - * (i) Redistributions of source code must retain the above - * copyright notice and contact information, this list of - * conditions and the following disclaimer. - * - * (ii) Any derived versions of this software (howsoever modified) - * remain the sole property of Synesis Software. - * - * (iii) Any derived versions of this software (howsoever modified) - * remain subject to all these conditions. - * - * (iv) Neither the name of Synesis Software nor the names of any - * subdivisions, employees or agents of Synesis Software, nor the - * names of any other contributors to this software may be used to - * endorse or promote products derived from this software without - * specific prior written permission. - * - * This source code is provided by Synesis Software "as is" and any - * warranties, whether expressed or implied, including, but not - * limited to, the implied warranties of merchantability and - * fitness for a particular purpose are disclaimed. In no event - * shall the Synesis Software be liable for any direct, indirect, - * incidental, special, exemplary, or consequential damages - * (including, but not limited to, procurement of substitute goods - * or services; loss of use, data, or profits; or business - * interruption) however caused and on any theory of liability, - * whether in contract, strict liability, or tort (including - * negligence or otherwise) arising in any way out of the use of - * this software, even if advised of the possibility of such - * damage. - * - * ////////////////////////////////////////////////////////////////////////// */ - - -#ifndef RECLS_INCL_H_RECLS_DEFS -#define RECLS_INCL_H_RECLS_DEFS - -/* ///////////////////////////////////////////////////////////////////////////// - * Includes - */ - -#if defined( - - -#ifdef __cplusplus - -#include - - - - -/* ////////////////////////////////////////////////////////////////////////// */ - -#ifndef RECLS_INCL_H_RECLS_DEFS - -/* ////////////////////////////////////////////////////////////////////////// */ diff -uNr gdc-0.17/d/phobos/etc/c/recls/recls_fileinfo.cpp gdc-0.18/d/phobos/etc/c/recls/recls_fileinfo.cpp --- gdc-0.17/d/phobos/etc/c/recls/recls_fileinfo.cpp 2004-10-26 02:41:27.000000000 +0200 +++ gdc-0.18/d/phobos/etc/c/recls/recls_fileinfo.cpp 1970-01-01 01:00:00.000000000 +0100 @@ -1,88 +0,0 @@ -/* ///////////////////////////////////////////////////////////////////////////// - * File: recls_api.cpp - * - * Purpose: Main (platform-independent) implementation file for the recls API. - * - * Created: 16th August 2003 - * Updated: 27th November 2003 - * - * License: (Licensed under the Synesis Software Standard Source License) - * - * Copyright (C) 2002-2003, Synesis Software Pty Ltd. - * - * All rights reserved. - * - * www: http://www.synesis.com.au/software - * http://www.recls.org/ - * - * email: submissions@recls.org for submissions - * admin@recls.org for other enquiries - * - * Redistribution and use in source and binary forms, with or - * without modification, are permitted provided that the following - * conditions are met: - * - * (i) Redistributions of source code must retain the above - * copyright notice and contact information, this list of - * conditions and the following disclaimer. - * - * (ii) Any derived versions of this software (howsoever modified) - * remain the sole property of Synesis Software. - * - * (iii) Any derived versions of this software (howsoever modified) - * remain subject to all these conditions. - * - * (iv) Neither the name of Synesis Software nor the names of any - * subdivisions, employees or agents of Synesis Software, nor the - * names of any other contributors to this software may be used to - * endorse or promote products derived from this software without - * specific prior written permission. - * - * This source code is provided by Synesis Software "as is" and any - * warranties, whether expressed or implied, including, but not - * limited to, the implied warranties of merchantability and - * fitness for a particular purpose are disclaimed. In no event - * shall the Synesis Software be liable for any direct, indirect, - * incidental, special, exemplary, or consequential damages - * (including, but not limited to, procurement of substitute goods - * or services; loss of use, data, or profits; or business - * interruption) however caused and on any theory of liability, - * whether in contract, strict liability, or tort (including - * negligence or otherwise) arising in any way out of the use of - * this software, even if advised of the possibility of such - * damage. - * - * ////////////////////////////////////////////////////////////////////////// */ - - -/* ///////////////////////////////////////////////////////////////////////////// - * Includes - */ - -#include "recls.h" -#include "recls_internal.h" -#include "recls_assert.h" - -#ifdef __cplusplus -# include -#endif /* __cplusplus */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace - */ - -#if !defined(RECLS_NO_NAMESPACE) -namespace recls -{ -#endif /* !RECLS_NO_NAMESPACE */ - - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace - */ - -#if !defined(RECLS_NO_NAMESPACE) -} /* namespace recls */ -#endif /* !RECLS_NO_NAMESPACE */ - -/* ////////////////////////////////////////////////////////////////////////// */ diff -uNr gdc-0.17/d/phobos/etc/c/recls/recls_fileinfo_unix.cpp gdc-0.18/d/phobos/etc/c/recls/recls_fileinfo_unix.cpp --- gdc-0.17/d/phobos/etc/c/recls/recls_fileinfo_unix.cpp 2004-10-26 02:41:27.000000000 +0200 +++ gdc-0.18/d/phobos/etc/c/recls/recls_fileinfo_unix.cpp 1970-01-01 01:00:00.000000000 +0100 @@ -1,307 +0,0 @@ -/* ///////////////////////////////////////////////////////////////////////////// - * File: recls_fileinfo_unix.cpp - * - * Purpose: UNIX implementation for the file information blocks of the recls API. - * - * Created: 2nd November 2003 - * Updated: 27th November 2003 - * - * License: (Licensed under the Synesis Software Standard Source License) - * - * Copyright (C) 2002-2003, Synesis Software Pty Ltd. - * - * All rights reserved. - * - * www: http://www.synesis.com.au/software - * http://www.recls.org/ - * - * email: submissions@recls.org for submissions - * admin@recls.org for other enquiries - * - * Redistribution and use in source and binary forms, with or - * without modification, are permitted provided that the following - * conditions are met: - * - * (i) Redistributions of source code must retain the above - * copyright notice and contact information, this list of - * conditions and the following disclaimer. - * - * (ii) Any derived versions of this software (howsoever modified) - * remain the sole property of Synesis Software. - * - * (iii) Any derived versions of this software (howsoever modified) - * remain subject to all these conditions. - * - * (iv) Neither the name of Synesis Software nor the names of any - * subdivisions, employees or agents of Synesis Software, nor the - * names of any other contributors to this software may be used to - * endorse or promote products derived from this software without - * specific prior written permission. - * - * This source code is provided by Synesis Software "as is" and any - * warranties, whether expressed or implied, including, but not - * limited to, the implied warranties of merchantability and - * fitness for a particular purpose are disclaimed. In no event - * shall the Synesis Software be liable for any direct, indirect, - * incidental, special, exemplary, or consequential damages - * (including, but not limited to, procurement of substitute goods - * or services; loss of use, data, or profits; or business - * interruption) however caused and on any theory of liability, - * whether in contract, strict liability, or tort (including - * negligence or otherwise) arising in any way out of the use of - * this software, even if advised of the possibility of such - * damage. - * - * ////////////////////////////////////////////////////////////////////////// */ - - -/* ///////////////////////////////////////////////////////////////////////////// - * Includes - */ - -#include "recls.h" -#include "recls_internal.h" -#include "recls_assert.h" - -#include -#include - -// For ease of debugging for those of you (us?) that prefer working on Win32, -// the definition of EMULATE_UNIX_ON_WIN32 will allow you to do so. -#if defined(EMULATE_UNIX_ON_WIN32) -# include -# if defined(_MT) || \ - defined(__MT__) -# ifndef _REENTRANT -# define _REENTRANT -# endif /* !_REENTRANT */ -# define RECLS_FILEINFO_MULTITHREADED -# endif /* _MT || __MT__ */ -#else /* ? EMULATE_UNIX_ON_WIN32 */ -# if defined(_REENTRANT) -# define RECLS_FILEINFO_MULTITHREADED -# endif /* _REENTRANT */ -#endif /* EMULATE_UNIX_ON_WIN32 */ - - -//#define RECLS_UNIX_USE_ATOMIC_OPERATIONS // Define this if you're on Linux (and you know what you're doing!) - -#if defined(RECLS_FILEINFO_MULTITHREADED) - // If we're multi-threading, then we have two options: -# if defined(RECLS_UNIX_USE_ATOMIC_OPERATIONS) - // 1. On Linux we can use the kernel's atomic operations, since all we need - // is atomic integer operations. Since these kernel operations are not - // standard, you must explicitly select them in your build by defining - // the symbol RECLS_UNIX_USE_ATOMIC_OPERATIONS -# include -# else /* ? RECLS_UNIX_USE_ATOMIC_OPERATIONS */ - // 2. On other UNIX systems we use the UNIXSTL thread_mutex class -# include -# endif /* !RECLS_UNIX_USE_ATOMIC_OPERATIONS */ -#else /* ? RECLS_FILEINFO_MULTITHREADED */ - // When not multi-threaded, we just use the STLSoft null_mutex class, which - // is just a stub -# include -#endif /* RECLS_FILEINFO_MULTITHREADED */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace - */ - -#if !defined(RECLS_NO_NAMESPACE) -namespace recls -{ -#endif /* !RECLS_NO_NAMESPACE */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Typedefs - */ - -#if defined(RECLS_FILEINFO_MULTITHREADED) && \ - defined(RECLS_UNIX_USE_ATOMIC_OPERATIONS) -typedef atomic_t rc_atomic_t; -# define rc_atomic_init(x) ATOMIC_INIT(x) -#else /* ? RECLS_FILEINFO_MULTITHREADED && RECLS_UNIX_USE_ATOMIC_OPERATIONS */ -typedef recls_sint32_t rc_atomic_t; -# define rc_atomic_init(x) x -#endif /* RECLS_FILEINFO_MULTITHREADED && RECLS_UNIX_USE_ATOMIC_OPERATIONS */ - -struct counted_recls_info_t -{ - volatile rc_atomic_t rc; - recls_uint32_t _; - struct recls_fileinfo_t info; -}; - -/* ///////////////////////////////////////////////////////////////////////////// - * Constants and definitions - */ - -#if !defined(RECLS_NO_NAMESPACE) -namespace -{ -#else -static -#endif /* !RECLS_NO_NAMESPACE */ - -volatile rc_atomic_t s_createdInfoBlocks = rc_atomic_init(0); -volatile rc_atomic_t s_sharedInfoBlocks = rc_atomic_init(0); - -#if !defined(RECLS_NO_NAMESPACE) -} // namespace recls -#endif /* !RECLS_NO_NAMESPACE */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Helpers - */ - -#if !defined(RECLS_UNIX_USE_ATOMIC_OPERATIONS) -namespace -{ -#if defined(RECLS_FILEINFO_MULTITHREADED) -// unixstl::process_mutex s_mx(true); - unixstl::thread_mutex s_mx(true); - typedef unixstl::thread_mutex mutex_t; -#else /* ? RECLS_FILEINFO_MULTITHREADED */ - stlsoft::null_mutex s_mx; - - typedef stlsoft::null_mutex mutex_t; -#endif /* RECLS_FILEINFO_MULTITHREADED */ -} -#endif /* !RECLS_UNIX_USE_ATOMIC_OPERATIONS */ - -inline void RC_PreIncrement(rc_atomic_t volatile *p) -{ -#if defined(RECLS_UNIX_USE_ATOMIC_OPERATIONS) - - atomic_inc(p); - -#else /* ? RECLS_UNIX_USE_ATOMIC_OPERATIONS */ - stlsoft::lock_scope lock(s_mx); - - ++(*p); -#endif /* !RECLS_UNIX_USE_ATOMIC_OPERATIONS */ -} - -inline recls_sint32_t RC_PreDecrement(rc_atomic_t volatile *p) -{ -#if defined(RECLS_UNIX_USE_ATOMIC_OPERATIONS) - - return 1 + atomic_dec_and_test(p); - -#else /* ? RECLS_UNIX_USE_ATOMIC_OPERATIONS */ - stlsoft::lock_scope lock(s_mx); - - return --(*p); -#endif /* !RECLS_UNIX_USE_ATOMIC_OPERATIONS */ -} - -inline recls_sint32_t RC_ReadValue(rc_atomic_t volatile *p) -{ -#if defined(RECLS_UNIX_USE_ATOMIC_OPERATIONS) - - return atomic_read(p); - -#else /* ? RECLS_UNIX_USE_ATOMIC_OPERATIONS */ - stlsoft::lock_scope lock(s_mx); - - return (*p); -#endif /* !RECLS_UNIX_USE_ATOMIC_OPERATIONS */ -} - -inline struct counted_recls_info_t *counted_info_from_info(recls_info_t i) -{ - recls_assert(i != NULL); - - // can't be bothered with all the C++ casts here! - return (struct counted_recls_info_t *)((recls_byte_t*)i - offsetof(counted_recls_info_t, info)); -} - -inline recls_info_t info_from_counted_info(struct counted_recls_info_t * ci) -{ - recls_assert(ci != NULL); - - return &ci->info; -} - -/* ///////////////////////////////////////////////////////////////////////////// - * File info functions - */ - -RECLS_FNDECL(recls_info_t) FileInfo_Allocate(size_t cb) -{ - // Simply allocate a lock-count prior to the main memory (but do it on an 8-byte block) - counted_recls_info_t *ci = static_cast(malloc(cb - sizeof(struct recls_fileinfo_t) + sizeof(struct counted_recls_info_t))); - recls_info_t info; - - if(NULL == ci) - { - info = NULL; - } - else - { - rc_atomic_t initial = rc_atomic_init(1); - - ci->rc = initial; // One initial reference - info = info_from_counted_info(ci); - - RC_PreIncrement(&s_createdInfoBlocks); - } - - return info; -} - -RECLS_FNDECL(void) FileInfo_Release(recls_info_t fileInfo) -{ - if(NULL != fileInfo) - { - counted_recls_info_t *pci = counted_info_from_info(fileInfo); - - if(0 == RC_PreDecrement(&pci->rc)) - { - free(pci); - - RC_PreDecrement(&s_createdInfoBlocks); - } - else - { - RC_PreDecrement(&s_sharedInfoBlocks); - } - } -} - -RECLS_FNDECL(recls_rc_t) FileInfo_Copy(recls_info_t fileInfo, recls_info_t *pinfo) -{ - recls_assert(NULL != pinfo); - - if(NULL != fileInfo) - { - counted_recls_info_t *pci = counted_info_from_info(fileInfo); - - RC_PreIncrement(&pci->rc); - RC_PreIncrement(&s_sharedInfoBlocks); - } - - *pinfo = fileInfo; - - return RECLS_RC_OK; -} - -RECLS_FNDECL(void) FileInfo_BlockCount(recls_sint32_t *pcCreated, recls_sint32_t *pcShared) -{ - recls_assert(NULL != pcCreated); - recls_assert(NULL != pcShared); - - *pcCreated = RC_ReadValue(&s_createdInfoBlocks); - *pcShared = RC_ReadValue(&s_sharedInfoBlocks); -} - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace - */ - -#if !defined(RECLS_NO_NAMESPACE) -} /* namespace recls */ -#endif /* !RECLS_NO_NAMESPACE */ - -/* ////////////////////////////////////////////////////////////////////////// */ diff -uNr gdc-0.17/d/phobos/etc/c/recls/recls_fileinfo_win32.cpp gdc-0.18/d/phobos/etc/c/recls/recls_fileinfo_win32.cpp --- gdc-0.17/d/phobos/etc/c/recls/recls_fileinfo_win32.cpp 2004-10-26 02:41:27.000000000 +0200 +++ gdc-0.18/d/phobos/etc/c/recls/recls_fileinfo_win32.cpp 1970-01-01 01:00:00.000000000 +0100 @@ -1,225 +0,0 @@ -/* ///////////////////////////////////////////////////////////////////////////// - * File: recls_fileinfo_win32.cpp - * - * Purpose: Win32 implementation for the file information blocks of the recls API. - * - * Created: 16th August 2003 - * Updated: 27th November 2003 - * - * License: (Licensed under the Synesis Software Standard Source License) - * - * Copyright (C) 2002-2003, Synesis Software Pty Ltd. - * - * All rights reserved. - * - * www: http://www.synesis.com.au/software - * http://www.recls.org/ - * - * email: submissions@recls.org for submissions - * admin@recls.org for other enquiries - * - * Redistribution and use in source and binary forms, with or - * without modification, are permitted provided that the following - * conditions are met: - * - * (i) Redistributions of source code must retain the above - * copyright notice and contact information, this list of - * conditions and the following disclaimer. - * - * (ii) Any derived versions of this software (howsoever modified) - * remain the sole property of Synesis Software. - * - * (iii) Any derived versions of this software (howsoever modified) - * remain subject to all these conditions. - * - * (iv) Neither the name of Synesis Software nor the names of any - * subdivisions, employees or agents of Synesis Software, nor the - * names of any other contributors to this software may be used to - * endorse or promote products derived from this software without - * specific prior written permission. - * - * This source code is provided by Synesis Software "as is" and any - * warranties, whether expressed or implied, including, but not - * limited to, the implied warranties of merchantability and - * fitness for a particular purpose are disclaimed. In no event - * shall the Synesis Software be liable for any direct, indirect, - * incidental, special, exemplary, or consequential damages - * (including, but not limited to, procurement of substitute goods - * or services; loss of use, data, or profits; or business - * interruption) however caused and on any theory of liability, - * whether in contract, strict liability, or tort (including - * negligence or otherwise) arising in any way out of the use of - * this software, even if advised of the possibility of such - * damage. - * - * ////////////////////////////////////////////////////////////////////////// */ - - -/* ///////////////////////////////////////////////////////////////////////////// - * Includes - */ - -#include "recls.h" -#include "recls_internal.h" -#include "recls_assert.h" - -#include - -#include - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace - */ - -#if !defined(RECLS_NO_NAMESPACE) -namespace recls -{ -#endif /* !RECLS_NO_NAMESPACE */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Constants and definitions - */ - -#if !defined(RECLS_NO_NAMESPACE) -namespace -{ -#else -static -#endif /* !RECLS_NO_NAMESPACE */ - -volatile recls_sint32_t s_createdInfoBlocks = 0; -volatile recls_sint32_t s_sharedInfoBlocks = 0; - -#if !defined(RECLS_NO_NAMESPACE) -} // namespace recls -#endif /* !RECLS_NO_NAMESPACE */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Typedefs - */ - -struct counted_recls_info_t -{ - volatile recls_sint32_t rc; - recls_uint32_t _; - struct recls_fileinfo_t info; -}; - -/* ///////////////////////////////////////////////////////////////////////////// - * Helpers - */ - -inline recls_sint32_t RC_PreIncrement(recls_sint32_t volatile *p) -{ - return winstl::atomic_preincrement(p); -} - -inline recls_sint32_t RC_PreDecrement(recls_sint32_t volatile *p) -{ - return winstl::atomic_predecrement(p); -} - -inline struct counted_recls_info_t *counted_info_from_info(recls_info_t i) -{ - recls_assert(i != NULL); - - // can't be bothered with all the C++ casts here! - return (struct counted_recls_info_t *)((recls_byte_t*)i - offsetof(counted_recls_info_t, info)); -} - -inline recls_info_t info_from_counted_info(struct counted_recls_info_t * ci) -{ - recls_assert(ci != NULL); - - return &ci->info; -} - -/* ///////////////////////////////////////////////////////////////////////////// - * File info functions - */ - -RECLS_FNDECL(recls_info_t) FileInfo_Allocate(size_t cb) -{ - // Simply allocate a lock-count prior to the main memory (but do it on an 8-byte block) - counted_recls_info_t *ci = static_cast(malloc(cb - sizeof(struct recls_fileinfo_t) + sizeof(struct counted_recls_info_t))); - recls_info_t info; - - if(NULL == ci) - { - info = NULL; - } - else - { - ci->rc = 1; // One initial reference - info = info_from_counted_info(ci); - - RC_PreIncrement(&s_createdInfoBlocks); - } - - return info; -} - -RECLS_FNDECL(void) FileInfo_Release(recls_info_t fileInfo) -{ - if(NULL != fileInfo) - { - counted_recls_info_t *pci = counted_info_from_info(fileInfo); - - if(0 == RC_PreDecrement(&pci->rc)) - { - free(pci); - - RC_PreDecrement(&s_createdInfoBlocks); - } - else - { - RC_PreDecrement(&s_sharedInfoBlocks); - } - } -} - -RECLS_FNDECL(recls_rc_t) FileInfo_Copy(recls_info_t fileInfo, recls_info_t *pinfo) -{ - recls_assert(NULL != pinfo); - - if(NULL != fileInfo) - { - counted_recls_info_t *pci = counted_info_from_info(fileInfo); - - RC_PreIncrement(&pci->rc); - RC_PreIncrement(&s_sharedInfoBlocks); - } - - *pinfo = fileInfo; - - return RECLS_RC_OK; -} - -RECLS_FNDECL(void) FileInfo_BlockCount(recls_sint32_t *pcCreated, recls_sint32_t *pcShared) -{ - recls_assert(NULL != pcCreated); - recls_assert(NULL != pcShared); - - // Because on 3.51 and 95, the InterlockedInc/Decrement functions do not - // return the values, we're going to fudge it - - RC_PreIncrement(&s_createdInfoBlocks); - recls_sint32_t createdInfoBlocks = s_createdInfoBlocks; - RC_PreDecrement(&s_createdInfoBlocks); - *pcCreated = createdInfoBlocks - 1; - - RC_PreIncrement(&s_sharedInfoBlocks); - recls_sint32_t sharedInfoBlocks = s_sharedInfoBlocks; - RC_PreDecrement(&s_sharedInfoBlocks); - *pcShared = sharedInfoBlocks - 1; -} - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace - */ - -#if !defined(RECLS_NO_NAMESPACE) -} /* namespace recls */ -#endif /* !RECLS_NO_NAMESPACE */ - -/* ////////////////////////////////////////////////////////////////////////// */ diff -uNr gdc-0.17/d/phobos/etc/c/recls/recls.h gdc-0.18/d/phobos/etc/c/recls/recls.h --- gdc-0.17/d/phobos/etc/c/recls/recls.h 2004-10-26 02:41:27.000000000 +0200 +++ gdc-0.18/d/phobos/etc/c/recls/recls.h 1970-01-01 01:00:00.000000000 +0100 @@ -1,655 +0,0 @@ -/* ///////////////////////////////////////////////////////////////////////////// - * File: recls.h - * - * Purpose: Main header file for the recls API. - * - * Created: 15th August 2003 - * Updated: 21st November 2003 - * - * License: (Licensed under the Synesis Software Standard Source License) - * - * Copyright (C) 2002-2003, Synesis Software Pty Ltd. - * - * All rights reserved. - * - * www: http://www.synesis.com.au/software - * http://www.recls.org/ - * - * email: submissions@recls.org for submissions - * admin@recls.org for other enquiries - * - * Redistribution and use in source and binary forms, with or - * without modification, are permitted provided that the following - * conditions are met: - * - * (i) Redistributions of source code must retain the above - * copyright notice and contact information, this list of - * conditions and the following disclaimer. - * - * (ii) Any derived versions of this software (howsoever modified) - * remain the sole property of Synesis Software. - * - * (iii) Any derived versions of this software (howsoever modified) - * remain subject to all these conditions. - * - * (iv) Neither the name of Synesis Software nor the names of any - * subdivisions, employees or agents of Synesis Software, nor the - * names of any other contributors to this software may be used to - * endorse or promote products derived from this software without - * specific prior written permission. - * - * This source code is provided by Synesis Software "as is" and any - * warranties, whether expressed or implied, including, but not - * limited to, the implied warranties of merchantability and - * fitness for a particular purpose are disclaimed. In no event - * shall the Synesis Software be liable for any direct, indirect, - * incidental, special, exemplary, or consequential damages - * (including, but not limited to, procurement of substitute goods - * or services; loss of use, data, or profits; or business - * interruption) however caused and on any theory of liability, - * whether in contract, strict liability, or tort (including - * negligence or otherwise) arising in any way out of the use of - * this software, even if advised of the possibility of such - * damage. - * - * ////////////////////////////////////////////////////////////////////////// */ - - -#ifndef RECLS_INCL_H_RECLS -#define RECLS_INCL_H_RECLS - -/* File version */ -#ifndef RECLS_DOCUMENTATION_SKIP_SECTION -# define RECLS_VER_H_RECLS_MAJOR 1 -# define RECLS_VER_H_RECLS_MINOR 5 -# define RECLS_VER_H_RECLS_REVISION 2 -# define RECLS_VER_H_RECLS_EDIT 24 -#endif /* !RECLS_DOCUMENTATION_SKIP_SECTION */ - -/** \file recls.h The root header for the \ref group_recls API */ - -/** \name recls API Version - * - * \ingroup group_recls - */ -/** @{ */ -/** \def RECLS_VER_MAJOR The major version number of RECLS */ - -/** \def RECLS_VER_MINOR The minor version number of RECLS */ - -/** \def RECLS_VER_REVISION The revision version number of RECLS */ - -/** \def RECLS_VER The current composite version number of RECLS */ -/** @} */ - -/* recls version */ -#define RECLS_VER_MAJOR 1 -#define RECLS_VER_MINOR 2 -#define RECLS_VER_REVISION 1 -#define RECLS_VER_1_0_1 0x01000100 -#define RECLS_VER_1_1_1 0x01010100 -#define RECLS_VER_1_2_1 0x01020100 -#define RECLS_VER RECLS_VER_1_2_1 - -/* ///////////////////////////////////////////////////////////////////////////// - * Strictness - */ - -#ifndef RECLS_NO_STRICT -# define RECLS_STRICT -#endif /* !RECLS_NO_STRICT */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Includes - */ - -/* Detects C & C++ things, such as namespace support */ -#include "recls_language.h" -/* Includes platform-specific headers */ -#include "recls_platform.h" -/* Includes stddef.h / cstddef, and defines the recls types: recls_s/uint8/16/32/64_t */ -#include "recls_compiler.h" -/* Defines recls_filesize_t, recls_time_t */ -#include "recls_platform_types.h" - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace - */ - -#if !defined(RECLS_NO_NAMESPACE) -namespace recls -{ -#endif /* !RECLS_NO_NAMESPACE */ - -#if !defined(RECLS_NO_NAMESPACE) -# define RECLS_QUAL(x) ::recls::x -#else -# define RECLS_QUAL(x) x -#endif /* !RECLS_NO_NAMESPACE */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Pre-processor discrimination - */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Function specifications - */ - -/*** Defines the recls linkage and calling convention */ -#define RECLS_FNDECL(rt) RECLS_LINKAGE_C rt RECLS_CALLCONV_DEFAULT - -/* ///////////////////////////////////////////////////////////////////////////// - * Typedefs - */ - -/* recls_rc_t */ -#ifdef __cplusplus - -/** The type of return codes issued by the API functions */ -typedef recls_sint32_t recls_rc_t; - -/** General success code */ -const recls_rc_t RECLS_RC_OK(0); -/** General failure code */ -const recls_rc_t RECLS_RC_FAIL(-1); - -/** Returns non-zero if the given return code indicates failure */ -inline bool RECLS_FAILED(recls_rc_t const &rc) -{ - return rc < 0; -} - -/** Returns non-zero if the given return code indicates success */ -inline bool RECLS_SUCCEEDED(recls_rc_t const &rc) -{ - return !RECLS_FAILED(rc); -} - -#else /* ? __cplusplus */ - -/** The type of return codes issued by the API functions */ -typedef recls_sint32_t recls_rc_t; - -/** General success code */ -#define RECLS_RC_OK (0) -/** General failure code */ -#define RECLS_RC_FAIL (-1) - -/** Evaluates to non-zero if the given return code indicates failure */ -#define RECLS_FAILED(rc) ((rc) < 0) -/** Evaluates to non-zero if the given return code indicates success */ -#define RECLS_SUCCEEDED(rc) (!FAILED(rc)) - -#endif /* __cplusplus */ - - -/* hrecls_t */ -struct hrecls_t_; -/** The handle to a recursive search operation */ -typedef struct hrecls_t_ const * hrecls_t; - - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace - */ - -#if !defined(RECLS_NO_NAMESPACE) -} /* namespace recls */ -#endif /* !RECLS_NO_NAMESPACE */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Includes - */ - -/* Defines result codes */ -#include "recls_retcodes.h" - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace - */ - -#if !defined(RECLS_NO_NAMESPACE) -namespace recls -{ -#endif /* !RECLS_NO_NAMESPACE */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Flags - */ - -/** \brief Search flags - * \ingroup group_recls - * - * These flags moderate the search behaviour of the - * \link recls::Recls_Search Recls_Search\endlink and - * \link recls::Recls_SearchProcess Recls_SearchProcess\endlink functions. - */ -enum RECLS_FLAG -{ - RECLS_F_FILES = 0x00000001 /*!< Include files in search. Included by default if none specified */ - , RECLS_F_DIRECTORIES = 0x00000002 /*!< Include directories in search. Not currently supported. */ - , RECLS_F_LINKS = 0x00000004 /*!< Include links in search. Ignored in Win32. */ - , RECLS_F_DEVICES = 0x00000008 /*!< Include devices in search. Not currently supported. */ - , RECLS_F_TYPEMASK = 0x00000FFF - , RECLS_F_RECURSIVE = 0x00010000 /*!< Searches given directory and all sub-directories */ - , RECLS_F_NO_FOLLOW_LINKS = 0x00020000 /*!< Does not expand links */ - , RECLS_F_DIRECTORY_PARTS = 0x00040000 /*!< Fills out the directory parts. Supported from version 1.1.1 onwards. */ - , RECLS_F_DETAILS_LATER = 0x00080000 /*!< Does not fill out anything other than the path. Not currently supported. */ -}; - -#if !defined(__cplusplus) && \ - !defined(RECLS_DOCUMENTATION_SKIP_SECTION) -typedef enum RECLS_FLAG RECLS_FLAG; -#endif /* !__cplusplus && !RECLS_DOCUMENTATION_SKIP_SECTION */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Typedefs - */ - -struct recls_fileinfo_t; - -/** Opaque type representing a file-system entry information */ -typedef struct recls_fileinfo_t const *recls_info_t; - -/** Opaque type representing a user-defined parameter to the process function */ -typedef void *recls_process_fn_param_t; - -/** User-supplied process function, used by Recls_SearchProcess() - * - * \param info entry info structure - * \param param the parameter passed to Recls_SearchProcess() - * \return A status to indicate whether to continue or cancel the processing - * \retval 0 cancel the processing - * \retval non-0 continue the processing - */ -typedef int (RECLS_CALLCONV_DEFAULT *hrecls_process_fn_t)(recls_info_t info, recls_process_fn_param_t param); - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace typedefs - */ - -#if !defined(RECLS_NO_NAMESPACE) -typedef recls_info_t info_t; -typedef recls_process_fn_param_t process_fn_param_t; -#endif /* !RECLS_NO_NAMESPACE */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Functions - */ - -/*************************************** - * Search control - */ - -/** \name Search control functions - * - * \ingroup group_recls - */ -/** @{ */ - -/** Searches a given directory for matching files of the given pattern - * - * - * \param searchRoot The directory representing the root of the search - * \param pattern The search pattern, e.g. "*.c" - * \param flags A combination of 0 or more RECLS_FLAG values - * \param phSrch Address of the search handle - * \return A status code indicating success/failure - * - */ -RECLS_FNDECL(recls_rc_t) Recls_Search( recls_char_t const *searchRoot - , recls_char_t const *pattern - , recls_uint32_t flags - , hrecls_t *phSrch); - -/** Searches a given directory for matching files of the given pattern, and processes them according to the given process function - * - * \param searchRoot The directory representing the root of the search - * \param pattern The search pattern, e.g. "*.c" - * \param flags A combination of 0 or more RECLS_FLAG values - * \param pfn The processing function - * \param param A caller-supplied parameter that is passed through to \c pfn on each invocation. The function can cancel the enumeration by returning 0 - * \return A status code indicating success/failure - * - * \note Available from version 1.1 of the recls API - */ -RECLS_FNDECL(recls_rc_t) Recls_SearchProcess( recls_char_t const *searchRoot - , recls_char_t const *pattern - , recls_uint32_t flags - , hrecls_process_fn_t pfn - , recls_process_fn_param_t param); - -/** Closes the given search - * - * \param hSrch Handle of the search to close. May not be NULL. - */ -RECLS_FNDECL(void) Recls_SearchClose( hrecls_t hSrch); - -/** @} */ - -/*************************************** - * Search enumeration - */ - -/** \name Search enumeration functions - * - * \ingroup group_recls - */ -/** @{ */ - -/** Advances the search one position - * - * \param hSrch Handle of the search to close. May not be NULL. - * \return Status code - * \retval RECLS_RC_OK Position was advanced; search handle can be queried for details - * \retval RECLS_RC_NO_MORE_DATA There are no more items in the search - * \retval Any other status code indicates an error - */ -RECLS_FNDECL(recls_rc_t) Recls_GetNext( hrecls_t hSrch); - -/** Advances the search one position, and retrieves the information for the new position - * - * \param hSrch Handle of the search to close. May not be NULL. - * \param phEntry Pointer to receive entry info structure. - * \return Status code - * \retval RECLS_RC_OK Position was advanced; search handle can be queried for details - * \retval RECLS_RC_NO_MORE_DATA There are no more items in the search - * \retval Any other status code indicates an error - */ -RECLS_FNDECL(recls_rc_t) Recls_GetDetails( hrecls_t hSrch - , recls_info_t *phEntry); - -/** Retrieves the information for the current search position - * - * \param hSrch Handle of the search to close. May not be NULL. - * \param phEntry Pointer to receive entry info structure. - * \return Status code - * \retval RECLS_RC_OK Position was advanced; search handle can be queried for details - * \retval Any other status code indicates an error - */ -RECLS_FNDECL(recls_rc_t) Recls_GetNextDetails( hrecls_t hSrch - , recls_info_t *phEntry); - -/** @} */ - -/*************************************** - * File entry info structure - */ - -/** \name File entry info structure functions - * - * \ingroup group_recls - */ -/** @{ */ - -/** Releases the resources associated with an entry info structure. - * - * \param hEntry The info entry structure. - */ -RECLS_FNDECL(void) Recls_CloseDetails( recls_info_t hEntry); - -/** Copies an entry info structure. - * - * \param hEntry The info entry structure. - * \param phEntry Address to receive a copy of the info entry structure. May not be NULL. - * \return Status code - * \retval RECLS_RC_OK Entry was generated. - * \retval Any other status code indicates an error - */ -RECLS_FNDECL(recls_rc_t) Recls_CopyDetails( recls_info_t hEntry - , recls_info_t *phEntry); - -/** Reports on the number of outstanding (i.e. in client code) file entry info structures - * - * \param hSrch Handle of the search to close. May not be NULL. - * \param count Pointer to an integer variable to receive the result. - * \return Status code - * \retval RECLS_RC_OK Information was retrieved. - * \retval Any other status code indicates an error - */ -RECLS_FNDECL(recls_rc_t) Recls_OutstandingDetails(hrecls_t hSrch - , recls_uint32_t *count); - -/** @} */ - -/*************************************** - * Error handling - */ - -/** \name Error handling functions - * - * \ingroup group_recls - */ -/** @{ */ - -/** Returns the last error code associated with the given search handle - * - * \param hSrch Handle of the search to close. May not be NULL. - * \return The last error code for the search handle - */ -RECLS_FNDECL(recls_rc_t) Recls_GetLastError( hrecls_t hSrch); - -/** Gets the error string representing the given error - * - * \param rc The error code - * \param buffer Pointer to character buffer in which to write the error. If NULL, the function returns the number of characters required. - * \param cchBuffer Number of character spaces in \c buffer. Ignored if \c buffer is NULL. - * \return The number of characters written to the buffer, or required for, the error. - */ -RECLS_FNDECL(size_t) Recls_GetErrorString( recls_rc_t rc - , recls_char_t *buffer - , size_t cchBuffer); - -/** Gets the error string representing the current error associated with the given search handle - * - * \param hSrch Handle of the search to close. May not be NULL. - * \param buffer Pointer to character buffer in which to write the error. If NULL, the function returns the number of characters required. - * \param cchBuffer Number of character spaces in \c buffer. Ignored if \c buffer is NULL. - * \return The number of characters written to the buffer, or required for, the error. - */ -RECLS_FNDECL(size_t) Recls_GetLastErrorString( hrecls_t hSrch - , recls_char_t *buffer - , size_t cchBuffer); - -/** @} */ - -/*************************************** - * Property elicitation - */ - -/** \name Property elicitation functions - * - * \ingroup group_recls - */ -/** @{ */ - -/** Retrieves the full path of the given entry recls_fileinfo_t - * - * \param hEntry The entry recls_fileinfo_t. Cannot be NULL - * \param buffer Pointer to character buffer in which to write the path. If NULL, the function returns the number of characters required. - * \param cchBuffer Number of character spaces in \c buffer. Ignored if \c buffer is NULL. - * \return The number of characters written to the buffer, or required for, the path. - */ -RECLS_FNDECL(size_t) Recls_GetPathProperty( recls_info_t hEntry - , recls_char_t *buffer - , size_t cchBuffer); - -/** Retrieves the directory of the given entry recls_fileinfo_t - * - * \param hEntry The entry recls_fileinfo_t. Cannot be NULL - * \param buffer Pointer to character buffer in which to write the directory. If NULL, the function returns the number of characters required. - * \param cchBuffer Number of character spaces in \c buffer. Ignored if \c buffer is NULL. - * \return The number of characters written to the buffer, or required for, the directory. - */ -RECLS_FNDECL(size_t) Recls_GetDirectoryProperty(recls_info_t hEntry - , recls_char_t *buffer - , size_t cchBuffer); - -/** Retrieves the directory and drive of the given entry recls_fileinfo_t - * - * \param hEntry The entry recls_fileinfo_t. Cannot be NULL - * \param buffer Pointer to character buffer in which to write the directory. If NULL, the function returns the number of characters required. - * \param cchBuffer Number of character spaces in \c buffer. Ignored if \c buffer is NULL. - * \return The number of characters written to the buffer, or required for, the directory. - * \note On systems that do not have a drive, this function behaves identically to Recls_GetDirectoryProperty() - */ -RECLS_FNDECL(size_t) Recls_GetDirectoryPathProperty( recls_info_t hEntry - , recls_char_t *buffer - , size_t cchBuffer); - -/** Retrieves the file (filename + extension) of the given entry recls_fileinfo_t - * - * \param hEntry The entry recls_fileinfo_t. Cannot be NULL - * \param buffer Pointer to character buffer in which to write the file. If NULL, the function returns the number of characters required. - * \param cchBuffer Number of character spaces in \c buffer. Ignored if \c buffer is NULL. - * \return The number of characters written to the buffer, or required for, the file. - */ -RECLS_FNDECL(size_t) Recls_GetFileProperty( recls_info_t hEntry - , recls_char_t *buffer - , size_t cchBuffer); - -/** Retrieves the short version of the file of the given entry recls_fileinfo_t - * - * \param hEntry The entry recls_fileinfo_t. Cannot be NULL - * \param buffer Pointer to character buffer in which to write the file. If NULL, the function returns the number of characters required. - * \param cchBuffer Number of character spaces in \c buffer. Ignored if \c buffer is NULL. - * \return The number of characters written to the buffer, or required for, the file. - * - * \note On systems where there is no concept of a short name, this function behaves exactly as Recls_GetFileProperty() - */ -RECLS_FNDECL(size_t) Recls_GetShortFileProperty(recls_info_t hEntry - , recls_char_t *buffer - , size_t cchBuffer); - -/** Retrieves the filename (not including extension, if any) of the given entry recls_fileinfo_t - * - * \param hEntry The entry recls_fileinfo_t. Cannot be NULL - * \param buffer Pointer to character buffer in which to write the filename. If NULL, the function returns the number of characters required. - * \param cchBuffer Number of character spaces in \c buffer. Ignored if \c buffer is NULL. - * \return The number of characters written to the buffer, or required for, the filename. - */ -RECLS_FNDECL(size_t) Recls_GetFileNameProperty( recls_info_t hEntry - , recls_char_t *buffer - , size_t cchBuffer); - -/** Retrieves the file extension of the given entry recls_fileinfo_t - * - * \param hEntry The entry recls_fileinfo_t. Cannot be NULL - * \param buffer Pointer to character buffer in which to write the extension. If NULL, the function returns the number of characters required. - * \param cchBuffer Number of character spaces in \c buffer. Ignored if \c buffer is NULL. - * \return The number of characters written to the buffer, or required for, the extension. - */ -RECLS_FNDECL(size_t) Recls_GetFileExtProperty( recls_info_t hEntry - , recls_char_t *buffer - , size_t cchBuffer); - -/** Retrieves a directory part of the given entry recls_fileinfo_t - * - * \param hEntry The entry recls_fileinfo_t. Cannot be NULL - * \param part The part requested. If -1, then the function returns the number of parts - * \param buffer Pointer to character buffer in which to write the extension. If NULL, the function returns the number of characters required. Ignored if part is -1. - * \param cchBuffer Number of character spaces in \c buffer. Ignored if \c buffer is NULL or part is -1. - * \return If \c part is -1, returns the number of parts. Otherwise, The number of characters written to the buffer, or required for, the extension. - * - * \note The behaviour is undefined if part is outside the range of parts. - */ -RECLS_FNDECL(size_t) Recls_GetDirectoryPartProperty(recls_info_t hEntry - , int part - , recls_char_t *buffer - , size_t cchBuffer); - - -/** Returns non-zero if the file entry is read-only. - * - * \param hEntry The file entry info structure to test. May not be NULL - * \retval true file entry is read-only - * \retval false file entry is not read-only - * - * \note There is no error return - */ -RECLS_FNDECL(recls_bool_t) Recls_IsFileReadOnly(recls_info_t hEntry); - -/** Returns non-zero if the file entry represents a directory. - * - * \param hEntry The file entry info structure to test. May not be NULL - * \retval true file entry is a directory - * \retval false file entry is not directory - * - * \note There is no error return - */ -RECLS_FNDECL(recls_bool_t) Recls_IsFileDirectory(recls_info_t hEntry); - -/** Returns non-zero if the file entry represents a link. - * - * \param hEntry The file entry info structure to test. May not be NULL - * \retval true file entry is a link - * \retval false file entry is not link - * - * \note There is no error return - */ -RECLS_FNDECL(recls_bool_t) Recls_IsFileLink( recls_info_t hEntry); - -/** Acquires the size of the file entry. - * - * \param hEntry The file entry info structure to test. May not be NULL - * \param size Pointer to the location in which to store the size - * - * \note There is no error return. File system entries that do not have a meaningful size will be given a notional size of 0. - */ -RECLS_FNDECL(void) Recls_GetSizeProperty( recls_info_t hEntry - , recls_filesize_t *size); - -/** Returns the time the file was created */ -RECLS_FNDECL(recls_time_t) Recls_GetCreationTime(recls_info_t hEntry); - -/** Returns the time the file was last modified */ -RECLS_FNDECL(recls_time_t) Recls_GetModificationTime(recls_info_t hEntry); - -/** Returns the time the file was last accessed */ -RECLS_FNDECL(recls_time_t) Recls_GetLastAccessTime(recls_info_t hEntry); - -/** Returns the time the file status was last changed */ -RECLS_FNDECL(recls_time_t) Recls_GetLastStatusChangeTime(recls_info_t hEntry); - -/** @} */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace - */ - -#if !defined(RECLS_NO_NAMESPACE) -} /* namespace recls */ -#endif /* !RECLS_NO_NAMESPACE */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Platform-specific includes - */ - -/*** \def RECLS_PLATFORM_API_WIN32 Defined if Win32 platform-specific extensions are in use */ -/*** \def RECLS_PLATFORM_API_UNIX Defined if UNIX platform-specific extensions are in use */ - -#ifdef RECLS_PLATFORM_API_WIN32 -# undef RECLS_PLATFORM_API_WIN32 -#endif /* RECLS_PLATFORM_API_WIN32 */ - -#ifdef RECLS_PLATFORM_API_UNIX -# undef RECLS_PLATFORM_API_UNIX -#endif /* RECLS_PLATFORM_API_UNIX */ - -#if !defined(RECLS_PURE_API) -# if defined(RECLS_PLATFORM_IS_WIN32) -# include "recls_win32.h" -# define RECLS_PLATFORM_API_WIN32 -# elif defined(RECLS_PLATFORM_IS_UNIX) -# include "recls_unix.h" -# define RECLS_PLATFORM_API_UNIX -# else -# error Platform not recognised -# endif /* platform */ -#endif /* !RECLS_PURE_API */ - -/* ////////////////////////////////////////////////////////////////////////// */ - -#endif /* !RECLS_INCL_H_RECLS */ - -/* ////////////////////////////////////////////////////////////////////////// */ diff -uNr gdc-0.17/d/phobos/etc/c/recls/recls_internal.cpp gdc-0.18/d/phobos/etc/c/recls/recls_internal.cpp --- gdc-0.17/d/phobos/etc/c/recls/recls_internal.cpp 2004-10-26 02:41:27.000000000 +0200 +++ gdc-0.18/d/phobos/etc/c/recls/recls_internal.cpp 1970-01-01 01:00:00.000000000 +0100 @@ -1,142 +0,0 @@ -/* ///////////////////////////////////////////////////////////////////////////// - * File: recls_internal.cpp - * - * Purpose: Implementation file for the recls API internal helpers. - * - * Created: 16th August 2003 - * Updated: 27th November 2003 - * - * License: (Licensed under the Synesis Software Standard Source License) - * - * Copyright (C) 2002-2003, Synesis Software Pty Ltd. - * - * All rights reserved. - * - * www: http://www.synesis.com.au/software - * http://www.recls.org/ - * - * email: submissions@recls.org for submissions - * admin@recls.org for other enquiries - * - * Redistribution and use in source and binary forms, with or - * without modification, are permitted provided that the following - * conditions are met: - * - * (i) Redistributions of source code must retain the above - * copyright notice and contact information, this list of - * conditions and the following disclaimer. - * - * (ii) Any derived versions of this software (howsoever modified) - * remain the sole property of Synesis Software. - * - * (iii) Any derived versions of this software (howsoever modified) - * remain subject to all these conditions. - * - * (iv) Neither the name of Synesis Software nor the names of any - * subdivisions, employees or agents of Synesis Software, nor the - * names of any other contributors to this software may be used to - * endorse or promote products derived from this software without - * specific prior written permission. - * - * This source code is provided by Synesis Software "as is" and any - * warranties, whether expressed or implied, including, but not - * limited to, the implied warranties of merchantability and - * fitness for a particular purpose are disclaimed. In no event - * shall the Synesis Software be liable for any direct, indirect, - * incidental, special, exemplary, or consequential damages - * (including, but not limited to, procurement of substitute goods - * or services; loss of use, data, or profits; or business - * interruption) however caused and on any theory of liability, - * whether in contract, strict liability, or tort (including - * negligence or otherwise) arising in any way out of the use of - * this software, even if advised of the possibility of such - * damage. - * - * ////////////////////////////////////////////////////////////////////////// */ - - -/* ///////////////////////////////////////////////////////////////////////////// - * Includes - */ - -#include "recls.h" -#include "recls_internal.h" -#include "recls_assert.h" - -#include - -#include - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace - */ - -#if !defined(RECLS_NO_NAMESPACE) -namespace recls -{ -#endif /* !RECLS_NO_NAMESPACE */ - -/* ////////////////////////////////////////////////////////////////////////// */ - -static size_t recls_strncpy(recls_char_t *dest, size_t cchDest, recls_char_t const *src, size_t cchSrc) -{ - size_t cchWritten; - - if(cchDest < cchSrc) - { - /* Just to straight strncpy. */ - strncpy(dest, src, cchDest); - - cchWritten = cchDest; - } - else - { - strncpy(dest, src, cchSrc); - - if(cchSrc < cchDest) - { - /* Fill the rest up with blanks. */ - - memset(&dest[cchSrc], 0, sizeof(recls_char_t) * (cchDest - cchSrc)); - } - - cchWritten = cchSrc; - } - - return cchWritten; -} - -/* ////////////////////////////////////////////////////////////////////////// */ - -#if defined(RECLS_COMPILER_IS_DMC) || \ - defined(RECLS_COMPILER_IS_WATCOM) -RECLS_FNDECL(size_t) Recls_GetStringProperty_( struct recls_strptrs_t const * ptrs - , recls_char_t * buffer - , size_t cchBuffer) -#else -RECLS_FNDECL(size_t) Recls_GetStringProperty_( struct recls_strptrs_t const *const ptrs - , recls_char_t *const buffer - , size_t const cchBuffer) -#endif /* RECLS_COMPILER_IS_DMC || RECLS_COMPILER_IS_WATCOM */ -{ - recls_assert(NULL != ptrs); - - size_t cch = ptrs->end - ptrs->begin; - - if(NULL != buffer) - { - cch = recls_strncpy(buffer, cchBuffer, ptrs->begin, cch); - } - - return cch; -} - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace - */ - -#if !defined(RECLS_NO_NAMESPACE) -} /* namespace recls */ -#endif /* !RECLS_NO_NAMESPACE */ - -/* ////////////////////////////////////////////////////////////////////////// */ diff -uNr gdc-0.17/d/phobos/etc/c/recls/recls_internal.h gdc-0.18/d/phobos/etc/c/recls/recls_internal.h --- gdc-0.17/d/phobos/etc/c/recls/recls_internal.h 2004-10-26 02:41:27.000000000 +0200 +++ gdc-0.18/d/phobos/etc/c/recls/recls_internal.h 1970-01-01 01:00:00.000000000 +0100 @@ -1,245 +0,0 @@ -/* ///////////////////////////////////////////////////////////////////////////// - * File: recls_internal.h - * - * Purpose: Main header file for the recls API. - * - * Created: 15th August 2003 - * Updated: 24th November 2003 - * - * License: (Licensed under the Synesis Software Standard Source License) - * - * Copyright (C) 2002-2003, Synesis Software Pty Ltd. - * - * All rights reserved. - * - * www: http://www.synesis.com.au/software - * http://www.recls.org/ - * - * email: submissions@recls.org for submissions - * admin@recls.org for other enquiries - * - * Redistribution and use in source and binary forms, with or - * without modification, are permitted provided that the following - * conditions are met: - * - * (i) Redistributions of source code must retain the above - * copyright notice and contact information, this list of - * conditions and the following disclaimer. - * - * (ii) Any derived versions of this software (howsoever modified) - * remain the sole property of Synesis Software. - * - * (iii) Any derived versions of this software (howsoever modified) - * remain subject to all these conditions. - * - * (iv) Neither the name of Synesis Software nor the names of any - * subdivisions, employees or agents of Synesis Software, nor the - * names of any other contributors to this software may be used to - * endorse or promote products derived from this software without - * specific prior written permission. - * - * This source code is provided by Synesis Software "as is" and any - * warranties, whether expressed or implied, including, but not - * limited to, the implied warranties of merchantability and - * fitness for a particular purpose are disclaimed. In no event - * shall the Synesis Software be liable for any direct, indirect, - * incidental, special, exemplary, or consequential damages - * (including, but not limited to, procurement of substitute goods - * or services; loss of use, data, or profits; or business - * interruption) however caused and on any theory of liability, - * whether in contract, strict liability, or tort (including - * negligence or otherwise) arising in any way out of the use of - * this software, even if advised of the possibility of such - * damage. - * - * ////////////////////////////////////////////////////////////////////////// */ - - -#ifndef RECLS_INCL_H_RECLS_INTERNAL -#define RECLS_INCL_H_RECLS_INTERNAL - -/* File version */ -#ifndef RECLS_DOCUMENTATION_SKIP_SECTION -# define RECLS_VER_H_RECLS_INTERNAL_MAJOR 1 -# define RECLS_VER_H_RECLS_INTERNAL_MINOR 2 -# define RECLS_VER_H_RECLS_INTERNAL_REVISION 3 -# define RECLS_VER_H_RECLS_INTERNAL_EDIT 12 -#endif /* !RECLS_DOCUMENTATION_SKIP_SECTION */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Includes - */ - -#ifndef __cplusplus -# error This file can only be included in C++ compilation units -#endif /* __cplusplus */ - -#include "recls.h" - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace - */ - -#if !defined(RECLS_NO_NAMESPACE) -namespace recls -{ -#endif /* !RECLS_NO_NAMESPACE */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Macros - */ - -#ifndef RECLS_NUM_ELEMENTS -# if defined(stlsoft_num_elements) -# define RECLS_NUM_ELEMENTS(x) stlsoft_num_elements(x) -# else /* ? stlsoft_num_elements */ -# define RECLS_NUM_ELEMENTS(x) (sizeof(x) / sizeof((x)[0])) -# endif /* stlsoft_num_elements */ -#endif /* !RECLS_NUM_ELEMENTS */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Classes - */ - -// class ReclsDNode -/// Interface for directory nodes -/// -/// \note It has an ugly name-prefix if need to compile with compiler that does not support namespaces -struct ReclsDNode -{ - /// Destructory - /// - /// ReclsDNode instances are not reference-counted, but are - /// deleted by their owner. They are non-shareable. - virtual ~ReclsDNode() = 0; - - virtual recls_rc_t GetNext() = 0; - - virtual recls_rc_t GetDetails(recls_info_t *pinfo) = 0; - - virtual recls_rc_t GetNextDetails(recls_info_t *pinfo) = 0; -}; - -inline ReclsDNode::~ReclsDNode() -{} - -// class ReclsDNode -/// Search info structure -/// -/// \note It has an ugly name-prefix if need to compile with compiler that does not support namespaces -class ReclsSearchInfo -{ -public: - typedef recls_char_t char_type; - typedef ReclsSearchInfo class_type; - -// Allocation -private: - void *operator new(size_t cb, int cDirParts, size_t cbRootDir); -#if !defined(RECLS_COMPILER_IS_BORLAND) && \ - !defined(RECLS_COMPILER_IS_DMC) && \ - !defined(RECLS_COMPILER_IS_INTEL) && \ - !defined(RECLS_COMPILER_IS_WATCOM) - void operator delete(void *pv, int cDirParts, size_t cbRootDir); -#endif /* !RECLS_COMPILER_IS_BORLAND && !RECLS_COMPILER_IS_DMC */ -public: - void operator delete(void *pv); - -// Construction -protected: - ReclsSearchInfo(int cDirParts - , char_type const *rootDir - , char_type const *pattern - , recls_uint32_t flags); -public: - static recls_rc_t FindAndCreate(char_type const *rootDir - , char_type const *pattern - , recls_uint32_t flags - , ReclsSearchInfo **ppsi); - -// Operations -public: - recls_rc_t GetNext(); - - recls_rc_t GetDetails(recls_info_t *pinfo); - - recls_rc_t GetNextDetails(recls_info_t *pinfo); - -// Accessors -public: - recls_rc_t GetLastError() const; - -// Handle interconversion -public: - static hrecls_t ToHandle(ReclsSearchInfo *si); - static ReclsSearchInfo *FromHandle(hrecls_t h); - -// Implementation -private: - char_type const *_calc_rootDir(int cDirParts, char_type const *rootDir); - -// Members -private: - recls_uint32_t m_flags; - ReclsDNode *m_dnode; - recls_rc_t m_lastError; - char_type const * const m_rootDir; - - /** The opaque data of the search */ - recls_byte_t data[1]; - /* - * The data comprises: - * - * - root dir - * - */ - -// Not to be implemented -private: - ReclsSearchInfo(ReclsSearchInfo const &); - ReclsSearchInfo &operator =(ReclsSearchInfo const &); -}; - -inline /* static */ hrecls_t ReclsSearchInfo::ToHandle(ReclsSearchInfo *si) -{ - return hrecls_t(si); -} - -inline /* static */ ReclsSearchInfo *ReclsSearchInfo::FromHandle(hrecls_t h) -{ - return const_cast(reinterpret_cast(h)); -} - -/* ///////////////////////////////////////////////////////////////////////////// - * File info functions - */ - -RECLS_FNDECL(recls_info_t) FileInfo_Allocate( size_t cb); -RECLS_FNDECL(void) FileInfo_Release( recls_info_t fileInfo); -RECLS_FNDECL(recls_rc_t) FileInfo_Copy( recls_info_t fileInfo - , recls_info_t *pinfo); - -RECLS_FNDECL(void) FileInfo_BlockCount(recls_sint32_t *pcCreated - , recls_sint32_t *pcShared); - -/* ///////////////////////////////////////////////////////////////////////////// - * Helper functions - */ - -RECLS_FNDECL(size_t) Recls_GetStringProperty_( struct recls_strptrs_t const *ptrs - , recls_char_t *buffer - , size_t cchBuffer); - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace - */ - -#if !defined(RECLS_NO_NAMESPACE) -} /* namespace recls */ -#endif /* !RECLS_NO_NAMESPACE */ - -/* ////////////////////////////////////////////////////////////////////////// */ - -#endif /* !RECLS_INCL_H_RECLS_INTERNAL */ - -/* ////////////////////////////////////////////////////////////////////////// */ diff -uNr gdc-0.17/d/phobos/etc/c/recls/recls_language.h gdc-0.18/d/phobos/etc/c/recls/recls_language.h --- gdc-0.17/d/phobos/etc/c/recls/recls_language.h 2004-10-26 02:41:27.000000000 +0200 +++ gdc-0.18/d/phobos/etc/c/recls/recls_language.h 1970-01-01 01:00:00.000000000 +0100 @@ -1,117 +0,0 @@ -/* ///////////////////////////////////////////////////////////////////////////// - * File: recls_language.h - * - * Purpose: Platform discrimination for the recls API. - * - * Created: 15th August 2003 - * Updated: 23rd September 2003 - * - * License: (Licensed under the Synesis Software Standard Source License) - * - * Copyright (C) 2002-2003, Synesis Software Pty Ltd. - * - * All rights reserved. - * - * www: http://www.synesis.com.au/software - * http://www.recls.org/ - * - * email: submissions@recls.org for submissions - * admin@recls.org for other enquiries - * - * Redistribution and use in source and binary forms, with or - * without modification, are permitted provided that the following - * conditions are met: - * - * (i) Redistributions of source code must retain the above - * copyright notice and contact information, this list of - * conditions and the following disclaimer. - * - * (ii) Any derived versions of this software (howsoever modified) - * remain the sole property of Synesis Software. - * - * (iii) Any derived versions of this software (howsoever modified) - * remain subject to all these conditions. - * - * (iv) Neither the name of Synesis Software nor the names of any - * subdivisions, employees or agents of Synesis Software, nor the - * names of any other contributors to this software may be used to - * endorse or promote products derived from this software without - * specific prior written permission. - * - * This source code is provided by Synesis Software "as is" and any - * warranties, whether expressed or implied, including, but not - * limited to, the implied warranties of merchantability and - * fitness for a particular purpose are disclaimed. In no event - * shall the Synesis Software be liable for any direct, indirect, - * incidental, special, exemplary, or consequential damages - * (including, but not limited to, procurement of substitute goods - * or services; loss of use, data, or profits; or business - * interruption) however caused and on any theory of liability, - * whether in contract, strict liability, or tort (including - * negligence or otherwise) arising in any way out of the use of - * this software, even if advised of the possibility of such - * damage. - * - * ////////////////////////////////////////////////////////////////////////// */ - - -#ifndef RECLS_INCL_H_RECLS_LANGUAGE -#define RECLS_INCL_H_RECLS_LANGUAGE - -/* File version */ -#ifndef RECLS_DOCUMENTATION_SKIP_SECTION -# define RECLS_VER_H_RECLS_LANGUAGE_MAJOR 1 -# define RECLS_VER_H_RECLS_LANGUAGE_MINOR 0 -# define RECLS_VER_H_RECLS_LANGUAGE_REVISION 8 -# define RECLS_VER_H_RECLS_LANGUAGE_EDIT 8 -#endif /* !RECLS_DOCUMENTATION_SKIP_SECTION */ - -/** \file recls_language.h Language detection for the \ref group_recls API */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Linkage - */ - -/** \def RECLS_LINKAGE_C The linkage for recls functions. Is \c extern \c "C" in C++ and \c extern in C. */ - -#ifdef __cplusplus -# define RECLS_LINKAGE_C extern "C" -# define RECLS_LINKAGE_CPP extern "C++" -#else -# define RECLS_LINKAGE_C extern -#endif /* __cplusplus */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace - */ - -#if !defined(__cplusplus) -# define RECLS_NO_NAMESPACE -#endif /* !__cplusplus */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace - */ - -#if !defined(RECLS_NO_NAMESPACE) -namespace recls -{ -#endif /* !RECLS_NO_NAMESPACE */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Typedefs - */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace - */ - -#if !defined(RECLS_NO_NAMESPACE) -} /* namespace recls */ -#endif /* !RECLS_NO_NAMESPACE */ - -/* ////////////////////////////////////////////////////////////////////////// */ - -#endif /* !RECLS_INCL_H_RECLS_LANGUAGE */ - -/* ////////////////////////////////////////////////////////////////////////// */ diff -uNr gdc-0.17/d/phobos/etc/c/recls/recls_platform.h gdc-0.18/d/phobos/etc/c/recls/recls_platform.h --- gdc-0.17/d/phobos/etc/c/recls/recls_platform.h 2004-10-26 02:41:27.000000000 +0200 +++ gdc-0.18/d/phobos/etc/c/recls/recls_platform.h 1970-01-01 01:00:00.000000000 +0100 @@ -1,148 +0,0 @@ -/* ///////////////////////////////////////////////////////////////////////////// - * File: recls_platform.h - * - * Purpose: Platform discrimination for the recls API. - * - * Created: 15th August 2003 - * Updated: 2nd November 2003 - * - * License: (Licensed under the Synesis Software Standard Source License) - * - * Copyright (C) 2002-2003, Synesis Software Pty Ltd. - * - * All rights reserved. - * - * www: http://www.synesis.com.au/software - * http://www.recls.org/ - * - * email: submissions@recls.org for submissions - * admin@recls.org for other enquiries - * - * Redistribution and use in source and binary forms, with or - * without modification, are permitted provided that the following - * conditions are met: - * - * (i) Redistributions of source code must retain the above - * copyright notice and contact information, this list of - * conditions and the following disclaimer. - * - * (ii) Any derived versions of this software (howsoever modified) - * remain the sole property of Synesis Software. - * - * (iii) Any derived versions of this software (howsoever modified) - * remain subject to all these conditions. - * - * (iv) Neither the name of Synesis Software nor the names of any - * subdivisions, employees or agents of Synesis Software, nor the - * names of any other contributors to this software may be used to - * endorse or promote products derived from this software without - * specific prior written permission. - * - * This source code is provided by Synesis Software "as is" and any - * warranties, whether expressed or implied, including, but not - * limited to, the implied warranties of merchantability and - * fitness for a particular purpose are disclaimed. In no event - * shall the Synesis Software be liable for any direct, indirect, - * incidental, special, exemplary, or consequential damages - * (including, but not limited to, procurement of substitute goods - * or services; loss of use, data, or profits; or business - * interruption) however caused and on any theory of liability, - * whether in contract, strict liability, or tort (including - * negligence or otherwise) arising in any way out of the use of - * this software, even if advised of the possibility of such - * damage. - * - * ////////////////////////////////////////////////////////////////////////// */ - - -#ifndef RECLS_INCL_H_RECLS_PLATFORM -#define RECLS_INCL_H_RECLS_PLATFORM - -/* File version */ -#ifndef RECLS_DOCUMENTATION_SKIP_SECTION -# define RECLS_VER_H_RECLS_PLATFORM_MAJOR 1 -# define RECLS_VER_H_RECLS_PLATFORM_MINOR 2 -# define RECLS_VER_H_RECLS_PLATFORM_REVISION 2 -# define RECLS_VER_H_RECLS_PLATFORM_EDIT 10 -#endif /* !RECLS_DOCUMENTATION_SKIP_SECTION */ - -/** \file recls_platform.h Platform detection for the \ref group_recls API */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Platform recognition - * - * Define the symbol RECLS_OVERRIDE_PLATFORM to provide your own platform - * discrimination - */ - -#ifndef RECLS_OVERRIDE_PLATFORM -# if defined(WIN32) || \ - defined(_WIN32) -# define RECLS_PLATFORM_IS_WIN32 -# elif defined(unix) || \ - defined(UNIX) || \ - defined(__unix) || \ - defined(__unix__) || \ - ( defined(__xlC__) && \ - defined(_POWER) && \ - defined(_AIX)) -# define RECLS_PLATFORM_IS_UNIX -# else -# error Platform not (yet) recognised -# endif /* platform */ -#endif /* !RECLS_OVERRIDE_PLATFORM */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Includes - */ - -#if defined(RECLS_PLATFORM_IS_WIN32) -# include -#elif defined(RECLS_PLATFORM_IS_UNIX) -# include -#else -# error Platform not (yet) recognised -#endif /* platform */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace - */ - -#if !defined(RECLS_NO_NAMESPACE) -namespace recls -{ -#endif /* !RECLS_NO_NAMESPACE */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Constants and definitions - */ - -/** \def RECLS_PATH_MAX The maximum number of characters in a path on the host operating-system. */ - -#if defined(RECLS_PLATFORM_IS_WIN32) - -# define RECLS_PATH_MAX (_MAX_PATH) - -#elif defined(RECLS_PLATFORM_IS_UNIX) - -# define RECLS_PATH_MAX (PATH_MAX) - -#else - -# error Platform not (yet) recognised - -#endif /* platform */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace - */ - -#if !defined(RECLS_NO_NAMESPACE) -} /* namespace recls */ -#endif /* !RECLS_NO_NAMESPACE */ - -/* ////////////////////////////////////////////////////////////////////////// */ - -#endif /* !RECLS_INCL_H_RECLS_PLATFORM */ - -/* ////////////////////////////////////////////////////////////////////////// */ diff -uNr gdc-0.17/d/phobos/etc/c/recls/recls_platform_types.h gdc-0.18/d/phobos/etc/c/recls/recls_platform_types.h --- gdc-0.17/d/phobos/etc/c/recls/recls_platform_types.h 2004-10-26 02:41:27.000000000 +0200 +++ gdc-0.18/d/phobos/etc/c/recls/recls_platform_types.h 1970-01-01 01:00:00.000000000 +0100 @@ -1,245 +0,0 @@ -/* ///////////////////////////////////////////////////////////////////////////// - * File: recls_platform_types.h - * - * Purpose: Platform discrimination for the recls API. - * - * Created: 18th August 2003 - * Updated: 21st November 2003 - * - * License: (Licensed under the Synesis Software Standard Source License) - * - * Copyright (C) 2002-2003, Synesis Software Pty Ltd. - * - * All rights reserved. - * - * www: http://www.synesis.com.au/software - * http://www.recls.org/ - * - * email: submissions@recls.org for submissions - * admin@recls.org for other enquiries - * - * Redistribution and use in source and binary forms, with or - * without modification, are permitted provided that the following - * conditions are met: - * - * (i) Redistributions of source code must retain the above - * copyright notice and contact information, this list of - * conditions and the following disclaimer. - * - * (ii) Any derived versions of this software (howsoever modified) - * remain the sole property of Synesis Software. - * - * (iii) Any derived versions of this software (howsoever modified) - * remain subject to all these conditions. - * - * (iv) Neither the name of Synesis Software nor the names of any - * subdivisions, employees or agents of Synesis Software, nor the - * names of any other contributors to this software may be used to - * endorse or promote products derived from this software without - * specific prior written permission. - * - * This source code is provided by Synesis Software "as is" and any - * warranties, whether expressed or implied, including, but not - * limited to, the implied warranties of merchantability and - * fitness for a particular purpose are disclaimed. In no event - * shall the Synesis Software be liable for any direct, indirect, - * incidental, special, exemplary, or consequential damages - * (including, but not limited to, procurement of substitute goods - * or services; loss of use, data, or profits; or business - * interruption) however caused and on any theory of liability, - * whether in contract, strict liability, or tort (including - * negligence or otherwise) arising in any way out of the use of - * this software, even if advised of the possibility of such - * damage. - * - * ////////////////////////////////////////////////////////////////////////// */ - - -#ifndef RECLS_INCL_H_RECLS_PLATFORM_TYPES -#define RECLS_INCL_H_RECLS_PLATFORM_TYPES - -/* File version */ -#ifndef RECLS_DOCUMENTATION_SKIP_SECTION -# define RECLS_VER_H_RECLS_PLATFORM_TYPES_MAJOR 1 -# define RECLS_VER_H_RECLS_PLATFORM_TYPES_MINOR 3 -# define RECLS_VER_H_RECLS_PLATFORM_TYPES_REVISION 1 -# define RECLS_VER_H_RECLS_PLATFORM_TYPES_EDIT 8 -#endif /* !RECLS_DOCUMENTATION_SKIP_SECTION */ - -/** \file recls_platform_types.h Platform-dependent types for the \ref group_recls API */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Includes - */ - -#ifndef RECLS_INCL_H_RECLS_PLATFORM -# error recls_platform_types.h must not be included directly. You should include recls.h -#endif /* !RECLS_INCL_H_RECLS_PLATFORM */ - -#if defined(RECLS_PLATFORM_IS_WIN32) -//# include -#elif defined(RECLS_PLATFORM_IS_UNIX) -# include -# include -#else -# error Platform not (yet) recognised -#endif /* platform */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace - */ - -#if !defined(RECLS_NO_NAMESPACE) -namespace recls -{ -#endif /* !RECLS_NO_NAMESPACE */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Platform-dependent types - */ - -/** \def recls_time_t The time type for the recls API */ -/** \def recls_filesize_t The file-size type for the recls API */ - -#if defined(RECLS_PLATFORM_IS_WIN32) - - typedef FILETIME recls_time_t; - typedef ULARGE_INTEGER recls_filesize_t; - -#elif defined(RECLS_PLATFORM_IS_UNIX) - - typedef time_t recls_time_t; - typedef off_t recls_filesize_t; - -#else - -# error Platform not (yet) recognised - - typedef platform-dependent-type recls_time_t; - typedef platform-dependent-type recls_filesize_t; - -#endif /* platform */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Typedefs - */ - -#ifdef RECLS_CHAR_TYPE_IS_CHAR -# undef RECLS_CHAR_TYPE_IS_CHAR -#endif /* RECLS_CHAR_TYPE_IS_CHAR */ - -#ifdef RECLS_CHAR_TYPE_IS_WCHAR -# undef RECLS_CHAR_TYPE_IS_WCHAR -#endif /* RECLS_CHAR_TYPE_IS_WCHAR */ - -/** The recls library ambient character type */ -#if 1 -typedef recls_char_a_t recls_char_t; -# define RECLS_CHAR_TYPE_IS_CHAR -#else /* ? 0 */ -typedef recls_char_w_t recls_char_t; -# define RECLS_CHAR_TYPE_IS_WCHAR -#endif /* 0 */ - - -/** An asymmetric range representing a sequence of characters (ie a string) */ -struct recls_strptrs_t -{ - /** Points to the start of the sequence. */ - recls_char_t const *begin; - /** Points to one-past-the-end of the sequence. */ - recls_char_t const *end; -}; - -/** An asymmetric range representing a sequence of recls_strptrs_t (ie a set of strings) */ -struct recls_strptrsptrs_t -{ - /** Points to the start of the sequence. */ - struct recls_strptrs_t const *begin; - /** Points to one-past-the-end of the sequence. */ - struct recls_strptrs_t const *end; -}; - -/** A file entry info structure - * - * \note Several parts of this structure are platform-dependent. - */ -struct recls_fileinfo_t -{ -/** \name attributes */ -/** @{ */ - /** The file attributes */ - recls_uint32_t attributes; -/** @} */ -/** \name Path components */ -/** @{ */ - /** The full path of the file */ - struct recls_strptrs_t path; -#if defined(RECLS_PLATFORM_IS_WIN32) - /** The short (8.3) path of the file - * - * \note This member is only defined for the Win32 platform. - */ - struct recls_strptrs_t shortFile; - /** The letter of the drive */ - recls_char_t drive; -#endif /* RECLS_PLATFORM_IS_WIN32 */ - /** The directory component */ - struct recls_strptrs_t directory; - /** The file name component (excluding extension) */ - struct recls_strptrs_t fileName; - /** The file extension component (excluding '.') */ - struct recls_strptrs_t fileExt; - /** The directory parts */ - struct recls_strptrsptrs_t directoryParts; -/** @} */ -/** \name File times */ -/** @{ */ -#if defined(RECLS_PLATFORM_IS_WIN32) - /** The time the file was created - * - * \note This member is only defined for the Win32 platform. - */ - recls_time_t creationTime; -#endif /* RECLS_PLATFORM_IS_WIN32 */ - /** The time the file was last modified */ - recls_time_t modificationTime; - /** The time the file was last accessed */ - recls_time_t lastAccessTime; -#if defined(RECLS_PLATFORM_IS_UNIX) - /** The time the file status was last changed - * - * \note This member is only defined for the UNIX platform. - */ - recls_time_t lastStatusChangeTime; -#endif /* RECLS_PLATFORM_IS_UNIX */ -/** @} */ -/** \name Size */ -/** @{ */ - /** The size of the file */ - recls_filesize_t size; -/** @} */ -/* data */ - /** The opaque data of the file; it is not accessible to any client code, and must not be manipulated in any way */ - recls_byte_t data[1]; - /* - * - * - full path - * - directory parts - * - */ -}; - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace - */ - -#if !defined(RECLS_NO_NAMESPACE) -} /* namespace recls */ -#endif /* !RECLS_NO_NAMESPACE */ - -/* ////////////////////////////////////////////////////////////////////////// */ - -#endif /* !RECLS_INCL_H_RECLS_PLATFORM_TYPES */ - -/* ////////////////////////////////////////////////////////////////////////// */ diff -uNr gdc-0.17/d/phobos/etc/c/recls/recls_retcodes.h gdc-0.18/d/phobos/etc/c/recls/recls_retcodes.h --- gdc-0.17/d/phobos/etc/c/recls/recls_retcodes.h 2004-10-26 02:41:27.000000000 +0200 +++ gdc-0.18/d/phobos/etc/c/recls/recls_retcodes.h 1970-01-01 01:00:00.000000000 +0100 @@ -1,111 +0,0 @@ -/* ///////////////////////////////////////////////////////////////////////////// - * File: recls_retcodes.h - * - * Purpose: Return codes for the recls API. - * - * Created: 15th August 2003 - * Updated: 27th September 2003 - * - * License: (Licensed under the Synesis Software Standard Source License) - * - * Copyright (C) 2002-2003, Synesis Software Pty Ltd. - * - * All rights reserved. - * - * www: http://www.synesis.com.au/software - * http://www.recls.org/ - * - * email: submissions@recls.org for submissions - * admin@recls.org for other enquiries - * - * Redistribution and use in source and binary forms, with or - * without modification, are permitted provided that the following - * conditions are met: - * - * (i) Redistributions of source code must retain the above - * copyright notice and contact information, this list of - * conditions and the following disclaimer. - * - * (ii) Any derived versions of this software (howsoever modified) - * remain the sole property of Synesis Software. - * - * (iii) Any derived versions of this software (howsoever modified) - * remain subject to all these conditions. - * - * (iv) Neither the name of Synesis Software nor the names of any - * subdivisions, employees or agents of Synesis Software, nor the - * names of any other contributors to this software may be used to - * endorse or promote products derived from this software without - * specific prior written permission. - * - * This source code is provided by Synesis Software "as is" and any - * warranties, whether expressed or implied, including, but not - * limited to, the implied warranties of merchantability and - * fitness for a particular purpose are disclaimed. In no event - * shall the Synesis Software be liable for any direct, indirect, - * incidental, special, exemplary, or consequential damages - * (including, but not limited to, procurement of substitute goods - * or services; loss of use, data, or profits; or business - * interruption) however caused and on any theory of liability, - * whether in contract, strict liability, or tort (including - * negligence or otherwise) arising in any way out of the use of - * this software, even if advised of the possibility of such - * damage. - * - * ////////////////////////////////////////////////////////////////////////// */ - - -#if !defined(RECLS_INCL_H_RECLS) && \ - !defined(RECLS_DOCUMENTATION_SKIP_SECTION) -# error recls_retcodes.h cannot be included directly. Include recls.h -#else - -/* File version */ -#ifndef RECLS_DOCUMENTATION_SKIP_SECTION -# define RECLS_VER_H_RECLS_RETCODES_MAJOR 1 -# define RECLS_VER_H_RECLS_RETCODES_MINOR 1 -# define RECLS_VER_H_RECLS_RETCODES_REVISION 2 -# define RECLS_VER_H_RECLS_RETCODES_EDIT 10 -#endif /* !RECLS_DOCUMENTATION_SKIP_SECTION */ - -/** \file recls_retcodes.h Return codes for the \ref group_recls API */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace - */ - -#if !defined(RECLS_NO_NAMESPACE) -namespace recls -{ -#endif /* !RECLS_NO_NAMESPACE */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Constants and definitions - */ - -/** No search is currently active */ -#define RECLS_RC_SEARCH_NO_CURRENT ((RECLS_QUAL(recls_rc_t))(-1 - 1001)) -/** The directory was invalid, or does not exist */ -#define RECLS_RC_INVALID_DIRECTORY ((RECLS_QUAL(recls_rc_t))(-1 - 1002)) -/** No more data is available */ -#define RECLS_RC_NO_MORE_DATA ((RECLS_QUAL(recls_rc_t))(-1 - 1003)) -/** Memory exhaustion */ -#define RECLS_RC_OUT_OF_MEMORY ((RECLS_QUAL(recls_rc_t))(-1 - 1004)) -/** Function not implemented */ -#define RECLS_RC_NOT_IMPLEMENTED ((RECLS_QUAL(recls_rc_t))(-1 - 1005)) -/** Invalid search type */ -#define RECLS_RC_INVALID_SEARCH_TYPE ((RECLS_QUAL(recls_rc_t))(-1 - 1006)) - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace - */ - -#if !defined(RECLS_NO_NAMESPACE) -} /* namespace recls */ -#endif /* !RECLS_NO_NAMESPACE */ - -/* ////////////////////////////////////////////////////////////////////////// */ - -#endif /* !RECLS_INCL_H_RECLS */ - -/* ////////////////////////////////////////////////////////////////////////// */ diff -uNr gdc-0.17/d/phobos/etc/c/recls/recls_unix.h gdc-0.18/d/phobos/etc/c/recls/recls_unix.h --- gdc-0.17/d/phobos/etc/c/recls/recls_unix.h 2004-10-26 02:41:27.000000000 +0200 +++ gdc-0.18/d/phobos/etc/c/recls/recls_unix.h 1970-01-01 01:00:00.000000000 +0100 @@ -1,115 +0,0 @@ -/* ///////////////////////////////////////////////////////////////////////////// - * File: recls_unix.h - * - * Purpose: UNIX-specific header file for the recls API. - * - * Created: 18th August 2003 - * Updated: 23rd September 2003 - * - * License: (Licensed under the Synesis Software Standard Source License) - * - * Copyright (C) 2002-2003, Synesis Software Pty Ltd. - * - * All rights reserved. - * - * www: http://www.synesis.com.au/software - * http://www.recls.org/ - * - * email: submissions@recls.org for submissions - * admin@recls.org for other enquiries - * - * Redistribution and use in source and binary forms, with or - * without modification, are permitted provided that the following - * conditions are met: - * - * (i) Redistributions of source code must retain the above - * copyright notice and contact information, this list of - * conditions and the following disclaimer. - * - * (ii) Any derived versions of this software (howsoever modified) - * remain the sole property of Synesis Software. - * - * (iii) Any derived versions of this software (howsoever modified) - * remain subject to all these conditions. - * - * (iv) Neither the name of Synesis Software nor the names of any - * subdivisions, employees or agents of Synesis Software, nor the - * names of any other contributors to this software may be used to - * endorse or promote products derived from this software without - * specific prior written permission. - * - * This source code is provided by Synesis Software "as is" and any - * warranties, whether expressed or implied, including, but not - * limited to, the implied warranties of merchantability and - * fitness for a particular purpose are disclaimed. In no event - * shall the Synesis Software be liable for any direct, indirect, - * incidental, special, exemplary, or consequential damages - * (including, but not limited to, procurement of substitute goods - * or services; loss of use, data, or profits; or business - * interruption) however caused and on any theory of liability, - * whether in contract, strict liability, or tort (including - * negligence or otherwise) arising in any way out of the use of - * this software, even if advised of the possibility of such - * damage. - * - * ////////////////////////////////////////////////////////////////////////// */ - - -#ifndef RECLS_INCL_H_RECLS_UNIX -#define RECLS_INCL_H_RECLS_UNIX - -/* File version */ -#ifndef RECLS_DOCUMENTATION_SKIP_SECTION -# define RECLS_VER_H_RECLS_UNIX_MAJOR 1 -# define RECLS_VER_H_RECLS_UNIX_MINOR 0 -# define RECLS_VER_H_RECLS_UNIX_REVISION 3 -# define RECLS_VER_H_RECLS_UNIX_EDIT 3 -#endif /* !RECLS_DOCUMENTATION_SKIP_SECTION */ - -/** \file recls_unix.h UNIX-specific parts of the \ref group_recls API */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Strictness - */ - -#ifndef RECLS_NO_STRICT -# define RECLS_STRICT -#endif /* !RECLS_NO_STRICT */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Includes - */ - -#include "recls.h" - -#ifndef RECLS_PLATFORM_IS_UNIX -# error recls_unix.h is to be included in UNIX compilations only -#endif /* RECLS_PLATFORM_IS_UNIX */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace - */ - -#if !defined(RECLS_NO_NAMESPACE) -namespace recls -{ -#endif /* !RECLS_NO_NAMESPACE */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Functions - */ - - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace - */ - -#if !defined(RECLS_NO_NAMESPACE) -} /* namespace recls */ -#endif /* !RECLS_NO_NAMESPACE */ - -/* ////////////////////////////////////////////////////////////////////////// */ - -#endif /* !RECLS_INCL_H_RECLS_UNIX */ - -/* ////////////////////////////////////////////////////////////////////////// */ diff -uNr gdc-0.17/d/phobos/etc/c/recls/recls_util.cpp gdc-0.18/d/phobos/etc/c/recls/recls_util.cpp --- gdc-0.17/d/phobos/etc/c/recls/recls_util.cpp 2004-10-26 02:41:27.000000000 +0200 +++ gdc-0.18/d/phobos/etc/c/recls/recls_util.cpp 1970-01-01 01:00:00.000000000 +0100 @@ -1,134 +0,0 @@ -/* ///////////////////////////////////////////////////////////////////////////// - * File: recls_util.cpp - * - * Purpose: Platform-independent utility functions for the recls API. - * - * Created: 17th August 2003 - * Updated: 27th November 2003 - * - * License: (Licensed under the Synesis Software Standard Source License) - * - * Copyright (C) 2002-2003, Synesis Software Pty Ltd. - * - * All rights reserved. - * - * www: http://www.synesis.com.au/software - * http://www.recls.org/ - * - * email: submissions@recls.org for submissions - * admin@recls.org for other enquiries - * - * Redistribution and use in source and binary forms, with or - * without modification, are permitted provided that the following - * conditions are met: - * - * (i) Redistributions of source code must retain the above - * copyright notice and contact information, this list of - * conditions and the following disclaimer. - * - * (ii) Any derived versions of this software (howsoever modified) - * remain the sole property of Synesis Software. - * - * (iii) Any derived versions of this software (howsoever modified) - * remain subject to all these conditions. - * - * (iv) Neither the name of Synesis Software nor the names of any - * subdivisions, employees or agents of Synesis Software, nor the - * names of any other contributors to this software may be used to - * endorse or promote products derived from this software without - * specific prior written permission. - * - * This source code is provided by Synesis Software "as is" and any - * warranties, whether expressed or implied, including, but not - * limited to, the implied warranties of merchantability and - * fitness for a particular purpose are disclaimed. In no event - * shall the Synesis Software be liable for any direct, indirect, - * incidental, special, exemplary, or consequential damages - * (including, but not limited to, procurement of substitute goods - * or services; loss of use, data, or profits; or business - * interruption) however caused and on any theory of liability, - * whether in contract, strict liability, or tort (including - * negligence or otherwise) arising in any way out of the use of - * this software, even if advised of the possibility of such - * damage. - * - * ////////////////////////////////////////////////////////////////////////// */ - - -/* ///////////////////////////////////////////////////////////////////////////// - * Includes - */ - -#include "recls.h" -#include "recls_internal.h" -#include "recls_assert.h" -#include "recls_util.h" - -#include - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace - */ - -#if !defined(RECLS_NO_NAMESPACE) -namespace recls -{ -#endif /* !RECLS_NO_NAMESPACE */ - -/* ////////////////////////////////////////////////////////////////////////// */ - -RECLS_LINKAGE_C size_t align_up_size(size_t i) -{ - return (size_t)((i + (4 - 1)) & ~(4 - 1)); -} - -RECLS_LINKAGE_C recls_bool_t is_dots(recls_char_t const *f) -{ - recls_assert(NULL != f); - - return ( f[0] == '.' && - f[1] == '\0') || - ( f[0] == '.' && - f[1] == '.' && - f[2] == '\0'); -} - -RECLS_LINKAGE_C size_t count_char_instances_a(recls_char_a_t const *begin, recls_char_a_t const *end, recls_char_a_t const ch) -{ - size_t cDirParts = 0; - - for(; begin != end; ++begin) - { - if(*begin == ch) - { - ++cDirParts; - } - } - - return cDirParts; -} - -RECLS_LINKAGE_C size_t count_char_instances_w(recls_char_w_t const *begin, recls_char_w_t const *end, recls_char_w_t const ch) -{ - size_t cDirParts = 0; - - for(; begin != end; ++begin) - { - if(*begin == ch) - { - ++cDirParts; - } - } - - return cDirParts; -} - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace - */ - -#if !defined(RECLS_NO_NAMESPACE) -} /* namespace recls */ -#endif /* !RECLS_NO_NAMESPACE */ - -/* ////////////////////////////////////////////////////////////////////////// */ diff -uNr gdc-0.17/d/phobos/etc/c/recls/recls_util.h gdc-0.18/d/phobos/etc/c/recls/recls_util.h --- gdc-0.17/d/phobos/etc/c/recls/recls_util.h 2004-10-26 02:41:27.000000000 +0200 +++ gdc-0.18/d/phobos/etc/c/recls/recls_util.h 1970-01-01 01:00:00.000000000 +0100 @@ -1,124 +0,0 @@ -/* ///////////////////////////////////////////////////////////////////////////// - * File: recls_util.h - * - * Purpose: Utility functions for the recls API. - * - * Created: 17th August 2003 - * Updated: 21st November 2003 - * - * Author: Matthew Wilson, Synesis Software Pty Ltd. - * - * License: (Licensed under the Synesis Software Standard Source License) - * - * Copyright (C) 2002-2003, Synesis Software Pty Ltd. - * - * All rights reserved. - * - * www: http://www.synesis.com.au/software - * http://www.recls.org/ - * - * email: submissions@recls.org for submissions - * admin@recls.org for other enquiries - * - * Redistribution and use in source and binary forms, with or - * without modification, are permitted provided that the following - * conditions are met: - * - * (i) Redistributions of source code must retain the above - * copyright notice and contact information, this list of - * conditions and the following disclaimer. - * - * (ii) Any derived versions of this software (howsoever modified) - * remain the sole property of Synesis Software. - * - * (iii) Any derived versions of this software (howsoever modified) - * remain subject to all these conditions. - * - * (iv) Neither the name of Synesis Software nor the names of any - * subdivisions, employees or agents of Synesis Software, nor the - * names of any other contributors to this software may be used to - * endorse or promote products derived from this software without - * specific prior written permission. - * - * This source code is provided by Synesis Software "as is" and any - * warranties, whether expressed or implied, including, but not - * limited to, the implied warranties of merchantability and - * fitness for a particular purpose are disclaimed. In no event - * shall the Synesis Software be liable for any direct, indirect, - * incidental, special, exemplary, or consequential damages - * (including, but not limited to, procurement of substitute goods - * or services; loss of use, data, or profits; or business - * interruption) however caused and on any theory of liability, - * whether in contract, strict liability, or tort (including - * negligence or otherwise) arising in any way out of the use of - * this software, even if advised of the possibility of such - * damage. - * - * ////////////////////////////////////////////////////////////////////////// */ - - -#ifndef RECLS_INCL_H_RECLS_UTIL -#define RECLS_INCL_H_RECLS_UTIL - -/* File version */ -#ifndef RECLS_DOCUMENTATION_SKIP_SECTION -# define RECLS_VER_H_RECLS_UTIL_MAJOR 1 -# define RECLS_VER_H_RECLS_UTIL_MINOR 4 -# define RECLS_VER_H_RECLS_UTIL_REVISION 1 -# define RECLS_VER_H_RECLS_UTIL_EDIT 9 -#endif /* !RECLS_DOCUMENTATION_SKIP_SECTION */ - -/** \file recls_util.h Utility functions for the \ref group_recls API */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Includes - */ - -#include "recls.h" - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace - */ - -#if !defined(RECLS_NO_NAMESPACE) -namespace recls -{ -#endif /* !RECLS_NO_NAMESPACE */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Functions - */ - -RECLS_LINKAGE_C recls_bool_t is_dots(recls_char_t const *f); -RECLS_LINKAGE_C recls_bool_t file_exists(recls_char_t const *f); -RECLS_LINKAGE_C size_t align_up_size(size_t i); -RECLS_LINKAGE_C size_t count_char_instances_a(recls_char_a_t const *begin, recls_char_a_t const *end, recls_char_a_t const ch); -RECLS_LINKAGE_C size_t count_char_instances_w(recls_char_w_t const *begin, recls_char_w_t const *end, recls_char_w_t const ch); -RECLS_LINKAGE_C size_t count_dir_parts_a(recls_char_a_t const *begin, recls_char_a_t const *end); -RECLS_LINKAGE_C size_t count_dir_parts_w(recls_char_w_t const *begin, recls_char_w_t const *end); - -#ifdef __cplusplus -inline size_t count_dir_parts(recls_char_a_t const *begin, recls_char_a_t const *end) -{ - return count_dir_parts_a(begin, end); -} - -inline size_t count_dir_parts(recls_char_w_t const *begin, recls_char_w_t const *end) -{ - return count_dir_parts_w(begin, end); -} -#endif /* __cplusplus */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace - */ - -#if !defined(RECLS_NO_NAMESPACE) -} /* namespace recls */ -#endif /* !RECLS_NO_NAMESPACE */ - -/* ////////////////////////////////////////////////////////////////////////// */ - -#endif /* !RECLS_INCL_H_RECLS_UTIL */ - -/* ////////////////////////////////////////////////////////////////////////// */ diff -uNr gdc-0.17/d/phobos/etc/c/recls/recls_util_unix.cpp gdc-0.18/d/phobos/etc/c/recls/recls_util_unix.cpp --- gdc-0.17/d/phobos/etc/c/recls/recls_util_unix.cpp 2004-10-26 02:41:27.000000000 +0200 +++ gdc-0.18/d/phobos/etc/c/recls/recls_util_unix.cpp 1970-01-01 01:00:00.000000000 +0100 @@ -1,116 +0,0 @@ -/* ///////////////////////////////////////////////////////////////////////////// - * File: recls_util_win32.cpp - * - * Purpose: Win32 utility functions for the recls API. - * - * Created: 17th August 2003 - * Updated: 27th November 2003 - * - * License: (Licensed under the Synesis Software Standard Source License) - * - * Copyright (C) 2002-2003, Synesis Software Pty Ltd. - * - * All rights reserved. - * - * www: http://www.synesis.com.au/software - * http://www.recls.org/ - * - * email: submissions@recls.org for submissions - * admin@recls.org for other enquiries - * - * Redistribution and use in source and binary forms, with or - * without modification, are permitted provided that the following - * conditions are met: - * - * (i) Redistributions of source code must retain the above - * copyright notice and contact information, this list of - * conditions and the following disclaimer. - * - * (ii) Any derived versions of this software (howsoever modified) - * remain the sole property of Synesis Software. - * - * (iii) Any derived versions of this software (howsoever modified) - * remain subject to all these conditions. - * - * (iv) Neither the name of Synesis Software nor the names of any - * subdivisions, employees or agents of Synesis Software, nor the - * names of any other contributors to this software may be used to - * endorse or promote products derived from this software without - * specific prior written permission. - * - * This source code is provided by Synesis Software "as is" and any - * warranties, whether expressed or implied, including, but not - * limited to, the implied warranties of merchantability and - * fitness for a particular purpose are disclaimed. In no event - * shall the Synesis Software be liable for any direct, indirect, - * incidental, special, exemplary, or consequential damages - * (including, but not limited to, procurement of substitute goods - * or services; loss of use, data, or profits; or business - * interruption) however caused and on any theory of liability, - * whether in contract, strict liability, or tort (including - * negligence or otherwise) arising in any way out of the use of - * this software, even if advised of the possibility of such - * damage. - * - * ////////////////////////////////////////////////////////////////////////// */ - - -/* ///////////////////////////////////////////////////////////////////////////// - * Includes - */ - -#include "recls.h" -#include "recls_internal.h" -#include "recls_assert.h" -#include "recls_util.h" - -#include - -#include - -#include -#include - -#include - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace - */ - -#if !defined(RECLS_NO_NAMESPACE) -namespace recls -{ -#endif /* !RECLS_NO_NAMESPACE */ - -unixstl_ns_using(filesystem_traits) - -/* ////////////////////////////////////////////////////////////////////////// */ - -RECLS_LINKAGE_C recls_bool_t file_exists(recls_char_t const *f) -{ - struct stat st; - - return 0 == stat(f, &st) || errno != ENOENT; -} - -RECLS_LINKAGE_C size_t count_dir_parts_a(recls_char_a_t const *begin, recls_char_a_t const *end) -{ - return count_char_instances_a(begin, end, unixstl_ns_qual(filesystem_traits)::path_name_separator()); -} - -#if 0 -RECLS_LINKAGE_C size_t count_dir_parts_w(recls_char_w_t const *begin, recls_char_w_t const *end) -{ - return count_char_instances_w(begin, end, unixstl_ns_qual(filesystem_traits)::path_name_separator()); -} -#endif /* 0 */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace - */ - -#if !defined(RECLS_NO_NAMESPACE) -} /* namespace recls */ -#endif /* !RECLS_NO_NAMESPACE */ - -/* ////////////////////////////////////////////////////////////////////////// */ diff -uNr gdc-0.17/d/phobos/etc/c/recls/recls_util_win32.cpp gdc-0.18/d/phobos/etc/c/recls/recls_util_win32.cpp --- gdc-0.17/d/phobos/etc/c/recls/recls_util_win32.cpp 2004-10-26 02:41:27.000000000 +0200 +++ gdc-0.18/d/phobos/etc/c/recls/recls_util_win32.cpp 1970-01-01 01:00:00.000000000 +0100 @@ -1,105 +0,0 @@ -/* ///////////////////////////////////////////////////////////////////////////// - * File: recls_util_win32.cpp - * - * Purpose: Win32 utility functions for the recls API. - * - * Created: 17th August 2003 - * Updated: 27th November 2003 - * - * License: (Licensed under the Synesis Software Standard Source License) - * - * Copyright (C) 2002-2003, Synesis Software Pty Ltd. - * - * All rights reserved. - * - * www: http://www.synesis.com.au/software - * http://www.recls.org/ - * - * email: submissions@recls.org for submissions - * admin@recls.org for other enquiries - * - * Redistribution and use in source and binary forms, with or - * without modification, are permitted provided that the following - * conditions are met: - * - * (i) Redistributions of source code must retain the above - * copyright notice and contact information, this list of - * conditions and the following disclaimer. - * - * (ii) Any derived versions of this software (howsoever modified) - * remain the sole property of Synesis Software. - * - * (iii) Any derived versions of this software (howsoever modified) - * remain subject to all these conditions. - * - * (iv) Neither the name of Synesis Software nor the names of any - * subdivisions, employees or agents of Synesis Software, nor the - * names of any other contributors to this software may be used to - * endorse or promote products derived from this software without - * specific prior written permission. - * - * This source code is provided by Synesis Software "as is" and any - * warranties, whether expressed or implied, including, but not - * limited to, the implied warranties of merchantability and - * fitness for a particular purpose are disclaimed. In no event - * shall the Synesis Software be liable for any direct, indirect, - * incidental, special, exemplary, or consequential damages - * (including, but not limited to, procurement of substitute goods - * or services; loss of use, data, or profits; or business - * interruption) however caused and on any theory of liability, - * whether in contract, strict liability, or tort (including - * negligence or otherwise) arising in any way out of the use of - * this software, even if advised of the possibility of such - * damage. - * - * ////////////////////////////////////////////////////////////////////////// */ - - -/* ///////////////////////////////////////////////////////////////////////////// - * Includes - */ - -#include "recls.h" -#include "recls_internal.h" -#include "recls_assert.h" -#include "recls_util.h" - -#include - -#include - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace - */ - -#if !defined(RECLS_NO_NAMESPACE) -namespace recls -{ -#endif /* !RECLS_NO_NAMESPACE */ - -/* ////////////////////////////////////////////////////////////////////////// */ - -RECLS_LINKAGE_C recls_bool_t file_exists(recls_char_t const *f) -{ - return 0xFFFFFFFF != ::GetFileAttributes(f); -} - -RECLS_LINKAGE_C size_t count_dir_parts_a(recls_char_a_t const *begin, recls_char_a_t const *end) -{ - return count_char_instances_a(begin, end, winstl_ns_qual(filesystem_traits)::path_name_separator()); -} - -RECLS_LINKAGE_C size_t count_dir_parts_w(recls_char_w_t const *begin, recls_char_w_t const *end) -{ - return count_char_instances_w(begin, end, winstl_ns_qual(filesystem_traits)::path_name_separator()); -} - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace - */ - -#if !defined(RECLS_NO_NAMESPACE) -} /* namespace recls */ -#endif /* !RECLS_NO_NAMESPACE */ - -/* ////////////////////////////////////////////////////////////////////////// */ diff -uNr gdc-0.17/d/phobos/etc/c/recls/recls_win32.h gdc-0.18/d/phobos/etc/c/recls/recls_win32.h --- gdc-0.17/d/phobos/etc/c/recls/recls_win32.h 2004-10-26 02:41:27.000000000 +0200 +++ gdc-0.18/d/phobos/etc/c/recls/recls_win32.h 1970-01-01 01:00:00.000000000 +0100 @@ -1,124 +0,0 @@ -/* ///////////////////////////////////////////////////////////////////////////// - * File: recls_win32.h - * - * Purpose: Win32-specific header file for the recls API. - * - * Created: 18th August 2003 - * Updated: 21st November 2003 - * - * Author: Matthew Wilson, Synesis Software Pty Ltd. - * - * License: (Licensed under the Synesis Software Standard Source License) - * - * Copyright (C) 2002-2003, Synesis Software Pty Ltd. - * - * All rights reserved. - * - * www: http://www.synesis.com.au/software - * http://www.recls.org/ - * - * email: submissions@recls.org for submissions - * admin@recls.org for other enquiries - * - * Redistribution and use in source and binary forms, with or - * without modification, are permitted provided that the following - * conditions are met: - * - * (i) Redistributions of source code must retain the above - * copyright notice and contact information, this list of - * conditions and the following disclaimer. - * - * (ii) Any derived versions of this software (howsoever modified) - * remain the sole property of Synesis Software. - * - * (iii) Any derived versions of this software (howsoever modified) - * remain subject to all these conditions. - * - * (iv) Neither the name of Synesis Software nor the names of any - * subdivisions, employees or agents of Synesis Software, nor the - * names of any other contributors to this software may be used to - * endorse or promote products derived from this software without - * specific prior written permission. - * - * This source code is provided by Synesis Software "as is" and any - * warranties, whether expressed or implied, including, but not - * limited to, the implied warranties of merchantability and - * fitness for a particular purpose are disclaimed. In no event - * shall the Synesis Software be liable for any direct, indirect, - * incidental, special, exemplary, or consequential damages - * (including, but not limited to, procurement of substitute goods - * or services; loss of use, data, or profits; or business - * interruption) however caused and on any theory of liability, - * whether in contract, strict liability, or tort (including - * negligence or otherwise) arising in any way out of the use of - * this software, even if advised of the possibility of such - * damage. - * - * ////////////////////////////////////////////////////////////////////////// */ - - -#ifndef RECLS_INCL_H_RECLS_WIN32 -#define RECLS_INCL_H_RECLS_WIN32 - -/* File version */ -#ifndef RECLS_DOCUMENTATION_SKIP_SECTION -# define RECLS_VER_H_RECLS_WIN32_MAJOR 1 -# define RECLS_VER_H_RECLS_WIN32_MINOR 1 -# define RECLS_VER_H_RECLS_WIN32_REVISION 2 -# define RECLS_VER_H_RECLS_WIN32_EDIT 6 -#endif /* !RECLS_DOCUMENTATION_SKIP_SECTION */ - -/** \file recls_win32.h Win32-specific parts of the \ref group_recls API */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Strictness - */ - -#ifndef RECLS_NO_STRICT -# define RECLS_STRICT -#endif /* !RECLS_NO_STRICT */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Includes - */ - -#include "recls.h" - -#ifndef RECLS_PLATFORM_IS_WIN32 -# error recls_win32.h is to be included in Win32 compilations only -#endif /* RECLS_PLATFORM_IS_WIN32 */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace - */ - -#if !defined(RECLS_NO_NAMESPACE) -namespace recls -{ -#endif /* !RECLS_NO_NAMESPACE */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Functions - */ - -/** Gets the drive associated with the given file entry info structure - * - * \param hEntry The info entry structure. - * \param pchDrive Pointer to a character to receive the drive character. Cannot be NULL. The character will be in uppercase. - */ -RECLS_FNDECL(void) Recls_GetDriveProperty( recls_info_t hEntry - , recls_char_t *pchDrive); - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace - */ - -#if !defined(RECLS_NO_NAMESPACE) -} /* namespace recls */ -#endif /* !RECLS_NO_NAMESPACE */ - -/* ////////////////////////////////////////////////////////////////////////// */ - -#endif /* !RECLS_INCL_H_RECLS_WIN32 */ - -/* ////////////////////////////////////////////////////////////////////////// */ diff -uNr gdc-0.17/d/phobos/etc/c/recls/win32.mak gdc-0.18/d/phobos/etc/c/recls/win32.mak --- gdc-0.17/d/phobos/etc/c/recls/win32.mak 2004-10-26 02:41:27.000000000 +0200 +++ gdc-0.18/d/phobos/etc/c/recls/win32.mak 1970-01-01 01:00:00.000000000 +0100 @@ -1,69 +0,0 @@ -# ############################################################################## -# File: makefile.win32 -# -# Purpose: Digital Mars C/C++ 8.38+ makefile for the recls library (std.recls) -# -# Created: 24th November 2003 -# Updated: 24th November 2003 -# -# Copyright: Synesis Software Pty Ltd, (c) 2003. All rights reserved. -# -# Home: www.synesis.com.au/software -# -# ############################################################################## - -# ############################################################################## -# Macros - -CC = dmc - -RECLS_LIBDIR = . - -STLSOFT_RECLS_PATCH_INCLUDE = $(RECLS_INCLUDE) - -STLSOFT_INCLUDE = ..\stlsoft - -CCFLAGS = -wx -o -CCDEFS = -DNDEBUG - -CCARGS = $(CCFLAGS) $(CCDEFS) -c -I. -I$(STLSOFT_INCLUDE) -Ic:\dm\stlport\stlport - -################################################################################ -# Objects - -OBJS_C = \ - .\recls_api.obj \ - .\recls_fileinfo.obj \ - .\recls_internal.obj \ - .\recls_util.obj \ - .\recls_api_win32.obj \ - .\recls_fileinfo_win32.obj \ - .\recls_util_win32.obj - - -################################################################################ -# Suffix rules - -.c.obj: - $(CC) $(CCARGS) -o$@ $? - -.cpp.obj: - $(CC) $(CCARGS) -o$@ $? - -################################################################################ -# Targets - -target: $(RECLS_LIBDIR)\recls.lib - -clean: - @echo Cleaning other file types - @if exist $(RECLS_LIBDIR)\recls.lib del $(RECLS_LIBDIR)\recls.lib - @del $(OBJS_C) 2>NUL - @if exist *.map del *.map - -# executables - -$(RECLS_LIBDIR)\recls.lib: $(OBJS_C) - lib -c $@ $(OBJS_C) - -################################################################################ diff -uNr gdc-0.17/d/phobos/etc/c/stlsoft/stlsoft_cccap_dmc.h gdc-0.18/d/phobos/etc/c/stlsoft/stlsoft_cccap_dmc.h --- gdc-0.17/d/phobos/etc/c/stlsoft/stlsoft_cccap_dmc.h 2004-10-26 02:41:27.000000000 +0200 +++ gdc-0.18/d/phobos/etc/c/stlsoft/stlsoft_cccap_dmc.h 1970-01-01 01:00:00.000000000 +0100 @@ -1,323 +0,0 @@ -/* ///////////////////////////////////////////////////////////////////////////// - * File: stlsoft_cccap_dmc.h - * - * Purpose: Compiler feature discrimination for Digital Mars C/C++. - * - * Created: 7th February 2003 - * Updated: 28th November 2003 - * - * Author: Matthew Wilson, Synesis Software Pty Ltd. - * - * License: (Licensed under the Synesis Software Standard Source License) - * - * Copyright (C) 2002-2003, Synesis Software Pty Ltd. - * - * All rights reserved. - * - * www: http://www.synesis.com.au/stlsoft - * http://www.stlsoft.org/ - * - * email: submissions@stlsoft.org for submissions - * admin@stlsoft.org for other enquiries - * - * Redistribution and use in source and binary forms, with or - * without modification, are permitted provided that the following - * conditions are met: - * - * (i) Redistributions of source code must retain the above - * copyright notice and contact information, this list of - * conditions and the following disclaimer. - * - * (ii) Any derived versions of this software (howsoever modified) - * remain the sole property of Synesis Software. - * - * (iii) Any derived versions of this software (howsoever modified) - * remain subject to all these conditions. - * - * (iv) Neither the name of Synesis Software nor the names of any - * subdivisions, employees or agents of Synesis Software, nor the - * names of any other contributors to this software may be used to - * endorse or promote products derived from this software without - * specific prior written permission. - * - * This source code is provided by Synesis Software "as is" and any - * warranties, whether expressed or implied, including, but not - * limited to, the implied warranties of merchantability and - * fitness for a particular purpose are disclaimed. In no event - * shall the Synesis Software be liable for any direct, indirect, - * incidental, special, exemplary, or consequential damages - * (including, but not limited to, procurement of substitute goods - * or services; loss of use, data, or profits; or business - * interruption) however caused and on any theory of liability, - * whether in contract, strict liability, or tort (including - * negligence or otherwise) arising in any way out of the use of - * this software, even if advised of the possibility of such - * damage. - * - * ////////////////////////////////////////////////////////////////////////// */ - - -#ifndef _STLSOFT_INCL_H_STLSOFT -# error This file must not be included independently of stlsoft.h -#endif /* !_STLSOFT_INCL_H_STLSOFT */ - -#ifdef _STLSOFT_INCL_H_STLSOFT_CCCAP_DMC -# error This file cannot be included more than once in any compilation unit -#endif /* _STLSOFT_INCL_H_STLSOFT_CCCAP_DMC */ - -/* ////////////////////////////////////////////////////////////////////////// */ - -# define _STLSOFT_VER_H_STLSOFT_CCCAP_DMC_MAJOR 1 -# define _STLSOFT_VER_H_STLSOFT_CCCAP_DMC_MINOR 13 -# define _STLSOFT_VER_H_STLSOFT_CCCAP_DMC_REVISION 2 -# define _STLSOFT_VER_H_STLSOFT_CCCAP_DMC_EDIT 34 - -/* ///////////////////////////////////////////////////////////////////////////// - * Compiler features - */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Includes - */ - -#include /* Needed to determine whether we're using STLport or SGI STL */ - -/* Messaging - */ - -#define STLSOFT_CF_PRAGMA_MESSAGE_SUPPORT - -/* Types: - */ - -/* bool */ -#ifdef _BOOL_DEFINED -# define __STLSOFT_CF_NATIVE_BOOL_SUPPORT -#else - /* Not defined */ -#endif /* _BOOL_DEFINED */ - -/* wchar_t */ -#ifdef _WCHAR_T_DEFINED -# define __STLSOFT_CF_NATIVE_WCHAR_T_SUPPORT -#else - /* Not defined */ -#endif /* _WCHAR_T_DEFINED */ - -/* Native 8-bit integer */ -//#define __STLSOFT_CF_NATIVE_8BIT_INT_SUPPORT - -/* Native 16-bit integer */ -//#define __STLSOFT_CF_NATIVE_16BIT_INT_SUPPORT - -/* Native 32-bit integer */ -//#define __STLSOFT_CF_NATIVE_32BIT_INT_SUPPORT - -/* Native 64-bit integer */ -#define __STLSOFT_CF_NATIVE___int64_SUPPORT - -/* long long */ -#define __STLSOFT_CF_NATIVE_LONG_LONG_SUPPORT - -/* Are integers a unique type (i.e. not int8/16/32/64)? */ -#define __STLSOFT_CF_INT_DISTINCT_TYPE - -#if __DMC__ >= 0x0835 -# define __STLSOFT_CF_STATIC_ASSERT_SUPPORT -#endif /* __DMC__ */ - -/* Exception support */ -#ifdef _CPPUNWIND -# define __STLSOFT_CF_EXCEPTION_SUPPORT -#else - /* Not defined */ -#endif /* _CPPUNWIND */ - -/* */ -//#define __STLSOFT_CF_FUNCTION_SIGNATURE_FULL_ARG_QUALIFICATION_REQUIRED - -/* Namespace support */ - /* The current versions (up to and including 8.32) of the Digital Mars - * compiler have issues whereby out-of-class inline methods seem to be placed - * within their namespace of instantiation rather than of definition, so - * namespace support is turned off. - */ -#if __DMC__ < 0x833 -# define _STLSOFT_NO_NAMESPACES -#endif /* __DMC__ < 0x832 */ - -#define __STLSOFT_CF_NAMESPACE_SUPPORT - -#define STLSOFT_CF_ANONYMOUS_UNION_SUPPORT - -/* Template support */ -#define __STLSOFT_CF_TEMPLATE_SUPPORT - -//#define STLSOFT_CF_TEMPLATE_TYPE_REQUIRED_IN_ARGS - -//#define __STLSOFT_CF_EXCEPTION_SIGNATURE_SUPPORT - -//#define __STLSOFT_CF_THROW_BAD_ALLOC - -#define __STLSOFT_CF_TEMPLATE_CLASS_DEFAULT_FUNDAMENTAL_ARGUMENT_SUPPORT - -#define __STLSOFT_CF_TEMPLATE_CLASS_DEFAULT_CLASS_ARGUMENT_SUPPORT - -#if __DMC__ >= 0x0837 -# define STLSOFT_CF_MEM_FUNC_AS_TEMPLATE_PARAM_SUPPORT -#else - /* Not defined */ -#endif /* __DMC__ */ - -#if __DMC__ >= 0x0832 -# define __STLSOFT_CF_MEMBER_TEMPLATE_FUNCTION_SUPPORT -#else - /* Not defined */ -#endif /* __DMC__ */ - -#if __DMC__ >= 0x0832 -# define __STLSOFT_CF_MEMBER_TEMPLATE_CTOR_SUPPORT -#else - /* Not defined */ -#endif /* __DMC__ */ - -#if 0 /* __DMC__ >= 0x0836? */ -# define __STLSOFT_CF_MEMBER_TEMPLATE_RANGE_METHOD_SUPPORT -#else - /* Not defined */ -#endif /* __DMC__ */ - -#if __DMC__ >= 0x0829 -# define __STLSOFT_CF_MEMBER_TEMPLATE_CLASS_SUPPORT -#else - /* Not defined */ -#endif /* __DMC__ */ - -#if __DMC__ >= 0x0829 -# define __STLSOFT_CF_TEMPLATE_SPECIALISATION_SYNTAX -#else - /* Not defined */ -#endif /* __DMC__ */ - -#if __DMC__ >= 0x0829 -# define __STLSOFT_CF_TEMPLATE_PARTIAL_SPECIALISATION_SUPPORT -#else - /* Not defined */ -#endif /* __DMC__ */ - -//#define __STLSOFT_CF_TEMPLATE_OUTOFCLASSFN_QUALIFIED_TYPE_SUPPORT - -#ifdef _STLPORT_VERSION -# define __STLSOFT_CF_std_NAMESPACE -#else - /* Not defined */ -#endif /* _STLPORT_VERSION */ - -#define __STLSOFT_CF_std_char_traits_AVAILABLE - -#if 0 /* __DMC__ >= 0x0836? */ -# define __STLSOFT_CF_ALLOCATOR_ALLOCATE_HAS_HINT -#else - /* Not defined */ -#endif /* __DMC__ */ - -#define __STLSOFT_CF_ALLOCATOR_DEALLOCATE_HAS_OBJECTCOUNT - -#if (__DMC__ >= 0x0829) -# define __STLSOFT_CF_BIDIRECTIONAL_ITERATOR_SUPPORT -#else - /* Not defined */ -#endif /* __DMC__ >= 0x0829 */ - -#define __STLSOFT_CF_EXPLICIT_KEYWORD_SUPPORT - -#define __STLSOFT_CF_MUTABLE_KEYWORD_SUPPORT - -#define __STLSOFT_CF_TYPENAME_PARAM_KEYWORD_SUPPORT - -#define __STLSOFT_CF_TYPENAME_TYPE_KEYWORD_SUPPORT - -#define __STLSOFT_CF_TYPENAME_TYPE_DEF_KEYWORD_SUPPORT - -//#define __STLSOFT_CF_TYPENAME_TYPE_MIL_KEYWORD_SUPPORT - -#define __STLSOFT_CF_MOVE_CONSTRUCTOR_SUPPORT - -#if __DMC__ >= 0x0834 -# define __STLSOFT_CF_KOENIG_LOOKUP_SUPPORT -#endif /* __DMC__ */ - -//#define __STLSOFT_CF_TEMPLATE_TEMPLATE_SUPPORT - -#if __DMC__ >= 0x0838 -# define __STLSOFT_CF_STATIC_ARRAY_SIZE_DETERMINATION_SUPPORT -#else - /* Not defined */ -#endif /* __DMC__ */ - -#define __STLSOFT_CF_VENEER_SUPPORT - -// Shims are supported -//# define __STLSOFT_CF_TEMPLATE_SHIMS_NOT_SUPPORTED - -#define __STLSOFT_CF_NEGATIVE_MODULUS_POSITIVE_GIVES_NEGATIVE_RESULT - -#define STLSOFT_CF_OPERATOR_BOOL_AS_OPERATOR_POINTER_TO_MEMBER_SUPPORT -#define STLSOFT_CF_OPERATOR_NOT_VIA_OPERATOR_POINTER_TO_MEMBER_SUPPORT - -#if defined(_STLSOFT_CUSTOM_ASSERT) - /* You have defined the pre-processor symbol _STLSOFT_CUSTOM_ASSERT, - * which stipulates that you will be providing your own assert. This - * requires that you have defined _STLSOFT_CUSTOM_ASSERT() as a macro - * taking 1 parameter (the condition to assert). - * - * Suppose you have a function _DisplayAssert(), which has the - * following signature: - * - * void _DisplayAssert(char const *file, int line, char const *expression); - * - * Presumably you would also have your own assert macro, say MY_ASSERT(), - * defined as: - * - * #define MY_ASSERT(_x) ((void)((!(_x)) ? ((void)(_DisplayAssert(__FILE__, __LINE__, #_x))) : ((void)0))) - * - * so you would simply need to define _STLSOFT_CUSTOM_ASSERT() in terms of - * MY_ASSERT(), as in: - * - * #define _STLSOFT_CUSTOM_ASSERT(_x) MY_ASSERT(_x) - * - * where - */ -# define __STLSOFT_CF_ASSERT_SUPPORT -# define stlsoft_assert(_x) _STLSOFT_CUSTOM_ASSERT(_x) -# if defined(_STLSOFT_CUSTOM_ASSERT_INCLUDE) -# define __STLSOFT_CF_ASSERT_INCLUDE_NAME _STLSOFT_CUSTOM_ASSERT_INCLUDE -# else -# error You must define _STLSOFT_CUSTOM_ASSERT_INCLUDE along with _STLSOFT_CUSTOM_ASSERT() -# endif /* !_STLSOFT_CUSTOM_ASSERT_INCLUDE */ -#else -# define __STLSOFT_CF_ASSERT_SUPPORT - //#define __STLSOFT_CF_USE_cassert -# define __STLSOFT_CF_ASSERT_INCLUDE_NAME -# define stlsoft_assert(_x) assert(_x) -#endif /* _STLSOFT_CUSTOM_ASSERT */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Calling convention - */ - -#define STLSOFT_CF_FASTCALL_SUPPORTED -#define STLSOFT_CF_STDCALL_SUPPORTED - -/* ///////////////////////////////////////////////////////////////////////////// - * Inline assembler - */ - -#define STSLSOFT_INLINE_ASM_SUPPORTED -#define STSLSOFT_ASM_IN_INLINE_SUPPORTED - -/* ///////////////////////////////////////////////////////////////////////////// - * Compiler warning suppression - */ - -/* ////////////////////////////////////////////////////////////////////////// */ diff -uNr gdc-0.17/d/phobos/etc/c/stlsoft/stlsoft_cccap_gcc.h gdc-0.18/d/phobos/etc/c/stlsoft/stlsoft_cccap_gcc.h --- gdc-0.17/d/phobos/etc/c/stlsoft/stlsoft_cccap_gcc.h 2004-10-26 02:41:27.000000000 +0200 +++ gdc-0.18/d/phobos/etc/c/stlsoft/stlsoft_cccap_gcc.h 1970-01-01 01:00:00.000000000 +0100 @@ -1,255 +0,0 @@ -/* ///////////////////////////////////////////////////////////////////////////// - * File: stlsoft_cccap_gcc.h - * - * Purpose: Compiler feature discrimination for GNU C/C++. - * - * Created: 7th February 2003 - * Updated: 22nd November 2003 - * - * Author: Matthew Wilson, Synesis Software Pty Ltd. - * - * License: (Licensed under the Synesis Software Standard Source License) - * - * Copyright (C) 2002-2003, Synesis Software Pty Ltd. - * - * All rights reserved. - * - * www: http://www.synesis.com.au/stlsoft - * http://www.stlsoft.org/ - * - * email: submissions@stlsoft.org for submissions - * admin@stlsoft.org for other enquiries - * - * Redistribution and use in source and binary forms, with or - * without modification, are permitted provided that the following - * conditions are met: - * - * (i) Redistributions of source code must retain the above - * copyright notice and contact information, this list of - * conditions and the following disclaimer. - * - * (ii) Any derived versions of this software (howsoever modified) - * remain the sole property of Synesis Software. - * - * (iii) Any derived versions of this software (howsoever modified) - * remain subject to all these conditions. - * - * (iv) Neither the name of Synesis Software nor the names of any - * subdivisions, employees or agents of Synesis Software, nor the - * names of any other contributors to this software may be used to - * endorse or promote products derived from this software without - * specific prior written permission. - * - * This source code is provided by Synesis Software "as is" and any - * warranties, whether expressed or implied, including, but not - * limited to, the implied warranties of merchantability and - * fitness for a particular purpose are disclaimed. In no event - * shall the Synesis Software be liable for any direct, indirect, - * incidental, special, exemplary, or consequential damages - * (including, but not limited to, procurement of substitute goods - * or services; loss of use, data, or profits; or business - * interruption) however caused and on any theory of liability, - * whether in contract, strict liability, or tort (including - * negligence or otherwise) arising in any way out of the use of - * this software, even if advised of the possibility of such - * damage. - * - * ////////////////////////////////////////////////////////////////////////// */ - - -#ifndef _STLSOFT_INCL_H_STLSOFT -# error This file must not be included independently of stlsoft.h -#endif /* !_STLSOFT_INCL_H_STLSOFT */ - -#ifdef _STLSOFT_INCL_H_STLSOFT_CCCAP_GCC -# error This file cannot be included more than once in any compilation unit -#endif /* _STLSOFT_INCL_H_STLSOFT_CCCAP_GCC */ - -/* ////////////////////////////////////////////////////////////////////////// */ - -#define _STLSOFT_VER_H_STLSOFT_CCCAP_GCC_MAJOR 1 -#define _STLSOFT_VER_H_STLSOFT_CCCAP_GCC_MINOR 10 -#define _STLSOFT_VER_H_STLSOFT_CCCAP_GCC_REVISION 1 -#define _STLSOFT_VER_H_STLSOFT_CCCAP_GCC_EDIT 22 - -/* ///////////////////////////////////////////////////////////////////////////// - * Compiler features - */ - -/* Messaging - */ - -//#define STLSOFT_CF_PRAGMA_MESSAGE_SUPPORT - -/* Types: - */ - -/* bool */ -#define __STLSOFT_CF_NATIVE_BOOL_SUPPORT - -/* wchar_t */ -//#define __STLSOFT_CF_NATIVE_WCHAR_T_SUPPORT - -/* Native 8-bit integer */ -//#define __STLSOFT_CF_NATIVE_8BIT_INT_SUPPORT - -/* Native 16-bit integer */ -//#define __STLSOFT_CF_NATIVE_16BIT_INT_SUPPORT - -/* Native 32-bit integer */ -//#define __STLSOFT_CF_NATIVE_32BIT_INT_SUPPORT - -/* Native 64-bit integer */ -//#define __STLSOFT_CF_NATIVE___int64_SUPPORT - -/* long long */ -#define __STLSOFT_CF_NATIVE_LONG_LONG_SUPPORT - -#define __STLSOFT_CF_INT_DISTINCT_TYPE - -#define __STLSOFT_CF_STATIC_ASSERT_SUPPORT - -/* Exception support */ -#define __STLSOFT_CF_EXCEPTION_SUPPORT - -/* */ -#define __STLSOFT_CF_FUNCTION_SIGNATURE_FULL_ARG_QUALIFICATION_REQUIRED - -/* Namespace support */ -//#define _STLSOFT_NO_NAMESPACES - -#define __STLSOFT_CF_NAMESPACE_SUPPORT - -#define STLSOFT_CF_ANONYMOUS_UNION_SUPPORT - -/* Template support */ -#define __STLSOFT_CF_TEMPLATE_SUPPORT - -//#define STLSOFT_CF_TEMPLATE_TYPE_REQUIRED_IN_ARGS - -#define __STLSOFT_CF_EXCEPTION_SIGNATURE_SUPPORT - -#define __STLSOFT_CF_THROW_BAD_ALLOC - -#define __STLSOFT_CF_TEMPLATE_CLASS_DEFAULT_FUNDAMENTAL_ARGUMENT_SUPPORT - -#define __STLSOFT_CF_TEMPLATE_CLASS_DEFAULT_CLASS_ARGUMENT_SUPPORT - -#define STLSOFT_CF_MEM_FUNC_AS_TEMPLATE_PARAM_SUPPORT - -#define __STLSOFT_CF_MEMBER_TEMPLATE_FUNCTION_SUPPORT - -#define __STLSOFT_CF_MEMBER_TEMPLATE_CTOR_SUPPORT - -#define __STLSOFT_CF_MEMBER_TEMPLATE_RANGE_METHOD_SUPPORT - -#define __STLSOFT_CF_MEMBER_TEMPLATE_CLASS_SUPPORT - -#define __STLSOFT_CF_TEMPLATE_SPECIALISATION_SYNTAX - -#define __STLSOFT_CF_TEMPLATE_PARTIAL_SPECIALISATION_SUPPORT - -#define __STLSOFT_CF_TEMPLATE_OUTOFCLASSFN_QUALIFIED_TYPE_SUPPORT - -#define __STLSOFT_CF_std_NAMESPACE - -#if __GNUC__ >= 3 -# define __STLSOFT_CF_std_char_traits_AVAILABLE -#endif /* */ - -#define __STLSOFT_CF_ALLOCATOR_ALLOCATE_HAS_HINT - -#define __STLSOFT_CF_ALLOCATOR_DEALLOCATE_HAS_OBJECTCOUNT - -#define __STLSOFT_CF_BIDIRECTIONAL_ITERATOR_SUPPORT - -#define __STLSOFT_CF_EXPLICIT_KEYWORD_SUPPORT - -#define __STLSOFT_CF_MUTABLE_KEYWORD_SUPPORT - -#define __STLSOFT_CF_TYPENAME_PARAM_KEYWORD_SUPPORT - -#define __STLSOFT_CF_TYPENAME_TYPE_KEYWORD_SUPPORT - -#define __STLSOFT_CF_TYPENAME_TYPE_DEF_KEYWORD_SUPPORT - -//#define __STLSOFT_CF_TYPENAME_TYPE_MIL_KEYWORD_SUPPORT - -//# define __STLSOFT_CF_MOVE_CONSTRUCTOR_SUPPORT - -#define __STLSOFT_CF_KOENIG_LOOKUP_SUPPORT - -#define __STLSOFT_CF_TEMPLATE_TEMPLATE_SUPPORT - -#if __GNUC__ >= 3 -# define __STLSOFT_CF_STATIC_ARRAY_SIZE_DETERMINATION_SUPPORT -#endif /* 2.95+ */ - -#if __GNUC__ >= 3 -# define __STLSOFT_CF_VENEER_SUPPORT -#endif /* */ - -// Shims are supported -//# define __STLSOFT_CF_TEMPLATE_SHIMS_NOT_SUPPORTED - -#define __STLSOFT_CF_NEGATIVE_MODULUS_POSITIVE_GIVES_NEGATIVE_RESULT - -#define STLSOFT_CF_OPERATOR_BOOL_AS_OPERATOR_POINTER_TO_MEMBER_SUPPORT -#define STLSOFT_CF_OPERATOR_NOT_VIA_OPERATOR_POINTER_TO_MEMBER_SUPPORT - -#if defined(_STLSOFT_CUSTOM_ASSERT) - /* You have defined the pre-processor symbol _STLSOFT_CUSTOM_ASSERT, - * which stipulates that you will be providing your own assert. This - * requires that you have defined _STLSOFT_CUSTOM_ASSERT() as a macro - * taking 1 parameter (the condition to assert). - * - * Suppose you have a function _DisplayAssert(), which has the - * following signature: - * - * void _DisplayAssert(char const *file, int line, char const *expression); - * - * Presumably you would also have your own assert macro, say MY_ASSERT(), - * defined as: - * - * #define MY_ASSERT(_x) ((void)((!(_x)) ? ((void)(_DisplayAssert(__FILE__, __LINE__, #_x))) : ((void)0))) - * - * so you would simply need to define _STLSOFT_CUSTOM_ASSERT() in terms of - * MY_ASSERT(), as in: - * - * #define _STLSOFT_CUSTOM_ASSERT(_x) MY_ASSERT(_x) - * - * where - */ -# define __STLSOFT_CF_ASSERT_SUPPORT -# define stlsoft_assert(_x) _STLSOFT_CUSTOM_ASSERT(_x) -# if defined(_STLSOFT_CUSTOM_ASSERT_INCLUDE) -# define __STLSOFT_CF_ASSERT_INCLUDE_NAME _STLSOFT_CUSTOM_ASSERT_INCLUDE -# else -# error You must define _STLSOFT_CUSTOM_ASSERT_INCLUDE along with _STLSOFT_CUSTOM_ASSERT() -# endif /* !_STLSOFT_CUSTOM_ASSERT_INCLUDE */ -#else -# define __STLSOFT_CF_ASSERT_SUPPORT -//# define __STLSOFT_CF_USE_cassert -# define __STLSOFT_CF_ASSERT_INCLUDE_NAME -# define stlsoft_assert(_x) assert(_x) -#endif /* _STLSOFT_CUSTOM_ASSERT */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Calling convention - */ - -#define STLSOFT_CF_FASTCALL_SUPPORTED -#define STLSOFT_CF_STDCALL_SUPPORTED - -/* ///////////////////////////////////////////////////////////////////////////// - * Inline assembler - */ - -//#define STSLSOFT_INLINE_ASM_SUPPORTED -//#define STSLSOFT_ASM_IN_INLINE_SUPPORTED - -/* ///////////////////////////////////////////////////////////////////////////// - * Compiler warning suppression - */ - -/* ////////////////////////////////////////////////////////////////////////// */ diff -uNr gdc-0.17/d/phobos/etc/c/stlsoft/stlsoft.h gdc-0.18/d/phobos/etc/c/stlsoft/stlsoft.h --- gdc-0.17/d/phobos/etc/c/stlsoft/stlsoft.h 2005-08-12 04:32:44.000000000 +0200 +++ gdc-0.18/d/phobos/etc/c/stlsoft/stlsoft.h 1970-01-01 01:00:00.000000000 +0100 @@ -1,1994 +0,0 @@ -/* ///////////////////////////////////////////////////////////////////////////// - * File: stlsoft.h - * - * Purpose: Root header for the STLSoft libraries. Performs various compiler - * and platform discriminations, and definitions of types. - * - * Created: 15th January 2002 - * Updated: 24th November 2003 - * - * Author: Matthew Wilson, Synesis Software Pty Ltd. - * - * License: (Licensed under the Synesis Software Standard Source License) - * - * Copyright (C) 2002-2003, Synesis Software Pty Ltd. - * - * All rights reserved. - * - * www: http://www.synesis.com.au/stlsoft - * http://www.stlsoft.org/ - * - * email: submissions@stlsoft.org for submissions - * admin@stlsoft.org for other enquiries - * - * Redistribution and use in source and binary forms, with or - * without modification, are permitted provided that the following - * conditions are met: - * - * (i) Redistributions of source code must retain the above - * copyright notice and contact information, this list of - * conditions and the following disclaimer. - * - * (ii) Any derived versions of this software (howsoever modified) - * remain the sole property of Synesis Software. - * - * (iii) Any derived versions of this software (howsoever modified) - * remain subject to all these conditions. - * - * (iv) Neither the name of Synesis Software nor the names of any - * subdivisions, employees or agents of Synesis Software, nor the - * names of any other contributors to this software may be used to - * endorse or promote products derived from this software without - * specific prior written permission. - * - * This source code is provided by Synesis Software "as is" and any - * warranties, whether expressed or implied, including, but not - * limited to, the implied warranties of merchantability and - * fitness for a particular purpose are disclaimed. In no event - * shall the Synesis Software be liable for any direct, indirect, - * incidental, special, exemplary, or consequential damages - * (including, but not limited to, procurement of substitute goods - * or services; loss of use, data, or profits; or business - * interruption) however caused and on any theory of liability, - * whether in contract, strict liability, or tort (including - * negligence or otherwise) arising in any way out of the use of - * this software, even if advised of the possibility of such - * damage. - * - * ////////////////////////////////////////////////////////////////////////// */ - - -#ifndef _STLSOFT_INCL_H_STLSOFT -#define _STLSOFT_INCL_H_STLSOFT - -/* File version */ -#ifndef __STLSOFT_DOCUMENTATION_SKIP_SECTION -# define _STLSOFT_VER_H_STLSOFT_MAJOR 1 -# define _STLSOFT_VER_H_STLSOFT_MINOR 48 -# define _STLSOFT_VER_H_STLSOFT_REVISION 2 -# define _STLSOFT_VER_H_STLSOFT_EDIT 166 -#endif /* !__STLSOFT_DOCUMENTATION_SKIP_SECTION */ - -/** \file stlsoft.h The root header for the \ref STLSoft project, and for all other \ref projects "projects" */ - -/** \weakgroup projects STLSoft Projects - * - * \brief The Projects that comprise the STLSoft libraries - * - * The STLSoft libraries are split up into sub-projects, where each sub-project only - * depends on the STLSoft main project, which resides in the stlsoft - * namespace. - */ - -/** \defgroup STLSoft STLSoft - * \ingroup projects - * - * \brief     ... Robust, Lightweight, Cross-platform, Template Software ... - * - * The philosophy of STLSoft is very simple: providing robust and lightweight software to the development community. The main STLSoft project, STLSoft itself (located at the site you are viewing now) provides cross-platform, technology/API-neutral classes and functions that stand on their own and are useful as independent libraries. They also support the other sub-projects (COMSTL, UNIXSTL, WinSTL, etc.) which are targeted at specific operating systems, technologies and APIs. - - * The philosophy of COMSTL is essentially - * the same as that of the STLSoft - * organisation: providing robust and lightweight software to the Component - * Object Model (COM) development community. - * COMSTL provides template-based software - * that builds on that provided by COM and - * STLSoft in order to reduce programmer - * effort and increase robustness in the use of the COM. - * - * Namespaces - * - * The COMSTL namespace comstl - * is actually an alias for the namespace stlsoft::comstl_project, - * and as such all the COMSTL project components actually reside within the - * stlsoft namespace - * - * Dependencies - * - * As with all parts of the STLSoft libraries, there are no - * dependencies on COMSTL binary components - * and no need to compile COMSTL implementation - * files; COMSTL is 100% header-only! - * - * As with most of the STLSoft sub-projects, - * COMSTL depends only on - * - * - Selected headers from the C standard library, such as wchar.h - * - Selected headers from the C++ standard library, such as new, functional - * - Selected header files of the STLSoft main project - * - The header files particular to the technology area, in this case the COM library headers, such as objbase.h - * - The binary (static and dynamic libraries) components particular to the technology area, in this case the COM libraries that ship with the operating system and your compiler(s) - * - * In addition, some parts of the libraries exhibit different behaviour when - * translated in different contexts, such as with _WIN32_DCOM - * defined, or with iaccess.h include. In all - * cases the libraries function correctly in whatever context they are compiled. - */ - -/* ///////////////////////////////////////////////////////////////////////////// - * STLSoft version - * - * The libraries version information is comprised of major, minor and revision - * components. - * - * The major version is denoted by the _STLSOFT_VER_MAJOR preprocessor symbol. - * A changes to the major version component implies that a dramatic change has - * occured in the libraries, such that considerable changes to source dependent - * on previous versions would need to be effected. - * - * The minor version is denoted by the _STLSOFT_VER_MINOR preprocessor symbol. - * Changes to the minor version component imply that a significant change has - * occured to the libraries, either in the addition of new functionality or in - * the destructive change to one or more components such that recomplilation and - * code change may be necessitated. - * - * The revision version is denoted by the _STLSOFT_VER_REVISIO preprocessor - * symbol. Changes to the revision version component imply that a bug has been - * fixed. Dependent code should be recompiled in order to pick up the changes. - * - * In addition to the individual version symbols - _STLSOFT_VER_MAJOR, - * _STLSOFT_VER_MINOR and _STLSOFT_VER_REVISION - a composite symbol _STLSOFT_VER - * is defined, where the upper 8 bits are 0, bits 16-23 represent the major - * component, bits 8-15 represent the minor component, and bits 0-7 represent - * the revision component. - * - * Each release of the libraries will bear a different version, and that version - * will also have its own symbol: Version 1.0.1 specifies _STLSOFT_VER_1_0_1. - * - * Thus the symbol _STLSOFT_VER may be compared meaningfully with a specific - * version symbol, e.g.# if _STLSOFT_VER >= _STLSOFT_VER_1_0_1 - */ - -/// \def _STLSOFT_VER_MAJOR -/// The major version number of STLSoft - -/// \def _STLSOFT_VER_MINOR -/// The minor version number of STLSoft - -/// \def _STLSOFT_VER_REVISION -/// The revision version number of STLSoft - -/// \def _STLSOFT_VER -/// The current composite version number of STLSoft - -#define _STLSOFT_VER_MAJOR 1 -#define _STLSOFT_VER_MINOR 6 -#define _STLSOFT_VER_REVISION 6 -#define _STLSOFT_VER_1_0_1 0x00010001 /*!< Version 1.0.1 */ -#define _STLSOFT_VER_1_0_2 0x00010002 /*!< Version 1.0.2 */ -#define _STLSOFT_VER_1_1_1 0x00010101 /*!< Version 1.1.1 */ -#define _STLSOFT_VER_1_1_2 0x00010102 /*!< Version 1.1.2 */ -#define _STLSOFT_VER_1_1_3 0x00010103 /*!< Version 1.1.3 */ -#define _STLSOFT_VER_1_2_1 0x00010201 /*!< Version 1.2.1 */ -#define _STLSOFT_VER_1_3_1 0x00010301 /*!< Version 1.3.1 */ -#define _STLSOFT_VER_1_3_2 0x00010302 /*!< Version 1.3.2 */ -#define _STLSOFT_VER_1_4_1 0x00010401 /*!< Version 1.4.1 */ -#define _STLSOFT_VER_1_4_2 0x00010402 /*!< Version 1.4.2 */ -#define _STLSOFT_VER_1_4_3 0x00010403 /*!< Version 1.4.3 */ -#define _STLSOFT_VER_1_4_4 0x00010404 /*!< Version 1.4.4 */ -#define _STLSOFT_VER_1_4_5 0x00010405 /*!< Version 1.4.5 */ -#define _STLSOFT_VER_1_4_6 0x00010406 /*!< Version 1.4.6 */ -#define _STLSOFT_VER_1_5_1 0x00010501 /*!< Version 1.5.1 */ -#define _STLSOFT_VER_1_5_2 0x00010502 /*!< Version 1.5.2 */ -#define _STLSOFT_VER_1_6_1 0x00010601 /*!< Version 1.6.1 */ -#define _STLSOFT_VER_1_6_2 0x00010602 /*!< Version 1.6.2 */ -#define _STLSOFT_VER_1_6_3 0x00010603 /*!< Version 1.6.3 */ -#define _STLSOFT_VER_1_6_4 0x00010604 /*!< Version 1.6.4 */ -#define _STLSOFT_VER_1_6_5 0x00010605 /*!< Version 1.6.5 */ -#define _STLSOFT_VER_1_6_6 0x00010606 /*!< Version 1.6.6 */ - -#define _STLSOFT_VER _STLSOFT_VER_1_6_6 - -/* ///////////////////////////////////////////////////////////////////////////// - * Basic macros - */ - -/* Compilation messages - * - * To see certain informational messages during compilation define the - * preprocessor symbol _STLSOFT_COMPILE_VERBOSE - */ - -#ifndef __STLSOFT_DOCUMENTATION_SKIP_SECTION -# define STLSOFT_STRINGIZE_(x) #x -# define STLSOFT_STRINGIZE(x) STLSOFT_STRINGIZE_(x) -#endif /* !__STLSOFT_DOCUMENTATION_SKIP_SECTION */ - -/* Simple macro indirection - */ - -#define STLSOFT_MACRO_INDIRECT(x) x - -/* ///////////////////////////////////////////////////////////////////////////// - * Sanity checks - 1 - * - * C++ - must be C++ compilation unit - */ - -/* Must be C++. */ -#ifndef __cplusplus -# error The STLSoft libraries are only compatible with C++ compilation units -#endif /* __cplusplus */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Compiler compatibility - * - * Currently the only compilers supported by the STLSoft libraries are - * - * Borland C++ 5.5, 5.51 & 5.6 - * Comeau 4.3.1 - * Digital Mars C/C++ 8.26 and above - * GCC 2.95, 2.96 & 3.2 - * Intel C/C++ 6.0 & 7.0 - * Metrowerks 2.4 & 3.0 (CodeWarrior 7.0 & 8.0) - * Visual C++ 4.2, 5.0, 6.0 & .NET - * Watcom C/C++ 11.0 - * - * The following compilers are intended to be supported in a future release: - * - * Comeau C++ - */ - -#ifdef __STLSOFT_COMPILER_IS_UNKNOWN -# undef __STLSOFT_COMPILER_IS_UNKNOWN -#endif /* __STLSOFT_COMPILER_IS_UNKNOWN */ - -#ifdef __STLSOFT_COMPILER_IS_BORLAND -# undef __STLSOFT_COMPILER_IS_BORLAND -#endif /* __STLSOFT_COMPILER_IS_BORLAND */ - -#ifdef __STLSOFT_COMPILER_IS_COMO -# undef __STLSOFT_COMPILER_IS_COMO -#endif /* __STLSOFT_COMPILER_IS_COMO */ - -#ifdef __STLSOFT_COMPILER_IS_DMC -# undef __STLSOFT_COMPILER_IS_DMC -#endif /* __STLSOFT_COMPILER_IS_DMC */ - -#ifdef __STLSOFT_COMPILER_IS_GCC -# undef __STLSOFT_COMPILER_IS_GCC -#endif /* __STLSOFT_COMPILER_IS_GCC */ - -#ifdef __STLSOFT_COMPILER_IS_INTEL -# undef __STLSOFT_COMPILER_IS_INTEL -#endif /* __STLSOFT_COMPILER_IS_INTEL */ - -#ifdef __STLSOFT_COMPILER_IS_MSVC -# undef __STLSOFT_COMPILER_IS_MSVC -#endif /* __STLSOFT_COMPILER_IS_MSVC */ - -#ifdef __STLSOFT_COMPILER_IS_MWERKS -# undef __STLSOFT_COMPILER_IS_MWERKS -#endif /* __STLSOFT_COMPILER_IS_MWERKS */ - -#ifdef __STLSOFT_COMPILER_IS_VECTORC -# undef __STLSOFT_COMPILER_IS_VECTORC -#endif /* __STLSOFT_COMPILER_IS_VECTORC */ - -#ifdef __STLSOFT_COMPILER_IS_WATCOM -# undef __STLSOFT_COMPILER_IS_WATCOM -#endif /* __STLSOFT_COMPILER_IS_WATCOM */ - -/* First we do a check to see whether other compilers are providing - * compatibility with Visual C++, and handle that. - */ - -#ifdef _MSC_VER -# if defined(__BORLANDC__) || /* Borland C/C++ */ \ - defined(__COMO__) || /* Comeau C/C++ */ \ - defined(__DMC__) || /* Digital Mars C/C++ */ \ - defined(__GNUC__) || /* GNU C/C++ */ \ - defined(__INTEL_COMPILER) || /* Intel C/C++ */ \ - defined(__MWERKS__) || /* Metrowerks C/C++ */ \ - defined(__WATCOMC__) /* Watcom C/C++ */ - /* Handle Microsoft Visual C++ support. */ -# if defined(_STLSOFT_NO_MSC_VER_SUPPORT) || \ - ( defined(_STLSOFT_STRICT) && \ - !defined(_STLSOFT_MSC_VER_SUPPORT)) -# undef _MSC_VER -# endif /* _STLSOFT_NO_MSC_VER_SUPPORT || (_STLSOFT_STRICT && _STLSOFT_MSC_VER_SUPPORT) */ -# endif /* compiler */ -#endif /* _MSC_VER */ - -#if defined(_STLSOFT_FORCE_CUSTOM_COMPILER) -# define __STLSOFT_COMPILER_LABEL_STRING "Custom (forced) compiler" -# define __STLSOFT_COMPILER_VERSION_STRING "Custom (forced) compiler" -# define __STLSOFT_COMPILER_IS_CUSTOM -# ifndef __STLSOFT_CF_CUSTOM_COMPILER_INCLUDE_NAME -# error When using the custom compiler option you must define the symbol __STLSOFT_CF_CUSTOM_COMPILER_INCLUDE_NAME, e.g. #define __STLSOFT_CF_CUSTOM_COMPILER_INCLUDE_NAME -# endif /* !__STLSOFT_CF_CUSTOM_COMPILER_INCLUDE_NAME */ - -#elif defined(__COMO__) /* Do Comeau next, so that no Comeau back-end server compilers are preferentially discriminated */ -/* Comeau C++ */ -# define __STLSOFT_COMPILER_IS_COMO -# define __STLSOFT_COMPILER_LABEL_STRING "Comeau C++" -# if __COMO_VERSION__ < 4300 -# error Only versions 4.3.0.1 and later of Comeau C++ compiler is supported by the STLSoft libraries -# elif (__COMO_VERSION__ == 4300) -# define __STLSOFT_COMPILER_VERSION_STRING "Comeau C++ 4.3.0.1" -# else -# define __STLSOFT_COMPILER_VERSION_STRING "Unknown version of Comeau C++" -# endif /* __COMO_VERSION__ */ - -#elif defined(__BORLANDC__) -/* Borland C++ */ -# define __STLSOFT_COMPILER_IS_BORLAND -# define __STLSOFT_COMPILER_LABEL_STRING "Borland C/C++" -# if 0 /* (__BORLANDC__ == 0x0460) */ -# define __STLSOFT_COMPILER_VERSION_STRING "Borland C++ 4.52" -# elif (__BORLANDC__ == 0x0550) -# define __STLSOFT_COMPILER_VERSION_STRING "Borland C++ 5.5" -# elif (__BORLANDC__ == 0x0551) -# define __STLSOFT_COMPILER_VERSION_STRING "Borland C++ 5.51" -# elif (__BORLANDC__ == 0x0560) -# define __STLSOFT_COMPILER_VERSION_STRING "Borland C++ 5.6" -# elif (__BORLANDC__ == 0x0564) -# define __STLSOFT_COMPILER_VERSION_STRING "Borland C++ 5.64 (C++ BuilderX)" -# else - /*# error Currently only versions 4.52, 5.5, 5.51 and 5.6 of the Borland C++ compiler are supported by the STLSoft libraries */ -# error Currently only versions 5.5, 5.51 and 5.6 of the Borland C++ compiler are supported by the STLSoft libraries -# endif /* __BORLANDC__ */ - -#elif defined(__DMC__) -/* Digital Mars C/C++ */ -# define __STLSOFT_COMPILER_IS_DMC -# define __STLSOFT_COMPILER_LABEL_STRING "Digital Mars C/C++" -# if (__DMC__ < 0x0826) -# error Only versions 8.26 and later of the Digital Mars C/C++ compilers are supported by the STLSoft libraries -# else -# if __DMC__ >= 0x0832 -# define __STLSOFT_COMPILER_VERSION_STRING __DMC_VERSION_STRING__ -# elif (__DMC__ == 0x0826) -# define __STLSOFT_COMPILER_VERSION_STRING "Digital Mars C/C++ 8.26" -# elif (__DMC__ == 0x0827) -# define __STLSOFT_COMPILER_VERSION_STRING "Digital Mars C/C++ 8.27" -# elif (__DMC__ == 0x0828) -# define __STLSOFT_COMPILER_VERSION_STRING "Digital Mars C/C++ 8.28" -# elif (__DMC__ == 0x0829) -# define __STLSOFT_COMPILER_VERSION_STRING "Digital Mars C/C++ 8.29" -# elif (__DMC__ == 0x0830) -# define __STLSOFT_COMPILER_VERSION_STRING "Digital Mars C/C++ 8.30" -# elif (__DMC__ == 0x0831) -# define __STLSOFT_COMPILER_VERSION_STRING "Digital Mars C/C++ 8.31" -# endif /* __DMC__ */ -# endif /* version */ - -#elif defined(__GNUC__) -/* GNU C/C++ */ -# define __STLSOFT_COMPILER_IS_GCC -# define __STLSOFT_COMPILER_LABEL_STRING "GNU C/C++" -# if __GNUC__ != 2 && \ - __GNUC__ != 3 && \ - __GNUC__ != 4 -# error GNU C/C++ compilers whose major version is not 2 or 3 are not currently supported by the STLSoft libraries -# elif __GNUC__ == 2 -# if __GNUC_MINOR__ < 95 -# error Currently only version 2.95 and above of the GNU C/C++ compiler is supported by the STLSoft libraries -# elif __GNUC_MINOR__ == 95 -# define __STLSOFT_COMPILER_VERSION_STRING "GNU C/C++ 2.95" -# elif __GNUC_MINOR__ == 96 -# define __STLSOFT_COMPILER_VERSION_STRING "GNU C/C++ 2.96" -# else -# define __STLSOFT_COMPILER_VERSION_STRING "GNU C/C++ >2.96 - you should be aware that this version may not be supported correctly" -# endif /* __GNUC__ != 2 */ -# elif __GNUC__ == 3 -# if __GNUC_MINOR__ == 2 -# define __STLSOFT_COMPILER_VERSION_STRING "GNU C/C++ 3.2" -# else -# define __STLSOFT_COMPILER_VERSION_STRING "GNU C/C++ >3.2 - you should be aware that this version may not be supported correctly" -# endif /* __GNUC__ != 2 */ -# elif __GNUC__ == 4 -# define __STLSOFT_COMPILER_VERSION_STRING "GNU C/C++ >= 4.0 - you should be aware that this version may not be supported correctly" -# endif /* __GNUC__ */ - -#elif defined(__INTEL_COMPILER) -/* Intel C++ */ -# define __STLSOFT_COMPILER_IS_INTEL -# define __STLSOFT_COMPILER_LABEL_STRING "Intel C/C++" -# if (__INTEL_COMPILER == 600) -# define __STLSOFT_COMPILER_VERSION_STRING "Intel C/C++ 6.0" -# elif (__INTEL_COMPILER == 700) -# define __STLSOFT_COMPILER_VERSION_STRING "Intel C/C++ 7.0" -# else -# error Only Intel C++ Compiler versions 6.0 and 7.0 currently supported by the STLSoft libraries -# endif /* __INTEL_COMPILER */ - -#elif defined(__MWERKS__) -/* Metrowerks C++ */ -# define __STLSOFT_COMPILER_IS_MWERKS -# define __STLSOFT_COMPILER_LABEL_STRING "Metrowerks CodeWarrior C/C++" -# if ((__MWERKS__ & 0xFF00) == 0x2400) -# define __STLSOFT_COMPILER_VERSION_STRING "Metrowerks CodeWarrior C++ 2.4" -# elif ((__MWERKS__ & 0xFF00) == 0x3000) -# define __STLSOFT_COMPILER_VERSION_STRING "Metrowerks CodeWarrior C++ 3.0" -# else -# error Only Metrowerks C++ Compiler 2.4 (CodeWarrior 7) and 3.0 (CodeWarrior 8) currently supported by the STLSoft libraries -# endif /* __MWERKS__ */ - -#elif defined(__VECTORC) -/* CodePlay Vector C/C++ */ -# define __STLSOFT_COMPILER_IS_VECTORC -# define __STLSOFT_COMPILER_LABEL_STRING "CodePlay VectorC C/C++" -# if (__VECTORC == 1) -# define __STLSOFT_COMPILER_VERSION_STRING "CodePlay VectorC C/C++" -# else -# error Currently only versions of the CodePlay Vector C/C++ compiler defining __VECTORC == 1 are supported by the STLSoft libraries -# endif /* __VECTORC */ - -#elif defined(__WATCOMC__) -/* Watcom C/C++ */ -# define __STLSOFT_COMPILER_IS_WATCOM -# define __STLSOFT_COMPILER_LABEL_STRING "Watcom C/C++" - -# if (__WATCOMC__ == 1100) -# define __STLSOFT_COMPILER_VERSION_STRING "Watcom C/C++ 11.0" -# elif (__WATCOMC__ == 1200) -# define __STLSOFT_COMPILER_VERSION_STRING "Open Watcom C/C++ 1.0 (Watcom 12.0)" -# else -# error Currently only versions 11.0 and 12.0 of the Watcom C/C++ compiler is supported by the STLSoft libraries -# endif /* __WATCOMC__ */ - -#elif defined(_MSC_VER) -/* Visual C++ */ -# define __STLSOFT_COMPILER_IS_MSVC -# define __STLSOFT_COMPILER_LABEL_STRING "Visual C++" - -# if (_MSC_VER == 1020) -# define __STLSOFT_COMPILER_VERSION_STRING "Visual C++ 4.2" -# elif (_MSC_VER == 1100) -# define __STLSOFT_COMPILER_VERSION_STRING "Visual C++ 5.0" -# elif (_MSC_VER == 1200) -# define __STLSOFT_COMPILER_VERSION_STRING "Visual C++ 6.0" -# elif (_MSC_VER == 1300) -# define __STLSOFT_COMPILER_VERSION_STRING "Visual C++ .NET (7.0)" -# elif (_MSC_VER == 1310) -# define __STLSOFT_COMPILER_VERSION_STRING "Visual C++ .NET (7.1)" -# else -# error Currently only versions 4.2, 5.0, 6.0, 7.0 & 7.1 of the Visual C++ compiler are supported by the STLSoft libraries -# endif /* _MSC_VER */ - -#else -/* No recognised compiler */ -# if defined(_STLSOFT_FORCE_UNKNOWN_COMPILER) || \ - defined(_STLSOFT_FORCE_ANY_COMPILER) -# define __STLSOFT_COMPILER_LABEL_STRING "Unknown (forced) compiler" -# define __STLSOFT_COMPILER_VERSION_STRING "Unknown (forced) compiler" -# define __STLSOFT_COMPILER_IS_UNKNOWN -# else -# error Compiler is not recognised. -# error Currently only Borland C++, Comeau C++, Digital Mars C/C++, GNU C/C++, -# error Intel C/C++, Metrowerks CodeWarrior, Visual C++ and Watcom C/C++ -# error compilers are supported by the STLSoft libraries -# error If you want to use the libraries with your compiler, you may specify the -# error _STLSOFT_FORCE_CUSTOM_COMPILER or _STLSOFT_FORCE_ANY_COMPILER pre-processor -# error symbols. -# error _STLSOFT_FORCE_ANY_COMPILER assumes that your compiler can support all -# error modern C++ compiler features, and causes the inclusion of the compiler -# error features file stlsoft_cccap_unknown.h, which is provided by STLSoft. -# error _STLSOFT_FORCE_CUSTOM_COMPILER requires that you specify the name of the -# error compiler features file in __STLSOFT_CF_CUSTOM_COMPILER_INCLUDE_NAME. -# error The idea is to use _STLSOFT_FORCE_ANY_COMPILER, to determine what language -# error features your compiler can support, and then copy, edit and use that file -# error via _STLSOFT_FORCE_CUSTOM_COMPILER and __STLSOFT_CF_CUSTOM_COMPILER_INCLUDE_NAME. -# endif /* _STLSOFT_FORCE_ANY_COMPILER */ - -#endif /* compiler tag */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Compiler language feature support - * - * Various compilers support the language differently (or not at all), so these - * features are discriminated here and utilised by various means within the code - * in order to minimise the use of the preprocessor conditionals in the other - * libraries' source code. - */ - -/* Template support. - * - * Discriminated symbol is __STLSOFT_CF_TEMPLATE_SUPPORT - */ - -#ifdef __STLSOFT_CF_TEMPLATE_SUPPORT -# undef __STLSOFT_CF_TEMPLATE_SUPPORT -#endif /* __STLSOFT_CF_TEMPLATE_SUPPORT */ - -/* Exception signature support. - * - * Discriminated symbol is __STLSOFT_CF_EXCEPTION_SIGNATURE_SUPPORT - */ -#ifdef __STLSOFT_CF_EXCEPTION_SIGNATURE_SUPPORT -# undef __STLSOFT_CF_EXCEPTION_SIGNATURE_SUPPORT -#endif /* __STLSOFT_CF_EXCEPTION_SIGNATURE_SUPPORT */ - -/* Native bool support. - * - * Discriminated symbol is __STLSOFT_CF_NATIVE_BOOL_SUPPORT - */ -#ifdef __STLSOFT_CF_NATIVE_BOOL_SUPPORT -# undef __STLSOFT_CF_NATIVE_BOOL_SUPPORT -#endif /* __STLSOFT_CF_NATIVE_BOOL_SUPPORT */ - -/* Native / typedef'd wchar_t support. - * - * Discriminated symbols are __STLSOFT_CF_NATIVE_WCHAR_T_SUPPORT - * __STLSOFT_CF_TYPEDEF_WCHAR_T_SUPPORT - * - * Implementation symbol is __STLSOFT_NATIVE_WCHAR_T - */ -#ifdef __STLSOFT_CF_NATIVE_WCHAR_T_SUPPORT -# undef __STLSOFT_CF_NATIVE_WCHAR_T_SUPPORT -#endif /* __STLSOFT_CF_NATIVE_WCHAR_T_SUPPORT */ - -#ifdef __STLSOFT_CF_TYPEDEF_WCHAR_T_SUPPORT -# undef __STLSOFT_CF_TYPEDEF_WCHAR_T_SUPPORT -#endif /* __STLSOFT_CF_TYPEDEF_WCHAR_T_SUPPORT */ - -#ifdef __STLSOFT_NATIVE_WCHAR_T -# undef __STLSOFT_NATIVE_WCHAR_T -#endif /* __STLSOFT_NATIVE_WCHAR_T */ - -/* 8-bit, 16-bit, 32-bit type support - * - * Discriminated symbol is __STLSOFT_CF_NATIVE_8BIT_INT_SUPPORT, - * __STLSOFT_CF_NATIVE_16BIT_INT_SUPPORT, - * __STLSOFT_CF_NATIVE_32BIT_INT_SUPPORT - * - * Implementation symbol are __STLSOFT_NATIVE_INT8_T, - * __STLSOFT_NATIVE_SINT8_T, - * __STLSOFT_NATIVE_UINT8_T, - * __STLSOFT_NATIVE_INT16_T, - * __STLSOFT_NATIVE_SINT16_T, - * __STLSOFT_NATIVE_UINT16_T, - * __STLSOFT_NATIVE_INT32_T, - * __STLSOFT_NATIVE_SINT32_T, - * __STLSOFT_NATIVE_UINT32_T - */ - -#ifdef __STLSOFT_CF_NATIVE_8BIT_INT_SUPPORT -# undef __STLSOFT_CF_NATIVE_8BIT_INT_SUPPORT -#endif /* __STLSOFT_CF_NATIVE_8BIT_INT_SUPPORT */ - -#ifdef __STLSOFT_CF_NATIVE_16BIT_INT_SUPPORT -# undef __STLSOFT_CF_NATIVE_16BIT_INT_SUPPORT -#endif /* __STLSOFT_CF_NATIVE_16BIT_INT_SUPPORT */ - -#ifdef __STLSOFT_CF_NATIVE_32BIT_INT_SUPPORT -# undef __STLSOFT_CF_NATIVE_32BIT_INT_SUPPORT -#endif /* __STLSOFT_CF_NATIVE_32BIT_INT_SUPPORT */ - -#ifdef __STLSOFT_NATIVE_INT8_T -# undef __STLSOFT_NATIVE_INT8_T -#endif /* __STLSOFT_NATIVE_INT8_T */ -#ifdef __STLSOFT_NATIVE_SINT8_T -# undef __STLSOFT_NATIVE_SINT8_T -#endif /* __STLSOFT_NATIVE_SINT8_T */ -#ifdef __STLSOFT_NATIVE_UINT8_T -# undef __STLSOFT_NATIVE_UINT8_T -#endif /* __STLSOFT_NATIVE_UINT8_T */ - -#ifdef __STLSOFT_NATIVE_INT16_T -# undef __STLSOFT_NATIVE_INT16_T -#endif /* __STLSOFT_NATIVE_INT16_T */ -#ifdef __STLSOFT_NATIVE_SINT16_T -# undef __STLSOFT_NATIVE_SINT16_T -#endif /* __STLSOFT_NATIVE_SINT16_T */ -#ifdef __STLSOFT_NATIVE_UINT16_T -# undef __STLSOFT_NATIVE_UINT16_T -#endif /* __STLSOFT_NATIVE_UINT16_T */ - -#ifdef __STLSOFT_NATIVE_INT32_T -# undef __STLSOFT_NATIVE_INT32_T -#endif /* __STLSOFT_NATIVE_INT32_T */ -#ifdef __STLSOFT_NATIVE_SINT32_T -# undef __STLSOFT_NATIVE_SINT32_T -#endif /* __STLSOFT_NATIVE_SINT32_T */ -#ifdef __STLSOFT_NATIVE_UINT32_T -# undef __STLSOFT_NATIVE_UINT32_T -#endif /* __STLSOFT_NATIVE_UINT32_T */ - -/* 64-bit support. - * - * Discriminated symbols are __STLSOFT_CF_NATIVE___int64_SUPPORT, - * __STLSOFT_CF_NATIVE_LONG_LONG_SUPPORT and - * __STLSOFT_CF_NATIVE_64BIT_INTEGER_SUPPORT. - * - * 64-bit support is discriminated in the following two forms: - * - * (i) long long - * (ii) __int64 - * - * Form (i) support is selectively preferred. Form (ii) support - * is only discriminated in the absence of form (i). - */ - -#ifdef __STLSOFT_CF_NATIVE_64BIT_INTEGER_SUPPORT -# undef __STLSOFT_CF_NATIVE_64BIT_INTEGER_SUPPORT -#endif /* __STLSOFT_CF_NATIVE_64BIT_INTEGER_SUPPORT */ - -#ifdef __STLSOFT_CF_NATIVE_LONG_LONG_SUPPORT -# undef __STLSOFT_CF_NATIVE_LONG_LONG_SUPPORT -#endif /* __STLSOFT_CF_NATIVE_LONG_LONG_SUPPORT */ - -#ifdef __STLSOFT_CF_NATIVE___int64_SUPPORT -# undef __STLSOFT_CF_NATIVE___int64_SUPPORT -#endif /* __STLSOFT_CF_NATIVE___int64_SUPPORT */ - -#ifdef __STLSOFT_CF_INT_DISTINCT_TYPE -# undef __STLSOFT_CF_INT_DISTINCT_TYPE -#endif /* __STLSOFT_CF_INT_DISTINCT_TYPE */ - -/* Compiler supports static assert. - * - * Discriminated symbol is __STLSOFT_CF_STATIC_ASSERT_SUPPORT - */ -#ifdef __STLSOFT_CF_STATIC_ASSERT_SUPPORT -# undef __STLSOFT_CF_STATIC_ASSERT_SUPPORT -#endif /* __STLSOFT_CF_STATIC_ASSERT_SUPPORT */ - -/* Function signature requires full-qualification. - * - * Discriminated symbol is __STLSOFT_CF_FUNCTION_SIGNATURE_FULL_ARG_QUALIFICATION_REQUIRED - */ -#ifdef __STLSOFT_CF_FUNCTION_SIGNATURE_FULL_ARG_QUALIFICATION_REQUIRED -# undef __STLSOFT_CF_FUNCTION_SIGNATURE_FULL_ARG_QUALIFICATION_REQUIRED -#endif /* __STLSOFT_CF_FUNCTION_SIGNATURE_FULL_ARG_QUALIFICATION_REQUIRED */ - -/* Exception support. - * - * Discriminated symbol is __STLSOFT_CF_EXCEPTION_SUPPORT - */ -#ifdef __STLSOFT_CF_EXCEPTION_SUPPORT -# undef __STLSOFT_CF_EXCEPTION_SUPPORT -#endif /* __STLSOFT_CF_EXCEPTION_SUPPORT */ - -/* Template class default fundamental type argument support - * - * Discriminated symbol is __STLSOFT_CF_TEMPLATE_CLASS_DEFAULT_FUNDAMENTAL_ARGUMENT_SUPPORT - * - * Microsoft Visual C++ 4.2 does not support template default fundamental type arguments. - */ -#ifdef __STLSOFT_CF_TEMPLATE_CLASS_DEFAULT_FUNDAMENTAL_ARGUMENT_SUPPORT -# undef __STLSOFT_CF_TEMPLATE_CLASS_DEFAULT_FUNDAMENTAL_ARGUMENT_SUPPORT -#endif /* __STLSOFT_CF_TEMPLATE_CLASS_DEFAULT_FUNDAMENTAL_ARGUMENT_SUPPORT */ - -/* Template class default class type argument support - * - * Discriminated symbol is __STLSOFT_CF_TEMPLATE_CLASS_DEFAULT_CLASS_ARGUMENT_SUPPORT - * - * Microsoft Visual C++ 4.2 does not support template default class type arguments. - */ -#ifdef __STLSOFT_CF_TEMPLATE_CLASS_DEFAULT_CLASS_ARGUMENT_SUPPORT -# undef __STLSOFT_CF_TEMPLATE_CLASS_DEFAULT_CLASS_ARGUMENT_SUPPORT -#endif /* __STLSOFT_CF_TEMPLATE_CLASS_DEFAULT_CLASS_ARGUMENT_SUPPORT */ - -/* Member functions can appear as template parameters - * - * Discriminated symbol is STLSOFT_CF_MEM_FUNC_AS_TEMPLATE_PARAM_SUPPORT - */ -#ifdef STLSOFT_CF_MEM_FUNC_AS_TEMPLATE_PARAM_SUPPORT -# undef STLSOFT_CF_MEM_FUNC_AS_TEMPLATE_PARAM_SUPPORT -#endif /* STLSOFT_CF_MEM_FUNC_AS_TEMPLATE_PARAM_SUPPORT */ - -/* Member template function support. - * - * Discriminated symbol is __STLSOFT_CF_MEMBER_TEMPLATE_FUNCTION_SUPPORT - */ -#ifdef __STLSOFT_CF_MEMBER_TEMPLATE_FUNCTION_SUPPORT -# undef __STLSOFT_CF_MEMBER_TEMPLATE_FUNCTION_SUPPORT -#endif // __STLSOFT_CF_MEMBER_TEMPLATE_FUNCTION_SUPPORT - -/* Member template constructor support. - * - * Discriminated symbol is __STLSOFT_CF_MEMBER_TEMPLATE_CTOR_SUPPORT - */ -#ifdef __STLSOFT_CF_MEMBER_TEMPLATE_CTOR_SUPPORT -# undef __STLSOFT_CF_MEMBER_TEMPLATE_CTOR_SUPPORT -#endif // __STLSOFT_CF_MEMBER_TEMPLATE_CTOR_SUPPORT - -/* Member template range method support. - * - * Discriminated symbol is __STLSOFT_CF_MEMBER_TEMPLATE_RANGE_METHOD_SUPPORT - */ -#ifdef __STLSOFT_CF_MEMBER_TEMPLATE_RANGE_METHOD_SUPPORT -# undef __STLSOFT_CF_MEMBER_TEMPLATE_RANGE_METHOD_SUPPORT -#endif // __STLSOFT_CF_MEMBER_TEMPLATE_RANGE_METHOD_SUPPORT - -/* Member template class support. - * - * Discriminated symbol is __STLSOFT_CF_MEMBER_TEMPLATE_CLASS_SUPPORT - */ -#ifdef __STLSOFT_CF_MEMBER_TEMPLATE_CLASS_SUPPORT -# undef __STLSOFT_CF_MEMBER_TEMPLATE_CLASS_SUPPORT -#endif // __STLSOFT_CF_MEMBER_TEMPLATE_CLASS_SUPPORT - -/* Template specialisation syntax support - * - * Discriminated symbol is __STLSOFT_CF_TEMPLATE_SPECIALISATION_SYNTAX - */ -#ifdef __STLSOFT_CF_TEMPLATE_SPECIALISATION_SYNTAX -# undef __STLSOFT_CF_TEMPLATE_SPECIALISATION_SYNTAX -#endif /* __STLSOFT_CF_TEMPLATE_SPECIALISATION_SYNTAX */ - -/* Template partial specialisation support. - * - * Discriminated symbol is __STLSOFT_CF_TEMPLATE_PARTIAL_SPECIALISATION_SUPPORT - */ -#ifdef __STLSOFT_CF_TEMPLATE_PARTIAL_SPECIALISATION_SUPPORT -# undef __STLSOFT_CF_TEMPLATE_PARTIAL_SPECIALISATION_SUPPORT -#endif // __STLSOFT_CF_TEMPLATE_PARTIAL_SPECIALISATION_SUPPORT - -/* Template out-of-class function specialisation support. - * - * Discriminated symbol is __STLSOFT_CF_TEMPLATE_OUTOFCLASSFN_QUALIFIED_TYPE_SUPPORT - */ -#ifdef __STLSOFT_CF_TEMPLATE_OUTOFCLASSFN_QUALIFIED_TYPE_SUPPORT -# undef __STLSOFT_CF_TEMPLATE_OUTOFCLASSFN_QUALIFIED_TYPE_SUPPORT -#endif /* __STLSOFT_CF_TEMPLATE_OUTOFCLASSFN_QUALIFIED_TYPE_SUPPORT */ - -/* Standard library STL elements in std namespace. - * - * Discriminated symbol is __STLSOFT_CF_std_NAMESPACE - */ -#ifdef __STLSOFT_CF_std_NAMESPACE -# undef __STLSOFT_CF_std_NAMESPACE -#endif /* __STLSOFT_CF_std_NAMESPACE */ - -/* std::char_traits available. - * - * Discriminated symbol is __STLSOFT_CF_std_char_traits_AVAILABLE - */ -#ifdef __STLSOFT_CF_std_char_traits_AVAILABLE -# undef __STLSOFT_CF_std_char_traits_AVAILABLE -#endif /* __STLSOFT_CF_std_char_traits_AVAILABLE */ - -/* stl-like allocator classes provide allocate() hint argument - * - * Discriminated symbol is __STLSOFT_CF_ALLOCATOR_ALLOCATE_HAS_HINT - * - * Note: this should be resolving on the library, not the compiler - */ -#ifdef __STLSOFT_CF_ALLOCATOR_ALLOCATE_HAS_HINT -# undef __STLSOFT_CF_ALLOCATOR_ALLOCATE_HAS_HINT -#endif /* __STLSOFT_CF_ALLOCATOR_ALLOCATE_HAS_HINT */ - -/* stl-like allocator classes provide deallocate() object count argument - * - * Discriminated symbol is __STLSOFT_CF_ALLOCATOR_DEALLOCATE_HAS_OBJECTCOUNT - * - * Note: this should be resolving on the library, not the compiler - */ -#ifdef __STLSOFT_CF_ALLOCATOR_DEALLOCATE_HAS_OBJECTCOUNT -# undef __STLSOFT_CF_ALLOCATOR_DEALLOCATE_HAS_OBJECTCOUNT -#endif /* __STLSOFT_CF_ALLOCATOR_DEALLOCATE_HAS_OBJECTCOUNT */ - -/* Bidirectional iterator support - */ -#ifdef __STLSOFT_CF_BIDIRECTIONAL_ITERATOR_SUPPORT -# undef __STLSOFT_CF_BIDIRECTIONAL_ITERATOR_SUPPORT -#endif /* __STLSOFT_CF_BIDIRECTIONAL_ITERATOR_SUPPORT */ - -/* explicit keyword support - * - * Discriminated symbol is __STLSOFT_CF_EXPLICIT_KEYWORD_SUPPORT - */ -#ifdef __STLSOFT_CF_EXPLICIT_KEYWORD_SUPPORT -# undef __STLSOFT_CF_EXPLICIT_KEYWORD_SUPPORT -#endif /* __STLSOFT_CF_EXPLICIT_KEYWORD_SUPPORT */ - -/* mutable keyword support - * - * Discriminated symbol is __STLSOFT_CF_MUTABLE_KEYWORD_SUPPORT - */ -#ifdef __STLSOFT_CF_MUTABLE_KEYWORD_SUPPORT -# undef __STLSOFT_CF_MUTABLE_KEYWORD_SUPPORT -#endif /* __STLSOFT_CF_MUTABLE_KEYWORD_SUPPORT */ - -/* typename keyword support - * - * Discriminated symbols are __STLSOFT_CF_TYPENAME_PARAM_KEYWORD_SUPPORT, - * __STLSOFT_CF_TYPENAME_TYPE_KEYWORD_SUPPORT, - * __STLSOFT_CF_TYPENAME_TYPE_DEF_KEYWORD_SUPPORT and - * __STLSOFT_CF_TYPENAME_TYPE_MIL_KEYWORD_SUPPORT - * - * The typename keyword is actually used for two distinct purposes: the - * generic type placeholder in template parameter specifications, and the - * stipulation to compilers that a particular template derived construct - * is a type, rather than a member or operation. - * - * These two uses have varying support on different compilers, hence the - * STLSoft libraries utilise the ss_typename_param_k pseudo keyword for the - * first purpose, and the ss_typename_type_k pseudo keyword for the second. - * - * In addition, some compilers cannot handle the use of typename as a type - * qualifier in a template default parameter, so we further define the keyword - * ss_typename_type_def_k. And some cannot handle it in a constructor - * initialiser list, for which ss_typename_type_mil_k is defined. - */ -#ifdef __STLSOFT_CF_TYPENAME_PARAM_KEYWORD_SUPPORT -# undef __STLSOFT_CF_TYPENAME_PARAM_KEYWORD_SUPPORT -#endif /* __STLSOFT_CF_TYPENAME_PARAM_KEYWORD_SUPPORT */ - -#ifdef __STLSOFT_CF_TYPENAME_TYPE_KEYWORD_SUPPORT -# undef __STLSOFT_CF_TYPENAME_TYPE_KEYWORD_SUPPORT -#endif /* __STLSOFT_CF_TYPENAME_TYPE_KEYWORD_SUPPORT */ - -#ifdef __STLSOFT_CF_TYPENAME_TYPE_DEF_KEYWORD_SUPPORT -# undef __STLSOFT_CF_TYPENAME_TYPE_DEF_KEYWORD_SUPPORT -#endif /* __STLSOFT_CF_TYPENAME_TYPE_DEF_KEYWORD_SUPPORT */ - -#ifdef __STLSOFT_CF_TYPENAME_TYPE_MIL_KEYWORD_SUPPORT -# undef __STLSOFT_CF_TYPENAME_TYPE_MIL_KEYWORD_SUPPORT -#endif /* __STLSOFT_CF_TYPENAME_TYPE_MIL_KEYWORD_SUPPORT */ - -/* Move constructor support - * - * Discriminated symbol is __STLSOFT_CF_MOVE_CONSTRUCTOR_SUPPORT - */ -#ifdef __STLSOFT_CF_MOVE_CONSTRUCTOR_SUPPORT -# undef __STLSOFT_CF_MOVE_CONSTRUCTOR_SUPPORT -#endif /* __STLSOFT_CF_MOVE_CONSTRUCTOR_SUPPORT */ - -/* Koening Lookup support - * - * Discriminated symbol is __STLSOFT_CF_KOENIG_LOOKUP_SUPPORT - */ -#ifdef __STLSOFT_CF_KOENIG_LOOKUP_SUPPORT -# undef __STLSOFT_CF_KOENIG_LOOKUP_SUPPORT -#endif /* __STLSOFT_CF_KOENIG_LOOKUP_SUPPORT */ - -/* Template template support - * - * Discriminated symbol is __STLSOFT_CF_TEMPLATE_TEMPLATE_SUPPORT - */ -#ifdef __STLSOFT_CF_TEMPLATE_TEMPLATE_SUPPORT -# undef __STLSOFT_CF_TEMPLATE_TEMPLATE_SUPPORT -#endif /* __STLSOFT_CF_TEMPLATE_TEMPLATE_SUPPORT */ - - -#ifdef __STLSOFT_CF_STATIC_ARRAY_SIZE_DETERMINATION_SUPPORT -# undef __STLSOFT_CF_STATIC_ARRAY_SIZE_DETERMINATION_SUPPORT -#endif /* __STLSOFT_CF_STATIC_ARRAY_SIZE_DETERMINATION_SUPPORT */ - -#ifdef __STLSOFT_CF_VENEER_SUPPORT -# undef __STLSOFT_CF_VENEER_SUPPORT -#endif /* __STLSOFT_CF_VENEER_SUPPORT */ - -#ifdef __STLSOFT_CF_TEMPLATE_SHIMS_NOT_SUPPORTED -# undef __STLSOFT_CF_TEMPLATE_SHIMS_NOT_SUPPORTED -#endif /* __STLSOFT_CF_TEMPLATE_SHIMS_NOT_SUPPORTED */ - -#ifdef __STLSOFT_CF_NEGATIVE_MODULUS_POSITIVE_GIVES_NEGATIVE_RESULT -# undef __STLSOFT_CF_NEGATIVE_MODULUS_POSITIVE_GIVES_NEGATIVE_RESULT -#endif /* __STLSOFT_CF_NEGATIVE_MODULUS_POSITIVE_GIVES_NEGATIVE_RESULT */ - -#ifdef STLSOFT_CF_OPERATOR_BOOL_AS_OPERATOR_POINTER_TO_MEMBER_SUPPORT -# undef STLSOFT_CF_OPERATOR_BOOL_AS_OPERATOR_POINTER_TO_MEMBER_SUPPORT -#endif /* STLSOFT_CF_OPERATOR_BOOL_AS_OPERATOR_POINTER_TO_MEMBER_SUPPORT */ - -#ifdef STLSOFT_CF_OPERATOR_NOT_VIA_OPERATOR_POINTER_TO_MEMBER_SUPPORT -# undef STLSOFT_CF_OPERATOR_NOT_VIA_OPERATOR_POINTER_TO_MEMBER_SUPPORT -#endif /* STLSOFT_CF_OPERATOR_NOT_VIA_OPERATOR_POINTER_TO_MEMBER_SUPPORT */ - -#ifdef STLSOFT_CF_FASTCALL_SUPPORTED -# undef STLSOFT_CF_FASTCALL_SUPPORTED -#endif /* STLSOFT_CF_FASTCALL_SUPPORTED */ - -#ifdef STLSOFT_CF_STDCALL_SUPPORTED -# undef STLSOFT_CF_STDCALL_SUPPORTED -#endif /* STLSOFT_CF_STDCALL_SUPPORTED */ - -#ifdef STSLSOFT_INLINE_ASM_SUPPORTED -# undef STSLSOFT_INLINE_ASM_SUPPORTED -#endif /* STSLSOFT_INLINE_ASM_SUPPORTED */ - -#ifdef STSLSOFT_ASM_IN_INLINE_SUPPORTED -# undef STSLSOFT_ASM_IN_INLINE_SUPPORTED -#endif /* STSLSOFT_ASM_IN_INLINE_SUPPORTED */ - -/* Now we include the appropriate compiler-specific header */ - -#if defined(__STLSOFT_COMPILER_IS_CUSTOM) -# include __STLSOFT_CF_CUSTOM_COMPILER_INCLUDE_NAME -#elif defined(__STLSOFT_COMPILER_IS_UNKNOWN) -# include "stlsoft_cccap_unknown.h" -#elif defined(__STLSOFT_COMPILER_IS_BORLAND) -# include "stlsoft_cccap_borland.h" -#elif defined(__STLSOFT_COMPILER_IS_COMO) -# include "stlsoft_cccap_como.h" -#elif defined(__STLSOFT_COMPILER_IS_DMC) -# include "stlsoft_cccap_dmc.h" -#elif defined(__STLSOFT_COMPILER_IS_GCC) -# include "stlsoft_cccap_gcc.h" -#elif defined(__STLSOFT_COMPILER_IS_INTEL) -# include "stlsoft_cccap_intel.h" -#elif defined(__STLSOFT_COMPILER_IS_MSVC) -# include "stlsoft_cccap_msvc.h" -#elif defined(__STLSOFT_COMPILER_IS_MWERKS) -# include "stlsoft_cccap_mwerks.h" -#elif defined(__STLSOFT_COMPILER_IS_VECTORC) -# include "stlsoft_cccap_vectorc.h" -#elif defined(__STLSOFT_COMPILER_IS_WATCOM) -# include "stlsoft_cccap_watcom.h" -#else -# error Compiler not correctly discriminated -#endif /* compiler */ - -#if defined(_STLSOFT_COMPILE_VERBOSE) && \ - !defined(STLSOFT_CF_PRAGMA_MESSAGE_SUPPORT) -# undef _STLSOFT_COMPILE_VERBOSE -# endif /* !STLSOFT_CF_PRAGMA_MESSAGE_SUPPORT && _STLSOFT_COMPILE_VERBOSE */ - -# ifdef _STLSOFT_COMPILE_VERBOSE -# pragma message(__STLSOFT_COMPILER_VERSION_STRING) -# endif /* STLSOFT_CF_PRAGMA_MESSAGE_SUPPORT && _STLSOFT_COMPILE_VERBOSE */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Sanity checks - 2 - * - * MBCS - none of the libraries code is written to support MBCS - */ - -/* Should not be MBCS. - * - * Only ANSI and Unicode character encoding schemese are explicitly supported. - */ -#ifdef _MBCS -# ifdef _STLSOFT_STRICT -# error The STLSoft libraries are not compatible with variable length character representation schemes such as MBCS -# else -# ifdef _STLSOFT_COMPILE_VERBOSE -# pragma message("The STLSoft libraries are not compatible with variable length character representation schemes such as MBCS") -# endif /* _STLSOFT_COMPILE_VERBOSE */ -# endif /* _STLSOFT_STRICT */ -#endif /* _MBCS */ - - - - - -/* Template support */ -#ifndef __STLSOFT_CF_TEMPLATE_SUPPORT -# error Template support not detected. STLSoft libraries are template-based and require this support. -#endif /* __STLSOFT_CF_TEMPLATE_SUPPORT */ - - -/* Native 64-bit integer support */ -#if defined(__STLSOFT_CF_NATIVE___int64_SUPPORT) || \ - defined(__STLSOFT_CF_NATIVE_LONG_LONG_SUPPORT) -# define __STLSOFT_CF_NATIVE_64BIT_INTEGER_SUPPORT -#endif /* __STLSOFT_CF_NATIVE___int64_SUPPORT || __STLSOFT_CF_NATIVE_LONG_LONG_SUPPORT */ - -/* Out-of-class method definition argument full-qualification requirement */ -#ifdef __STLSOFT_CF_FUNCTION_SIGNATURE_FULL_ARG_QUALIFICATION_REQUIRED -# define _stlsoft_qualify_fn_arg(Q, T) Q::T -#else -# define _stlsoft_qualify_fn_arg(Q, T) T -#endif /* __STLSOFT_CF_FUNCTION_SIGNATURE_FULL_ARG_QUALIFICATION_REQUIRED */ - -/* Out-of-memory throws bad_alloc. - * - * Discriminated symbol is __STLSOFT_CF_NOTHROW_BAD_ALLOC - * - * By default, compilations with the Borland, and Watcom compilers throw - * bad_alloc in conditions of memory exhaustion, and those with Digital Mars - * and Microsoft do not. - * - * The Microsoft compilers do not throw bad_alloc for long established reasons, - * though they can be made to do so (see Matthew Wilson, "Generating - * Out-Of-Memory Exceptions", Windows Developer's Journal, Vol 12 Number 5, May - * 2001). This feature may be added in a forthcoming release of the libraries. - * - * The Digital Mars compiler appears to ship without any header files that - * define bad_alloc (whether in std or not), so it is therefore assumed that - * operator new will not throw exceptions in out of memory conditions. - * - * Define __STLSOFT_CF_THROW_BAD_ALLOC to force Microsoft to do so. - * Define __STLSOFT_CF_NO_THROW_BAD_ALLOC to prevent Borland/Comeau/Digital Mars/ - * GCC/Metrowerks/Watcom from doing so. - */ - -#ifndef __STLSOFT_CF_EXCEPTION_SUPPORT -# define __STLSOFT_CF_NOTHROW_BAD_ALLOC -#endif /* !__STLSOFT_CF_EXCEPTION_SUPPORT */ - -#ifdef __STLSOFT_CF_NOTHROW_BAD_ALLOC -# ifdef __STLSOFT_CF_THROW_BAD_ALLOC -# undef __STLSOFT_CF_THROW_BAD_ALLOC -# endif /* __STLSOFT_CF_THROW_BAD_ALLOC */ -#else - /* Leave it to whatever the compiler's capability discrimination has determined */ -#endif /* __STLSOFT_CF_NOTHROW_BAD_ALLOC */ - - -/* Template specialisation syntax support - */ -#ifdef __STLSOFT_TEMPLATE_SPECIALISATION -# undef __STLSOFT_TEMPLATE_SPECIALISATION -#endif /* __STLSOFT_TEMPLATE_SPECIALISATION */ - -#ifdef __STLSOFT_CF_TEMPLATE_SPECIALISATION_SYNTAX -# define STLSOFT_TEMPLATE_SPECIALISATION template <> -#else -# define STLSOFT_TEMPLATE_SPECIALISATION -#endif /* __STLSOFT_CF_TEMPLATE_SPECIALISATION_SYNTAX */ - - -/* Keyword support. - * - * Define _STLSOFT_FORCE_ALL_KEYWORDS to force the assumption of compiler - * support for all keywords. - * - * Define _STLSOFT_FORCE_KEYWORD_EXPLICIT to force the assumption of compiler - * support for the explicit keyword - * - * Define _STLSOFT_FORCE_KEYWORD_MUTABLE to force the assumption of compiler - * support for the mutable keyword - * - * Define _STLSOFT_FORCE_KEYWORD_TYPENAME to force the assumption of compiler - * support for the typename keyword - */ - -#ifdef _STLSOFT_FORCE_ALL_KEYWORDS -# define _STLSOFT_FORCE_KEYWORD_EXPLICIT -# define _STLSOFT_FORCE_KEYWORD_MUTABLE -# define _STLSOFT_FORCE_KEYWORD_TYPENAME -#endif /* _STLSOFT_FORCE_ALL_KEYWORDS */ - -#if !defined(__STLSOFT_CF_EXPLICIT_KEYWORD_SUPPORT) && \ - defined(_STLSOFT_FORCE_KEYWORD_EXPLICIT) -# define __STLSOFT_CF_EXPLICIT_KEYWORD_SUPPORT -#endif /* !__STLSOFT_CF_EXPLICIT_KEYWORD_SUPPORT && _STLSOFT_FORCE_KEYWORD_EXPLICIT */ - -#if !defined(__STLSOFT_CF_MUTABLE_KEYWORD_SUPPORT) && \ - defined(_STLSOFT_FORCE_KEYWORD_MUTABLE) -# define __STLSOFT_CF_MUTABLE_KEYWORD_SUPPORT -#endif /* !__STLSOFT_CF_MUTABLE_KEYWORD_SUPPORT && _STLSOFT_FORCE_KEYWORD_MUTABLE */ - -#if !defined(__STLSOFT_CF_TYPENAME_PARAM_KEYWORD_SUPPORT) && \ - defined(_STLSOFT_FORCE_KEYWORD_TYPENAME) -# define __STLSOFT_CF_TYPENAME_PARAM_KEYWORD_SUPPORT -#endif /* !__STLSOFT_CF_TYPENAME_PARAM_KEYWORD_SUPPORT && _STLSOFT_FORCE_KEYWORD_TYPENAME */ - -#if !defined(__STLSOFT_CF_TYPENAME_TYPE_KEYWORD_SUPPORT) && \ - defined(_STLSOFT_FORCE_KEYWORD_TYPENAME) -# define __STLSOFT_CF_TYPENAME_TYPE_KEYWORD_SUPPORT -#endif /* !__STLSOFT_CF_TYPENAME_TYPE_KEYWORD_SUPPORT && _STLSOFT_FORCE_KEYWORD_TYPENAME */ - -#if !defined(__STLSOFT_CF_TYPENAME_TYPE_DEF_KEYWORD_SUPPORT) && \ - defined(_STLSOFT_FORCE_KEYWORD_TYPENAME) -# define __STLSOFT_CF_TYPENAME_TYPE_DEF_KEYWORD_SUPPORT -#endif /* !__STLSOFT_CF_TYPENAME_TYPE_DEF_KEYWORD_SUPPORT && _STLSOFT_FORCE_KEYWORD_TYPENAME */ - -#if !defined(__STLSOFT_CF_TYPENAME_TYPE_MIL_KEYWORD_SUPPORT) && \ - defined(_STLSOFT_FORCE_KEYWORD_TYPENAME) -# define __STLSOFT_CF_TYPENAME_TYPE_MIL_KEYWORD_SUPPORT -#endif /* !__STLSOFT_CF_TYPENAME_TYPE_MIL_KEYWORD_SUPPORT && _STLSOFT_FORCE_KEYWORD_TYPENAME */ - -/* ///////////////////////////////////////////////////////////////////////////// - * operator bool() - * - * If the symbol STLSOFT_CF_OPERATOR_BOOL_AS_OPERATOR_POINTER_TO_MEMBER_SUPPORT - * is defined, operator bool should be defined as follows: - * - * class X - * { - * private: - * struct boolean { int i; } - * typedef int boolean::*boolean_t; - * public: - * operator boolean_t () const; - * - * otherwise it should be - * - * class X - * { - * private: - * typedef ss_bool_t boolean_t; - * public: - * operator boolean_t () const; - * - * - * If the symbol STLSOFT_CF_OPERATOR_NOT_VIA_OPERATOR_POINTER_TO_MEMBER_SUPPORT - * is defined, it means that (!x) can de deduced by the compiler, otherwise it - * will need to be provided - * - * If STLSOFT_CF_OPERATOR_BOOL_AS_OPERATOR_POINTER_TO_MEMBER_SUPPORT is not defined - * then STLSOFT_CF_OPERATOR_NOT_VIA_OPERATOR_POINTER_TO_MEMBER_SUPPORT should not be - * defined, so we do a check here. - * - */ - -#if !defined(STLSOFT_CF_OPERATOR_BOOL_AS_OPERATOR_POINTER_TO_MEMBER_SUPPORT) && \ - defined(STLSOFT_CF_OPERATOR_NOT_VIA_OPERATOR_POINTER_TO_MEMBER_SUPPORT) -# error Cannot rely on use of boolean as pointer to member for operator ! -# error Undefine STLSOFT_CF_OPERATOR_NOT_VIA_OPERATOR_POINTER_TO_MEMBER_SUPPORT when -# error STLSOFT_CF_OPERATOR_BOOL_AS_OPERATOR_POINTER_TO_MEMBER_SUPPORT is not defined -#endif /* !STLSOFT_CF_OPERATOR_BOOL_AS_OPERATOR_POINTER_TO_MEMBER_SUPPORT && STLSOFT_CF_OPERATOR_NOT_VIA_OPERATOR_POINTER_TO_MEMBER_SUPPORT */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Obsolete symbol definitions - * - * Define _STLSOFT_INCLUDE_OBSOLETE to include the definitions of symbols prior - * to version 1.5.1 - */ - -/* Verify that the significant changes to STLSoft 1.5.1 are checked with respect - * to other previously released projects - */ - -#if ( defined(_ATLSTL_VER) && \ - _ATLSTL_VER <= 0x00010204) || \ - ( defined(_COMSTL_VER) && \ - _COMSTL_VER <= 0x00010201) || \ - ( defined(_MFCSTL_VER) && \ - _MFCSTL_VER <= 0x00010202) || \ - ( defined(_UNIXSTL_VER) && \ - _UNIXSTL_VER <= 0x00000901) || \ - ( defined(_WINSTL_VER) && \ - _WINSTL_VER <= 0x00010201) -# ifdef _STLSOFT_STRICT -# error You are using an old version of one or more of ATLSTL, COMSTL, MFCSTL, UNIXSTL and WinSTL. Please upgrade all dependent projects in line with the STLSoft version you are using -# else -# ifdef _STLSOFT_COMPILE_VERBOSE -# pragma message("You are using an old version of one or more of ATLSTL, COMSTL, MFCSTL, UNIXSTL and WinSTL. _STLSOFT_INCLUDE_OBSOLETE will be defined (but is not guaranteed to work!)") -# endif /* _STLSOFT_COMPILE_VERBOSE */ -# ifndef _STLSOFT_INCLUDE_OBSOLETE -# define _STLSOFT_INCLUDE_OBSOLETE -# endif /* !_STLSOFT_INCLUDE_OBSOLETE */ -# endif /* _STLSOFT_STRICT */ -#endif /* sub-project versions */ - -#ifdef _STLSOFT_INCLUDE_OBSOLETE -# include "stlsoft_cc_obsolete.h" -#endif /* _STLSOFT_INCLUDE_OBSOLETE */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Includes - */ - -#ifndef _STLSOFT_NO_STD_INCLUDES -# include // standard types -# include // standard constants -#endif /* !_STLSOFT_NO_STD_INCLUDES */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Debugging - * - * The macro stlsoft_assert provides standard debug-mode assert functionality. - */ - -#if defined(_STLSOFT_NO_ASSERT) && \ - defined(__STLSOFT_CF_ASSERT_SUPPORT) -# undef __STLSOFT_CF_ASSERT_SUPPORT -#endif /* _STLSOFT_NO_ASSERT && __STLSOFT_CF_ASSERT_SUPPORT */ - -/// \def stlsoft_assert Defines a runtime assertion -/// -/// \param ex Must be non-zero, or an assertion will be fired -#ifdef __STLSOFT_CF_ASSERT_SUPPORT -# ifdef __STLSOFT_CF_USE_cassert - /* Using the standard assertion mechanism, located in */ -# include -# define stlsoft_assert(ex) assert(ex) -# else - /* Using either a custom or proprietary assertion mechanism, so must - * provide the header include name - */ -# ifndef __STLSOFT_CF_ASSERT_INCLUDE_NAME -# error Must supply an assert include filename with custom or proprietary assertion mechanism -# else -# include __STLSOFT_CF_ASSERT_INCLUDE_NAME -# endif /* !__STLSOFT_CF_ASSERT_INCLUDE_NAME */ -# endif /* __STLSOFT_CF_USE_cassert */ -# ifndef stlsoft_assert -# error If your compiler discrimination file supports assertions, it must defined stlsoft_assert() (taking a single parameter) -# endif /* !stlsoft_assert */ -#endif /* !__STLSOFT_CF_ASSERT_SUPPORT */ - -/// \def stlsoft_message_assert Defines a runtime assertion, with message -/// -/// \param ex Must be non-zero, or an assertion will be fired -/// \param _m The literal character string message to be included in the assertion -#if defined(__STLSOFT_CF_ASSERT_SUPPORT) -# if defined(__WATCOMC__) -# define stlsoft_message_assert(_m, ex) stlsoft_assert(ex) -# else -# define stlsoft_message_assert(_m, ex) stlsoft_assert((_m, ex)) -# endif /* __WATCOMC__ */ -#else -# define stlsoft_message_assert(_m, ex) -#endif /* __STLSOFT_CF_ASSERT_SUPPORT */ - -/// \def stlsoft_static_assert Defines a compile-time assertion -/// -/// \param ex Must be non-zero, or compilation will fail -#if defined(__STLSOFT_CF_STATIC_ASSERT_SUPPORT) -# if defined(__STLSOFT_COMPILER_IS_GCC) -# define stlsoft_static_assert(ex) do { typedef int ai[(ex) ? 1 : -1]; } while(0) -# else -# define stlsoft_static_assert(ex) do { typedef int ai[(ex) ? 1 : 0]; } while(0) -# endif /* compiler */ -#else -# define stlsoft_static_assert(ex) stlsoft_message_assert("Static assertion failed: ", (ex)) -#endif /* __STLSOFT_COMPILER_IS_DMC */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace - * - * The STLSoft uses namespaces by default, unless the _STLSOFT_NO_NAMESPACES - * preprocessor symbol is defined, in which case all elements are placed within - * the global namespace. - * - * The macro stlsoft_ns_qual() macro can be used to refer to elements in the - * STLSoft libraries irrespective of whether they are in the stlsoft namespace - * or in the global namespace. - * - * Some compilers do not support the standard library in the std namespace, so - * the stlsoft_ns_qual_std() macro can be used to refer to elements in the - * STLSoft libraries irrespective of whether they are in the std namespace or - * in the global namespace. - */ - -/* No STLSoft namespaces means no stlsoft namespace */ -#ifdef _STLSOFT_NO_NAMESPACES -# define _STLSOFT_NO_NAMESPACE -#endif /* _STLSOFT_NO_NAMESPACES */ - -#ifndef _STLSOFT_NO_NAMESPACE -/// The STLSoft namespace - \c stlsoft - is the namespace for the STLSoft main -/// project, and the root namespace for all the other STLSoft projects, whose -/// individual namespaces reside within it. -namespace stlsoft -{ -#endif /* !_STLSOFT_NO_NAMESPACE */ - -/// \def stlsoft_ns_qual(x) -/// Qualifies with stlsoft:: if STLSoft is using namespaces or, if not, does not qualify - -/// \def stlsoft_ns_using(x) -/// Declares a using directive (with respect to stlsoft) if STLSoft is using namespaces or, if not, does nothing - -#ifndef _STLSOFT_NO_NAMESPACE -# define stlsoft_ns_qual(x) ::stlsoft::x -# define stlsoft_ns_using(x) using ::stlsoft::x; -#else -# define stlsoft_ns_qual(x) x -# define stlsoft_ns_using(x) -#endif /* !_STLSOFT_NO_NAMESPACE */ - -/// \def stlsoft_ns_qual_std(x) -/// Qualifies with std:: if STLSoft is being translated in the context of the standard library being within the std namespace or, if not, does not qualify - -/// \def stlsoft_ns_using_std(x) -/// Declares a using directive (with respect to std) if STLSoft is being translated in the context of the standard library being within the std namespace or, if not, does nothing - -#ifdef __STLSOFT_CF_std_NAMESPACE -# define stlsoft_ns_qual_std(x) ::std::x -# define stlsoft_ns_using_std(x) using ::std::x; -#else -# define stlsoft_ns_qual_std(x) x -# define stlsoft_ns_using_std(x) -#endif /* !__STLSOFT_CF_std_NAMESPACE */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Typedefs - * - * The STLSoft uses a number of typedefs to aid in compiler-independence in the - * libraries' main code. - */ - -/* Type definitions - precursors */ - -#ifndef __STLSOFT_DOCUMENTATION_SKIP_SECTION - -/* ptrdiff_t - */ -#ifndef _STLSOFT_NO_STD_INCLUDES - typedef ptrdiff_t ss_ptrdiff_pr_t_; // ptr diff -#else - typedef int ss_ptrdiff_pr_t_; // ptr diff -#endif /* !_STLSOFT_NO_STD_INCLUDES */ - -/* size_t - */ -#ifndef _STLSOFT_NO_STD_INCLUDES - typedef size_t ss_size_pr_t_; // size -#else - typedef unsigned int ss_size_pr_t_; // size -#endif /* !_STLSOFT_NO_STD_INCLUDES */ - -/* wchar_t - * - * wchar_t is either a built-in type, or is defined to unsigned 16-bit value - */ - -#ifdef __STLSOFT_CF_NATIVE_WCHAR_T_SUPPORT - /* It's some kind of compiler native type. */ -# ifndef __STLSOFT_NATIVE_WCHAR_T - /* either wchar_t itself */ - typedef wchar_t ss_char_w_pr_t_; // Unicode char type -# else - /* or a compiler-specific type */ - typedef __STLSOFT_NATIVE_WCHAR_T ss_char_w_pr_t_; // Unicode char type -# endif /* !__STLSOFT_NATIVE_WCHAR_T */ -#elif defined(__STLSOFT_CF_TYPEDEF_WCHAR_T_SUPPORT) - typedef wchar_t ss_char_w_pr_t_; // Unicode char type -#else - /* It's some kind of library-defined type. */ -# ifndef _STLSOFT_NO_STD_INCLUDES - typedef wchar_t ss_char_w_pr_t_; // Unicode char type -# else - typedef unsigned short ss_char_w_pr_t_; // Unicode char type -# endif /* __STLSOFT_CF_NATIVE_WCHAR_T_SUPPORT */ -#endif /* !__STLSOFT_CF_NATIVE_WCHAR_T_SUPPORT */ - -/* 8-bit */ -#ifdef __STLSOFT_CF_NATIVE_8BIT_INT_SUPPORT - typedef __STLSOFT_NATIVE_INT8_T ss_int8_pr_t_; - typedef __STLSOFT_NATIVE_SINT8_T ss_sint8_pr_t_; - typedef __STLSOFT_NATIVE_UINT8_T ss_uint8_pr_t_; -#else - typedef signed char ss_int8_pr_t_; - typedef signed char ss_sint8_pr_t_; - typedef unsigned char ss_uint8_pr_t_; -#endif /* __STLSOFT_CF_NATIVE_8BIT_INT_SUPPORT */ - -/* 16-bit */ -#ifdef __STLSOFT_CF_NATIVE_16BIT_INT_SUPPORT - typedef __STLSOFT_NATIVE_INT16_T ss_int16_pr_t_; - typedef __STLSOFT_NATIVE_SINT16_T ss_sint16_pr_t_; - typedef __STLSOFT_NATIVE_UINT16_T ss_uint16_pr_t_; -#else - typedef short ss_int16_pr_t_; - typedef signed short ss_sint16_pr_t_; - typedef unsigned short ss_uint16_pr_t_; -#endif /* __STLSOFT_CF_NATIVE_16BIT_INT_SUPPORT */ - -/* 32-bit */ -#ifdef __STLSOFT_CF_NATIVE_32BIT_INT_SUPPORT - typedef __STLSOFT_NATIVE_INT32_T ss_int32_pr_t_; - typedef __STLSOFT_NATIVE_SINT32_T ss_sint32_pr_t_; - typedef __STLSOFT_NATIVE_UINT32_T ss_uint32_pr_t_; -#else - typedef long ss_int32_pr_t_; - typedef signed long ss_sint32_pr_t_; - typedef unsigned long ss_uint32_pr_t_; -#endif /* __STLSOFT_CF_NATIVE_32BIT_INT_SUPPORT */ - -/* 64-bit */ -#ifdef __STLSOFT_CF_NATIVE___int64_SUPPORT - typedef __int64 ss_int64_pr_t_; - typedef signed __int64 ss_sint64_pr_t_; - typedef unsigned __int64 ss_uint64_pr_t_; -#elif defined(__STLSOFT_CF_NATIVE_LONG_LONG_SUPPORT) - typedef long long ss_int64_pr_t_; - typedef signed long long ss_sint64_pr_t_; - typedef unsigned long long ss_uint64_pr_t_; -#endif /* __STLSOFT_CF_NATIVE_LONG_LONG_SUPPORT */ - -/* bool */ -#ifdef __STLSOFT_CF_NATIVE_BOOL_SUPPORT - typedef bool ss_bool_pr_t_; -#else - typedef unsigned int ss_bool_pr_t_; -#endif /* __STLSOFT_CF_NATIVE_BOOL_SUPPORT */ - -#endif /* !__STLSOFT_DOCUMENTATION_SKIP_SECTION */ - -/* Type definitions - proper */ - -typedef char ss_char_a_t; //!< Ansi char type -typedef ss_char_w_pr_t_ ss_char_w_t; //!< Unicode char type -typedef ss_int8_pr_t_ ss_int8_t; //!< 8-bit integer -typedef ss_sint8_pr_t_ ss_sint8_t; //!< 8-bit signed integer -typedef ss_uint8_pr_t_ ss_uint8_t; //!< 8-bit unsigned integer -typedef ss_int16_pr_t_ ss_int16_t; //!< 16-bit integer -typedef ss_sint16_pr_t_ ss_sint16_t; //!< 16-bit signed integer -typedef ss_uint16_pr_t_ ss_uint16_t; //!< 16-bit unsigned integer -typedef ss_int32_pr_t_ ss_int32_t; //!< 32-bit integer -typedef ss_sint32_pr_t_ ss_sint32_t; //!< 32-bit signed integer -typedef ss_uint32_pr_t_ ss_uint32_t; //!< 32-bit unsigned integer -#ifdef __STLSOFT_CF_NATIVE_64BIT_INTEGER_SUPPORT - typedef ss_int64_pr_t_ ss_int64_t; //!< 64-bit integer - typedef ss_sint64_pr_t_ ss_sint64_t; //!< 64-bit signed integer - typedef ss_uint64_pr_t_ ss_uint64_t; //!< 64-bit unsigned integer -#endif /* __STLSOFT_CF_NATIVE_64BIT_INTEGER_SUPPORT */ -typedef short ss_short_t; //!< short integer -typedef int ss_int_t; //!< integer -typedef signed int ss_sint_t; //!< signed integer -typedef unsigned int ss_uint_t; //!< unsigned integer -typedef long ss_long_t; //!< long integer -typedef ss_uint8_t ss_byte_t; //!< Byte -typedef ss_bool_pr_t_ ss_bool_t; //!< bool -typedef ss_size_pr_t_ ss_size_t; //!< size -typedef ss_ptrdiff_pr_t_ ss_ptrdiff_t; //!< ptr diff -typedef long ss_streampos_t; //!< streampos -typedef long ss_streamoff_t; //!< streamoff - -#ifndef _STLSOFT_NO_NAMESPACE -typedef ss_char_a_t char_a_t; //!< Ansi char type -typedef ss_char_w_t char_w_t; //!< Unicode char type -typedef ss_int8_t int8_t; //!< 8-bit integer -typedef ss_sint8_t sint8_t; //!< 8-bit signed integer -typedef ss_uint8_t uint8_t; //!< 8-bit unsigned integer -typedef ss_int16_t int16_t; //!< 16-bit integer -typedef ss_sint16_t sint16_t; //!< 16-bit signed integer -typedef ss_uint16_t uint16_t; //!< 16-bit unsigned integer -typedef ss_int32_t int32_t; //!< 32-bit integer -typedef ss_sint32_t sint32_t; //!< 32-bit signed integer -typedef ss_uint32_t uint32_t; //!< 32-bit unsigned integer -# ifdef __STLSOFT_CF_NATIVE_64BIT_INTEGER_SUPPORT -typedef ss_int64_t int64_t; //!< 64-bit integer -typedef ss_sint64_t sint64_t; //!< 64-bit signed integer -typedef ss_uint64_t uint64_t; //!< 64-bit unsigned integer -# endif /* __STLSOFT_CF_NATIVE_64BIT_INTEGER_SUPPORT */ -typedef ss_short_t short_t; //!< short integer -typedef ss_int_t int_t; //!< integer -typedef ss_sint_t sint_t; //!< signed integer -typedef ss_uint_t uint_t; //!< unsigned integer -typedef ss_long_t long_t; //!< long integer -typedef ss_byte_t byte_t; //!< Byte -typedef ss_bool_t bool_t; //!< bool -typedef ss_size_t size_t; //!< size -typedef ss_ptrdiff_t ptrdiff_t; //!< ptr diff -typedef ss_streampos_t streampos_t; //!< streampos -typedef ss_streamoff_t streamoff_t; //!< streamoff -#endif /* !_STLSOFT_NO_NAMESPACE */ - - -#if 0 -template -struct uintp_traits; - -STLSOFT_GEN_TRAIT_SPECIALISATION -struct uintp_traits<1> -{ - typedef uint8_t unsigned_type; -} - -typedef size_traits::signed_type sintp_t; -typedef size_traits::unsigned_type uintp_t; - -#endif /* 0 */ - - - -#ifndef __STLSOFT_DOCUMENTATION_SKIP_SECTION -#ifdef __cplusplus -struct stlsoft_size_checker -{ -#ifdef __STLSOFT_COMPILER_IS_GCC -protected: // GCC is too "helpful" in this case, so must declare as protected -#else -private: -#endif /* __STLSOFT_COMPILER_IS_GCC */ - stlsoft_size_checker(); - ~stlsoft_size_checker() - { - // Char types - stlsoft_static_assert(sizeof(ss_char_a_t) >= 1); - stlsoft_static_assert(sizeof(ss_char_w_t) >= 2); - // 8-bit types - stlsoft_static_assert(sizeof(ss_int8_t) == 1); - stlsoft_static_assert(sizeof(ss_sint8_t) == sizeof(ss_int8_t)); - stlsoft_static_assert(sizeof(ss_uint8_t) == sizeof(ss_int8_t)); - // 16-bit types - stlsoft_static_assert(sizeof(ss_int16_t) == 2); - stlsoft_static_assert(sizeof(ss_sint16_t) == sizeof(ss_int16_t)); - stlsoft_static_assert(sizeof(ss_uint16_t) == sizeof(ss_int16_t)); - // 32-bit types - stlsoft_static_assert(sizeof(ss_int32_t) == 4); - stlsoft_static_assert(sizeof(ss_sint32_t) == sizeof(ss_int32_t)); - stlsoft_static_assert(sizeof(ss_uint32_t) == sizeof(ss_int32_t)); - // 64-bit types -#ifdef __STLSOFT_CF_NATIVE_64BIT_INTEGER_SUPPORT - stlsoft_static_assert(sizeof(ss_int64_t) == 8); - stlsoft_static_assert(sizeof(ss_sint64_t) == sizeof(ss_int64_t)); - stlsoft_static_assert(sizeof(ss_uint64_t) == sizeof(ss_int64_t)); -#endif /* __STLSOFT_CF_NATIVE_64BIT_INTEGER_SUPPORT */ - // Integer types - stlsoft_static_assert(sizeof(ss_int_t) >= 1); - stlsoft_static_assert(sizeof(ss_sint_t) == sizeof(ss_int_t)); - stlsoft_static_assert(sizeof(ss_uint_t) == sizeof(ss_int_t)); - stlsoft_static_assert(sizeof(ss_long_t) >= sizeof(ss_int_t)); - // byte type - stlsoft_static_assert(sizeof(ss_byte_t) == 1); - // Bool type - stlsoft_static_assert(sizeof(ss_bool_t) >= 1); - // Other types - stlsoft_static_assert(sizeof(ss_size_t) >= 1); - stlsoft_static_assert(sizeof(ss_ptrdiff_t) >= 1); - stlsoft_static_assert(sizeof(ss_streampos_t) >= 1); - stlsoft_static_assert(sizeof(ss_streamoff_t) >= 1); - } -}; -#endif /* __cplusplus */ -#endif /* !__STLSOFT_DOCUMENTATION_SKIP_SECTION */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Keywords - * - * The STLSoft uses a number of preprocessor symbols to aid in compiler - * compatibility in the libraries' code. - * - * ss_explicit_k - explicit, or nothing - * ss_mutable_k - mutable, or nothing - * ss_typename_type_k - typename, or nothing (used within template - * definitions for declaring types derived from - * externally derived types) - * ss_typename_param_k - typename or class (used for template parameters) - * ss_typename_type_def_k - typename qualifier in template default parameters - * ss_typename_type_mil_k - typename qualifier in constructor initialiser lists - */ - -/// \def ss_explicit_k -/// -/// Evaluates to explicit on translators that support the keyword, otherwise to nothing -#ifdef __STLSOFT_CF_EXPLICIT_KEYWORD_SUPPORT -# define ss_explicit_k explicit -#else -# define ss_explicit_k -#endif /* __STLSOFT_CF_EXPLICIT_KEYWORD_SUPPORT */ - -/// \def ss_mutable_k -/// -/// Evaluates to mutable on translators that support the keyword, otherwise to nothing -#ifdef __STLSOFT_CF_MUTABLE_KEYWORD_SUPPORT -# define ss_mutable_k mutable -#else -# define ss_mutable_k -#endif /* __STLSOFT_CF_MUTABLE_KEYWORD_SUPPORT */ - -/// \def ss_typename_param_k -/// -/// Evaluates to typename on translators that support the keyword, otherwise to class -#ifdef __STLSOFT_CF_TYPENAME_PARAM_KEYWORD_SUPPORT -# define ss_typename_param_k typename -#else -# define ss_typename_param_k class -#endif /* __STLSOFT_CF_TYPENAME_PARAM_KEYWORD_SUPPORT */ - -/// \def ss_typename_type_k -/// -/// Evaluates to typename on translators that support the keyword, otherwise to nothing -#ifdef __STLSOFT_CF_TYPENAME_TYPE_KEYWORD_SUPPORT -# define ss_typename_type_k typename -#else -# define ss_typename_type_k -#endif /* __STLSOFT_CF_TYPENAME_TYPE_KEYWORD_SUPPORT */ - -/// \def ss_typename_type_def_k -/// -/// Evaluates to typename on translators that support the keyword, otherwise to nothing -#ifdef __STLSOFT_CF_TYPENAME_TYPE_DEF_KEYWORD_SUPPORT -# define ss_typename_type_def_k typename -#else -# define ss_typename_type_def_k -#endif /* __STLSOFT_CF_TYPENAME_TYPE_DEF_KEYWORD_SUPPORT */ - -/// \def ss_typename_type_mil_k -/// -/// Evaluates to typename on translators that support the keyword, otherwise to nothing -#ifdef __STLSOFT_CF_TYPENAME_TYPE_MIL_KEYWORD_SUPPORT -# define ss_typename_type_mil_k typename -#else -# define ss_typename_type_mil_k -#endif /* __STLSOFT_CF_TYPENAME_TYPE_MIL_KEYWORD_SUPPORT */ - - - -#ifndef __STLSOFT_DOCUMENTATION_SKIP_SECTION -/* ///////////////////////////////////////////////////////////////////////////// - * Values - * - * Since the boolean type may not be supported natively on all compilers, the - * values of true and false may also not be provided. Hence the values of - * ss_true_v and ss_false_v are defined, and are used in all code. - */ - -#ifdef __STLSOFT_CF_NATIVE_BOOL_SUPPORT -# define ss_true_v (true) -# define ss_false_v (false) -#else -# define ss_true_v (1) -# define ss_false_v (0) -#endif /* __STLSOFT_CF_NATIVE_BOOL_SUPPORT */ - -#endif /* !__STLSOFT_DOCUMENTATION_SKIP_SECTION */ -/* ///////////////////////////////////////////////////////////////////////////// - * Code modification macros - */ - -/// \defgroup code_modification_macros Code Modification Macros -/// \ingroup STLSoft -/// \brief These macros are used to help out where compiler differences are -/// so great as to cause great disgusting messes in the class/function implementations -/// @{ - -/* Exception signatures. */ -#if !defined(__STLSOFT_DOCUMENTATION_SKIP_SECTION) && \ - defined(__STLSOFT_CF_EXCEPTION_SIGNATURE_SUPPORT) -# define stlsoft_throw_0() throw () -# define stlsoft_throw_1(x1) throw (x1) -# define stlsoft_throw_2(x1, x2) throw (x1, x2) -# define stlsoft_throw_3(x1, x2, x3) throw (x1, x2, x3) -# define stlsoft_throw_4(x1, x2, x3, x4) throw (x1, x2, x3, x4) -# define stlsoft_throw_5(x1, x2, x3, x4, x5) throw (x1, x2, x3, x4, x5) -# define stlsoft_throw_6(x1, x2, x3, x4, x5, x6) throw (x1, x2, x3, x4, x5, x6) -# define stlsoft_throw_7(x1, x2, x3, x4, x5, x6, x7) throw (x1, x2, x3, x4, x5, x6, x7) -# define stlsoft_throw_8(x1, x2, x3, x4, x5, x6, x7, x8) throw (x1, x2, x3, x4, x5, x6, x7, x8) -#else -# define stlsoft_throw_0() -# define stlsoft_throw_1(x1) -# define stlsoft_throw_2(x1, x2) -# define stlsoft_throw_3(x1, x2, x3) -# define stlsoft_throw_4(x1, x2, x3, x4) -# define stlsoft_throw_5(x1, x2, x3, x4, x5) -# define stlsoft_throw_6(x1, x2, x3, x4, x5, x6) -# define stlsoft_throw_7(x1, x2, x3, x4, x5, x6, x7) -# define stlsoft_throw_8(x1, x2, x3, x4, x5, x6, x7, x8) -#endif /* __STLSOFT_CF_EXCEPTION_SIGNATURE_SUPPORT && !__STLSOFT_DOCUMENTATION_SKIP_SECTION */ - -/// \def stlsoft_num_elements -/// -/// Evaluates, at compile time, to the number of elements within the given vector entity -/// -/// Is it used as follows: -/// -/// \htmlonly -/// -/// int               ai[20]; -///
    -/// int               i     = 32; -///
    -/// int               *pi   = &i; -///
    -/// std::vector<int>  vi; -///
    -///
    -/// size_t            s_ai  = stlsoft_num_elements(ai);   // Ok -///
    -/// size_t            s_i   = stlsoft_num_elements(i);    // Error -///
    -/// size_t            s_pi  = stlsoft_num_elements(pi);   // Error -///
    -/// size_t            s_vi  = stlsoft_num_elements(vi);   // Error -///
    -///
    -/// \endhtmlonly -/// -/// \note For most of the supported compilers, this macro will reject application to pointer -/// types, or to class types providing operator []. This helps to avoid the common -/// gotcha whereby (sizeof(ar) / sizeof(ar[0])) is applied to such types, without -/// causing a compiler error. - -#ifndef __STLSOFT_DOCUMENTATION_SKIP_SECTION -# define _stlsoft_num_elements(ar) (sizeof(ar) / sizeof(0[(ar)])) - -# if defined(__cplusplus) && \ - defined(__STLSOFT_CF_STATIC_ARRAY_SIZE_DETERMINATION_SUPPORT) -# if 0/* defined(__STLSOFT_COMPILER_IS_GCC) */ -# pragma pack(push, 1) -template -struct ss_array_size_struct -{ - ss_sint8_t c[N]; -}; -# pragma pack(pop) - -template -ss_array_size_struct ss_static_array_size(T (&)[N]); - -# define stlsoft_num_elements(ar) sizeof(stlsoft_ns_qual(ss_static_array_size)(ar)) -# else /* ? 0 */ -template -struct ss_array_size_struct -{ - ss_sint8_t c[N]; -}; - -template -ss_array_size_struct ss_static_array_size(T (&)[N]); - -# define stlsoft_num_elements(ar) sizeof(stlsoft_ns_qual(ss_static_array_size)(ar).c) -# endif /* 0 */ -# else -# define stlsoft_num_elements(ar) _stlsoft_num_elements(ar) -# endif /* __cplusplus && __STLSOFT_CF_STATIC_ARRAY_SIZE_DETERMINATION_SUPPORT */ -#else -# define stlsoft_num_elements(ar) -#endif /* !__STLSOFT_DOCUMENTATION_SKIP_SECTION */ - -/// \def stlsoft_raw_offsetof -/// -/// Evaluates, at compile time, the offset of a structure/class member - -#if defined(__STLSOFT_COMPILER_IS_GCC) && \ - __GNUC__ >= 3 -# define stlsoft_raw_offsetof(s, m) (reinterpret_cast(&reinterpret_cast(1)->m) - 1) -#else -# ifndef _STLSOFT_NO_STD_INCLUDES -# define stlsoft_raw_offsetof(s, m) offsetof(s, m) -# else -# define stlsoft_raw_offsetof(s, m) reinterpret_cast(&static_cast(0)->m) -# endif /* !_STLSOFT_NO_STD_INCLUDES */ -#endif /* __GNUC__ >= 3 */ - - -/* destroy function */ -#ifndef __STLSOFT_DOCUMENTATION_SKIP_SECTION -template -void stlsoft_destroy_instance_fn(T *p) -{ - p->~T(); - - /* SSCB: Borland C++ and Visual C++ remove the dtor for basic - * structs, and then warn that p is unused. This reference - * suppresses that warning. - */ - ((void)p); -} -#endif /* !__STLSOFT_DOCUMENTATION_SKIP_SECTION */ - -/// \def stlsoft_destroy_instance -/// -/// Destroys the given instance \c p of the given type (\c t and \c _type) -#if defined(__STLSOFT_DOCUMENTATION_SKIP_SECTION) || \ - defined(__STLSOFT_COMPILER_IS_DMC) -# define stlsoft_destroy_instance(t, _type, p) do { (p)->~t(); } while(0) -#else -# define stlsoft_destroy_instance(t, _type, p) stlsoft_destroy_instance_fn((p)) -#endif /* __STLSOFT_COMPILER_IS_DMC */ - -/// Generates an opaque type with the name \c type -/// -/// For example, the following defines two distinct opaque types: -/// -/// \htmlonly -/// -/// stlsoft_gen_opaque(HThread) -///
    -/// stlsoft_gen_opaque(HProcess) -///
    -///
    -///
    -/// \endhtmlonly -/// -/// The two types are incompatible with each other, and with any other types (except that -/// they are both convertible to void const * - -#define stlsoft_gen_opaque(type) typedef struct __stlsoft_htype##type{ int i;} const *type; - -#ifndef __STLSOFT_DOCUMENTATION_SKIP_SECTION -/// Define a 'final' class, ie. one that cannot be inherited from -# define stlsoft_sterile_class(_cls) class __m__##_cls { private: __m__##_cls(){} ~__m__##_cls(){} friend class _cls; }; class _cls: public __m__##_cls -#endif /* !__STLSOFT_DOCUMENTATION_SKIP_SECTION */ - -/// \def STLSOFT_DECLARE_TEMPLATE_PARAM_AS_FRIEND -/// \ingroup code_modification_macros -/// -/// \brief Declares a template (class) parameter to be a friend of the template. -/// -/// Is it used as follows: -/// -/// \htmlonly -/// -/// template<typename T> -///
    -/// class Thing -///
    -/// { -///
    -///   STLSOFT_DECLARE_TEMPLATE_PARAM_AS_FRIEND(T); -///
    -///
    -/// private: -///
    -///   int m_member; // Thing<T>::m_member visible to T -///
    -/// }; -///
    -///
    -/// \endhtmlonly -/// -/// \note This is contrary to the C++-98 standard. Section 7.1.5.3(2) notes: "...within a class -/// template with a template type-parameter T, the declaration ["]friend class T;["] is ill-formed." -/// However, it gives the expected behaviour for all compilers currently supported by STLSoft - -#if defined(__STLSOFT_DOCUMENTATION_SKIP_SECTION) || \ - defined(__STLSOFT_COMPILER_IS_BORLAND) || \ - defined(__STLSOFT_COMPILER_IS_COMO) || \ - defined(__STLSOFT_COMPILER_IS_DMC) || \ - ( defined(__STLSOFT_COMPILER_IS_GCC) && \ - __GNUC__ < 3) || \ - defined(__STLSOFT_COMPILER_IS_INTEL) || \ - defined(__STLSOFT_COMPILER_IS_MSVC) || \ - defined(__STLSOFT_COMPILER_IS_VECTORC) || \ - defined(__STLSOFT_COMPILER_IS_WATCOM) -# define STLSOFT_DECLARE_TEMPLATE_PARAM_AS_FRIEND(T) friend T -#elif defined(__STLSOFT_COMPILER_IS_MWERKS) -# define STLSOFT_DECLARE_TEMPLATE_PARAM_AS_FRIEND(T) friend class T -#elif defined(__STLSOFT_COMPILER_IS_GCC) && \ - __GNUC__ >= 3 - -# define STLSOFT_DECLARE_TEMPLATE_PARAM_AS_FRIEND(T) \ - \ - struct friend_maker \ - { \ - typedef T T2; \ - }; \ - \ - typedef typename friend_maker::T2 friend_type; \ - \ - friend friend_type - -#else -# error Compiler not discriminated -#endif /* compiler */ - - -/// \def STLSOFT_GEN_TRAIT_SPECIALISATION -/// \ingroup code_modification_macros -/// -/// \brief Used to define a specialisation of a traits type -/// -#define STLSOFT_GEN_TRAIT_SPECIALISATION(TR, T, V) \ - \ - STLSOFT_TEMPLATE_SPECIALISATION \ - struct TR \ - { \ - enum { value = V }; \ - }; - - -/// \def STLSOFT_SUPPRESS_UNUSED -/// \ingroup code_modification_macros -/// -/// \brief Used to suppress unused variable warnings -/// -#ifdef __STLSOFT_COMPILER_IS_INTEL -# define STLSOFT_SUPPRESS_UNUSED(x) ((void)((x) = (x))) -#else /* ? __STLSOFT_COMPILER_IS_INTEL */ -# define STLSOFT_SUPPRESS_UNUSED(x) ((void)x) -#endif /* __STLSOFT_COMPILER_IS_INTEL */ - - - -/// @} - -/// \defgroup pointer_manipulation_functions Pointer Manipulation Functions -/// \ingroup STLSoft -/// \brief These functions assist in calculations with, and the manipulation of pointers -/// @{ - -/// Offsets a pointer by a number of bytes -/// -/// \param p The pointer to be offset -/// \param n The number of bytes to offset -/// \result \c p offset by \c bytes -template -inline void const *ptr_byte_offset(T const p, ss_ptrdiff_t n) -{ - return static_cast(static_cast(static_cast(p)) + n); -} - -/// Offsets a pointer by a number of elements -/// -/// \param p The pointer to be offset -/// \param n The number of elements to offset -/// \result \c p offset by \c elements -template -inline T const *ptr_offset(T const *p, ss_ptrdiff_t n) -{ - return p + n; -} - -/// Get the difference in bytes between two pointers -template -inline ss_ptrdiff_t ptr_byte_diff(T1 const *p1, T2 const *p2) -{ - return static_cast(static_cast(p1)) - static_cast(static_cast(p2)); -} - -/// Get the difference in elements between two pointers -template -inline ss_ptrdiff_t ptr_diff(T1 const *p1, T2 const *p2) -{ - return p1 - p2; -} - -/// @} // end of group pointer_manipulation_functions - -/* Mutable support */ -#ifndef __STLSOFT_DOCUMENTATION_SKIP_SECTION -template -#ifdef __STLSOFT_CF_MUTABLE_KEYWORD_SUPPORT -inline T &mutable_access(T &t) -#else -inline T &mutable_access(T const &t) -#endif /* __STLSOFT_CF_MUTABLE_KEYWORD_SUPPORT */ -{ -#ifdef __STLSOFT_CF_MUTABLE_KEYWORD_SUPPORT - return t; -#else - return const_cast(t); -#endif /* __STLSOFT_CF_MUTABLE_KEYWORD_SUPPORT */ -} -#endif /* !__STLSOFT_DOCUMENTATION_SKIP_SECTION */ - -/* Move constructor support */ -#ifdef __STLSOFT_CF_MOVE_CONSTRUCTOR_SUPPORT -# define stlsoft_define_move_rhs_type(t) t & -#else -# define stlsoft_define_move_rhs_type(t) t const & -#endif /* __STLSOFT_CF_MOVE_CONSTRUCTOR_SUPPORT */ - -template -inline T &move_lhs_from_rhs(stlsoft_define_move_rhs_type(T) t) -{ -#ifdef __STLSOFT_CF_MOVE_CONSTRUCTOR_SUPPORT - return t; -#else - return const_cast(t); -#endif /* __STLSOFT_CF_MOVE_CONSTRUCTOR_SUPPORT */ -} - -/* ///////////////////////////////////////////////////////////////////////////// - * Memory - */ - -// function operator new -// -// When namespaces are being used, stlsoft provides its own placement new, -// otherwise it includes in order to access the global version. - -#ifdef _STLSOFT_NO_NAMESPACE -# if defined(__STLSOFT_COMPILER_IS_BORLAND) && \ - __BORLANDC__ < 0x0550 -# include -# else -# include -# endif /* __STLSOFT_COMPILER_IS_BORLAND && __BORLANDC__ < 0x0550 */ -#else -# if ( defined(__STLSOFT_COMPILER_IS_DMC) && \ - __DMC__ < 0x0833) || \ - ( defined(__STLSOFT_COMPILER_IS_MSVC) && \ - _MSC_VER < 1300) -inline void *operator new(ss_size_t /* si */, void *pv) -{ - return pv; -} -# endif /* compiler */ -#endif /* !_STLSOFT_NO_NAMESPACE */ - -/* ////////////////////////////////////////////////////////////////////////// */ - -#ifndef _STLSOFT_NO_NAMESPACE -} // namespace stlsoft -#endif /* !_STLSOFT_NO_NAMESPACE */ - -/* ////////////////////////////////////////////////////////////////////////// */ - -#endif /* !_STLSOFT_INCL_H_STLSOFT */ - -/* ////////////////////////////////////////////////////////////////////////// */ diff -uNr gdc-0.17/d/phobos/etc/c/stlsoft/stlsoft_iterator.h gdc-0.18/d/phobos/etc/c/stlsoft/stlsoft_iterator.h --- gdc-0.17/d/phobos/etc/c/stlsoft/stlsoft_iterator.h 2004-10-26 02:41:27.000000000 +0200 +++ gdc-0.18/d/phobos/etc/c/stlsoft/stlsoft_iterator.h 1970-01-01 01:00:00.000000000 +0100 @@ -1,766 +0,0 @@ -/* //////////////////////////////////////////////////////////////////////////// - * File: stlsoft_iterator.h (originally MTIter.h, ::SynesisStl) - * - * Purpose: iterator classes. - * - * Created: 2nd January 2000 - * Updated: 28th November 2003 - * - * Author: Matthew Wilson, Synesis Software Pty Ltd. - * - * License: (Licensed under the Synesis Software Standard Source License) - * - * Copyright (C) 2002-2003, Synesis Software Pty Ltd. - * - * All rights reserved. - * - * www: http://www.synesis.com.au/stlsoft - * http://www.stlsoft.org/ - * - * email: submissions@stlsoft.org for submissions - * admin@stlsoft.org for other enquiries - * - * Redistribution and use in source and binary forms, with or - * without modification, are permitted provided that the following - * conditions are met: - * - * (i) Redistributions of source code must retain the above - * copyright notice and contact information, this list of - * conditions and the following disclaimer. - * - * (ii) Any derived versions of this software (howsoever modified) - * remain the sole property of Synesis Software. - * - * (iii) Any derived versions of this software (howsoever modified) - * remain subject to all these conditions. - * - * (iv) Neither the name of Synesis Software nor the names of any - * subdivisions, employees or agents of Synesis Software, nor the - * names of any other contributors to this software may be used to - * endorse or promote products derived from this software without - * specific prior written permission. - * - * This source code is provided by Synesis Software "as is" and any - * warranties, whether expressed or implied, including, but not - * limited to, the implied warranties of merchantability and - * fitness for a particular purpose are disclaimed. In no event - * shall the Synesis Software be liable for any direct, indirect, - * incidental, special, exemplary, or consequential damages - * (including, but not limited to, procurement of substitute goods - * or services; loss of use, data, or profits; or business - * interruption) however caused and on any theory of liability, - * whether in contract, strict liability, or tort (including - * negligence or otherwise) arising in any way out of the use of - * this software, even if advised of the possibility of such - * damage. - * - * ////////////////////////////////////////////////////////////////////////// */ - - -#ifndef _STLSOFT_INCL_H_STLSOFT_ITERATOR -#define _STLSOFT_INCL_H_STLSOFT_ITERATOR - -#ifndef __STLSOFT_DOCUMENTATION_SKIP_SECTION -# define _STLSOFT_VER_H_STLSOFT_ITERATOR_MAJOR 1 -# define _STLSOFT_VER_H_STLSOFT_ITERATOR_MINOR 14 -# define _STLSOFT_VER_H_STLSOFT_ITERATOR_REVISION 1 -# define _STLSOFT_VER_H_STLSOFT_ITERATOR_EDIT 43 -#endif /* !__STLSOFT_DOCUMENTATION_SKIP_SECTION */ - -/* //////////////////////////////////////////////////////////////////////////// - * Includes - */ - -#ifndef _STLSOFT_INCL_H_STLSOFT -# include "stlsoft.h" // Include the STLSoft root header -#endif /* !_STLSOFT_INCL_H_STLSOFT */ -#include // std::iterator, std::reverse_iterator, std::reverse_bidirectional_iterator - -/* ///////////////////////////////////////////////////////////////////////////// - * Warnings - */ - -/* This is here temporarily, until a better solution can be found. */ -#ifdef __STLSOFT_COMPILER_IS_MSVC -# pragma warning(disable : 4097) // suppresses: typedef-name 'identifier1' used as synonym for class-name 'identifier2' -#endif /* __STLSOFT_COMPILER_IS_MSVC */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace - */ - -#ifndef _STLSOFT_NO_NAMESPACE -namespace stlsoft -{ -#endif /* _STLSOFT_NO_NAMESPACE */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Library identification - */ - -// This is all some hideous kludge caused by Dinkumware's standard library's -// failure to leave behind any definitive discriminatable vestige of its -// presence. - -#ifdef __STLSOFT_CF_MIGHT_BE_DINKUMWARE_MS_NAUGHTIES -# undef __STLSOFT_CF_MIGHT_BE_DINKUMWARE_MS_NAUGHTIES -#endif /* !__STLSOFT_CF_MIGHT_BE_DINKUMWARE_MS_NAUGHTIES */ - -#ifdef __STLSOFT_CF_MIGHT_BE_DINKUMWARE_MS_NAUGHTIES_1300 -# undef __STLSOFT_CF_MIGHT_BE_DINKUMWARE_MS_NAUGHTIES_1300 -#endif /* !__STLSOFT_CF_MIGHT_BE_DINKUMWARE_MS_NAUGHTIES_1300 */ - -#ifdef __STLSOFT_CF_STL_IS_STLPORT -# undef __STLSOFT_CF_STL_IS_STLPORT -#endif /* !__STLSOFT_CF_STL_IS_STLPORT */ - -/* Detect whether Dinkumware "may" be present - * - * Discriminated symbol is __STLSOFT_CF_MIGHT_BE_DINKUMWARE_MS_NAUGHTIES - */ -#if ( defined(__STLSOFT_COMPILER_IS_INTEL) || \ - ( defined(__STLSOFT_COMPILER_IS_MSVC) && \ - _MSC_VER >= 1200 && \ - _MSC_VER < 1310)) && \ - defined(_STD_BEGIN) && \ - defined(_STD_END) && \ - defined(_Mbstinit) -# define __STLSOFT_CF_MIGHT_BE_DINKUMWARE_MS_NAUGHTIES -#endif /* _MSC_VER && _MSC_VER == 1300 */ - -#if defined(__STLSOFT_CF_MIGHT_BE_DINKUMWARE_MS_NAUGHTIES) && \ - defined(_DEPRECATED) && \ - defined(_HAS_TEMPLATE_PARTIAL_ORDERING) && \ - defined(_CPPLIB_VER) -# define __STLSOFT_CF_MIGHT_BE_DINKUMWARE_MS_NAUGHTIES_1300 -#endif /* */ - -/* Detect whether STLport is present - * - * Discriminated symbol is __STLSOFT_CF_STL_IS_STLPORT - */ -#ifdef _STLPORT_VERSION -# define __STLSOFT_CF_STL_IS_STLPORT -#endif /* _STLPORT_VERSION */ - -/* Must be either Dinkumware or STLport if compiling with Intel or Visual C++ - */ -#if ( defined(__STLSOFT_COMPILER_IS_INTEL) || \ - ( defined(__STLSOFT_COMPILER_IS_MSVC) && \ - _MSC_VER >= 1200 && \ - _MSC_VER < 1310)) && \ - ( !defined(__STLSOFT_CF_MIGHT_BE_DINKUMWARE_MS_NAUGHTIES) && \ - !defined(__STLSOFT_CF_STL_IS_STLPORT)) -# error When compiling with Intel C/C++ or Microsoft Visual C++, only the Dinkumware or STLport STL implementations are currently supported. -# error Please contact STLSoft (admin@stlsoft.org) if you need to support a different STL implementation with these compilers. -#endif /* (Intel || MSVC) && !DinkumWare && !STLport */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Iterator macros - */ - -/* reverse_iterator */ - -#if defined(__STLSOFT_COMPILER_IS_BORLAND) -# define stlsoft_reverse_iterator(I, T, R, P, D) stlsoft_ns_qual_std(reverse_iterator) -#elif defined(__STLSOFT_COMPILER_IS_CUSTOM) || \ - defined(__STLSOFT_COMPILER_IS_UNKNOWN) -# define stlsoft_reverse_iterator(I, T, R, P, D) stlsoft_ns_qual_std(reverse_iterator) -#elif defined(__STLSOFT_COMPILER_IS_DMC) -# if defined(__STLSOFT_CF_STL_IS_STLPORT) -# define stlsoft_reverse_iterator(I, T, R, P, D) stlsoft_ns_qual_std(reverse_iterator) -# else /* ? __STLSOFT_CF_STL_IS_STLPORT */ -# define stlsoft_reverse_iterator(I, T, R, P, D) stlsoft_ns_qual_std(reverse_iterator) -# endif /* __STLSOFT_CF_STL_IS_STLPORT */ -#elif defined(__STLSOFT_COMPILER_IS_COMO) -# define stlsoft_reverse_iterator(I, T, R, P, D) stlsoft_ns_qual_std(reverse_iterator) -#elif defined(__STLSOFT_COMPILER_IS_GCC) -# if __GNUC__ < 3 -# define stlsoft_reverse_iterator(I, T, R, P, D) ::reverse_iterator -# else -# define stlsoft_reverse_iterator(I, T, R, P, D) stlsoft_ns_qual_std(reverse_iterator) -# endif /* __GNUC__ < 3 */ -#elif defined(__STLSOFT_COMPILER_IS_INTEL) -# if defined(__STLSOFT_CF_STL_IS_STLPORT) || \ - defined(__STLSOFT_CF_MIGHT_BE_DINKUMWARE_MS_NAUGHTIES_1300) -# define stlsoft_reverse_iterator(I, T, R, P, D) stlsoft_ns_qual_std(reverse_iterator) -# else -# define stlsoft_reverse_iterator(I, T, R, P, D) stlsoft_ns_qual_std(reverse_iterator) -# endif /* __STLSOFT_CF_STL_IS_STLPORT || __STLSOFT_CF_MIGHT_BE_DINKUMWARE_MS_NAUGHTIES_1300 */ -#elif defined(__STLSOFT_COMPILER_IS_MWERKS) -# define stlsoft_reverse_iterator(I, T, R, P, D) stlsoft_ns_qual_std(reverse_iterator) -#elif defined(__STLSOFT_COMPILER_IS_MSVC) -# if _MSC_VER >= 1310 -# define stlsoft_reverse_iterator(I, T, R, P, D) stlsoft_ns_qual_std(reverse_iterator) -# elif defined(__STLSOFT_CF_STL_IS_STLPORT) -# define stlsoft_reverse_iterator(I, T, R, P, D) stlsoft_ns_qual_std(reverse_iterator) -# elif defined(__STLSOFT_CF_MIGHT_BE_DINKUMWARE_MS_NAUGHTIES_1300) -# define stlsoft_reverse_iterator(I, T, R, P, D) stlsoft_ns_qual_std(reverse_iterator) -# else -# define stlsoft_reverse_iterator(I, T, R, P, D) stlsoft_ns_qual_std(reverse_iterator) -# endif /* __STLSOFT_CF_STL_IS_STLPORT || __STLSOFT_CF_MIGHT_BE_DINKUMWARE_MS_NAUGHTIES_1300 */ -#elif defined(__STLSOFT_COMPILER_IS_WATCOM) -# if defined(__STLSOFT_CF_STL_IS_STLPORT) -# define stlsoft_reverse_iterator(I, T, R, P, D) stlsoft_ns_qual_std(reverse_iterator) -# else -# error Watcom is not supported independently of STLport -# endif /* __STLSOFT_CF_STL_IS_STLPORT */ -#else -# error Compiler not recognised -#endif /* compiler */ - -/* reverse_bidirectional_iterator */ - -#if defined(__STLSOFT_COMPILER_IS_BORLAND) -# define stlsoft_reverse_bidirectional_iterator(I, T, R, P, D) stlsoft_ns_qual_std(reverse_iterator) -#elif defined(__STLSOFT_COMPILER_IS_CUSTOM) || \ - defined(__STLSOFT_COMPILER_IS_UNKNOWN) -# define stlsoft_reverse_bidirectional_iterator(I, T, R, P, D) stlsoft_ns_qual_std(reverse_bidirectional_iterator) -#elif defined(__STLSOFT_COMPILER_IS_DMC) -# if defined(__STLSOFT_CF_STL_IS_STLPORT) -# define stlsoft_reverse_bidirectional_iterator(I, T, R, P, D) stlsoft_ns_qual_std(reverse_iterator) -# else /* ? __STLSOFT_CF_STL_IS_STLPORT */ -# define stlsoft_reverse_bidirectional_iterator(I, T, R, P, D) stlsoft_ns_qual_std(reverse_bidirectional_iterator) -# endif /* __STLSOFT_CF_STL_IS_STLPORT */ -#elif defined(__STLSOFT_COMPILER_IS_COMO) -# define stlsoft_reverse_bidirectional_iterator(I, T, R, P, D) stlsoft_ns_qual_std(reverse_iterator) -#elif defined(__STLSOFT_COMPILER_IS_GCC) -# if __GNUC__ < 3 -# define stlsoft_reverse_bidirectional_iterator(I, T, R, P, D) ::reverse_iterator -# else -# define stlsoft_reverse_bidirectional_iterator(I, T, R, P, D) stlsoft_ns_qual_std(reverse_iterator) -# endif /* __GNUC__ < 3 */ -#elif defined(__STLSOFT_COMPILER_IS_MWERKS) -# define stlsoft_reverse_bidirectional_iterator(I, T, R, P, D) stlsoft_ns_qual_std(reverse_iterator) -#elif defined(__STLSOFT_COMPILER_IS_INTEL) -# ifdef __STLSOFT_CF_STL_IS_STLPORT -# define stlsoft_reverse_bidirectional_iterator(I, T, R, P, D) stlsoft_ns_qual_std(reverse_iterator) -# else -# define stlsoft_reverse_bidirectional_iterator(I, T, R, P, D) stlsoft_ns_qual_std(reverse_bidirectional_iterator) -# endif /* __STLSOFT_CF_STL_IS_STLPORT */ -#elif defined(__STLSOFT_COMPILER_IS_MSVC) -# ifdef __STLSOFT_CF_STL_IS_STLPORT -# ifdef _STLP_CLASS_PARTIAL_SPECIALIZATION -# define stlsoft_reverse_bidirectional_iterator(I, T, R, P, D) stlsoft_ns_qual_std(reverse_iterator) -# else -# define stlsoft_reverse_bidirectional_iterator(I, T, R, P, D) stlsoft_ns_qual_std(reverse_bidirectional_iterator) -# endif /* _STLP_CLASS_PARTIAL_SPECIALIZATION */ -# else -# define stlsoft_reverse_bidirectional_iterator(I, T, R, P, D) stlsoft_ns_qual_std(reverse_bidirectional_iterator) -# endif /* __STLSOFT_CF_STL_IS_STLPORT */ -#elif defined(__STLSOFT_COMPILER_IS_WATCOM) -# if defined(__STLSOFT_CF_STL_IS_STLPORT) -# define stlsoft_reverse_bidirectional_iterator(I, T, R, P, D) stlsoft_ns_qual_std(reverse_iterator) -# else -# error Watcom is not supported independently of STLport -# endif /* __STLSOFT_CF_STL_IS_STLPORT */ -#else -# error Compiler not recognised -#endif /* compiler */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Iterators - */ - -// class iterator_base -/// Base type for iterator types -// -/// This class abstract std::iterator functionality for deriving classes, hiding -/// the inconsistencies and incompatibilities of the various compilers and/or -/// libraries supported by the STLSoft libraries. -/// -/// \param C The iterator category -/// \param T The value type -/// \param D The distance type -/// \param P The pointer type -/// \param R The reference type -template< ss_typename_param_k C /* category */ - , ss_typename_param_k T /* type */ - , ss_typename_param_k D /* distance */ - , ss_typename_param_k P /* pointer */ - , ss_typename_param_k R /* reference */ - > -struct iterator_base -#if defined(__STLSOFT_COMPILER_IS_INTEL) || \ - defined(__STLSOFT_COMPILER_IS_MSVC) - : public stlsoft_ns_qual_std(iterator) -#elif defined(__STLSOFT_COMPILER_IS_MWERKS) - : public stlsoft_ns_qual_std(iterator) -#endif /* __STLSOFT_COMPILER_IS_MSVC */ -{ -#if defined(__STLSOFT_COMPILER_IS_INTEL) || \ - defined(__STLSOFT_COMPILER_IS_MSVC) - typedef stlsoft_ns_qual_std(iterator) parent_class_type; -#elif defined(__STLSOFT_COMPILER_IS_MWERKS) - typedef stlsoft_ns_qual_std(iterator) parent_class_type; -#endif /* __STLSOFT_COMPILER_IS_MSVC */ - -public: -#if defined(__STLSOFT_COMPILER_IS_INTEL) || \ - defined(__STLSOFT_COMPILER_IS_MSVC) || \ - defined(__STLSOFT_COMPILER_IS_MWERKS) - typedef ss_typename_type_k parent_class_type::iterator_category iterator_category; - typedef ss_typename_type_k parent_class_type::value_type value_type; -# if ( defined(__STLSOFT_COMPILER_IS_INTEL) || \ - defined(__STLSOFT_COMPILER_IS_MSVC)) && \ - !defined(__STLSOFT_CF_STL_IS_STLPORT) - typedef ss_typename_type_k parent_class_type::distance_type difference_type; - typedef P pointer; - typedef R reference; -# else - typedef ss_typename_type_k parent_class_type::difference_type difference_type; - typedef ss_typename_type_k parent_class_type::pointer pointer; - typedef ss_typename_type_k parent_class_type::reference reference; -# endif /* __STLSOFT_COMPILER_IS_MSVC */ - -#elif defined(__STLSOFT_COMPILER_IS_GCC) || \ - defined(__STLSOFT_COMPILER_IS_BORLAND) -# if defined(__STLSOFT_COMPILER_IS_GCC) -# if __GNUC__ < 3 - typedef __STD::input_iterator_tag iterator_category; -# else - typedef stlsoft_ns_qual_std(input_iterator_tag) iterator_category; -# endif /* __GNUC__ < 3 */ -# elif defined(__STLSOFT_COMPILER_IS_BORLAND) - typedef stlsoft_ns_qual_std(input_iterator_tag) iterator_category; -# endif /* __STLSOFT_COMPILER_IS_GCC || __STLSOFT_COMPILER_IS_BORLAND */ - typedef T value_type; - typedef D difference_type; - typedef P pointer; - typedef R reference; -#else - /* All other compilers. */ -# if defined(__STLSOFT_COMPILER_IS_CUSTOM) || \ - defined(__STLSOFT_COMPILER_IS_UNKNOWN) || \ - defined(__STLSOFT_COMPILER_IS_DMC) - typedef C iterator_category; - typedef T value_type; - typedef D difference_type; - typedef P pointer; - typedef R reference; -# elif defined(__STLSOFT_COMPILER_IS_WATCOM) -# if defined(__STLSOFT_CF_STL_IS_STLPORT) - typedef ss_typename_type_k parent_class_type::distance_type difference_type; - typedef P pointer; - typedef R reference; -# else -# error Watcom is not supported independently of STLport -# endif /* __STLSOFT_CF_STL_IS_STLPORT */ -# else -# error Compiler not supported -# endif /* !__STLSOFT_COMPILER_IS_DMC */ -#endif /* __STLSOFT_COMPILER_IS_GCC || __STLSOFT_COMPILER_IS_BORLAND */ - - /* These two are for compatibility with older non-standard implementations, and - * will be benignly ignored by anything not requiring them. - */ - typedef pointer pointer_type; - typedef reference reference_type; -}; - - -// reverse_iterator_base, const_reverse_iterator_base, -// reverse_bidirectional_iterator_base and const_reverse_bidirectional_iterator_base -// -// These classes act as the base for reverse iterators, insulating deriving -// classes from the inconsistencies and incompatibilities of the various -// compilers and/or libraries supported by the STLSoft libraries. - -// class reverse_iterator_base -/// Base type for reverse_iterator types -// -/// This class acts as the base for reverse iterators, insulating deriving -/// classes from the inconsistencies and incompatibilities of the various -/// compilers and/or libraries supported by the STLSoft libraries. -/// -/// \param I The iterator type -/// \param T The value type -/// \param R The reference type -/// \param P The pointer type -/// \param D The distance type -template< ss_typename_param_k I - , ss_typename_param_k T - , ss_typename_param_k R - , ss_typename_param_k P - , ss_typename_param_k D - > -struct reverse_iterator_base - : public stlsoft_reverse_iterator(I, T, R, P, D) -{ -public: - typedef stlsoft_reverse_iterator(I, T, R, P, D) parent_class_type; - - typedef ss_typename_type_k parent_class_type::iterator_category iterator_category; - typedef ss_typename_type_k parent_class_type::value_type value_type; -# if ( defined(__STLSOFT_COMPILER_IS_INTEL) || \ - defined(__STLSOFT_COMPILER_IS_MSVC)) && \ - _MSC_VER < 1300 && /* This is truly hideous, but since PJP doesn't put version numbers in the VC++ stl swill, we have no choice */ \ - !defined(__STLSOFT_CF_STL_IS_STLPORT) - typedef ss_typename_type_k parent_class_type::distance_type difference_type; - typedef ss_typename_type_k parent_class_type::pointer_type pointer; - typedef ss_typename_type_k parent_class_type::reference_type reference; -#else - typedef ss_typename_type_k parent_class_type::difference_type difference_type; - typedef ss_typename_type_k parent_class_type::pointer pointer; - typedef ss_typename_type_k parent_class_type::reference reference; -#endif /* __STLSOFT_COMPILER_IS_MSVC */ - - /* These two are for compatibility with older non-standard implementations, and - * will be benignly ignored by anything not requiring them. - */ - typedef pointer pointer_type; - typedef reference reference_type; - -// Construction -public: - /// Constructor - ss_explicit_k reverse_iterator_base(I i) - : parent_class_type(i) - {} -}; - -// class const_reverse_iterator_base -/// Base type for const_reverse_iterator types -// -/// This class acts as the base for const reverse iterators, insulating deriving -/// classes from the inconsistencies and incompatibilities of the various -/// compilers and/or libraries supported by the STLSoft libraries. -/// -/// \param I The iterator type -/// \param T The value type -/// \param R The reference type -/// \param P The pointer type -/// \param D The distance type -template< ss_typename_param_k I - , ss_typename_param_k T - , ss_typename_param_k R - , ss_typename_param_k P - , ss_typename_param_k D - > -struct const_reverse_iterator_base - : public stlsoft_reverse_iterator(I, T, R, P, D) -{ -public: - typedef stlsoft_reverse_iterator(I, T, R, P, D) parent_class_type; - - typedef ss_typename_type_k parent_class_type::iterator_category iterator_category; - typedef ss_typename_type_k parent_class_type::value_type value_type; -# if ( defined(__STLSOFT_COMPILER_IS_INTEL) || \ - defined(__STLSOFT_COMPILER_IS_MSVC)) && \ - _MSC_VER < 1300 && /* This is truly hideous, but since PJP doesn't put version numbers in the VC++ stl swill, we have no choice */ \ - !defined(__STLSOFT_CF_STL_IS_STLPORT) - typedef ss_typename_type_k parent_class_type::distance_type difference_type; - typedef ss_typename_type_k parent_class_type::pointer_type pointer; - typedef ss_typename_type_k parent_class_type::reference_type reference; -#else - typedef ss_typename_type_k parent_class_type::difference_type difference_type; - typedef ss_typename_type_k parent_class_type::pointer pointer; - typedef ss_typename_type_k parent_class_type::reference reference; -#endif /* __STLSOFT_COMPILER_IS_MSVC && __STLSOFT_CF_STL_IS_STLPORT */ - - /* These two are for compatibility with older non-standard implementations, and - * will be benignly ignored by anything not requiring them. - */ - typedef pointer pointer_type; - typedef reference reference_type; - -// Construction -public: - /// Constructor - ss_explicit_k const_reverse_iterator_base(I i) - : parent_class_type(i) - {} -}; - -#ifdef __STLSOFT_CF_BIDIRECTIONAL_ITERATOR_SUPPORT - -// class reverse_bidirectional_iterator_base -/// Base type for reverse_bidirectional_iterator types -// -/// This class acts as the base for reverse bidirectional iterators, -/// insulating deriving classes from the inconsistencies and incompatibilities -/// of the various compilers and/or libraries supported by the STLSoft libraries. -/// -/// \param I The iterator type -/// \param T The value type -/// \param R The reference type -/// \param P The pointer type -/// \param D The distance type -template< ss_typename_param_k I - , ss_typename_param_k T - , ss_typename_param_k R - , ss_typename_param_k P - , ss_typename_param_k D - > -struct reverse_bidirectional_iterator_base - : public stlsoft_reverse_bidirectional_iterator(I, T, R, P, D) -{ -public: - typedef stlsoft_reverse_bidirectional_iterator(I, T, R, P, D) parent_class_type; - - typedef ss_typename_type_k parent_class_type::iterator_category iterator_category; - typedef ss_typename_type_k parent_class_type::value_type value_type; -# if ( defined(__STLSOFT_COMPILER_IS_INTEL) || \ - defined(__STLSOFT_COMPILER_IS_MSVC)) && \ - _MSC_VER < 1300 && /* This is truly hideous, but since PJP doesn't put version numbers in the VC++ stl swill, we have no choice */ \ - !defined(__STLSOFT_CF_STL_IS_STLPORT) - typedef ss_typename_type_k parent_class_type::distance_type difference_type; - typedef ss_typename_type_k parent_class_type::pointer_type pointer; - typedef ss_typename_type_k parent_class_type::reference_type reference; -#else - typedef ss_typename_type_k parent_class_type::difference_type difference_type; - typedef ss_typename_type_k parent_class_type::pointer pointer; - typedef ss_typename_type_k parent_class_type::reference reference; -#endif /* __STLSOFT_COMPILER_IS_MSVC */ - - /* These two are for compatibility with older non-standard implementations, and - * will be benignly ignored by anything not requiring them. - */ - typedef pointer pointer_type; - typedef reference reference_type; - -// Construction -public: - /// Constructor - ss_explicit_k reverse_bidirectional_iterator_base(I i) - : parent_class_type(i) - {} -}; - -// class const_reverse_bidirectional_iterator_base -/// Base type for const_reverse_bidirectional_iterator types -// -/// This class acts as the base for const reverse bidirectional iterators, -/// insulating deriving classes from the inconsistencies and incompatibilities -/// of the various compilers and/or libraries supported by the STLSoft libraries. -/// -/// \param I The iterator type -/// \param T The value type -/// \param R The reference type -/// \param P The pointer type -/// \param D The distance type -template< ss_typename_param_k I - , ss_typename_param_k T - , ss_typename_param_k R - , ss_typename_param_k P - , ss_typename_param_k D - > -struct const_reverse_bidirectional_iterator_base - : public stlsoft_reverse_bidirectional_iterator(I, T, R, P, D) -{ -public: - typedef stlsoft_reverse_bidirectional_iterator(I, T, R, P, D) parent_class_type; - - typedef ss_typename_type_k parent_class_type::iterator_category iterator_category; - typedef ss_typename_type_k parent_class_type::value_type value_type; -# if ( defined(__STLSOFT_COMPILER_IS_INTEL) || \ - defined(__STLSOFT_COMPILER_IS_MSVC)) && \ - _MSC_VER < 1300 && /* This is truly hideous, but since PJP doesn't put version numbers in the VC++ stl swill, we have no choice */ \ - !defined(__STLSOFT_CF_STL_IS_STLPORT) - typedef ss_typename_type_k parent_class_type::distance_type difference_type; - typedef ss_typename_type_k parent_class_type::pointer_type pointer; - typedef ss_typename_type_k parent_class_type::reference_type reference; -#else - typedef ss_typename_type_k parent_class_type::difference_type difference_type; - typedef ss_typename_type_k parent_class_type::pointer pointer; - typedef ss_typename_type_k parent_class_type::reference reference; -#endif /* __STLSOFT_COMPILER_IS_MSVC && __STLSOFT_CF_STL_IS_STLPORT */ - - /* These two are for compatibility with older non-standard implementations, and - * will be benignly ignored by anything not requiring them. - */ - typedef pointer pointer_type; - typedef reference reference_type; - -// Construction -public: - /// Constructor - ss_explicit_k const_reverse_bidirectional_iterator_base(I i) - : parent_class_type(i) - {} -}; - -#endif /* __STLSOFT_CF_BIDIRECTIONAL_ITERATOR_SUPPORT */ - -// Random access iterator support - -#ifdef __STLSOFT_CF_MIGHT_BE_DINKUMWARE_MS_NAUGHTIES - -#ifndef _STLSOFT_NO_NAMESPACE -} // namespace stlsoft -#endif /* _STLSOFT_NO_NAMESPACE */ - -template< ss_typename_param_k _Ty - , ss_typename_param_k _Diff - , ss_typename_param_k _Pointer - , ss_typename_param_k _Reference - , ss_typename_param_k _Pointer2 - , ss_typename_param_k _Reference2 - > -class _Ptrit -{ -public: - typedef _Pointer iterator_type; - -private: - char x[1024]; -}; - -namespace std -{ - namespace test_dinkumware - { - template< ss_typename_param_k T1 - , ss_typename_param_k T2 - , bool S - > - struct select_type - { - typedef T1 selected_type; - }; - -#ifdef __STLSOFT_CF_TEMPLATE_PARTIAL_SPECIALISATION_SUPPORT - template< ss_typename_param_k T1 - , ss_typename_param_k T2 - > - struct select_type - { - typedef T2 selected_type; - }; -#endif //# ifdef __STLSOFT_CF_TEMPLATE_PARTIAL_SPECIALISATION_SUPPORT - - template< class V - , class P - , class R - > - class _Ptrit_tdkw - { - typedef _Ptrit _Ptrit_type; - - public: - typedef select_type<_Ptrit_type, P, sizeof(_Ptrit_type) < 1024>::selected_type iterator_type; - }; - - } -} - -#ifndef _STLSOFT_NO_NAMESPACE -namespace stlsoft -{ -#endif /* _STLSOFT_NO_NAMESPACE */ - -#endif /* !__STLSOFT_CF_MIGHT_BE_DINKUMWARE_MS_NAUGHTIES */ - -/// Pointer iterator type -/// -/// \param V The value type -/// \param P The pointer type -/// \param R The reference type -template< ss_typename_param_k V - , ss_typename_param_k P - , ss_typename_param_k R - > -struct pointer_iterator -{ -#if defined(__STLSOFT_CF_MIGHT_BE_DINKUMWARE_MS_NAUGHTIES) && \ - !defined(__STLSOFT_CF_STL_IS_STLPORT) -# if defined(__STLSOFT_CF_MIGHT_BE_DINKUMWARE_MS_NAUGHTIES_1300) - typedef std::test_dinkumware::_Ptrit_tdkw::iterator_type iterator_type; -# else - typedef P iterator_type; -# endif /* __STLSOFT_CF_MIGHT_BE_DINKUMWARE_MS_NAUGHTIES_1300 */ -#elif defined(__STLSOFT_COMPILER_IS_MSVC) && \ - !defined(__STLSOFT_CF_STL_IS_STLPORT) && \ - defined(_XUTILITY_) && \ - _MSC_VER == 1300 - typedef std::_Ptrit iterator_type; -#else - typedef P iterator_type; -#endif /* !__STLSOFT_CF_MIGHT_BE_DINKUMWARE_MS_NAUGHTIES */ -}; - -/* ////////////////////////////////////////////////////////////////////////// */ - -#if defined(__STLSOFT_COMPILER_IS_DMC) && \ - !defined(__STLSOFT_CF_STL_IS_STLPORT) -template< ss_typename_param_k V - , ss_typename_param_k P - , ss_typename_param_k R - > -inline random_access_iterator_tag iterator_category(pointer_iterator::iterator_type const &) -{ - return random_access_iterator_tag(); -} - -template< ss_typename_param_k V - , ss_typename_param_k P - , ss_typename_param_k R - > -inline ptrdiff_t* distance_type(pointer_iterator::iterator_type const &) -{ - return static_cast(0); -} -#endif /* __STLSOFT_COMPILER_IS_DMC && !__STLSOFT_CF_STL_IS_STLPORT */ - -/* ////////////////////////////////////////////////////////////////////////// */ - - -/// Iterator category obtainer -/// -/// \param I The iterator type -/// \param i The iterator instance - -#if defined(__STLSOFT_COMPILER_IS_DMC) -# if defined(__STLSOFT_CF_STL_IS_STLPORT) -# define stlsoft_iterator_query_category(I, i) (stlsoft_ns_qual_std(iterator_traits)::iterator_category()) -//# error Digital Mars with STLport not yet supported -# else -# define stlsoft_iterator_query_category(I, i) (stlsoft_ns_qual_std(iterator_category)(i)) -# endif /* */ -#elif defined(__STLSOFT_COMPILER_IS_INTEL) -# if defined(__STLSOFT_CF_STL_IS_STLPORT) -# define stlsoft_iterator_query_category(I, i) (stlsoft_ns_qual_std(iterator_traits)::iterator_category()) -# elif defined(__STLSOFT_CF_MIGHT_BE_DINKUMWARE_MS_NAUGHTIES) -# define stlsoft_iterator_query_category(I, i) (stlsoft_ns_qual_std(_Iter_cat)(i)) -# else -# error -# endif /* */ -#elif defined(__STLSOFT_COMPILER_IS_MSVC) -# if defined(__STLSOFT_CF_STL_IS_STLPORT) -# if _MSC_VER < 1300 -# define stlsoft_iterator_query_category(I, i) (stlsoft_ns_qual_std(iterator_category)(i)) -# else -# define stlsoft_iterator_query_category(I, i) (stlsoft_ns_qual_std(iterator_category)(i)) -# endif /* _MSC_VER < 1300 */ -# elif defined(__STLSOFT_CF_MIGHT_BE_DINKUMWARE_MS_NAUGHTIES) -# define stlsoft_iterator_query_category(I, i) (stlsoft_ns_qual_std(_Iter_cat)(i)) -# elif(_MSC_VER >= 1310) -# define stlsoft_iterator_query_category(I, i) (stlsoft_ns_qual_std(iterator_traits)::iterator_category()) -# elif(_MSC_VER >= 1200) -# error -# endif /* */ -#else -# define stlsoft_iterator_query_category(I, i) (stlsoft_ns_qual_std(iterator_traits)::iterator_category()) -#endif /* __STLSOFT_CF_MIGHT_BE_DINKUMWARE_MS_NAUGHTIES && !__STLSOFT_CF_STL_IS_STLPORT */ - -#if 0 -template -struct queried_iterator_category -{ -}; - -template -query_iterator_category -#endif /* 0 */ - -/* ////////////////////////////////////////////////////////////////////////// */ - -#ifndef _STLSOFT_NO_NAMESPACE -} // namespace stlsoft -#endif /* _STLSOFT_NO_NAMESPACE */ - -/* ////////////////////////////////////////////////////////////////////////// */ - -#endif /* _STLSOFT_INCL_H_STLSOFT_ITERATOR */ - -/* ////////////////////////////////////////////////////////////////////////// */ diff -uNr gdc-0.17/d/phobos/etc/c/stlsoft/stlsoft_lock_scope.h gdc-0.18/d/phobos/etc/c/stlsoft/stlsoft_lock_scope.h --- gdc-0.17/d/phobos/etc/c/stlsoft/stlsoft_lock_scope.h 2004-10-26 02:41:27.000000000 +0200 +++ gdc-0.18/d/phobos/etc/c/stlsoft/stlsoft_lock_scope.h 1970-01-01 01:00:00.000000000 +0100 @@ -1,237 +0,0 @@ -/* //////////////////////////////////////////////////////////////////////////// - * File: stlsoft_lock_scope.h (originally MLLock.h, ::SynesisStd) - * - * Purpose: Synchronisation object lock scoping class. - * - * Created: 1st October 1994 - * Updated: 22nd November 2003 - * - * Author: Matthew Wilson, Synesis Software Pty Ltd. - * - * License: (Licensed under the Synesis Software Standard Source License) - * - * Copyright (C) 2002-2003, Synesis Software Pty Ltd. - * - * All rights reserved. - * - * www: http://www.synesis.com.au/stlsoft - * http://www.stlsoft.org/ - * - * email: submissions@stlsoft.org for submissions - * admin@stlsoft.org for other enquiries - * - * Redistribution and use in source and binary forms, with or - * without modification, are permitted provided that the following - * conditions are met: - * - * (i) Redistributions of source code must retain the above - * copyright notice and contact information, this list of - * conditions and the following disclaimer. - * - * (ii) Any derived versions of this software (howsoever modified) - * remain the sole property of Synesis Software. - * - * (iii) Any derived versions of this software (howsoever modified) - * remain subject to all these conditions. - * - * (iv) Neither the name of Synesis Software nor the names of any - * subdivisions, employees or agents of Synesis Software, nor the - * names of any other contributors to this software may be used to - * endorse or promote products derived from this software without - * specific prior written permission. - * - * This source code is provided by Synesis Software "as is" and any - * warranties, whether expressed or implied, including, but not - * limited to, the implied warranties of merchantability and - * fitness for a particular purpose are disclaimed. In no event - * shall the Synesis Software be liable for any direct, indirect, - * incidental, special, exemplary, or consequential damages - * (including, but not limited to, procurement of substitute goods - * or services; loss of use, data, or profits; or business - * interruption) however caused and on any theory of liability, - * whether in contract, strict liability, or tort (including - * negligence or otherwise) arising in any way out of the use of - * this software, even if advised of the possibility of such - * damage. - * - * ////////////////////////////////////////////////////////////////////////// */ - - -#ifndef _STLSOFT_INCL_H_STLSOFT_LOCK_SCOPE -#define _STLSOFT_INCL_H_STLSOFT_LOCK_SCOPE - -#ifndef __STLSOFT_DOCUMENTATION_SKIP_SECTION -#define _STLSOFT_VER_H_STLSOFT_LOCK_SCOPE_MAJOR 3 -#define _STLSOFT_VER_H_STLSOFT_LOCK_SCOPE_MINOR 0 -#define _STLSOFT_VER_H_STLSOFT_LOCK_SCOPE_REVISION 2 -#define _STLSOFT_VER_H_STLSOFT_LOCK_SCOPE_EDIT 89 -#endif /* !__STLSOFT_DOCUMENTATION_SKIP_SECTION */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Includes - */ - -#ifndef _STLSOFT_INCL_H_STLSOFT -# include "stlsoft.h" // Include the STLSoft root header -#endif /* !_STLSOFT_INCL_H_STLSOFT */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace - */ - -#ifndef _STLSOFT_NO_NAMESPACE -namespace stlsoft -{ -#endif /* _STLSOFT_NO_NAMESPACE */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Classes - */ - -// class lock_traits - -/// Traits class for lockable objects -/// -/// \param L The lockable class -template -struct lock_traits -{ -public: - /// The lockable type - typedef L lock_type; - /// The current parameterisation of this type - typedef lock_traits class_type; - -// Operations -public: - /// Locks the given lockable instance - static void lock(lock_type &c) - { - lock_instance(c); - } - - /// Unlocks the given lockable instance - static void unlock(lock_type &c) - { - unlock_instance(c); - } -}; - -// class lock_invert_traits - -/// Traits class for inverting the lock status of lockable objects -/// -/// \param L The lockable class -template -struct lock_invert_traits -{ -public: - /// The lockable type - typedef L lock_type; - /// The current parameterisation of this type - typedef lock_invert_traits class_type; - -// Operations -public: - /// Unlocks the given lockable instance - static void lock(lock_type &c) - { - unlock_instance(c); - } - - /// Locks the given lockable instance - static void unlock(lock_type &c) - { - lock_instance(c); - } -}; - -// class lock_traits_inverter - -/// Traits inverter class for inverting the lock behaviour of lockable traits types -/// -/// \param L The traits class -template -struct lock_traits_inverter -{ -public: - /// The traits type - typedef T traits_type; - /// The lockable type - typedef ss_typename_type_k traits_type::lock_type lock_type; - /// The current parameterisation of this type - typedef lock_traits_inverter class_type; - -// Operations -public: - /// Unlocks the given lockable instance - static void lock(lock_type &c) - { - traits_type::unlock(c); - } - - /// Locks the given lockable instance - static void unlock(lock_type &c) - { - traits_type::lock(c); - } -}; - -// class lock_scope - -/// This class scopes the lock status of a lockable type -/// -/// \param L The lockable type, e.g. stlsoft::null_mutex -/// \param T The lock traits. On translators that support default template arguments this defaults to lock_traits -template< ss_typename_param_k L -#ifdef __STLSOFT_CF_TEMPLATE_CLASS_DEFAULT_CLASS_ARGUMENT_SUPPORT - , ss_typename_param_k T = lock_traits -#else - , ss_typename_param_k T -#endif /* __STLSOFT_CF_TEMPLATE_CLASS_DEFAULT_CLASS_ARGUMENT_SUPPORT */ - > -class lock_scope -{ -public: - /// The lockable type - typedef L lock_type; - /// The traits type - typedef T traits_type; - /// The current parameterisation of this type - typedef lock_scope class_type; - -// Construction -public: - /// Locks the lockable instance - lock_scope(lock_type &l) - : m_l(l) - { - traits_type::lock(m_l); - } - /// Unlocks the lockable instance - ~lock_scope() - { - traits_type::unlock(m_l); - } - -// Members -private: - lock_type &m_l; - -// Not to be implemented -private: - lock_scope(class_type const &rhs); - lock_scope &operator =(class_type const &rhs); -}; - -/* ////////////////////////////////////////////////////////////////////////// */ - -#ifndef _STLSOFT_NO_NAMESPACE -} // namespace stlsoft -#endif /* _STLSOFT_NO_NAMESPACE */ - -/* ////////////////////////////////////////////////////////////////////////// */ - -#endif /* !_STLSOFT_INCL_H_STLSOFT_LOCK_SCOPE */ - -/* ////////////////////////////////////////////////////////////////////////// */ diff -uNr gdc-0.17/d/phobos/etc/c/stlsoft/stlsoft_nulldef.h gdc-0.18/d/phobos/etc/c/stlsoft/stlsoft_nulldef.h --- gdc-0.17/d/phobos/etc/c/stlsoft/stlsoft_nulldef.h 2004-10-26 02:41:27.000000000 +0200 +++ gdc-0.18/d/phobos/etc/c/stlsoft/stlsoft_nulldef.h 1970-01-01 01:00:00.000000000 +0100 @@ -1,111 +0,0 @@ -/* ///////////////////////////////////////////////////////////////////////////// - * File: stlsoft_nulldef.h - * - * Purpose: Include for defining NULL to be the NULL_v template class. - * - * Created: 17th December 2002 - * Updated: 24th November 2003 - * - * Author: Matthew Wilson, Synesis Software Pty Ltd. - * - * License: (Licensed under the Synesis Software Standard Source License) - * - * Copyright (C) 2002-2003, Synesis Software Pty Ltd. - * - * All rights reserved. - * - * www: http://www.synesis.com.au/stlsoft - * http://www.stlsoft.org/ - * - * email: submissions@stlsoft.org for submissions - * admin@stlsoft.org for other enquiries - * - * Redistribution and use in source and binary forms, with or - * without modification, are permitted provided that the following - * conditions are met: - * - * (i) Redistributions of source code must retain the above - * copyright notice and contact information, this list of - * conditions and the following disclaimer. - * - * (ii) Any derived versions of this software (howsoever modified) - * remain the sole property of Synesis Software. - * - * (iii) Any derived versions of this software (howsoever modified) - * remain subject to all these conditions. - * - * (iv) Neither the name of Synesis Software nor the names of any - * subdivisions, employees or agents of Synesis Software, nor the - * names of any other contributors to this software may be used to - * endorse or promote products derived from this software without - * specific prior written permission. - * - * This source code is provided by Synesis Software "as is" and any - * warranties, whether expressed or implied, including, but not - * limited to, the implied warranties of merchantability and - * fitness for a particular purpose are disclaimed. In no event - * shall the Synesis Software be liable for any direct, indirect, - * incidental, special, exemplary, or consequential damages - * (including, but not limited to, procurement of substitute goods - * or services; loss of use, data, or profits; or business - * interruption) however caused and on any theory of liability, - * whether in contract, strict liability, or tort (including - * negligence or otherwise) arising in any way out of the use of - * this software, even if advised of the possibility of such - * damage. - * - * ////////////////////////////////////////////////////////////////////////// */ - - -#ifndef _STLSOFT_INCL_H_STLSOFT_NULLDEF -#define _STLSOFT_INCL_H_STLSOFT_NULLDEF - -#ifndef __STLSOFT_DOCUMENTATION_SKIP_SECTION -#define _STLSOFT_VER_H_STLSOFT_NULLDEF_MAJOR 1 -#define _STLSOFT_VER_H_STLSOFT_NULLDEF_MINOR 0 -#define _STLSOFT_VER_H_STLSOFT_NULLDEF_REVISION 5 -#define _STLSOFT_VER_H_STLSOFT_NULLDEF_EDIT 8 -#endif /* !__STLSOFT_DOCUMENTATION_SKIP_SECTION */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Includes - */ - -#ifndef _STLSOFT_INCL_H_STLSOFT -# include "stlsoft.h" // Include the STLSoft root header -#endif /* !_STLSOFT_INCL_H_STLSOFT */ -#ifndef _STLSOFT_INCL_H_STLSOFT_NULL -# include "stlsoft_null.h" // Include the STLSoft root header -#endif /* !_STLSOFT_INCL_H_STLSOFT_NULL */ - -#include // Always make sure that this is included, irrespective of - // its potential inclusion within stlsoft.h - -/* ///////////////////////////////////////////////////////////////////////////// - * Definitions - */ - -#ifndef NULL -# ifdef _STLSOFT_COMPILE_VERBOSE -# pragma message("NULL not defined. This is potentially dangerous. You are advised to include its defining header before stlsoft_nulldef.h") -# endif /* _STLSOFT_COMPILE_VERBOSE */ -#endif /* !NULL */ - -#ifdef _STLSOFT_NULL_v_DEFINED -# ifdef __cplusplus -# ifdef NULL -# undef NULL -# endif /* NULL */ - /// \def NULL - /// - /// By including this file, \c NULL is (re-)defined to be stlsoft::NULL_v() - /// which means that any use of \c NULL must be with pointer types. -# define NULL stlsoft_ns_qual(NULL_v)::create() -# endif /* __cplusplus */ -#endif /* _STLSOFT_NULL_v_DEFINED */ - -/* ////////////////////////////////////////////////////////////////////////// */ - -#endif /* !_STLSOFT_INCL_H_STLSOFT_NULLDEF */ - -/* ////////////////////////////////////////////////////////////////////////// */ diff -uNr gdc-0.17/d/phobos/etc/c/stlsoft/stlsoft_null.h gdc-0.18/d/phobos/etc/c/stlsoft/stlsoft_null.h --- gdc-0.17/d/phobos/etc/c/stlsoft/stlsoft_null.h 2004-10-26 02:41:27.000000000 +0200 +++ gdc-0.18/d/phobos/etc/c/stlsoft/stlsoft_null.h 1970-01-01 01:00:00.000000000 +0100 @@ -1,240 +0,0 @@ -/* ///////////////////////////////////////////////////////////////////////////// - * File: stlsoft_null.h - * - * Purpose: NULL_v template class. - * - * Created: 8th September 2002 - * Updated: 24th November 2003 - * - * Author: Matthew Wilson, Synesis Software Pty Ltd. - * - * License: (Licensed under the Synesis Software Standard Source License) - * - * Copyright (C) 2002-2003, Synesis Software Pty Ltd. - * - * All rights reserved. - * - * www: http://www.synesis.com.au/stlsoft - * http://www.stlsoft.org/ - * - * email: submissions@stlsoft.org for submissions - * admin@stlsoft.org for other enquiries - * - * Redistribution and use in source and binary forms, with or - * without modification, are permitted provided that the following - * conditions are met: - * - * (i) Redistributions of source code must retain the above - * copyright notice and contact information, this list of - * conditions and the following disclaimer. - * - * (ii) Any derived versions of this software (howsoever modified) - * remain the sole property of Synesis Software. - * - * (iii) Any derived versions of this software (howsoever modified) - * remain subject to all these conditions. - * - * (iv) Neither the name of Synesis Software nor the names of any - * subdivisions, employees or agents of Synesis Software, nor the - * names of any other contributors to this software may be used to - * endorse or promote products derived from this software without - * specific prior written permission. - * - * This source code is provided by Synesis Software "as is" and any - * warranties, whether expressed or implied, including, but not - * limited to, the implied warranties of merchantability and - * fitness for a particular purpose are disclaimed. In no event - * shall the Synesis Software be liable for any direct, indirect, - * incidental, special, exemplary, or consequential damages - * (including, but not limited to, procurement of substitute goods - * or services; loss of use, data, or profits; or business - * interruption) however caused and on any theory of liability, - * whether in contract, strict liability, or tort (including - * negligence or otherwise) arising in any way out of the use of - * this software, even if advised of the possibility of such - * damage. - * - * ////////////////////////////////////////////////////////////////////////// */ - - -#ifndef _STLSOFT_INCL_H_STLSOFT_NULL -#define _STLSOFT_INCL_H_STLSOFT_NULL - -#ifndef __STLSOFT_DOCUMENTATION_SKIP_SECTION -#define _STLSOFT_VER_H_STLSOFT_NULL_MAJOR 1 -#define _STLSOFT_VER_H_STLSOFT_NULL_MINOR 6 -#define _STLSOFT_VER_H_STLSOFT_NULL_REVISION 1 -#define _STLSOFT_VER_H_STLSOFT_NULL_EDIT 19 -#endif /* !__STLSOFT_DOCUMENTATION_SKIP_SECTION */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Includes - */ - -#ifndef _STLSOFT_INCL_H_STLSOFT -# include "stlsoft.h" // Include the STLSoft root header -#endif /* !_STLSOFT_INCL_H_STLSOFT */ - -/* _STLSOFT_NULL_v_DEFINED */ - -#ifdef _STLSOFT_NULL_v_DEFINED -# undef _STLSOFT_NULL_v_DEFINED -#endif /* _STLSOFT_NULL_v_DEFINED */ - -#define _STLSOFT_NULL_v_DEFINED - -#if defined(__STLSOFT_COMPILER_IS_DMC) -//# if __DMC__ < 0x0832 -# undef _STLSOFT_NULL_v_DEFINED -//# endif /* __DMC__ < 0x0832 */ -#elif defined(__STLSOFT_COMPILER_IS_MSVC) && \ - _MSC_VER < 1310 -# undef _STLSOFT_NULL_v_DEFINED -#elif defined(__STLSOFT_COMPILER_IS_WATCOM) -# undef _STLSOFT_NULL_v_DEFINED -#endif /* compiler */ - -/* _STLSOFT_NULL_v_DEFINED_PTR_TO_MEMBER_SUPPORT */ - -#ifdef _STLSOFT_NULL_v_DEFINED_PTR_TO_MEMBER_SUPPORT -# undef _STLSOFT_NULL_v_DEFINED_PTR_TO_MEMBER_SUPPORT -#endif /* _STLSOFT_NULL_v_DEFINED_PTR_TO_MEMBER_SUPPORT */ - -#define _STLSOFT_NULL_v_DEFINED_PTR_TO_MEMBER_SUPPORT - -#if defined(__STLSOFT_COMPILER_IS_GCC) -# undef _STLSOFT_NULL_v_DEFINED_PTR_TO_MEMBER_SUPPORT -#elif defined(__STLSOFT_COMPILER_IS_MWERKS) -# undef _STLSOFT_NULL_v_DEFINED_PTR_TO_MEMBER_SUPPORT -#endif /* compiler */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace - */ - -#ifndef _STLSOFT_NO_NAMESPACE -namespace stlsoft -{ -#endif /* _STLSOFT_NO_NAMESPACE */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Classes - */ - -#ifdef _STLSOFT_NULL_v_DEFINED - -/// \brief Represents a type that can be an active replacement for NULL -/// -/// This class can act as a replacement for the NULL macro, by being validly -/// assigned to or equated with pointer types only, as in -/// -/// int i = NULL; // error -/// int *p = NULL; // OK -/// -/// if(i == NULL) {} // error -/// if(NULL == i) {} // error -/// -/// if(p == NULL) {} // OK -/// if(NULL == p) {} // OK -/// -/// -/// When used via inclusion of the file stlsoft_nulldef.h, the macro NULL is -/// redefined as NULL_v(), such that expressions containing NULL will be valid -/// against pointers only. -struct NULL_v -{ -// Construction -public: - /// Default constructor - NULL_v() - {} - -/// Static creation -public: - static NULL_v create() - { - return NULL_v(); - } - -// Conversion -public: - /// Implicit conversion operator (convertible to any pointer type) - /// - /// \param T The type of the pointer to which an instance will be convertible - template - operator T *() const - { - return 0; - } - -#ifdef _STLSOFT_NULL_v_DEFINED_PTR_TO_MEMBER_SUPPORT - /// Implicit conversion operator (convertible to any pointer type) - /// - /// \param T The type of the pointer to which an instance will be convertible - template - operator T2 C::*() const - { - return 0; - } -#endif /* _STLSOFT_NULL_v_DEFINED_PTR_TO_MEMBER_SUPPORT */ - - /// Evaluates whether an instance of a type is null - /// - /// \param rhs A reference arbitrary type which will be compared to null - template - ss_bool_t equals(T const &rhs) const - { - return rhs == 0; - } - -// Not to be implemented -private: - void operator &() const; - - NULL_v(NULL_v const &); - NULL_v const &operator =(NULL_v const &); -}; - -#if 1 -/// operator == for NULL_v and an arbitrary type -template -inline ss_bool_t operator ==(NULL_v const &lhs, T const &rhs) -{ - return lhs.equals(rhs); -} - -/// operator == for an arbitrary type and NULL_v -template -inline ss_bool_t operator ==(T const &lhs, NULL_v const &rhs) -{ - return rhs.equals(lhs); -} - -/// operator != for NULL_v and an arbitrary type -template -inline ss_bool_t operator !=(NULL_v const &lhs, T const &rhs) -{ - return !lhs.equals(rhs); -} - -/// operator != for an arbitrary type and NULL_v -template -inline ss_bool_t operator !=(T const &lhs, NULL_v const &rhs) -{ - return !rhs.equals(lhs); -} -#endif /* 0 */ - -#endif /* _STLSOFT_NULL_v_DEFINED */ - -/* ////////////////////////////////////////////////////////////////////////// */ - -#ifndef _STLSOFT_NO_NAMESPACE -} // namespace stlsoft -#endif /* _STLSOFT_NO_NAMESPACE */ - -/* ////////////////////////////////////////////////////////////////////////// */ - -#endif /* !_STLSOFT_INCL_H_STLSOFT_NULL */ - -/* ////////////////////////////////////////////////////////////////////////// */ diff -uNr gdc-0.17/d/phobos/etc/c/stlsoft/stlsoft_null_mutex.h gdc-0.18/d/phobos/etc/c/stlsoft/stlsoft_null_mutex.h --- gdc-0.17/d/phobos/etc/c/stlsoft/stlsoft_null_mutex.h 2004-10-26 02:41:27.000000000 +0200 +++ gdc-0.18/d/phobos/etc/c/stlsoft/stlsoft_null_mutex.h 1970-01-01 01:00:00.000000000 +0100 @@ -1,162 +0,0 @@ -/* //////////////////////////////////////////////////////////////////////////// - * File: stlsoft_null_mutex.h (originally MLMutex.h, ::SynesisStd) - * - * Purpose: Mutual exclusion model class. - * - * Date: 19th December 1997 - * Updated: 2nd July 2003 - * - * Author: Matthew Wilson, Synesis Software Pty Ltd. - * - * License: (Licensed under the Synesis Software Standard Source License) - * - * Copyright (C) 2002-2003, Synesis Software Pty Ltd. - * - * All rights reserved. - * - * www: http://www.synesis.com.au/stlsoft - * http://www.stlsoft.org/ - * - * email: submissions@stlsoft.org for submissions - * admin@stlsoft.org for other enquiries - * - * Redistribution and use in source and binary forms, with or - * without modification, are permitted provided that the following - * conditions are met: - * - * (i) Redistributions of source code must retain the above - * copyright notice and contact information, this list of - * conditions and the following disclaimer. - * - * (ii) Any derived versions of this software (howsoever modified) - * remain the sole property of Synesis Software. - * - * (iii) Any derived versions of this software (howsoever modified) - * remain subject to all these conditions. - * - * (iv) Neither the name of Synesis Software nor the names of any - * subdivisions, employees or agents of Synesis Software, nor the - * names of any other contributors to this software may be used to - * endorse or promote products derived from this software without - * specific prior written permission. - * - * This source code is provided by Synesis Software "as is" and any - * warranties, whether expressed or implied, including, but not - * limited to, the implied warranties of merchantability and - * fitness for a particular purpose are disclaimed. In no event - * shall the Synesis Software be liable for any direct, indirect, - * incidental, special, exemplary, or consequential damages - * (including, but not limited to, procurement of substitute goods - * or services; loss of use, data, or profits; or business - * interruption) however caused and on any theory of liability, - * whether in contract, strict liability, or tort (including - * negligence or otherwise) arising in any way out of the use of - * this software, even if advised of the possibility of such - * damage. - * - * ////////////////////////////////////////////////////////////////////////// */ - - -#ifndef _STLSOFT_INCL_H_STLSOFT_NULL_MUTEX -#define _STLSOFT_INCL_H_STLSOFT_NULL_MUTEX - -#ifndef __STLSOFT_DOCUMENTATION_SKIP_SECTION -#define _STLSOFT_VER_H_STLSOFT_NULL_MUTEX_MAJOR 1 -#define _STLSOFT_VER_H_STLSOFT_NULL_MUTEX_MINOR 1 -#define _STLSOFT_VER_H_STLSOFT_NULL_MUTEX_REVISION 1 -#define _STLSOFT_VER_H_STLSOFT_NULL_MUTEX_EDIT 10 -#endif /* !__STLSOFT_DOCUMENTATION_SKIP_SECTION */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Includes - */ - -#ifndef _STLSOFT_INCL_H_STLSOFT - #include "stlsoft.h" // Include the STLSoft root header -#endif /* !_STLSOFT_INCL_H_STLSOFT */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace - */ - -#ifndef _STLSOFT_NO_NAMESPACE -namespace stlsoft -{ -#endif /* _STLSOFT_NO_NAMESPACE */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Classes - */ - -// class null_mutex - -/// This class provides a null implementation of the mutex model -class null_mutex -{ -public: - typedef null_mutex class_type; - -// Construction -public: - /// Creates an instance of the mutex - null_mutex() stlsoft_throw_0() - {} - -// Operations -public: - /// Acquires a lock on the mutex, pending the thread until the lock is aquired - void lock() stlsoft_throw_0() - {} - /// Releases an aquired lock on the mutex - void unlock() stlsoft_throw_0() - {} - -// Not to be implemented -private: - null_mutex(class_type const &rhs); - null_mutex &operator =(class_type const &rhs); -}; - -/* ///////////////////////////////////////////////////////////////////////////// - * Control shims - */ - -/// \weakgroup concepts STLSoft Concepts - -/// \weakgroup concepts_shims Shims -/// \ingroup concepts - -/// \weakgroup concepts_shims_sync_control Synchronisation Control Shims -/// \ingroup concepts_shims -/// \brief These \ref concepts_shims "shims" control the behaviour of synchronisation objects - -/// \defgroup stlsoft_sync_control_shims Synchronisation Control Shims (STLSoft) -/// \ingroup STLSoft concepts_shims_sync_control -/// \brief These \ref concepts_shims "shims" control the behaviour of synchronisation objects -/// @{ - -/// This control \ref concepts_shims "shim" aquires a lock on the given mutex -/// -/// \param mx The mutex on which to aquire the lock -inline void lock_instance(null_mutex &) -{} - -/// This control ref concepts_shims "shim" releases a lock on the given mutex -/// -/// \param mx The mutex on which to release the lock -inline void unlock_instance(null_mutex &) -{} - -/// @} // end of group stlsoft_sync_control_shims - -/* ////////////////////////////////////////////////////////////////////////// */ - -#ifndef _STLSOFT_NO_NAMESPACE -} // namespace stlsoft -#endif /* _STLSOFT_NO_NAMESPACE */ - -/* ////////////////////////////////////////////////////////////////////////// */ - -#endif /* !_STLSOFT_INCL_H_STLSOFT_NULL_MUTEX */ - -/* ////////////////////////////////////////////////////////////////////////// */ diff -uNr gdc-0.17/d/phobos/etc/c/stlsoft/stlsoft_static_initialisers.h gdc-0.18/d/phobos/etc/c/stlsoft/stlsoft_static_initialisers.h --- gdc-0.17/d/phobos/etc/c/stlsoft/stlsoft_static_initialisers.h 2004-10-26 02:41:27.000000000 +0200 +++ gdc-0.18/d/phobos/etc/c/stlsoft/stlsoft_static_initialisers.h 1970-01-01 01:00:00.000000000 +0100 @@ -1,255 +0,0 @@ -/* ///////////////////////////////////////////////////////////////////////////// - * File: stlsoft_static_initialisers.h (formerly MLClsCtr.h, ::SynesisStd) - * - * Purpose: Class constructor. - * - * Created: 17th February 1997 - * Updated: 26th November 2003 - * - * Author: Matthew Wilson, Synesis Software Pty Ltd. - * - * License: (Licensed under the Synesis Software Standard Source License) - * - * Copyright (C) 2002-2003, Synesis Software Pty Ltd. - * - * All rights reserved. - * - * www: http://www.synesis.com.au/stlsoft - * http://www.stlsoft.org/ - * - * email: submissions@stlsoft.org for submissions - * admin@stlsoft.org for other enquiries - * - * Redistribution and use in source and binary forms, with or - * without modification, are permitted provided that the following - * conditions are met: - * - * (i) Redistributions of source code must retain the above - * copyright notice and contact information, this list of - * conditions and the following disclaimer. - * - * (ii) Any derived versions of this software (howsoever modified) - * remain the sole property of Synesis Software. - * - * (iii) Any derived versions of this software (howsoever modified) - * remain subject to all these conditions. - * - * (iv) Neither the name of Synesis Software nor the names of any - * subdivisions, employees or agents of Synesis Software, nor the - * names of any other contributors to this software may be used to - * endorse or promote products derived from this software without - * specific prior written permission. - * - * This source code is provided by Synesis Software "as is" and any - * warranties, whether expressed or implied, including, but not - * limited to, the implied warranties of merchantability and - * fitness for a particular purpose are disclaimed. In no event - * shall the Synesis Software be liable for any direct, indirect, - * incidental, special, exemplary, or consequential damages - * (including, but not limited to, procurement of substitute goods - * or services; loss of use, data, or profits; or business - * interruption) however caused and on any theory of liability, - * whether in contract, strict liability, or tort (including - * negligence or otherwise) arising in any way out of the use of - * this software, even if advised of the possibility of such - * damage. - * - * ////////////////////////////////////////////////////////////////////////// */ - - -#ifndef _STLSOFT_INCL_H_STLSOFT_STATIC_INITIALISERS -#define _STLSOFT_INCL_H_STLSOFT_STATIC_INITIALISERS - -#ifndef __STLSOFT_DOCUMENTATION_SKIP_SECTION -# define _STLSOFT_VER_H_STLSOFT_STATIC_INITIALISERS_MAJOR 1 -# define _STLSOFT_VER_H_STLSOFT_STATIC_INITIALISERS_MINOR 8 -# define _STLSOFT_VER_H_STLSOFT_STATIC_INITIALISERS_REVISION 2 -# define _STLSOFT_VER_H_STLSOFT_STATIC_INITIALISERS_EDIT 191 -#endif /* !__STLSOFT_DOCUMENTATION_SKIP_SECTION */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Includes - */ - -#ifndef _STLSOFT_INCL_H_STLSOFT -# include "stlsoft.h" // Include the STLSoft root header -#endif /* !_STLSOFT_INCL_H_STLSOFT */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace - */ - -#ifndef _STLSOFT_NO_NAMESPACE -namespace stlsoft -{ -#endif /* _STLSOFT_NO_NAMESPACE */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Classes - */ - -#if 0 -class method_constructor -{ -public: - template - method_constructor(T const &t, void (T::*const fn)()) - { - (t.*fn)(); - } - template - method_constructor(T const &t, R (T::*const fn)()) - { - (t.*fn)(); - } -}; -#endif /* 0 */ - -/// static_initialiser -/// -/// Initialises any non-class function or type -class static_initialiser -{ -public: - typedef static_initialiser class_type; - -/// \name Constructors -//@{ -public: -#ifdef __STLSOFT_CF_MEMBER_TEMPLATE_CTOR_SUPPORT - template - static_initialiser(T const &/* t */) - {} - template - static_initialiser(T const * /* pt */) - {} -#else - static_initialiser(int /* t */) - {} - static_initialiser(void const * /* pt */) - {} -#endif // __STLSOFT_CF_MEMBER_TEMPLATE_CTOR_SUPPORT -//@} - -/// \name Not to be implemented -//@{ -private: - static_initialiser(class_type const &); - static_initialiser &operator =(class_type const &); - -#ifdef __STLSOFT_COMPILER_IS_COMO - void *operator new(ss_size_t) stlsoft_throw_0() - { - return 0; - } -#else /* ? __STLSOFT_COMPILER_IS_COMO */ - void *operator new(ss_size_t) stlsoft_throw_0(); -#endif /* __STLSOFT_COMPILER_IS_COMO */ - void operator delete(void *) - {} -//@} -}; - - -class api_constructor -{ -/// \name Constructors -//@{ -public: - api_constructor(void (*pfnInit)(), void (*pfnUninit)()) - : m_pfnUninit(pfnUninit) - { - if(NULL != pfnInit) - { - (*pfnInit)(); - } - } - ~api_constructor() - { - if(NULL != m_pfnUninit) - { - (*m_pfnUninit)(); - } - } -//@} - -/// \name Members -//@{ -private: - void (*m_pfnUninit)(void); -//@} - -/// \name Not to be implemented -//@{ -private: - api_constructor(api_constructor const &); - api_constructor &operator =(api_constructor const &); - -#ifdef __STLSOFT_COMPILER_IS_COMO - void *operator new(ss_size_t) stlsoft_throw_0() - { - return 0; - } -#else /* ? __STLSOFT_COMPILER_IS_COMO */ - void *operator new(ss_size_t) stlsoft_throw_0(); -#endif /* __STLSOFT_COMPILER_IS_COMO */ - void operator delete(void *) - {} -//@} -}; - -template -class class_constructor - : protected api_constructor -{ -/// \name Member types -//@{ -public: - typedef void (*class_init_fn_t)(); - typedef void (*class_uninit_fn_t)(); - -//@} - -/// \name Constructors -//@{ -public: - ss_explicit_k class_constructor() - : api_constructor(&T::class_init, &T::class_uninit) - {} - - ss_explicit_k class_constructor( class_init_fn_t pfnInit - , class_uninit_fn_t pfnUninit) - : api_constructor(pfnInit, pfnUninit) - {} -//@} - -/// \name Not to be implemented -//@{ -private: - class_constructor(class_constructor const &); - class_constructor &operator =(class_constructor const &); - -#ifdef __STLSOFT_COMPILER_IS_COMO - void *operator new(ss_size_t) stlsoft_throw_0() - { - return 0; - } -#else /* ? __STLSOFT_COMPILER_IS_COMO */ - void *operator new(ss_size_t) stlsoft_throw_0(); -#endif /* __STLSOFT_COMPILER_IS_COMO */ - void operator delete(void *) - {} -//@} -}; - -/* ////////////////////////////////////////////////////////////////////////// */ - -#ifndef _STLSOFT_NO_NAMESPACE -} // namespace stlsoft -#endif /* _STLSOFT_NO_NAMESPACE */ - -/* ////////////////////////////////////////////////////////////////////////// */ - -#endif /* !_STLSOFT_INCL_H_STLSOFT_STATIC_INITIALISERS */ - -/* ////////////////////////////////////////////////////////////////////////// */ diff -uNr gdc-0.17/d/phobos/etc/c/stlsoft/unixstl_current_directory.h gdc-0.18/d/phobos/etc/c/stlsoft/unixstl_current_directory.h --- gdc-0.17/d/phobos/etc/c/stlsoft/unixstl_current_directory.h 2004-10-26 02:41:27.000000000 +0200 +++ gdc-0.18/d/phobos/etc/c/stlsoft/unixstl_current_directory.h 1970-01-01 01:00:00.000000000 +0100 @@ -1,251 +0,0 @@ -/* ///////////////////////////////////////////////////////////////////////////// - * File: unixstl_current_directory.h - * - * Purpose: Simple class that gets, and makes accessible, the current - * directory. - * - * Created: 1st November 2003 - * Updated: 2nd November 2003 - * - * Author: Matthew Wilson, Synesis Software Pty Ltd. - * - * License: (Licensed under the Synesis Software Standard Source License) - * - * Copyright (C) 2002-2003, Synesis Software Pty Ltd. - * - * All rights reserved. - * - * www: http://www.synesis.com.au/unixstl - * http://www.unixstl.org/ - * - * email: submissions@unixstl.org for submissions - * admin@unixstl.org for other enquiries - * - * Redistribution and use in source and binary forms, with or - * without modification, are permitted provided that the following - * conditions are met: - * - * (i) Redistributions of source code must retain the above - * copyright notice and contact information, this list of - * conditions and the following disclaimer. - * - * (ii) Any derived versions of this software (howsoever modified) - * remain the sole property of Synesis Software. - * - * (iii) Any derived versions of this software (howsoever modified) - * remain subject to all these conditions. - * - * (iv) Neither the name of Synesis Software nor the names of any - * subdivisions, employees or agents of Synesis Software, nor the - * names of any other contributors to this software may be used to - * endorse or promote products derived from this software without - * specific prior written permission. - * - * This source code is provided by Synesis Software "as is" and any - * warranties, whether expressed or implied, including, but not - * limited to, the implied warranties of merchantability and - * fitness for a particular purpose are disclaimed. In no event - * shall the Synesis Software be liable for any direct, indirect, - * incidental, special, exemplary, or consequential damages - * (including, but not limited to, procurement of substitute goods - * or services; loss of use, data, or profits; or business - * interruption) however caused and on any theory of liability, - * whether in contract, strict liability, or tort (including - * negligence or otherwise) arising in any way out of the use of - * this software, even if advised of the possibility of such - * damage. - * - * ////////////////////////////////////////////////////////////////////////// */ - - -#ifndef _UNIXSTL_INCL_H_UNIXSTL_CURRENT_DIRECTORY -#define _UNIXSTL_INCL_H_UNIXSTL_CURRENT_DIRECTORY - -#ifndef __STLSOFT_DOCUMENTATION_SKIP_SECTION -#define _UNIXSTL_VER_H_UNIXSTL_CURRENT_DIRECTORY_MAJOR 1 -#define _UNIXSTL_VER_H_UNIXSTL_CURRENT_DIRECTORY_MINOR 0 -#define _UNIXSTL_VER_H_UNIXSTL_CURRENT_DIRECTORY_REVISION 2 -#define _UNIXSTL_VER_H_UNIXSTL_CURRENT_DIRECTORY_EDIT 2 -#endif /* !__STLSOFT_DOCUMENTATION_SKIP_SECTION */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Includes - */ - -#ifndef _UNIXSTL_INCL_H_UNIXSTL -# include "unixstl.h" // Include the WinSTL root header -#endif /* !_UNIXSTL_INCL_H_UNIXSTL */ -#ifndef _UNIXSTL_INCL_H_UNIXSTL_FILESYSTEM_TRAITS -# include "unixstl_filesystem_traits.h" // file_traits -#endif /* !_UNIXSTL_INCL_H_UNIXSTL_FILESYSTEM_TRAITS */ -#include - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace - */ - -#ifndef _UNIXSTL_NO_NAMESPACE -# ifdef _STLSOFT_NO_NAMESPACE -/* There is no stlsoft namespace, so must define ::unixstl */ -namespace unixstl -{ -# else -/* Define stlsoft::unixstl_project */ - -namespace stlsoft -{ - -namespace unixstl_project -{ - -# endif /* _STLSOFT_NO_NAMESPACE */ -#endif /* !_UNIXSTL_NO_NAMESPACE */ - -/* ////////////////////////////////////////////////////////////////////////// */ - -/// \weakgroup libraries STLSoft Libraries -/// \brief The individual libraries - -/// \weakgroup libraries_filesystem File-System Library -/// \ingroup libraries -/// \brief This library provides facilities for defining and manipulating file-system objects - -/// \weakgroup unixstl_filesystem_library File-System Library (WinSTL) -/// \ingroup WinSTL libraries_filesystem -/// \brief This library provides facilities for defining and manipulating file-system objects for the Win32 API -/// @{ - -/* ///////////////////////////////////////////////////////////////////////////// - * basic_current_directory - * - * This class wraps the GetCurrentDirectory() API function, and effectively acts - * as a C-string of its value. - */ - -/// Represents the current directory -/// -/// \param C The character type -/// \param T The traits type. On translators that support default template arguments, this defaults to filesystem_traits -template< ss_typename_param_k C -#ifdef __STLSOFT_CF_TEMPLATE_CLASS_DEFAULT_CLASS_ARGUMENT_SUPPORT - , ss_typename_param_k T = filesystem_traits -#else - , ss_typename_param_k T /* = filesystem_traits */ -#endif /* __STLSOFT_CF_TEMPLATE_CLASS_DEFAULT_CLASS_ARGUMENT_SUPPORT */ - > -class basic_current_directory -{ -public: - /// The char type - typedef C char_type; - /// The traits type - typedef T traits_type; - /// The current parameterisation of the type - typedef basic_current_directory class_type; - /// The size type - typedef us_size_t size_type; - -// Construction -public: - /// Default constructor - basic_current_directory(); - -// Operations -public: - /// Gets the current directory into the given buffer - static size_type get_path(char_type *buffer, size_type cchBuffer); - -// Attributes -public: - /// Returns a non-mutable (const) pointer to the path - char_type const *get_path() const; - /// Returns the length of the converted path - size_type length() const; - -// Conversions -public: - /// Implicit conversion to a non-mutable (const) pointer to the path - operator char_type const *() const - { - return get_path(); - } - -// Members -private: - char_type m_dir[1 + PATH_MAX]; - size_type const m_len; - -// Not to be implemented -private: - basic_current_directory(const class_type &); - basic_current_directory &operator =(const class_type &); -}; - -/* ///////////////////////////////////////////////////////////////////////////// - * Typedefs for commonly encountered types - */ - -/// Instantiation of the basic_current_directory template for the ANSI character type \c char -typedef basic_current_directory > current_directory_a; -/// Instantiation of the basic_current_directory template for the Unicode character type \c wchar_t -typedef basic_current_directory > current_directory_w; - -/* ///////////////////////////////////////////////////////////////////////////// - * Implementation - */ - -#ifndef __STLSOFT_DOCUMENTATION_SKIP_SECTION - -template< ss_typename_param_k C - , ss_typename_param_k T - > -inline basic_current_directory::basic_current_directory() - : m_len(get_path(m_dir, unixstl_num_elements(m_dir))) -{} - -template< ss_typename_param_k C - , ss_typename_param_k T - > -inline /* static */ ss_typename_type_k basic_current_directory::size_type basic_current_directory::get_path(ss_typename_type_k basic_current_directory::char_type *buffer, ss_typename_type_k basic_current_directory::size_type cchBuffer) -{ - return static_cast(traits_type::get_current_directory(cchBuffer, buffer)); -} - -template< ss_typename_param_k C - , ss_typename_param_k T - > -inline ss_typename_type_k basic_current_directory::char_type const *basic_current_directory::get_path() const -{ - return m_dir; -} - -template< ss_typename_param_k C - , ss_typename_param_k T - > -inline ss_typename_type_k basic_current_directory::size_type basic_current_directory::length() const -{ - return m_len; -} - -#endif /* !__STLSOFT_DOCUMENTATION_SKIP_SECTION */ - -/* ////////////////////////////////////////////////////////////////////////// */ - -/// @} // end of group unixstl_filesystem_library - -/* ////////////////////////////////////////////////////////////////////////// */ - -#ifndef _UNIXSTL_NO_NAMESPACE -# ifdef _STLSOFT_NO_NAMESPACE -} // namespace unixstl -# else -} // namespace unixstl_project -} // namespace stlsoft -# endif /* _STLSOFT_NO_NAMESPACE */ -#endif /* !_UNIXSTL_NO_NAMESPACE */ - -/* ////////////////////////////////////////////////////////////////////////// */ - -#endif /* _UNIXSTL_INCL_H_UNIXSTL_CURRENT_DIRECTORY */ - -/* ////////////////////////////////////////////////////////////////////////// */ diff -uNr gdc-0.17/d/phobos/etc/c/stlsoft/unixstl_current_directory_scope.h gdc-0.18/d/phobos/etc/c/stlsoft/unixstl_current_directory_scope.h --- gdc-0.17/d/phobos/etc/c/stlsoft/unixstl_current_directory_scope.h 2004-10-26 02:41:27.000000000 +0200 +++ gdc-0.18/d/phobos/etc/c/stlsoft/unixstl_current_directory_scope.h 1970-01-01 01:00:00.000000000 +0100 @@ -1,313 +0,0 @@ -/* ///////////////////////////////////////////////////////////////////////////// - * File: unixstl_current_directory_scope.h (formerly MLPwdScp.h, ::SynesisStd) - * - * Purpose: Current working directory scoping class. - * - * Created: 12th November 1998 - * Updated: 2nd November 2003 - * - * Author: Matthew Wilson, Synesis Software Pty Ltd. - * - * License: (Licensed under the Synesis Software Standard Source License) - * - * Copyright (C) 2002-2003, Synesis Software Pty Ltd. - * - * All rights reserved. - * - * www: http://www.synesis.com.au/unixstl - * http://www.unixstl.org/ - * - * email: submissions@unixstl.org for submissions - * admin@unixstl.org for other enquiries - * - * Redistribution and use in source and binary forms, with or - * without modification, are permitted provided that the following - * conditions are met: - * - * (i) Redistributions of source code must retain the above - * copyright notice and contact information, this list of - * conditions and the following disclaimer. - * - * (ii) Any derived versions of this software (howsoever modified) - * remain the sole property of Synesis Software. - * - * (iii) Any derived versions of this software (howsoever modified) - * remain subject to all these conditions. - * - * (iv) Neither the name of Synesis Software nor the names of any - * subdivisions, employees or agents of Synesis Software, nor the - * names of any other contributors to this software may be used to - * endorse or promote products derived from this software without - * specific prior written permission. - * - * This source code is provided by Synesis Software "as is" and any - * warranties, whether expressed or implied, including, but not - * limited to, the implied warranties of merchantability and - * fitness for a particular purpose are disclaimed. In no event - * shall the Synesis Software be liable for any direct, indirect, - * incidental, special, exemplary, or consequential damages - * (including, but not limited to, procurement of substitute goods - * or services; loss of use, data, or profits; or business - * interruption) however caused and on any theory of liability, - * whether in contract, strict liability, or tort (including - * negligence or otherwise) arising in any way out of the use of - * this software, even if advised of the possibility of such - * damage. - * - * ////////////////////////////////////////////////////////////////////////// */ - - -#ifndef _UNIXSTL_INCL_H_UNIXSTL_CURRENT_DIRECTORY_SCOPE -#define _UNIXSTL_INCL_H_UNIXSTL_CURRENT_DIRECTORY_SCOPE - -#ifndef __STLSOFT_DOCUMENTATION_SKIP_SECTION -#define _UNIXSTL_VER_H_UNIXSTL_CURRENT_DIRECTORY_SCOPE_MAJOR 2 -#define _UNIXSTL_VER_H_UNIXSTL_CURRENT_DIRECTORY_SCOPE_MINOR 4 -#define _UNIXSTL_VER_H_UNIXSTL_CURRENT_DIRECTORY_SCOPE_REVISION 2 -#define _UNIXSTL_VER_H_UNIXSTL_CURRENT_DIRECTORY_SCOPE_EDIT 51 -#endif /* !__STLSOFT_DOCUMENTATION_SKIP_SECTION */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Includes - */ - -#ifndef _UNIXSTL_INCL_H_WINSTL -# include "unixstl.h" // Include the UNIXSTL root header -#endif /* !_UNIXSTL_INCL_H_WINSTL */ -#ifndef _UNIXSTL_INCL_H_UNIXSTL_FILESYSTEM_TRAITS -# include "unixstl_filesystem_traits.h" // file_traits -#endif /* !_UNIXSTL_INCL_H_UNIXSTL_FILESYSTEM_TRAITS */ -#ifndef _STLSOFT_INCL_H_STLSOFT_STRING_ACCESS -# include "stlsoft_string_access.h" // stlsoft::c_str_ptr -#endif /* !_STLSOFT_INCL_H_STLSOFT_STRING_ACCESS */ -#ifndef _UNIXSTL_INCL_H_UNIXSTL_STRING_ACCESS -# include "unixstl_string_access.h" // unixstl::c_str_ptr -#endif /* !_UNIXSTL_INCL_H_UNIXSTL_STRING_ACCESS */ -#include - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace - */ - -#ifndef _UNIXSTL_NO_NAMESPACE -# ifdef _STLSOFT_NO_NAMESPACE -/* There is no stlsoft namespace, so must define ::unixstl */ -namespace unixstl -{ -# else -/* Define stlsoft::unixstl_project */ - -namespace stlsoft -{ - -namespace unixstl_project -{ - -# endif /* _STLSOFT_NO_NAMESPACE */ -#endif /* !_UNIXSTL_NO_NAMESPACE */ - -stlsoft_ns_using(c_str_ptr) - -/* ////////////////////////////////////////////////////////////////////////// */ - -/// \weakgroup libraries STLSoft Libraries -/// \brief The individual libraries - -/// \weakgroup libraries_filesystem File-System Library -/// \ingroup libraries -/// \brief This library provides facilities for defining and manipulating file-system objects - -/// \defgroup unixstl_filesystem_library File-System Library (UNIXSTL) -/// \ingroup UNIXSTL libraries_filesystem -/// \brief This library provides facilities for defining and manipulating UNIX file-system objects -/// @{ - -/* ///////////////////////////////////////////////////////////////////////////// - * basic_current_directory_scope - * - * This class pushes the given directory as the current directory upon - * construction, and pops back to the original at destruction. - */ - -/// \brief Current directory scoping class -/// -/// This class scopes the process's current directory, by changing to the path -/// given in the constructor, and then, if that succeeded, changing back in the -/// destructor -/// -/// \param C The character type (e.g. \c char, \c wchar_t) -/// \param T The file-system traits. In translators that support default template parameters that defaults to \c filesystem_traits - -template< ss_typename_param_k C -#ifdef __STLSOFT_CF_TEMPLATE_CLASS_DEFAULT_CLASS_ARGUMENT_SUPPORT - , ss_typename_param_k T = filesystem_traits -#else - , ss_typename_param_k T /* = filesystem_traits */ -#endif /* __STLSOFT_CF_TEMPLATE_CLASS_DEFAULT_CLASS_ARGUMENT_SUPPORT */ - > -class basic_current_directory_scope -{ -public: - typedef C char_type; /*!< The character type */ -private: - typedef T traits_type; - typedef basic_current_directory_scope class_type; - -// Construction -public: - /// \brief Constructs a scope instance and changes to the given directory - /// - /// \param dir The name of the directory to change the current directory to - ss_explicit_k basic_current_directory_scope(char_type const *dir); -#if defined(__STLSOFT_CF_MEMBER_TEMPLATE_CTOR_SUPPORT) - /// \brief Constructs a scope instance and changes to the given directory - /// - /// \param dir The name of the directory to change the current directory to - template - ss_explicit_k basic_current_directory_scope(S const &dir) - { - _init(c_str_ptr(dir)); - } -#endif /* __STLSOFT_CF_MEMBER_TEMPLATE_CTOR_SUPPORT */ - /// \brief Returns the current directory to its original location - ~basic_current_directory_scope() unixstl_throw_0(); - -// Conversions -public: - /// Returns a C-string pointer to the original directory - operator char_type const *() const; - -/// \name State -/// @{ -private: -#ifdef STLSOFT_CF_OPERATOR_BOOL_AS_OPERATOR_POINTER_TO_MEMBER_SUPPORT - /// An opaque type to use for boolean evaluation - struct boolean { int i; }; - typedef int boolean::*boolean_t; -#else /* ? STLSOFT_CF_OPERATOR_BOOL_AS_OPERATOR_POINTER_TO_MEMBER_SUPPORT */ - typedef us_bool_t boolean_t; -#endif /* STLSOFT_CF_OPERATOR_BOOL_AS_OPERATOR_POINTER_TO_MEMBER_SUPPORT */ -public: - /// Indicates whether the construction was successful - /// - /// \retval true The scope instance was successfully constructed and the current directory changed as per the constructor argument - /// \retval false The scope instance was not successfully constructed, and the current directory was unchanged. - operator boolean_t () const; -#ifndef STLSOFT_CF_OPERATOR_NOT_VIA_OPERATOR_POINTER_TO_MEMBER_SUPPORT - /// Indicates whether the construction failed - /// - /// This method is the opposite of operator us_bool_t(), and the return values are inverted. - us_bool_t operator !() const; -#endif /* !STLSOFT_CF_OPERATOR_NOT_VIA_OPERATOR_POINTER_TO_MEMBER_SUPPORT */ - -/// @} - -// Implementation -private: - void _init(char_type const *dir); - -// Members -private: - char_type m_previous[1 + PATH_MAX]; - -// Not to be implemented -private: - basic_current_directory_scope(); - basic_current_directory_scope(class_type const &); - class_type const &operator =(class_type const &); -}; - -/* ///////////////////////////////////////////////////////////////////////////// - * Typedefs for commonly encountered types - */ - -/// Instantiation of the basic_current_directory_scope template for the ANSI character type \c char -typedef basic_current_directory_scope > current_directory_scope_a; -/// Instantiation of the basic_current_directory_scope template for the Unicode character type \c wchar_t -typedef basic_current_directory_scope > current_directory_scope_w; - -/* ///////////////////////////////////////////////////////////////////////////// - * Implementation - */ - -template< ss_typename_param_k C - , ss_typename_param_k T - > -inline void basic_current_directory_scope::_init(ss_typename_type_k basic_current_directory_scope::char_type const *dir) -{ - if( 0 == traits_type::get_current_directory(unixstl_num_elements(m_previous), m_previous) || - !traits_type::set_current_directory(dir)) - { - m_previous[0] = '\0'; - } -} - -template< ss_typename_param_k C - , ss_typename_param_k T - > -inline basic_current_directory_scope::basic_current_directory_scope(ss_typename_type_k basic_current_directory_scope::char_type const *dir) -{ - _init(c_str_ptr(dir)); -} - -template< ss_typename_param_k C - , ss_typename_param_k T - > -inline basic_current_directory_scope::~basic_current_directory_scope() unixstl_throw_0() -{ - if(m_previous[0] != '\0') - { - traits_type::set_current_directory(m_previous); - } -} - -template< ss_typename_param_k C - , ss_typename_param_k T - > -inline basic_current_directory_scope::operator ss_typename_type_k basic_current_directory_scope::char_type const *() const -{ - return m_previous; -} - -template< ss_typename_param_k C - , ss_typename_param_k T - > -inline basic_current_directory_scope::operator ss_typename_type_k basic_current_directory_scope::boolean_t () const -{ -#ifdef STLSOFT_CF_OPERATOR_BOOL_AS_OPERATOR_POINTER_TO_MEMBER_SUPPORT - return m_previous[0] != '\0' ? &boolean::i : NULL; -#else /* ? STLSOFT_CF_OPERATOR_BOOL_AS_OPERATOR_POINTER_TO_MEMBER_SUPPORT */ - return m_previous[0] != '\0'; -#endif /* STLSOFT_CF_OPERATOR_BOOL_AS_OPERATOR_POINTER_TO_MEMBER_SUPPORT */ -} - -#ifndef STLSOFT_CF_OPERATOR_NOT_VIA_OPERATOR_POINTER_TO_MEMBER_SUPPORT -template< ss_typename_param_k C - , ss_typename_param_k T - > -inline us_bool_t basic_current_directory_scope::operator !() const -{ - return !operator us_bool_t(); -} -#endif /* !STLSOFT_CF_OPERATOR_NOT_VIA_OPERATOR_POINTER_TO_MEMBER_SUPPORT */ - -/* ////////////////////////////////////////////////////////////////////////// */ - -/// @} // end of group unixstl_filesystem_library - -/* ////////////////////////////////////////////////////////////////////////// */ - -#ifndef _UNIXSTL_NO_NAMESPACE -# ifdef _STLSOFT_NO_NAMESPACE -} // namespace unixstl -# else -} // namespace unixstl_project -} // namespace stlsoft -# endif /* _STLSOFT_NO_NAMESPACE */ -#endif /* !_UNIXSTL_NO_NAMESPACE */ - -/* ////////////////////////////////////////////////////////////////////////// */ - -#endif /* _UNIXSTL_INCL_H_UNIXSTL_CURRENT_DIRECTORY_SCOPE */ - -/* ////////////////////////////////////////////////////////////////////////// */ diff -uNr gdc-0.17/d/phobos/etc/c/stlsoft/unixstl_environment_variable.h gdc-0.18/d/phobos/etc/c/stlsoft/unixstl_environment_variable.h --- gdc-0.17/d/phobos/etc/c/stlsoft/unixstl_environment_variable.h 2004-10-26 02:41:27.000000000 +0200 +++ gdc-0.18/d/phobos/etc/c/stlsoft/unixstl_environment_variable.h 1970-01-01 01:00:00.000000000 +0100 @@ -1,255 +0,0 @@ -/* ///////////////////////////////////////////////////////////////////////////// - * File: unixstl_environment_variable.h - * - * Purpose: Simple class that provides access to an environment variable. - * - * Created: 2nd November 2003 - * Updated: 2nd November 2003 - * - * Author: Matthew Wilson, Synesis Software Pty Ltd. - * - * License: (Licensed under the Synesis Software Standard Source License) - * - * Copyright (C) 2002-2003, Synesis Software Pty Ltd. - * - * All rights reserved. - * - * www: http://www.synesis.com.au/unixstl - * http://www.unixstl.org/ - * - * email: submissions@unixstl.org for submissions - * admin@unixstl.org for other enquiries - * - * Redistribution and use in source and binary forms, with or - * without modification, are permitted provided that the following - * conditions are met: - * - * (i) Redistributions of source code must retain the above - * copyright notice and contact information, this list of - * conditions and the following disclaimer. - * - * (ii) Any derived versions of this software (howsoever modified) - * remain the sole property of Synesis Software. - * - * (iii) Any derived versions of this software (howsoever modified) - * remain subject to all these conditions. - * - * (iv) Neither the name of Synesis Software nor the names of any - * subdivisions, employees or agents of Synesis Software, nor the - * names of any other contributors to this software may be used to - * endorse or promote products derived from this software without - * specific prior written permission. - * - * This source code is provided by Synesis Software "as is" and any - * warranties, whether expressed or implied, including, but not - * limited to, the implied warranties of merchantability and - * fitness for a particular purpose are disclaimed. In no event - * shall the Synesis Software be liable for any direct, indirect, - * incidental, special, exemplary, or consequential damages - * (including, but not limited to, procurement of substitute goods - * or services; loss of use, data, or profits; or business - * interruption) however caused and on any theory of liability, - * whether in contract, strict liability, or tort (including - * negligence or otherwise) arising in any way out of the use of - * this software, even if advised of the possibility of such - * damage. - * - * ////////////////////////////////////////////////////////////////////////// */ - - -#ifndef _UNIXSTL_INCL_H_UNIXSTL_ENVIRONMENT_VARIABLE -#define _UNIXSTL_INCL_H_UNIXSTL_ENVIRONMENT_VARIABLE - -#ifndef __STLSOFT_DOCUMENTATION_SKIP_SECTION -#define _UNIXSTL_VER_H_UNIXSTL_ENVIRONMENT_VARIABLE_MAJOR 1 -#define _UNIXSTL_VER_H_UNIXSTL_ENVIRONMENT_VARIABLE_MINOR 3 -#define _UNIXSTL_VER_H_UNIXSTL_ENVIRONMENT_VARIABLE_REVISION 1 -#define _UNIXSTL_VER_H_UNIXSTL_ENVIRONMENT_VARIABLE_EDIT 14 -#endif /* !__STLSOFT_DOCUMENTATION_SKIP_SECTION */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Includes - */ - -#ifndef _UNIXSTL_INCL_H_UNIXSTL -# include "unixstl.h" // Include the WinSTL root header -#endif /* !_UNIXSTL_INCL_H_UNIXSTL */ -#ifndef _UNIXSTL_INCL_H_UNIXSTL_SYSTEM_VERSION -# include "unixstl_filesystem_traits.h" // Include the WinSTL get_environment_variable -#endif /* !_UNIXSTL_INCL_H_UNIXSTL_SYSTEM_VERSION */ -#ifndef _STLSOFT_INCL_H_STLSOFT_STRING_ACCESS -# include "stlsoft_string_access.h" // stlsoft::c_str_ptr -#endif /* !_STLSOFT_INCL_H_STLSOFT_STRING_ACCESS */ -#ifndef _UNIXSTL_INCL_H_UNIXSTL_STRING_ACCESS -# include "unixstl_string_access.h" // unixstl::c_str_ptr -#endif /* !_UNIXSTL_INCL_H_UNIXSTL_STRING_ACCESS */ -#ifndef _STLSOFT_INCL_H_STLSOFT_AUTO_BUFFER -# include "stlsoft_auto_buffer.h" // stlsoft::auto_buffer -#endif /* !_STLSOFT_INCL_H_STLSOFT_AUTO_BUFFER */ -#ifndef _STLSOFT_INCL_H_STLSOFT_MALLOC_ALLOCATOR -# include "stlsoft_malloc_allocator.h" // malloc_allocator -#endif /* _STLSOFT_INCL_H_STLSOFT_MALLOC_ALLOCATOR */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace - */ - -#ifndef _UNIXSTL_NO_NAMESPACE -# ifdef _STLSOFT_NO_NAMESPACE -/* There is no stlsoft namespace, so must define ::unixstl */ -namespace unixstl -{ -# else -/* Define stlsoft::unixstl_project */ - -namespace stlsoft -{ - -namespace unixstl_project -{ - -# endif /* _STLSOFT_NO_NAMESPACE */ -#endif /* !_UNIXSTL_NO_NAMESPACE */ - -stlsoft_ns_using(c_str_ptr) - -/* ////////////////////////////////////////////////////////////////////////// */ - -/// \weakgroup libraries STLSoft Libraries -/// \brief The individual libraries - -/// \weakgroup libraries_system System Library -/// \ingroup libraries -/// \brief This library provides facilities for accessing system attributes - -/// \defgroup unixstl_system_library System Library (WinSTL) -/// \ingroup WinSTL libraries_system -/// \brief This library provides facilities for accessing Win32 system attributes -/// @{ - -/* ///////////////////////////////////////////////////////////////////////////// - * basic_environment_variable - * - * This class converts a relative path to an absolute one, and effectively acts - * as a C-string of its value. - */ - -/// Represents an environment variable -/// -/// \param C The character type -/// \param T The traits type. On translators that support default template arguments, this defaults to filesystem_traits -template< ss_typename_param_k C -#ifdef __STLSOFT_CF_TEMPLATE_CLASS_DEFAULT_CLASS_ARGUMENT_SUPPORT - , ss_typename_param_k T = filesystem_traits -#else - , ss_typename_param_k T /* = filesystem_traits */ -#endif /* __STLSOFT_CF_TEMPLATE_CLASS_DEFAULT_CLASS_ARGUMENT_SUPPORT */ - > -class basic_environment_variable -{ -public: - /// The char type - typedef C char_type; - /// The traits type - typedef T traits_type; - /// The current parameterisation of the type - typedef basic_environment_variable class_type; - /// The size type - typedef size_t size_type; - -// Construction -public: - /// Create an instance representing the given environment variable - ss_explicit_k basic_environment_variable(char_type const *name) - : m_buffer(1 + traits_type::get_environment_variable(name, 0, 0)) - { - if( 0 == traits_type::get_environment_variable(name, m_buffer, m_buffer.size()) && - 0 != m_buffer.size()) - { - m_buffer[0] = 0; - } - } -#ifdef __STLSOFT_CF_MEMBER_TEMPLATE_CTOR_SUPPORT - /// Create an instance representing the given environment variable - template - ss_explicit_k basic_environment_variable(S const &name) - : m_buffer(1 + traits_type::get_environment_variable(c_str_ptr(name), 0, 0)) - { - if( 0 == traits_type::get_environment_variable(c_str_ptr(name), m_buffer, m_buffer.size()) && - 0 != m_buffer.size()) - { - m_buffer[0] = 0; - } - } -#endif /* __STLSOFT_CF_MEMBER_TEMPLATE_CTOR_SUPPORT */ - -// Conversions -public: - /// Implicit conversion to a non-mutable (const) pointer to the variable - operator char_type const *() const - { - return m_buffer.data(); - } - -// Attributes -public: - /// Returns the length of the variable - size_type length() const - { - return m_buffer.size() - 1; - } - -// Members -private: - typedef stlsoft_ns_qual(auto_buffer) > buffer_t; - - buffer_t m_buffer; - -// Not to be implemented -private: - basic_environment_variable(basic_environment_variable const &); - basic_environment_variable &operator =(basic_environment_variable const &); -}; - -/* ///////////////////////////////////////////////////////////////////////////// - * Typedefs for commonly encountered types - */ - -/// Instantiation of the basic_environment_variable template for the ANSI character type \c char -typedef basic_environment_variable > environment_variable_a; -/// Instantiation of the basic_environment_variable template for the Unicode character type \c wchar_t -typedef basic_environment_variable > environment_variable_w; - -/* ///////////////////////////////////////////////////////////////////////////// - * Helper functions - */ - -#if !defined(__STLSOFT_COMPILER_IS_MSVC) || \ - _MSC_VER >= 1100 - -/// This helper function makes an environment variable without needing to -/// qualify the template parameter. -template -inline basic_environment_variable make_environment_variable(C const *path) -{ - return basic_environment_variable(path); -} - -#endif /* !(_MSC_VER < 1100) */ - -/* ////////////////////////////////////////////////////////////////////////// */ - -#ifndef _UNIXSTL_NO_NAMESPACE -# ifdef _STLSOFT_NO_NAMESPACE -} // namespace unixstl -# else -} // namespace unixstl_project -} // namespace stlsoft -# endif /* _STLSOFT_NO_NAMESPACE */ -#endif /* !_UNIXSTL_NO_NAMESPACE */ - -/* ////////////////////////////////////////////////////////////////////////// */ - -#endif /* _UNIXSTL_INCL_H_UNIXSTL_ENVIRONMENT_VARIABLE */ - -/* ////////////////////////////////////////////////////////////////////////// */ diff -uNr gdc-0.17/d/phobos/etc/c/stlsoft/unixstl_filesystem_traits.h gdc-0.18/d/phobos/etc/c/stlsoft/unixstl_filesystem_traits.h --- gdc-0.17/d/phobos/etc/c/stlsoft/unixstl_filesystem_traits.h 2004-10-26 02:41:27.000000000 +0200 +++ gdc-0.18/d/phobos/etc/c/stlsoft/unixstl_filesystem_traits.h 1970-01-01 01:00:00.000000000 +0100 @@ -1,462 +0,0 @@ -/* ///////////////////////////////////////////////////////////////////////////// - * File: unixstl_filesystem_traits.h - * - * Purpose: Contains the filesystem_traits template class, and ANSI and - * Unicode specialisations thereof. - * - * Created: 15th November 2002 - * Updated: 3rd November 2003 - * - * Author: Matthew Wilson, Synesis Software Pty Ltd. - * - * License: (Licensed under the Synesis Software Standard Source License) - * - * Copyright (C) 2002-2003, Synesis Software Pty Ltd. - * - * All rights reserved. - * - * www: http://www.synesis.com.au/unixstl - * http://www.unixstl.org/ - * - * email: submissions@unixstl.org for submissions - * admin@unixstl.org for other enquiries - * - * Redistribution and use in source and binary forms, with or - * without modification, are permitted provided that the following - * conditions are met: - * - * (i) Redistributions of source code must retain the above - * copyright notice and contact information, this list of - * conditions and the following disclaimer. - * - * (ii) Any derived versions of this software (howsoever modified) - * remain the sole property of Synesis Software. - * - * (iii) Any derived versions of this software (howsoever modified) - * remain subject to all these conditions. - * - * (iv) Neither the name of Synesis Software nor the names of any - * subdivisions, employees or agents of Synesis Software, nor the - * names of any other contributors to this software may be used to - * endorse or promote products derived from this software without - * specific prior written permission. - * - * This source code is provided by Synesis Software "as is" and any - * warranties, whether expressed or implied, including, but not - * limited to, the implied warranties of merchantability and - * fitness for a particular purpose are disclaimed. In no event - * shall the Synesis Software be liable for any direct, indirect, - * incidental, special, exemplary, or consequential damages - * (including, but not limited to, procurement of substitute goods - * or services; loss of use, data, or profits; or business - * interruption) however caused and on any theory of liability, - * whether in contract, strict liability, or tort (including - * negligence or otherwise) arising in any way out of the use of - * this software, even if advised of the possibility of such - * damage. - * - * ////////////////////////////////////////////////////////////////////////// */ - - -#ifndef _UNIXSTL_INCL_H_UNIXSTL_FILESYSTEM_TRAITS -#define _UNIXSTL_INCL_H_UNIXSTL_FILESYSTEM_TRAITS - -#ifndef __STLSOFT_DOCUMENTATION_SKIP_SECTION -#define _UNIXSTL_VER_H_UNIXSTL_FILESYSTEM_TRAITS_MAJOR 1 -#define _UNIXSTL_VER_H_UNIXSTL_FILESYSTEM_TRAITS_MINOR 6 -#define _UNIXSTL_VER_H_UNIXSTL_FILESYSTEM_TRAITS_REVISION 1 -#define _UNIXSTL_VER_H_UNIXSTL_FILESYSTEM_TRAITS_EDIT 22 -#endif /* !__STLSOFT_DOCUMENTATION_SKIP_SECTION */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Includes - */ - -#ifndef _UNIXSTL_INCL_H_WINSTL -# include "unixstl.h" // Include the UNIXSTL root header -#endif /* !_UNIXSTL_INCL_H_WINSTL */ -#include -#include -#include - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace - */ - -#ifndef _UNIXSTL_NO_NAMESPACE -# ifdef _STLSOFT_NO_NAMESPACE -/* There is no stlsoft namespace, so must define ::unixstl */ -namespace unixstl -{ -# else -/* Define stlsoft::unixstl_project */ - -namespace stlsoft -{ - -namespace unixstl_project -{ - -# endif /* _STLSOFT_NO_NAMESPACE */ -#endif /* !_UNIXSTL_NO_NAMESPACE */ - -/* ////////////////////////////////////////////////////////////////////////// */ - -/// \weakgroup libraries STLSoft Libraries -/// \brief The individual libraries - -/// \weakgroup libraries_filesystem File-System Library -/// \ingroup libraries -/// \brief This library provides facilities for defining and manipulating file-system objects - -/// \defgroup unixstl_filesystem_library File-System Library (UNIXSTL) -/// \ingroup UNIXSTL libraries_filesystem -/// \brief This library provides facilities for defining and manipulating UNIX file-system objects -/// @{ - -/* ///////////////////////////////////////////////////////////////////////////// - * Classes - * - * filesystem_traits - a traits template, along with - * filesystem_traits and - * filesystem_traits - */ - -/// \brief Traits class for file-system operations -/// -/// \param C The character type (e.g. \c char, \c wchar_t) -template -#ifdef __STLSOFT_DOCUMENTATION_SKIP_SECTION -struct filesystem_traits -{ -public: - typedef C char_type; /*!< The character type */ - typedef us_size_t size_type; /*!< The size type */ - -public: - // General string handling - - /// Copies the contents of \c src to \c dest - static char_type *str_copy(char_type *dest, char_type const *src); - /// Appends the contents of \c src to \c dest - static char_type *str_cat(char_type *dest, char_type const *src); - /// Comparies the contents of \c src and \c dest - static us_int_t str_compare(char_type const *s1, char_type const *s2); - /// Evaluates the length of \c src - static size_type str_len(char_type const *src); - - // File-system entry names - - /// Appends a path name separator to \c dir if one does not exist - static char_type *ensure_dir_end(char_type *dir); - /// Removes a path name separator to \c dir if one does not exist - static char_type *remove_dir_end(char_type *dir); - /// Returns \c true if dir is \c "." or \c ".." - static us_bool_t is_dots(char_type const *dir); - /// Returns the path separator - /// - /// This is the separator that is used to separate multiple paths on the operating system. On UNIX it is ':' - static char_type path_separator(); - /// Returns the path name separator - /// - /// This is the separator that is used to separate parts of a path on the operating system. On UNIX it is '/' - static char_type path_name_separator(); - /// Returns the wildcard pattern that represents all possible matches - /// - /// \note On UNIX it is '*' - static char_type const *pattern_all(); - /// Gets the full path name into the given buffer, returning a pointer to the file-part - static us_size_t get_full_path_name(char_type const *fileName, us_size_t cchBuffer, char_type *buffer, char_type **ppFile); - /// Gets the full path name into the given buffer - static us_size_t get_full_path_name(char_type const *fileName, us_size_t cchBuffer, char_type *buffer); - - // File system state - - /// Sets the current directory to \c dir - static us_bool_t set_current_directory(char_type const *dir); - /// Retrieves the name of the current directory into \c buffer up to a maximum of \c cchBuffer characters - static us_uint_t get_current_directory(us_uint_t cchBuffer, char_type *buffer); - - // Environment - - /// Gets an environment variable into the given buffer - static us_uint_t get_environment_variable(char_type const *name, char_type *buffer, us_uint_t cchBuffer); - /// Expands environment strings in \c src into \dest, up to a maximum \c cchDest characters - static us_uint_t expand_environment_strings(char_type const *src, char_type *buffer, us_uint_t cchBuffer); -}; -#else -struct filesystem_traits; - -#ifdef __STLSOFT_CF_TEMPLATE_SPECIALISATION_SYNTAX -template <> -#endif /* __STLSOFT_CF_TEMPLATE_SPECIALISATION_SYNTAX */ -struct filesystem_traits -{ -public: - typedef us_char_a_t char_type; - typedef us_size_t size_type; - -public: - // General string handling - static char_type *str_copy(char_type *dest, char_type const *src) - { - return strcpy(dest, src); - } - - static char_type *str_cat(char_type *dest, char_type const *src) - { - return strcat(dest, src); - } - - static us_int_t str_compare(char_type const *s1, char_type const *s2) - { - return strcmp(s1, s2); - } - - static size_type str_len(char_type const *src) - { - return static_cast(strlen(src)); - } - - // File-system entry names - static char_type *ensure_dir_end(char_type *dir) - { - char_type *end; - - for(end = dir; *end != '\0'; ++end) - {} - - if( dir < end && - *(end - 1) != path_name_separator()) - { - *end = path_name_separator(); - *(end + 1) = '\0'; - } - - return dir; - } - - static char_type *remove_dir_end(char_type *dir) - { - char_type *end; - - for(end = dir; *end != '\0'; ++end) - {} - - if( dir < end && - *(end - 1) == path_name_separator()) - { - *(end - 1) = '\0'; - } - - return dir; - } - - static us_bool_t is_dots(char_type const *dir) - { - return dir != 0 && - dir[0] == '.' && - ( dir[1] == '\0' || - ( dir[1] == '.' && - dir[2] == '\0')); - } - - static char_type path_separator() - { - return ':'; - } - - static char_type path_name_separator() - { - return '/'; - } - - static char_type const *pattern_all() - { - return "*"; - } - - static us_size_t get_full_path_name(char_type const *fileName, us_size_t cchBuffer, char_type *buffer, char_type **ppFile); - - static us_size_t get_full_path_name(char_type const *fileName, us_size_t cchBuffer, char_type *buffer) - { - unixstl_assert(buffer != NULL); - - if(fileName[0] == path_name_separator()) - { - str_copy(buffer, fileName); - } - else - { - get_current_directory(cchBuffer, buffer); - if(0 != str_compare(fileName, ".")) - { - ensure_dir_end(buffer); - str_cat(buffer, fileName); - } - } - - return str_len(buffer); - } - - // File system state - static us_bool_t set_current_directory(char_type const *dir) - { - return chdir(dir) == 0; - } - - static us_uint_t get_current_directory(us_uint_t cchBuffer, char_type *buffer) - { - return getcwd(buffer, cchBuffer) != 0; - } - - // Environment - - static us_uint_t get_environment_variable(char_type const *name, char_type *buffer, us_uint_t cchBuffer) - { - char *var = getenv(name); - - if(NULL == var) - { - return 0; - } - else - { - size_t var_len = strlen(var); - - strncpy(buffer, var, cchBuffer); - - return (var_len < cchBuffer) ? var_len : cchBuffer; - } - } - - static us_uint_t expand_environment_strings(char_type const *src, char_type *buffer, us_uint_t cchBuffer); -}; - -#if 0 -#ifdef __STLSOFT_CF_TEMPLATE_SPECIALISATION_SYNTAX -template <> -#endif /* __STLSOFT_CF_TEMPLATE_SPECIALISATION_SYNTAX */ -struct filesystem_traits -{ -public: - typedef us_char_w_t char_type; - typedef us_size_t size_type; - -public: - // General string handling - static char_type *str_copy(char_type *dest, char_type const *src) - { - return wcscpy(dest, src); - } - - static char_type *str_cat(char_type *dest, char_type const *src) - { - return wcscat(dest, src); - } - - static us_int_t str_compare(char_type const *s1, char_type const *s2) - { - return wcscmp(s1, s2); - } - - static size_type str_len(char_type const *src) - { - return static_cast(wcslen(src)); - } - - // File-system entry names - static char_type *ensure_dir_end(char_type *dir) - { - char_type *end; - - for(end = dir; *end != L'\0'; ++end) - {} - - if( dir < end && - *(end - 1) != path_name_separator()) - { - *end = path_name_separator(); - *(end + 1) = L'\0'; - } - - return dir; - } - - static char_type *remove_dir_end(char_type *dir) - { - char_type *end; - - for(end = dir; *end != L'\0'; ++end) - {} - - if( dir < end && - *(end - 1) == path_name_separator()) - { - *(end - 1) = L'\0'; - } - - return dir; - } - - static us_bool_t is_dots(char_type const *dir) - { - return dir != 0 && - dir[0] == '.' && - ( dir[1] == L'\0' || - ( dir[1] == L'.' && - dir[2] == L'\0')); - } - - static char_type path_separator() - { - return L':'; - } - - static char_type path_name_separator() - { - return L'/'; - } - - static char_type const *pattern_all() - { - return L"*"; - } - - static us_size_t get_full_path_name(char_type const *fileName, us_size_t cchBuffer, char_type *buffer, char_type **ppFile); - static us_size_t get_full_path_name(char_type const *fileName, us_size_t cchBuffer, char_type *buffer) - { - char_type *pFile; - - return get_full_path_name(fileName, cchBuffer, buffer, &pFile); - } - - // File system state - static us_bool_t set_current_directory(char_type const *dir); - - static us_uint_t get_current_directory(us_uint_t cchBuffer, char_type *buffer); -}; -#endif /* 0 */ - -#endif /* !__STLSOFT_DOCUMENTATION_SKIP_SECTION */ - -/* ////////////////////////////////////////////////////////////////////////// */ - -/// @} // end of group unixstl_filesystem_library - -/* ////////////////////////////////////////////////////////////////////////// */ - -#ifndef _UNIXSTL_NO_NAMESPACE -# ifdef _STLSOFT_NO_NAMESPACE -} // namespace unixstl -# else -} // namespace unixstl_project -} // namespace stlsoft -# endif /* _STLSOFT_NO_NAMESPACE */ -#endif /* !_UNIXSTL_NO_NAMESPACE */ - -/* ////////////////////////////////////////////////////////////////////////// */ - -#endif /* _UNIXSTL_INCL_H_UNIXSTL_FILESYSTEM_TRAITS */ - -/* ////////////////////////////////////////////////////////////////////////// */ diff -uNr gdc-0.17/d/phobos/etc/c/stlsoft/unixstl_findfile_sequence.h gdc-0.18/d/phobos/etc/c/stlsoft/unixstl_findfile_sequence.h --- gdc-0.17/d/phobos/etc/c/stlsoft/unixstl_findfile_sequence.h 2004-10-26 02:41:27.000000000 +0200 +++ gdc-0.18/d/phobos/etc/c/stlsoft/unixstl_findfile_sequence.h 1970-01-01 01:00:00.000000000 +0100 @@ -1,170 +0,0 @@ -/* ///////////////////////////////////////////////////////////////////////////// - * File: unixstl_findfile_sequence.h - * - * Purpose: findfile_sequence class. It is now implemented as a typedef to - * the glob_sequence class. - * - * Created: 15th January 2002 - * Updated: 3rd November 2003 - * - * Author: Matthew Wilson, Synesis Software Pty Ltd. - * - * License: (Licensed under the Synesis Software Standard Source License) - * - * Copyright (C) 2002-2003, Synesis Software Pty Ltd. - * - * All rights reserved. - * - * www: http://www.synesis.com.au/unixstl - * http://www.unixstl.org/ - * - * email: submissions@unixstl.org for submissions - * admin@unixstl.org for other enquiries - * - * Redistribution and use in source and binary forms, with or - * without modification, are permitted provided that the following - * conditions are met: - * - * (i) Redistributions of source code must retain the above - * copyright notice and contact information, this list of - * conditions and the following disclaimer. - * - * (ii) Any derived versions of this software (howsoever modified) - * remain the sole property of Synesis Software. - * - * (iii) Any derived versions of this software (howsoever modified) - * remain subject to all these conditions. - * - * (iv) Neither the name of Synesis Software nor the names of any - * subdivisions, employees or agents of Synesis Software, nor the - * names of any other contributors to this software may be used to - * endorse or promote products derived from this software without - * specific prior written permission. - * - * This source code is provided by Synesis Software "as is" and any - * warranties, whether expressed or implied, including, but not - * limited to, the implied warranties of merchantability and - * fitness for a particular purpose are disclaimed. In no event - * shall the Synesis Software be liable for any direct, indirect, - * incidental, special, exemplary, or consequential damages - * (including, but not limited to, procurement of substitute goods - * or services; loss of use, data, or profits; or business - * interruption) however caused and on any theory of liability, - * whether in contract, strict liability, or tort (including - * negligence or otherwise) arising in any way out of the use of - * this software, even if advised of the possibility of such - * damage. - * - * ////////////////////////////////////////////////////////////////////////// */ - - -#ifndef _INCL_UNIXSTL_H_UNIXSTL_FINDFILE_SEQUENCE -#define _INCL_UNIXSTL_H_UNIXSTL_FINDFILE_SEQUENCE - -#ifndef __STLSOFT_DOCUMENTATION_SKIP_SECTION -#define _UNIXSTL_VER_H_UNIXSTL_FINDFILE_SEQUENCE_MAJOR 2 -#define _UNIXSTL_VER_H_UNIXSTL_FINDFILE_SEQUENCE_MINOR 1 -#define _UNIXSTL_VER_H_UNIXSTL_FINDFILE_SEQUENCE_REVISION 1 -#define _UNIXSTL_VER_H_UNIXSTL_FINDFILE_SEQUENCE_EDIT 43 -#endif /* !__STLSOFT_DOCUMENTATION_SKIP_SECTION */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Includes - */ - -#ifndef _INCL_UNIXSTL_H_UNIXSTL -# include "unixstl.h" // Include the UNIXSTL root header -#endif /* !_INCL_UNIXSTL_H_UNIXSTL */ - -#ifdef _UNIXSTL_FINDFILE_SEQUENCE_NO_BACK_SLASH_TERMINATOR -# define _UNIXSTL_GLOB_SEQUENCE_NO_BACK_SLASH_TERMINATOR -#endif /* _UNIXSTL_FINDFILE_SEQUENCE_NO_BACK_SLASH_TERMINATOR */ - -#ifndef _INCL_UNIXSTL_H_UNIXSTL_GLOB_SEQUENCE -# include "unixstl_glob_sequence.h" // glob_sequence -#endif /* !_INCL_UNIXSTL_H_UNIXSTL_GLOB_SEQUENCE */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace - * - * The UNIXSTL components are contained within the unixstl namespace. This is - * actually an alias for stlsoft::unixstl_project, - * - * The definition matrix is as follows: - * - * _STLSOFT_NO_NAMESPACE _UNIXSTL_NO_NAMESPACE unixstl definition - * --------------------- --------------------- ----------------- - * not defined not defined = stlsoft::unixstl_project - * not defined defined not defined - * defined not defined unixstl - * defined defined not defined - * - */ - -/* No STLSoft namespaces means no UNIXSTL namespaces */ -#ifdef _STLSOFT_NO_NAMESPACES -# define _UNIXSTL_NO_NAMESPACES -#endif /* _STLSOFT_NO_NAMESPACES */ - -/* No UNIXSTL namespaces means no unixstl namespace */ -#ifdef _UNIXSTL_NO_NAMESPACES -# define _UNIXSTL_NO_NAMESPACE -#endif /* _UNIXSTL_NO_NAMESPACES */ - -#ifndef _UNIXSTL_NO_NAMESPACE -# ifdef _STLSOFT_NO_NAMESPACE -/* There is no stlsoft namespace, so must define ::unixstl */ -namespace unixstl -{ -# else -/* Define stlsoft::unixstl_project */ - -namespace stlsoft -{ - -namespace unixstl_project -{ - -# endif /* _STLSOFT_NO_NAMESPACE */ -#endif /* !_UNIXSTL_NO_NAMESPACE */ - -/* ////////////////////////////////////////////////////////////////////////// */ - -/// \weakgroup libraries STLSoft Libraries -/// \brief The individual libraries - -/// \weakgroup libraries_filesystem File-System Library -/// \ingroup libraries -/// \brief This library provides facilities for defining and manipulating file-system objects - -/// \defgroup unixstl_filesystem_library File-System Library (UNIXSTL) -/// \ingroup UNIXSTL libraries_filesystem -/// \brief This library provides facilities for defining and manipulating UNIX file-system objects -/// @{ - -/* ///////////////////////////////////////////////////////////////////////////// - * Typedefs - */ - -typedef glob_sequence findfile_sequence; - -/* ////////////////////////////////////////////////////////////////////////// */ - -/// @} // end of group unixstl_filesystem_library - -/* ////////////////////////////////////////////////////////////////////////// */ - -#ifndef _UNIXSTL_NO_NAMESPACE -# ifdef _STLSOFT_NO_NAMESPACE -} // namespace unixstl -# else -} // namespace unixstl_project -} // namespace stlsoft -# endif /* _STLSOFT_NO_NAMESPACE */ -#endif /* !_UNIXSTL_NO_NAMESPACE */ - -/* ////////////////////////////////////////////////////////////////////////// */ - -#endif /* !_INCL_UNIXSTL_H_UNIXSTL_FINDFILE_SEQUENCE */ - -/* ////////////////////////////////////////////////////////////////////////// */ diff -uNr gdc-0.17/d/phobos/etc/c/stlsoft/unixstl_functionals.h gdc-0.18/d/phobos/etc/c/stlsoft/unixstl_functionals.h --- gdc-0.17/d/phobos/etc/c/stlsoft/unixstl_functionals.h 2004-10-26 02:41:27.000000000 +0200 +++ gdc-0.18/d/phobos/etc/c/stlsoft/unixstl_functionals.h 1970-01-01 01:00:00.000000000 +0100 @@ -1,213 +0,0 @@ -/* ///////////////////////////////////////////////////////////////////////////// - * File: unixstl_functionals.h - * - * Purpose: A number of useful functionals . - * - * Created: 2nd November 2003 - * Updated: 2nd November 2003 - * - * Author: Matthew Wilson, Synesis Software Pty Ltd. - * - * License: (Licensed under the Synesis Software Standard Source License) - * - * Copyright (C) 2002-2003, Synesis Software Pty Ltd. - * - * All rights reserved. - * - * www: http://www.synesis.com.au/unixstl - * http://www.unixstl.org/ - * - * email: submissions@unixstl.org for submissions - * admin@unixstl.org for other enquiries - * - * Redistribution and use in source and binary forms, with or - * without modification, are permitted provided that the following - * conditions are met: - * - * (i) Redistributions of source code must retain the above - * copyright notice and contact information, this list of - * conditions and the following disclaimer. - * - * (ii) Any derived versions of this software (howsoever modified) - * remain the sole property of Synesis Software. - * - * (iii) Any derived versions of this software (howsoever modified) - * remain subject to all these conditions. - * - * (iv) Neither the name of Synesis Software nor the names of any - * subdivisions, employees or agents of Synesis Software, nor the - * names of any other contributors to this software may be used to - * endorse or promote products derived from this software without - * specific prior written permission. - * - * This source code is provided by Synesis Software "as is" and any - * warranties, whether expressed or implied, including, but not - * limited to, the implied warranties of merchantability and - * fitness for a particular purpose are disclaimed. In no event - * shall the Synesis Software be liable for any direct, indirect, - * incidental, special, exemplary, or consequential damages - * (including, but not limited to, procurement of substitute goods - * or services; loss of use, data, or profits; or business - * interruption) however caused and on any theory of liability, - * whether in contract, strict liability, or tort (including - * negligence or otherwise) arising in any way out of the use of - * this software, even if advised of the possibility of such - * damage. - * - * ////////////////////////////////////////////////////////////////////////// */ - - -#ifndef _UNIXSTL_INCL_H_UNIXSTL_FUNCTIONALS -#define _UNIXSTL_INCL_H_UNIXSTL_FUNCTIONALS - -#ifndef __STLSOFT_DOCUMENTATION_SKIP_SECTION -#define _UNIXSTL_VER_H_UNIXSTL_FUNCTIONALS_MAJOR 1 -#define _UNIXSTL_VER_H_UNIXSTL_FUNCTIONALS_MINOR 0 -#define _UNIXSTL_VER_H_UNIXSTL_FUNCTIONALS_REVISION 2 -#define _UNIXSTL_VER_H_UNIXSTL_FUNCTIONALS_EDIT 3 -#endif /* !__STLSOFT_DOCUMENTATION_SKIP_SECTION */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Includes - */ - -#ifndef _UNIXSTL_INCL_H_UNIXSTL -# include "unixstl.h" // Include the WinSTL root header -#endif /* !_UNIXSTL_INCL_H_UNIXSTL */ -#ifndef _STLSOFT_INCL_H_STLSOFT_STRING_ACCESS -# include "stlsoft_string_access.h" // c_str_ptr, etc. -#endif /* !_STLSOFT_INCL_H_STLSOFT_STRING_ACCESS */ -#ifndef _UNIXSTL_INCL_H_UNIXSTL_STRING_ACCESS -# include "unixstl_string_access.h" // c_str_ptr, etc. -#endif /* !_UNIXSTL_INCL_H_UNIXSTL_STRING_ACCESS */ -#ifndef _UNIXSTL_INCL_H_UNIXSTL_FILESYSTEM_TRAITS -# include "unixstl_filesystem_traits.h" -#endif /* !_UNIXSTL_INCL_H_UNIXSTL_FILESYSTEM_TRAITS */ -#ifndef _UNIXSTL_FUNCTIONALS_NO_STD -# include -#endif /* _UNIXSTL_FUNCTIONALS_NO_STD */ -#include - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace - */ - -#ifndef _UNIXSTL_NO_NAMESPACE -# ifdef _STLSOFT_NO_NAMESPACE -/* There is no stlsoft namespace, so must define ::unixstl */ -namespace unixstl -{ -# else -/* Define stlsoft::unixstl_project */ - -namespace stlsoft -{ - -namespace unixstl_project -{ - -# endif /* _STLSOFT_NO_NAMESPACE */ -#endif /* !_UNIXSTL_NO_NAMESPACE */ - -stlsoft_ns_using(c_str_ptr) - -/* ///////////////////////////////////////////////////////////////////////////// - * Classes - */ - -/// Function object that compares two file-system paths -/// -/// \param C The character type -template -struct compare_path -#ifndef _UNIXSTL_FUNCTIONALS_NO_STD - : unixstl_ns_qual_std(binary_function) -#endif /* _UNIXSTL_FUNCTIONALS_NO_STD */ -{ -public: - /// The character type - typedef C char_type; -#ifndef _UNIXSTL_FUNCTIONALS_NO_STD -private: - typedef unixstl_ns_qual_std(binary_function) parent_class_type; -public: - /// The first argument type - typedef ss_typename_type_k parent_class_type::first_argument_type first_argument_type; - /// The second argument type - typedef ss_typename_type_k parent_class_type::second_argument_type second_argument_type; - /// The result type - typedef ss_typename_type_k parent_class_type::result_type result_type; -#else - /// The first argument type - typedef const char_type *first_argument_type; - /// The second argument type - typedef const char_type *second_argument_type; - /// The result type - typedef us_bool_t result_type; -#endif /* _UNIXSTL_FUNCTIONALS_NO_STD */ - /// The traits type - typedef filesystem_traits traits_type; - /// The current parameterisation of the type - typedef compare_path class_type; - -public: - /// Function call, compares \c s1 with \c s2 - /// - /// \note The comparison is determined by evaluation the full-paths of both \c s1 and \c s2 -#ifdef __STLSOFT_CF_MEMBER_TEMPLATE_FUNCTION_SUPPORT - template - result_type operator ()(T1 const &s1, T2 const &s2) - { - return _compare(c_str_ptr(s1), c_str_ptr(s2)); - } -#else - result_type operator ()(first_argument_type s1, second_argument_type s2) - { - return _compare(s1, s2); - } -#endif /* __STLSOFT_CF_MEMBER_TEMPLATE_FUNCTION_SUPPORT */ - -// Implementation -private: - result_type _compare(char_type const *s1, char_type const *s2) - { - char_type path1[PATH_MAX + 1]; - char_type path2[PATH_MAX + 1]; - result_type result; - - if(!traits_type::get_full_path_name(s1, unixstl_num_elements(path1), path1)) - { - result = false; - } - else if(!traits_type::get_full_path_name(s2, unixstl_num_elements(path2), path2)) - { - result = false; - } - else - { - traits_type::ensure_dir_end(path1); - traits_type::ensure_dir_end(path2); - - result = traits_type::str_compare(path1, path2) == 0; - } - - return result; - } -}; - -/* ////////////////////////////////////////////////////////////////////////// */ - -#ifndef _UNIXSTL_NO_NAMESPACE -# ifdef _STLSOFT_NO_NAMESPACE -} // namespace unixstl -# else -} // namespace unixstl_project -} // namespace stlsoft -# endif /* _STLSOFT_NO_NAMESPACE */ -#endif /* !_UNIXSTL_NO_NAMESPACE */ - -/* ////////////////////////////////////////////////////////////////////////// */ - -#endif /* _UNIXSTL_INCL_H_UNIXSTL_FUNCTIONALS */ - -/* ////////////////////////////////////////////////////////////////////////// */ diff -uNr gdc-0.17/d/phobos/etc/c/stlsoft/unixstl_glob_sequence.h gdc-0.18/d/phobos/etc/c/stlsoft/unixstl_glob_sequence.h --- gdc-0.17/d/phobos/etc/c/stlsoft/unixstl_glob_sequence.h 2005-08-12 04:32:44.000000000 +0200 +++ gdc-0.18/d/phobos/etc/c/stlsoft/unixstl_glob_sequence.h 1970-01-01 01:00:00.000000000 +0100 @@ -1,551 +0,0 @@ -/* ///////////////////////////////////////////////////////////////////////////// - * File: unixstl_glob_sequence.h (formerly unixstl_findfile_sequence.h) - * - * Purpose: glob_sequence class. - * - * Created: 15th January 2002 - * Updated: 10th November 2003 - * - * Author: Matthew Wilson, Synesis Software Pty Ltd. - * - * License: (Licensed under the Synesis Software Standard Source License) - * - * Copyright (C) 2002-2003, Synesis Software Pty Ltd. - * - * All rights reserved. - * - * www: http://www.synesis.com.au/unixstl - * http://www.unixstl.org/ - * - * email: submissions@unixstl.org for submissions - * admin@unixstl.org for other enquiries - * - * Redistribution and use in source and binary forms, with or - * without modification, are permitted provided that the following - * conditions are met: - * - * (i) Redistributions of source code must retain the above - * copyright notice and contact information, this list of - * conditions and the following disclaimer. - * - * (ii) Any derived versions of this software (howsoever modified) - * remain the sole property of Synesis Software. - * - * (iii) Any derived versions of this software (howsoever modified) - * remain subject to all these conditions. - * - * (iv) Neither the name of Synesis Software nor the names of any - * subdivisions, employees or agents of Synesis Software, nor the - * names of any other contributors to this software may be used to - * endorse or promote products derived from this software without - * specific prior written permission. - * - * This source code is provided by Synesis Software "as is" and any - * warranties, whether expressed or implied, including, but not - * limited to, the implied warranties of merchantability and - * fitness for a particular purpose are disclaimed. In no event - * shall the Synesis Software be liable for any direct, indirect, - * incidental, special, exemplary, or consequential damages - * (including, but not limited to, procurement of substitute goods - * or services; loss of use, data, or profits; or business - * interruption) however caused and on any theory of liability, - * whether in contract, strict liability, or tort (including - * negligence or otherwise) arising in any way out of the use of - * this software, even if advised of the possibility of such - * damage. - * - * ////////////////////////////////////////////////////////////////////////// */ - -/* NOTE: This file has been patched from the original DMD distribution to - work with the GDC compiler. - - Modified by David Friedman, September 2004 -*/ - - -#ifndef _INCL_UNIXSTL_H_UNIXSTL_GLOB_SEQUENCE -#define _INCL_UNIXSTL_H_UNIXSTL_GLOB_SEQUENCE - -#ifndef __STLSOFT_DOCUMENTATION_SKIP_SECTION -#define _UNIXSTL_VER_H_UNIXSTL_GLOB_SEQUENCE_MAJOR 2 -#define _UNIXSTL_VER_H_UNIXSTL_GLOB_SEQUENCE_MINOR 1 -#define _UNIXSTL_VER_H_UNIXSTL_GLOB_SEQUENCE_REVISION 4 -#define _UNIXSTL_VER_H_UNIXSTL_GLOB_SEQUENCE_EDIT 46 -#endif /* !__STLSOFT_DOCUMENTATION_SKIP_SECTION */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Includes - */ - -#ifndef _INCL_UNIXSTL_H_UNIXSTL -# include "unixstl.h" // Include the UNIXSTL root header -#endif /* !_INCL_UNIXSTL_H_UNIXSTL */ -#ifndef _INCL_UNIXSTL_H_UNIXSTL_FILESYSTEM_TRAITS -# include "unixstl_filesystem_traits.h" // filesystem_traits -#endif /* !_INCL_UNIXSTL_H_UNIXSTL_FILESYSTEM_TRAITS */ -#ifndef _STLSOFT_INCL_H_STLSOFT_ITERATOR -# include "stlsoft_iterator.h" -#endif /* !_STLSOFT_INCL_H_STLSOFT_ITERATOR */ -#include -#include -#include -#include - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace - * - * The UNIXSTL components are contained within the unixstl namespace. This is - * actually an alias for stlsoft::unixstl_project, - * - * The definition matrix is as follows: - * - * _STLSOFT_NO_NAMESPACE _UNIXSTL_NO_NAMESPACE unixstl definition - * --------------------- --------------------- ----------------- - * not defined not defined = stlsoft::unixstl_project - * not defined defined not defined - * defined not defined unixstl - * defined defined not defined - * - */ - -/* No STLSoft namespaces means no UNIXSTL namespaces */ -#ifdef _STLSOFT_NO_NAMESPACES -# define _UNIXSTL_NO_NAMESPACES -#endif /* _STLSOFT_NO_NAMESPACES */ - -/* No UNIXSTL namespaces means no unixstl namespace */ -#ifdef _UNIXSTL_NO_NAMESPACES -# define _UNIXSTL_NO_NAMESPACE -#endif /* _UNIXSTL_NO_NAMESPACES */ - -#ifndef _UNIXSTL_NO_NAMESPACE -# ifdef _STLSOFT_NO_NAMESPACE -/* There is no stlsoft namespace, so must define ::unixstl */ -namespace unixstl -{ -# else -/* Define stlsoft::unixstl_project */ - -namespace stlsoft -{ - -namespace unixstl_project -{ - -# endif /* _STLSOFT_NO_NAMESPACE */ -#endif /* !_UNIXSTL_NO_NAMESPACE */ - -/* ////////////////////////////////////////////////////////////////////////// */ - -/// \weakgroup libraries STLSoft Libraries -/// \brief The individual libraries - -/// \weakgroup libraries_filesystem File-System Library -/// \ingroup libraries -/// \brief This library provides facilities for defining and manipulating file-system objects - -/// \defgroup unixstl_filesystem_library File-System Library (UNIXSTL) -/// \ingroup UNIXSTL libraries_filesystem -/// \brief This library provides facilities for defining and manipulating UNIX file-system objects -/// @{ - -/* ///////////////////////////////////////////////////////////////////////////// - * Classes - */ - -/// \brief STL-like readonly sequence based on the results of file-system wildcard matches -/// -/// This class presents and STL-like readonly sequence interface to allow the -/// iteration over the results of file-system wildcard matches. - -class glob_sequence -{ -private: - typedef glob_sequence class_type; -public: - /// The char type - typedef us_char_a_t char_type; - /// The value type - typedef char_type const *value_type; - /// The type of the const (non-mutating) iterator - typedef value_type *const_iterator; -private: -// typedef value_type &reference; - typedef value_type const &const_reference; -// typedef value_type *pointer; - typedef value_type const *const_pointer; -public: - /// The size type - typedef us_size_t size_type; - /// The difference type - typedef us_ptrdiff_t difference_type; - - /// The type of the const (non-mutating) reverse iterator - typedef stlsoft_ns_qual(reverse_iterator_base) < const_iterator - , value_type - , const_reference - , const_pointer - , difference_type - > const_reverse_iterator; - -public: - enum flags - { - includeDots = 0x0008 /*!< Requests that dots directories be included in the returned sequence */ - , directories = 0x0010 /*!< Causes the search to include directories */ - , files = 0x0020 /*!< Causes the search to include files */ - , noSort = 0x0100 /*!< Does not sort entries */ - , markDirs = 0x0200 /*!< Mark directories with a trailing path name separator */ - , - }; - -// Construction -public: - /// \brief Constructs a sequence according to the given criteria - /// - /// The constructor initialises a glob_sequence instance on the given - /// pattern with the given flags. - /// - /// \param pattern The pattern against which to match the file-system contents - /// \param flags Flags to alter the behaviour of the search - ss_explicit_k glob_sequence(char_type const *pattern, us_int_t flags = noSort) - : m_flags(validate_flags_(flags)) - { - m_cItems = _init(pattern); - } - - /// \brief Constructs a sequence according to the given criteria - /// - /// The constructor initialises a glob_sequence instance on the given - /// pattern with the given flags. - /// - /// \param directory The directory in which the pattern is located - /// \param pattern The pattern against which to match the file-system contents - /// \param flags Flags to alter the behaviour of the search - glob_sequence(char_type const *directory, char_type const *pattern, us_int_t flags = noSort) - : m_flags(validate_flags_(flags)) - { - m_cItems = _init(directory, pattern); - } - - // Releases any acquired resources - ~glob_sequence() unixstl_throw_0() - { - if(NULL != m_base) - { - globfree(&m_gl); - } - } - -// Attributes -public: - /// Returns the number of elements in the sequence - us_size_t size() const - { - return m_cItems; - } - - /// \brief Indicates whether the search sequence is empty - us_bool_t empty() const - { - return size() == 0; - } - - /// \brief Returns the value corresponding to the given index - /// - /// \note In debug-mode a runtime assert is applied to enforce that the index is valid. There is no release-time checking on the index validity! - value_type const operator [](size_type index) const - { - unixstl_message_assert("index access out of range in glob_sequence", index < m_cItems + 1); // Has to be +1, since legitimate to take address of one-past-the-end - - return m_base[index]; - } - -// Iteration -public: - /// Begins the iteration - /// - /// \return An iterator representing the start of the sequence - const_iterator begin() const - { - return m_base; - } - /// Ends the iteration - /// - /// \return An iterator representing the end of the sequence - const_iterator end() const - { - return m_base + m_cItems; - } - - /// Begins the reverse iteration - /// - /// \return An iterator representing the start of the reverse sequence - const_reverse_iterator rbegin() const - { - return const_reverse_iterator(end()); - } - /// Ends the reverse iteration - /// - /// \return An iterator representing the end of the reverse sequence - const_reverse_iterator rend() const - { - return const_reverse_iterator(begin()); - } - -// Implementation -private: - static us_int_t validate_flags_(us_int_t flags) - { - if((flags & (directories | files)) == 0) - { - flags |= (directories | files); - } - - if((flags & directories) == 0) - { - // It's more efficient to not bother doing a separate dots check if all - // directories are being elided. -// flags |= includeDots; - } - - return flags; - } - - // Returns true if pch == "" or "/" (or "\\"), false otherwise - static us_bool_t _is_end_of_path_elements(char_type const *pch, difference_type index) - { - return pch[index] == '\0' || - ( pch[index + 1] == '\0' && - ( -#if defined(_UNIXSTL_COMPILER_IS_UNKNOWN) && \ - !defined(_UNIXSTL_GLOB_SEQUENCE_NO_BACK_SLASH_TERMINATOR) - pch[index] == '\\' || -#endif /* _UNIXSTL_COMPILER_IS_UNKNOWN && !_UNIXSTL_GLOB_SEQUENCE_NO_BACK_SLASH_TERMINATOR */ - pch[index] == '/')); - } - - static us_bool_t _is_dots(char_type const *s, us_bool_t &bTwoDots) - { - return s != 0 && - s[0] == '.' && - ( (bTwoDots = false, _is_end_of_path_elements(s, 1)) || - (bTwoDots = true, ( s[1] == '.' && - _is_end_of_path_elements(s, 2)))); - } - - us_int_t _init(char_type const *directory, char_type const *pattern) - { - us_int_t glob_flags = 0; - char_type _directory[1 + PATH_MAX]; - char_type _pattern[1 + PATH_MAX]; - - // If a directory is given, always turn it into an absolute directory - if( NULL != directory && - 0 != *directory) - { - filesystem_traits::str_copy(_directory, directory); - filesystem_traits::ensure_dir_end(_directory); - directory = _directory; - } - - // If a directory is given, always prefix into pattern - if( NULL != directory && - 0 != *directory) - { - filesystem_traits::str_copy(_pattern, directory); - filesystem_traits::str_cat(_pattern, pattern); - - pattern = _pattern; - } - - if(m_flags & noSort) - { - glob_flags |= GLOB_NOSORT; - } - - if(m_flags & markDirs) - { - glob_flags |= GLOB_MARK; - } - - if((m_flags & (directories | files)) == directories) - { -#ifdef GLOB_ONLYDIR - glob_flags |= GLOB_ONLYDIR; -#else -#define UNIXSTL_GLOB_SEQUENCE_ULTRA_CAUTIOUS -#endif - } - - if(0 == glob(pattern, glob_flags, NULL, &m_gl)) - { - char_type **base = m_gl.gl_pathv; - us_int_t cItems = m_gl.gl_pathc; - - if(!(m_flags & includeDots)) - { - // Now remove the dots. If located at the start of - // the gl buffer, then simply increment m_base to - // be above that. If not then rearrange the base - // two pointers such that they are there. - - us_bool_t foundDot1 = false; - us_bool_t foundDot2 = false; - char_type **begin = base; - char_type **end = begin + cItems; - - for(; begin != end; ++begin) - { - us_bool_t bTwoDots; - - if(_is_dots(*begin, bTwoDots)) - { - if(begin != base) - { - // Swap with whatever is at base[0] - char_type *t = *begin; - - *begin = *base; - *base = t; - } - - ++base; - --cItems; - - (bTwoDots ? foundDot2 : foundDot1) = true; - - if( foundDot1 && - foundDot2) - { - break; - } - } - } - } - - // We should be able to trust glob() to return only directories when - // asked, so we assume the following only needs to be done when - // have asked for files alone -#ifdef GLOB_ONLYDIR -#ifdef UNIXSTL_GLOB_SEQUENCE_ULTRA_CAUTIOUS - if((m_flags & (directories | files)) != (directories | files)) -#else /* ? UNIXSTL_GLOB_SEQUENCE_ULTRA_CAUTIOUS */ - if((m_flags & (directories | files)) == files) -#endif /* UNIXSTL_GLOB_SEQUENCE_ULTRA_CAUTIOUS */ -#else - if (1) -#endif - { - char_type **begin = base; - char_type **end = begin + cItems; - - for(; begin != end; ++begin) - { - // Now need to process the file, by using stat - struct stat st; - int res; - char_type buffer[PATH_MAX]; - char_type *entry = *begin; - - if(0 != (m_flags & markDirs)) - { - filesystem_traits::str_copy(buffer, entry); - filesystem_traits::remove_dir_end(buffer); - entry = buffer; - } - res = stat(entry, &st); - - if(0 != res) - { - // Failed to get info from entry. Must assume it is - // dead, so skip it - } - else - { -#ifdef UNIXSTL_GLOB_SEQUENCE_ULTRA_CAUTIOUS - if(m_flags & directories) // Want directories - { - if(S_IFDIR == (st.st_mode & S_IFDIR)) - { - continue; // A directory, so accept it - } - } -#endif /* UNIXSTL_GLOB_SEQUENCE_ULTRA_CAUTIOUS */ - if(m_flags & files) // Want files - { - if(S_IFREG == (st.st_mode & S_IFREG)) - { - continue; // A file, so accept it - } - } - } - - if(begin != base) - { - // Swap with whatever is at base[0] - char_type *t = *begin; - - *begin = *base; - *base = t; - } - - ++base; - --cItems; - } - } - - // Set m_base and m_cItems to the correct values, with - // or without dots. m_base is cast here to remove the - // need for const-casting throughout the rest of the - // class - m_base = const_cast(base); - - return cItems; - } - else - { - m_base = NULL; - - return 0; - } - } - - us_int_t _init(char_type const *pattern) - { - return _init(NULL, pattern); - } - -// Members -private: - us_int_t const m_flags; - glob_t m_gl; - char_type const **m_base; - us_int_t m_cItems; - -// Not to be implemented -private: - glob_sequence(class_type const &); - class_type const &operator =(class_type const &); -}; - -/* ////////////////////////////////////////////////////////////////////////// */ - -/// @} // end of group unixstl_filesystem_library - -/* ////////////////////////////////////////////////////////////////////////// */ - -#ifndef _UNIXSTL_NO_NAMESPACE -# ifdef _STLSOFT_NO_NAMESPACE -} // namespace unixstl -# else -} // namespace unixstl_project -} // namespace stlsoft -# endif /* _STLSOFT_NO_NAMESPACE */ -#endif /* !_UNIXSTL_NO_NAMESPACE */ - -/* ////////////////////////////////////////////////////////////////////////// */ - -#endif /* !_INCL_UNIXSTL_H_UNIXSTL_GLOB_SEQUENCE */ - -/* ////////////////////////////////////////////////////////////////////////// */ diff -uNr gdc-0.17/d/phobos/etc/c/stlsoft/unixstl.h gdc-0.18/d/phobos/etc/c/stlsoft/unixstl.h --- gdc-0.17/d/phobos/etc/c/stlsoft/unixstl.h 2004-10-26 02:41:27.000000000 +0200 +++ gdc-0.18/d/phobos/etc/c/stlsoft/unixstl.h 1970-01-01 01:00:00.000000000 +0100 @@ -1,436 +0,0 @@ -/* ///////////////////////////////////////////////////////////////////////////// - * File: unixstl.h - * - * Purpose: Root header for the UNIXSTL libraries. Performs various compiler - * and platform discriminations, and definitions of types. - * - * Created: 15th January 2002 - * Updated: 16th October 2003 - * - * Author: Matthew Wilson, Synesis Software Pty Ltd. - * - * License: (Licensed under the Synesis Software Standard Source License) - * - * Copyright (C) 2002-2003, Synesis Software Pty Ltd. - * - * All rights reserved. - * - * www: http://www.synesis.com.au/unixstl - * http://www.unixstl.org/ - * - * email: submissions@unixstl.org for submissions - * admin@unixstl.org for other enquiries - * - * Redistribution and use in source and binary forms, with or - * without modification, are permitted provided that the following - * conditions are met: - * - * (i) Redistributions of source code must retain the above - * copyright notice and contact information, this list of - * conditions and the following disclaimer. - * - * (ii) Any derived versions of this software (howsoever modified) - * remain the sole property of Synesis Software. - * - * (iii) Any derived versions of this software (howsoever modified) - * remain subject to all these conditions. - * - * (iv) Neither the name of Synesis Software nor the names of any - * subdivisions, employees or agents of Synesis Software, nor the - * names of any other contributors to this software may be used to - * endorse or promote products derived from this software without - * specific prior written permission. - * - * This source code is provided by Synesis Software "as is" and any - * warranties, whether expressed or implied, including, but not - * limited to, the implied warranties of merchantability and - * fitness for a particular purpose are disclaimed. In no event - * shall the Synesis Software be liable for any direct, indirect, - * incidental, special, exemplary, or consequential damages - * (including, but not limited to, procurement of substitute goods - * or services; loss of use, data, or profits; or business - * interruption) however caused and on any theory of liability, - * whether in contract, strict liability, or tort (including - * negligence or otherwise) arising in any way out of the use of - * this software, even if advised of the possibility of such - * damage. - * - * ////////////////////////////////////////////////////////////////////////// */ - - -#ifndef _UNIXSTL_INCL_H_UNIXSTL -#define _UNIXSTL_INCL_H_UNIXSTL - -/* File version */ -#ifndef __STLSOFT_DOCUMENTATION_SKIP_SECTION -#define _UNIXSTL_VER_H_UNIXSTL_MAJOR 1 -#define _UNIXSTL_VER_H_UNIXSTL_MINOR 5 -#define _UNIXSTL_VER_H_UNIXSTL_REVISION 2 -#define _UNIXSTL_VER_H_UNIXSTL_EDIT 28 -#endif /* !__STLSOFT_DOCUMENTATION_SKIP_SECTION */ - -/** \file unixstl.h The root header for the \ref UNIXSTL project */ - -/** \weakgroup projects STLSoft Projects - * - * \brief The Projects that comprise the STLSoft libraries - */ - -/** \defgroup UNIXSTL UNIXSTL - * \ingroup projects - * - * \brief     Template Software for the UNIX Operating System - * - * The philosophy of UNIXSTL (http://unixstl.org/) is essentially the same as that - * of the STLSoft (http://stlsoft.org/) organisation: providing robust and - * lightweight software to the UNIX development - * community. UNIXSTL provides template-based software that builds on that - * provided by UNIX and STLSoft in order to reduce programmer effort and increase - * robustness in the use of the UNIX. - * - * Namespaces - * - * The UNIXSTL namespace unixstl is actually an alias for the - * namespace stlsoft::unixstl_project, and as such all the - * UNIXSTL project components actually reside within the - * stlsoft namespace. However, there is never any need to - * use the stlsoft::unixstl_project namespace in your code, - * and you should always use the alias unixstl. - * - * Dependencies - * - * As with all parts of the STLSoft libraries, there are no - * dependencies on UNIXSTL binary components and no need to compile UNIXSTL - * implementation files; UNIXSTL is 100% header-only! - * - * As with most of the STLSoft sub-projects, UNIXSTL depends only on: - * - * - Selected headers from the C standard library, such as wchar.h - * - Selected headers from the C++ standard library, such as new, functional - * - Selected header files of the STLSoft main project - * - The header files particular to the technology area, in this case the UNIX library headers, such as dirent.h - * - The binary (static and dynamic libraries) components particular to the technology area, in this case the UNIX libraries that ship with the operating system and your compiler(s) - */ - -/* ///////////////////////////////////////////////////////////////////////////// - * UNIXSTL version - * - * The libraries version information is comprised of major, minor and revision - * components. - * - * The major version is denoted by the _UNIXSTL_VER_MAJOR preprocessor symbol. - * A changes to the major version component implies that a dramatic change has - * occurred in the libraries, such that considerable changes to source dependent - * on previous versions would need to be effected. - * - * The minor version is denoted by the _UNIXSTL_VER_MINOR preprocessor symbol. - * Changes to the minor version component imply that a significant change has - * occurred to the libraries, either in the addition of new functionality or in - * the destructive change to one or more components such that recomplilation and - * code change may be necessitated. - * - * The revision version is denoted by the _UNIXSTL_VER_REVISIO preprocessor - * symbol. Changes to the revision version component imply that a bug has been - * fixed. Dependent code should be recompiled in order to pick up the changes. - * - * In addition to the individual version symbols - _UNIXSTL_VER_MAJOR, - * _UNIXSTL_VER_MINOR and _UNIXSTL_VER_REVISION - a composite symbol _UNIXSTL_VER - * is defined, where the upper 8 bits are 0, bits 16-23 represent the major - * component, bits 8-15 represent the minor component, and bits 0-7 represent - * the revision component. - * - * Each release of the libraries will bear a different version, and that version - * will also have its own symbol: Version 1.0.1 specifies _UNIXSTL_VER_1_0_1. - * - * Thus the symbol _UNIXSTL_VER may be compared meaningfully with a specific - * version symbol, e.g. #if _UNIXSTL_VER >= _UNIXSTL_VER_1_0_1 - */ - -/// \def _UNIXSTL_VER_MAJOR -/// The major version number of UNIXSTL - -/// \def _UNIXSTL_VER_MINOR -/// The minor version number of UNIXSTL - -/// \def _UNIXSTL_VER_REVISION -/// The revision version number of UNIXSTL - -/// \def _UNIXSTL_VER -/// The current composite version number of UNIXSTL - -#define _UNIXSTL_VER_MAJOR 1 -#define _UNIXSTL_VER_MINOR 1 -#define _UNIXSTL_VER_REVISION 1 -#define _UNIXSTL_VER_0_9_1 0x00000901 /*!< Version 0.9.1 */ -#define _UNIXSTL_VER_0_9_2 0x00000902 /*!< Version 0.9.2 */ -#define _UNIXSTL_VER_1_0_1 0x00010001 /*!< Version 1.0.1 */ -#define _UNIXSTL_VER_1_0_2 0x00010002 /*!< Version 1.0.2 */ -#define _UNIXSTL_VER_1_0_3 0x00010003 /*!< Version 1.0.3 */ -#define _UNIXSTL_VER_1_1_1 0x00010101 /*!< Version 1.1.1 */ - -#define _UNIXSTL_VER _UNIXSTL_VER_1_1_1 - -/* ///////////////////////////////////////////////////////////////////////////// - * Includes - */ - -#ifndef _STLSOFT_INCL_H_STLSOFT - #include "stlsoft.h" // Include the STLSoft root header -#endif /* !_STLSOFT_INCL_H_STLSOFT */ - -/* ///////////////////////////////////////////////////////////////////////////// - * STLSoft version compatibility - */ - -#if !defined(_STLSOFT_VER_1_5_1) || \ - _STLSOFT_VER < _STLSOFT_VER_1_5_1 - #error This version of the UNIXSTL libraries requires STLSoft version 1.5.1 or later -#endif /* _STLSOFT_VER < _STLSOFT_VER_1_5_1 */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Compiler compatibility - * - * Currently the only compilers supported by the UNIXSTL libraries are - * - * GCC 2.95, 2.96, 3.2 - * Intel C/C++ 6.0 & 7.0 - */ - -#if defined(__STLSOFT_COMPILER_IS_GCC) -/* GNU C/C++ */ - #if __GNUC__ < 2 || \ - ( __GNUC__ == 2 && \ - __GNUC_MINOR__ < 95) - #error Versions of GNU C/C++ prior to 2.95 are not supported by the UNIXSTL libraries - #endif /* __GNUC__ */ - -#elif defined(__STLSOFT_COMPILER_IS_INTEL) -/* Intel C++ */ - #if (__INTEL_COMPILER < 700) - #error Versions of Intel C++ prior to 7.0 are not supported by the UNIXSTL libraries - #endif /* __INTEL_COMPILER */ - -#else -/* No recognised compiler */ -# ifdef _STLSOFT_FORCE_ANY_COMPILER -# define _UNIXSTL_COMPILER_IS_UNKNOWN -# ifdef _STLSOFT_COMPILE_VERBOSE -# pragma message("Compiler is unknown to UNIXSTL") -# endif /* _STLSOFT_COMPILE_VERBOSE */ -# else -# error Currently only GNU C/C++ compiler supported by the UNIXSTL libraries -# endif /* _STLSOFT_FORCE_ANY_COMPILER */ -#endif /* compiler */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Debugging - * - * The macro unixstl_assert provides standard debug-mode assert functionality. - */ - -/// Defines a runtime assertion -/// -/// \param _x Must be non-zero, or an assertion will be fired -#define unixstl_assert(_x) stlsoft_assert(_x) - -/// Defines a runtime assertion, with message -/// -/// \param _x Must be non-zero, or an assertion will be fired -/// \param _m The literal character string message to be included in the assertion -#define unixstl_message_assert(_m, _x) stlsoft_message_assert(_m, _x) - -/// Defines a compile-time assertion -/// -/// \param _x Must be non-zero, or compilation will fail -#define unixstl_static_assert(_x) stlsoft_static_assert(_x) - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace - * - * The UNIXSTL components are contained within the unixstl namespace. This is - * usually an alias for stlsoft::unixstl_project, - * - * When compilers support namespaces they are defined by default. They can be - * undefined using a cascasing system, as follows: - * - * If _STLSOFT_NO_NAMESPACES is defined, then _UNIXSTL_NO_NAMESPACES is defined. - * - * If _UNIXSTL_NO_NAMESPACES is defined, then _UNIXSTL_NO_NAMESPACE is defined. - * - * If _UNIXSTL_NO_NAMESPACE is defined, then the UNIXSTL constructs are defined - * in the global scope. - * - * If _STLSOFT_NO_NAMESPACES, _UNIXSTL_NO_NAMESPACES and _UNIXSTL_NO_NAMESPACE are - * all undefined but the symbol _STLSOFT_NO_NAMESPACE is defined (whence the - * namespace stlsoft does not exist), then the UNIXSTL constructs are defined - * within the unixstl namespace. The definition matrix is as follows: - * - * _STLSOFT_NO_NAMESPACE _UNIXSTL_NO_NAMESPACE unixstl definition - * --------------------- -------------------- ----------------- - * not defined not defined = stlsoft::unixstl_project - * not defined defined not defined - * defined not defined unixstl - * defined defined not defined - * - * - * - * The macro unixstl_ns_qual() macro can be used to refer to elements in the - * UNIXSTL libraries irrespective of whether they are in the - * stlsoft::unixstl_project (or unixstl) namespace or in the global namespace. - * - * Furthermore, some compilers do not support the standard library in the std - * namespace, so the unixstl_ns_qual_std() macro can be used to refer to elements - * in the UNIXSTL libraries irrespective of whether they are in the std namespace - * or in the global namespace. - */ - -/* No STLSoft namespaces means no UNIXSTL namespaces */ -#ifdef _STLSOFT_NO_NAMESPACES - #define _UNIXSTL_NO_NAMESPACES -#endif /* _STLSOFT_NO_NAMESPACES */ - -/* No UNIXSTL namespaces means no unixstl namespace */ -#ifdef _UNIXSTL_NO_NAMESPACES - #define _UNIXSTL_NO_NAMESPACE -#endif /* _UNIXSTL_NO_NAMESPACES */ - -#ifndef _UNIXSTL_NO_NAMESPACE - #ifdef _STLSOFT_NO_NAMESPACE -/* There is no stlsoft namespace, so must define ::unixstl */ -namespace unixstl -{ - #else -/* Define stlsoft::unixstl_project */ - -namespace stlsoft -{ - -/// The UNIXSTL namespace - \c unixstl (aliased to \c stlsoft::unixstl_project) - is -/// the namespace for the UNIXSTL project. -namespace unixstl_project -{ - - #endif /* _STLSOFT_NO_NAMESPACE */ -#else -stlsoft_ns_using(move_lhs_from_rhs) -#endif /* !_UNIXSTL_NO_NAMESPACE */ - -/// \def unixstl_ns_qual(x) -/// Qualifies with unixstl:: if UNIXSTL is using namespaces or, if not, does not qualify - -/// \def unixstl_ns_using(x) -/// Declares a using directive (with respect to unixstl) if UNIXSTL is using namespaces or, if not, does nothing - -#ifndef _UNIXSTL_NO_NAMESPACE - #define unixstl_ns_qual(x) ::unixstl::x - #define unixstl_ns_using(x) using ::unixstl::x; -#else - #define unixstl_ns_qual(x) x - #define unixstl_ns_using(x) -#endif /* !_UNIXSTL_NO_NAMESPACE */ - -/// \def unixstl_ns_qual_std(x) -/// Qualifies with std:: if UNIXSTL is being translated in the context of the standard library being within the std namespace or, if not, does not qualify - -/// \def unixstl_ns_using_std(x) -/// Declares a using directive (with respect to std) if UNIXSTL is being translated in the context of the standard library being within the std namespace or, if not, does nothing - -#ifdef __STLSOFT_CF_std_NAMESPACE - #define unixstl_ns_qual_std(x) ::std::x - #define unixstl_ns_using_std(x) using ::std::x; -#else - #define unixstl_ns_qual_std(x) x - #define unixstl_ns_using_std(x) -#endif /* !__STLSOFT_CF_std_NAMESPACE */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Typedefs - * - * The UNIXSTL uses a number of typedefs to aid in compiler-independence in the - * libraries' main code. - */ - -typedef stlsoft_ns_qual(ss_char_a_t) us_char_a_t; //!< Ansi char type -typedef stlsoft_ns_qual(ss_char_w_t) us_char_w_t; //!< Unicode char type -typedef stlsoft_ns_qual(ss_sint8_t) us_sint8_t; //!< 8-bit signed integer -typedef stlsoft_ns_qual(ss_uint8_t) us_uint8_t; //!< 8-bit unsigned integer -typedef stlsoft_ns_qual(ss_int16_t) us_int16_t; //!< 16-bit integer -typedef stlsoft_ns_qual(ss_sint16_t) us_sint16_t; //!< 16-bit signed integer -typedef stlsoft_ns_qual(ss_uint16_t) us_uint16_t; //!< 16-bit unsigned integer -typedef stlsoft_ns_qual(ss_int32_t) us_int32_t; //!< 32-bit integer -typedef stlsoft_ns_qual(ss_sint32_t) us_sint32_t; //!< 32-bit signed integer -typedef stlsoft_ns_qual(ss_uint32_t) us_uint32_t; //!< 32-bit unsigned integer -#ifdef __STLSOFT_CF_NATIVE_64BIT_INTEGER_SUPPORT -typedef stlsoft_ns_qual(ss_int64_t) us_int64_t; //!< 64-bit integer -typedef stlsoft_ns_qual(ss_sint64_t) us_sint64_t; //!< 64-bit signed integer -typedef stlsoft_ns_qual(ss_uint64_t) us_uint64_t; //!< 64-bit unsigned integer -#endif /* __STLSOFT_CF_NATIVE_64BIT_INTEGER_SUPPORT */ -typedef stlsoft_ns_qual(ss_int_t) us_int_t; //!< integer -typedef stlsoft_ns_qual(ss_sint_t) us_sint_t; //!< signed integer -typedef stlsoft_ns_qual(ss_uint_t) us_uint_t; //!< unsigned integer -typedef stlsoft_ns_qual(ss_long_t) us_long_t; //!< long -typedef stlsoft_ns_qual(ss_bool_t) us_bool_t; //!< bool -typedef stlsoft_ns_qual(ss_size_t) us_size_t; //!< size -typedef stlsoft_ns_qual(ss_ptrdiff_t) us_ptrdiff_t; //!< ptr diff -typedef stlsoft_ns_qual(ss_streampos_t) us_streampos_t; //!< streampos -typedef stlsoft_ns_qual(ss_streamoff_t) us_streamoff_t; //!< streamoff - -#ifndef __STLSOFT_DOCUMENTATION_SKIP_SECTION -/* ///////////////////////////////////////////////////////////////////////////// - * Values - * - * Since the boolean type may not be supported natively on all compilers, the - * values of true and false may also not be provided. Hence the values of - * us_true_v and us_false_v are defined, and are used in all code. - */ - -#define us_true_v ss_true_v -#define us_false_v ss_false_v - -#endif /* !__STLSOFT_DOCUMENTATION_SKIP_SECTION */ -/* ///////////////////////////////////////////////////////////////////////////// - * Code modification macros - */ - -#ifndef __STLSOFT_DOCUMENTATION_SKIP_SECTION -/* Exception signatures. */ -#define unixstl_throw_0() stlsoft_throw_0() -#define unixstl_throw_1(x1) stlsoft_throw_1(x1) -#define unixstl_throw_2(x1, x2) stlsoft_throw_2(x1, x2) -#define unixstl_throw_3(x1, x2, x3) stlsoft_throw_3(x1, x2, x3) -#define unixstl_throw_4(x1, x2, x3, x4) stlsoft_throw_4(x1, x2, x3, x4) -#define unixstl_throw_5(x1, x2, x3, x4, x5) stlsoft_throw_5(x1, x2, x3, x4, x5) -#define unixstl_throw_6(x1, x2, x3, x4, x5, x6) stlsoft_throw_6(x1, x2, x3, x4, x5, x6) -#define unixstl_throw_7(x1, x2, x3, x4, x5, x6, x7) stlsoft_throw_7(x1, x2, x3, x4, x5, x6, x7) -#define unixstl_throw_8(x1, x2, x3, x4, x5, x6, x7, x8) stlsoft_throw_8(x1, x2, x3, x4, x5, x6, x7, x8) -#endif /* !__STLSOFT_DOCUMENTATION_SKIP_SECTION */ - -/// Evaluates, at compile time, to the number of elements within the given vector entity -#define unixstl_num_elements(_x) stlsoft_num_elements(_x) - -/// Destroys the given instance \c p of the given type (\c t and \c _type) -#define unixstl_destroy_instance(t, _type, p) stlsoft_destroy_instance(t, _type, p) - -/// Generates an opaque type with the name \c _htype -#define unixstl_gen_opaque(_htype) stlsoft_gen_opaque(_htype) - -/// Define a 'final' class, ie. one that cannot be inherited from -#define unixstl_sterile_class(_cls) stlsoft_sterile_class(_cls) - -/* ////////////////////////////////////////////////////////////////////////// */ - -#ifndef _UNIXSTL_NO_NAMESPACE - #ifdef _STLSOFT_NO_NAMESPACE -} // namespace unixstl - #else -} // namespace unixstl_project -} // namespace stlsoft -namespace unixstl = ::stlsoft::unixstl_project; - #endif /* _STLSOFT_NO_NAMESPACE */ -#endif /* !_UNIXSTL_NO_NAMESPACE */ - -/* ////////////////////////////////////////////////////////////////////////// */ - -#endif /* !_UNIXSTL_INCL_H_UNIXSTL */ - -/* ////////////////////////////////////////////////////////////////////////// */ diff -uNr gdc-0.17/d/phobos/etc/c/stlsoft/unixstl_limits.h gdc-0.18/d/phobos/etc/c/stlsoft/unixstl_limits.h --- gdc-0.17/d/phobos/etc/c/stlsoft/unixstl_limits.h 2004-10-26 02:41:27.000000000 +0200 +++ gdc-0.18/d/phobos/etc/c/stlsoft/unixstl_limits.h 1970-01-01 01:00:00.000000000 +0100 @@ -1,173 +0,0 @@ -/* ///////////////////////////////////////////////////////////////////////////// - * File: unixstl_limits.h - * - * Purpose: Header for limits. - * - * Created: 14th November 2002 - * Updated: 2nd November 2003 - * - * Author: Matthew Wilson, Synesis Software Pty Ltd. - * - * License: (Licensed under the Synesis Software Standard Source License) - * - * Copyright (C) 2002-2003, Synesis Software Pty Ltd. - * - * All rights reserved. - * - * www: http://www.synesis.com.au/unixstl - * http://www.unixstl.org/ - * - * email: submissions@unixstl.org for submissions - * admin@unixstl.org for other enquiries - * - * Redistribution and use in source and binary forms, with or - * without modification, are permitted provided that the following - * conditions are met: - * - * (i) Redistributions of source code must retain the above - * copyright notice and contact information, this list of - * conditions and the following disclaimer. - * - * (ii) Any derived versions of this software (howsoever modified) - * remain the sole property of Synesis Software. - * - * (iii) Any derived versions of this software (howsoever modified) - * remain subject to all these conditions. - * - * (iv) Neither the name of Synesis Software nor the names of any - * subdivisions, employees or agents of Synesis Software, nor the - * names of any other contributors to this software may be used to - * endorse or promote products derived from this software without - * specific prior written permission. - * - * This source code is provided by Synesis Software "as is" and any - * warranties, whether expressed or implied, including, but not - * limited to, the implied warranties of merchantability and - * fitness for a particular purpose are disclaimed. In no event - * shall the Synesis Software be liable for any direct, indirect, - * incidental, special, exemplary, or consequential damages - * (including, but not limited to, procurement of substitute goods - * or services; loss of use, data, or profits; or business - * interruption) however caused and on any theory of liability, - * whether in contract, strict liability, or tort (including - * negligence or otherwise) arising in any way out of the use of - * this software, even if advised of the possibility of such - * damage. - * - * ////////////////////////////////////////////////////////////////////////// */ - - -#ifndef _INCL_UNIXSTL_H_UNIXSTL_LIMITS -#define _INCL_UNIXSTL_H_UNIXSTL_LIMITS - -#ifndef __STLSOFT_DOCUMENTATION_SKIP_SECTION -#define _UNIXSTL_VER_H_UNIXSTL_LIMITS_MAJOR 1 -#define _UNIXSTL_VER_H_UNIXSTL_LIMITS_MINOR 1 -#define _UNIXSTL_VER_H_UNIXSTL_LIMITS_REVISION 2 -#define _UNIXSTL_VER_H_UNIXSTL_LIMITS_EDIT 9 -#endif /* !__STLSOFT_DOCUMENTATION_SKIP_SECTION */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Includes - */ - -#ifndef _INCL_UNIXSTL_H_UNIXSTL -# include "unixstl.h" // Include the UNIXSTL root header -#endif /* !_INCL_UNIXSTL_H_UNIXSTL */ -#include -#include - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace - * - * The UNIXSTL components are contained within the unixstl namespace. This is - * actually an alias for stlsoft::unixstl_project, - * - * The definition matrix is as follows: - * - * _STLSOFT_NO_NAMESPACE _UNIXSTL_NO_NAMESPACE unixstl definition - * --------------------- --------------------- ----------------- - * not defined not defined = stlsoft::unixstl_project - * not defined defined not defined - * defined not defined unixstl - * defined defined not defined - * - */ - -/* No STLSoft namespaces means no UNIXSTL namespaces */ -#ifdef _STLSOFT_NO_NAMESPACES -# define _UNIXSTL_NO_NAMESPACES -#endif /* _STLSOFT_NO_NAMESPACES */ - -/* No UNIXSTL namespaces means no unixstl namespace */ -#ifdef _UNIXSTL_NO_NAMESPACES -# define _UNIXSTL_NO_NAMESPACE -#endif /* _UNIXSTL_NO_NAMESPACES */ - -#ifndef _UNIXSTL_NO_NAMESPACE -# ifdef _STLSOFT_NO_NAMESPACE -/* There is no stlsoft namespace, so must define ::unixstl */ -namespace unixstl -{ -# else -/* Define stlsoft::unixstl_project */ - -namespace stlsoft -{ - -namespace unixstl_project -{ - -# endif /* _STLSOFT_NO_NAMESPACE */ -#else -stlsoft_ns_using(move_lhs_from_rhs) -#endif /* !_UNIXSTL_NO_NAMESPACE */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Constants and definitions - */ - -/* UNIXSTL_NAME_MAX */ - -/** \def UNIXSTL_NAME_MAX - * - * The maxiumum number of characters in a UNIXSTL file-system name - */ - -#ifdef NAME_MAX -# define UNIXSTL_NAME_MAX NAME_MAX -#elif defined(PATH_MAX) -# define UNIXSTL_NAME_MAX PATH_MAX -#else -# define UNIXSTL_NAME_MAX (512) -#endif /* NAME_MAX */ - -/* UNIXSTL_PATH_MAX */ - -/** \def UNIXSTL_PATH_MAX - * - * The maxiumum number of characters in a UNIXSTL file-system path - */ - -#ifdef PATH_MAX -# define UNIXSTL_PATH_MAX PATH_MAX -#else -# define UNIXSTL_PATH_MAX (512) -#endif /* NAME_MAX */ - -/* ////////////////////////////////////////////////////////////////////////// */ - -#ifndef _UNIXSTL_NO_NAMESPACE -# ifdef _STLSOFT_NO_NAMESPACE -} // namespace unixstl -# else -} // namespace unixstl_project -} // namespace stlsoft -# endif /* _STLSOFT_NO_NAMESPACE */ -#endif /* !_UNIXSTL_NO_NAMESPACE */ - -/* ////////////////////////////////////////////////////////////////////////// */ - -#endif /* !_INCL_UNIXSTL_H_UNIXSTL_LIMITS */ - -/* ////////////////////////////////////////////////////////////////////////// */ diff -uNr gdc-0.17/d/phobos/etc/c/stlsoft/unixstl_process_mutex.h gdc-0.18/d/phobos/etc/c/stlsoft/unixstl_process_mutex.h --- gdc-0.17/d/phobos/etc/c/stlsoft/unixstl_process_mutex.h 2004-10-26 02:41:27.000000000 +0200 +++ gdc-0.18/d/phobos/etc/c/stlsoft/unixstl_process_mutex.h 1970-01-01 01:00:00.000000000 +0100 @@ -1,296 +0,0 @@ -/* //////////////////////////////////////////////////////////////////////////// - * File: unixstl_process_mutex.h - * - * Purpose: Intra-process mutext, based on PTHREADS. - * - * Date: 15th May 2002 - * Updated: 23rd November 2003 - * - * Author: Matthew Wilson, Synesis Software Pty Ltd. - * - * License: (Licensed under the Synesis Software Standard Source License) - * - * Copyright (C) 2002-2003, Synesis Software Pty Ltd. - * - * All rights reserved. - * - * www: http://www.synesis.com.au/unixstl - * http://www.unixstl.org/ - * - * email: submissions@unixstl.org for submissions - * admin@unixstl.org for other enquiries - * - * Redistribution and use in source and binary forms, with or - * without modification, are permitted provided that the following - * conditions are met: - * - * (i) Redistributions of source code must retain the above - * copyright notice and contact information, this list of - * conditions and the following disclaimer. - * - * (ii) Any derived versions of this software (howsoever modified) - * remain the sole property of Synesis Software. - * - * (iii) Any derived versions of this software (howsoever modified) - * remain subject to all these conditions. - * - * (iv) Neither the name of Synesis Software nor the names of any - * subdivisions, employees or agents of Synesis Software, nor the - * names of any other contributors to this software may be used to - * endorse or promote products derived from this software without - * specific prior written permission. - * - * This source code is provided by Synesis Software "as is" and any - * warranties, whether expressed or implied, including, but not - * limited to, the implied warranties of merchantability and - * fitness for a particular purpose are disclaimed. In no event - * shall the Synesis Software be liable for any direct, indirect, - * incidental, special, exemplary, or consequential damages - * (including, but not limited to, procurement of substitute goods - * or services; loss of use, data, or profits; or business - * interruption) however caused and on any theory of liability, - * whether in contract, strict liability, or tort (including - * negligence or otherwise) arising in any way out of the use of - * this software, even if advised of the possibility of such - * damage. - * - * ////////////////////////////////////////////////////////////////////////// */ - - -#ifndef _UNIXSTL_INCL_H_UNIXSTL_PROCESS_MUTEX -#define _UNIXSTL_INCL_H_UNIXSTL_PROCESS_MUTEX - -#ifndef __STLSOFT_DOCUMENTATION_SKIP_SECTION -# define _UNIXSTL_VER_H_UNIXSTL_PROCESS_MUTEX_MAJOR 1 -# define _UNIXSTL_VER_H_UNIXSTL_PROCESS_MUTEX_MINOR 3 -# define _UNIXSTL_VER_H_UNIXSTL_PROCESS_MUTEX_REVISION 4 -# define _UNIXSTL_VER_H_UNIXSTL_PROCESS_MUTEX_EDIT 15 -#endif /* !__STLSOFT_DOCUMENTATION_SKIP_SECTION */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Includes - */ - -#ifndef _UNIXSTL_INCL_H_UNIXSTL -# include "unixstl.h" // Include the UNIXSTL root header -#endif /* !_UNIXSTL_INCL_H_UNIXSTL */ -#if !defined(_REENTRANT) && \ - !defined(_POSIX_THREADS) -# error unixstl_process_mutex.h must be compiled in the context of PTHREADS -#endif /* !_REENTRANT && !_POSIX_THREADS */ -#include - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace - */ - -#ifndef _UNIXSTL_NO_NAMESPACE -# ifdef _STLSOFT_NO_NAMESPACE -/* There is no stlsoft namespace, so must define ::unixstl */ -namespace unixstl -{ -# else -/* Define stlsoft::unixstl_project */ - -namespace stlsoft -{ - -namespace unixstl_project -{ - -# endif /* _STLSOFT_NO_NAMESPACE */ -#endif /* !_UNIXSTL_NO_NAMESPACE */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Classes - */ - -// class process_mutex -/// This class provides an implementation of the mutex model based on the Win32 CRITICAL_SECTION -class process_mutex -{ -public: - typedef process_mutex class_type; - -// Construction -public: - /// Creates an instance of the mutex - ss_explicit_k process_mutex(us_bool_t bRecursive) unixstl_throw_0() - : m_init(create_(&m_mx, 0, bRecursive)) - {} -#if defined(_POSIX_THREAD_PROCESS_SHARED) - /// Creates an instance of the mutex - process_mutex(int pshared, us_bool_t bRecursive) unixstl_throw_0() - : m_init(create_(&m_mx, pshared, bRecursive)) - {} -#endif /* _POSIX_THREAD_PROCESS_SHARED */ - /// Destroys an instance of the mutex - ~process_mutex() unixstl_throw_0() - { - if(m_init) - { - ::pthread_mutex_destroy(&m_mx); - } - } - -// Operations -public: - /// Acquires a lock on the mutex, pending the thread until the lock is aquired - void lock() unixstl_throw_0() - { - pthread_mutex_lock(&m_mx); - } - /// Attempts to lock the mutex - /// - /// \return true if the mutex was aquired, or false if not - /// \note Only available with Windows NT 4 and later - bool try_lock() - { - return pthread_mutex_trylock(&m_mx) == 0; - } - /// Releases an aquired lock on the mutex - void unlock() unixstl_throw_0() - { - pthread_mutex_unlock(&m_mx); - } - -// Implementation -private: - static us_bool_t create_(pthread_mutex_t *mx, int pshared, us_bool_t bRecursive) - { - us_bool_t bSuccess = false; - pthread_mutexattr_t attr; - - if(0 == ::pthread_mutexattr_init(&attr)) - { - if( !bRecursive || - 0 == ::pthread_mutexattr_settype(&attr, PTHREAD_MUTEX_RECURSIVE)) - { -#if defined(_POSIX_THREAD_PROCESS_SHARED) - if(0 == ::pthread_mutexattr_setpshared(&attr, pshared)) -#else - ((void)pshared); -#endif /* _POSIX_THREAD_PROCESS_SHARED */ - { - if(0 == ::pthread_mutex_init(mx, &attr)) - { - bSuccess = true; - } - } - } - - ::pthread_mutexattr_destroy(&attr); - } - - return bSuccess; - } - -// Members -private: - pthread_mutex_t m_mx; // mx - us_bool_t m_init; - -// Not to be implemented -private: - process_mutex(class_type const &rhs); - process_mutex &operator =(class_type const &rhs); -}; - -/* ///////////////////////////////////////////////////////////////////////////// - * Control shims - */ - -#ifndef _UNIXSTL_NO_NAMESPACE -# ifdef _STLSOFT_NO_NAMESPACE -} // namespace unixstl -# else -} // namespace unixstl_project -# endif /* _STLSOFT_NO_NAMESPACE */ -#endif /* !_UNIXSTL_NO_NAMESPACE */ - -/// \weakgroup concepts STLSoft Concepts - -/// \weakgroup concepts_shims Shims -/// \ingroup concepts - -/// \weakgroup concepts_shims_sync_control Synchronisation Control Shims -/// \ingroup concepts_shims -/// \brief These \ref concepts_shims "shims" control the behaviour of synchronisation objects - -/// \defgroup unixstl_sync_control_shims Synchronisation Control Shims (UNIXSTL) -/// \ingroup UNIXSTL concepts_shims_sync_control -/// \brief These \ref concepts_shims "shims" control the behaviour of Win32 synchronisation objects -/// @{ - -/// This control ref concepts_shims "shim" aquires a lock on the given mutex -/// -/// \param mx The mutex on which to aquire the lock -inline void lock_instance(unixstl_ns_qual(process_mutex) &mx) -{ - mx.lock(); -} - -/// This control ref concepts_shims "shim" releases a lock on the given mutex -/// -/// \param mx The mutex on which to release the lock -inline void unlock_instance(unixstl_ns_qual(process_mutex) &mx) -{ - mx.unlock(); -} - -/// @} // end of group unixstl_sync_control_shims - -#ifndef _UNIXSTL_NO_NAMESPACE -# ifdef _STLSOFT_NO_NAMESPACE -namespace unixstl -{ -# else -namespace unixstl_project -{ -# endif /* _STLSOFT_NO_NAMESPACE */ -#endif /* !_UNIXSTL_NO_NAMESPACE */ - -/* ///////////////////////////////////////////////////////////////////////////// - * lock_traits (for the compilers that do not support Koenig Lookup) - */ - -// class lock_traits -/// Traits for the process_mutex class (for compilers that do not support Koenig Lookup) -struct thread_mutex_lock_traits -{ -public: - /// The lockable type - typedef process_mutex lock_type; - typedef thread_mutex_lock_traits class_type; - -// Operations -public: - /// Lock the given process_mutex instance - static void lock(process_mutex &c) - { - lock_instance(c); - } - - /// Unlock the given process_mutex instance - static void unlock(process_mutex &c) - { - unlock_instance(c); - } -}; - -/* ////////////////////////////////////////////////////////////////////////// */ - -#ifndef _UNIXSTL_NO_NAMESPACE -# ifdef _STLSOFT_NO_NAMESPACE -} // namespace unixstl -# else -} // namespace unixstl_project -} // namespace stlsoft -# endif /* _STLSOFT_NO_NAMESPACE */ -#endif /* !_UNIXSTL_NO_NAMESPACE */ - -/* ////////////////////////////////////////////////////////////////////////// */ - -#endif /* !_UNIXSTL_INCL_H_UNIXSTL_PROCESS_MUTEX */ - -/* ////////////////////////////////////////////////////////////////////////// */ diff -uNr gdc-0.17/d/phobos/etc/c/stlsoft/unixstl_readdir_sequence.h gdc-0.18/d/phobos/etc/c/stlsoft/unixstl_readdir_sequence.h --- gdc-0.17/d/phobos/etc/c/stlsoft/unixstl_readdir_sequence.h 2004-10-26 02:41:27.000000000 +0200 +++ gdc-0.18/d/phobos/etc/c/stlsoft/unixstl_readdir_sequence.h 1970-01-01 01:00:00.000000000 +0100 @@ -1,553 +0,0 @@ -/* ///////////////////////////////////////////////////////////////////////////// - * File: unixstl_readdir_sequence.h - * - * Purpose: readdir_sequence class. - * - * Created: 15th January 2002 - * Updated: 24th November 2003 - * - * Author: Matthew Wilson, Synesis Software Pty Ltd. - * - * License: (Licensed under the Synesis Software Standard Source License) - * - * Copyright (C) 2002-2003, Synesis Software Pty Ltd. - * - * All rights reserved. - * - * www: http://www.synesis.com.au/unixstl - * http://www.unixstl.org/ - * - * email: submissions@unixstl.org for submissions - * admin@unixstl.org for other enquiries - * - * Redistribution and use in source and binary forms, with or - * without modification, are permitted provided that the following - * conditions are met: - * - * (i) Redistributions of source code must retain the above - * copyright notice and contact information, this list of - * conditions and the following disclaimer. - * - * (ii) Any derived versions of this software (howsoever modified) - * remain the sole property of Synesis Software. - * - * (iii) Any derived versions of this software (howsoever modified) - * remain subject to all these conditions. - * - * (iv) Neither the name of Synesis Software nor the names of any - * subdivisions, employees or agents of Synesis Software, nor the - * names of any other contributors to this software may be used to - * endorse or promote products derived from this software without - * specific prior written permission. - * - * This source code is provided by Synesis Software "as is" and any - * warranties, whether expressed or implied, including, but not - * limited to, the implied warranties of merchantability and - * fitness for a particular purpose are disclaimed. In no event - * shall the Synesis Software be liable for any direct, indirect, - * incidental, special, exemplary, or consequential damages - * (including, but not limited to, procurement of substitute goods - * or services; loss of use, data, or profits; or business - * interruption) however caused and on any theory of liability, - * whether in contract, strict liability, or tort (including - * negligence or otherwise) arising in any way out of the use of - * this software, even if advised of the possibility of such - * damage. - * - * ////////////////////////////////////////////////////////////////////////// */ - - -#ifndef _INCL_UNIXSTL_H_UNIXSTL_READDIR_SEQUENCE -#define _INCL_UNIXSTL_H_UNIXSTL_READDIR_SEQUENCE - -#ifndef __STLSOFT_DOCUMENTATION_SKIP_SECTION -# define _UNIXSTL_VER_H_UNIXSTL_READDIR_SEQUENCE_MAJOR 1 -# define _UNIXSTL_VER_H_UNIXSTL_READDIR_SEQUENCE_MINOR 5 -# define _UNIXSTL_VER_H_UNIXSTL_READDIR_SEQUENCE_REVISION 2 -# define _UNIXSTL_VER_H_UNIXSTL_READDIR_SEQUENCE_EDIT 42 -#endif /* !__STLSOFT_DOCUMENTATION_SKIP_SECTION */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Includes - */ - -#ifndef _INCL_UNIXSTL_H_UNIXSTL -# include "unixstl.h" // Include the UNIXSTL root header -#endif /* !_INCL_UNIXSTL_H_UNIXSTL */ -#ifndef _INCL_UNIXSTL_H_UNIXSTL_LIMITS -# include "unixstl_limits.h" // UNIXSTL_NAME_MAX -#endif /* !_INCL_UNIXSTL_H_UNIXSTL_LIMITS */ -#ifndef _STLSOFT_INCL_H_STLSOFT_FRAME_STRING -# include "stlsoft_frame_string.h" // stlsoft::basic_frame_string -#endif /* !_STLSOFT_INCL_H_STLSOFT_FRAME_STRING */ -#ifndef _STLSOFT_INCL_H_STLSOFT_ITERATOR -# include "stlsoft_iterator.h" -#endif /* !_STLSOFT_INCL_H_STLSOFT_ITERATOR */ - -#include -#include -#include - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace - * - * The UNIXSTL components are contained within the unixstl namespace. This is - * actually an alias for stlsoft::unixstl_project, - * - * The definition matrix is as follows: - * - * _STLSOFT_NO_NAMESPACE _UNIXSTL_NO_NAMESPACE unixstl definition - * --------------------- --------------------- ----------------- - * not defined not defined = stlsoft::unixstl_project - * not defined defined not defined - * defined not defined unixstl - * defined defined not defined - * - */ - -/* No STLSoft namespaces means no UNIXSTL namespaces */ -#ifdef _STLSOFT_NO_NAMESPACES -# define _UNIXSTL_NO_NAMESPACES -#endif /* _STLSOFT_NO_NAMESPACES */ - -/* No UNIXSTL namespaces means no unixstl namespace */ -#ifdef _UNIXSTL_NO_NAMESPACES -# define _UNIXSTL_NO_NAMESPACE -#endif /* _UNIXSTL_NO_NAMESPACES */ - -#ifndef _UNIXSTL_NO_NAMESPACE -# ifdef _STLSOFT_NO_NAMESPACE -/* There is no stlsoft namespace, so must define ::unixstl */ -namespace unixstl -{ -# else -/* Define stlsoft::unixstl_project */ - -namespace stlsoft -{ - -namespace unixstl_project -{ - -# endif /* _STLSOFT_NO_NAMESPACE */ -#endif /* !_UNIXSTL_NO_NAMESPACE */ - -/* ////////////////////////////////////////////////////////////////////////// */ - -/// \weakgroup libraries STLSoft Libraries -/// \brief The individual libraries - -/// \weakgroup libraries_filesystem File-System Library -/// \ingroup libraries -/// \brief This library provides facilities for defining and manipulating file-system objects - -/// \defgroup unixstl_filesystem_library File-System Library (UNIXSTL) -/// \ingroup UNIXSTL libraries_filesystem -/// \brief This library provides facilities for defining and manipulating UNIX file-system objects -/// @{ - -/* ///////////////////////////////////////////////////////////////////////////// - * Utility classes - */ - -#ifndef __STLSOFT_DOCUMENTATION_SKIP_SECTION -struct rds_shared_handle -{ - DIR *dir; - ss_sint32_t cRefs; - -public: - ss_explicit_k rds_shared_handle(DIR *d) - : dir(d) - , cRefs(1) - {} - void Release() - { - if(--cRefs == 0) - { - delete this; - } - } -#if defined(__STLSOFT_COMPILER_IS_GCC) -protected: -#else /* ? __STLSOFT_COMPILER_IS_GCC */ -private: -#endif /* __STLSOFT_COMPILER_IS_GCC */ - ~rds_shared_handle() - { - unixstl_message_assert("Shared search handle being destroyed with outstanding references!", 0 == cRefs); - - if(NULL != dir) - { - closedir(dir); - } - } -}; -#endif /* !__STLSOFT_DOCUMENTATION_SKIP_SECTION */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Classes - */ - -/// \brief Iterator for readdir_sequence class -/// -/// This class performs as a non-mutating iterator (aka const iterator) for the -/// readdir_sequence class. -/// -/// - -class readdir_sequence_const_iterator - : public stlsoft_ns_qual(iterator_base) < unixstl_ns_qual_std(input_iterator_tag) - , struct dirent const * - , us_ptrdiff_t - , struct dirent const ** - , struct dirent const *& - > -{ -public: - /// The class type - typedef readdir_sequence_const_iterator class_type; - /// The type on the rhs of move expressions - typedef stlsoft_define_move_rhs_type(class_type) rhs_type; - /// The value type - typedef struct dirent const *value_type; -// typedef value_type *pointer; -// typedef value_type &reference; - -// Construction -private: - friend class readdir_sequence; - - enum - { - includeDots = 0x0008 /*!< Requests that dots directories be included in the returned sequence */ - , directories = 0x0010 /*!< Causes the search to include directories */ - , files = 0x0020 /*!< Causes the search to include files */ -#ifndef __STLSOFT_DOCUMENTATION_SKIP_SECTION - , noSort = 0 /* 0x0100 */ //!< -#endif /* !__STLSOFT_DOCUMENTATION_SKIP_SECTION */ - , - }; - - /// Construct an instance and begin a sequence iteration on the given dir. - readdir_sequence_const_iterator(DIR *dir, us_uint_t flags) - : m_handle(new rds_shared_handle(dir)) - , m_entry(NULL) - , m_flags(flags) - { - // It's more efficient to not bother doing a separate dots check if all - // directories are being elided. - if(0 == (m_flags & directories)) - { - m_flags |= includeDots; - } - - if(NULL != m_handle) - { - operator ++(); - } - } - /// Constructs an instance based on the given directory entry - readdir_sequence_const_iterator(dirent *entry) - : m_handle(NULL) - , m_entry(entry) - {} -public: - /// Default constructor - readdir_sequence_const_iterator() - : m_handle(NULL) - , m_entry(NULL) - {} - /// Move constructor - readdir_sequence_const_iterator(class_type const &rhs) - : m_handle(rhs.m_handle) - , m_entry(rhs.m_entry) - { - if(NULL != m_handle) - { - ++m_handle->cRefs; - } - } - /// Release the search handle - ~readdir_sequence_const_iterator() unixstl_throw_0() - { - if(NULL != m_handle) - { - m_handle->Release(); - } - } - - /// Move assignment operator - class_type const &operator =(rhs_type rhs) - { - m_handle = rhs.m_handle; - if(NULL != m_handle) - { - m_handle->Release(); - } - - m_entry = rhs.m_entry; - m_flags = rhs.m_flags; - - if(NULL != m_handle) - { - ++m_handle->cRefs; - } - - return *this; - } - -// Accessors -public: - /// Returns the value representative - value_type operator *() const - { - unixstl_message_assert( "Dereferencing invalid iterator", NULL != m_entry); - - return m_entry; - } - - /// Moves the iteration on to the next point in the sequence, or end() if - /// the sequence is exhausted - class_type &operator ++() - { - unixstl_message_assert( "Incrementing invalid iterator", NULL != m_handle); - - for(;;) - { - m_entry = readdir(m_handle->dir); - - if(NULL != m_entry) - { - unixstl_assert(NULL != m_entry->d_name); - - if(0 == (m_flags & includeDots)) - { - if( m_entry->d_name[0] == '.' && - ( m_entry->d_name[1] == '\0' || - ( m_entry->d_name[1] == '.' && - m_entry->d_name[2] == '\0'))) - { - continue; // Don't want dots; skip it - } - } - - if((m_flags & (directories | files)) != (directories | files)) - { - // Now need to process the file, by using stat - struct stat st; - - if(0 != stat(m_entry->d_name, &st)) - { - // Failed to get info from entry. Must assume it is - // dead, so skip it - continue; - } - else - { - if(m_flags & directories) // Want directories - { - if(S_IFDIR == (st.st_mode & S_IFDIR)) - { - // It is a directory, so accept it - break; - } - } - if(m_flags & files) // Want files - { - if(S_IFREG == (st.st_mode & S_IFREG)) - { - // It is a file, so accept it - break; - } - } - - continue; // Not a match, so skip this entry - } - } - } - - break; - } - - if(NULL == m_entry) - { - unixstl_assert(NULL != m_handle); - - m_handle->Release(); - - m_handle = NULL; - } - - return *this; - } - /// Post-increment form of operator ++(). - /// - /// \note Because this version uses a temporary on which to call the - /// pre-increment form it is thereby less efficient, and should not be used - /// except where post-increment semantics are required. - class_type operator ++(int) - { - class_type ret(*this); - - operator ++(); - - return ret; - } - - /// Compares \c this for equality with \c rhs - /// - /// \param rhs The instance against which to test - /// \retval true if the iterators are equivalent - /// \retval false if the iterators are not equivalent - bool operator ==(class_type const &rhs) const - { - unixstl_assert(NULL == m_handle || NULL == rhs.m_handle || m_handle->dir == rhs.m_handle->dir); - - return m_entry == rhs.m_entry; - } - /// Compares \c this for inequality with \c rhs - /// - /// \param rhs The instance against which to test - /// \retval false if the iterators are equivalent - /// \retval true if the iterators are not equivalent - bool operator !=(class_type const &rhs) const - { - return !operator ==(rhs); - } - -// Members -private: - rds_shared_handle *m_handle; - struct dirent *m_entry; - us_uint_t m_flags; - -// Not to be implemented -private: -}; - - -/// \brief STL-like readonly sequence based on directory contents -/// -/// This class presents and STL-like readonly sequence interface to allow the -/// iteration over the contents of a directory. - -class readdir_sequence -{ -private: - typedef readdir_sequence class_type; -public: -// typedef us_size_t size_type; - typedef readdir_sequence_const_iterator const_iterator; - typedef readdir_sequence_const_iterator::value_type value_type; -// typedef readdir_sequence_const_iterator::pointer pointer; -// typedef readdir_sequence_const_iterator::pointer const const_pointer; -// typedef readdir_sequence_const_iterator::reference reference; - typedef readdir_sequence_const_iterator::reference const const_reference; - -private: - typedef stlsoft_ns_qual(basic_frame_string) < us_char_a_t - , UNIXSTL_NAME_MAX - > string_type; - -public: - enum - { - includeDots = const_iterator::includeDots /*!< Requests that dots directories be included in the returned sequence */ - , directories = const_iterator::directories /*!< Causes the search to include directories */ - , files = const_iterator::files /*!< Causes the search to include files */ -#ifndef __STLSOFT_DOCUMENTATION_SKIP_SECTION - , noSort = const_iterator::noSort /* 0x0100 */ //!< -#endif /* !__STLSOFT_DOCUMENTATION_SKIP_SECTION */ - , - }; - -// Construction -public: - /// \brief Constructs a sequence according to the given criteria - /// - /// The constructor initialises a readdir_sequence instance on the given - /// directory with the given flags. - /// - /// \param name The directory whose contents are to be searched - /// \param flags Flags to alter the behaviour of the search - /// - /// \note The \c flags parameter defaults to directories | files because - /// this reflects the default behaviour of \c readdir(), and also because it is the - /// most efficient. - readdir_sequence(us_char_a_t const *name, us_int_t flags = directories | files) - : m_name(name) - , m_flags(validate_flags_(flags)) - {} - -// Iteration -public: - /// Begins the iteration - /// - /// \return An iterator representing the start of the sequence - const_iterator begin() const - { - DIR *dir = opendir(m_name.c_str()); - - return const_iterator(dir, m_flags); - } - /// Ends the iteration - /// - /// \return An iterator representing the end of the sequence - const_iterator end() const - { - return const_iterator(); - } - -// Attributes -public: -#if 0 - /// Returns the number of elements in the sequence - /// - /// \note Nor currently implemented - size_type size() const - { - return 0; - } -#endif /* 0 */ - - /// \brief Indicates whether the search sequence is empty - us_bool_t empty() const - { - return begin() != end(); - } - -// Implementation -private: - /// \brief Ensures that the flags are correct - static us_int_t validate_flags_(us_int_t flags) - { - return (0 == (flags & (directories | files))) ? (flags | (directories | files)) : flags; - } - -// Members -private: - string_type m_name; - us_int_t m_flags; -}; - -/* ////////////////////////////////////////////////////////////////////////// */ - -/// @} // end of group unixstl_filesystem_library - -/* ////////////////////////////////////////////////////////////////////////// */ - -#ifndef _UNIXSTL_NO_NAMESPACE -# ifdef _STLSOFT_NO_NAMESPACE -} // namespace unixstl -# else -} // namespace unixstl_project -} // namespace stlsoft -# endif /* _STLSOFT_NO_NAMESPACE */ -#endif /* !_UNIXSTL_NO_NAMESPACE */ - -/* ////////////////////////////////////////////////////////////////////////// */ - -#endif /* !_INCL_UNIXSTL_H_UNIXSTL_READDIR_SEQUENCE */ - -/* ////////////////////////////////////////////////////////////////////////// */ diff -uNr gdc-0.17/d/phobos/etc/c/stlsoft/unixstl_spin_mutex.h gdc-0.18/d/phobos/etc/c/stlsoft/unixstl_spin_mutex.h --- gdc-0.17/d/phobos/etc/c/stlsoft/unixstl_spin_mutex.h 2004-10-26 02:41:27.000000000 +0200 +++ gdc-0.18/d/phobos/etc/c/stlsoft/unixstl_spin_mutex.h 1970-01-01 01:00:00.000000000 +0100 @@ -1,260 +0,0 @@ -/* //////////////////////////////////////////////////////////////////////////// - * File: unixstl_spin_mutex.h (originally MWSpinMx.h, ::SynesisWin) - * - * Purpose: Intra-process mutex, based on spin waits. - * - * Date: 27th August 1997 - * Updated: 23rd November 2003 - * - * Author: Matthew Wilson, Synesis Software Pty Ltd. - * - * License: (Licensed under the Synesis Software Standard Source License) - * - * Copyright (C) 2002-2003, Synesis Software Pty Ltd. - * - * All rights reserved. - * - * www: http://www.synesis.com.au/unixstl - * http://www.unixstl.org/ - * - * email: submissions@unixstl.org for submissions - * admin@unixstl.org for other enquiries - * - * Redistribution and use in source and binary forms, with or - * without modification, are permitted provided that the following - * conditions are met: - * - * (i) Redistributions of source code must retain the above - * copyright notice and contact information, this list of - * conditions and the following disclaimer. - * - * (ii) Any derived versions of this software (howsoever modified) - * remain the sole property of Synesis Software. - * - * (iii) Any derived versions of this software (howsoever modified) - * remain subject to all these conditions. - * - * (iv) Neither the name of Synesis Software nor the names of any - * subdivisions, employees or agents of Synesis Software, nor the - * names of any other contributors to this software may be used to - * endorse or promote products derived from this software without - * specific prior written permission. - * - * This source code is provided by Synesis Software "as is" and any - * warranties, whether expressed or implied, including, but not - * limited to, the implied warranties of merchantability and - * fitness for a particular purpose are disclaimed. In no event - * shall the Synesis Software be liable for any direct, indirect, - * incidental, special, exemplary, or consequential damages - * (including, but not limited to, procurement of substitute goods - * or services; loss of use, data, or profits; or business - * interruption) however caused and on any theory of liability, - * whether in contract, strict liability, or tort (including - * negligence or otherwise) arising in any way out of the use of - * this software, even if advised of the possibility of such - * damage. - * - * ////////////////////////////////////////////////////////////////////////// */ - - -#ifndef _UNIXSTL_INCL_H_UNIXSTL_SPIN_MUTEX -#define _UNIXSTL_INCL_H_UNIXSTL_SPIN_MUTEX - -#ifndef __STLSOFT_DOCUMENTATION_SKIP_SECTION -#define _UNIXSTL_VER_H_UNIXSTL_SPIN_MUTEX_MAJOR 1 -#define _UNIXSTL_VER_H_UNIXSTL_SPIN_MUTEX_MINOR 2 -#define _UNIXSTL_VER_H_UNIXSTL_SPIN_MUTEX_REVISION 2 -#define _UNIXSTL_VER_H_UNIXSTL_SPIN_MUTEX_EDIT 8 -#endif /* !__STLSOFT_DOCUMENTATION_SKIP_SECTION */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Includes - */ - -#ifndef _UNIXSTL_INCL_H_UNIXSTL -# include "unixstl.h" // Include the UNIXSTL root header -#endif /* !_UNIXSTL_INCL_H_UNIXSTL */ -#include // Only works for Linux. For other OSs, use unixstl_process_mutex.h - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace - */ - -#ifndef _UNIXSTL_NO_NAMESPACE -# ifdef _STLSOFT_NO_NAMESPACE -/* There is no stlsoft namespace, so must define ::unixstl */ -namespace unixstl -{ -# else -/* Define stlsoft::unixstl_project */ - -namespace stlsoft -{ - -namespace unixstl_project -{ - -# endif /* _STLSOFT_NO_NAMESPACE */ -#endif /* !_UNIXSTL_NO_NAMESPACE */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Classes - */ - -// class spin_mutex -/// This class provides an implementation of the mutex model based on a spinning mechanism -class spin_mutex -{ -public: - typedef spin_mutex class_type; - -// Construction -public: - /// Creates an instance of the mutex - ss_explicit_k spin_mutex(us_sint32_t *p) unixstl_throw_0() - : m_spinCount((NULL != p) ? p : &m_internalCount) - , m_internalCount(0) -#ifdef STLSOFT_SPINMUTEX_COUNT_LOCKS - , m_cLocks(0) -#endif // STLSOFT_SPINMUTEX_COUNT_LOCKS - {} - /// Destroys an instance of the mutex - ~spin_mutex() unixstl_throw_0() - { -#ifdef STLSOFT_SPINMUTEX_COUNT_LOCKS - stlsoft_assert(m_cLocks == 0); -#endif // STLSOFT_SPINMUTEX_COUNT_LOCKS - } - -// Operations -public: - /// Acquires a lock on the mutex, pending the thread until the lock is aquired - void lock() unixstl_throw_0() - { - for(; 0 != atomic_write((LPLONG)m_spinCount, 1); ::Sleep(1)) - {} -#ifdef STLSOFT_SPINMUTEX_COUNT_LOCKS - stlsoft_assert(++m_cLocks != 0); -#endif // STLSOFT_SPINMUTEX_COUNT_LOCKS - } - /// Releases an aquired lock on the mutex - void unlock() unixstl_throw_0() - { -#ifdef STLSOFT_SPINMUTEX_COUNT_LOCKS - stlsoft_assert(m_cLocks-- != 0); -#endif // STLSOFT_SPINMUTEX_COUNT_LOCKS - atomic_write(m_spinCount, 0); - } - -// Members -private: - us_sint32_t *m_spinCount; - us_sint32_t m_internalCount; -#ifdef STLSOFT_SPINMUTEX_COUNT_LOCKS - us_sint32_t m_cLocks; // Used as check on matched Lock/Unlock calls -#endif // STLSOFT_SPINMUTEX_COUNT_LOCKS - -// Not to be implemented -private: - spin_mutex(class_type const &rhs); - spin_mutex &operator =(class_type const &rhs); -}; - -/* ///////////////////////////////////////////////////////////////////////////// - * Control shims - */ - -#ifndef _UNIXSTL_NO_NAMESPACE -# ifdef _STLSOFT_NO_NAMESPACE -} // namespace unixstl -# else -} // namespace unixstl_project -# endif /* _STLSOFT_NO_NAMESPACE */ -#endif /* !_UNIXSTL_NO_NAMESPACE */ - -/// \weakgroup concepts STLSoft Concepts - -/// \weakgroup concepts_shims Shims -/// \ingroup concepts - -/// \weakgroup concepts_shims_sync_control Synchronisation Control Shims -/// \ingroup concepts_shims -/// \brief These \ref concepts_shims "shims" control the behaviour of synchronisation objects - -/// \defgroup unixstl_sync_control_shims Synchronisation Control Shims (UNIXSTL) -/// \ingroup UNIXSTL concepts_shims_sync_control -/// \brief These \ref concepts_shims "shims" control the behaviour of Win32 synchronisation objects -/// @{ - -/// This control ref concepts_shims "shim" aquires a lock on the given mutex -/// -/// \param mx The mutex on which to aquire the lock -inline void lock_instance(unixstl_ns_qual(spin_mutex) &mx) -{ - mx.lock(); -} - -/// This control ref concepts_shims "shim" releases a lock on the given mutex -/// -/// \param mx The mutex on which to release the lock -inline void unlock_instance(unixstl_ns_qual(spin_mutex) &mx) -{ - mx.unlock(); -} - -/// @} // end of group unixstl_sync_control_shims - -#ifndef _UNIXSTL_NO_NAMESPACE -# ifdef _STLSOFT_NO_NAMESPACE -namespace unixstl -{ -# else -namespace unixstl_project -{ -# endif /* _STLSOFT_NO_NAMESPACE */ -#endif /* !_UNIXSTL_NO_NAMESPACE */ - -/* ///////////////////////////////////////////////////////////////////////////// - * lock_traits (for the compilers that do not support Koenig Lookup) - */ - -// class lock_traits -/// Traits for the spin_mutex class (for compilers that do not support Koenig Lookup) -struct spin_mutex_lock_traits -{ -public: - /// The lockable type - typedef spin_mutex lock_type; - typedef spin_mutex_lock_traits class_type; - -// Operations -public: - /// Lock the given spin_mutex instance - static void lock(spin_mutex &c) - { - lock_instance(c); - } - - /// Unlock the given spin_mutex instance - static void unlock(spin_mutex &c) - { - unlock_instance(c); - } -}; - -/* ////////////////////////////////////////////////////////////////////////// */ - -#ifndef _UNIXSTL_NO_NAMESPACE -# ifdef _STLSOFT_NO_NAMESPACE -} // namespace unixstl -# else -} // namespace unixstl_project -} // namespace stlsoft -# endif /* _STLSOFT_NO_NAMESPACE */ -#endif /* !_UNIXSTL_NO_NAMESPACE */ - -/* ////////////////////////////////////////////////////////////////////////// */ - -#endif /* !_WINSTL_INCL_H_UNIXSTL_SPIN_MUTEX */ - -/* ////////////////////////////////////////////////////////////////////////// */ diff -uNr gdc-0.17/d/phobos/etc/c/stlsoft/unixstl_string_access.h gdc-0.18/d/phobos/etc/c/stlsoft/unixstl_string_access.h --- gdc-0.17/d/phobos/etc/c/stlsoft/unixstl_string_access.h 2004-10-26 02:41:27.000000000 +0200 +++ gdc-0.18/d/phobos/etc/c/stlsoft/unixstl_string_access.h 1970-01-01 01:00:00.000000000 +0100 @@ -1,209 +0,0 @@ -/* ///////////////////////////////////////////////////////////////////////////// - * File: unixstl_string_access.h - * - * Purpose: Contains classes and functions for dealing with OLE/COM strings. - * - * Created: 11th January 2003 - * Updated: 13th August 2003 - * - * Author: Matthew Wilson, Synesis Software Pty Ltd. - * - * License: (Licensed under the Synesis Software Standard Source License) - * - * Copyright (C) 2002-2003, Synesis Software Pty Ltd. - * - * All rights reserved. - * - * www: http://www.synesis.com.au/unixstl - * http://www.unixstl.org/ - * - * email: submissions@unixstl.org for submissions - * admin@unixstl.org for other enquiries - * - * Redistribution and use in source and binary forms, with or - * without modification, are permitted provided that the following - * conditions are met: - * - * (i) Redistributions of source code must retain the above - * copyright notice and contact information, this list of - * conditions and the following disclaimer. - * - * (ii) Any derived versions of this software (howsoever modified) - * remain the sole property of Synesis Software. - * - * (iii) Any derived versions of this software (howsoever modified) - * remain subject to all these conditions. - * - * (iv) Neither the name of Synesis Software nor the names of any - * subdivisions, employees or agents of Synesis Software, nor the - * names of any other contributors to this software may be used to - * endorse or promote products derived from this software without - * specific prior written permission. - * - * This source code is provided by Synesis Software "as is" and any - * warranties, whether expressed or implied, including, but not - * limited to, the implied warranties of merchantability and - * fitness for a particular purpose are disclaimed. In no event - * shall the Synesis Software be liable for any direct, indirect, - * incidental, special, exemplary, or consequential damages - * (including, but not limited to, procurement of substitute goods - * or services; loss of use, data, or profits; or business - * interruption) however caused and on any theory of liability, - * whether in contract, strict liability, or tort (including - * negligence or otherwise) arising in any way out of the use of - * this software, even if advised of the possibility of such - * damage. - * - * ////////////////////////////////////////////////////////////////////////// */ - - -#ifndef _UNIXSTL_INCL_H_UNIXSTL_STRING_ACCESS -#define _UNIXSTL_INCL_H_UNIXSTL_STRING_ACCESS - -#ifndef __STLSOFT_DOCUMENTATION_SKIP_SECTION -#define _UNIXSTL_VER_H_UNIXSTL_STRING_ACCESS_MAJOR 1 -#define _UNIXSTL_VER_H_UNIXSTL_STRING_ACCESS_MINOR 1 -#define _UNIXSTL_VER_H_UNIXSTL_STRING_ACCESS_REVISION 2 -#define _UNIXSTL_VER_H_UNIXSTL_STRING_ACCESS_EDIT 10 -#endif /* !__STLSOFT_DOCUMENTATION_SKIP_SECTION */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Includes - */ - -#ifndef _UNIXSTL_INCL_H_UNIXSTL - #include "unixstl.h" // Include the UNIXSTL root header -#endif /* !_UNIXSTL_INCL_H_UNIXSTL */ -#include - -/* ///////////////////////////////////////////////////////////////////////////// - * Forward declarations - */ - -struct dirent; - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace - * - * The UNIXSTL components are contained within the unixstl namespace. This is - * actually an alias for stlsoft::unixstl_project, - * - * The definition matrix is as follows: - * - * _STLSOFT_NO_NAMESPACE _UNIXSTL_NO_NAMESPACE unixstl definition - * --------------------- -------------------- ----------------- - * not defined not defined = stlsoft::unixstl_project - * not defined defined not defined - * defined not defined unixstl - * defined defined not defined - * - */ - -#ifndef _UNIXSTL_NO_NAMESPACE - #ifdef _STLSOFT_NO_NAMESPACE -/* There is no stlsoft namespace, so must define ::unixstl */ -namespace unixstl -{ - #else -/* Define stlsoft::unixstl_project */ - -namespace stlsoft -{ - -namespace unixstl_project -{ - - #endif /* _STLSOFT_NO_NAMESPACE */ -#endif /* !_UNIXSTL_NO_NAMESPACE */ - -/* ////////////////////////////////////////////////////////////////////////// */ - -/// \weakgroup concepts STLSoft Concepts - -/// \weakgroup concepts_shims Shims -/// \ingroup concepts - -/// \weakgroup concepts_shims_string_access String Access Shims -/// \ingroup concepts_shims -/// \brief These \ref concepts_shims "shims" retrieve the C-string for arbitrary types - -/// \defgroup unixstl_string_access_shims String Access Shims (UNIXSTL) -/// \ingroup UNIXSTL concepts_shims_string_access -/// \brief These \ref concepts_shims "shims" retrieve the C-string for arbitrary types -/// @{ - -/* ///////////////////////////////////////////////////////////////////////////// - * c_str_ptr_null - * - * This can be applied to an expression, and the return value is either a - * pointer to the character string or NULL. - */ - -/// \brief Returns the corresponding C-string pointer of the dirent structure \c d, or NULL if \c d is empty -inline us_char_a_t const *c_str_ptr_null(struct dirent const *d) -{ - return (d == 0 || d->d_name[0] == 0) ? 0 : d->d_name; -} - -/// \brief Returns the corresponding C-string pointer of the dirent structure \c d, or NULL if \c d is empty -inline us_char_a_t const *c_str_ptr_null(struct dirent const &d) -{ - return d.d_name[0] == 0 ? 0 : d.d_name; -} - -/* ///////////////////////////////////////////////////////////////////////////// - * c_str_ptr - * - * This can be applied to an expression, and the return value is either a - * pointer to the character string or to an empty string. - */ - -/// \brief Returns the corresponding C-string pointer of the dirent structure \c d -inline us_char_a_t const *c_str_ptr(struct dirent const *d) -{ - return (d == 0) ? "" : d->d_name; -} - -/// \brief Returns the corresponding C-string pointer of the dirent structure \c d -inline us_char_a_t const *c_str_ptr(struct dirent const &d) -{ - return d.d_name; -} - -/* ///////////////////////////////////////////////////////////////////////////// - * c_str_len - * - * This can be applied to an expression, and the return value is the number of - * characters in the character string in the expression. - */ - - -/* ///////////////////////////////////////////////////////////////////////////// - * c_str_size - * - * This can be applied to an expression, and the return value is the number of - * bytes required to store the character string in the expression, NOT including - * the null-terminating character. - */ - - -/* ////////////////////////////////////////////////////////////////////////// */ - -/// @} // end of group unixstl_string_access_shims - -/* ////////////////////////////////////////////////////////////////////////// */ - -#ifndef _UNIXSTL_NO_NAMESPACE - #ifdef _STLSOFT_NO_NAMESPACE -} // namespace unixstl - #else -} // namespace unixstl_project -} // namespace stlsoft - #endif /* _STLSOFT_NO_NAMESPACE */ -#endif /* !_UNIXSTL_NO_NAMESPACE */ - -/* ////////////////////////////////////////////////////////////////////////// */ - -#endif /* !_UNIXSTL_INCL_H_UNIXSTL_STRING_ACCESS */ - -/* ////////////////////////////////////////////////////////////////////////// */ diff -uNr gdc-0.17/d/phobos/etc/c/stlsoft/unixstl_thread_mutex.h gdc-0.18/d/phobos/etc/c/stlsoft/unixstl_thread_mutex.h --- gdc-0.17/d/phobos/etc/c/stlsoft/unixstl_thread_mutex.h 2004-10-26 02:41:27.000000000 +0200 +++ gdc-0.18/d/phobos/etc/c/stlsoft/unixstl_thread_mutex.h 1970-01-01 01:00:00.000000000 +0100 @@ -1,283 +0,0 @@ -/* //////////////////////////////////////////////////////////////////////////// - * File: unixstl_thread_mutex.h (originally MLCrtSct.h, ::SynesisStd) - * - * Purpose: Intra-process mutext, based on PTHREADS CRITICAL_SECTION. - * - * Date: 17th December 1996 - * Updated: 23rd November 2003 - * - * Author: Matthew Wilson, Synesis Software Pty Ltd. - * - * License: (Licensed under the Synesis Software Standard Source License) - * - * Copyright (C) 2002-2003, Synesis Software Pty Ltd. - * - * All rights reserved. - * - * www: http://www.synesis.com.au/unixstl - * http://www.unixstl.org/ - * - * email: submissions@unixstl.org for submissions - * admin@unixstl.org for other enquiries - * - * Redistribution and use in source and binary forms, with or - * without modification, are permitted provided that the following - * conditions are met: - * - * (i) Redistributions of source code must retain the above - * copyright notice and contact information, this list of - * conditions and the following disclaimer. - * - * (ii) Any derived versions of this software (howsoever modified) - * remain the sole property of Synesis Software. - * - * (iii) Any derived versions of this software (howsoever modified) - * remain subject to all these conditions. - * - * (iv) Neither the name of Synesis Software nor the names of any - * subdivisions, employees or agents of Synesis Software, nor the - * names of any other contributors to this software may be used to - * endorse or promote products derived from this software without - * specific prior written permission. - * - * This source code is provided by Synesis Software "as is" and any - * warranties, whether expressed or implied, including, but not - * limited to, the implied warranties of merchantability and - * fitness for a particular purpose are disclaimed. In no event - * shall the Synesis Software be liable for any direct, indirect, - * incidental, special, exemplary, or consequential damages - * (including, but not limited to, procurement of substitute goods - * or services; loss of use, data, or profits; or business - * interruption) however caused and on any theory of liability, - * whether in contract, strict liability, or tort (including - * negligence or otherwise) arising in any way out of the use of - * this software, even if advised of the possibility of such - * damage. - * - * ////////////////////////////////////////////////////////////////////////// */ - - -#ifndef _UNIXSTL_INCL_H_UNIXSTL_THREAD_MUTEX -#define _UNIXSTL_INCL_H_UNIXSTL_THREAD_MUTEX - -#ifndef __STLSOFT_DOCUMENTATION_SKIP_SECTION -# define _UNIXSTL_VER_H_UNIXSTL_THREAD_MUTEX_MAJOR 1 -# define _UNIXSTL_VER_H_UNIXSTL_THREAD_MUTEX_MINOR 2 -# define _UNIXSTL_VER_H_UNIXSTL_THREAD_MUTEX_REVISION 2 -# define _UNIXSTL_VER_H_UNIXSTL_THREAD_MUTEX_EDIT 10 -#endif /* !__STLSOFT_DOCUMENTATION_SKIP_SECTION */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Includes - */ - -#ifndef _UNIXSTL_INCL_H_UNIXSTL -# include "unixstl.h" // Include the UNIXSTL root header -#endif /* !_UNIXSTL_INCL_H_UNIXSTL */ -#if !defined(_REENTRANT) && \ - !defined(_POSIX_THREADS) -# error unixstl_thread_mutex.h must be compiled in the context of PTHREADS -#endif /* !_REENTRANT && !_POSIX_THREADS */ -#include - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace - */ - -#ifndef _UNIXSTL_NO_NAMESPACE -# ifdef _STLSOFT_NO_NAMESPACE -/* There is no stlsoft namespace, so must define ::unixstl */ -namespace unixstl -{ -# else -/* Define stlsoft::unixstl_project */ - -namespace stlsoft -{ - -namespace unixstl_project -{ - -# endif /* _STLSOFT_NO_NAMESPACE */ -#endif /* !_UNIXSTL_NO_NAMESPACE */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Classes - */ - -// class thread_mutex -/// This class provides an implementation of the mutex model based on the PTHREADS mutex -class thread_mutex -{ -public: - typedef thread_mutex class_type; - -// Construction -public: - /// Creates an instance of the mutex - ss_explicit_k thread_mutex(us_bool_t bRecursive = true) unixstl_throw_0() - : m_init(create_(&m_mx, bRecursive)) - {} - /// Destroys an instance of the mutex - ~thread_mutex() unixstl_throw_0() - { - if(m_init) - { - ::pthread_mutex_destroy(&m_mx); - } - } - -// Operations -public: - /// Acquires a lock on the mutex, pending the thread until the lock is aquired - void lock() unixstl_throw_0() - { - pthread_mutex_lock(&m_mx); - } - /// Attempts to lock the mutex - /// - /// \return true if the mutex was aquired, or false if not - /// \note Only available with Windows NT 4 and later - bool try_lock() - { - return pthread_mutex_trylock(&m_mx) == 0; - } - /// Releases an aquired lock on the mutex - void unlock() unixstl_throw_0() - { - pthread_mutex_unlock(&m_mx); - } - -// Implementation -private: - static us_bool_t create_(pthread_mutex_t *mx, us_bool_t bRecursive) - { - us_bool_t bSuccess = false; - pthread_mutexattr_t attr; - - if(0 == ::pthread_mutexattr_init(&attr)) - { - if( !bRecursive || - 0 == ::pthread_mutexattr_settype(&attr, PTHREAD_MUTEX_RECURSIVE)) - { - if(0 == ::pthread_mutex_init(mx, &attr)) - { - bSuccess = true; - } - } - - ::pthread_mutexattr_destroy(&attr); - } - - return bSuccess; - } - -// Members -private: - pthread_mutex_t m_mx; // mx - us_bool_t m_init; - -// Not to be implemented -private: - thread_mutex(class_type const &rhs); - thread_mutex &operator =(class_type const &rhs); -}; - -/* ///////////////////////////////////////////////////////////////////////////// - * Control shims - */ - -#ifndef _UNIXSTL_NO_NAMESPACE -# ifdef _STLSOFT_NO_NAMESPACE -} // namespace unixstl -# else -} // namespace unixstl_project -# endif /* _STLSOFT_NO_NAMESPACE */ -#endif /* !_UNIXSTL_NO_NAMESPACE */ - -/// \weakgroup concepts STLSoft Concepts - -/// \weakgroup concepts_shims Shims -/// \ingroup concepts - -/// \weakgroup concepts_shims_sync_control Synchronisation Control Shims -/// \ingroup concepts_shims -/// \brief These \ref concepts_shims "shims" control the behaviour of synchronisation objects - -/// \defgroup unixstl_sync_control_shims Synchronisation Control Shims (UNIXSTL) -/// \ingroup UNIXSTL concepts_shims_sync_control -/// \brief These \ref concepts_shims "shims" control the behaviour of Win32 synchronisation objects -/// @{ - -/// This control ref concepts_shims "shim" aquires a lock on the given mutex -/// -/// \param mx The mutex on which to aquire the lock -inline void lock_instance(unixstl_ns_qual(thread_mutex) &mx) -{ - mx.lock(); -} - -/// This control ref concepts_shims "shim" releases a lock on the given mutex -/// -/// \param mx The mutex on which to release the lock -inline void unlock_instance(unixstl_ns_qual(thread_mutex) &mx) -{ - mx.unlock(); -} - -/// @} // end of group unixstl_sync_control_shims - -#ifndef _UNIXSTL_NO_NAMESPACE -# ifdef _STLSOFT_NO_NAMESPACE -namespace unixstl -{ -# else -namespace unixstl_project -{ -# endif /* _STLSOFT_NO_NAMESPACE */ -#endif /* !_UNIXSTL_NO_NAMESPACE */ - -/* ///////////////////////////////////////////////////////////////////////////// - * lock_traits (for the compilers that do not support Koenig Lookup) - */ - -// class lock_traits -/// Traits for the thread_mutex class (for compilers that do not support Koenig Lookup) -struct thread_mutex_lock_traits -{ -public: - /// The lockable type - typedef thread_mutex lock_type; - typedef thread_mutex_lock_traits class_type; - -// Operations -public: - /// Lock the given thread_mutex instance - static void lock(thread_mutex &c) - { - lock_instance(c); - } - - /// Unlock the given thread_mutex instance - static void unlock(thread_mutex &c) - { - unlock_instance(c); - } -}; - -/* ////////////////////////////////////////////////////////////////////////// */ - -#ifndef _UNIXSTL_NO_NAMESPACE -# ifdef _STLSOFT_NO_NAMESPACE -} // namespace unixstl -# else -} // namespace unixstl_project -} // namespace stlsoft -# endif /* _STLSOFT_NO_NAMESPACE */ -#endif /* !_UNIXSTL_NO_NAMESPACE */ - -/* ////////////////////////////////////////////////////////////////////////// */ - -#endif /* !_UNIXSTL_INCL_H_UNIXSTL_THREAD_MUTEX */ - -/* ////////////////////////////////////////////////////////////////////////// */ diff -uNr gdc-0.17/d/phobos/etc/c/stlsoft/winstl_atomic_functions.h gdc-0.18/d/phobos/etc/c/stlsoft/winstl_atomic_functions.h --- gdc-0.17/d/phobos/etc/c/stlsoft/winstl_atomic_functions.h 2004-10-26 02:41:27.000000000 +0200 +++ gdc-0.18/d/phobos/etc/c/stlsoft/winstl_atomic_functions.h 1970-01-01 01:00:00.000000000 +0100 @@ -1,1559 +0,0 @@ -/* ///////////////////////////////////////////////////////////////////////////// - * File: winstl_atomic_functions.h (formerly MLAtomic.cpp, ::SynesisStd) - * - * Purpose: WinSTL atomic functions. - * - * Created: 23rd October 1997 - * Updated: 17th November 2003 - * - * Author: Matthew Wilson, Synesis Software Pty Ltd. - * - * License: (Licensed under the Synesis Software Standard Source License) - * - * Copyright (C) 2002-2003, Synesis Software Pty Ltd. - * - * All rights reserved. - * - * www: http://www.synesis.com.au/winstl - * http://www.winstl.org/ - * - * email: submissions@winstl.org for submissions - * admin@winstl.org for other enquiries - * - * Redistribution and use in source and binary forms, with or - * without modification, are permitted provided that the following - * conditions are met: - * - * (i) Redistributions of source code must retain the above - * copyright notice and contact information, this list of - * conditions and the following disclaimer. - * - * (ii) Any derived versions of this software (howsoever modified) - * remain the sole property of Synesis Software. - * - * (iii) Any derived versions of this software (howsoever modified) - * remain subject to all these conditions. - * - * (iv) Neither the name of Synesis Software nor the names of any - * subdivisions, employees or agents of Synesis Software, nor the - * names of any other contributors to this software may be used to - * endorse or promote products derived from this software without - * specific prior written permission. - * - * This source code is provided by Synesis Software "as is" and any - * warranties, whether expressed or implied, including, but not - * limited to, the implied warranties of merchantability and - * fitness for a particular purpose are disclaimed. In no event - * shall the Synesis Software be liable for any direct, indirect, - * incidental, special, exemplary, or consequential damages - * (including, but not limited to, procurement of substitute goods - * or services; loss of use, data, or profits; or business - * interruption) however caused and on any theory of liability, - * whether in contract, strict liability, or tort (including - * negligence or otherwise) arising in any way out of the use of - * this software, even if advised of the possibility of such - * damage. - * - * ////////////////////////////////////////////////////////////////////////// */ - - -#ifndef _WINSTL_INCL_H_WINSTL_ATOMIC_FUNCTIONS -#define _WINSTL_INCL_H_WINSTL_ATOMIC_FUNCTIONS - -#ifndef __STLSOFT_DOCUMENTATION_SKIP_SECTION -#define _WINSTL_VER_H_WINSTL_ATOMIC_FUNCTIONS_MAJOR 2 -#define _WINSTL_VER_H_WINSTL_ATOMIC_FUNCTIONS_MINOR 5 -#define _WINSTL_VER_H_WINSTL_ATOMIC_FUNCTIONS_REVISION 1 -#define _WINSTL_VER_H_WINSTL_ATOMIC_FUNCTIONS_EDIT 156 -#endif /* !__STLSOFT_DOCUMENTATION_SKIP_SECTION */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Includes - */ - -#ifndef _WINSTL_INCL_H_WINSTL -# include "winstl.h" // Include the WinSTL root header -#endif /* !_WINSTL_INCL_H_WINSTL */ -#ifndef _WINSTL_INCL_H_SPINMUTEXT -# include "winstl_spin_mutex.h" -#endif /* _WINSTL_INCL_H_SPINMUTEXT */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Compatibility - */ - -#if !defined(_M_IX86) -# error Not valid for processors other than Intel -#endif /* _M_IX86 */ - -#ifdef STLSOFT_ATOMIC_CALLCONV -# undef STLSOFT_ATOMIC_CALLCONV -#endif /* STLSOFT_ATOMIC_CALLCONV */ -#ifdef WINSTL_ATOMIC_FNS_CALLCONV_IS_FASTCALL -# undef WINSTL_ATOMIC_FNS_CALLCONV_IS_FASTCALL -#endif /* WINSTL_ATOMIC_FNS_CALLCONV_IS_FASTCALL */ -#ifdef WINSTL_ATOMIC_FNS_CALLCONV_IS_STDCALL -# undef WINSTL_ATOMIC_FNS_CALLCONV_IS_STDCALL -#endif /* WINSTL_ATOMIC_FNS_CALLCONV_IS_STDCALL */ - -#ifndef STLSOFT_NO_FASTCALL -# if defined(__STLSOFT_COMPILER_IS_BORLAND) || \ - defined(__STLSOFT_COMPILER_IS_DMC) || \ - defined(__STLSOFT_COMPILER_IS_WATCOM) -# define STLSOFT_NO_FASTCALL -# endif /* compiler */ -#endif /* STLSOFT_NO_FASTCALL */ - -#if defined(STLSOFT_CF_FASTCALL_SUPPORTED) && \ - !defined(STLSOFT_NO_FASTCALL) -# define WINSTL_ATOMIC_FNS_CALLCONV_IS_FASTCALL -# define WINSTL_ATOMIC_FNS_CALLCONV __fastcall -#elif defined(STLSOFT_CF_STDCALL_SUPPORTED) -# define WINSTL_ATOMIC_FNS_CALLCONV_IS_STDCALL -# define WINSTL_ATOMIC_FNS_CALLCONV __stdcall -#else -# error Need to define calling convention -#endif /* call-conv */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace - */ - -#ifndef _WINSTL_NO_NAMESPACE -# ifdef _STLSOFT_NO_NAMESPACE -/* There is no stlsoft namespace, so must define ::winstl */ -namespace winstl -{ -# else -/* Define stlsoft::winstl_project */ - -namespace stlsoft -{ - -namespace winstl_project -{ - -# endif /* _STLSOFT_NO_NAMESPACE */ -#endif /* !_WINSTL_NO_NAMESPACE */ - -/* ////////////////////////////////////////////////////////////////////////// */ - -/// \weakgroup libraries STLSoft Libraries -/// \brief The individual libraries - -/// \weakgroup libraries_threading Threading Library -/// \ingroup libraries -/// \brief This library provides synchronisation and threading facilities - -/// \weakgroup winstl_perf_library Threading Library (WinSTL) -/// \ingroup WinSTL libraries_threading -/// \brief This library provides synchronisation and threading facilities for the Win32 API -/// @{ - -/* ///////////////////////////////////////////////////////////////////////////// - * Implementation options - * - * Because some compilers can make the code actually faster when it the naked - * functions are not inline, we provide for that here. If you want to out-of-line - * the functions, then you just need to define WINSTL_ATOMIC_FNS_DECLARATION_ONLY - * in the code that uses it, and define WINSTL_ATOMIC_FNS_DEFINITION in one - * implementation file. - */ - -#ifdef WINSTL_ATOMIC_FNS_DECL_ -# undef WINSTL_ATOMIC_FNS_DECL_ -#endif /* WINSTL_ATOMIC_FNS_DECL_ */ - -#ifdef WINSTL_ATOMIC_FNS_IMPL_ -# undef WINSTL_ATOMIC_FNS_IMPL_ -#endif /* WINSTL_ATOMIC_FNS_IMPL_ */ - -#if defined(WINSTL_ATOMIC_FNS_DECLARATION_ONLY) -/* Only the function declarations are included */ -# define WINSTL_ATOMIC_FNS_DECL_(type) type WINSTL_ATOMIC_FNS_CALLCONV -#elif defined(WINSTL_ATOMIC_FNS_DEFINITION) -/* Only the function definitions are included */ -# ifdef STSLSOFT_INLINE_ASM_SUPPORTED -# define WINSTL_ATOMIC_FNS_IMPL_(type) __declspec(naked) type WINSTL_ATOMIC_FNS_CALLCONV -# else /* ? STSLSOFT_INLINE_ASM_SUPPORTED */ -# define WINSTL_ATOMIC_FNS_IMPL_(type) type WINSTL_ATOMIC_FNS_CALLCONV -# endif /* STSLSOFT_INLINE_ASM_SUPPORTED */ -#else -# if defined(__STLSOFT_COMPILER_IS_MWERKS) && \ - (__MWERKS__ & 0xFF00) < 0x3000 -# error CodeWarrior 7 and earlier does not generate correct code when inline naked functions are used -# endif /* __MWERKS__ & 0xFF00) < 0x3000 */ - -# ifdef STSLSOFT_INLINE_ASM_SUPPORTED - /* The default is to define them inline */ -# ifdef STSLSOFT_ASM_IN_INLINE_SUPPORTED -# define WINSTL_ATOMIC_FNS_DECL_(type) inline type WINSTL_ATOMIC_FNS_CALLCONV -# define WINSTL_ATOMIC_FNS_IMPL_(type) inline __declspec(naked) type WINSTL_ATOMIC_FNS_CALLCONV -# else /* ? STSLSOFT_ASM_IN_INLINE_SUPPORTED */ -# define WINSTL_ATOMIC_FNS_DECL_(type) type WINSTL_ATOMIC_FNS_CALLCONV -# define WINSTL_ATOMIC_FNS_IMPL_(type) static __declspec(naked) type WINSTL_ATOMIC_FNS_CALLCONV -# endif /* STSLSOFT_ASM_IN_INLINE_SUPPORTED */ -# else /* ? STSLSOFT_INLINE_ASM_SUPPORTED */ - /* ASM not supported, so we're using the Win32 functions */ -# define WINSTL_ATOMIC_FNS_DECL_(type) inline type WINSTL_ATOMIC_FNS_CALLCONV -# define WINSTL_ATOMIC_FNS_IMPL_(type) inline type WINSTL_ATOMIC_FNS_CALLCONV -# endif /* STSLSOFT_INLINE_ASM_SUPPORTED */ -#endif /* declaration / definition */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Atomic function declarations - */ - -#ifndef WINSTL_ATOMIC_FNS_DEFINITION - -/* Uni-processor variants */ -WINSTL_ATOMIC_FNS_DECL_(ws_sint32_t) atomic_preincrement_up(ws_sint32_t volatile *pl); -WINSTL_ATOMIC_FNS_DECL_(ws_sint32_t) atomic_predecrement_up(ws_sint32_t volatile *pl); -WINSTL_ATOMIC_FNS_DECL_(ws_sint32_t) atomic_postincrement_up(ws_sint32_t volatile *pl); -WINSTL_ATOMIC_FNS_DECL_(ws_sint32_t) atomic_postdecrement_up(ws_sint32_t volatile *pl); -WINSTL_ATOMIC_FNS_DECL_(void) atomic_increment_up(ws_sint32_t volatile *pl); -WINSTL_ATOMIC_FNS_DECL_(void) atomic_decrement_up(ws_sint32_t volatile *pl); - -WINSTL_ATOMIC_FNS_DECL_(ws_sint32_t) atomic_write_up(ws_sint32_t volatile *pl, ws_sint32_t n); -WINSTL_ATOMIC_FNS_DECL_(ws_sint32_t) atomic_read_up(ws_sint32_t volatile const *pl); - -WINSTL_ATOMIC_FNS_DECL_(ws_sint32_t) atomic_postadd_up(ws_sint32_t volatile *pl, ws_sint32_t n); -inline ws_sint32_t atomic_preadd_up(ws_sint32_t volatile *pl, ws_sint32_t n); - - - -/* SMP variants */ -WINSTL_ATOMIC_FNS_DECL_(ws_sint32_t) atomic_preincrement_smp(ws_sint32_t volatile *pl); -WINSTL_ATOMIC_FNS_DECL_(ws_sint32_t) atomic_predecrement_smp(ws_sint32_t volatile *pl); -WINSTL_ATOMIC_FNS_DECL_(ws_sint32_t) atomic_postincrement_smp(ws_sint32_t volatile *pl); -WINSTL_ATOMIC_FNS_DECL_(ws_sint32_t) atomic_postdecrement_smp(ws_sint32_t volatile *pl); -WINSTL_ATOMIC_FNS_DECL_(void) atomic_increment_smp(ws_sint32_t volatile *pl); -WINSTL_ATOMIC_FNS_DECL_(void) atomic_decrement_smp(ws_sint32_t volatile *pl); - -WINSTL_ATOMIC_FNS_DECL_(ws_sint32_t) atomic_write_smp(ws_sint32_t volatile *pl, ws_sint32_t n); -WINSTL_ATOMIC_FNS_DECL_(ws_sint32_t) atomic_read_smp(ws_sint32_t volatile const *pl); - -WINSTL_ATOMIC_FNS_DECL_(ws_sint32_t) atomic_postadd_smp(ws_sint32_t volatile *pl, ws_sint32_t n); -inline ws_sint32_t atomic_preadd_smp(ws_sint32_t volatile *pl, ws_sint32_t n); - - - -/* Multi-processor detection variants */ -WINSTL_ATOMIC_FNS_DECL_(ws_sint32_t) atomic_preincrement(ws_sint32_t volatile *pl); -WINSTL_ATOMIC_FNS_DECL_(ws_sint32_t) atomic_predecrement(ws_sint32_t volatile *pl); -WINSTL_ATOMIC_FNS_DECL_(ws_sint32_t) atomic_postincrement(ws_sint32_t volatile *pl); -WINSTL_ATOMIC_FNS_DECL_(ws_sint32_t) atomic_postdecrement(ws_sint32_t volatile *pl); -WINSTL_ATOMIC_FNS_DECL_(void) atomic_increment(ws_sint32_t volatile *pl); -WINSTL_ATOMIC_FNS_DECL_(void) atomic_decrement(ws_sint32_t volatile *pl); - -WINSTL_ATOMIC_FNS_DECL_(ws_sint32_t) atomic_write(ws_sint32_t volatile *pl, ws_sint32_t n); -WINSTL_ATOMIC_FNS_DECL_(ws_sint32_t) atomic_read(ws_sint32_t volatile const *pl); - -WINSTL_ATOMIC_FNS_DECL_(ws_sint32_t) atomic_postadd(ws_sint32_t volatile *pl, ws_sint32_t n); -inline ws_sint32_t atomic_preadd(ws_sint32_t volatile *pl, ws_sint32_t n); - - -#endif /* !WINSTL_ATOMIC_FNS_DEFINITION */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Atomic function definitions - */ - -#ifndef __STLSOFT_DOCUMENTATION_SKIP_SECTION - -# if !defined(WINSTL_ATOMIC_FNS_DECLARATION_ONLY) - -# ifdef STSLSOFT_INLINE_ASM_SUPPORTED -/* Inline assembler versions */ - -#ifdef __STLSOFT_COMPILER_IS_BORLAND -# pragma warn -8002 /* Suppresses: "Restarting compile using assembly" */ -# pragma warn -8070 /* Suppresses: "Function should return a value" */ -#endif /* __STLSOFT_COMPILER_IS_BORLAND */ - -// Uni-processor - -WINSTL_ATOMIC_FNS_IMPL_(ws_sint32_t) atomic_preincrement_up(ws_sint32_t volatile * /* pl */) -{ - _asm - { - // pop 1 into eax, which can then be atomically added into *pl (held - // in ecx). Since it's an xadd it exchanges the previous value into eax - mov eax, 1 - -#if defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_FASTCALL) - // __fastcall: ecx is pl -#elif defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_STDCALL) - // __stdcall: arguments are on the stack - - mov ecx, dword ptr [esp + 4] -#else -# error Need to define calling convention -#endif /* call-conv */ - - xadd dword ptr [ecx], eax - - // Since this is pre-increment, we need to inc eax to catch up with the - // real value - inc eax - -#if defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_FASTCALL) - ret -#elif defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_STDCALL) - ret 4 -#endif /* call-conv */ - } -} - -WINSTL_ATOMIC_FNS_IMPL_(ws_sint32_t) atomic_predecrement_up(ws_sint32_t volatile * /* pl */) -{ - _asm - { - // pop 1 into eax, which can then be atomically added into *pl (held - // in ecx). Since it's an xadd it exchanges the previous value into eax - mov eax, -1 - -#if defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_FASTCALL) - // __fastcall: ecx is pl -#elif defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_STDCALL) - // __stdcall: arguments are on the stack - - mov ecx, dword ptr [esp + 4] -#else -# error Need to define calling convention -#endif /* call-conv */ - - xadd dword ptr [ecx], eax - - // Since this is pre-decrement, we need to inc eax to catch up with the - // real value - dec eax - -#if defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_FASTCALL) - ret -#elif defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_STDCALL) - ret 4 -#endif /* call-conv */ - } -} - -WINSTL_ATOMIC_FNS_IMPL_(ws_sint32_t) atomic_postincrement_up(ws_sint32_t volatile * /* pl */) -{ - _asm - { - // pop 1 into eax, which can then be atomically added into *pl (held - // in ecx). Since it's an xadd it exchanges the previous value into eax - mov eax, 1 - -#if defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_FASTCALL) - // __fastcall: ecx is pl -#elif defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_STDCALL) - // __stdcall: arguments are on the stack - - mov ecx, dword ptr [esp + 4] -#else -# error Need to define calling convention -#endif /* call-conv */ - - xadd dword ptr [ecx], eax - - // Since this is post-increment, we need do nothing, since the previous - // value is in eax - -#if defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_FASTCALL) - ret -#elif defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_STDCALL) - ret 4 -#endif /* call-conv */ - } -} - -WINSTL_ATOMIC_FNS_IMPL_(ws_sint32_t) atomic_postdecrement_up(ws_sint32_t volatile * /* pl */) -{ - _asm - { - // pop 1 into eax, which can then be atomically added into *pl (held - // in ecx). Since it's an xadd it exchanges the previous value into eax - mov eax, -1 - -#if defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_FASTCALL) - // __fastcall: ecx is pl -#elif defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_STDCALL) - // __stdcall: arguments are on the stack - - mov ecx, dword ptr [esp + 4] -#else -# error Need to define calling convention -#endif /* call-conv */ - - xadd dword ptr [ecx], eax - - // Since this is post-decrement, we need do nothing, since the previous - // value is in eax - -#if defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_FASTCALL) - ret -#elif defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_STDCALL) - ret 4 -#endif /* call-conv */ - } -} - -WINSTL_ATOMIC_FNS_IMPL_(void) atomic_increment_up(ws_sint32_t volatile * /* pl */) -{ - _asm - { -#if defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_FASTCALL) - // __fastcall: ecx is pl -#elif defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_STDCALL) - // __stdcall: arguments are on the stack - - mov ecx, dword ptr [esp + 4] -#else -# error Need to define calling convention -#endif /* call-conv */ - - add dword ptr [ecx], 1 - -#if defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_FASTCALL) - ret -#elif defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_STDCALL) - ret 4 -#endif /* call-conv */ - } -} - -WINSTL_ATOMIC_FNS_IMPL_(void) atomic_decrement_up(ws_sint32_t volatile * /* pl */) -{ - _asm - { -#if defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_FASTCALL) - // __fastcall: ecx is pl -#elif defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_STDCALL) - // __stdcall: arguments are on the stack - - mov ecx, dword ptr [esp + 4] -#else -# error Need to define calling convention -#endif /* call-conv */ - - sub dword ptr [ecx], 1 - -#if defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_FASTCALL) - ret -#elif defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_STDCALL) - ret 4 -#endif /* call-conv */ - } -} - -WINSTL_ATOMIC_FNS_IMPL_(ws_sint32_t) atomic_read_up(ws_sint32_t volatile const * /* pl */) -{ - _asm - { - mov eax, 0 -#if defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_FASTCALL) - // __fastcall: ecx is pl - -#elif defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_STDCALL) - // __stdcall: arguments are on the stack - mov ecx, dword ptr [esp + 4] -#else -# error Need to define calling convention -#endif /* call-conv */ - - // pop 0 into eax, which can then be atomically added into *pl (held - // in ecx), leaving the value unchanged. - xadd dword ptr [ecx], eax - - // Since it's an xadd it exchanges the previous value into eax, which - // is exactly what's required - -#if defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_FASTCALL) - ret -#elif defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_STDCALL) - ret 4 -#endif /* call-conv */ - } -} - -WINSTL_ATOMIC_FNS_IMPL_(ws_sint32_t) atomic_write_up(ws_sint32_t volatile * /* pl */, ws_sint32_t /* n */) -{ - _asm - { -#if defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_FASTCALL) - // __fastcall: ecx is pl, edx is n - - // Just exchange *pl and n - xchg dword ptr [ecx], edx - - // The previous value goes into edx, so me move it into eax for return - mov eax, edx - - ret -#elif defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_STDCALL) - // __stdcall: arguments are on the stack: pl in esp+4, pl in esp+8 - mov ecx, dword ptr [esp + 4] // Load the address of pl into ecx - mov eax, dword ptr [esp + 8] // Load the value into eax, so the return value will be there waiting - - xchg dword ptr [ecx], eax - - ret 8 -#else -# error Need to define calling convention -#endif /* call-conv */ - } -} - - -WINSTL_ATOMIC_FNS_IMPL_(ws_sint32_t) atomic_postadd_up(ws_sint32_t volatile * /* pl */, ws_sint32_t /* n */) -{ - // Thanks to Eugene Gershnik for the fast-call implementation - __asm - { -#if defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_FASTCALL) - // __fastcall: ecx is pl, edx is n - - // Simply atomically add them, which will leave the previous value - // in edx - xadd dword ptr [ecx], edx - - // Just need to move adx into eax to return it - mov eax, edx - - ret -#elif defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_STDCALL) - // __stdcall: arguments are on the stack: pl in esp+4, pl in esp+8 - - // Simply atomically add them, which will leave the previous value - // in edx - mov ecx, dword ptr [esp + 4] // Load the address of pl into ecx - mov eax, dword ptr [esp + 8] // Load the value into eax, so the return value will be there waiting - - xadd dword ptr [ecx], eax - - // Just need to move adx into eax to return it - - ret 8 -#else -# error Need to define calling convention -#endif /* call-conv */ - } -} - -// Symmetric multi-processor - -WINSTL_ATOMIC_FNS_IMPL_(ws_sint32_t) atomic_preincrement_smp(ws_sint32_t volatile * /* pl */) -{ - _asm - { - // pop 1 into eax, which can then be atomically added into *pl (held - // in ecx). Since it's an xadd it exchanges the previous value into eax - mov eax, 1 - -#if defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_FASTCALL) - // __fastcall: ecx is pl -#elif defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_STDCALL) - // __stdcall: arguments are on the stack - - mov ecx, dword ptr [esp + 4] -#else -# error Need to define calling convention -#endif /* call-conv */ - - lock xadd dword ptr [ecx], eax - - // Since this is pre-increment, we need to inc eax to catch up with the - // real value - inc eax - -#if defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_FASTCALL) - ret -#elif defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_STDCALL) - ret 4 -#endif /* call-conv */ - } -} - -WINSTL_ATOMIC_FNS_IMPL_(ws_sint32_t) atomic_predecrement_smp(ws_sint32_t volatile * /* pl */) -{ - _asm - { - // pop 1 into eax, which can then be atomically added into *pl (held - // in ecx). Since it's an xadd it exchanges the previous value into eax - mov eax, -1 - -#if defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_FASTCALL) - // __fastcall: ecx is pl -#elif defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_STDCALL) - // __stdcall: arguments are on the stack - - mov ecx, dword ptr [esp + 4] -#else -# error Need to define calling convention -#endif /* call-conv */ - - lock xadd dword ptr [ecx], eax - - // Since this is pre-decrement, we need to inc eax to catch up with the - // real value - dec eax - -#if defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_FASTCALL) - ret -#elif defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_STDCALL) - ret 4 -#endif /* call-conv */ - } -} - -WINSTL_ATOMIC_FNS_IMPL_(ws_sint32_t) atomic_postincrement_smp(ws_sint32_t volatile * /* pl */) -{ - _asm - { - // pop 1 into eax, which can then be atomically added into *pl (held - // in ecx). Since it's an xadd it exchanges the previous value into eax - mov eax, 1 - -#if defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_FASTCALL) - // __fastcall: ecx is pl -#elif defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_STDCALL) - // __stdcall: arguments are on the stack - - mov ecx, dword ptr [esp + 4] -#else -# error Need to define calling convention -#endif /* call-conv */ - - lock xadd dword ptr [ecx], eax - - // Since this is post-increment, we need do nothing, since the previous - // value is in eax - -#if defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_FASTCALL) - ret -#elif defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_STDCALL) - ret 4 -#endif /* call-conv */ - } -} - -WINSTL_ATOMIC_FNS_IMPL_(ws_sint32_t) atomic_postdecrement_smp(ws_sint32_t volatile * /* pl */) -{ - _asm - { - // pop 1 into eax, which can then be atomically added into *pl (held - // in ecx). Since it's an xadd it exchanges the previous value into eax - mov eax, -1 - -#if defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_FASTCALL) - // __fastcall: ecx is pl -#elif defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_STDCALL) - // __stdcall: arguments are on the stack - - mov ecx, dword ptr [esp + 4] -#else -# error Need to define calling convention -#endif /* call-conv */ - - lock xadd dword ptr [ecx], eax - - // Since this is post-decrement, we need do nothing, since the previous - // value is in eax - -#if defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_FASTCALL) - ret -#elif defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_STDCALL) - ret 4 -#endif /* call-conv */ - } -} - -WINSTL_ATOMIC_FNS_IMPL_(void) atomic_increment_smp(ws_sint32_t volatile * /* pl */) -{ - __asm - { - call atomic_postincrement_smp -#if defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_FASTCALL) - ret -#elif defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_STDCALL) - ret 4 -#endif /* call-conv */ - } -} - -WINSTL_ATOMIC_FNS_IMPL_(void) atomic_decrement_smp(ws_sint32_t volatile * /* pl */) -{ - __asm - { - call atomic_postdecrement_smp -#if defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_FASTCALL) - ret -#elif defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_STDCALL) - ret 4 -#endif /* call-conv */ - } -} - -WINSTL_ATOMIC_FNS_IMPL_(ws_sint32_t) atomic_read_smp(ws_sint32_t volatile const * /* pl */) -{ - _asm - { - mov eax, 0 -#if defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_FASTCALL) - // __fastcall: ecx is pl - -#elif defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_STDCALL) - // __stdcall: arguments are on the stack - mov ecx, dword ptr [esp + 4] -#else -# error Need to define calling convention -#endif /* call-conv */ - - // pop 0 into eax, which can then be atomically added into *pl (held - // in ecx), leaving the value unchanged. - lock xadd dword ptr [ecx], eax - - // Since it's an xadd it exchanges the previous value into eax, which - // is exactly what's required - -#if defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_FASTCALL) - ret -#elif defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_STDCALL) - ret 4 -#endif /* call-conv */ - } -} - -WINSTL_ATOMIC_FNS_IMPL_(ws_sint32_t) atomic_write_smp(ws_sint32_t volatile * /* pl */, ws_sint32_t /* n */) -{ - _asm - { -#if defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_FASTCALL) - // __fastcall: ecx is pl, edx is n - - // Just exchange *pl and n - /* lock */ xchg dword ptr [ecx], edx - - // The previous value goes into edx, so me move it into eax for return - mov eax, edx - - ret -#elif defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_STDCALL) - // __stdcall: arguments are on the stack: pl in esp+4, pl in esp+8 - mov ecx, dword ptr [esp + 4] // Load the address of pl into ecx - mov eax, dword ptr [esp + 8] // Load the value into eax, so the return value will be there waiting - - /* lock */ xchg dword ptr [ecx], eax - - ret 8 -#else -# error Need to define calling convention -#endif /* call-conv */ - } -} - - -WINSTL_ATOMIC_FNS_IMPL_(ws_sint32_t) atomic_postadd_smp(ws_sint32_t volatile * /* pl */, ws_sint32_t /* n */) -{ - // Thanks to Eugene Gershnik for the fast-call implementation - __asm - { -#if defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_FASTCALL) - // __fastcall: ecx is pl, edx is n - - // Simply atomically add them, which will leave the previous value - // in edx - lock xadd dword ptr [ecx], edx - - // Just need to move adx into eax to return it - mov eax, edx - - ret -#elif defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_STDCALL) - // __stdcall: arguments are on the stack: pl in esp+4, pl in esp+8 - - // Simply atomically add them, which will leave the previous value - // in edx - mov ecx, dword ptr [esp + 4] // Load the address of pl into ecx - mov eax, dword ptr [esp + 8] // Load the value into eax, so the return value will be there waiting - - lock xadd dword ptr [ecx], eax - - // Just need to move adx into eax to return it - - ret 8 -#else -# error Need to define calling convention -#endif /* call-conv */ - } -} - -// Processor detecting - -namespace -{ - ws_bool_t is_host_up() - { - // All these statics are guaranteed to be zero as a result of the module/process loading - static ws_sint32_t s_spin; // The spin variable - static ws_bool_t s_init; // This is guaranteed to be zero - static ws_bool_t s_up; // This is the flag variably, also guaranteed to be zero - - // Simple spin lock - if(!s_init) // Low cost pre-test. In the unlikely event that another thread does come in and - { // also see this as false, the dual initialisation of all three statics is benign - spin_mutex smx(&s_spin); - - smx.lock(); - if(!s_init) - { - SYSTEM_INFO sys_info; - - ::GetSystemInfo(&sys_info); - - s_init = true; - - s_up = 1 == sys_info.dwNumberOfProcessors; - } - smx.unlock(); - } - - return s_up; - } - - // s_up is guaranteed to be zero at load time. - // - // There is a race condition with all static variables, since multiple threads - // can come in and one can have set the hidden flag variable without prior to - // setting the static variable itself, just at the time that an arbitrary number - // of other threads pick up the pre-initialised value. - // - // However, because the test here is whether to skip the lock, the pathological - // case is benign. The only cost in the very rare case where it happens is that - // the thread(s) will use bus locking until such time as the static is fully - // initialised. - static ws_bool_t s_up = is_host_up(); -} - -WINSTL_ATOMIC_FNS_IMPL_(ws_sint32_t) atomic_preincrement(ws_sint32_t volatile * /* pl */) -{ - if(s_up) - { - _asm - { - // pop 1 into eax, which can then be atomically added into *pl (held - // in ecx). Since it's an xadd it exchanges the previous value into eax - mov eax, 1 - -#if defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_FASTCALL) - // __fastcall: ecx is pl -#elif defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_STDCALL) - // __stdcall: arguments are on the stack - - mov ecx, dword ptr [esp + 4] -#else -# error Need to define calling convention -#endif /* call-conv */ - - xadd dword ptr [ecx], eax - - // Since this is pre-increment, we need to inc eax to catch up with the - // real value - inc eax - -#if defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_FASTCALL) - ret -#elif defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_STDCALL) - ret 4 -#endif /* call-conv */ - } - } - else - { - _asm - { - // pop 1 into eax, which can then be atomically added into *pl (held - // in ecx). Since it's an xadd it exchanges the previous value into eax - mov eax, 1 - -#if defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_FASTCALL) - // __fastcall: ecx is pl -#elif defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_STDCALL) - // __stdcall: arguments are on the stack - - mov ecx, dword ptr [esp + 4] -#else -# error Need to define calling convention -#endif /* call-conv */ - - lock xadd dword ptr [ecx], eax - - // Since this is pre-increment, we need to inc eax to catch up with the - // real value - inc eax - -#if defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_FASTCALL) - ret -#elif defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_STDCALL) - ret 4 -#endif /* call-conv */ - } - } -} - -WINSTL_ATOMIC_FNS_IMPL_(ws_sint32_t) atomic_predecrement(ws_sint32_t volatile * /* pl */) -{ - if(s_up) - { - _asm - { - // pop 1 into eax, which can then be atomically added into *pl (held - // in ecx). Since it's an xadd it exchanges the previous value into eax - mov eax, -1 - -#if defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_FASTCALL) - // __fastcall: ecx is pl -#elif defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_STDCALL) - // __stdcall: arguments are on the stack - - mov ecx, dword ptr [esp + 4] -#else -# error Need to define calling convention -#endif /* call-conv */ - - xadd dword ptr [ecx], eax - - // Since this is pre-decrement, we need to inc eax to catch up with the - // real value - dec eax - -#if defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_FASTCALL) - ret -#elif defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_STDCALL) - ret 4 -#endif /* call-conv */ - } - } - else - { - _asm - { - // pop 1 into eax, which can then be atomically added into *pl (held - // in ecx). Since it's an xadd it exchanges the previous value into eax - mov eax, -1 - -#if defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_FASTCALL) - // __fastcall: ecx is pl -#elif defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_STDCALL) - // __stdcall: arguments are on the stack - - mov ecx, dword ptr [esp + 4] -#else -# error Need to define calling convention -#endif /* call-conv */ - - lock xadd dword ptr [ecx], eax - - // Since this is pre-decrement, we need to inc eax to catch up with the - // real value - dec eax - -#if defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_FASTCALL) - ret -#elif defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_STDCALL) - ret 4 -#endif /* call-conv */ - } - } -} - -WINSTL_ATOMIC_FNS_IMPL_(ws_sint32_t) atomic_postincrement(ws_sint32_t volatile * /* pl */) -{ - if(s_up) - { - _asm - { - // pop 1 into eax, which can then be atomically added into *pl (held - // in ecx). Since it's an xadd it exchanges the previous value into eax - mov eax, 1 - -#if defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_FASTCALL) - // __fastcall: ecx is pl -#elif defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_STDCALL) - // __stdcall: arguments are on the stack - - mov ecx, dword ptr [esp + 4] -#else -# error Need to define calling convention -#endif /* call-conv */ - - xadd dword ptr [ecx], eax - - // Since this is post-increment, we need do nothing, since the previous - // value is in eax - -#if defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_FASTCALL) - ret -#elif defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_STDCALL) - ret 4 -#endif /* call-conv */ - } - } - else - { - _asm - { - // pop 1 into eax, which can then be atomically added into *pl (held - // in ecx). Since it's an xadd it exchanges the previous value into eax - mov eax, 1 - -#if defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_FASTCALL) - // __fastcall: ecx is pl -#elif defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_STDCALL) - // __stdcall: arguments are on the stack - - mov ecx, dword ptr [esp + 4] -#else -# error Need to define calling convention -#endif /* call-conv */ - - lock xadd dword ptr [ecx], eax - - // Since this is post-increment, we need do nothing, since the previous - // value is in eax - -#if defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_FASTCALL) - ret -#elif defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_STDCALL) - ret 4 -#endif /* call-conv */ - } - } -} - -WINSTL_ATOMIC_FNS_IMPL_(ws_sint32_t) atomic_postdecrement(ws_sint32_t volatile * /* pl */) -{ - if(s_up) - { - _asm - { - // pop 1 into eax, which can then be atomically added into *pl (held - // in ecx). Since it's an xadd it exchanges the previous value into eax - mov eax, -1 - -#if defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_FASTCALL) - // __fastcall: ecx is pl -#elif defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_STDCALL) - // __stdcall: arguments are on the stack - - mov ecx, dword ptr [esp + 4] -#else -# error Need to define calling convention -#endif /* call-conv */ - - xadd dword ptr [ecx], eax - - // Since this is post-decrement, we need do nothing, since the previous - // value is in eax - -#if defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_FASTCALL) - ret -#elif defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_STDCALL) - ret 4 -#endif /* call-conv */ - } - } - else - { - _asm - { - // pop 1 into eax, which can then be atomically added into *pl (held - // in ecx). Since it's an xadd it exchanges the previous value into eax - mov eax, -1 - -#if defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_FASTCALL) - // __fastcall: ecx is pl -#elif defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_STDCALL) - // __stdcall: arguments are on the stack - - mov ecx, dword ptr [esp + 4] -#else -# error Need to define calling convention -#endif /* call-conv */ - - lock xadd dword ptr [ecx], eax - - // Since this is post-decrement, we need do nothing, since the previous - // value is in eax - -#if defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_FASTCALL) - ret -#elif defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_STDCALL) - ret 4 -#endif /* call-conv */ - } - } -} - -WINSTL_ATOMIC_FNS_IMPL_(void) atomic_increment(ws_sint32_t volatile * /* pl */) -{ - if(s_up) - { - _asm - { -#if defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_FASTCALL) - // __fastcall: ecx is pl -#elif defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_STDCALL) - // __stdcall: arguments are on the stack - - mov ecx, dword ptr [esp + 4] -#else -# error Need to define calling convention -#endif /* call-conv */ - - add dword ptr [ecx], 1 - -#if defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_FASTCALL) - ret -#elif defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_STDCALL) - ret 4 -#endif /* call-conv */ - } - } - else - { - _asm - { -#if defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_FASTCALL) - // __fastcall: ecx is pl -#elif defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_STDCALL) - // __stdcall: arguments are on the stack - - mov ecx, dword ptr [esp + 4] -#else -# error Need to define calling convention -#endif /* call-conv */ - -#if defined(__STLSOFT_COMPILER_IS_VECTORC) - mov eax, 1 - lock xadd dword ptr [ecx], eax -#else /* ? compiler */ - // This might be wrong - lock add dword ptr [ecx], 1 -#endif /* compiler */ - - -#if defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_FASTCALL) - ret -#elif defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_STDCALL) - ret 4 -#endif /* call-conv */ - } - } -} - -WINSTL_ATOMIC_FNS_IMPL_(void) atomic_decrement(ws_sint32_t volatile * /* pl */) -{ - if(s_up) - { - _asm - { -#if defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_FASTCALL) - // __fastcall: ecx is pl -#elif defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_STDCALL) - // __stdcall: arguments are on the stack - - mov ecx, dword ptr [esp + 4] -#else -# error Need to define calling convention -#endif /* call-conv */ - - add dword ptr [ecx], -1 - -#if defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_FASTCALL) - ret -#elif defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_STDCALL) - ret 4 -#endif /* call-conv */ - } - } - else - { - _asm - { -#if defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_FASTCALL) - // __fastcall: ecx is pl -#elif defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_STDCALL) - // __stdcall: arguments are on the stack - - mov ecx, dword ptr [esp + 4] -#else -# error Need to define calling convention -#endif /* call-conv */ - -#if defined(__STLSOFT_COMPILER_IS_VECTORC) - mov eax, -1 - lock xadd dword ptr [ecx], eax -#else /* ? compiler */ - // This might be wrong - lock sub dword ptr [ecx], 1 -#endif /* compiler */ - -#if defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_FASTCALL) - ret -#elif defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_STDCALL) - ret 4 -#endif /* call-conv */ - } - } -} - -WINSTL_ATOMIC_FNS_IMPL_(ws_sint32_t) atomic_read(ws_sint32_t volatile const * /* pl */) -{ - if(s_up) - { - _asm - { - mov eax, 0 -#if defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_FASTCALL) - // __fastcall: ecx is pl - -#elif defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_STDCALL) - // __stdcall: arguments are on the stack - mov ecx, dword ptr [esp + 4] -#else -# error Need to define calling convention -#endif /* call-conv */ - - // pop 0 into eax, which can then be atomically added into *pl (held - // in ecx), leaving the value unchanged. - xadd dword ptr [ecx], eax - - // Since it's an xadd it exchanges the previous value into eax, which - // is exactly what's required - -#if defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_FASTCALL) - ret -#elif defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_STDCALL) - ret 4 -#endif /* call-conv */ - } - } - else - { - _asm - { - mov eax, 0 -#if defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_FASTCALL) - // __fastcall: ecx is pl - -#elif defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_STDCALL) - // __stdcall: arguments are on the stack - mov ecx, dword ptr [esp + 4] -#else -# error Need to define calling convention -#endif /* call-conv */ - - // pop 0 into eax, which can then be atomically added into *pl (held - // in ecx), leaving the value unchanged. - lock xadd dword ptr [ecx], eax - - // Since it's an xadd it exchanges the previous value into eax, which - // is exactly what's required - -#if defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_FASTCALL) - ret -#elif defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_STDCALL) - ret 4 -#endif /* call-conv */ - } - } -} - -WINSTL_ATOMIC_FNS_IMPL_(ws_sint32_t) atomic_write(ws_sint32_t volatile * /* pl */, ws_sint32_t /* n */) -{ - _asm - { -#if defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_FASTCALL) - // __fastcall: ecx is pl, edx is n - - // Just exchange *pl and n - lock xchg dword ptr [ecx], edx - - // The previous value goes into edx, so me move it into eax for return - mov eax, edx - - ret -#elif defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_STDCALL) - // __stdcall: arguments are on the stack: pl in esp+4, pl in esp+8 - mov ecx, dword ptr [esp + 4] // Load the address of pl into ecx - mov eax, dword ptr [esp + 8] // Load the value into eax, so the return value will be there waiting - - xchg dword ptr [ecx], eax - - ret 8 -#else -# error Need to define calling convention -#endif /* call-conv */ - } -} - - -WINSTL_ATOMIC_FNS_IMPL_(ws_sint32_t) atomic_postadd(ws_sint32_t volatile * /* pl */, ws_sint32_t /* n */) -{ - // Thanks to Eugene Gershnik for the fast-call implementation - if(s_up) - { - __asm - { -#if defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_FASTCALL) - // __fastcall: ecx is pl, edx is n - - // Simply atomically add them, which will leave the previous value - // in edx - xadd dword ptr [ecx], edx - - // Just need to move adx into eax to return it - mov eax, edx - - ret -#elif defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_STDCALL) - // __stdcall: arguments are on the stack: pl in esp+4, pl in esp+8 - - // Simply atomically add them, which will leave the previous value - // in edx - mov ecx, dword ptr [esp + 4] // Load the address of pl into ecx - mov eax, dword ptr [esp + 8] // Load the value into eax, so the return value will be there waiting - - xadd dword ptr [ecx], eax - - // Just need to move adx into eax to return it - - ret 8 -#else -# error Need to define calling convention -#endif /* call-conv */ - } - } - else - { - __asm - { -#if defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_FASTCALL) - // __fastcall: ecx is pl, edx is n - - // Simply atomically add them, which will leave the previous value - // in edx - lock xadd dword ptr [ecx], edx - - // Just need to move adx into eax to return it - mov eax, edx - - ret -#elif defined(WINSTL_ATOMIC_FNS_CALLCONV_IS_STDCALL) - // __stdcall: arguments are on the stack: pl in esp+4, pl in esp+8 - - // Simply atomically add them, which will leave the previous value - // in edx - mov ecx, dword ptr [esp + 4] // Load the address of pl into ecx - mov eax, dword ptr [esp + 8] // Load the value into eax, so the return value will be there waiting - - lock xadd dword ptr [ecx], eax - - // Just need to move adx into eax to return it - - ret 8 -#else -# error Need to define calling convention -#endif /* call-conv */ - } - } -} - -#ifdef __STLSOFT_COMPILER_IS_BORLAND -# pragma warn .8070 /* Suppresses: "Function should return a value" */ -# pragma warn .8002 /* Suppresses: "Restarting compile using assembly" */ -#endif /* __STLSOFT_COMPILER_IS_BORLAND */ - -# else /* STSLSOFT_INLINE_ASM_SUPPORTED */ -/* Non-assembler versions - * - * These use the Win32 Interlocked functions. These are not guaranteed to give - * precise answers on Windows 95. - */ - - -/* Multi-processor detection variants */ -WINSTL_ATOMIC_FNS_IMPL_(ws_sint32_t) atomic_preincrement(ws_sint32_t volatile *pl) -{ - return ::InterlockedIncrement((LPLONG)pl); -} - -WINSTL_ATOMIC_FNS_IMPL_(ws_sint32_t) atomic_predecrement(ws_sint32_t volatile *pl) -{ - return ::InterlockedDecrement((LPLONG)pl); -} - -WINSTL_ATOMIC_FNS_IMPL_(ws_sint32_t) atomic_postincrement(ws_sint32_t volatile *pl) -{ - ws_sint32_t pre = *pl; - - ::InterlockedIncrement((LPLONG)pl); - - return pre; -} - -WINSTL_ATOMIC_FNS_IMPL_(ws_sint32_t) atomic_postdecrement(ws_sint32_t volatile *pl) -{ - ws_sint32_t pre = *pl; - - ::InterlockedDecrement((LPLONG)pl); - - return pre; -} - -WINSTL_ATOMIC_FNS_IMPL_(void) atomic_increment(ws_sint32_t volatile *pl) -{ - ::InterlockedIncrement((LPLONG)pl); -} - -WINSTL_ATOMIC_FNS_IMPL_(void) atomic_decrement(ws_sint32_t volatile *pl) -{ - ::InterlockedDecrement((LPLONG)pl); -} - -WINSTL_ATOMIC_FNS_IMPL_(ws_sint32_t) atomic_write(ws_sint32_t volatile *pl, ws_sint32_t n) -{ - return ::InterlockedExchange((LPLONG)pl, n); -} - -WINSTL_ATOMIC_FNS_IMPL_(ws_sint32_t) atomic_read(ws_sint32_t volatile const *pl); -WINSTL_ATOMIC_FNS_IMPL_(ws_sint32_t) atomic_postadd(ws_sint32_t volatile *pl, ws_sint32_t n); - - -/* Uni-processor variants */ - -WINSTL_ATOMIC_FNS_IMPL_(ws_sint32_t) atomic_preincrement_up(ws_sint32_t volatile *pl) -{ - return atomic_preincrement(pl); -} - -WINSTL_ATOMIC_FNS_IMPL_(ws_sint32_t) atomic_predecrement_up(ws_sint32_t volatile *pl) -{ - return atomic_predecrement(pl); -} - -WINSTL_ATOMIC_FNS_IMPL_(ws_sint32_t) atomic_postincrement_up(ws_sint32_t volatile *pl) -{ - return atomic_postincrement(pl); -} - -WINSTL_ATOMIC_FNS_IMPL_(ws_sint32_t) atomic_postdecrement_up(ws_sint32_t volatile *pl) -{ - return atomic_postdecrement(pl); -} - -WINSTL_ATOMIC_FNS_IMPL_(void) atomic_increment_up(ws_sint32_t volatile *pl) -{ - atomic_increment(pl); -} - -WINSTL_ATOMIC_FNS_IMPL_(void) atomic_decrement_up(ws_sint32_t volatile *pl) -{ - atomic_decrement(pl); -} - -WINSTL_ATOMIC_FNS_IMPL_(ws_sint32_t) atomic_write_up(ws_sint32_t volatile *pl, ws_sint32_t n) -{ - return atomic_write(pl, n); -} - -WINSTL_ATOMIC_FNS_IMPL_(ws_sint32_t) atomic_read_up(ws_sint32_t volatile const *pl); -WINSTL_ATOMIC_FNS_IMPL_(ws_sint32_t) atomic_postadd_up(ws_sint32_t volatile *pl, ws_sint32_t n); - -/* SMP variants */ - -WINSTL_ATOMIC_FNS_IMPL_(ws_sint32_t) atomic_preincrement_smp(ws_sint32_t volatile *pl) -{ - return atomic_preincrement(pl); -} - -WINSTL_ATOMIC_FNS_IMPL_(ws_sint32_t) atomic_predecrement_smp(ws_sint32_t volatile *pl) -{ - return atomic_predecrement(pl); -} - -WINSTL_ATOMIC_FNS_IMPL_(ws_sint32_t) atomic_postincrement_smp(ws_sint32_t volatile *pl) -{ - return atomic_postincrement(pl); -} - -WINSTL_ATOMIC_FNS_IMPL_(ws_sint32_t) atomic_postdecrement_smp(ws_sint32_t volatile *pl) -{ - return atomic_postdecrement(pl); -} - -WINSTL_ATOMIC_FNS_IMPL_(void) atomic_increment_smp(ws_sint32_t volatile *pl) -{ - atomic_increment(pl); -} - -WINSTL_ATOMIC_FNS_IMPL_(void) atomic_decrement_smp(ws_sint32_t volatile *pl) -{ - atomic_decrement(pl); -} - -WINSTL_ATOMIC_FNS_IMPL_(ws_sint32_t) atomic_write_smp(ws_sint32_t volatile *pl, ws_sint32_t n) -{ - return atomic_write(pl, n); -} - -WINSTL_ATOMIC_FNS_IMPL_(ws_sint32_t) atomic_read_smp(ws_sint32_t volatile const *pl); -WINSTL_ATOMIC_FNS_IMPL_(ws_sint32_t) atomic_postadd_smp(ws_sint32_t volatile *pl, ws_sint32_t n); - -# endif /* STSLSOFT_INLINE_ASM_SUPPORTED */ - -# endif /* !WINSTL_ATOMIC_FNS_DECLARATION_ONLY */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Other inline atomic function - */ - -inline ws_sint32_t atomic_preadd_up(ws_sint32_t volatile *pl, ws_sint32_t n) -{ - return n + atomic_postadd_up(pl, n); -} - -inline ws_sint32_t atomic_preadd_smp(ws_sint32_t volatile *pl, ws_sint32_t n) -{ - return n + atomic_postadd_smp(pl, n); -} - -inline ws_sint32_t atomic_preadd(ws_sint32_t volatile *pl, ws_sint32_t n) -{ - return n + atomic_postadd(pl, n); -} - -#endif /* !__STLSOFT_DOCUMENTATION_SKIP_SECTION */ - -/* ////////////////////////////////////////////////////////////////////////// */ - -/// @} // end of group winstl_perf_library - -/* ////////////////////////////////////////////////////////////////////////// */ - -#ifndef _WINSTL_NO_NAMESPACE -# ifdef _STLSOFT_NO_NAMESPACE -} // namespace winstl -# else -} // namespace winstl_project -} // namespace stlsoft -# endif /* _STLSOFT_NO_NAMESPACE */ -#endif /* !_WINSTL_NO_NAMESPACE */ - -/* ////////////////////////////////////////////////////////////////////////// */ - -#endif /* !_WINSTL_INCL_H_WINSTL_ATOMIC_FUNCTIONS */ - -/* ////////////////////////////////////////////////////////////////////////// */ diff -uNr gdc-0.17/d/phobos/etc/c/stlsoft/winstl_filesystem_traits.h gdc-0.18/d/phobos/etc/c/stlsoft/winstl_filesystem_traits.h --- gdc-0.17/d/phobos/etc/c/stlsoft/winstl_filesystem_traits.h 2004-10-26 02:41:27.000000000 +0200 +++ gdc-0.18/d/phobos/etc/c/stlsoft/winstl_filesystem_traits.h 1970-01-01 01:00:00.000000000 +0100 @@ -1,646 +0,0 @@ -/* ///////////////////////////////////////////////////////////////////////////// - * File: winstl_filesystem_traits.h - * - * Purpose: Contains the filesystem_traits template class, and ANSI and - * Unicode specialisations thereof. - * - * Created: 15th November 2002 - * Updated: 28th November 2003 - * - * Author: Matthew Wilson, Synesis Software Pty Ltd. - * - * License: (Licensed under the Synesis Software Standard Source License) - * - * Copyright (C) 2002-2003, Synesis Software Pty Ltd. - * - * All rights reserved. - * - * www: http://www.synesis.com.au/winstl - * http://www.winstl.org/ - * - * email: submissions@winstl.org for submissions - * admin@winstl.org for other enquiries - * - * Redistribution and use in source and binary forms, with or - * without modification, are permitted provided that the following - * conditions are met: - * - * (i) Redistributions of source code must retain the above - * copyright notice and contact information, this list of - * conditions and the following disclaimer. - * - * (ii) Any derived versions of this software (howsoever modified) - * remain the sole property of Synesis Software. - * - * (iii) Any derived versions of this software (howsoever modified) - * remain subject to all these conditions. - * - * (iv) Neither the name of Synesis Software nor the names of any - * subdivisions, employees or agents of Synesis Software, nor the - * names of any other contributors to this software may be used to - * endorse or promote products derived from this software without - * specific prior written permission. - * - * This source code is provided by Synesis Software "as is" and any - * warranties, whether expressed or implied, including, but not - * limited to, the implied warranties of merchantability and - * fitness for a particular purpose are disclaimed. In no event - * shall the Synesis Software be liable for any direct, indirect, - * incidental, special, exemplary, or consequential damages - * (including, but not limited to, procurement of substitute goods - * or services; loss of use, data, or profits; or business - * interruption) however caused and on any theory of liability, - * whether in contract, strict liability, or tort (including - * negligence or otherwise) arising in any way out of the use of - * this software, even if advised of the possibility of such - * damage. - * - * ////////////////////////////////////////////////////////////////////////// */ - - -#ifndef _WINSTL_INCL_H_WINSTL_FILESYSTEM_TRAITS -#define _WINSTL_INCL_H_WINSTL_FILESYSTEM_TRAITS - -#ifndef __STLSOFT_DOCUMENTATION_SKIP_SECTION -# define _WINSTL_VER_H_WINSTL_FILESYSTEM_TRAITS_MAJOR 1 -# define _WINSTL_VER_H_WINSTL_FILESYSTEM_TRAITS_MINOR 7 -# define _WINSTL_VER_H_WINSTL_FILESYSTEM_TRAITS_REVISION 1 -# define _WINSTL_VER_H_WINSTL_FILESYSTEM_TRAITS_EDIT 23 -#endif /* !__STLSOFT_DOCUMENTATION_SKIP_SECTION */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Includes - */ - -#ifndef _WINSTL_INCL_H_WINSTL -# include "winstl.h" // Include the WinSTL root header -#endif /* !_WINSTL_INCL_H_WINSTL */ - -/* ///////////////////////////////////////////////////////////////////////////// - * FindVolume API declarations - * - * The FindVolume API is not visible in the Windows headers unless _WIN32_WINNT - * is defined as 0x0500 or greater. Where this definition is not present, the - * functions are declared here, unless _WINSTL_NO_FINDVOLUME_API is defined. - * - * Where _WINSTL_NO_FINDVOLUME_API is defined, the requisite members of the - * traits classes are undeclared. - */ - -#ifndef __STLSOFT_DOCUMENTATION_SKIP_SECTION - -#ifndef _WINSTL_NO_FINDVOLUME_API -# if !defined(_WIN32_WINNT) || \ - (_WIN32_WINNT < 0x0500) - -HANDLE WINAPI FindFirstVolumeA( - LPSTR lpszVolumeName, // output buffer - DWORD cchBufferLength // size of output buffer -); - -HANDLE WINAPI FindFirstVolumeW( - LPWSTR lpszVolumeName, // output buffer - DWORD cchBufferLength // size of output buffer -); - -BOOL WINAPI FindNextVolumeA( - HANDLE hFindVolume, // volume search handle - LPSTR lpszVolumeName, // output buffer - DWORD cchBufferLength // size of output buffer -); - -BOOL WINAPI FindNextVolumeW( - HANDLE hFindVolume, // volume search handle - LPWSTR lpszVolumeName, // output buffer - DWORD cchBufferLength // size of output buffer -); - -BOOL WINAPI FindVolumeClose( - HANDLE hFindVolume - ); - -# endif /* _WIN32_WINNT < 0x0500 */ -#endif /* !_WINSTL_NO_FINDVOLUME_API */ - -#endif /* !__STLSOFT_DOCUMENTATION_SKIP_SECTION */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace - */ - -#ifndef _WINSTL_NO_NAMESPACE -# ifdef _STLSOFT_NO_NAMESPACE -/* There is no stlsoft namespace, so must define ::winstl */ -namespace winstl -{ -# else -/* Define stlsoft::winstl_project */ - -namespace stlsoft -{ - -namespace winstl_project -{ - -# endif /* _STLSOFT_NO_NAMESPACE */ -#endif /* !_WINSTL_NO_NAMESPACE */ - -/* ////////////////////////////////////////////////////////////////////////// */ - -/// \weakgroup libraries STLSoft Libraries -/// \brief The individual libraries - -/// \weakgroup libraries_filesystem File-System Library -/// \ingroup libraries -/// \brief This library provides facilities for defining and manipulating file-system objects - -/// \weakgroup winstl_filesystem_library File-System Library (WinSTL) -/// \ingroup WinSTL libraries_filesystem -/// \brief This library provides facilities for defining and manipulating file-system objects for the Win32 API -/// @{ - -/* ///////////////////////////////////////////////////////////////////////////// - * Classes - */ - -#ifdef __STLSOFT_DOCUMENTATION_SKIP_SECTION -/// Traits for accessing the correct file-system functions for a given character type -/// -/// filesystem_traits is a traits class for determining the correct file-system -/// structures and functions for a given character type. -/// -/// \param C The character type -template -struct filesystem_traits -{ -public: - /// The character type - typedef C char_type; - /// The size type - typedef ws_size_t size_type; - /// The difference type - typedef ws_ptrdiff_t difference_type; - /// The find data type - typedef WIN32_FIND_DATA find_data_type; // Placeholder only - -public: - // General string handling - - /// Copies the contents of \c src to \c dest - static char_type *str_copy(char_type *dest, char_type const *src); - /// Appends the contents of \c src to \c dest - static char_type *str_cat(char_type *dest, char_type const *src); - /// Comparies the contents of \c src and \c dest - static ws_int_t str_compare(char_type const *s1, char_type const *s2); - /// Comparies the contents of \c src and \c dest in a case-insensitive fashion - static ws_int_t str_compare_no_case(char_type const *s1, char_type const *s2); - /// Evaluates the length of \c src - static size_type str_len(char_type const *src); - - // File-system entry names - - /// Appends a file-system path separator to \c dir if one does not exist - static char_type *ensure_dir_end(char_type *dir); - /// Returns \c true if dir is \c "." or \c ".." - static ws_bool_t is_dots(char_type const *dir); - /// Returns the path separator - /// - /// This is the separator that is used to separate multiple paths on the operating system. On UNIX it is ':' - static char_type path_separator(); - /// Returns the path name separator - /// - /// This is the separator that is used to separate parts of a path on the operating system. On UNIX it is '/' - static char_type path_name_separator(); - /// Returns the wildcard pattern that represents all possible matches - /// - /// \note On Win32 it is '*.*' - static char_type const *pattern_all(); - /// Gets the full path name into the given buffer, returning a pointer to the file-part - static ws_dword_t get_full_path_name(char_type const *fileName, ws_dword_t cchBuffer, char_type *buffer, char_type **ppFile); - /// Gets the full path name into the given buffer - static ws_dword_t get_full_path_name(char_type const *fileName, ws_dword_t cchBuffer, char_type *buffer); - /// Gets the short path name into the given buffer - static ws_dword_t get_short_path_name(char_type const *fileName, char_type *buffer, ws_dword_t cchBuffer); - - // FindFile() API - - /// Initiate a file-system search - static HANDLE find_first_file(char_type const *spec, find_data_type *findData); -#if _WIN32_WINNT >= 0x0400 - /// Initiate a file-system search - NT4+-only - static HANDLE find_first_file_ex(char_type const *spec, FINDEX_SEARCH_OPS flags, find_data_type *findData); -#endif /* _WIN32_WINNT >= 0x0400 */ - /// Advance a given file-system search - static ws_bool_t find_next_file(HANDLE h, find_data_type *findData); - - // FindVolume() API - -#ifndef _WINSTL_NO_FINDVOLUME_API - /// Initiate a file-system volume search - static HANDLE find_first_volume(char_type *volume_name, size_type cch_volume_name); - /// Advance a given file-system volume search - static ws_bool_t find_next_volume(HANDLE h, char_type *volume_name, size_type cch_volume_name); -#endif // !_WINSTL_NO_FINDVOLUME_API - - // Modules - - /// Gets the full path name of the given module - static ws_dword_t get_module_filename(HINSTANCE hModule, char_type *buffer, ws_dword_t cchBuffer); - /// Gets the full path name of the system directory - static ws_uint_t get_system_directory(char_type *buffer, ws_uint_t cchBuffer); - /// Gets the full path name of the windows directory - static ws_uint_t get_windows_directory(char_type *buffer, ws_uint_t cchBuffer); - - // File system state - - /// Sets the current directory to \c dir - static ws_bool_t set_current_directory(char_type const *dir); - /// Retrieves the name of the current directory into \c buffer up to a maximum of \c cchBuffer characters - static ws_uint_t get_current_directory(ws_uint_t cchBuffer, char_type *buffer); - - /// Returns whether a file exists or not - static ws_bool_t file_exists(char_type const *fileName); - - // Environment - - /// Gets an environment variable into the given buffer - static ws_dword_t get_environment_variable(char_type const *name, char_type *buffer, ws_uint_t cchBuffer); - /// Expands environment strings in \c src into \dest, up to a maximum \c cchDest characters - static ws_dword_t expand_environment_strings(char_type const *src, char_type *buffer, ws_uint_t cchBuffer); -}; - -#else - -template -struct filesystem_traits; - -#ifdef __STLSOFT_CF_TEMPLATE_SPECIALISATION_SYNTAX -template <> -#endif /* __STLSOFT_CF_TEMPLATE_SPECIALISATION_SYNTAX */ -struct filesystem_traits -{ -public: - typedef ws_char_a_t char_type; - typedef ws_size_t size_type; - typedef ws_ptrdiff_t difference_type; - typedef WIN32_FIND_DATAA find_data_type; - -public: - // General string handling - static char_type *str_copy(char_type *dest, char_type const *src) - { - return lstrcpyA(dest, src); - } - - static char_type *str_cat(char_type *dest, char_type const *src) - { - return lstrcatA(dest, src); - } - - static ws_int_t str_compare(char_type const *s1, char_type const *s2) - { - return lstrcmpA(s1, s2); - } - - static ws_int_t str_compare_no_case(char_type const *s1, char_type const *s2) - { - return lstrcmpiA(s1, s2); - } - - static size_type str_len(char_type const *src) - { - return static_cast(lstrlenA(src)); - } - - // File-system entry names - static char_type *ensure_dir_end(char_type *dir) - { - char_type *end; - - for(end = dir; *end != '\0'; ++end) - {} - - if( dir < end && - *(end - 1) != path_name_separator()) - { - *end = path_name_separator(); - *(end + 1) = '\0'; - } - - return dir; - } - - static ws_bool_t is_dots(char_type const *dir) - { - return dir != 0 && - dir[0] == '.' && - ( dir[1] == '\0' || - ( dir[1] == '.' && - dir[2] == '\0')); - } - - static char_type path_separator() - { - return ';'; - } - - static char_type path_name_separator() - { - return '\\'; - } - - static char_type const *pattern_all() - { - return "*.*"; - } - - static ws_dword_t get_full_path_name(char_type const *fileName, ws_dword_t cchBuffer, char_type *buffer, char_type **ppFile) - { - return ::GetFullPathNameA(fileName, cchBuffer, buffer, ppFile); - } - - static ws_dword_t get_full_path_name(char_type const *fileName, ws_dword_t cchBuffer, char_type *buffer) - { - char_type *pFile; - - return get_full_path_name(fileName, cchBuffer, buffer, &pFile); - } - - static ws_dword_t get_short_path_name(char_type const *fileName, char_type *buffer, ws_dword_t cchBuffer) - { - return ::GetShortPathNameA(fileName, buffer, cchBuffer); - } - - // FindFile() API - static HANDLE find_first_file(char_type const *spec, find_data_type *findData) - { - return ::FindFirstFileA(spec, findData); - } - -#if _WIN32_WINNT >= 0x0400 - static HANDLE find_first_file_ex(char_type const *spec, FINDEX_SEARCH_OPS flags, find_data_type *findData) - { - return ::FindFirstFileExA(spec, FindExInfoStandard, findData, flags, NULL, 0); - } -#endif /* _WIN32_WINNT >= 0x0400 */ - - static ws_bool_t find_next_file(HANDLE h, find_data_type *findData) - { - return ::FindNextFileA(h, findData) != FALSE; - } - - // FindVolume() API -#ifndef _WINSTL_NO_FINDVOLUME_API - static HANDLE find_first_volume(char_type *volume_name, size_type cch_volume_name) - { - return ::FindFirstVolumeA(volume_name, cch_volume_name); - } - - static ws_bool_t find_next_volume(HANDLE h, char_type *volume_name, size_type cch_volume_name) - { - return ::FindNextVolumeA(h, volume_name, cch_volume_name) != FALSE; - } -#endif // !_WINSTL_NO_FINDVOLUME_API - - // Modules - static ws_dword_t get_module_filename(HINSTANCE hModule, char_type *buffer, ws_dword_t cchBuffer) - { - return ::GetModuleFileNameA(hModule, buffer, cchBuffer); - } - - static ws_uint_t get_system_directory(char_type *buffer, ws_uint_t cchBuffer) - { - return ::GetSystemDirectoryA(buffer, cchBuffer); - } - - static ws_uint_t get_windows_directory(char_type *buffer, ws_uint_t cchBuffer) - { - return ::GetWindowsDirectoryA(buffer, cchBuffer); - } - - // File system state - static ws_bool_t set_current_directory(char_type const *dir) - { - return ::SetCurrentDirectoryA(dir) != FALSE; - } - - static ws_uint_t get_current_directory(ws_uint_t cchBuffer, char_type *buffer) - { - return ::GetCurrentDirectoryA(cchBuffer, buffer); - } - - /// Returns whether a file exists or not - static ws_bool_t file_exists(char_type const *fileName) - { - return 0xFFFFFFFF != ::GetFileAttributesA(fileName); - } - - // Environment - static ws_dword_t get_environment_variable(char_type const *name, char_type *buffer, ws_uint_t cchBuffer) - { - return ::GetEnvironmentVariableA(name, buffer, cchBuffer); - } - - static size_type expand_environment_strings(char_type const *src, char_type *dest, size_type cch_dest) - { - return static_cast(::ExpandEnvironmentStringsA(src, dest, cch_dest)); - } -}; - -#ifdef __STLSOFT_CF_TEMPLATE_SPECIALISATION_SYNTAX -template <> -#endif /* __STLSOFT_CF_TEMPLATE_SPECIALISATION_SYNTAX */ -struct filesystem_traits -{ -public: - typedef ws_char_w_t char_type; - typedef ws_size_t size_type; - typedef ws_ptrdiff_t difference_type; - typedef WIN32_FIND_DATAW find_data_type; - -public: - // General string handling - static char_type *str_copy(char_type *dest, char_type const *src) - { - return lstrcpyW(dest, src); - } - - static char_type *str_cat(char_type *dest, char_type const *src) - { - return lstrcatW(dest, src); - } - - static ws_int_t str_compare(char_type const *s1, char_type const *s2) - { - return lstrcmpW(s1, s2); - } - - static ws_int_t str_compare_no_case(char_type const *s1, char_type const *s2) - { - return lstrcmpiW(s1, s2); - } - - static size_type str_len(char_type const *src) - { - return static_cast(lstrlenW(src)); - } - - // File-system entry names - static char_type *ensure_dir_end(char_type *dir) - { - char_type *end; - - for(end = dir; *end != L'\0'; ++end) - {} - - if( dir < end && - *(end - 1) != path_name_separator()) - { - *end = path_name_separator(); - *(end + 1) = L'\0'; - } - - return dir; - } - - static ws_bool_t is_dots(char_type const *dir) - { - return dir != 0 && - dir[0] == '.' && - ( dir[1] == L'\0' || - ( dir[1] == L'.' && - dir[2] == L'\0')); - } - - static char_type path_separator() - { - return L';'; - } - - static char_type path_name_separator() - { - return L'\\'; - } - - static char_type const *pattern_all() - { - return L"*.*"; - } - - static ws_dword_t get_full_path_name(char_type const *fileName, ws_dword_t cchBuffer, char_type *buffer, char_type **ppFile) - { - winstl_message_assert("GetFullPathNameW() will crash when the file-name and buffer parameters are the same", fileName != buffer); - - return ::GetFullPathNameW(fileName, cchBuffer, buffer, ppFile); - } - - static ws_dword_t get_full_path_name(char_type const *fileName, ws_dword_t cchBuffer, char_type *buffer) - { - char_type *pFile; - - return get_full_path_name(fileName, cchBuffer, buffer, &pFile); - } - - static ws_dword_t get_short_path_name(char_type const *fileName, char_type *buffer, ws_dword_t cchBuffer) - { - return ::GetShortPathNameW(fileName, buffer, cchBuffer); - } - - // FindFile() API - static HANDLE find_first_file(char_type const *spec, find_data_type *findData) - { - return ::FindFirstFileW(spec, findData); - } - -#if _WIN32_WINNT >= 0x0400 - static HANDLE find_first_file_ex(char_type const *spec, FINDEX_SEARCH_OPS flags, find_data_type *findData) - { - return ::FindFirstFileExW(spec, FindExInfoStandard, findData, flags, NULL, 0); - } -#endif /* _WIN32_WINNT >= 0x0400 */ - - static ws_bool_t find_next_file(HANDLE h, find_data_type *findData) - { - return ::FindNextFileW(h, findData) != FALSE; - } - - // FindVolume() API -#ifndef _WINSTL_NO_FINDVOLUME_API - static HANDLE find_first_volume(char_type *volume_name, size_type cch_volume_name) - { - return ::FindFirstVolumeW(volume_name, cch_volume_name); - } - - static ws_bool_t find_next_volume(HANDLE h, char_type *volume_name, size_type cch_volume_name) - { - return ::FindNextVolumeW(h, volume_name, cch_volume_name) != FALSE; - } -#endif // !_WINSTL_NO_FINDVOLUME_API - - // Modules - static ws_dword_t get_module_filename(HINSTANCE hModule, char_type *buffer, ws_dword_t cchBuffer) - { - return ::GetModuleFileNameW(hModule, buffer, cchBuffer); - } - - static ws_uint_t get_system_directory(char_type *buffer, ws_uint_t cchBuffer) - { - return ::GetSystemDirectoryW(buffer, cchBuffer); - } - - static ws_uint_t get_windows_directory(char_type *buffer, ws_uint_t cchBuffer) - { - return ::GetWindowsDirectoryW(buffer, cchBuffer); - } - - // File system state - static ws_bool_t set_current_directory(char_type const *dir) - { - return ::SetCurrentDirectoryW(dir) != FALSE; - } - - static ws_uint_t get_current_directory(ws_uint_t cchBuffer, char_type *buffer) - { - return ::GetCurrentDirectoryW(cchBuffer, buffer); - } - - /// Returns whether a file exists or not - static ws_bool_t file_exists(char_type const *fileName) - { - return 0xFFFFFFFF != ::GetFileAttributesW(fileName); - } - - // Environment - static ws_dword_t get_environment_variable(char_type const *name, char_type *buffer, ws_uint_t cchBuffer) - { - return ::GetEnvironmentVariableW(name, buffer, cchBuffer); - } - - static size_type expand_environment_strings(char_type const *src, char_type *dest, size_type cch_dest) - { - return static_cast(::ExpandEnvironmentStringsW(src, dest, cch_dest)); - } -}; - -#endif /* __STLSOFT_DOCUMENTATION_SKIP_SECTION */ - -/* ////////////////////////////////////////////////////////////////////////// */ - -/// @} // end of group winstl_filesystem_library - -/* ////////////////////////////////////////////////////////////////////////// */ - -#ifndef _WINSTL_NO_NAMESPACE -# ifdef _STLSOFT_NO_NAMESPACE -} // namespace winstl -# else -} // namespace winstl_project -} // namespace stlsoft -# endif /* _STLSOFT_NO_NAMESPACE */ -#endif /* !_WINSTL_NO_NAMESPACE */ - -/* ////////////////////////////////////////////////////////////////////////// */ - -#endif /* _WINSTL_INCL_H_WINSTL_FILESYSTEM_TRAITS */ - -/* ////////////////////////////////////////////////////////////////////////// */ diff -uNr gdc-0.17/d/phobos/etc/c/stlsoft/winstl_findfile_sequence.h gdc-0.18/d/phobos/etc/c/stlsoft/winstl_findfile_sequence.h --- gdc-0.17/d/phobos/etc/c/stlsoft/winstl_findfile_sequence.h 2004-10-26 02:41:27.000000000 +0200 +++ gdc-0.18/d/phobos/etc/c/stlsoft/winstl_findfile_sequence.h 1970-01-01 01:00:00.000000000 +0100 @@ -1,901 +0,0 @@ -/* ///////////////////////////////////////////////////////////////////////////// - * File: winstl_findfile_sequence.h - * - * Purpose: Contains the basic_findfile_sequence template class, and ANSI - * and Unicode specialisations thereof. - * - * Notes: 1. The original implementation of the class had the const_iterator - * and value_type as nested classes. Unfortunately, Visual C++ 5 & - * 6 both had either compilation or linking problems so these are - * regretably now implemented as independent classes. - * - * 2. This class was described in detail in the article - * "Adapting Windows Enumeration Models to STL Iterator Concepts" - * (http://www.windevnet.com/documents/win0303a/), in the March - * 2003 issue of Windows Developer Network (http://windevnet.com). - * - * Created: 15th January 2002 - * Updated: 24th November 2003 - * - * Author: Matthew Wilson, Synesis Software Pty Ltd. - * - * License: (Licensed under the Synesis Software Standard Source License) - * - * Copyright (C) 2002-2003, Synesis Software Pty Ltd. - * - * All rights reserved. - * - * www: http://www.synesis.com.au/winstl - * http://www.winstl.org/ - * - * email: submissions@winstl.org for submissions - * admin@winstl.org for other enquiries - * - * Redistribution and use in source and binary forms, with or - * without modification, are permitted provided that the following - * conditions are met: - * - * (i) Redistributions of source code must retain the above - * copyright notice and contact information, this list of - * conditions and the following disclaimer. - * - * (ii) Any derived versions of this software (howsoever modified) - * remain the sole property of Synesis Software. - * - * (iii) Any derived versions of this software (howsoever modified) - * remain subject to all these conditions. - * - * (iv) Neither the name of Synesis Software nor the names of any - * subdivisions, employees or agents of Synesis Software, nor the - * names of any other contributors to this software may be used to - * endorse or promote products derived from this software without - * specific prior written permission. - * - * This source code is provided by Synesis Software "as is" and any - * warranties, whether expressed or implied, including, but not - * limited to, the implied warranties of merchantability and - * fitness for a particular purpose are disclaimed. In no event - * shall the Synesis Software be liable for any direct, indirect, - * incidental, special, exemplary, or consequential damages - * (including, but not limited to, procurement of substitute goods - * or services; loss of use, data, or profits; or business - * interruption) however caused and on any theory of liability, - * whether in contract, strict liability, or tort (including - * negligence or otherwise) arising in any way out of the use of - * this software, even if advised of the possibility of such - * damage. - * - * ////////////////////////////////////////////////////////////////////////// */ - - -#ifndef _WINSTL_INCL_H_WINSTL_FINDFILE_SEQUENCE -#define _WINSTL_INCL_H_WINSTL_FINDFILE_SEQUENCE - -#ifndef __STLSOFT_DOCUMENTATION_SKIP_SECTION -# define _WINSTL_VER_H_WINSTL_FINDFILE_SEQUENCE_MAJOR 1 -# define _WINSTL_VER_H_WINSTL_FINDFILE_SEQUENCE_MINOR 17 -# define _WINSTL_VER_H_WINSTL_FINDFILE_SEQUENCE_REVISION 3 -# define _WINSTL_VER_H_WINSTL_FINDFILE_SEQUENCE_EDIT 80 -#endif /* !__STLSOFT_DOCUMENTATION_SKIP_SECTION */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Includes - */ - -#ifndef _WINSTL_INCL_H_WINSTL -# include "winstl.h" // Include the WinSTL root header -#endif /* !_WINSTL_INCL_H_WINSTL */ -#ifndef _WINSTL_INCL_H_WINSTL_FILESYSTEM_TRAITS -# include "winstl_filesystem_traits.h" // file_traits -#endif /* !_WINSTL_INCL_H_WINSTL_FILESYSTEM_TRAITS */ -#ifndef _WINSTL_INCL_H_WINSTL_SYSTEM_VERSION -# include "winstl_system_version.h" // winnt(), major() -#endif /* !_WINSTL_INCL_H_WINSTL_SYSTEM_VERSION */ -#ifndef _STLSOFT_INCL_H_STLSOFT_ITERATOR -# include "stlsoft_iterator.h" // iterator_base -#endif /* !_STLSOFT_INCL_H_STLSOFT_ITERATOR */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Pre-processor - * - * Definition of the - */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace - */ - -#ifndef _WINSTL_NO_NAMESPACE -# ifdef _STLSOFT_NO_NAMESPACE -/* There is no stlsoft namespace, so must define ::winstl */ -namespace winstl -{ -# else -/* Define stlsoft::winstl_project */ - -namespace stlsoft -{ - -namespace winstl_project -{ - -# endif /* _STLSOFT_NO_NAMESPACE */ -#endif /* !_WINSTL_NO_NAMESPACE */ - -/* ////////////////////////////////////////////////////////////////////////// */ - -/// \weakgroup libraries STLSoft Libraries -/// \brief The individual libraries - -/// \weakgroup libraries_filesystem File-System Library -/// \ingroup libraries -/// \brief This library provides facilities for defining and manipulating file-system objects - -/// \weakgroup winstl_filesystem_library File-System Library (WinSTL) -/// \ingroup WinSTL libraries_filesystem -/// \brief This library provides facilities for defining and manipulating file-system objects for the Win32 API -/// @{ - -/* ///////////////////////////////////////////////////////////////////////////// - * Forward declarations - */ - -#ifndef __STLSOFT_DOCUMENTATION_SKIP_SECTION - -template -class basic_findfile_sequence_value_type; - -template -class basic_findfile_sequence_const_input_iterator; - -#endif /* !__STLSOFT_DOCUMENTATION_SKIP_SECTION */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Utility classes - */ - -#ifndef __STLSOFT_DOCUMENTATION_SKIP_SECTION -struct ffs_shared_handle -{ - HANDLE hSrch; - ss_sint32_t cRefs; - -public: - ss_explicit_k ffs_shared_handle(HANDLE h) - : hSrch(h) - , cRefs(1) - {} - void Release() - { - if(--cRefs == 0) - { - delete this; - } - } -#if defined(__STLSOFT_COMPILER_IS_GCC) -protected: -#else /* ? __STLSOFT_COMPILER_IS_GCC */ -private: -#endif /* __STLSOFT_COMPILER_IS_GCC */ - ~ffs_shared_handle() - { - winstl_message_assert("Shared search handle being destroyed with outstanding references!", 0 == cRefs); - - if(hSrch != INVALID_HANDLE_VALUE) - { - ::FindClose(hSrch); - } - } -}; -#endif /* !__STLSOFT_DOCUMENTATION_SKIP_SECTION */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Classes - */ - -// class basic_findfile_sequence -/// Presents an STL-like sequence interface over the items on the file-system -/// -/// \param C The character type -/// \param T The traits type. On translators that support default template arguments this defaults to filesystem_traits -/// -/// \note This class was described in detail in the article -/// "Adapting Windows Enumeration Models to STL Iterator Concepts" -/// (http://www.windevnet.com/documents/win0303a/), in the March 2003 issue of -/// Windows Developer Network (http://windevnet.com). -template< ss_typename_param_k C -#ifdef __STLSOFT_CF_TEMPLATE_CLASS_DEFAULT_CLASS_ARGUMENT_SUPPORT - , ss_typename_param_k T = filesystem_traits -#else - , ss_typename_param_k T /* = filesystem_traits */ -#endif /* __STLSOFT_CF_TEMPLATE_CLASS_DEFAULT_CLASS_ARGUMENT_SUPPORT */ - > -class basic_findfile_sequence -{ -public: - /// The character type - typedef C char_type; - /// The traits type - typedef T traits_type; - /// The current parameterisation of the type - typedef basic_findfile_sequence class_type; - /// The value type - typedef basic_findfile_sequence_value_type value_type; - /// The non-mutating (const) iterator type supporting the Input Iterator concept - typedef basic_findfile_sequence_const_input_iterator const_input_iterator; - /// The non-mutating (const) iterator type - typedef const_input_iterator const_iterator; - /// The reference type - typedef value_type &reference; - /// The non-mutable (const) reference type - typedef value_type const &const_reference; - /// The find-data type - typedef ss_typename_type_k traits_type::find_data_type find_data_type; - /// The size type - typedef ws_size_t size_type; - - enum - { - includeDots = 0x0008 //!< Causes the search to include the "." and ".." directories, which are elided by default - , directories = 0x0010 //!< Causes the search to include directories - , files = 0x0020 //!< Causes the search to include files -#ifndef __STLSOFT_DOCUMENTATION_SKIP_SECTION - , noSort = 0 /* 0x0100 */ //!< -#endif /* !__STLSOFT_DOCUMENTATION_SKIP_SECTION */ - , - }; - -// Construction -public: - /// Commence a search according to the given search pattern and flags - ss_explicit_k basic_findfile_sequence(char_type const *searchSpec, ws_int_t flags = directories | files); - /// Commence a search according to the given search pattern and flags, relative to \c directory - basic_findfile_sequence(char_type const *directory, char_type const *searchSpec, ws_int_t flags = directories | files); - /// Destructor - ~basic_findfile_sequence() winstl_throw_0(); - -// Iteration -public: - /// Begins the iteration - /// - /// \return An iterator representing the start of the sequence - const_iterator begin() const; - /// Ends the iteration - /// - /// \return An iterator representing the end of the sequence - const_iterator end() const; - -// Attributes -public: - /// Returns the directory of the search - /// - /// \note Will be the empty string for instances created with the first constructor - char_type const *get_directory() const; - -// State -public: - /// Returns the number of items in the sequence - size_type size() const; - /// Indicates whether the sequence is empty - ws_bool_t empty() const; - /// Returns the maximum number of items in the sequence - static size_type max_size(); - -// Members -private: - friend class basic_findfile_sequence_value_type; - friend class basic_findfile_sequence_const_input_iterator; - - char_type m_directory[_MAX_DIR + 1]; - char_type m_subpath[_MAX_PATH + 1]; - char_type m_search[_MAX_PATH + 1]; - ws_int_t m_flags; - -// Implementation -private: - static ws_int_t validate_flags_(ws_int_t flags); - static void extract_subpath_(char_type *dest, char_type const *searchSpec); - - static HANDLE find_first_file_(char_type const *spec, ws_int_t flags, find_data_type *findData); - HANDLE begin_(find_data_type &findData) const; - -// Not to be implemented -private: - basic_findfile_sequence(class_type const &); - basic_findfile_sequence const &operator =(class_type const &); -}; - -/* ///////////////////////////////////////////////////////////////////////////// - * Typedefs for commonly encountered types - */ - -/// Instantiation of the basic_findfile_sequence template for the ANSI character type \c char -typedef basic_findfile_sequence > findfile_sequence_a; -/// Instantiation of the basic_findfile_sequence template for the Unicode character type \c wchar_t -typedef basic_findfile_sequence > findfile_sequence_w; -/// Instantiation of the basic_findfile_sequence template for the Win32 character type \c TCHAR -typedef basic_findfile_sequence > findfile_sequence; - -/* ////////////////////////////////////////////////////////////////////////// */ - -// class basic_findfile_sequence_value_type -/// Value type for the basic_findfile_sequence -template< ss_typename_param_k C - , ss_typename_param_k T - > -class basic_findfile_sequence_value_type -{ -public: - /// The character type - typedef C char_type; - /// The traits type - typedef T traits_type; - /// The current parameterisation of the type - typedef basic_findfile_sequence_value_type class_type; - /// The find-data type - typedef ss_typename_type_k traits_type::find_data_type find_data_type; - -public: - /// Default constructor - basic_findfile_sequence_value_type(); -private: - basic_findfile_sequence_value_type(find_data_type const &data, char_type const *path) - : m_data(data) - { - traits_type::str_copy(m_path, path); - traits_type::ensure_dir_end(m_path); - traits_type::str_cat(m_path, data.cFileName); - } -public: - /// Denstructor - ~basic_findfile_sequence_value_type() winstl_throw_0(); - - /// Copy assignment operator - class_type &operator =(class_type const &rhs); - - /// Returns a non-mutating reference to find-data - find_data_type const &get_find_data() const; - /// Returns a non-mutating reference to find-data - /// - /// \deprecated This method may be removed in a future release. get_find_data() should be used instead - find_data_type const &GetFindData() const; // Deprecated - - /// Returns the filename part of the item - char_type const *get_filename() const; - /// Returns the short form of the filename part of the item - char_type const *get_short_filename() const; - /// Returns the full path of the item - char_type const *get_path() const; - - /// Implicit conversion to a pointer-to-const of the full path - operator char_type const * () const; - -// Members -private: - friend class basic_findfile_sequence_const_input_iterator; - - find_data_type m_data; - char_type m_path[_MAX_PATH + 1]; -}; - -// class basic_findfile_sequence_const_input_iterator -/// Iterator type for the basic_findfile_sequence supporting the Input Iterator concept -template -class basic_findfile_sequence_const_input_iterator - : public stlsoft_ns_qual(iterator_base) -{ -public: - /// The character type - typedef C char_type; - /// The traits type - typedef T traits_type; - /// The value type - typedef V value_type; - /// The current parameterisation of the type - typedef basic_findfile_sequence_const_input_iterator class_type; - /// The find-data type - typedef ss_typename_type_k traits_type::find_data_type find_data_type; -private: - typedef basic_findfile_sequence sequence_type; - -private: - basic_findfile_sequence_const_input_iterator(sequence_type const &l, HANDLE hSrch, find_data_type const &data) - : m_list(&l) - , m_handle(new ffs_shared_handle(hSrch)) - , m_data(data) - {} - basic_findfile_sequence_const_input_iterator(sequence_type const &l); -public: - /// Default constructor - basic_findfile_sequence_const_input_iterator(); - /// Move constructor - basic_findfile_sequence_const_input_iterator(class_type const &rhs); - /// Denstructor - ~basic_findfile_sequence_const_input_iterator() winstl_throw_0(); - -public: - /// Pre-increment operator - class_type &operator ++(); - /// Post-increment operator - class_type operator ++(int); - /// Dereference to return the value at the current position - const value_type operator *() const; - /// Evaluates whether \c this and \c rhs are equivalent - ws_bool_t operator ==(class_type const &rhs) const; - /// Evaluates whether \c this and \c rhs are not equivalent - ws_bool_t operator !=(class_type const &rhs) const; - -// Members -private: - friend class basic_findfile_sequence; - - sequence_type const * const m_list; - ffs_shared_handle *m_handle; - ss_typename_type_k traits_type::find_data_type m_data; - -// Not to be implemented -private: - basic_findfile_sequence_const_input_iterator &operator =(class_type const &rhs); -}; - -/////////////////////////////////////////////////////////////////////////////// -// Shims - -template -inline ws_bool_t is_empty(basic_findfile_sequence const &s) -{ - return s.empty(); -} - -/////////////////////////////////////////////////////////////////////////////// -// Implementation - -#ifndef __STLSOFT_DOCUMENTATION_SKIP_SECTION - -// basic_findfile_sequence - -template -inline /* static */ HANDLE basic_findfile_sequence::find_first_file_(ss_typename_type_k basic_findfile_sequence::char_type const *spec, ws_int_t flags, ss_typename_type_k basic_findfile_sequence::find_data_type *findData) -{ - HANDLE hSrch; - -#if _WIN32_WINNT >= 0x0400 - if( (directories == (flags & (directories | files))) && - system_version::winnt() && - system_version::major() >= 4) - { - hSrch = traits_type::find_first_file_ex(spec, FindExSearchLimitToDirectories , findData); - } - else -#else - ((void)flags); -#endif /* _WIN32_WINNT >= 0x0400 */ - { - hSrch = traits_type::find_first_file(spec, findData); - } - - return hSrch; -} - -template -inline HANDLE basic_findfile_sequence::begin_(ss_typename_type_k basic_findfile_sequence::find_data_type &findData) const -{ - HANDLE hSrch = find_first_file_(m_search, m_flags, &findData); - - if(hSrch != INVALID_HANDLE_VALUE) - { - // Now need to validate against the flags - - for(; hSrch != INVALID_HANDLE_VALUE; ) - { - if((findData.dwFileAttributes & FILE_ATTRIBUTE_DIRECTORY) == 0) - { - // A file, and files requested, so break - if(m_flags & files) - { - break; - } - } - else - { - if(traits_type::is_dots(findData.cFileName)) - { - if(m_flags & includeDots) - { - // A dots file, and dots are requested - break; - } - } - else if(m_flags & directories) - { - // A directory, and directories requested - break; - } - } - - if(!traits_type::find_next_file(hSrch, &findData)) - { - ::FindClose(hSrch); - - hSrch = INVALID_HANDLE_VALUE; - - break; - } - } - } - - return hSrch; -} - -template -inline /* static */ ws_int_t basic_findfile_sequence::validate_flags_(ws_int_t flags) -{ - return (flags & (directories | files)) == 0 ? (flags | (directories | files)) : flags; -} - -template -inline /* static */ void basic_findfile_sequence::extract_subpath_(char_type *dest, char_type const *searchSpec) -{ - char_type *pFile; - - traits_type::get_full_path_name(searchSpec, _MAX_PATH, dest, &pFile); - - if(pFile != 0) - { - *pFile = '\0'; - } -} - -// Construction -template -inline basic_findfile_sequence::basic_findfile_sequence(char_type const *searchSpec, ws_int_t flags /* = directories | files */) - : m_flags(validate_flags_(flags)) -{ - m_directory[0] = '\0'; - - traits_type::str_copy(m_search, searchSpec); - - extract_subpath_(m_subpath, searchSpec); -} - -template -inline basic_findfile_sequence::basic_findfile_sequence(char_type const *directory, char_type const * searchSpec, ws_int_t flags /* = directories | files */) - : m_flags(validate_flags_(flags)) -{ - traits_type::str_copy(m_directory, directory); - - traits_type::str_copy(m_search, directory); - traits_type::ensure_dir_end(m_search); - traits_type::str_cat(m_search, searchSpec); - - extract_subpath_(m_subpath, m_search); -} - -template -inline basic_findfile_sequence::~basic_findfile_sequence() winstl_throw_0() -{} - -// Iteration -template -inline ss_typename_type_k basic_findfile_sequence::const_iterator basic_findfile_sequence::begin() const -{ - ss_typename_type_k traits_type::find_data_type findData; - HANDLE hSrch = begin_(findData); - - if(hSrch == INVALID_HANDLE_VALUE) - { - return const_input_iterator(*this); - } - else - { - return const_input_iterator(*this, hSrch, findData); - } -} - -template -inline ss_typename_type_k basic_findfile_sequence::const_iterator basic_findfile_sequence::end() const -{ - return const_input_iterator(*this); -} - -// Attributes -template -ss_typename_type_k basic_findfile_sequence::char_type const *basic_findfile_sequence::get_directory() const -{ - return m_directory; -} - -// State -template -inline ss_typename_type_k basic_findfile_sequence::size_type basic_findfile_sequence::size() const -{ - const_input_iterator b = begin(); - const_input_iterator e = end(); - size_type c = 0; - - for(; b != e; ++b) - { - ++c; - } - - return c; -} - -template -inline ws_bool_t basic_findfile_sequence::empty() const -{ - return begin() == end(); -} - -template -inline /* static */ ss_typename_type_k basic_findfile_sequence::size_type basic_findfile_sequence::max_size() -{ - return static_cast(-1); -} - -// basic_findfile_sequence_value_type - -template -inline basic_findfile_sequence_value_type::basic_findfile_sequence_value_type() -{ - m_data.dwFileAttributes = 0xFFFFFFFF; - m_data.cFileName[0] = '\0'; - m_data.cAlternateFileName[0] = '\0'; - m_path[0] = '\0'; -} - - -template -inline basic_findfile_sequence_value_type::~basic_findfile_sequence_value_type() winstl_throw_0() -{} - -#if 0 -template -#ifdef __STLSOFT_CF_FUNCTION_SIGNATURE_FULL_ARG_QUALIFICATION_REQUIRED -inline basic_findfile_sequence_value_type::operator basic_findfile_sequence_value_type::char_type const *() const -#else -inline basic_findfile_sequence_value_type::operator char_type const *() const -#endif /* __STLSOFT_CF_FUNCTION_SIGNATURE_FULL_ARG_QUALIFICATION_REQUIRED */ -{ - return m_data.cFileName; -} -#endif /* 0 */ - -template -inline ss_typename_type_k basic_findfile_sequence_value_type::find_data_type const &basic_findfile_sequence_value_type::get_find_data() const -{ - return m_data; -} - -template -inline ss_typename_type_k basic_findfile_sequence_value_type::find_data_type const &basic_findfile_sequence_value_type::GetFindData() const -{ - return get_find_data(); -} - -template -inline ss_typename_type_k basic_findfile_sequence_value_type::char_type const *basic_findfile_sequence_value_type::get_filename() const -{ - return m_data.cFileName; -} - -template -inline ss_typename_type_k basic_findfile_sequence_value_type::char_type const *basic_findfile_sequence_value_type::get_short_filename() const -{ - return m_data.cAlternateFileName[0] != '\0' ? m_data.cAlternateFileName : m_data.cFileName; -} - -template -inline ss_typename_type_k basic_findfile_sequence_value_type::char_type const *basic_findfile_sequence_value_type::get_path() const -{ - return m_path; -} - -template -#if defined(__STLSOFT_COMPILER_IS_GCC) || \ - ( defined(__STLSOFT_COMPILER_IS_MSVC) && \ - _MSC_VER < 1100) -inline basic_findfile_sequence_value_type::operator C const * () const -#else -inline basic_findfile_sequence_value_type::operator ss_typename_type_k basic_findfile_sequence_value_type::char_type const * () const -#endif /* !__GNUC__ */ -{ - return get_path(); -} - -// operator == () -template -inline ws_bool_t operator == (basic_findfile_sequence_value_type const &lhs, basic_findfile_sequence_value_type const &rhs) -{ - return 0 == basic_findfile_sequence_value_type::traits_type::str_compare(lhs.get_path(), rhs.get_path()); -} - -template -inline ws_bool_t operator == (basic_findfile_sequence_value_type const &lhs, C const *rhs) -{ - return 0 == basic_findfile_sequence_value_type::traits_type::str_compare(lhs.get_path(), rhs); -} - -template -inline ws_bool_t operator == (C const *lhs, basic_findfile_sequence_value_type const &rhs) -{ - return 0 == basic_findfile_sequence_value_type::traits_type::str_compare(lhs, rhs.get_path()); -} - -// basic_findfile_sequence_const_input_iterator - -template -inline basic_findfile_sequence_const_input_iterator::basic_findfile_sequence_const_input_iterator() - : m_list(NULL) - , m_handle(NULL) -{} - -template -inline basic_findfile_sequence_const_input_iterator::basic_findfile_sequence_const_input_iterator(sequence_type const &l) - : m_list(&l) - , m_handle(NULL) -{} - -template -inline basic_findfile_sequence_const_input_iterator::basic_findfile_sequence_const_input_iterator(class_type const &rhs) - : m_list(rhs.m_list) - , m_handle(rhs.m_handle) - , m_data(rhs.m_data) -{ - if(NULL != m_handle) - { - ++m_handle->cRefs; - } -} - -template -inline ss_typename_type_k basic_findfile_sequence_const_input_iterator::class_type &basic_findfile_sequence_const_input_iterator::operator =(ss_typename_param_k basic_findfile_sequence_const_input_iterator::class_type const &rhs) -{ - winstl_message_assert("Assigning iterators from separate sequences", m_list == rhs.m_list); // Should only be comparing iterators from same container - - m_handle = rhs.m_handle; - m_data = rhs.m_data; - - if(NULL != m_handle) - { - ++m_handle->cRefs; - } - - return *this; -} - -template -inline basic_findfile_sequence_const_input_iterator::~basic_findfile_sequence_const_input_iterator() winstl_throw_0() -{ - if(NULL != m_handle) - { - m_handle->Release(); - } -} - -template -inline ss_typename_type_k basic_findfile_sequence_const_input_iterator::class_type &basic_findfile_sequence_const_input_iterator::operator ++() -{ - ws_int_t flags = m_list->m_flags; - - winstl_message_assert("Attempting to increment an invalid iterator!", NULL != m_handle); - - for(; m_handle->hSrch != INVALID_HANDLE_VALUE; ) - { - if(!traits_type::find_next_file(m_handle->hSrch, &m_data)) - { - m_handle->Release(); - - m_handle = NULL; - - break; - } - else - { - if((m_data.dwFileAttributes & FILE_ATTRIBUTE_DIRECTORY) == 0) - { - // A file, and files requested, so break - if(flags & sequence_type::files) - { - break; - } - } - else - { - if(traits_type::is_dots(m_data.cFileName)) - { - if(flags & sequence_type::includeDots) - { - // A dots file, and dots are requested - break; - } - } - else if(flags & sequence_type::directories) - { - // A directory, and directories requested - break; - } - } - } - } - - return *this; -} - -template -inline ss_typename_type_k basic_findfile_sequence_const_input_iterator::class_type basic_findfile_sequence_const_input_iterator::operator ++(int) -{ - class_type ret(*this); - - operator ++(); - - return ret; -} - -template -inline const ss_typename_type_k basic_findfile_sequence_const_input_iterator::value_type basic_findfile_sequence_const_input_iterator::operator *() const -{ - if(NULL != m_handle) - { - return value_type(m_data, m_list->m_subpath); - } - else - { - winstl_message_assert("Dereferencing end()-valued iterator", 0); - - return value_type(); - } -} - -template -inline ws_bool_t basic_findfile_sequence_const_input_iterator::operator ==(class_type const &rhs) const -{ - ws_bool_t eq; - - // Should only be comparing iterators from same container - winstl_message_assert("Comparing iterators from separate sequences", m_list == rhs.m_list); - - // Not equal if one but not both handles is the INVALID_HANDLE_VALUE - // or if the data is not equal. - if( (NULL == m_handle) != (NULL == rhs.m_handle) || - ( NULL != m_handle && - traits_type::str_compare(m_data.cFileName, rhs.m_data.cFileName) != 0)) - { - eq = ws_false_v; - } - else - { - eq = ws_true_v; - } - - return eq; -} - -template -inline ws_bool_t basic_findfile_sequence_const_input_iterator::operator !=(class_type const &rhs) const -{ - return ! operator ==(rhs); -} - -#endif /* !__STLSOFT_DOCUMENTATION_SKIP_SECTION */ - -/* ////////////////////////////////////////////////////////////////////////// */ - -/// @} // end of group winstl_filesystem_library - -/* ////////////////////////////////////////////////////////////////////////// */ - -#ifndef _WINSTL_NO_NAMESPACE -# ifdef _STLSOFT_NO_NAMESPACE -} // namespace winstl -# else -} // namespace winstl_project -} // namespace stlsoft -# endif /* _STLSOFT_NO_NAMESPACE */ -#endif /* !_WINSTL_NO_NAMESPACE */ - -/* ////////////////////////////////////////////////////////////////////////// */ - -#endif /* _WINSTL_INCL_H_WINSTL_FINDFILE_SEQUENCE */ - -/* ////////////////////////////////////////////////////////////////////////// */ diff -uNr gdc-0.17/d/phobos/etc/c/stlsoft/winstl.h gdc-0.18/d/phobos/etc/c/stlsoft/winstl.h --- gdc-0.17/d/phobos/etc/c/stlsoft/winstl.h 2004-10-26 02:41:27.000000000 +0200 +++ gdc-0.18/d/phobos/etc/c/stlsoft/winstl.h 1970-01-01 01:00:00.000000000 +0100 @@ -1,528 +0,0 @@ -/* ///////////////////////////////////////////////////////////////////////////// - * File: winstl.h - * - * Purpose: Root header for the WinSTL libraries. Performs various compiler - * and platform discriminations, and definitions of types. - * - * Created: 15th January 2002 - * Updated: 17th November 2003 - * - * Author: Matthew Wilson, Synesis Software Pty Ltd. - * - * License: (Licensed under the Synesis Software Standard Source License) - * - * Copyright (C) 2002-2003, Synesis Software Pty Ltd. - * - * All rights reserved. - * - * www: http://www.synesis.com.au/winstl - * http://www.winstl.org/ - * - * email: submissions@winstl.org for submissions - * admin@winstl.org for other enquiries - * - * Redistribution and use in source and binary forms, with or - * without modification, are permitted provided that the following - * conditions are met: - * - * (i) Redistributions of source code must retain the above - * copyright notice and contact information, this list of - * conditions and the following disclaimer. - * - * (ii) Any derived versions of this software (howsoever modified) - * remain the sole property of Synesis Software. - * - * (iii) Any derived versions of this software (howsoever modified) - * remain subject to all these conditions. - * - * (iv) Neither the name of Synesis Software nor the names of any - * subdivisions, employees or agents of Synesis Software, nor the - * names of any other contributors to this software may be used to - * endorse or promote products derived from this software without - * specific prior written permission. - * - * This source code is provided by Synesis Software "as is" and any - * warranties, whether expressed or implied, including, but not - * limited to, the implied warranties of merchantability and - * fitness for a particular purpose are disclaimed. In no event - * shall the Synesis Software be liable for any direct, indirect, - * incidental, special, exemplary, or consequential damages - * (including, but not limited to, procurement of substitute goods - * or services; loss of use, data, or profits; or business - * interruption) however caused and on any theory of liability, - * whether in contract, strict liability, or tort (including - * negligence or otherwise) arising in any way out of the use of - * this software, even if advised of the possibility of such - * damage. - * - * ////////////////////////////////////////////////////////////////////////// */ - - -#ifndef _WINSTL_INCL_H_WINSTL -#define _WINSTL_INCL_H_WINSTL - -/* File version */ -#ifndef __STLSOFT_DOCUMENTATION_SKIP_SECTION -#define _WINSTL_VER_H_WINSTL_MAJOR 1 -#define _WINSTL_VER_H_WINSTL_MINOR 26 -#define _WINSTL_VER_H_WINSTL_REVISION 1 -#define _WINSTL_VER_H_WINSTL_EDIT 100 -#endif /* !__STLSOFT_DOCUMENTATION_SKIP_SECTION */ - -/** \file winstl.h The root header for the \ref WinSTL project */ - -/** \weakgroup projects STLSoft Projects - * - * \brief The Projects that comprise the STLSoft libraries - */ - -/** \defgroup WinSTL WinSTL - * \ingroup projects - * - * \brief     Where the Standard Template Library meets the Win32 API - * - * The philosophy of WinSTL (http://winstl.org/) is essentially the same as that - * of the STLSoft (http://stlsoft.org/) organisation: providing robust and - * lightweight software to the Win32 API development - * community. WinSTL provides template-based software that builds on that - * provided by Win and STLSoft in order to reduce programmer effort and increase - * robustness in the use of the Win. - * - * Namespaces - * - * The WinSTL namespace winstl is actually an alias for the - * namespace stlsoft::winstl_project, and as such all the - * WinSTL project components actually reside within the - * stlsoft namespace. However, there is never any need to - * use the stlsoft::winstl_project namespace in your code, - * and you should always use the alias winstl. - * - * Dependencies - * - * As with all parts of the STLSoft libraries, there are no - * dependencies on WinSTL binary components and no need to compile WinSTL - * implementation files; WinSTL is 100% header-only! - * - * As with most of the STLSoft sub-projects, WinSTL depends only on: - * - * - Selected headers from the C standard library, such as wchar.h - * - Selected headers from the C++ standard library, such as new, functional - * - Selected header files of the STLSoft main project - * - The header files particular to the technology area, in this case the Win32 API library headers, such as objbase.h - * - The binary (static and dynamic libraries) components particular to the technology area, in this case the Win32 API libraries that ship with the operating system and your compiler(s) - * - * In addition, some parts of the libraries exhibit different behaviour when - * translated in different contexts, such as the value of _WIN32_WINNT, - * or with ntsecapi.h include. In all - * cases the libraries function correctly in whatever context they are compiled. - */ - -/* ///////////////////////////////////////////////////////////////////////////// - * WinSTL version - * - * The libraries version information is comprised of major, minor and revision - * components. - * - * The major version is denoted by the _WINSTL_VER_MAJOR preprocessor symbol. - * A changes to the major version component implies that a dramatic change has - * occurred in the libraries, such that considerable changes to source dependent - * on previous versions would need to be effected. - * - * The minor version is denoted by the _WINSTL_VER_MINOR preprocessor symbol. - * Changes to the minor version component imply that a significant change has - * occurred to the libraries, either in the addition of new functionality or in - * the destructive change to one or more components such that recomplilation and - * code change may be necessitated. - * - * The revision version is denoted by the _WINSTL_VER_REVISIO preprocessor - * symbol. Changes to the revision version component imply that a bug has been - * fixed. Dependent code should be recompiled in order to pick up the changes. - * - * In addition to the individual version symbols - _WINSTL_VER_MAJOR, - * _WINSTL_VER_MINOR and _WINSTL_VER_REVISION - a composite symbol _WINSTL_VER - * is defined, where the upper 8 bits are 0, bits 16-23 represent the major - * component, bits 8-15 represent the minor component, and bits 0-7 represent - * the revision component. - * - * Each release of the libraries will bear a different version, and that version - * will also have its own symbol: Version 1.0.1 specifies _WINSTL_VER_1_0_1. - * - * Thus the symbol _WINSTL_VER may be compared meaningfully with a specific - * version symbol, e.g. #if _WINSTL_VER >= _WINSTL_VER_1_0_1 - */ - -/// \def _WINSTL_VER_MAJOR -/// The major version number of WinSTL - -/// \def _WINSTL_VER_MINOR -/// The minor version number of WinSTL - -/// \def _WINSTL_VER_REVISION -/// The revision version number of WinSTL - -/// \def _WINSTL_VER -/// The current composite version number of WinSTL - -#define _WINSTL_VER_MAJOR 1 -#define _WINSTL_VER_MINOR 4 -#define _WINSTL_VER_REVISION 1 -#define _WINSTL_VER_1_0_1 0x00010001 /*!< Version 1.0.1 */ -#define _WINSTL_VER_1_0_2 0x00010002 /*!< Version 1.0.2 */ -#define _WINSTL_VER_1_1_1 0x00010101 /*!< Version 1.1.1 */ -#define _WINSTL_VER_1_2_1 0x00010201 /*!< Version 1.2.1 */ -#define _WINSTL_VER_1_3_1 0x00010301 /*!< Version 1.3.1 */ -#define _WINSTL_VER_1_3_2 0x00010302 /*!< Version 1.3.2 */ -#define _WINSTL_VER_1_3_3 0x00010303 /*!< Version 1.3.3 */ -#define _WINSTL_VER_1_3_4 0x00010304 /*!< Version 1.3.4 */ -#define _WINSTL_VER_1_3_5 0x00010305 /*!< Version 1.3.5 */ -#define _WINSTL_VER_1_3_6 0x00010306 /*!< Version 1.3.6 */ -#define _WINSTL_VER_1_3_7 0x00010307 /*!< Version 1.3.7 */ -#define _WINSTL_VER_1_4_1 0x00010401 /*!< Version 1.4.1 */ - -#define _WINSTL_VER _WINSTL_VER_1_4_1 - -/* ///////////////////////////////////////////////////////////////////////////// - * Includes - */ - -/* Strict */ -#ifndef __STLSOFT_DOCUMENTATION_SKIP_SECTION -# ifndef STRICT -# if defined(_WINSTL_STRICT) || \ - ( !defined(_WINSTL_NO_STRICT) && \ - !defined(NO_STRICT)) -# define STRICT 1 -# endif /* !NO_STRICT && !_WINSTL_NO_STRICT */ -# endif /* STRICT */ -#endif /* !__STLSOFT_DOCUMENTATION_SKIP_SECTION */ - -#ifndef _STLSOFT_INCL_H_STLSOFT -# include "stlsoft.h" // STLSoft root header -#endif /* !_STLSOFT_INCL_H_STLSOFT */ -#include // Windows base header - -/* ///////////////////////////////////////////////////////////////////////////// - * STLSoft version compatibility - */ - -#if !defined(_STLSOFT_VER_1_5_1) || \ - _STLSOFT_VER < _STLSOFT_VER_1_5_1 -# error This version of the WinSTL libraries requires STLSoft version 1.5.1 or later -#endif /* _STLSOFT_VER < _STLSOFT_VER_1_5_1 */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Sanity checks - * - * Win32 - must be compiled in context of Win32 API - * MBCS - none of the libraries' code is written to support MBCS - */ - -/* Must be Win32 api. */ -#if !defined(WIN32) && \ - !defined(_WIN32) -# error The WinSTL libraries is currently only compatible with the Win32 API -#endif /* !WIN32 && !_WIN32 */ - -/* Should not be MBCS. */ -#ifdef _MBCS -# ifdef _WINSTL_STRICT -# error The WinSTL libraries are not compatible with variable length character representation schemes such as MBCS -# else -# ifdef _STLSOFT_COMPILE_VERBOSE -# pragma message("The WinSTL libraries are not compatible with variable length character representation schemes such as MBCS") -# endif /* _STLSOFT_COMPILE_VERBOSE */ -# endif /* _WINSTL_STRICT */ -#endif /* _MBCS */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Compiler compatibility - * - * Currently the only compilers supported by the WinSTL libraries are - * - * Borland C++ 5.5, 5.51, 5.6 - * Digital Mars C/C++ 8.26 - 8.32 - * Metrowerks 2.4 & 3.0 (CodeWarrior 7.0 & 8.0) - * Intel C/C++ 6.0 & 7.0 - * Visual C++ 4.2, 5.0, 6.0, 7.0 - * Watcom C/C++ 11.0 - */ - -#if defined(__STLSOFT_COMPILER_IS_BORLAND) -/* Borland C++ */ -# if __BORLANDC__ < 0x0550 -# error Versions of Borland C++ prior to 5.5 are not supported by the WinSTL libraries -# endif /* __BORLANDC__ */ - -#elif defined(__STLSOFT_COMPILER_IS_COMO) -/* Comeau C++ */ -# if __COMO_VERSION__ < 4300 -# error Versions of Comeau C++ prior to 4.3 are not supported by the WinSTL libraries -# endif /* __COMO_VERSION__ */ - -#elif defined(__STLSOFT_COMPILER_IS_DMC) -/* Digital Mars C/C++ */ -# if __DMC__ < 0x0826 -# error Versions of Digital Mars C/C++ prior to 8.26 are not supported by the WinSTL libraries -# endif /* __DMC__ */ - -#elif defined(__STLSOFT_COMPILER_IS_GCC) -/* GNU C/C++ */ -# if __GNUC__ < 2 || \ - ( __GNUC__ == 2 && \ - __GNUC_MINOR__ < 95) -# error Versions of GNU C/C++ prior to 2.95 are not supported by the WinSTL libraries -# endif /* __GNUC__ */ - -#elif defined(__STLSOFT_COMPILER_IS_INTEL) -/* Intel C++ */ -# if (__INTEL_COMPILER < 600) -# error Versions of Intel C++ prior to 6.0 are not supported by the WinSTL libraries -# endif /* __INTEL_COMPILER */ - -#elif defined(__STLSOFT_COMPILER_IS_MWERKS) -/* Metrowerks C++ */ -# if (__MWERKS__ & 0xFF00) < 0x2400 -# error Versions of Metrowerks CodeWarrior C++ prior to 7.0 are not supported by the WinSTL libraries -# endif /* __MWERKS__ */ - -#elif defined(__STLSOFT_COMPILER_IS_MSVC) -/* Visual C++ */ -# if _MSC_VER < 1020 -# error Versions of Visual C++ prior to 4.2 are not supported by the WinSTL libraries -# endif /* _MSC_VER */ - -#elif defined(__STLSOFT_COMPILER_IS_VECTORC) -/* VectorC C/C++ */ - -#elif defined(__STLSOFT_COMPILER_IS_WATCOM) -/* Watcom C/C++ */ -# if (__WATCOMC__ < 1200) -# error Versions of Watcom C/C++ prior to 12.0 are not supported by the WinSTL libraries -# endif /* __WATCOMC__ */ - -#else -/* No recognised compiler */ -# ifdef _STLSOFT_FORCE_ANY_COMPILER -# define _WINSTL_COMPILER_IS_UNKNOWN -# ifdef _STLSOFT_COMPILE_VERBOSE -# pragma message("Compiler is unknown to WinSTL") -# endif /* _STLSOFT_COMPILE_VERBOSE */ -# else -# error Currently only Borland C++, Digital Mars C/C++, Intel C/C++, Metrowerks CodeWarrior and Visual C++ compilers are supported by the WinSTL libraries -# endif /* _STLSOFT_FORCE_ANY_COMPILER */ -#endif /* compiler */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Debugging - * - * The macro winstl_assert provides standard debug-mode assert functionality. - */ - -/// Defines a runtime assertion -/// -/// \param _x Must be non-zero, or an assertion will be fired -#define winstl_assert(_x) stlsoft_assert(_x) - -/// Defines a runtime assertion, with message -/// -/// \param _x Must be non-zero, or an assertion will be fired -/// \param _m The literal character string message to be included in the assertion -#define winstl_message_assert(_m, _x) stlsoft_message_assert(_m, _x) - -/// Defines a compile-time assertion -/// -/// \param _x Must be non-zero, or compilation will fail -#define winstl_static_assert(_x) stlsoft_static_assert(_x) - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace - * - * The WinSTL components are contained within the winstl namespace. This is - * usually an alias for stlsoft::winstl_project, - * - * When compilers support namespaces they are defined by default. They can be - * undefined using a cascasing system, as follows: - * - * If _STLSOFT_NO_NAMESPACES is defined, then _WINSTL_NO_NAMESPACES is defined. - * - * If _WINSTL_NO_NAMESPACES is defined, then _WINSTL_NO_NAMESPACE is defined. - * - * If _WINSTL_NO_NAMESPACE is defined, then the WinSTL constructs are defined - * in the global scope. - * - * If _STLSOFT_NO_NAMESPACES, _WINSTL_NO_NAMESPACES and _WINSTL_NO_NAMESPACE are - * all undefined but the symbol _STLSOFT_NO_NAMESPACE is defined (whence the - * namespace stlsoft does not exist), then the WinSTL constructs are defined - * within the winstl namespace. The definition matrix is as follows: - * - * _STLSOFT_NO_NAMESPACE _WINSTL_NO_NAMESPACE winstl definition - * --------------------- -------------------- ----------------- - * not defined not defined = stlsoft::winstl_project - * not defined defined not defined - * defined not defined winstl - * defined defined not defined - * - * - * - * The macro winstl_ns_qual() macro can be used to refer to elements in the - * WinSTL libraries irrespective of whether they are in the - * stlsoft::winstl_project (or winstl) namespace or in the global namespace. - * - * Furthermore, some compilers do not support the standard library in the std - * namespace, so the winstl_ns_qual_std() macro can be used to refer to elements - * in the WinSTL libraries irrespective of whether they are in the std namespace - * or in the global namespace. - */ - -/* No STLSoft namespaces means no WinSTL namespaces */ -#ifdef _STLSOFT_NO_NAMESPACES -# define _WINSTL_NO_NAMESPACES -#endif /* _STLSOFT_NO_NAMESPACES */ - -/* No WinSTL namespaces means no winstl namespace */ -#ifdef _WINSTL_NO_NAMESPACES -# define _WINSTL_NO_NAMESPACE -#endif /* _WINSTL_NO_NAMESPACES */ - -#ifndef _WINSTL_NO_NAMESPACE -# ifdef _STLSOFT_NO_NAMESPACE -/* There is no stlsoft namespace, so must define ::winstl */ -namespace winstl -{ -# else -/* Define stlsoft::winstl_project */ - -namespace stlsoft -{ - -/// The WinSTL namespace - \c winstl (aliased to \c stlsoft::winstl_project) - is -/// the namespace for the WinSTL project. -namespace winstl_project -{ - -# endif /* _STLSOFT_NO_NAMESPACE */ -#else -stlsoft_ns_using(move_lhs_from_rhs) -#endif /* !_WINSTL_NO_NAMESPACE */ - -/// \def winstl_ns_qual(x) -/// Qualifies with winstl:: if WinSTL is using namespaces or, if not, does not qualify - -/// \def winstl_ns_using(x) -/// Declares a using directive (with respect to winstl) if WinSTL is using namespaces or, if not, does nothing - -#ifndef _WINSTL_NO_NAMESPACE -# define winstl_ns_qual(x) ::winstl::x -# define winstl_ns_using(x) using ::winstl::x; -#else -# define winstl_ns_qual(x) x -# define winstl_ns_using(x) -#endif /* !_WINSTL_NO_NAMESPACE */ - -/// \def winstl_ns_qual_std(x) -/// Qualifies with std:: if WinSTL is being translated in the context of the standard library being within the std namespace or, if not, does not qualify - -/// \def winstl_ns_using_std(x) -/// Declares a using directive (with respect to std) if WinSTL is being translated in the context of the standard library being within the std namespace or, if not, does nothing - -#ifdef __STLSOFT_CF_std_NAMESPACE -# define winstl_ns_qual_std(x) ::std::x -# define winstl_ns_using_std(x) using ::std::x; -#else -# define winstl_ns_qual_std(x) x -# define winstl_ns_using_std(x) -#endif /* !__STLSOFT_CF_std_NAMESPACE */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Typedefs - * - * The WinSTL uses a number of typedefs to aid in compiler-independence in the - * libraries' main code. - */ - -typedef stlsoft_ns_qual(ss_char_a_t) ws_char_a_t; //!< Ansi char type -typedef stlsoft_ns_qual(ss_char_w_t) ws_char_w_t; //!< Unicode char type -typedef stlsoft_ns_qual(ss_sint8_t) ws_sint8_t; //!< 8-bit signed integer -typedef stlsoft_ns_qual(ss_uint8_t) ws_uint8_t; //!< 8-bit unsigned integer -typedef stlsoft_ns_qual(ss_int16_t) ws_int16_t; //!< 16-bit integer -typedef stlsoft_ns_qual(ss_sint16_t) ws_sint16_t; //!< 16-bit signed integer -typedef stlsoft_ns_qual(ss_uint16_t) ws_uint16_t; //!< 16-bit unsigned integer -typedef stlsoft_ns_qual(ss_int32_t) ws_int32_t; //!< 32-bit integer -typedef stlsoft_ns_qual(ss_sint32_t) ws_sint32_t; //!< 32-bit signed integer -typedef stlsoft_ns_qual(ss_uint32_t) ws_uint32_t; //!< 32-bit unsigned integer -#ifdef __STLSOFT_CF_NATIVE_64BIT_INTEGER_SUPPORT - typedef stlsoft_ns_qual(ss_int64_t) ws_int64_t; //!< 64-bit integer - typedef stlsoft_ns_qual(ss_sint64_t) ws_sint64_t; //!< 64-bit signed integer - typedef stlsoft_ns_qual(ss_uint64_t) ws_uint64_t; //!< 64-bit unsigned integer -#endif /* __STLSOFT_CF_NATIVE_64BIT_INTEGER_SUPPORT */ -typedef stlsoft_ns_qual(ss_int_t) ws_int_t; //!< integer -typedef stlsoft_ns_qual(ss_sint_t) ws_sint_t; //!< signed integer -typedef stlsoft_ns_qual(ss_uint_t) ws_uint_t; //!< unsigned integer -typedef stlsoft_ns_qual(ss_long_t) ws_long_t; //!< long -typedef stlsoft_ns_qual(ss_byte_t) ws_byte_t; //!< Byte -typedef stlsoft_ns_qual(ss_bool_t) ws_bool_t; //!< bool -typedef DWORD ws_dword_t; //!< dword -typedef stlsoft_ns_qual(ss_size_t) ws_size_t; //!< size -typedef stlsoft_ns_qual(ss_ptrdiff_t) ws_ptrdiff_t; //!< ptr diff -typedef stlsoft_ns_qual(ss_streampos_t) ws_streampos_t; //!< streampos -typedef stlsoft_ns_qual(ss_streamoff_t) ws_streamoff_t; //!< streamoff - -#ifndef __STLSOFT_DOCUMENTATION_SKIP_SECTION -/* ///////////////////////////////////////////////////////////////////////////// - * Values - * - * Since the boolean type may not be supported natively on all compilers, the - * values of true and false may also not be provided. Hence the values of - * ws_true_v and ws_false_v are defined, and are used in all code. - */ - -#define ws_true_v ss_true_v -#define ws_false_v ss_false_v - -#endif /* !__STLSOFT_DOCUMENTATION_SKIP_SECTION */ -/* ///////////////////////////////////////////////////////////////////////////// - * Code modification macros - */ - -#ifndef __STLSOFT_DOCUMENTATION_SKIP_SECTION -/* Exception signatures. */ -# define winstl_throw_0() stlsoft_throw_0() -# define winstl_throw_1(x1) stlsoft_throw_1(x1) -# define winstl_throw_2(x1, x2) stlsoft_throw_2(x1, x2) -# define winstl_throw_3(x1, x2, x3) stlsoft_throw_3(x1, x2, x3) -# define winstl_throw_4(x1, x2, x3, x4) stlsoft_throw_4(x1, x2, x3, x4) -# define winstl_throw_5(x1, x2, x3, x4, x5) stlsoft_throw_5(x1, x2, x3, x4, x5) -# define winstl_throw_6(x1, x2, x3, x4, x5, x6) stlsoft_throw_6(x1, x2, x3, x4, x5, x6) -# define winstl_throw_7(x1, x2, x3, x4, x5, x6, x7) stlsoft_throw_7(x1, x2, x3, x4, x5, x6, x7) -# define winstl_throw_8(x1, x2, x3, x4, x5, x6, x7, x8) stlsoft_throw_8(x1, x2, x3, x4, x5, x6, x7, x8) -#endif /* !__STLSOFT_DOCUMENTATION_SKIP_SECTION */ - -/// Evaluates, at compile time, to the number of elements within the given vector entity -#define winstl_num_elements(_x) stlsoft_num_elements(_x) - -/// Destroys the given instance \c p of the given type (\c t and \c _type) -#define winstl_destroy_instance(t, _type, p) stlsoft_destroy_instance(t, _type, p) - -/// Generates an opaque type with the name \c _htype -#define winstl_gen_opaque(_htype) stlsoft_gen_opaque(_htype) - -/// Define a 'final' class, ie. one that cannot be inherited from -#define winstl_sterile_class(_cls) stlsoft_sterile_class(_cls) - -/* ////////////////////////////////////////////////////////////////////////// */ - -#ifndef _WINSTL_NO_NAMESPACE -# ifdef _STLSOFT_NO_NAMESPACE -} // namespace winstl -# else -} // namespace winstl_project -} // namespace stlsoft -namespace winstl = ::stlsoft::winstl_project; -# endif /* _STLSOFT_NO_NAMESPACE */ -#endif /* !_WINSTL_NO_NAMESPACE */ - -/* ////////////////////////////////////////////////////////////////////////// */ - -#endif /* _WINSTL_INCL_H_WINSTL */ - -/* ////////////////////////////////////////////////////////////////////////// */ diff -uNr gdc-0.17/d/phobos/etc/c/stlsoft/winstl_spin_mutex.h gdc-0.18/d/phobos/etc/c/stlsoft/winstl_spin_mutex.h --- gdc-0.17/d/phobos/etc/c/stlsoft/winstl_spin_mutex.h 2004-10-26 02:41:27.000000000 +0200 +++ gdc-0.18/d/phobos/etc/c/stlsoft/winstl_spin_mutex.h 1970-01-01 01:00:00.000000000 +0100 @@ -1,261 +0,0 @@ -/* //////////////////////////////////////////////////////////////////////////// - * File: winstl_spin_mutex.h (originally MWSpinMx.h, ::SynesisWin) - * - * Purpose: Intra-process mutex, based on spin waits. - * - * Date: 27th August 1997 - * Updated: 24th November 2003 - * - * Author: Matthew Wilson, Synesis Software Pty Ltd. - * - * License: (Licensed under the Synesis Software Standard Source License) - * - * Copyright (C) 2002-2003, Synesis Software Pty Ltd. - * - * All rights reserved. - * - * www: http://www.synesis.com.au/winstl - * http://www.winstl.org/ - * - * email: submissions@winstl.org for submissions - * admin@winstl.org for other enquiries - * - * Redistribution and use in source and binary forms, with or - * without modification, are permitted provided that the following - * conditions are met: - * - * (i) Redistributions of source code must retain the above - * copyright notice and contact information, this list of - * conditions and the following disclaimer. - * - * (ii) Any derived versions of this software (howsoever modified) - * remain the sole property of Synesis Software. - * - * (iii) Any derived versions of this software (howsoever modified) - * remain subject to all these conditions. - * - * (iv) Neither the name of Synesis Software nor the names of any - * subdivisions, employees or agents of Synesis Software, nor the - * names of any other contributors to this software may be used to - * endorse or promote products derived from this software without - * specific prior written permission. - * - * This source code is provided by Synesis Software "as is" and any - * warranties, whether expressed or implied, including, but not - * limited to, the implied warranties of merchantability and - * fitness for a particular purpose are disclaimed. In no event - * shall the Synesis Software be liable for any direct, indirect, - * incidental, special, exemplary, or consequential damages - * (including, but not limited to, procurement of substitute goods - * or services; loss of use, data, or profits; or business - * interruption) however caused and on any theory of liability, - * whether in contract, strict liability, or tort (including - * negligence or otherwise) arising in any way out of the use of - * this software, even if advised of the possibility of such - * damage. - * - * ////////////////////////////////////////////////////////////////////////// */ - - -#ifndef _WINSTL_INCL_H_WINSTL_SPIN_MUTEX -#define _WINSTL_INCL_H_WINSTL_SPIN_MUTEX - -#ifndef __STLSOFT_DOCUMENTATION_SKIP_SECTION -#define _WINSTL_VER_H_WINSTL_SPIN_MUTEX_MAJOR 1 -#define _WINSTL_VER_H_WINSTL_SPIN_MUTEX_MINOR 3 -#define _WINSTL_VER_H_WINSTL_SPIN_MUTEX_REVISION 3 -#define _WINSTL_VER_H_WINSTL_SPIN_MUTEX_EDIT 12 -#endif /* !__STLSOFT_DOCUMENTATION_SKIP_SECTION */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Includes - */ - -#ifndef _WINSTL_INCL_H_WINSTL -# include "winstl.h" // Include the WinSTL root header -#endif /* !_WINSTL_INCL_H_WINSTL */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace - */ - -#ifndef _WINSTL_NO_NAMESPACE -# ifdef _STLSOFT_NO_NAMESPACE -/* There is no stlsoft namespace, so must define ::winstl */ -namespace winstl -{ -# else -/* Define stlsoft::winstl_project */ - -namespace stlsoft -{ - -namespace winstl_project -{ - -# endif /* _STLSOFT_NO_NAMESPACE */ -#endif /* !_WINSTL_NO_NAMESPACE */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Classes - */ - -// class spin_mutex -/// This class provides an implementation of the mutex model based on a spinning mechanism -class spin_mutex -{ -public: - typedef spin_mutex class_type; - -// Construction -public: - /// Creates an instance of the mutex - ss_explicit_k spin_mutex(ws_sint32_t *p) winstl_throw_0() - : m_spinCount((NULL != p) ? p : &m_internalCount) - , m_internalCount(0) -#ifdef STLSOFT_SPINMUTEX_COUNT_LOCKS - , m_cLocks(0) -#endif // STLSOFT_SPINMUTEX_COUNT_LOCKS - {} - /// Destroys an instance of the mutex - ~spin_mutex() winstl_throw_0() - { -#ifdef STLSOFT_SPINMUTEX_COUNT_LOCKS - stlsoft_assert(m_cLocks == 0); -#endif // STLSOFT_SPINMUTEX_COUNT_LOCKS - } - -// Operations -public: - /// Acquires a lock on the mutex, pending the thread until the lock is aquired - void lock() winstl_throw_0() - { - for(; 0 != ::InterlockedExchange((LPLONG)m_spinCount, 1); ::Sleep(1)) - {} -#ifdef STLSOFT_SPINMUTEX_COUNT_LOCKS - stlsoft_assert(++m_cLocks != 0); -#endif // STLSOFT_SPINMUTEX_COUNT_LOCKS - } - /// Releases an aquired lock on the mutex - void unlock() winstl_throw_0() - { -#ifdef STLSOFT_SPINMUTEX_COUNT_LOCKS - stlsoft_assert(m_cLocks-- != 0); -#endif // STLSOFT_SPINMUTEX_COUNT_LOCKS - ::InterlockedExchange((LPLONG)m_spinCount, 0); - } - -// Members -private: - ws_sint32_t *m_spinCount; - ws_sint32_t m_internalCount; -#ifdef STLSOFT_SPINMUTEX_COUNT_LOCKS - ws_sint32_t m_cLocks; // Used as check on matched Lock/Unlock calls -#endif // STLSOFT_SPINMUTEX_COUNT_LOCKS - -// Not to be implemented -private: - spin_mutex(class_type const &rhs); - spin_mutex &operator =(class_type const &rhs); -}; - -/* ///////////////////////////////////////////////////////////////////////////// - * Control shims - */ - -#ifndef _WINSTL_NO_NAMESPACE -# ifdef _STLSOFT_NO_NAMESPACE -} // namespace winstl -# else -} // namespace winstl_project -# endif /* _STLSOFT_NO_NAMESPACE */ -#endif /* !_WINSTL_NO_NAMESPACE */ - -/// \weakgroup concepts STLSoft Concepts - -/// \weakgroup concepts_shims Shims -/// \ingroup concepts - -/// \weakgroup concepts_shims_sync_control Synchronisation Control Shims -/// \ingroup concepts_shims -/// \brief These \ref concepts_shims "shims" control the behaviour of synchronisation objects - -/// \defgroup winstl_sync_control_shims Synchronisation Control Shims (WinSTL) -/// \ingroup WinSTL concepts_shims_sync_control -/// \brief These \ref concepts_shims "shims" control the behaviour of Win32 synchronisation objects -/// @{ - -/// This control ref concepts_shims "shim" aquires a lock on the given mutex -/// -/// \param mx The mutex on which to aquire the lock -inline void lock_instance(winstl_ns_qual(spin_mutex) &mx) -{ - mx.lock(); -} - -/// This control ref concepts_shims "shim" releases a lock on the given mutex -/// -/// \param mx The mutex on which to release the lock -inline void unlock_instance(winstl_ns_qual(spin_mutex) &mx) -{ - mx.unlock(); -} - -/// @} // end of group winstl_sync_control_shims - -#ifndef _WINSTL_NO_NAMESPACE -# ifdef _STLSOFT_NO_NAMESPACE -namespace winstl { -# else -namespace winstl_project { -# if defined(__STLSOFT_COMPILER_IS_BORLAND) -using ::stlsoft::lock_instance; -using ::stlsoft::unlock_instance; -# endif /* __STLSOFT_COMPILER_IS_BORLAND */ -# endif /* _STLSOFT_NO_NAMESPACE */ -#endif /* !_WINSTL_NO_NAMESPACE */ - -/* ///////////////////////////////////////////////////////////////////////////// - * lock_traits (for the compilers that do not support Koenig Lookup) - */ - -// class lock_traits -/// Traits for the spin_mutex class (for compilers that do not support Koenig Lookup) -struct spin_mutex_lock_traits -{ -public: - /// The lockable type - typedef spin_mutex lock_type; - typedef spin_mutex_lock_traits class_type; - -// Operations -public: - /// Lock the given spin_mutex instance - static void lock(spin_mutex &c) - { - lock_instance(c); - } - - /// Unlock the given spin_mutex instance - static void unlock(spin_mutex &c) - { - unlock_instance(c); - } -}; - -/* ////////////////////////////////////////////////////////////////////////// */ - -#ifndef _WINSTL_NO_NAMESPACE -# ifdef _STLSOFT_NO_NAMESPACE -} // namespace winstl -# else -} // namespace winstl_project -} // namespace stlsoft -# endif /* _STLSOFT_NO_NAMESPACE */ -#endif /* !_WINSTL_NO_NAMESPACE */ - -/* ////////////////////////////////////////////////////////////////////////// */ - -#endif /* !_WINSTL_INCL_H_WINSTL_SPIN_MUTEX */ - -/* ////////////////////////////////////////////////////////////////////////// */ diff -uNr gdc-0.17/d/phobos/etc/c/stlsoft/winstl_system_version.h gdc-0.18/d/phobos/etc/c/stlsoft/winstl_system_version.h --- gdc-0.17/d/phobos/etc/c/stlsoft/winstl_system_version.h 2004-10-26 02:41:27.000000000 +0200 +++ gdc-0.18/d/phobos/etc/c/stlsoft/winstl_system_version.h 1970-01-01 01:00:00.000000000 +0100 @@ -1,222 +0,0 @@ -/* ///////////////////////////////////////////////////////////////////////////// - * File: winstl_system_version.h - * - * Purpose: Contains the basic_system_version class, which provides - * information about the host system version. - * - * Created: 10th February 2002 - * Updated: 24th November 2003 - * - * Author: Matthew Wilson, Synesis Software Pty Ltd. - * - * License: (Licensed under the Synesis Software Standard Source License) - * - * Copyright (C) 2002-2003, Synesis Software Pty Ltd. - * - * All rights reserved. - * - * www: http://www.synesis.com.au/winstl - * http://www.winstl.org/ - * - * email: submissions@winstl.org for submissions - * admin@winstl.org for other enquiries - * - * Redistribution and use in source and binary forms, with or - * without modification, are permitted provided that the following - * conditions are met: - * - * (i) Redistributions of source code must retain the above - * copyright notice and contact information, this list of - * conditions and the following disclaimer. - * - * (ii) Any derived versions of this software (howsoever modified) - * remain the sole property of Synesis Software. - * - * (iii) Any derived versions of this software (howsoever modified) - * remain subject to all these conditions. - * - * (iv) Neither the name of Synesis Software nor the names of any - * subdivisions, employees or agents of Synesis Software, nor the - * names of any other contributors to this software may be used to - * endorse or promote products derived from this software without - * specific prior written permission. - * - * This source code is provided by Synesis Software "as is" and any - * warranties, whether expressed or implied, including, but not - * limited to, the implied warranties of merchantability and - * fitness for a particular purpose are disclaimed. In no event - * shall the Synesis Software be liable for any direct, indirect, - * incidental, special, exemplary, or consequential damages - * (including, but not limited to, procurement of substitute goods - * or services; loss of use, data, or profits; or business - * interruption) however caused and on any theory of liability, - * whether in contract, strict liability, or tort (including - * negligence or otherwise) arising in any way out of the use of - * this software, even if advised of the possibility of such - * damage. - * - * ////////////////////////////////////////////////////////////////////////// */ - - -#ifndef _WINSTL_INCL_H_WINSTL_SYSTEM_VERSION -#define _WINSTL_INCL_H_WINSTL_SYSTEM_VERSION - -#ifndef __STLSOFT_DOCUMENTATION_SKIP_SECTION -# define _WINSTL_VER_H_WINSTL_SYSTEM_VERSION_MAJOR 1 -# define _WINSTL_VER_H_WINSTL_SYSTEM_VERSION_MINOR 5 -# define _WINSTL_VER_H_WINSTL_SYSTEM_VERSION_REVISION 2 -# define _WINSTL_VER_H_WINSTL_SYSTEM_VERSION_EDIT 22 -#endif /* !__STLSOFT_DOCUMENTATION_SKIP_SECTION */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Includes - */ - -#ifndef _WINSTL_INCL_H_WINSTL - #include "winstl.h" // Include the WinSTL root header -#endif /* !_WINSTL_INCL_H_WINSTL */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace - */ - -#ifndef _WINSTL_NO_NAMESPACE - #ifdef _STLSOFT_NO_NAMESPACE -/* There is no stlsoft namespace, so must define ::winstl */ -namespace winstl -{ - #else -/* Define stlsoft::winstl_project */ - -namespace stlsoft -{ - -namespace winstl_project -{ - - #endif /* _STLSOFT_NO_NAMESPACE */ -#endif /* !_WINSTL_NO_NAMESPACE */ - -/* ////////////////////////////////////////////////////////////////////////// */ - -/// \weakgroup libraries STLSoft Libraries -/// \brief The individual libraries - -/// \weakgroup libraries_system System Library -/// \ingroup libraries -/// \brief This library provides facilities for accessing system attributes - -/// \defgroup winstl_system_library System Library (WinSTL) -/// \ingroup WinSTL libraries_system -/// \brief This library provides facilities for accessing Win32 system attributes -/// @{ - -/* ///////////////////////////////////////////////////////////////////////////// - * Classes - */ - -/// Provides system version information -/// -/// This class wraps the GetSystemInfo() API function. Since the information that -/// this function provides is constant for any particular active system for its -/// lifetime, the function is called only once, as implemented via the -/// _get_versioninfo() method. -class system_version -{ -public: - typedef system_version class_type; - -// Operations -public: - - // Operating system type - - /// Returns \c true if the operating system is one of the NT family (NT, 2000, XP, .NET) - static ws_bool_t winnt() - { - return _get_versioninfo().dwPlatformId == VER_PLATFORM_WIN32_NT; - } - - /// Returns \c true if the operating system is one of the 95 family (95, 98, ME) - static ws_bool_t win9x() - { - return _get_versioninfo().dwPlatformId == VER_PLATFORM_WIN32_WINDOWS; - } - - /// Returns \c true if the operating system is Win32s - static ws_bool_t win32s() - { - return _get_versioninfo().dwPlatformId == VER_PLATFORM_WIN32s; - } - - // Operating system version - - /// Returns the operating system major version - static ws_uint_t major() - { - return _get_versioninfo().dwMajorVersion; - } - - /// Returns the operating system minor version - static ws_uint_t minor() - { - return _get_versioninfo().dwMinorVersion; - } - - // Build number - - /// Returns the operating system build number - static ws_uint32_t build_number() - { - return winnt() ? _get_versioninfo().dwBuildNumber : LOWORD(_get_versioninfo().dwBuildNumber); - } - - // Structure access - - /// Provides a non-mutable (const) reference to the \c OSVERSIONINFO instance - static const OSVERSIONINFO &get_versioninfo() - { - return _get_versioninfo(); - } - -// Implementation -private: - /// Unfortunately, something in this technique scares the Borland compilers (5.5 - /// and 5.51) into Internal compiler errors so the s_init variable in - /// _get_versioninfo() is int rather than bool when compiling for borland. - static OSVERSIONINFO &_get_versioninfo() - { - static OSVERSIONINFO s_versioninfo; -#ifdef __STLSOFT_COMPILER_IS_BORLAND - /* WSCB: Borland has an internal compiler error if use ws_bool_t */ - static ws_int_t s_init = (s_versioninfo.dwOSVersionInfoSize = sizeof(s_versioninfo), ::GetVersionEx(&s_versioninfo), ws_true_v); -#else - static ws_bool_t s_init = (s_versioninfo.dwOSVersionInfoSize = sizeof(s_versioninfo), ::GetVersionEx(&s_versioninfo), ws_true_v); -#endif /* __STLSOFT_COMPILER_IS_BORLAND */ - - STLSOFT_SUPPRESS_UNUSED(s_init); // Placate GCC - - return s_versioninfo; - } -}; - -/* ////////////////////////////////////////////////////////////////////////// */ - -/// @} // end of group winstl_system_library - -/* ////////////////////////////////////////////////////////////////////////// */ - -#ifndef _WINSTL_NO_NAMESPACE - #ifdef _STLSOFT_NO_NAMESPACE -} // namespace winstl - #else -} // namespace winstl_project -} // namespace stlsoft - #endif /* _STLSOFT_NO_NAMESPACE */ -#endif /* !_WINSTL_NO_NAMESPACE */ - -/* ////////////////////////////////////////////////////////////////////////// */ - -#endif /* _WINSTL_INCL_H_WINSTL_SYSTEM_VERSION */ - -/* ////////////////////////////////////////////////////////////////////////// */ diff -uNr gdc-0.17/d/phobos/etc/c/stlsoft/winstl_thread_mutex.h gdc-0.18/d/phobos/etc/c/stlsoft/winstl_thread_mutex.h --- gdc-0.17/d/phobos/etc/c/stlsoft/winstl_thread_mutex.h 2004-10-26 02:41:27.000000000 +0200 +++ gdc-0.18/d/phobos/etc/c/stlsoft/winstl_thread_mutex.h 1970-01-01 01:00:00.000000000 +0100 @@ -1,299 +0,0 @@ -/* //////////////////////////////////////////////////////////////////////////// - * File: winstl_thread_mutex.h (originally MWCrtSct.h, ::SynesisWin) - * - * Purpose: Intra-process mutex, based on Windows CRITICAL_SECTION. - * - * Date: 17th December 1996 - * Updated: 24th November 2003 - * - * Author: Matthew Wilson, Synesis Software Pty Ltd. - * - * License: (Licensed under the Synesis Software Standard Source License) - * - * Copyright (C) 2002-2003, Synesis Software Pty Ltd. - * - * All rights reserved. - * - * www: http://www.synesis.com.au/winstl - * http://www.winstl.org/ - * - * email: submissions@winstl.org for submissions - * admin@winstl.org for other enquiries - * - * Redistribution and use in source and binary forms, with or - * without modification, are permitted provided that the following - * conditions are met: - * - * (i) Redistributions of source code must retain the above - * copyright notice and contact information, this list of - * conditions and the following disclaimer. - * - * (ii) Any derived versions of this software (howsoever modified) - * remain the sole property of Synesis Software. - * - * (iii) Any derived versions of this software (howsoever modified) - * remain subject to all these conditions. - * - * (iv) Neither the name of Synesis Software nor the names of any - * subdivisions, employees or agents of Synesis Software, nor the - * names of any other contributors to this software may be used to - * endorse or promote products derived from this software without - * specific prior written permission. - * - * This source code is provided by Synesis Software "as is" and any - * warranties, whether expressed or implied, including, but not - * limited to, the implied warranties of merchantability and - * fitness for a particular purpose are disclaimed. In no event - * shall the Synesis Software be liable for any direct, indirect, - * incidental, special, exemplary, or consequential damages - * (including, but not limited to, procurement of substitute goods - * or services; loss of use, data, or profits; or business - * interruption) however caused and on any theory of liability, - * whether in contract, strict liability, or tort (including - * negligence or otherwise) arising in any way out of the use of - * this software, even if advised of the possibility of such - * damage. - * - * ////////////////////////////////////////////////////////////////////////// */ - - -#ifndef _WINSTL_INCL_H_WINSTL_THREAD_MUTEX -#define _WINSTL_INCL_H_WINSTL_THREAD_MUTEX - -#ifndef __STLSOFT_DOCUMENTATION_SKIP_SECTION -#define _WINSTL_VER_H_WINSTL_THREAD_MUTEX_MAJOR 1 -#define _WINSTL_VER_H_WINSTL_THREAD_MUTEX_MINOR 3 -#define _WINSTL_VER_H_WINSTL_THREAD_MUTEX_REVISION 4 -#define _WINSTL_VER_H_WINSTL_THREAD_MUTEX_EDIT 14 -#endif /* !__STLSOFT_DOCUMENTATION_SKIP_SECTION */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Includes - */ - -#ifndef _WINSTL_INCL_H_WINSTL -# include "winstl.h" // Include the WinSTL root header -#endif /* !_WINSTL_INCL_H_WINSTL */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace - */ - -#ifndef _WINSTL_NO_NAMESPACE -# ifdef _STLSOFT_NO_NAMESPACE -/* There is no stlsoft namespace, so must define ::winstl */ -namespace winstl -{ -# else -/* Define stlsoft::winstl_project */ - -namespace stlsoft -{ - -namespace winstl_project -{ - -# endif /* _STLSOFT_NO_NAMESPACE */ -#endif /* !_WINSTL_NO_NAMESPACE */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Spin-count support - */ - -#ifdef __WINSTL_THREAD_MUTEX_SPIN_COUNT_SUPPORT -# undef __WINSTL_THREAD_MUTEX_SPIN_COUNT_SUPPORT -#endif /* __WINSTL_THREAD_MUTEX_SPIN_COUNT_SUPPORT */ - -#ifdef __WINSTL_THREAD_MUTEX_TRY_LOCK_SUPPORT -# undef __WINSTL_THREAD_MUTEX_TRY_LOCK_SUPPORT -#endif /* __WINSTL_THREAD_MUTEX_TRY_LOCK_SUPPORT */ - -#if defined(_WIN32_WINNT) && \ - _WIN32_WINNT >= 0x0403 -# define __WINSTL_THREAD_MUTEX_SPIN_COUNT_SUPPORT -#endif /* _WIN32_WINNT >= 0x0403 */ - -#if defined(_WIN32_WINNT) && \ - _WIN32_WINNT >= 0x0400 -# define __WINSTL_THREAD_MUTEX_TRY_LOCK_SUPPORT -#endif /* _WIN32_WINNT >= 0x0400 */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Classes - */ - -// class thread_mutex -/// This class provides an implementation of the mutex model based on the Win32 CRITICAL_SECTION -class thread_mutex -{ -public: - typedef thread_mutex class_type; - -// Construction -public: - /// Creates an instance of the mutex - thread_mutex() winstl_throw_0() - { - ::InitializeCriticalSection(&m_cs); - } -#if defined(__WINSTL_THREAD_MUTEX_SPIN_COUNT_SUPPORT) - /// Creates an instance of the mutex and sets its spin count - /// - /// \param spinCount The new spin count for the mutex - /// \note Only available with Windows NT 4 SP3 and later - thread_mutex(ws_dword_t spinCount) winstl_throw_0() - { - ::InitializeCriticalSectionAndSpinCount(&m_cs, spinCount); - } -#endif /* __WINSTL_THREAD_MUTEX_SPIN_COUNT_SUPPORT */ - /// Destroys an instance of the mutex - ~thread_mutex() winstl_throw_0() - { - ::DeleteCriticalSection(&m_cs); - } - -// Operations -public: - /// Acquires a lock on the mutex, pending the thread until the lock is aquired - void lock() winstl_throw_0() - { - ::EnterCriticalSection(&m_cs); - } -#if defined(__WINSTL_THREAD_MUTEX_TRY_LOCK_SUPPORT) - /// Attempts to lock the mutex - /// - /// \return true if the mutex was aquired, or false if not - /// \note Only available with Windows NT 4 and later - bool try_lock() - { - return ::TryEnterCriticalSection(&m_cs) != FALSE; - } -#endif /* __WINSTL_THREAD_MUTEX_TRY_LOCK_SUPPORT */ - /// Releases an aquired lock on the mutex - void unlock() winstl_throw_0() - { - ::LeaveCriticalSection(&m_cs); - } - -#if defined(__WINSTL_THREAD_MUTEX_SPIN_COUNT_SUPPORT) - /// Sets the spin count for the mutex - /// - /// \param spinCount The new spin count for the mutex - /// \return The previous spin count associated with the mutex - /// \note Only available with Windows NT 4 SP3 and later - ws_dword_t set_spin_count(ws_dword_t spinCount) winstl_throw_0() - { - return ::SetCriticalSectionSpinCount(&m_cs, spinCount); - } -#endif /* __WINSTL_THREAD_MUTEX_SPIN_COUNT_SUPPORT */ - -// Members -private: - CRITICAL_SECTION m_cs; // critical section - -// Not to be implemented -private: - thread_mutex(class_type const &rhs); - thread_mutex &operator =(class_type const &rhs); -}; - -/* ///////////////////////////////////////////////////////////////////////////// - * Control shims - */ - -#ifndef _WINSTL_NO_NAMESPACE -# ifdef _STLSOFT_NO_NAMESPACE -} // namespace winstl -# else -} // namespace winstl_project -# endif /* _STLSOFT_NO_NAMESPACE */ -#endif /* !_WINSTL_NO_NAMESPACE */ - -/// \weakgroup concepts STLSoft Concepts - -/// \weakgroup concepts_shims Shims -/// \ingroup concepts - -/// \weakgroup concepts_shims_sync_control Synchronisation Control Shims -/// \ingroup concepts_shims -/// \brief These \ref concepts_shims "shims" control the behaviour of synchronisation objects - -/// \defgroup winstl_sync_control_shims Synchronisation Control Shims (WinSTL) -/// \ingroup WinSTL concepts_shims_sync_control -/// \brief These \ref concepts_shims "shims" control the behaviour of Win32 synchronisation objects -/// @{ - -/// This control ref concepts_shims "shim" aquires a lock on the given mutex -/// -/// \param mx The mutex on which to aquire the lock -inline void lock_instance(winstl_ns_qual(thread_mutex) &mx) -{ - mx.lock(); -} - -/// This control ref concepts_shims "shim" releases a lock on the given mutex -/// -/// \param mx The mutex on which to release the lock -inline void unlock_instance(winstl_ns_qual(thread_mutex) &mx) -{ - mx.unlock(); -} - -/// @} // end of group winstl_sync_control_shims - -#ifndef _WINSTL_NO_NAMESPACE -# ifdef _STLSOFT_NO_NAMESPACE -namespace winstl { -# else -namespace winstl_project { -# if defined(__STLSOFT_COMPILER_IS_BORLAND) -using ::stlsoft::lock_instance; -using ::stlsoft::unlock_instance; -# endif /* __STLSOFT_COMPILER_IS_BORLAND */ -# endif /* _STLSOFT_NO_NAMESPACE */ -#endif /* !_WINSTL_NO_NAMESPACE */ - -/* ///////////////////////////////////////////////////////////////////////////// - * lock_traits (for the compilers that do not support Koenig Lookup) - */ - -// class lock_traits -/// Traits for the thread_mutex class (for compilers that do not support Koenig Lookup) -struct thread_mutex_lock_traits -{ -public: - /// The lockable type - typedef thread_mutex lock_type; - typedef thread_mutex_lock_traits class_type; - -// Operations -public: - /// Lock the given thread_mutex instance - static void lock(thread_mutex &c) - { - lock_instance(c); - } - - /// Unlock the given thread_mutex instance - static void unlock(thread_mutex &c) - { - unlock_instance(c); - } -}; - -/* ////////////////////////////////////////////////////////////////////////// */ - -#ifndef _WINSTL_NO_NAMESPACE -# ifdef _STLSOFT_NO_NAMESPACE -} // namespace winstl -# else -} // namespace winstl_project -} // namespace stlsoft -# endif /* _STLSOFT_NO_NAMESPACE */ -#endif /* !_WINSTL_NO_NAMESPACE */ - -/* ////////////////////////////////////////////////////////////////////////// */ - -#endif /* !_WINSTL_INCL_H_WINSTL_THREAD_MUTEX */ - -/* ////////////////////////////////////////////////////////////////////////// */ diff -uNr gdc-0.17/d/phobos/etc/c/stlsoft/winstl_tls_index.h gdc-0.18/d/phobos/etc/c/stlsoft/winstl_tls_index.h --- gdc-0.17/d/phobos/etc/c/stlsoft/winstl_tls_index.h 2004-10-26 02:41:27.000000000 +0200 +++ gdc-0.18/d/phobos/etc/c/stlsoft/winstl_tls_index.h 1970-01-01 01:00:00.000000000 +0100 @@ -1,185 +0,0 @@ -/* ///////////////////////////////////////////////////////////////////////////// - * File: winstl_tls_index.h (formerly in MWTlsFns.h, ::SynesisWin) - * - * Purpose: Win32 TLS slot index. - * - * Created: 20th January 1999 - * Updated: 24th September 2003 - * - * Author: Matthew Wilson, Synesis Software Pty Ltd. - * - * License: (Licensed under the Synesis Software Standard Source License) - * - * Copyright (C) 2002-2003, Synesis Software Pty Ltd. - * - * All rights reserved. - * - * www: http://www.synesis.com.au/winstl - * http://www.winstl.org/ - * - * email: submissions@winstl.org for submissions - * admin@winstl.org for other enquiries - * - * Redistribution and use in source and binary forms, with or - * without modification, are permitted provided that the following - * conditions are met: - * - * (i) Redistributions of source code must retain the above - * copyright notice and contact information, this list of - * conditions and the following disclaimer. - * - * (ii) Any derived versions of this software (howsoever modified) - * remain the sole property of Synesis Software. - * - * (iii) Any derived versions of this software (howsoever modified) - * remain subject to all these conditions. - * - * (iv) Neither the name of Synesis Software nor the names of any - * subdivisions, employees or agents of Synesis Software, nor the - * names of any other contributors to this software may be used to - * endorse or promote products derived from this software without - * specific prior written permission. - * - * This source code is provided by Synesis Software "as is" and any - * warranties, whether expressed or implied, including, but not - * limited to, the implied warranties of merchantability and - * fitness for a particular purpose are disclaimed. In no event - * shall the Synesis Software be liable for any direct, indirect, - * incidental, special, exemplary, or consequential damages - * (including, but not limited to, procurement of substitute goods - * or services; loss of use, data, or profits; or business - * interruption) however caused and on any theory of liability, - * whether in contract, strict liability, or tort (including - * negligence or otherwise) arising in any way out of the use of - * this software, even if advised of the possibility of such - * damage. - * - * ////////////////////////////////////////////////////////////////////////// */ - - -#ifndef _WINSTL_INCL_H_WINSTL_TLS_INDEX -#define _WINSTL_INCL_H_WINSTL_TLS_INDEX - -#ifndef __STLSOFT_DOCUMENTATION_SKIP_SECTION -# define _WINSTL_VER_H_WINSTL_TLS_INDEX_MAJOR 1 -# define _WINSTL_VER_H_WINSTL_TLS_INDEX_MINOR 0 -# define _WINSTL_VER_H_WINSTL_TLS_INDEX_REVISION 1 -# define _WINSTL_VER_H_WINSTL_TLS_INDEX_EDIT 2 -#endif /* !__STLSOFT_DOCUMENTATION_SKIP_SECTION */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Includes - */ - -#ifndef _WINSTL_INCL_H_WINSTL -# include "winstl.h" // Include the WinSTL root header -#endif /* !_WINSTL_INCL_H_WINSTL */ - -/* ///////////////////////////////////////////////////////////////////////////// - * Namespace - */ - -#ifndef _WINSTL_NO_NAMESPACE -# ifdef _STLSOFT_NO_NAMESPACE -/* There is no stlsoft namespace, so must define ::winstl */ -namespace winstl -{ - #else -/* Define stlsoft::winstl_project */ - -namespace stlsoft -{ - -namespace winstl_project -{ - -# endif /* _STLSOFT_NO_NAMESPACE */ -#endif /* !_WINSTL_NO_NAMESPACE */ - -/* ////////////////////////////////////////////////////////////////////////// */ - -/// \weakgroup libraries STLSoft Libraries -/// \brief The individual libraries - -/// \weakgroup libraries_system System Library -/// \ingroup libraries -/// \brief This library provides facilities for accessing system attributes - -/// \defgroup winstl_system_library System Library (WinSTL) -/// \ingroup WinSTL libraries_system -/// \brief This library provides facilities for accessing Win32 system attributes -/// @{ - -/* ///////////////////////////////////////////////////////////////////////////// - * Classes - */ - -/// A TLS index -/// -/// -class tls_index -{ -public: - typedef tls_index class_type; - -/// Operations -/// @{ -public: - ss_explicit_k tls_index() stlsoft_throw_0() - : m_dwIndex(::TlsAlloc()) - { - if(0xFFFFFFFF == m_dwIndex) - { - ::RaiseException(STATUS_NO_MEMORY, EXCEPTION_NONCONTINUABLE, 0, 0); - } - } - ~tls_index() stlsoft_throw_0() - { - if(0xFFFFFFFF != m_dwIndex) - { - ::TlsFree(m_dwIndex); - } - } - -/// @} - -/// Operations -/// @{ -public: - operator ws_dword_t () const - { - return m_dwIndex; - } - -/// @} - -// Members -private: - ws_dword_t m_dwIndex; - -// Not to be implemented -private: - tls_index(tls_index const &); - tls_index &operator =(tls_index const &); -}; - -/* ////////////////////////////////////////////////////////////////////////// */ - -/// @} // end of group winstl_system_library - -/* ////////////////////////////////////////////////////////////////////////// */ - -#ifndef _WINSTL_NO_NAMESPACE -# ifdef _STLSOFT_NO_NAMESPACE -} // namespace winstl -# else -} // namespace winstl_project -} // namespace stlsoft -# endif /* _STLSOFT_NO_NAMESPACE */ -#endif /* !_WINSTL_NO_NAMESPACE */ - -/* ////////////////////////////////////////////////////////////////////////// */ - -#endif /* _WINSTL_INCL_H_WINSTL_TLS_INDEX */ - -/* ////////////////////////////////////////////////////////////////////////// */ diff -uNr gdc-0.17/d/phobos/internal/aaA.d gdc-0.18/d/phobos/internal/aaA.d --- gdc-0.17/d/phobos/internal/aaA.d 2005-06-22 05:13:40.000000000 +0200 +++ gdc-0.18/d/phobos/internal/aaA.d 2006-05-18 02:05:55.000000000 +0200 @@ -1,6 +1,27 @@ //_ aaA.d -// Copyright (c) 2000-2004 by Digital Mars -// Written by Walter Bright + +/* + * Copyright (C) 2000-2006 by Digital Mars, www.digitalmars.com + * Written by Walter Bright + * + * This software is provided 'as-is', without any express or implied + * warranty. In no event will the authors be held liable for any damages + * arising from the use of this software. + * + * Permission is granted to anyone to use this software for any purpose, + * including commercial applications, and to alter it and redistribute it + * freely, subject to the following restrictions: + * + * o The origin of this software must not be misrepresented; you must not + * claim that you wrote the original software. If you use this software + * in a product, an acknowledgment in the product documentation would be + * appreciated but is not required. + * o Altered source versions must be plainly marked as such, and must not + * be misrepresented as being the original software. + * o This notice may not be removed or altered from any source + * distribution. + */ + /* NOTE: This file has been patched from the original DMD distribution to work with the GDC compiler. @@ -10,24 +31,26 @@ import std.c.stdio; import std.c.stdlib; +import std.c.string; import std.string; import std.outofmemory; // Implementation of associative array +// Auto-rehash and pre-allocate - Dave Fladebo static uint[] prime_list = [ - 97ul, 389ul, - 1543ul, 6151ul, - 24593ul, 98317ul, - 393241ul, 1572869ul, - 6291469ul, 25165843ul, - 100663319ul, 402653189ul, - 1610612741ul, 4294967291ul + 97UL, 389UL, + 1543UL, 6151UL, + 24593UL, 98317UL, + 393241UL, 1572869UL, + 6291469UL, 25165843UL, + 100663319UL, 402653189UL, + 1610612741UL, 4294967291UL ]; struct Array { - int length; + size_t length; void* ptr; } @@ -35,15 +58,46 @@ { aaA *left; aaA *right; - union - { - uint nodes; // used in the head element to store the total # of AA elements - uint hash; - } + hash_t hash; /* key */ /* value */ } +struct BB +{ + aaA*[] b; + size_t nodes; // total number of aaA nodes +} + +/* This is the type actually seen by the programmer, although + * it is completely opaque. + */ + +struct AA +{ + BB* a; + version (X86_64) + { + } + else + { + // This is here only to retain binary compatibility with the + // old way we did AA's. Should eventually be removed. + int reserved; + } +} + +/********************************** + * Align to next pointer boundary, so that + * GC won't be faced with misaligned pointers + * in value. + */ + +size_t aligntsize(size_t tsize) +{ + // Is pointer alignment on the x64 4 bytes or 8? + return (tsize + size_t.sizeof - 1) & ~(size_t.sizeof - 1); +} extern (C): @@ -54,9 +108,7 @@ /+ void _aaInvAh(aaA*[] aa) { - uint i; - - for (i = 1; i < aa.length; i++) + for (size_t i = 0; i < aa.length; i++) { if (aa[i]) _aaInvAh_x(aa[i]); @@ -78,7 +130,7 @@ private void _aaInvAh_x(aaA *e) { - uint key_hash; + hash_t key_hash; aaA *e1; aaA *e2; @@ -121,7 +173,7 @@ * Determine number of entries in associative array. */ -int _aaLen(aaA*[] aa) +size_t _aaLen(AA aa) in { //printf("_aaLen()+\n"); @@ -129,15 +181,31 @@ } out (result) { - assert(result >= 0); + size_t len = 0; - int len = 0; - uint i; + void _aaLen_x(aaA* ex) + { + auto e = ex; + len++; + + while (1) + { + if (e.right) + _aaLen_x(e.right); + e = e.left; + if (!e) + break; + len++; + } + } - for (i = 1; i < aa.length; i++) + if (aa.a) { - if (aa[i]) - len += _aaLen_x(aa[i]); + foreach (e; aa.a.b) + { + if (e) + _aaLen_x(e); + } } assert(len == result); @@ -145,31 +213,16 @@ } body { - return aa.length ? aa[0].nodes : 0; + return aa.a ? aa.a.nodes : 0; } -private int _aaLen_x(aaA *e) -{ - int len = 1; - - while (1) - { - if (e.right) - len += _aaLen_x(e.right); - e = e.left; - if (!e) - break; - len++; - } - return len; -} /************************************************* * Get pointer to value in associative array indexed by key. * Add entry for key if it is not already there. */ -void *_aaGet(aaA*[] *aa, TypeInfo keyti, int valuesize, ...) +void *_aaGetp(AA* aa, TypeInfo keyti, size_t valuesize, void *pkey) in { assert(aa); @@ -177,41 +230,31 @@ out (result) { assert(result); - assert((*aa).length); - //assert(_aaInAh(*aa, key)); - assert(*aa); + assert(aa.a); + assert(aa.a.b.length); + //assert(_aaInAh(*aa.a, key)); } body { - void *pkey = cast(void *)(&valuesize + 1); - version (BigEndian) - { - switch(keyti.tsize()) { - case 1: pkey = cast(byte*)pkey + 3; break; - case 2: pkey = cast(byte*)pkey + 2; break; - default: - ; - } - } + size_t i; + aaA* e; + auto keysize = aligntsize(keyti.tsize()); - uint key_hash; - uint i; - aaA *e; - aaA **pe; - int keysize = keyti.tsize(); + if (!aa.a) + aa.a = new BB(); - if (!(*aa).length) + if (!aa.a.b.length) { alias aaA *pa; + auto len = prime_list[0]; - *aa = new pa[prime_list[0] + 1]; - (*aa)[0] = cast(aaA *) cast(void*) new byte[aaA.sizeof]; + aa.a.b = new pa[len]; } - key_hash = keyti.getHash(pkey); + auto key_hash = keyti.getHash(pkey); //printf("hash = %d\n", key_hash); - i = (key_hash % ((*aa).length - 1)) + 1; - pe = &(*aa)[i]; + i = key_hash % aa.a.b.length; + auto pe = &aa.a.b[i]; while ((e = *pe) != null) { int c; @@ -236,9 +279,9 @@ e.hash = key_hash; *pe = e; - uint nodes = ++(*aa)[0].nodes; - //printf("length = %d, nodes = %d\n", (*aa).length, nodes); - if (nodes > (*aa).length * 4) + auto nodes = ++aa.a.nodes; + //printf("length = %d, nodes = %d\n", (*aa.a).length, nodes); + if (nodes > aa.a.b.length * 4) { _aaRehash(aa,keyti); } @@ -253,22 +296,21 @@ * Returns null if it is not already there. */ -void *_aaGetRvalue(aaA*[] aa, TypeInfo keyti, int valuesize, ...) +void *_aaGetRvaluep(AA aa, TypeInfo keyti, size_t valuesize, void *pkey) { - void *pkey = cast(void *)(&valuesize + 1); - uint key_hash; - uint i; - aaA *e; - aaA **pe; - int keysize = keyti.tsize(); + if (!aa.a) + return null; + + auto keysize = aligntsize(keyti.tsize()); + auto len = aa.a.b.length; - if (aa.length) + if (len) { - key_hash = keyti.getHash(pkey); + auto key_hash = keyti.getHash(pkey); //printf("hash = %d\n", key_hash); - i = (key_hash % (aa.length - 1)) + 1; - pe = &aa[i]; - while ((e = *pe) != null) + size_t i = key_hash % len; + auto e = aa.a.b[i]; + while (e != null) { int c; c = key_hash - e.hash; @@ -280,9 +322,9 @@ } if (c < 0) - pe = &e.left; + e = e.left; else - pe = &e.right; + e = e.right; } } return null; // not found, caller will throw exception @@ -296,7 +338,7 @@ * !=null in aa, return pointer to value */ -void* _aaIn(aaA*[] aa, TypeInfo keyti, ...) +void* _aaInp(AA aa, TypeInfo keyti, void *pkey) in { } @@ -306,43 +348,34 @@ } body { - void *pkey = cast(void *)(&keyti + 1); - version (BigEndian) + if (aa.a) { - switch(keyti.tsize()) { - case 1: pkey = cast(byte*)pkey + 3; break; - case 2: pkey = cast(byte*)pkey + 2; break; - default: - ; - } - } - uint key_hash; - uint i; - aaA *e; + //printf("_aaIn(), .length = %d, .ptr = %x\n", aa.a.length, cast(uint)aa.a.ptr); + auto len = aa.a.b.length; - //printf("_aaIn(), aa.length = %d, .ptr = %x\n", aa.length, cast(uint)aa.ptr); - if (aa.length > 1) - { - key_hash = keyti.getHash(pkey); - //printf("hash = %d\n", key_hash); - i = (key_hash % (aa.length - 1)) + 1; - e = aa[i]; - while (e != null) - { int c; + if (len) + { + auto key_hash = keyti.getHash(pkey); + //printf("hash = %d\n", key_hash); + size_t i = key_hash % len; + auto e = aa.a.b[i]; + while (e != null) + { int c; - c = key_hash - e.hash; - if (c == 0) - { - c = keyti.compare(pkey, e + 1); + c = key_hash - e.hash; if (c == 0) - return cast(void *)(e + 1) + keyti.tsize(); - } + { + c = keyti.compare(pkey, e + 1); + if (c == 0) + return cast(void *)(e + 1) + aligntsize(keyti.tsize()); + } - if (c < 0) - e = e.left; - else - e = e.right; + if (c < 0) + e = e.left; + else + e = e.right; + } } } @@ -356,30 +389,16 @@ * If key is not in aa[], do nothing. */ -void _aaDel(aaA*[] aa, TypeInfo keyti, ...) +void _aaDelp(AA aa, TypeInfo keyti, void *pkey) { - void *pkey = cast(void *)(&keyti + 1); - version (BigEndian) - { - switch(keyti.tsize()) { - case 1: pkey = cast(byte*)pkey + 3; break; - case 2: pkey = cast(byte*)pkey + 2; break; - default: - ; - } - } - - uint key_hash; - uint i; - aaA *e; - aaA **pe; + aaA* e; - if (aa.length > 1) + if (aa.a && aa.a.b.length) { - key_hash = keyti.getHash(pkey); + auto key_hash = keyti.getHash(pkey); //printf("hash = %d\n", key_hash); - i = (key_hash % (aa.length - 1)) + 1; - pe = &aa[i]; + size_t i = key_hash % aa.a.b.length; + auto pe = &aa.a.b[i]; while ((e = *pe) != null) // null means not found { int c; @@ -414,7 +433,7 @@ e.right = null; } - aa[0].nodes--; + aa.a.nodes--; // Should notify GC that e can be free'd now break; @@ -431,43 +450,59 @@ /******************************************** - * Produce array of v byte values from aa. + * Produce array of values from aa. */ -Array _aaValues(aaA*[] aa, uint k, uint v) +Array _aaValues(AA aa, size_t keysize, size_t valuesize) + in { - uint resi; + assert(keysize == aligntsize(keysize)); + } + body + { + size_t resi; Array a; - a.length = _aaLen(aa); - a.ptr = new byte[a.length * v]; - resi = 0; - for (uint i = 1; i < aa.length; i++) + void _aaValues_x(aaA* e) { - if (aa[i]) - _aaValues_x(aa[i], a.ptr, resi, k, v); + do + { + memcpy(a.ptr + resi * valuesize, + cast(byte*)e + aaA.sizeof + keysize, + valuesize); + resi++; + if (e.left) + { if (!e.right) + { e = e.left; + continue; + } + _aaValues_x(e.left); + } + e = e.right; + } while (e != null); } - assert(resi == a.length); - return a; - } -void _aaValues_x(aaA *e, void *ptr, inout uint resi, uint k, uint v) - { - do + if (aa.a) { - memcpy(ptr + resi * v, cast(byte*)e + aaA.sizeof + k, v); - resi++; - if (e.left) - _aaValues_x(e.left, ptr, resi, k, v); - e = e.right; - } while (e != null); + a.length = _aaLen(aa); + a.ptr = new byte[a.length * valuesize]; + resi = 0; + foreach (e; aa.a.b) + { + if (e) + _aaValues_x(e); + } + assert(resi == a.length); + } + return a; } + /******************************************** * Rehash an array. */ -aaA*[] _aaRehash(aaA*[]* paa, TypeInfo keyti) +AA _aaRehash(AA* paa, TypeInfo keyti) in { //_aaInvAh(paa); @@ -478,138 +513,130 @@ } body { - int len; - aaA*[] aa; - aaA*[] newaa; - int i; + BB newb; - //printf("Rehash\n"); - aa = *paa; - len = _aaLen(aa); - if (len) + void _aaRehash_x(aaA* olde) { - for (i = 0; i < prime_list.length - 1; i++) + while (1) { - if (len <= prime_list[i]) + auto left = olde.left; + auto right = olde.right; + olde.left = null; + olde.right = null; + + aaA* e; + + //printf("rehash %p\n", olde); + auto key_hash = olde.hash; + size_t i = key_hash % newb.b.length; + auto pe = &newb.b[i]; + while ((e = *pe) != null) + { int c; + + //printf("\te = %p, e.left = %p, e.right = %p\n", e, e.left, e.right); + assert(e.left != e); + assert(e.right != e); + c = key_hash - e.hash; + if (c == 0) + c = keyti.compare(olde + 1, e + 1); + if (c < 0) + pe = &e.left; + else if (c > 0) + pe = &e.right; + else + assert(0); + } + *pe = olde; + + if (right) + { + if (!left) + { olde = right; + continue; + } + _aaRehash_x(right); + } + if (!left) break; + olde = left; } - len = prime_list[i] + 1; - newaa = new aaA*[len]; - newaa[0] = cast(aaA *) cast(void*) new byte[aaA.sizeof]; - - for (i = 1; i < aa.length; i++) - { - if (aa[i]) - _aaRehash_x(newaa, aa[i], keyti); - } - - newaa[0].nodes = aa[0].nodes; } - *paa = newaa; - return newaa; - } + //printf("Rehash\n"); + if (paa.a) + { + auto aa = paa.a; + auto len = _aaLen(*paa); + if (len) + { size_t i; -private void _aaRehash_x(aaA*[] newaa, aaA *olde, TypeInfo keyti) -{ - aaA *left; - aaA *right; + for (i = 0; i < prime_list.length - 1; i++) + { + if (len <= prime_list[i]) + break; + } + len = prime_list[i]; + newb.b = new aaA*[len]; - while (1) - { - left = olde.left; - right = olde.right; - olde.left = null; - olde.right = null; - - uint key_hash; - uint i; - aaA *e; - aaA **pe; - - //printf("rehash %p\n", olde); - key_hash = olde.hash; - i = (key_hash % (newaa.length - 1)) + 1; - pe = &newaa[i]; - while ((e = *pe) != null) - { int c; + foreach (e; aa.b) + { + if (e) + _aaRehash_x(e); + } - //printf("\te = %p, e.left = %p, e.right = %p\n", e, e.left, e.right); - assert(e.left != e); - assert(e.right != e); - c = key_hash - e.hash; - if (c == 0) - c = keyti.compare(olde + 1, e + 1); - if (c < 0) - pe = &e.left; - else if (c > 0) - pe = &e.right; - else - assert(0); - } - *pe = olde; + newb.nodes = aa.nodes; + } - if (right) - { - _aaRehash_x(newaa, right, keyti); + *paa.a = newb; } - if (!left) - break; - olde = left; + return *paa; } -} /******************************************** * Produce array of N byte keys from aa. */ -Array _aaKeys(aaA*[] aa, uint n) +Array _aaKeys(AA aa, size_t keysize) { - uint len; byte[] res; - uint i; - uint resi; + size_t resi; - len = _aaLen(aa); - res = new byte[len * n]; + void _aaKeys_x(aaA* e) + { + do + { + memcpy(&res[resi * keysize], cast(byte*)(e + 1), keysize); + resi++; + if (e.left) + { if (!e.right) + { e = e.left; + continue; + } + _aaKeys_x(e.left); + } + e = e.right; + } while (e != null); + } + + Array a; + auto len = _aaLen(aa); + if (!len) + return a; + res = new byte[len * keysize]; resi = 0; - for (i = 1; i < aa.length; i++) + foreach (e; aa.a.b) { - if (aa[i]) - _aaKeys_x(aa[i], res, resi, n); + if (e) + _aaKeys_x(e); } assert(resi == len); - Array a; a.length = len; a.ptr = res; return a; } -private -void _aaKeys_x(aaA *e, byte[] res, inout uint resi, uint n) - in - { - assert(e); - assert(resi < res.length); - } - out - { - assert(resi <= res.length); - } - body - { - do - { - memcpy(&res[resi * n], cast(byte*)(e + 1), n); - resi++; - if (e.left) - _aaKeys_x(e.left, res, resi, n); - e = e.right; - } while (e != null); - } - /********************************************** * 'apply' for associative arrays - to support foreach @@ -618,10 +645,15 @@ // dg is D, but _aaApply() is C extern (D) typedef int delegate(void *) dg_t; -int _aaApply(aaA*[] aa, int keysize, dg_t dg) +int _aaApply(AA aa, size_t keysize, dg_t dg) +in +{ + assert(aligntsize(keysize) == keysize); +} +body { int result; - //printf("_aaApply(aa = x%llx, keysize = %d, dg = x%llx)\n", aa, keysize, dg); + //printf("_aaApply(aa = x%llx, keysize = %d, dg = x%llx)\n", aa.a, keysize, dg); int treewalker(aaA* e) { int result; @@ -633,7 +665,12 @@ if (result) break; if (e.right) - { result = treewalker(e.right); + { if (!e.left) + { + e = e.right; + continue; + } + result = treewalker(e.right); if (result) break; } @@ -643,13 +680,16 @@ return result; } - for (uint i = 1; i < aa.length; i++) + if (aa.a) { - if (aa[i]) + foreach (e; aa.a.b) { - result = treewalker(aa[i]); - if (result) - break; + if (e) + { + result = treewalker(e); + if (result) + break; + } } } return result; @@ -658,10 +698,15 @@ // dg is D, but _aaApply2() is C extern (D) typedef int delegate(void *, void *) dg2_t; -int _aaApply2(aaA*[] aa, int keysize, dg2_t dg) +int _aaApply2(AA aa, size_t keysize, dg2_t dg) +in +{ + assert(aligntsize(keysize) == keysize); +} +body { int result; - //printf("_aaApply(aa = x%llx, keysize = %d, dg = x%llx)\n", aa, keysize, dg); + //printf("_aaApply(aa = x%llx, keysize = %d, dg = x%llx)\n", aa.a, keysize, dg); int treewalker(aaA* e) { int result; @@ -673,7 +718,12 @@ if (result) break; if (e.right) - { result = treewalker(e.right); + { if (!e.left) + { + e = e.right; + continue; + } + result = treewalker(e.right); if (result) break; } @@ -683,13 +733,16 @@ return result; } - for (uint i = 1; i < aa.length; i++) + if (aa.a) { - if (aa[i]) + foreach (e; aa.a.b) { - result = treewalker(aa[i]); - if (result) - break; + if (e) + { + result = treewalker(e); + if (result) + break; + } } } return result; diff -uNr gdc-0.17/d/phobos/internal/adi.d gdc-0.18/d/phobos/internal/adi.d --- gdc-0.17/d/phobos/internal/adi.d 2005-05-29 23:09:19.000000000 +0200 +++ gdc-0.18/d/phobos/internal/adi.d 2006-05-14 04:21:51.000000000 +0200 @@ -1,6 +1,6 @@ //_ adi.d /* - * Copyright (C) 2000-2005 by Digital Mars, www.digitalmars.com + * Copyright (C) 2000-2006 by Digital Mars, www.digitalmars.com * Written by Walter Bright * * This software is provided 'as-is', without any express or implied @@ -35,14 +35,15 @@ import std.stdio; import std.c.stdio; import std.c.stdlib; +import std.c.string; import std.string; import std.outofmemory; struct Array { - int length; - void *ptr; + size_t length; + void* ptr; } /********************************************** @@ -60,8 +61,8 @@ char* hi = &a[length - 1]; while (lo < hi) - { char clo = *lo; - char chi = *hi; + { auto clo = *lo; + auto chi = *hi; //printf("lo = %d, hi = %d\n", lo, hi); if (clo <= 0x7F && chi <= 0x7F) @@ -151,8 +152,8 @@ wchar* hi = &a[length - 1]; while (lo < hi) - { wchar clo = *lo; - wchar chi = *hi; + { auto clo = *lo; + auto chi = *hi; if ((clo < 0xD800 || clo > 0xDFFF) && (chi < 0xD800 || chi > 0xDFFF)) @@ -382,7 +383,7 @@ { if (a.length >= 2) { - byte *tmp; + byte* tmp; byte[16] buffer; void* lo = a.ptr; @@ -568,9 +569,8 @@ body { Array r; - int size; - size = a.length * szelem; + auto size = a.length * szelem; r.ptr = cast(void *) new byte[size]; r.length = a.length; memcpy(r.ptr, a.ptr, size); @@ -605,9 +605,8 @@ body { Array r; - int size; - size = (a.length + 31) / 32; + auto size = (a.length + 31) / 32; r.ptr = cast(void *) new uint[size]; r.length = a.length; memcpy(r.ptr, a.ptr, size * uint.sizeof); @@ -642,10 +641,10 @@ //printf("a1.length = %d, a2.length = %d\n", a1.length, a2.length); if (a1.length != a2.length) return 0; // not equal - int sz = ti.tsize(); + auto sz = ti.tsize(); //printf("sz = %d\n", sz); - void *p1 = a1.ptr; - void *p2 = a2.ptr; + auto p1 = a1.ptr; + auto p2 = a2.ptr; /+ for (int i = 0; i < a1.length; i++) @@ -654,7 +653,11 @@ } +/ - for (int i = 0; i < a1.length; i++) + if (sz == 1) + // We should really have a ti.isPOD() check for this + return (memcmp(p1, p2, a1.length) == 0); + + for (size_t i = 0; i < a1.length; i++) { if (!ti.equals(p1 + i * sz, p2 + i * sz)) return 0; // not equal @@ -684,9 +687,9 @@ if (a1.length != a2.length) return 0; // not equal - ubyte *p1 = cast(ubyte*)a1.ptr; - ubyte *p2 = cast(ubyte*)a2.ptr; - uint n = a1.length / 8; + auto p1 = cast(ubyte*)a1.ptr; + auto p2 = cast(ubyte*)a2.ptr; + auto n = a1.length / 8; for (i = 0; i < n; i++) { if (p1[i] != p2[i]) @@ -723,24 +726,32 @@ extern (C) int _adCmp(Array a1, Array a2, TypeInfo ti) { - int len; - //printf("adCmp()\n"); - len = a1.length; + auto len = a1.length; if (a2.length < len) len = a2.length; - int sz = ti.tsize(); + auto sz = ti.tsize(); void *p1 = a1.ptr; void *p2 = a2.ptr; - for (int i = 0; i < len; i++) - { - int c; - c = ti.compare(p1 + i * sz, p2 + i * sz); + if (sz == 1) + { // We should really have a ti.isPOD() check for this + auto c = memcmp(p1, p2, len); if (c) return c; } - return cast(int)a1.length - cast(int)a2.length; + else + { + for (size_t i = 0; i < len; i++) + { + auto c = ti.compare(p1 + i * sz, p2 + i * sz); + if (c) + return c; + } + } + if (a1.length == a2.length) + return 0; + return (a1.length > a2.length) ? 1 : -1; } unittest diff -uNr gdc-0.17/d/phobos/internal/arraycast.d gdc-0.18/d/phobos/internal/arraycast.d --- gdc-0.17/d/phobos/internal/arraycast.d 2005-04-28 23:12:43.000000000 +0200 +++ gdc-0.18/d/phobos/internal/arraycast.d 2006-04-16 17:13:30.000000000 +0200 @@ -87,6 +87,8 @@ unittest { + version (D_Bits) + { bit[int.sizeof * 3 * 8] b; int[] i; short[] s; @@ -96,6 +98,7 @@ s = cast(short[])b; assert(s.length == 6); + } } diff -uNr gdc-0.17/d/phobos/internal/arraycat.d gdc-0.18/d/phobos/internal/arraycat.d --- gdc-0.17/d/phobos/internal/arraycat.d 2005-05-29 23:09:19.000000000 +0200 +++ gdc-0.18/d/phobos/internal/arraycat.d 2006-05-14 03:05:56.000000000 +0200 @@ -21,37 +21,40 @@ * distribution. */ +module arraycat; import object; import std.string; +import std.c.string; import std.c.stdio; +import std.c.stdarg; extern (C): byte[] _d_arraycatn(uint size, uint n, ...) { byte[] a; uint length; - byte[]* p; uint i; byte[] b; + va_list va; - p = cast(byte[]*)(&n + 1); + va_start!(typeof(n))(va, n); for (i = 0; i < n; i++) { - b = *p++; + b = va_arg!(typeof(b))(va); length += b.length; } if (!length) return null; a = new byte[length * size]; - p = cast(byte[]*)(&n + 1); + va_start!(typeof(n))(va, n); uint j = 0; for (i = 0; i < n; i++) { - b = *p++; + b = va_arg!(typeof(b))(va); if (b.length) { memcpy(&a[j], b, b.length * size); @@ -96,7 +99,9 @@ if (to.length != from.length) { - throw new Error("lengths don't match for array copy"); + //throw new Error(std.string.format("lengths don't match for array copy, %s = %s", to.length, from.length)); + throw new Error("lengths don't match for array copy," ~ + toString(to.length) ~ " = " ~ toString(from.length)); } else if (cast(byte *)to + to.length * size <= cast(byte *)from || cast(byte *)from + from.length * size <= cast(byte *)to) diff -uNr gdc-0.17/d/phobos/internal/critical.c gdc-0.18/d/phobos/internal/critical.c --- gdc-0.17/d/phobos/internal/critical.c 2005-04-28 23:12:43.000000000 +0200 +++ gdc-0.18/d/phobos/internal/critical.c 2005-12-10 03:31:59.000000000 +0100 @@ -129,7 +129,11 @@ { dcs->next = dcs_list; dcs_list = dcs; +#ifndef PTHREAD_MUTEX_ALREADY_RECURSIVE pthread_mutex_init(&dcs->cs, & _criticals_attr); +#else + pthread_mutex_init(&dcs->cs, NULL); +#endif } pthread_mutex_unlock(&critical_section.cs); } @@ -146,8 +150,10 @@ { if (!dcs_list) { //printf("_STI_critical_init()\n"); +#ifndef PTHREAD_MUTEX_ALREADY_RECURSIVE pthread_mutexattr_init(&_criticals_attr); pthread_mutexattr_settype(&_criticals_attr, PTHREAD_MUTEX_RECURSIVE); +#endif // The global critical section doesn't need to be recursive pthread_mutex_init(&critical_section.cs, 0); diff -uNr gdc-0.17/d/phobos/internal/dgccmain2.d gdc-0.18/d/phobos/internal/dgccmain2.d --- gdc-0.17/d/phobos/internal/dgccmain2.d 2005-09-09 23:27:05.000000000 +0200 +++ gdc-0.18/d/phobos/internal/dgccmain2.d 2006-05-13 21:05:42.000000000 +0200 @@ -6,7 +6,7 @@ import object; import std.c.stdio; import std.c.stdlib; -import std.string; +import std.c.string; version (GNU) { private import gcc.config; @@ -24,6 +24,8 @@ extern (C) void _moduleDtor(); extern (C) void _moduleUnitTests(); +extern (C) bool no_catch_exceptions = false; + /*********************************** * The D main() function supplied by the user's program */ @@ -57,15 +59,15 @@ version (GC_Use_Stack_Guess) stackOriginGuess = &argv; + version (GNU_CBridge_Stdio) + _d_gnu_cbridge_init_stdio(); // Win32: original didn't do this -- what about Gcc? _STI_monitor_staticctor(); _STI_critical_init(); gc_init(); - version (GNU_CBridge_Stdio) - _d_gnu_cbridge_init_stdio(); am = cast(char[] *) malloc(argc * (char[]).sizeof); - try + void go() { _moduleCtor(); _moduleUnitTests(); @@ -82,11 +84,19 @@ _moduleDtor(); gc_term(); } - catch (Object o) + + if (no_catch_exceptions) + go(); + else { - printf("Error: "); - o.print(); - exit(EXIT_FAILURE); + try + go(); + catch (Object o) + { + printf("Error: "); + o.print(); + exit(EXIT_FAILURE); + } } free(am); diff -uNr gdc-0.17/d/phobos/internal/dmain2.d gdc-0.18/d/phobos/internal/dmain2.d --- gdc-0.17/d/phobos/internal/dmain2.d 2005-04-28 23:12:43.000000000 +0200 +++ gdc-0.18/d/phobos/internal/dmain2.d 2006-05-13 21:05:42.000000000 +0200 @@ -6,6 +6,7 @@ import object; import std.c.stdio; +import std.c.string; import std.c.stdlib; import std.string; @@ -20,6 +21,8 @@ extern (C) void _moduleDtor(); extern (C) void _moduleUnitTests(); +extern (C) bool no_catch_exceptions = false; + /*********************************** * The D main() function supplied by the user's program */ @@ -56,7 +59,7 @@ am = cast(char[] *) alloca(argc * (char[]).sizeof); } - try + if (no_catch_exceptions) { _moduleCtor(); _moduleUnitTests(); @@ -73,11 +76,31 @@ _moduleDtor(); gc_term(); } - catch (Object o) + else { - printf("Error: "); - o.print(); - exit(EXIT_FAILURE); + try + { + _moduleCtor(); + _moduleUnitTests(); + + for (i = 0; i < argc; i++) + { + int len = strlen(argv[i]); + am[i] = argv[i][0 .. len]; + } + + args = am[0 .. argc]; + + result = main(args); + _moduleDtor(); + gc_term(); + } + catch (Object o) + { + printf("Error: "); + o.print(); + exit(EXIT_FAILURE); + } } version (linux) diff -uNr gdc-0.17/d/phobos/internal/fpmath.d gdc-0.18/d/phobos/internal/fpmath.d --- gdc-0.17/d/phobos/internal/fpmath.d 1970-01-01 01:00:00.000000000 +0100 +++ gdc-0.18/d/phobos/internal/fpmath.d 2005-12-26 04:37:38.000000000 +0100 @@ -0,0 +1,172 @@ +module gcc.fpmath; + +enum +{ + FP_NAN = 1, + FP_INFINITE, + FP_ZERO, + FP_SUBNORMAL, + FP_NORMAL, +} + +enum RealFormat +{ + SameAsDouble, + DoubleDouble, + Intel80, +} + +struct Info { + static if (real.sizeof == double.sizeof) { + static const RealFormat realFormat = RealFormat.SameAsDouble; + } else version (PPC) { + static const RealFormat realFormat = RealFormat.DoubleDouble; + union real_rec { + real f; + struct { double hd, ld; } + } + } else version (X86) { + static const RealFormat realFormat = RealFormat.Intel80; + union real_rec { + real f; + struct { uint li, mi, hi; } + } + } else { + static assert(0); + } +} + +union float_rec { + float f; + uint i; +} + +int signbit(float f) +{ + float_rec r = void; + r.f = f; + return r.i & 0x80000000; +} + +int fpclassify(float f) +{ + float_rec r = void; + r.f = f; + uint i = r.i & 0x7fffffff; + + if (! i) + return FP_ZERO; + else if (i < 0x00800000) + return FP_SUBNORMAL; + else if (i < 0x7f800000) + return FP_NORMAL; + else if (i < 0x7f800001) + return FP_INFINITE; + else + return FP_NAN; +} + +union double_rec { + double f; + struct { + version (BigEndian) + uint hi, li; + else + uint li, hi; + } +} + +int signbit(double f) +{ + double_rec r = void; + r.f = f; + return r.hi & 0x80000000; +} + +int fpclassify(double f) +{ + double_rec r = void; + r.f = f; + uint i = r.hi & 0x7fffffff; + + if (! (i | r.li)) + return FP_ZERO; + else if (i < 0x00100000) + return FP_SUBNORMAL; + else if (i < 0x7ff00000) + return FP_NORMAL; + else if (i == 0x7ff00000 && ! r.li) + return FP_INFINITE; + else + return FP_NAN; +} + +int signbit(real f) +{ + static if (Info.realFormat == RealFormat.SameAsDouble) { + return signbit(cast(double) f); + } else static if (Info.realFormat == RealFormat.DoubleDouble) { + Info.real_rec r = void; + r.f = f; + return signbit(r.hd); + } else static if (Info.realFormat == RealFormat.Intel80) { + Info.real_rec r = void; + r.f = f; + return r.hi & 0x00008000; + } +} + +int fpclassify(real f) +{ + static if (Info.realFormat == RealFormat.SameAsDouble) { + return fpclassify(cast(double) f); + } else static if (Info.realFormat == RealFormat.DoubleDouble) { + Info.real_rec r = void; + r.f = f; + return fpclassify(r.hd); + } else static if (Info.realFormat == RealFormat.Intel80) { + Info.real_rec r = void; + r.f = f; + uint i = r.hi & 0x00007fff; + uint li = r.li | (r.mi & 0x7fffffff) ; + if (! i && ! li) + return FP_ZERO; + else if (i < 0x00000001 && (r.mi & 0x80000000) == 0) + return FP_SUBNORMAL; + else if (i < 0x00007fff) + return FP_NORMAL; + else if (i == 0x00007fff && ! li) + return FP_INFINITE; + else + return FP_NAN; + } +} + +unittest +{ + static if (Info.realFormat == RealFormat.SameAsDouble) { + const real xrsn = 0x1p-1050; + } else static if (Info.realFormat == RealFormat.DoubleDouble) { + const real xrsn = 0x1p-1050; + } else static if (Info.realFormat == RealFormat.Intel80) { + const real xrsn = 0x1p-16390; + } + + static float[] xfi = [ float.nan, -float.nan, float.infinity, -float.infinity, + 0.0f, -0.0f, 0x1p-135f, -0x1p-135f, 4.2f, -4.2f ]; + static double[] xdi = [ double.nan, -double.nan, double.infinity, -double.infinity, + 0.0, -0.0, 0x1p-1050, -0x1p-1050, 4.2, -4.2 ]; + static real[] xri = [ real.nan, -real.nan, real.infinity, -real.infinity, + 0.0L, -0.0L, xrsn, -xrsn, 4.2L, -4.2L ]; + static int[] xo = [ FP_NAN, FP_NAN, FP_INFINITE, FP_INFINITE, + FP_ZERO, FP_ZERO, FP_SUBNORMAL, FP_SUBNORMAL, FP_NORMAL, FP_NORMAL]; + + foreach (int i, int cls; xo) { + assert( fpclassify(xfi[i]) == xo[i] ); + assert( fpclassify(xdi[i]) == xo[i] ); + assert( fpclassify(xri[i]) == xo[i] ); + assert( ( signbit(xfi[i]) ?1:0 ) == (i & 1) ); + assert( ( signbit(xdi[i]) ?1:0 ) == (i & 1) ); + assert( ( signbit(xri[i]) ?1:0 ) == (i & 1) ); + } +} diff -uNr gdc-0.17/d/phobos/internal/gc/gcbits.d gdc-0.18/d/phobos/internal/gc/gcbits.d --- gdc-0.17/d/phobos/internal/gc/gcbits.d 2004-10-26 02:41:27.000000000 +0200 +++ gdc-0.18/d/phobos/internal/gc/gcbits.d 2006-05-13 21:05:42.000000000 +0200 @@ -10,7 +10,7 @@ Modified by David Friedman, September 2004 */ -import std.string; +import std.c.string; import std.c.stdlib; import std.outofmemory; import std.intrinsic; @@ -66,8 +66,8 @@ } body { - return (cast(bit *)(data + 1))[i]; - //return data[1 + (i >> BITS_SHIFT)] & (1 << (i & BITS_MASK)); + //return (cast(bit *)(data + 1))[i]; + return data[1 + (i >> BITS_SHIFT)] & (1 << (i & BITS_MASK)); } void set(uint i) @@ -77,8 +77,8 @@ } body { - (cast(bit *)(data + 1))[i] = 1; - //data[1 + (i >> BITS_SHIFT)] |= (1 << (i & BITS_MASK)); + //(cast(bit *)(data + 1))[i] = 1; + data[1 + (i >> BITS_SHIFT)] |= (1 << (i & BITS_MASK)); } void clear(uint i) @@ -88,8 +88,8 @@ } body { - (cast(bit *)(data + 1))[i] = 0; - //data[1 + (i >> BITS_SHIFT)] &= ~(1 << (i & BITS_MASK)); + //(cast(bit *)(data + 1))[i] = 0; + data[1 + (i >> BITS_SHIFT)] &= ~(1 << (i & BITS_MASK)); } uint testClear(uint i) @@ -113,13 +113,13 @@ else { uint result; - result = (cast(bit *)(data + 1))[i]; - (cast(bit *)(data + 1))[i] = 0; + //result = (cast(bit *)(data + 1))[i]; + //(cast(bit *)(data + 1))[i] = 0; - //uint *p = &data[1 + (i >> BITS_SHIFT)]; - //uint mask = (1 << (i & BITS_MASK)); - //result = *p & mask; - //*p &= ~mask; + uint *p = &data[1 + (i >> BITS_SHIFT)]; + uint mask = (1 << (i & BITS_MASK)); + result = *p & mask; + *p &= ~mask; return result; } } diff -uNr gdc-0.17/d/phobos/internal/gc/gc.d gdc-0.18/d/phobos/internal/gc/gc.d --- gdc-0.17/d/phobos/internal/gc/gc.d 2005-11-27 16:59:45.000000000 +0100 +++ gdc-0.18/d/phobos/internal/gc/gc.d 2006-05-14 04:21:51.000000000 +0200 @@ -1,6 +1,6 @@ /* - * Copyright (C) 2004 by Digital Mars, www.digitalmars.com + * Copyright (C) 2004-2005 by Digital Mars, www.digitalmars.com * Written by Walter Bright * * This software is provided 'as-is', without any express or implied @@ -40,7 +40,7 @@ import std.c.stdarg; import std.c.stdlib; -import std.string; +import std.c.string; import gcx; import std.outofmemory; import gcstats; @@ -203,7 +203,7 @@ } } -Array _d_new(uint length, uint size) +Array _d_new(size_t length, size_t size) { void *p; Array result; @@ -242,49 +242,7 @@ } +/ -Array _d_newarrayi(uint length, uint size, ...) -{ - void *p; - Array result; - - //debug(PRINTF) printf("_d_newarrayi(length = %d, size = %d)\n", length, size); - /* - if (length == 0 || size == 0) - result = 0; - else - */ - if (length && size) - { - //void* q = cast(void*)(&size + 1); // pointer to initializer - va_list q; - va_start!(uint)(q, size); // q is pointer to ... initializer - version (BigEndian) - { - switch(size) { - case 1: q = cast(va_list)( cast(byte*)q + 3 ); break; - case 2: q = cast(va_list)( cast(byte*)q + 2 ); break; - default: - ; - } - } - p = _gc.malloc(length * size + 1); - debug(PRINTF) printf(" p = %p\n", p); - if (size == 1) - memset(p, *cast(ubyte*)q, length); - else - { - for (uint u = 0; u < length; u++) - { - memcpy(p + u * size, q, size); - } - } - result.length = length; - result.data = cast(byte*)p; - } - return result; -} - -Array _d_newarrayip(uint length, uint size, void * init) +Array _d_newarrayip(size_t length, size_t size, void * init) { Array result; @@ -308,7 +266,7 @@ } -Array _d_newbitarray(uint length, bit value) +Array _d_newbitarray(size_t length, bit value) { void *p; Array result; @@ -320,7 +278,7 @@ else */ if (length) - { uint size = ((length + 31) >> 5) * 4 + 1; // number of bytes + { size_t size = ((length + 31) >> 5) * 4 + 1; // number of bytes // (not sure what the extra byte is for...) ubyte fill = value ? 0xFF : 0; @@ -335,7 +293,7 @@ struct Array { - uint length; + size_t length; byte *data; }; @@ -414,10 +372,15 @@ */ extern (C) -byte[] _d_arraysetlength(uint newlength, uint sizeelem, Array *p) +byte[] _d_arraysetlength(size_t newlength, size_t sizeelem, Array *p) +in +{ + assert(sizeelem); + assert(!p.length || p.data); +} +body { byte* newdata; - uint newsize; debug(PRINTF) { @@ -426,18 +389,44 @@ printf("\tp.data = %p, p.length = %d\n", p.data, p.length); } - assert(sizeelem); - assert(!p.length || p.data); if (newlength) { - newsize = sizeelem * newlength; - if (p.length) - { uint size = p.length * sizeelem; + version (GNU) + { + static char x = 0; + if (x) + goto Loverflow; + } + + version (D_InlineAsm_X86) + { + size_t newsize = void; + + asm + { + mov EAX,newlength ; + mul EAX,sizeelem ; + mov newsize,EAX ; + jc Loverflow ; + } + } + else + { + size_t newsize = sizeelem * newlength; + if (newsize / newlength != sizeelem) + goto Loverflow; + } + //printf("newsize = %x, newlength = %x\n", newsize, newlength); + + if (p.length) + { newdata = p.data; - if (newsize > size) + if (newlength > p.length) { - uint cap = _gc.capacity(p.data); + size_t size = p.length * sizeelem; + size_t cap = _gc.capacity(p.data); + if (cap <= newsize) { newdata = cast(byte *)_gc.malloc(newsize + 1); @@ -459,6 +448,9 @@ p.data = newdata; p.length = newlength; return newdata[0 .. newlength]; + +Loverflow: + _d_OutOfMemory(); } /*************************** @@ -466,10 +458,10 @@ */ extern (C) -bit[] _d_arraysetlengthb(uint newlength, Array *p) +bit[] _d_arraysetlengthb(size_t newlength, Array *p) { byte* newdata; - uint newsize; + size_t newsize; debug (PRINTF) printf("p = %p, newlength = %d\n", p, newlength); @@ -479,12 +471,12 @@ { newsize = ((newlength + 31) >> 5) * 4; // # bytes rounded up to uint if (p.length) - { uint size = ((p.length + 31) >> 5) * 4; + { size_t size = ((p.length + 31) >> 5) * 4; newdata = p.data; if (newsize > size) { - uint cap = _gc.capacity(p.data); + size_t cap = _gc.capacity(p.data); if (cap <= newsize) { newdata = cast(byte *)_gc.malloc(newsize + 1); @@ -514,16 +506,15 @@ */ extern (C) -Array _d_arrayappend(Array *px, byte[] y, uint size) +Array _d_arrayappend(Array *px, byte[] y, size_t size) { - uint cap = _gc.capacity(px.data); - uint length = px.length; - uint newlength = length + y.length; + size_t cap = _gc.capacity(px.data); + size_t length = px.length; + size_t newlength = length + y.length; if (newlength * size > cap) { byte* newdata; - //newdata = cast(byte *)_gc.malloc(newlength * size); newdata = cast(byte *)_gc.malloc(newCapacity(newlength, size) + 1); memcpy(newdata, px.data, length * size); px.data = newdata; @@ -537,10 +528,10 @@ Array _d_arrayappendb(Array *px, bit[] y) { - uint cap = _gc.capacity(px.data); - uint length = px.length; - uint newlength = length + y.length; - uint newsize = (newlength + 7) / 8; + size_t cap = _gc.capacity(px.data); + size_t length = px.length; + size_t newlength = length + y.length; + size_t newsize = (newlength + 7) / 8; if (newsize > cap) { void* newdata; @@ -565,16 +556,16 @@ } -uint newCapacity(uint newlength, uint size) +size_t newCapacity(size_t newlength, size_t size) { version(none) { - uint newcap = newlength * size; + size_t newcap = newlength * size; } else { /* - * Better version by davejf: + * Better version by Dave Fladebo: * This uses an inverse logorithmic algorithm to pre-allocate a bit more * space for larger arrays. * - Arrays smaller than 4096 bytes are left as-is, so for the most @@ -591,8 +582,8 @@ * - Perhaps most importantly, overall memory usage and stress on the GC * is decreased significantly for demanding environments. */ - uint newcap = newlength * size; - uint newext = 0; + size_t newcap = newlength * size; + size_t newext = 0; if (newcap > 4096) { @@ -600,22 +591,29 @@ // Redo above line using only integer math - int log2plus1(uint c) + static int log2plus1(size_t c) { int i; - if (c == 0) - i = -1; - else - for (i = 1; c >>= 1; i++) - { } - return i; + if (c == 0) + i = -1; + else + for (i = 1; c >>= 1; i++) + { } + return i; } - long mult = 100 + (1000L * size) / (6 * log2plus1(newcap)); + /* The following setting for mult sets how much bigger + * the new size will be over what is actually needed. + * 100 means the same size, more means proportionally more. + * More means faster but more memory consumption. + */ + //long mult = 100 + (1000L * size) / (6 * log2plus1(newcap)); + long mult = 100 + (1000L * size) / log2plus1(newcap); + // testing shows 1.02 for large arrays is about the point of diminishing return if (mult < 102) mult = 102; - newext = cast(uint)((newcap * mult) / 100); + newext = cast(size_t)((newcap * mult) / 100); newext -= newext % size; //printf("mult: %2.2f, mult2: %2.2f, alloc: %2.2f\n",mult/100.0,mult2,newext / cast(double)size); } @@ -626,7 +624,7 @@ } extern (C) -byte[] _d_arrayappendc(inout byte[] x, in uint size, ...) +byte[] _d_arrayappendcp(inout byte[] x, in size_t size, void *argp) { size_t cap = _gc.capacity(x); size_t length = x.length; @@ -646,40 +644,26 @@ memcpy(newdata, x, length * size); (cast(void **)(&x))[1] = newdata; } - byte *argp = cast(byte *)(&size + 1); *cast(size_t *)&x = newlength; - version (LittleEndian) { - (cast(byte *)x)[length * size .. newlength * size] = argp[0 .. size]; - } else { - switch (size) { - case 1: - (cast(byte*)x)[length] = *(argp+3); - break; - case 2: - (cast(short*)x)[length] = *cast(short*)(argp+2); - break; - default: - (cast(byte *)x)[length * size .. newlength * size] = argp[0 .. size]; - } - } - assert((cast(uint)x.ptr & 15) == 0); + (cast(byte *)x)[length * size .. newlength * size] = (cast(byte*)argp)[0 .. size]; + assert((cast(size_t)x.ptr & 15) == 0); assert(_gc.capacity(x.ptr) > x.length * size); return x; } extern (C) -byte[] _d_arraycat(byte[] x, byte[] y, uint size) +byte[] _d_arraycat(byte[] x, byte[] y, size_t size) out (result) { //printf("_d_arraycat(%d,%p ~ %d,%p size = %d => %d,%p)\n", x.length, x.ptr, y.length, y.ptr, size, result.length, result.ptr); assert(result.length == x.length + y.length); - for (uint i = 0; i < x.length * size; i++) + for (size_t i = 0; i < x.length * size; i++) assert((cast(byte*)result)[i] == (cast(byte*)x)[i]); - for (uint i = 0; i < y.length * size; i++) + for (size_t i = 0; i < y.length * size; i++) assert((cast(byte*)result)[x.length * size + i] == (cast(byte*)y)[i]); - uint cap = _gc.capacity(result.ptr); + size_t cap = _gc.capacity(result.ptr); assert(!cap || cap > result.length * size); } body diff -uNr gdc-0.17/d/phobos/internal/gc/gcgcc.d gdc-0.18/d/phobos/internal/gc/gcgcc.d --- gdc-0.17/d/phobos/internal/gc/gcgcc.d 2005-08-12 04:32:44.000000000 +0200 +++ gdc-0.18/d/phobos/internal/gc/gcgcc.d 2005-12-10 03:31:59.000000000 +0100 @@ -31,7 +31,48 @@ { return munmap(base, nbytes); } +} +else version (GC_Use_Alloc_Valloc) +{ + extern (C) void * valloc(size_t); + void *os_mem_map(uint nbytes) { return valloc(nbytes); } + int os_mem_commit(void *base, uint offset, uint nbytes) { return 0; } + int os_mem_decommit(void *base, uint offset, uint nbytes) { return 0; } + int os_mem_unmap(void *base, uint nbytes) { free(base); return 0; } +} +else version (GC_Use_Alloc_Malloc) +{ + /* Assumes malloc granularity is at least (void *).sizeof. If + (req_size + PAGESIZE) is allocated, and the pointer is rounded + up to PAGESIZE alignment, there will be space for a void* at the + end after PAGESIZE bytes used by the GC. */ + private import gcx; // for PAGESIZE + + const uint PAGE_MASK = PAGESIZE - 1; + + void *os_mem_map(uint nbytes) + { byte * p, q; + p = cast(byte *) malloc(nbytes + PAGESIZE); + q = p + ((PAGESIZE - ((cast(size_t) p & PAGE_MASK))) & PAGE_MASK); + * cast(void**)(q + nbytes) = p; + return q; + } + int os_mem_commit(void *base, uint offset, uint nbytes) + { + return 0; + } + + int os_mem_decommit(void *base, uint offset, uint nbytes) + { + return 0; + } + + int os_mem_unmap(void *base, uint nbytes) + { + free( * cast(void**)( cast(byte*) base + nbytes ) ); + return 0; + } } else version (GC_Use_Alloc_Fixed_Heap) { diff -uNr gdc-0.17/d/phobos/internal/gc/gcgccextern.d gdc-0.18/d/phobos/internal/gc/gcgccextern.d --- gdc-0.17/d/phobos/internal/gc/gcgccextern.d 2005-05-29 23:09:19.000000000 +0200 +++ gdc-0.18/d/phobos/internal/gc/gcgccextern.d 2005-12-10 03:31:59.000000000 +0100 @@ -53,6 +53,12 @@ */ enum FM { One = 1, MinMax = 0, Two = 0 } } + else version (skyos) + { + alias _data_start__ Data_Start; + alias _bss_end__ Data_End; + enum FM { One = 1, MinMax = 0, Two = 0 } + } } enum DataSegmentTracking { diff -uNr gdc-0.17/d/phobos/internal/gc/gcx.d gdc-0.18/d/phobos/internal/gc/gcx.d --- gdc-0.17/d/phobos/internal/gc/gcx.d 2005-08-12 04:32:44.000000000 +0200 +++ gdc-0.18/d/phobos/internal/gc/gcx.d 2006-05-18 02:05:55.000000000 +0200 @@ -1,5 +1,5 @@ // -// Copyright (C) 2001-2004 by Digital Mars +// Copyright (C) 2001-2006 by Digital Mars // All Rights Reserved // Written by Walter Bright // www.digitalmars.com @@ -60,8 +60,8 @@ import gclinux; } -version (BigEndian) - private import std.intrinsic; +/*version (BigEndian) + private import std.intrinsic;*/ @@ -239,7 +239,8 @@ if (std.thread.Thread.nthreads == 1) { - /* The reason this works is because none of the gc code + /* Single-threaded no-sync - Dave Fladebo. + * The reason this works is because none of the gc code * can start up a new thread from within mallocNoSync(). * Skip the sync for speed reasons. */ @@ -264,7 +265,17 @@ size += SENTINEL_EXTRA; // Compute size bin - bin = gcx.findBin(size); + // Cache previous binsize lookup - Dave Fladebo. + static size_t lastsize = -1; + static Bins lastbin; + if (size == lastsize) + bin = lastbin; + else + { + bin = gcx.findBin(size); + lastsize = size; + lastbin = bin; + } if (bin < B_PAGE) { @@ -302,7 +313,11 @@ // Return next item from free list gcx.bucket[bin] = (cast(List *)p).next; - memset(p + size, 0, binsize[bin] - size); + version(GNU) + memset(p + size, 0, binsize[bin] - size); + else + // 'inline' memset - Dave Fladebo. + foreach(inout byte b; cast(byte[])(p + size)[0..binsize[bin] - size]) { b = 0; } //debug(PRINTF) printf("\tmalloc => %x\n", p); debug (MEMSTOMP) memset(p, 0xF0, size); } @@ -1570,8 +1585,9 @@ *b = 0; o = pool.baseAddr + (b - bbase) * 32 * 16; - version (BigEndian) + /* version (BigEndian) bitm = bswap(bitm); + */ if (!(bitm & 0xFFFF)) { bitm >>= 16; @@ -2091,7 +2107,10 @@ int opCmp(Pool *p2) { - return baseAddr - p2.baseAddr; + if (baseAddr < p2.baseAddr) + return -1; + else + return baseAddr > p2.baseAddr; } } diff -uNr gdc-0.17/d/phobos/internal/gc/linux.mak gdc-0.18/d/phobos/internal/gc/linux.mak --- gdc-0.17/d/phobos/internal/gc/linux.mak 2004-12-19 18:51:04.000000000 +0100 +++ gdc-0.18/d/phobos/internal/gc/linux.mak 2006-05-14 01:38:32.000000000 +0200 @@ -34,10 +34,10 @@ $(DMD) -c $(DFLAGS) gc.d gcx.o : gcx.d - $(DMD) -c $(DFLAGS) gcx.d + $(DMD) -c $(DFLAGS) gcx.d gcbits.d -gcbits.o : gcbits.d - $(DMD) -c $(DFLAGS) gcbits.d +#gcbits.o : gcbits.d +# $(DMD) -c $(DFLAGS) gcbits.d gclinux.o : gclinux.d $(DMD) -c $(DFLAGS) gclinux.d diff -uNr gdc-0.17/d/phobos/internal/gc/testgc.d gdc-0.18/d/phobos/internal/gc/testgc.d --- gdc-0.17/d/phobos/internal/gc/testgc.d 2005-04-28 23:12:43.000000000 +0200 +++ gdc-0.18/d/phobos/internal/gc/testgc.d 2006-05-14 01:38:32.000000000 +0200 @@ -299,9 +299,179 @@ /* ---------------------------- */ +void test2() +{ + char[] str; + + for (int i = 0; i < 10_000; i++) + str = str ~ "ABCDEFGHIJKLMNOPQRST"; +} + +/* ---------------------------- */ + +/* The Great Computer Language Shootout + http://shootout.alioth.debian.org/ + + http://www.bagley.org/~doug/shootout/ + + converted to D by Dave Fladebo + compile: dmd -O -inline -release hash.d +*/ + + +void test3() +{ + int n = 1000; + + char[32] str; + int[char[]] X; + + for(int i = 1; i <= n; i++) { + int len = sprintf(str,"%x",i); + X[str[0..len].dup] = i; + } + + int c; + for(int i = n; i > 0; i--) { + int len = sprintf(str,"%d",i); + if(str[0..len] in X) c++; + } + + printf("%d\n", c); +} + +/* ---------------------------- */ + +void test4() +{ + const int iters = 1_000_000; + C[] c = new C[iters]; + int i; + for(i = 0; i < iters; i++) + { + c[i] = new C; + delete c[i]; + } + printf("%d\n", i); +} + +class C +{ + int i, j, k; + real l, m, n; +} + +/* ---------------------------- */ + +/* The Computer Language Shootout Benchmarks + http://shootout.alioth.debian.org/ + + contributed by Dave Fladebo + compile: dmd -O -inline -release binarytrees.d +*/ + + +int test5() +{ + TreeNode* stretchTree, longLivedTree, tempTree; + int depth, minDepth, maxDepth, stretchDepth, N = 1; + + minDepth = 4; + maxDepth = (minDepth + 2) > N ? minDepth + 2 : N; + stretchDepth = maxDepth + 1; + + stretchTree = TreeNode.BottomUpTree(0, stretchDepth); + printf("stretch tree of depth %d\t check: %d\n", stretchDepth, stretchTree.ItemCheck); + //TreeNode.DeleteTree(stretchTree); + + longLivedTree = TreeNode.BottomUpTree(0, maxDepth); + + for(depth = minDepth; depth <= maxDepth; depth += 2) + { + int check, iterations = 1 << (maxDepth - depth + minDepth); + + for(int i = 0; i < iterations; i++) + { + tempTree = TreeNode.BottomUpTree(i, depth); + check += tempTree.ItemCheck; + //TreeNode.DeleteTree(tempTree); + + tempTree = TreeNode.BottomUpTree(-i, depth); + check += tempTree.ItemCheck; + //TreeNode.DeleteTree(tempTree); + } + + //printf(iterations * 2,"\t trees of depth ",depth,"\t check: ",check); + } + + //writefln("long lived tree of depth ",maxDepth,"\t check: ",longLivedTree.ItemCheck); + + return 0; +} + +struct TreeNode +{ +public: + static TreeNode* BottomUpTree(int item, int depth) + { + if(depth > 0) + return TreeNode(item + ,BottomUpTree(2 * item - 1, depth - 1) + ,BottomUpTree(2 * item, depth - 1)); + return TreeNode(item); + } + + int ItemCheck() + { + if(left) + return item + left.ItemCheck() - right.ItemCheck(); + return item; + } + + static void DeleteTree(TreeNode* tree) + { + if(tree.left) + { + DeleteTree(tree.left); + DeleteTree(tree.right); + } + + delete tree; + } + +private: + TreeNode* left, right; + int item; + + static TreeNode* opCall(int item, TreeNode* left = null, TreeNode* right = null) + { + TreeNode* t = new TreeNode; + t.left = left; + t.right = right; + t.item = item; + return t; + } + + //new(uint sz) + //{ + // return std.c.stdlib.malloc(sz); + //} + + //delete(void* p) + //{ + // free(p); + //} +} + +/* ---------------------------- */ + int main(char[][] args) { test1(); + test2(); + test3(); + test4(); + test5(); gc_t gc; diff -uNr gdc-0.17/d/phobos/internal/gc/win32.mak gdc-0.18/d/phobos/internal/gc/win32.mak --- gdc-0.17/d/phobos/internal/gc/win32.mak 2004-10-26 02:41:27.000000000 +0200 +++ gdc-0.18/d/phobos/internal/gc/win32.mak 2006-05-14 01:38:32.000000000 +0200 @@ -5,8 +5,9 @@ DMD=\dmd\bin\dmd #DFLAGS=-unittest -g -release -DFLAGS=-release -O -inline -#DFLAGS=-release -inline -O +#DFLAGS=-inline -O +DFLAGS=-release -inline -O +#DFLAGS=-g CC=dmc CFLAGS=-g -mn -6 -r -Igc @@ -39,8 +40,13 @@ lib dmgc /c/noi +gc+gcx+gcbits+win32; gc.obj : gc.d -gcx.obj : gcx.d -gcbits.obj : gcbits.d + $(DMD) -c -release -inline -O $* + +gcx.obj : gcx.d gcbits.d + $(DMD) -c -release -inline -O gcx gcbits + +#gcbits.obj : gcbits.d + win32.obj : win32.d zip : $(SRC) diff -uNr gdc-0.17/d/phobos/internal/llmath.d gdc-0.18/d/phobos/internal/llmath.d --- gdc-0.17/d/phobos/internal/llmath.d 2005-04-28 23:12:43.000000000 +0200 +++ gdc-0.18/d/phobos/internal/llmath.d 2006-05-13 21:05:42.000000000 +0200 @@ -53,7 +53,7 @@ mov ECX,EDX ; mov EBX,EAX ; // [ECX,EBX] = [EDX,EAX] xor EAX,EAX ; - cwd ; // [EDX,EAX] = 0 + cdq ; // [EDX,EAX] = 0 even ; L4: cmp ESI,ECX ; // is [ECX,EBX] > [ESI,EDI]? ja L3 ; // yes @@ -221,6 +221,19 @@ } } +// Same as __U64_LDBL, but return result as double in [EDX,EAX] +ulong __ULLNGDBL() +{ + asm + { naked ; + call __U64_LDBL ; + sub ESP,8 ; + fstp double ptr [ESP] ; + pop EAX ; + pop EDX ; + ret ; + } +} // Convert double to ulong diff -uNr gdc-0.17/d/phobos/internal/monitor.c gdc-0.18/d/phobos/internal/monitor.c --- gdc-0.17/d/phobos/internal/monitor.c 2004-10-26 02:41:27.000000000 +0200 +++ gdc-0.18/d/phobos/internal/monitor.c 2005-12-10 03:31:59.000000000 +0100 @@ -114,8 +114,11 @@ void _STI_monitor_staticctor() { if (!inited) - { pthread_mutexattr_init(&_monitors_attr); + { +#ifndef PTHREAD_MUTEX_ALREADY_RECURSIVE + pthread_mutexattr_init(&_monitors_attr); pthread_mutexattr_settype(&_monitors_attr, PTHREAD_MUTEX_RECURSIVE); +#endif pthread_mutex_init(&_monitor_critsec, 0); // the global critical section doesn't need to be recursive inited = 1; } @@ -125,8 +128,10 @@ { if (inited) { inited = 0; +#ifndef PTHREAD_MUTEX_ALREADY_RECURSIVE pthread_mutex_destroy(&_monitor_critsec); pthread_mutexattr_destroy(&_monitors_attr); +#endif } } @@ -142,7 +147,11 @@ if (!h->monitor) // if, in the meantime, another thread didn't set it { h->monitor = (unsigned)cs; +#ifndef PTHREAD_MUTEX_ALREADY_RECURSIVE pthread_mutex_init(cs, & _monitors_attr); +#else + pthread_mutex_init(cs, NULL); +#endif cs = NULL; } pthread_mutex_unlock(&_monitor_critsec); diff -uNr gdc-0.17/d/phobos/internal/object.d gdc-0.18/d/phobos/internal/object.d --- gdc-0.17/d/phobos/internal/object.d 2005-10-13 03:06:51.000000000 +0200 +++ gdc-0.18/d/phobos/internal/object.d 2006-05-14 03:05:56.000000000 +0200 @@ -5,11 +5,11 @@ * * This module is implicitly imported. * Macros: - * WIKI = Object + * WIKI = Phobos/Object */ /* - * Copyright (C) 2004-2005 by Digital Mars, www.digitalmars.com + * Copyright (C) 2004-2006 by Digital Mars, www.digitalmars.com * Written by Walter Bright * * This software is provided 'as-is', without any express or implied @@ -49,7 +49,7 @@ } /// Standard boolean type. Implemented as a $(B bit) type. -alias bit bool; +alias bool bit; version (X86_64) { @@ -68,13 +68,17 @@ * analogous to C's ptrdiff_t. */ alias long ptrdiff_t; + + alias ulong hash_t; } else { alias uint size_t; alias int ptrdiff_t; + alias uint hash_t; } + /****************** * All D class objects inherit from Object. */ @@ -96,7 +100,7 @@ /** * Compute hash function for Object. */ - uint toHash() + hash_t toHash() { // BUG: this prevents a compacting GC from working, needs to be fixed return cast(uint)cast(void *)this; @@ -188,7 +192,7 @@ } /// Returns a hash of the instance of a type. - uint getHash(void *p) { return cast(uint)p; } + hash_t getHash(void *p) { return cast(uint)p; } /// Compares two instances for equality. int equals(void *p1, void *p2) { return p1 == p2; } @@ -216,7 +220,7 @@ class TypeInfo_Typedef : TypeInfo { char[] toString() { return name; } - uint getHash(void *p) { return base.getHash(p); } + hash_t getHash(void *p) { return base.getHash(p); } int equals(void *p1, void *p2) { return base.equals(p1, p2); } int compare(void *p1, void *p2) { return base.compare(p1, p2); } size_t tsize() { return base.tsize(); } @@ -234,7 +238,7 @@ { char[] toString() { return next.toString() ~ "*"; } - uint getHash(void *p) + hash_t getHash(void *p) { return cast(uint)*cast(void* *)p; } @@ -268,9 +272,9 @@ { char[] toString() { return next.toString() ~ "[]"; } - uint getHash(void *p) + hash_t getHash(void *p) { size_t sz = next.tsize(); - uint hash = 0; + hash_t hash = 0; void[] a = *cast(void[]*)p; for (size_t i = 0; i < a.length; i++) hash += next.getHash(a.ptr + i * sz); @@ -332,9 +336,9 @@ return next.toString() ~ "[" ~ std.string.toString(len) ~ "]"; } - uint getHash(void *p) + hash_t getHash(void *p) { size_t sz = next.tsize(); - uint hash = 0; + hash_t hash = 0; for (size_t i = 0; i < len; i++) hash += next.getHash(p + i * sz); return hash; @@ -451,7 +455,7 @@ { char[] toString() { return info.name; } - uint getHash(void *p) + hash_t getHash(void *p) { Object o = *cast(Object*)p; assert(o); @@ -499,8 +503,8 @@ { char[] toString() { return name; } - uint getHash(void *p) - { uint h; + hash_t getHash(void *p) + { hash_t h; assert(p); if (xtoHash) @@ -578,7 +582,7 @@ char[] name; size_t xsize; - uint function(void*) xtoHash; + hash_t function(void*) xtoHash; int function(void*,void*) xopEquals; int function(void*,void*) xopCmp; } @@ -629,3 +633,4 @@ } //extern (C) int nullext = 0; + diff -uNr gdc-0.17/d/phobos/internal/qsort.d gdc-0.18/d/phobos/internal/qsort.d --- gdc-0.17/d/phobos/internal/qsort.d 2005-04-28 23:12:43.000000000 +0200 +++ gdc-0.18/d/phobos/internal/qsort.d 1970-01-01 01:00:00.000000000 +0100 @@ -1,167 +0,0 @@ -/* - Portions of this file are: - Copyright Prototronics, 1987 - Totem Lake P.O. 8117 - Kirkland, Washington 98034 - (206) 820-1972 - Licensed to Digital Mars. - - June 11, 1987 from Ray Gardner's - Denver, Colorado) public domain version - - Use qsort2.d instead of this file if a redistributable version of - _adSort() is required. -*/ - -/* NOTE: This file has been patched from the original DMD distribution to - work with the GDC compiler. - - Modified by David Friedman, September 2004 -*/ - - -/* -** Sorts an array starting at base, of length nbr_elements, each -** element of size width_bytes, ordered via compare_function; which -** is called as (*comp_fp)(ptr_to_element1, ptr_to_element2) -** and returns < 0 if element1 < element2, 0 if element1 = element2, -** > 0 if element1 > element2. Most of the refinements are due to -** R. Sedgewick. See "Implementing Quicksort Programs", Comm. ACM, -** Oct. 1978, and Corrigendum, Comm. ACM, June 1979. -*/ - -//debug=qsort; // uncomment to turn on debugging printf's - -import std.c.stdio; -import std.c.stdlib; -import std.string; -import std.outofmemory; - -struct Array -{ - int length; - void *ptr; -} - - -private const int _maxspan = 7; // subarrays of _maxspan or fewer elements - // will be sorted by a simple insertion sort - -/* Adjust _maxspan according to relative cost of a swap and a compare. Reduce -_maxspan (not less than 1) if a swap is very expensive such as when you have -an array of large structures to be sorted, rather than an array of pointers to -structures. The default value is optimized for a high cost for compares. */ - - -extern (C) Array _adSort(Array a, TypeInfo ti) -{ - byte* base; - byte*[40] stack; // stack - byte** sp; // stack pointer - byte* i, j, limit; // scan and limit pointers - uint thresh; // size of _maxspan elements in bytes - uint width = ti.tsize(); - - base = cast(byte *)a.ptr; - thresh = _maxspan * width; // init threshold - sp = stack; // init stack pointer - limit = base + a.length * width; // pointer past end of array - while (1) // repeat until done then return - { - while (limit - base > thresh) // if more than _maxspan elements - { - //swap middle, base - ti.swap((cast(uint)(limit - base) >> 1) - - (((cast(uint)(limit - base) >> 1)) % width) + base, base); - - i = base + width; // i scans from left to right - j = limit - width; // j scans from right to left - - if (ti.compare(i, j) > 0) // Sedgewick's - ti.swap(i, j); // three-element sort - if (ti.compare(base, j) > 0) // sets things up - ti.swap(base, j); // so that - if (ti.compare(i, base) > 0) // *i <= *base <= *j - ti.swap(i, base); // *base is the pivot element - - while (1) - { - do // move i right until *i >= pivot - i += width; - while (ti.compare(i, base) < 0); - do // move j left until *j <= pivot - j -= width; - while (ti.compare(j, base) > 0); - if (i > j) // break loop if pointers crossed - break; - ti.swap(i, j); // else swap elements, keep scanning - } - ti.swap(base, j); // move pivot into correct place - if (j - base > limit - i) // if left subarray is larger... - { - sp[0] = base; // stack left subarray base - sp[1] = j; // and limit - base = i; // sort the right subarray - } - else // else right subarray is larger - { - sp[0] = i; // stack right subarray base - sp[1] = limit; // and limit - limit = j; // sort the left subarray - } - sp += 2; // increment stack pointer - assert(sp < cast(byte**)stack + stack.length); - } - - // Insertion sort on remaining subarray - i = base + width; - while (i < limit) - { - j = i; - while (j > base && ti.compare(j - width, j) > 0) - { - ti.swap(j - width, j); - j -= width; - } - i += width; - } - - if (sp > stack) // if any entries on stack... - { - sp -= 2; // pop the base and limit - base = sp[0]; - limit = sp[1]; - } - else // else stack empty, all done - return a; - } -} - - -unittest -{ - debug(qsort) printf("array.sort.unittest()\n"); - - int a[] = new int[10]; - - a[0] = 23; - a[1] = 1; - a[2] = 64; - a[3] = 5; - a[4] = 6; - a[5] = 5; - a[6] = 17; - a[7] = 3; - a[8] = 0; - a[9] = -1; - - a.sort; - - for (int i = 0; i < a.length - 1; i++) - { - //printf("i = %d", i); - //printf(" %d %d\n", a[i], a[i + 1]); - assert(a[i] <= a[i + 1]); - } -} - diff -uNr gdc-0.17/d/phobos/internal/qsortg.d gdc-0.18/d/phobos/internal/qsortg.d --- gdc-0.17/d/phobos/internal/qsortg.d 1970-01-01 01:00:00.000000000 +0100 +++ gdc-0.18/d/phobos/internal/qsortg.d 2006-04-26 05:23:05.000000000 +0200 @@ -0,0 +1,115 @@ + +struct Array +{ + int length; + void * ptr; +} + +extern (C) Array _adSort(Array a, TypeInfo ti) +{ + static const uint Qsort_Threshold = 7; + + struct StackEntry { + byte *l; + byte *r; + } + + size_t elem_size = ti.tsize(); + size_t qsort_limit = elem_size * Qsort_Threshold; + + static assert(ubyte.sizeof == 1); + static assert(ubyte.max == 255); + + StackEntry[size_t.sizeof * 8] stack; // log2( size_t.max ) + StackEntry * sp = stack; + byte* lbound = cast(byte *) a.ptr; + byte* rbound = cast(byte *) a.ptr + a.length * elem_size; + byte* li = void; + byte* ri = void; + + while (1) + { + if (rbound - lbound > qsort_limit) + { + ti.swap(lbound, + lbound + ( + ((rbound - lbound) >>> 1) - + (((rbound - lbound) >>> 1) % elem_size) + )); + + li = lbound + elem_size; + ri = rbound - elem_size; + + if (ti.compare(li, ri) > 0) + ti.swap(li, ri); + if (ti.compare(lbound, ri) > 0) + ti.swap(lbound, ri); + if (ti.compare(li, lbound) > 0) + ti.swap(li, lbound); + + while (1) + { + do + li += elem_size; + while (ti.compare(li, lbound) < 0); + do + ri -= elem_size; + while (ti.compare(ri, lbound) > 0); + if (li > ri) + break; + ti.swap(li, ri); + } + ti.swap(lbound, ri); + if (ri - lbound > rbound - li) + { + sp.l = lbound; + sp.r = ri; + lbound = li; + } + else + { + sp.l = li; + sp.r = rbound; + rbound = ri; + } + ++sp; + } else { + // Use insertion sort + for (ri = lbound, li = lbound + elem_size; + li < rbound; + ri = li, li += elem_size) + { + for ( ; ti.compare(ri, ri + elem_size) > 0; + ri -= elem_size) + { + ti.swap(ri, ri + elem_size); + if (ri == lbound) + break; + } + } + if (sp != stack) + { + --sp; + lbound = sp.l; + rbound = sp.r; + } + else + return a; + } + } +} + +unittest +{ + static void check(int[] a) { + for (uint i = 1; i < a.length; i++) + assert(a[i-1] <= a[i]); + } + + static int[] t1 = [ 4, 3, 19, 7, 6, 20, 11, 1, 2, 5 ]; + int[] a; + + a = t1; + a.sort; + check(a); +} diff -uNr gdc-0.17/d/phobos/internal/switch.d gdc-0.18/d/phobos/internal/switch.d --- gdc-0.17/d/phobos/internal/switch.d 2005-04-28 23:12:43.000000000 +0200 +++ gdc-0.18/d/phobos/internal/switch.d 2006-05-13 21:05:42.000000000 +0200 @@ -23,6 +23,7 @@ import std.c.stdio; +import std.c.string; import std.string; /****************************************************** diff -uNr gdc-0.17/d/phobos/internal/trace.d gdc-0.18/d/phobos/internal/trace.d --- gdc-0.17/d/phobos/internal/trace.d 2005-06-22 05:13:40.000000000 +0200 +++ gdc-0.18/d/phobos/internal/trace.d 2006-05-13 21:05:42.000000000 +0200 @@ -1,7 +1,7 @@ /* Trace dynamic profiler. * For use with the Digital Mars DMD compiler. - * Copyright (C) 1995-2005 by Digital Mars + * Copyright (C) 1995-2006 by Digital Mars * All Rights Reserved * Written by Walter Bright * www.digitalmars.com @@ -12,6 +12,7 @@ import std.stdio; import std.ctype; import std.string; +import std.c.string; import std.c.stdlib; extern (C): diff -uNr gdc-0.17/d/phobos/linux.mak gdc-0.18/d/phobos/linux.mak --- gdc-0.17/d/phobos/linux.mak 2005-11-28 05:17:52.000000000 +0100 +++ gdc-0.18/d/phobos/linux.mak 2006-05-14 04:21:51.000000000 +0200 @@ -57,19 +57,19 @@ process.o syserror.o \ socket.o socketstream.o stdarg.o stdio.o format.o \ perf.o openrj.o uni.o trace.o boxer.o \ - demangle.o \ + demangle.o cover.o bitarray.o \ ti_wchar.o ti_uint.o ti_short.o ti_ushort.o \ ti_byte.o ti_ubyte.o ti_long.o ti_ulong.o ti_ptr.o \ ti_float.o ti_double.o ti_real.o ti_delegate.o \ ti_creal.o ti_ireal.o ti_cfloat.o ti_ifloat.o \ ti_cdouble.o ti_idouble.o \ ti_Aa.o ti_AC.o ti_Ag.o ti_Aubyte.o ti_Aushort.o ti_Ashort.o \ - ti_C.o ti_int.o ti_char.o ti_dchar.o ti_Adchar.o ti_bit.o \ + ti_C.o ti_int.o ti_char.o ti_dchar.o ti_Adchar.o \ ti_Aint.o ti_Auint.o ti_Along.o ti_Aulong.o ti_Awchar.o \ ti_Afloat.o ti_Adouble.o ti_Areal.o \ ti_Acfloat.o ti_Acdouble.o ti_Acreal.o \ - ti_Abit.o ti_void.o \ - date.o dateparse.o llmath.o math2.o Czlib.o Dzlib.o zip.o recls.o + ti_void.o \ + date.o dateparse.o llmath.o math2.o Czlib.o Dzlib.o zip.o ZLIB_OBJS= etc/c/zlib/adler32.o etc/c/zlib/compress.o \ etc/c/zlib/crc32.o etc/c/zlib/gzio.o \ @@ -78,14 +78,6 @@ etc/c/zlib/inflate.o etc/c/zlib/infback.o \ etc/c/zlib/inftrees.o etc/c/zlib/inffast.o -RECLS_OBJS= etc/c/recls/recls_api.o \ - etc/c/recls/recls_fileinfo.o \ - etc/c/recls/recls_internal.o \ - etc/c/recls/recls_util.o \ - etc/c/recls/recls_api_unix.o \ - etc/c/recls/recls_fileinfo_unix.o \ - etc/c/recls/recls_util_unix.o - GC_OBJS= internal/gc/gc.o internal/gc/gcx.o \ internal/gc/gcbits.o internal/gc/gclinux.o @@ -97,20 +89,20 @@ std/outbuffer.d std/math2.d std/thread.d std/md5.d std/base64.d \ std/asserterror.d std/dateparse.d std/outofmemory.d std/mmfile.d \ std/intrinsic.d std/array.d std/switcherr.d std/syserror.d \ - std/regexp.d std/random.d std/stream.d std/process.d std/recls.d \ + std/regexp.d std/random.d std/stream.d std/process.d \ std/socket.d std/socketstream.d std/loader.d std/stdarg.d \ std/stdio.d std/format.d std/perf.d std/openrj.d std/uni.d \ - std/boxer.d std/cstream.d std/demangle.d + std/boxer.d std/cstream.d std/demangle.d std/cover.d std/bitarray.d SRC_STD_C= std/c/process.d std/c/stdlib.d std/c/time.d std/c/stdio.d \ - std/c/math.d std/c/stdarg.d std/c/stddef.d + std/c/math.d std/c/stdarg.d std/c/stddef.d std/c/fenv.d std/c/string.d SRC_TI= \ std/typeinfo/ti_wchar.d std/typeinfo/ti_uint.d \ std/typeinfo/ti_short.d std/typeinfo/ti_ushort.d \ std/typeinfo/ti_byte.d std/typeinfo/ti_ubyte.d \ std/typeinfo/ti_long.d std/typeinfo/ti_ulong.d \ - std/typeinfo/ti_ptr.d std/typeinfo/ti_bit.d \ + std/typeinfo/ti_ptr.d \ std/typeinfo/ti_float.d std/typeinfo/ti_double.d \ std/typeinfo/ti_real.d std/typeinfo/ti_delegate.d \ std/typeinfo/ti_creal.d std/typeinfo/ti_ireal.d \ @@ -127,7 +119,7 @@ std/typeinfo/ti_Areal.d \ std/typeinfo/ti_Acfloat.d std/typeinfo/ti_Acdouble.d \ std/typeinfo/ti_Acreal.d \ - std/typeinfo/ti_Abit.d std/typeinfo/ti_void.d \ + std/typeinfo/ti_void.d \ std/typeinfo/ti_Awchar.d std/typeinfo/ti_dchar.d SRC_INT= \ @@ -195,171 +187,14 @@ internal/gc/win32.mak \ internal/gc/linux.mak -SRC_STLSOFT= \ - etc/c/stlsoft/stlsoft_null_mutex.h \ - etc/c/stlsoft/unixstl_string_access.h \ - etc/c/stlsoft/unixstl.h \ - etc/c/stlsoft/winstl_tls_index.h \ - etc/c/stlsoft/unixstl_environment_variable.h \ - etc/c/stlsoft/unixstl_functionals.h \ - etc/c/stlsoft/unixstl_current_directory.h \ - etc/c/stlsoft/unixstl_limits.h \ - etc/c/stlsoft/unixstl_current_directory_scope.h \ - etc/c/stlsoft/unixstl_filesystem_traits.h \ - etc/c/stlsoft/unixstl_findfile_sequence.h \ - etc/c/stlsoft/unixstl_glob_sequence.h \ - etc/c/stlsoft/winstl.h \ - etc/c/stlsoft/winstl_atomic_functions.h \ - etc/c/stlsoft/stlsoft_cccap_gcc.h \ - etc/c/stlsoft/stlsoft_lock_scope.h \ - etc/c/stlsoft/unixstl_thread_mutex.h \ - etc/c/stlsoft/unixstl_spin_mutex.h \ - etc/c/stlsoft/unixstl_process_mutex.h \ - etc/c/stlsoft/stlsoft_null.h \ - etc/c/stlsoft/stlsoft_nulldef.h \ - etc/c/stlsoft/winstl_thread_mutex.h \ - etc/c/stlsoft/winstl_spin_mutex.h \ - etc/c/stlsoft/winstl_system_version.h \ - etc/c/stlsoft/winstl_findfile_sequence.h \ - etc/c/stlsoft/unixstl_readdir_sequence.h \ - etc/c/stlsoft/stlsoft.h \ - etc/c/stlsoft/stlsoft_static_initialisers.h \ - etc/c/stlsoft/stlsoft_iterator.h \ - etc/c/stlsoft/stlsoft_cccap_dmc.h \ - etc/c/stlsoft/winstl_filesystem_traits.h - -SRC_RECLS= \ - etc/c/recls/recls_compiler.h \ - etc/c/recls/recls_language.h \ - etc/c/recls/recls_unix.h \ - etc/c/recls/recls_retcodes.h \ - etc/c/recls/recls_assert.h \ - etc/c/recls/recls_platform.h \ - etc/c/recls/recls_win32.h \ - etc/c/recls/recls.h \ - etc/c/recls/recls_util.h \ - etc/c/recls/recls_compiler_dmc.h \ - etc/c/recls/recls_compiler_gcc.h \ - etc/c/recls/recls_platform_types.h \ - etc/c/recls/recls_internal.h \ - etc/c/recls/recls_debug.h \ - etc/c/recls/recls_fileinfo_win32.cpp \ - etc/c/recls/recls_api_unix.cpp \ - etc/c/recls/recls_api.cpp \ - etc/c/recls/recls_util_win32.cpp \ - etc/c/recls/recls_util_unix.cpp \ - etc/c/recls/recls_util.cpp \ - etc/c/recls/recls_internal.cpp \ - etc/c/recls/recls_fileinfo.cpp \ - etc/c/recls/recls_defs.h \ - etc/c/recls/recls_fileinfo_unix.cpp \ - etc/c/recls/recls_api_win32.cpp \ - etc/c/recls/win32.mak \ - etc/c/recls/linux.mak \ - etc/c/recls/recls.lib - -SRC_STLSOFT_NEW= \ - etc/c/stlsoft/winstl_file_path_buffer.h \ - etc/c/stlsoft/inetstl_connection.h \ - etc/c/stlsoft/inetstl_filesystem_traits.h \ - etc/c/stlsoft/inetstl_findfile_sequence.h \ - etc/c/stlsoft/inetstl_searchspec_sequence.h \ - etc/c/stlsoft/inetstl_session.h \ - etc/c/stlsoft/stlsoft.h \ - etc/c/stlsoft/stlsoft_allocator_base.h \ - etc/c/stlsoft/inetstl.h \ - etc/c/stlsoft/stlsoft_auto_buffer.h \ - etc/c/stlsoft/stlsoft_cccap_dmc.h \ - etc/c/stlsoft/stlsoft_cccap_gcc.h \ - etc/c/stlsoft/stlsoft_char_traits.h \ - etc/c/stlsoft/stlsoft_constraints.h \ - etc/c/stlsoft/stlsoft_exceptions.h \ - etc/c/stlsoft/stlsoft_iterator.h \ - etc/c/stlsoft/stlsoft_meta.h \ - etc/c/stlsoft/stlsoft_new_allocator.h \ - etc/c/stlsoft/stlsoft_any_caster.h \ - etc/c/stlsoft/stlsoft_nulldef.h \ - etc/c/stlsoft/stlsoft_sap_cast.h \ - etc/c/stlsoft/stlsoft_searchspec_sequence.h \ - etc/c/stlsoft/stlsoft_sign_traits.h \ - etc/c/stlsoft/stlsoft_simple_algorithms.h \ - etc/c/stlsoft/stlsoft_simple_string.h \ - etc/c/stlsoft/stlsoft_size_traits.h \ - etc/c/stlsoft/stlsoft_string_access.h \ - etc/c/stlsoft/stlsoft_string_tokeniser.h \ - etc/c/stlsoft/stlsoft_type_traits.h \ - etc/c/stlsoft/unixstl.h \ - etc/c/stlsoft/unixstl_filesystem_traits.h \ - etc/c/stlsoft/unixstl_file_path_buffer.h \ - etc/c/stlsoft/unixstl_glob_sequence.h \ - etc/c/stlsoft/unixstl_string_access.h \ - etc/c/stlsoft/unixstl_thread_mutex.h \ - etc/c/stlsoft/winstl.h \ - etc/c/stlsoft/winstl_atomic_functions.h \ - etc/c/stlsoft/winstl_char_conversions.h \ - etc/c/stlsoft/winstl_filesystem_traits.h \ - etc/c/stlsoft/winstl_spin_mutex.h \ - etc/c/stlsoft/winstl_findfile_sequence.h \ - etc/c/stlsoft/winstl_processheap_allocator.h \ - etc/c/stlsoft/winstl_system_version.h \ - etc/c/stlsoft/stlsoft_null.h - -SRC_RECLS_NEW= \ - etc/c/recls/recls_compiler_gcc.h \ - etc/c/recls/recls_retcodes.h \ - etc/c/recls/EntryFunctions.h \ - etc/c/recls/recls_platform_types.h \ - etc/c/recls/recls.h \ - etc/c/recls/recls_wininet_dl.h \ - etc/c/recls/ReclsFileSearch.h \ - etc/c/recls/ReclsFileSearchDirectoryNode_unix.cpp \ - etc/c/recls/ReclsFileSearchDirectoryNode_unix.h \ - etc/c/recls/ReclsFileSearchDirectoryNode_win32.cpp \ - etc/c/recls/ReclsFileSearchDirectoryNode_win32.h \ - etc/c/recls/recls_wininet_dl.cpp \ - etc/c/recls/ReclsFileSearch_unix.cpp \ - etc/c/recls/ReclsFileSearch_win32.cpp \ - etc/c/recls/recls_win32.h \ - etc/c/recls/ReclsFtpSearch.h \ - etc/c/recls/ReclsFtpSearchDirectoryNode_win32.cpp \ - etc/c/recls/ReclsFtpSearchDirectoryNode_win32.h \ - etc/c/recls/recls_util_win32.cpp \ - etc/c/recls/ReclsFtpSearch_win32.cpp \ - etc/c/recls/recls_util_unix.cpp \ - etc/c/recls/recls_api.cpp \ - etc/c/recls/recls_util.h \ - etc/c/recls/recls_api_unix.cpp \ - etc/c/recls/recls_api_win32.cpp \ - etc/c/recls/recls_util.cpp \ - etc/c/recls/recls_assert.h \ - etc/c/recls/recls_compiler.h \ - etc/c/recls/recls_compiler_dmc.h \ - etc/c/recls/recls_platform.h \ - etc/c/recls/recls_debug.h \ - etc/c/recls/recls_defs.h \ - etc/c/recls/recls_fileinfo.cpp \ - etc/c/recls/recls_fileinfo_unix.cpp \ - etc/c/recls/recls_fileinfo_win32.cpp \ - etc/c/recls/recls_unix.h \ - etc/c/recls/recls_ftp.h \ - etc/c/recls/recls_ftp_api_win32.cpp \ - etc/c/recls/recls_internal.cpp \ - etc/c/recls/recls_internal.h \ - etc/c/recls/recls_roots_win32.cpp \ - etc/c/recls/recls_language.h \ - etc/c/recls/recls_roots_unix.cpp \ - etc/c/recls/win32.mak \ - etc/c/recls/linux.mak - ALLSRCS = $(SRC) $(SRC_STD) $(SRC_STD_C) $(SRC_TI) $(SRC_INT) $(SRC_STD_WIN) \ $(SRC_STD_C_WIN) $(SRC_STD_C_LINUX) $(SRC_ETC) $(SRC_ETC_C) \ - $(SRC_ZLIB) $(SRC_GC) \ - $(SRC_RECLS) $(SRC_STLSOFT) + $(SRC_ZLIB) $(SRC_GC) #libphobos.a : $(OBJS) internal/gc/dmgc.a linux.mak -libphobos.a : $(OBJS) internal/gc/dmgc.a $(ZLIB_OBJS) $(RECLS_OBJS) linux.mak - ar -r $@ $(OBJS) $(ZLIB_OBJS) $(GC_OBJS) $(RECLS_OBJS) +libphobos.a : $(OBJS) internal/gc/dmgc.a $(ZLIB_OBJS) linux.mak + ar -r $@ $(OBJS) $(ZLIB_OBJS) $(GC_OBJS) ########################################################### @@ -369,12 +204,6 @@ # cd ../.. make -C ./internal/gc -f linux.mak dmgc.a -$(RECLS_OBJS): -# cd etc/c/recls -# make -f linux.mak -# cd ../../.. - make -C ./etc/c/recls -f linux.mak - $(ZLIB_OBJS): # cd etc/c/zlib # make -f linux.mak @@ -473,6 +302,9 @@ base64.o : std/base64.d $(DMD) -c $(DFLAGS) std/base64.d +bitarray.o : std/bitarray.d + $(DMD) -c $(DFLAGS) std/bitarray.d + boxer.o : std/boxer.d $(DMD) -c $(DFLAGS) std/boxer.d @@ -482,6 +314,9 @@ conv.o : std/conv.d $(DMD) -c $(DFLAGS) std/conv.d +cover.o : std/cover.d + $(DMD) -c $(DFLAGS) std/cover.d + cstream.o : std/cstream.d $(DMD) -c $(DFLAGS) std/cstream.d @@ -542,9 +377,6 @@ random.o : std/random.d $(DMD) -c $(DFLAGS) std/random.d -recls.o : std/recls.d - $(DMD) -c $(DFLAGS) std/recls.d - regexp.o : std/regexp.d $(DMD) -c $(DFLAGS) std/regexp.d diff -uNr gdc-0.17/d/phobos/Makefile.in gdc-0.18/d/phobos/Makefile.in --- gdc-0.17/d/phobos/Makefile.in 2005-11-28 05:17:52.000000000 +0100 +++ gdc-0.18/d/phobos/Makefile.in 2006-05-18 03:01:42.000000000 +0200 @@ -22,8 +22,7 @@ RANLIB = @RANLIB@ CFLAGS=@CFLAGS@ -OUR_CFLAGS=@DEFS@ -I $(srcdir)/etc/c/stlsoft -I . -I $(srcdir)/gcc - +OUR_CFLAGS=@DEFS@ -I . -I $(srcdir)/gcc D_GC_FLAGS=@D_GC_FLAGS@ # Because parts of Phobos are generated (and are in flux), we need @@ -34,9 +33,6 @@ DFLAGS=@DFLAGS@ $(D_GC_FLAGS) -nostdinc -D_ENABLE_RECLS=@D_ENABLE_RECLS@ -D_RECLS_OS=@D_RECLS_OS@ - D_GENERATE_FRAGMENTS=@D_GENERATE_FRAGMENTS@ D_FRAGMENT_SRCDIR=@D_FRAGMENT_SRCDIR@ @@ -55,12 +51,6 @@ LIBS=@LIBS@ CC=@CC@ GDC=@GDC@ -CXX=@CXX@ - -# For recls -CXXFLAGS=@CXXFLAGS@ -RECLS_CXXFLAGS=@RECLS_CXXFLAGS@ -OUR_CXXFLAGS=@DEFS@ -I $(srcdir)/etc/c/stlsoft srcdir=@srcdir@ VPATH = @srcdir@ @@ -77,18 +67,20 @@ gdc_include_dir=@gdc_include_dir@ +config_d_src=$(host_alias)/gcc/config.d +configunix_d_src=$(host_alias)/gcc/configunix.d + +D_PREREQ_SRCS=@D_PREREQ_SRCS@ + all: libgphobos.a %.o : %.c $(CC) -o $@ $(OUR_CFLAGS) $(CFLAGS) -c $< -%.o : %.cpp - $(CXX) -o $@ $(CXXFLAGS) $(OUR_CXXFLAGS) $(RECLS_CXXFLAGS) -c $< - -%.o : %.d $(host_alias)/gcc/config.d +%.o : %.d $(host_alias)/gcc/config.d $(D_PREREQ_SRCS) $(GDC) -o $@ $(DFLAGS) -I $(srcdir) -I $(srcdir)/internal/gc -I ./$(host_alias) -c $< -%.t.o : %.d $(host_alias)/gcc/config.d +%.t.o : %.d $(host_alias)/gcc/config.d $(D_PREREQ_SRCS) $(GDC) -o $@ $(DFLAGS) -fno-release -funittest -I $(srcdir) -I $(srcdir)/internal/gc -I ./$(host_alias) -c $< internal/gc/gcx.t.o: $(srcdir)/internal/gc/gcx.d @@ -96,9 +88,6 @@ %.t.o : %.o cp $< $@ -#%.o : $(host_alias)/%.d $(host_alias)/gcc/config.d -# $(GDC) -o $@ $(DFLAGS) -I $(srcdir) -I $(srcdir)/internal/gc -I ./$(host_alias) -c $< - Makefile: Makefile.in ./config.status @@ -116,13 +105,13 @@ TI=ti_AC.o ti_Aa.o ti_Adchar.o ti_Ag.o ti_Aint.o ti_Along.o ti_Ashort.o \ ti_Aubyte.o ti_Auint.o ti_Aulong.o ti_Aushort.o ti_Awchar.o ti_C.o \ - ti_bit.o ti_byte.o ti_cdouble.o ti_cfloat.o ti_char.o ti_creal.o \ + ti_byte.o ti_cdouble.o ti_cfloat.o ti_char.o ti_creal.o \ ti_dchar.o ti_delegate.o ti_double.o ti_float.o ti_idouble.o ti_ifloat.o \ ti_int.o ti_ireal.o ti_long.o ti_ptr.o ti_real.o ti_short.o ti_ubyte.o \ ti_uint.o ti_ulong.o ti_ushort.o ti_wchar.o \ ti_Afloat.o ti_Adouble.o ti_Areal.o \ ti_Acfloat.o ti_Acdouble.o ti_Acreal.o \ - ti_Abit.o ti_void.o + ti_void.o MAIN_OBJS=std/asserterror.o internal/switch.o gcstats.o \ internal/critical.o internal/object.o internal/monitor.o internal/arraycat.o internal/invariant.o \ @@ -131,14 +120,14 @@ internal/cast.o std/path.o std/string.o internal/memset.o std/math.o std/mmfile.o \ std/outbuffer.o std/ctype.o std/regexp.o std/random.o \ std/stream.o std/cstream.o std/switcherr.o std/array.o std/gc.o \ - internal/qsort.o std/thread.o internal/obj.o std/utf.o std/uri.o \ + internal/qsortg.o std/thread.o internal/obj.o std/utf.o std/uri.o \ crc32.o std/conv.o internal/arraycast.o errno.o \ std/process.o std/syserror.o \ std/socket.o std/socketstream.o std/c/stdarg.o std/stdio.o std/format.o \ - std/perf.o std/openrj.o std/uni.o std/boxer.o std/demangle.o \ + std/perf.o std/openrj.o std/uni.o std/boxer.o std/demangle.o std/bitarray.o \ $(subst ti_,std/typeinfo/ti_,$(TI)) \ std/date.o std/dateparse.o std/math2.o etc/c/zlib.o std/zlib.o std/zip.o \ - internal/dgccmain2.o internal/rundmain.o + internal/dgccmain2.o internal/rundmain.o std/stdarg.o # This should not be linked into a shared library. CMAIN_OBJS=internal/cmain.o @@ -150,19 +139,6 @@ etc/c/zlib/inflate.o etc/c/zlib/infback.o \ etc/c/zlib/inftrees.o etc/c/zlib/inffast.o -ifdef D_ENABLE_RECLS -RECLS_OBJS=etc/c/recls/recls_api.o \ - etc/c/recls/recls_fileinfo.o \ - etc/c/recls/recls_internal.o \ - etc/c/recls/recls_util.o \ - etc/c/recls/recls_api_$(D_RECLS_OS).o \ - etc/c/recls/recls_fileinfo_$(D_RECLS_OS).o \ - etc/c/recls/recls_util_$(D_RECLS_OS).o \ - std/recls.o -else -RECLS_OBJS= -endif - GC_OBJS= internal/gc/gc.o internal/gc/gcx.o \ internal/gc/gcbits.o GC_OBJS += @D_GC_MODULES@ @@ -198,10 +174,10 @@ gen_config1: config/gen_config1.o $(CC) -o $@ $^ -$(host_alias)/gcc/config.d: $(CONFIG_D_FRAGMENTS) stamp-tgtdir +$(config_d_src): $(CONFIG_D_FRAGMENTS) stamp-tgtdir cat $^ > $@ -gcc/config.o: $(host_alias)/gcc/config.d +gcc/config.o: $(config_d_src) $(GDC) -o $@ $(DFLAGS) -I $(srcdir) -I $(srcdir)/internal/gc -I ./$(host_alias) -c $< gcc/config.t.o: gcc/config.o cp gcc/config.o gcc/config.t.o @@ -223,18 +199,18 @@ frag-math: gen_math ./gen_math > $@ || rm -f $@ else -frag-gen: gen_config1 +frag-gen: $(D_FRAGMENT_SRCDIR)/$@ cp $(D_FRAGMENT_SRCDIR)/$@ $@ -frag-unix: gen_unix +frag-unix: $(D_FRAGMENT_SRCDIR)/$@ cp $(D_FRAGMENT_SRCDIR)/$@ $@ -frag-math: gen_math +frag-math: $(D_FRAGMENT_SRCDIR)/$@ cp $(D_FRAGMENT_SRCDIR)/$@ $@ endif -$(host_alias)/gcc/configunix.d: $(CONFIG_UNIX_FRAGMENTS) stamp-tgtdir +$(configunix_d_src): $(CONFIG_UNIX_FRAGMENTS) stamp-tgtdir cat $^ > $@ -gcc/configunix.o: $(host_alias)/gcc/configunix.d $(host_alias)/gcc/config.d +gcc/configunix.o: $(configunix_d_src) $(config_d_src) $(GDC) -o $@ $(DFLAGS) -I $(srcdir) -I $(srcdir)/internal/gc -I ./$(host_alias) -c $< gcc/configunix.t.o: gcc/configunix.o cp gcc/configunix.o gcc/configunix.t.o @@ -242,15 +218,15 @@ gcc/cbridge_math.o: gcc/cbridge_math.c $(CC) -o $@ $(OUR_CFLAGS) $(CFLAGS) -fno-strict-aliasing -c $< -std/stream.o: std/stream.d $(host_alias)/gcc/config.d +std/stream.o: std/stream.d $(D_PREREQ_SRCS) $(GDC) -o $@ $(DFLAGS) -fdeprecated -I $(srcdir) -I $(srcdir)/internal/gc -I ./$(host_alias) -c $< -std/stream.t.o: std/stream.d $(host_alias)/gcc/config.d +std/stream.t.o: std/stream.d $(D_PREREQ_SRCS) $(GDC) -o $@ $(DFLAGS) -fdeprecated -I $(srcdir) -I $(srcdir)/internal/gc -I ./$(host_alias) -c $< # GCC_OBJS (gcc/config.o) first so I don't have to write more deps -ALL_PHOBOS_OBJS = $(D_EXTRA_OBJS) $(GCC_OBJS) $(MAIN_OBJS) $(ZLIB_OBJS) $(GC_OBJS) $(RECLS_OBJS) $(WEAK_OBJS) +ALL_PHOBOS_OBJS = $(D_EXTRA_OBJS) $(GCC_OBJS) $(MAIN_OBJS) $(ZLIB_OBJS) $(GC_OBJS) $(WEAK_OBJS) libgphobos.a : $(ALL_PHOBOS_OBJS) $(CMAIN_OBJS) $(AR) -r $@ $(ALL_PHOBOS_OBJS) $(CMAIN_OBJS) @@ -280,10 +256,11 @@ # 3.3.x install-sh can't handle multiple source arguments # $(INSTALL_HEADER) $(srcdir)/$$i/*.[hd] $(DESTDIR)$(gdc_include_dir)/$$i; done -install: $(host_alias)/gcc/config.d libgphobos.a - for i in etc etc/c etc/c/recls etc/c/stlsoft etc/c/zlib \ +install: $(D_PREREQ_SRCS) libgphobos.a + for i in etc etc/c \ + etc/c/stlsoft etc/c/zlib \ gcc std std/c \ - std/c/darwin std/c/linux std/c/mach std/c/unix std/c/windows \ + std/c/darwin std/c/linux std/c/mach std/c/skyos std/c/unix std/c/windows \ std/typeinfo std/windows; do \ $(mkinstalldirs) $(DESTDIR)$(gdc_include_dir)/$$i; \ for f in $(srcdir)/$$i/*.[hd]; do $(INSTALL_HEADER) $$f $(DESTDIR)$(gdc_include_dir)/$$i; done; \ @@ -291,8 +268,8 @@ for i in crc32.d gcstats.d object.d; do \ $(INSTALL_HEADER) $(srcdir)/$$i $(DESTDIR)$(gdc_include_dir); done $(mkinstalldirs) $(DESTDIR)$(gdc_include_dir)/$(host_alias)/gcc - $(INSTALL_HEADER) $(host_alias)/gcc/config.d $(DESTDIR)$(gdc_include_dir)/$(host_alias)/gcc - if test -f $(host_alias)/gcc/configunix.d; then $(INSTALL_HEADER) $(host_alias)/gcc/configunix.d $(DESTDIR)$(gdc_include_dir)/$(host_alias)/gcc; fi + $(INSTALL_HEADER) $(config_d_src) $(DESTDIR)$(gdc_include_dir)/$(host_alias)/gcc + if test -f $(configunix_d_src); then $(INSTALL_HEADER) $(host_alias)/gcc/configunix.d $(DESTDIR)$(gdc_include_dir)/$(host_alias)/gcc; fi $(INSTALL) phobos-ver-syms $(DESTDIR)$(gdc_include_dir)/$(host_alias) $(mkinstalldirs) $(DESTDIR)$(toolexeclibdir) $(INSTALL) libgphobos.a $(DESTDIR)$(toolexeclibdir) @@ -307,6 +284,7 @@ rm -f unittest$(EXEEXT) testgc$(EXEEXT) rm -f config/gen_config1.o config/gen_unix.o config/gen_math.o rm -f gen_config1$(EXEEXT) gen_unix$(EXEEXT) gen_math$(EXEEXT) - rm -f frag-gen $(host_alias)/gcc/config.d $(host_alias)/gcc/configunix.d + rm -f frag-gen frag-math frag-unix + rm -f $(config_d_src) $(configunix_d_src) rm -f libgphobos.a rm -f libgphobos_t.a diff -uNr gdc-0.17/d/phobos/object.d gdc-0.18/d/phobos/object.d --- gdc-0.17/d/phobos/object.d 2005-10-26 03:33:56.000000000 +0200 +++ gdc-0.18/d/phobos/object.d 2006-05-14 03:05:56.000000000 +0200 @@ -3,10 +3,12 @@ module object; -alias bit bool; +//alias bit bool; +alias bool bit; alias typeof(int.sizeof) size_t; alias typeof(cast(void*)0 - cast(void*)0) ptrdiff_t; +alias size_t hash_t; extern (C) { int printf(char *, ...); @@ -44,7 +46,7 @@ class TypeInfo { - uint getHash(void *p); + hash_t getHash(void *p); int equals(void *p1, void *p2); int compare(void *p1, void *p2); size_t tsize(); diff -uNr gdc-0.17/d/phobos/phobos-ver-syms.in gdc-0.18/d/phobos/phobos-ver-syms.in --- gdc-0.17/d/phobos/phobos-ver-syms.in 2005-10-29 04:40:46.000000000 +0200 +++ gdc-0.18/d/phobos/phobos-ver-syms.in 2006-03-12 15:56:29.000000000 +0100 @@ -13,3 +13,5 @@ @DCFG_STRTOLD@ @DCFG_SA_LEN@ @DCFG_CBRIDGE_STDIO@ +@DCFG_MMAP@ +@DCFG_GETPWNAM_R@ diff -uNr gdc-0.17/d/phobos/std/asserterror.d gdc-0.18/d/phobos/std/asserterror.d --- gdc-0.17/d/phobos/std/asserterror.d 2004-10-26 02:41:27.000000000 +0200 +++ gdc-0.18/d/phobos/std/asserterror.d 2006-03-12 15:16:26.000000000 +0100 @@ -23,8 +23,6 @@ /* This code is careful to not use gc allocated memory, * as that may be the source of the problem. * Instead, stick with C functions. - * We'll never free the malloc'd memory, but that doesn't matter, - * as we're aborting anyway. */ len = 22 + filename.length + uint.sizeof * 3 + 1; @@ -42,6 +40,14 @@ super(buffer[0 .. count]); } } + + ~this() + { + if (msg.ptr) + { std.c.stdlib.free(msg.ptr); + msg = null; + } + } } diff -uNr gdc-0.17/d/phobos/std/base64.d gdc-0.18/d/phobos/std/base64.d --- gdc-0.17/d/phobos/std/base64.d 2005-10-13 03:06:51.000000000 +0200 +++ gdc-0.18/d/phobos/std/base64.d 2006-04-16 17:13:30.000000000 +0200 @@ -2,7 +2,7 @@ * Encodes/decodes MIME base64 data. * * Macros: - * WIKI=StdBase64 + * WIKI=Phobos/StdBase64 * References: * Wikipedia Base64$(BR) * RFC 2045$(BR) diff -uNr gdc-0.17/d/phobos/std/bitarray.d gdc-0.18/d/phobos/std/bitarray.d --- gdc-0.17/d/phobos/std/bitarray.d 1970-01-01 01:00:00.000000000 +0100 +++ gdc-0.18/d/phobos/std/bitarray.d 2006-05-13 21:05:42.000000000 +0200 @@ -0,0 +1,948 @@ +/*********************** + * Macros: + * WIKI = StdBitarray + */ + +module std.bitarray; + +//debug = bitarray; // uncomment to turn on debugging printf's + +private import std.intrinsic; + +/** + * An array of bits. + */ + +struct BitArray +{ + size_t len; + uint* ptr; + + size_t dim() + { + return (len + 31) / 32; + } + + size_t length() + { + return len; + } + + void length(size_t newlen) + { + if (newlen != len) + { + size_t olddim = dim(); + size_t newdim = (newlen + 31) / 32; + + if (newdim != olddim) + { + // Create a fake array so we can use D's realloc machinery + uint[] b = ptr[0 .. olddim]; + b.length = newdim; // realloc + ptr = b.ptr; + if (newdim & 31) + { // Set any pad bits to 0 + ptr[newdim - 1] &= ~(~0 << (newdim & 31)); + } + } + + len = newlen; + } + } + + /********************************************** + * Support for [$(I index)] operation for BitArray. + */ + bool opIndex(size_t i) + in + { + assert(i < len); + } + body + { + return cast(bool)bt(ptr, i); + } + + /** ditto */ + bool opIndexAssign(bool b, size_t i) + in + { + assert(i < len); + } + body + { + if (b) + bts(ptr, i); + else + btr(ptr, i); + return b; + } + + /********************************************** + * Support for array.dup property for BitArray. + */ + BitArray dup() + { + BitArray ba; + + uint[] b = ptr[0 .. dim].dup; + ba.len = len; + ba.ptr = b.ptr; + return ba; + } + + unittest + { + BitArray a; + BitArray b; + int i; + + debug(bitarray) printf("BitArray.dup.unittest\n"); + + a.length = 3; + a[0] = 1; a[1] = 0; a[2] = 1; + b = a.dup; + assert(b.length == 3); + for (i = 0; i < 3; i++) + { debug(bitarray) printf("b[%d] = %d\n", i, b[i]); + assert(b[i] == (((i ^ 1) & 1) ? true : false)); + } + } + + /********************************************** + * Support for foreach loops for BitArray. + */ + int opApply(int delegate(inout bool) dg) + { + int result; + + for (size_t i = 0; i < len; i++) + { bool b = opIndex(i); + result = dg(b); + (*this)[i] = b; + if (result) + break; + } + return result; + } + + /** ditto */ + int opApply(int delegate(inout size_t, inout bool) dg) + { + int result; + + for (size_t i = 0; i < len; i++) + { bool b = opIndex(i); + result = dg(i, b); + (*this)[i] = b; + if (result) + break; + } + return result; + } + + unittest + { + debug(bitarray) printf("BitArray.opApply unittest\n"); + + static bool[] ba = [1,0,1]; + + BitArray a; a.init(ba); + + int i; + foreach (b;a) + { + switch (i) + { case 0: assert(b == true); break; + case 1: assert(b == false); break; + case 2: assert(b == true); break; + } + i++; + } + + foreach (j,b;a) + { + switch (j) + { case 0: assert(b == true); break; + case 1: assert(b == false); break; + case 2: assert(b == true); break; + } + } + } + + + /********************************************** + * Support for array.reverse property for BitArray. + */ + + BitArray reverse() + out (result) + { + assert(result == *this); + } + body + { + if (len >= 2) + { + bool t; + size_t lo, hi; + + lo = 0; + hi = len - 1; + for (; lo < hi; lo++, hi--) + { + t = (*this)[lo]; + (*this)[lo] = (*this)[hi]; + (*this)[hi] = t; + } + } + return *this; + } + + unittest + { + debug(bitarray) printf("BitArray.reverse.unittest\n"); + + BitArray b; + static bool[5] data = [1,0,1,1,0]; + int i; + + b.init(data); + b.reverse; + for (i = 0; i < data.length; i++) + { + assert(b[i] == data[4 - i]); + } + } + + + /********************************************** + * Support for array.sort property for BitArray. + */ + + BitArray sort() + out (result) + { + assert(result == *this); + } + body + { + if (len >= 2) + { + size_t lo, hi; + + lo = 0; + hi = len - 1; + while (1) + { + while (1) + { + if (lo >= hi) + goto Ldone; + if ((*this)[lo] == true) + break; + lo++; + } + + while (1) + { + if (lo >= hi) + goto Ldone; + if ((*this)[hi] == false) + break; + hi--; + } + + (*this)[lo] = false; + (*this)[hi] = true; + + lo++; + hi--; + } + Ldone: + ; + } + return *this; + } + + unittest + { + debug(bitarray) printf("BitArray.sort.unittest\n"); + + static uint x = 0b1100011000; + static BitArray ba = { 10, &x }; + ba.sort; + for (size_t i = 0; i < 6; i++) + assert(ba[i] == false); + for (size_t i = 6; i < 10; i++) + assert(ba[i] == true); + } + + + /*************************************** + * Support for operators == and != for bit arrays. + */ + + int opEquals(BitArray a2) + { int i; + + if (this.length != a2.length) + return 0; // not equal + uint *p1 = cast(uint*)this.ptr; + uint *p2 = cast(uint*)a2.ptr; + uint n = this.length / (8 * uint.sizeof); + for (i = 0; i < n; i++) + { + if (p1[i] != p2[i]) + return 0; // not equal + } + + uint mask; + + n = this.length & ((8 * uint.sizeof) - 1); + mask = (1 << n) - 1; + //printf("i = %d, n = %d, mask = %x, %x, %x\n", i, n, mask, p1[i], p2[i]); + return (mask == 0) || (p1[i] & mask) == (p2[i] & mask); + } + + unittest + { + debug(bitarray) printf("BitArray.opEquals unittest\n"); + + static bool[] ba = [1,0,1,0,1]; + static bool[] bb = [1,0,1]; + static bool[] bc = [1,0,1,0,1,0,1]; + static bool[] bd = [1,0,1,1,1]; + static bool[] be = [1,0,1,0,1]; + + BitArray a; a.init(ba); + BitArray b; b.init(bb); + BitArray c; c.init(bc); + BitArray d; d.init(bd); + BitArray e; e.init(be); + + assert(a != b); + assert(a != c); + assert(a != d); + assert(a == e); + } + + /*************************************** + * Implement comparison operators. + */ + + int opCmp(BitArray a2) + { + uint len; + uint i; + + len = this.length; + if (a2.length < len) + len = a2.length; + uint* p1 = cast(uint*)this.ptr; + uint* p2 = cast(uint*)a2.ptr; + uint n = len / (8 * uint.sizeof); + for (i = 0; i < n; i++) + { + if (p1[i] != p2[i]) + break; // not equal + } + /* + for (uint j = i * 8; j < len; j++) + { ubyte mask = 1 << j; + int c; + + c = cast(int)(p1[i] & mask) - cast(int)(p2[i] & mask); + if (c) + return c; + } + */ + uint mask = 1; + for (uint j = i * (8 * uint.sizeof); j < len; j++) + { int c; + + c = cast(int)(p1[i] & mask) - cast(int)(p2[i] & mask); + if (c) + return c; + mask <<= 1; + } + return cast(int)this.len - cast(int)a2.length; + } + + unittest + { + debug(bitarray) printf("BitArray.opCmp unittest\n"); + + static bool[] ba = [1,0,1,0,1]; + static bool[] bb = [1,0,1]; + static bool[] bc = [1,0,1,0,1,0,1]; + static bool[] bd = [1,0,1,1,1]; + static bool[] be = [1,0,1,0,1]; + + BitArray a; a.init(ba); + BitArray b; b.init(bb); + BitArray c; c.init(bc); + BitArray d; d.init(bd); + BitArray e; e.init(be); + + assert(a > b); + assert(a >= b); + assert(a < c); + assert(a <= c); + assert(a < d); + assert(a <= d); + assert(a == e); + assert(a <= e); + assert(a >= e); + } + + /*************************************** + * Set BitArray to contents of ba[] + */ + + void init(bool[] ba) + { + length = ba.length; + foreach (i, b; ba) + { + (*this)[i] = b; + } + } + + + /*************************************** + * Map BitArray onto v[], with numbits being the number of bits + * in the array. Does not copy the data. + * + * This is the inverse of opCast. + */ + void init(void[] v, size_t numbits) + in + { + assert(numbits <= v.length * 8); + assert((v.length & 3) == 0); + } + body + { + ptr = cast(uint*)v.ptr; + len = numbits; + } + + unittest + { + debug(bitarray) printf("BitArray.init unittest\n"); + + static bool[] ba = [1,0,1,0,1]; + + BitArray a; a.init(ba); + BitArray b; + void[] v; + + v = cast(void[])a; + b.init(v, a.length); + + assert(b[0] == 1); + assert(b[1] == 0); + assert(b[2] == 1); + assert(b[3] == 0); + assert(b[4] == 1); + + a[0] = 0; + assert(b[0] == 0); + + assert(a == b); + } + + /*************************************** + * Convert to void[]. + */ + void[] opCast() + { + return cast(void[])ptr[0 .. dim]; + } + + unittest + { + debug(bitarray) printf("BitArray.opCast unittest\n"); + + static bool[] ba = [1,0,1,0,1]; + + BitArray a; a.init(ba); + void[] v = cast(void[])a; + + assert(v.length == a.dim * uint.sizeof); + } + + /*************************************** + * Support for unary operator ~ for bit arrays. + */ + BitArray opCom() + { + auto dim = this.dim(); + + BitArray result; + + result.length = len; + for (size_t i = 0; i < dim; i++) + result.ptr[i] = ~this.ptr[i]; + if (len & 31) + result.ptr[dim - 1] &= ~(~0 << (len & 31)); + return result; + } + + unittest + { + debug(bitarray) printf("BitArray.opCom unittest\n"); + + static bool[] ba = [1,0,1,0,1]; + + BitArray a; a.init(ba); + BitArray b = ~a; + + assert(b[0] == 0); + assert(b[1] == 1); + assert(b[2] == 0); + assert(b[3] == 1); + assert(b[4] == 0); + } + + + /*************************************** + * Support for binary operator & for bit arrays. + */ + BitArray opAnd(BitArray e2) + in + { + assert(len == e2.length); + } + body + { + auto dim = this.dim(); + + BitArray result; + + result.length = len; + for (size_t i = 0; i < dim; i++) + result.ptr[i] = this.ptr[i] & e2.ptr[i]; + return result; + } + + unittest + { + debug(bitarray) printf("BitArray.opAnd unittest\n"); + + static bool[] ba = [1,0,1,0,1]; + static bool[] bb = [1,0,1,1,0]; + + BitArray a; a.init(ba); + BitArray b; b.init(bb); + + BitArray c = a & b; + + assert(c[0] == 1); + assert(c[1] == 0); + assert(c[2] == 1); + assert(c[3] == 0); + assert(c[4] == 0); + } + + + /*************************************** + * Support for binary operator | for bit arrays. + */ + BitArray opOr(BitArray e2) + in + { + assert(len == e2.length); + } + body + { + auto dim = this.dim(); + + BitArray result; + + result.length = len; + for (size_t i = 0; i < dim; i++) + result.ptr[i] = this.ptr[i] | e2.ptr[i]; + return result; + } + + unittest + { + debug(bitarray) printf("BitArray.opOr unittest\n"); + + static bool[] ba = [1,0,1,0,1]; + static bool[] bb = [1,0,1,1,0]; + + BitArray a; a.init(ba); + BitArray b; b.init(bb); + + BitArray c = a | b; + + assert(c[0] == 1); + assert(c[1] == 0); + assert(c[2] == 1); + assert(c[3] == 1); + assert(c[4] == 1); + } + + + /*************************************** + * Support for binary operator ^ for bit arrays. + */ + BitArray opXor(BitArray e2) + in + { + assert(len == e2.length); + } + body + { + auto dim = this.dim(); + + BitArray result; + + result.length = len; + for (size_t i = 0; i < dim; i++) + result.ptr[i] = this.ptr[i] ^ e2.ptr[i]; + return result; + } + + unittest + { + debug(bitarray) printf("BitArray.opXor unittest\n"); + + static bool[] ba = [1,0,1,0,1]; + static bool[] bb = [1,0,1,1,0]; + + BitArray a; a.init(ba); + BitArray b; b.init(bb); + + BitArray c = a ^ b; + + assert(c[0] == 0); + assert(c[1] == 0); + assert(c[2] == 0); + assert(c[3] == 1); + assert(c[4] == 1); + } + + + /*************************************** + * Support for binary operator - for bit arrays. + * + * $(I a - b) for BitArrays means the same thing as $(I a & ~b). + */ + BitArray opSub(BitArray e2) + in + { + assert(len == e2.length); + } + body + { + auto dim = this.dim(); + + BitArray result; + + result.length = len; + for (size_t i = 0; i < dim; i++) + result.ptr[i] = this.ptr[i] & ~e2.ptr[i]; + return result; + } + + unittest + { + debug(bitarray) printf("BitArray.opSub unittest\n"); + + static bool[] ba = [1,0,1,0,1]; + static bool[] bb = [1,0,1,1,0]; + + BitArray a; a.init(ba); + BitArray b; b.init(bb); + + BitArray c = a - b; + + assert(c[0] == 0); + assert(c[1] == 0); + assert(c[2] == 0); + assert(c[3] == 0); + assert(c[4] == 1); + } + + + /*************************************** + * Support for operator &= bit arrays. + */ + BitArray opAndAssign(BitArray e2) + in + { + assert(len == e2.length); + } + body + { + auto dim = this.dim(); + + for (size_t i = 0; i < dim; i++) + ptr[i] &= e2.ptr[i]; + return *this; + } + + unittest + { + debug(bitarray) printf("BitArray.opAndAssign unittest\n"); + + static bool[] ba = [1,0,1,0,1]; + static bool[] bb = [1,0,1,1,0]; + + BitArray a; a.init(ba); + BitArray b; b.init(bb); + + a &= b; + assert(a[0] == 1); + assert(a[1] == 0); + assert(a[2] == 1); + assert(a[3] == 0); + assert(a[4] == 0); + } + + + /*************************************** + * Support for operator |= for bit arrays. + */ + BitArray opOrAssign(BitArray e2) + in + { + assert(len == e2.length); + } + body + { + auto dim = this.dim(); + + for (size_t i = 0; i < dim; i++) + ptr[i] |= e2.ptr[i]; + return *this; + } + + unittest + { + debug(bitarray) printf("BitArray.opOrAssign unittest\n"); + + static bool[] ba = [1,0,1,0,1]; + static bool[] bb = [1,0,1,1,0]; + + BitArray a; a.init(ba); + BitArray b; b.init(bb); + + a |= b; + assert(a[0] == 1); + assert(a[1] == 0); + assert(a[2] == 1); + assert(a[3] == 1); + assert(a[4] == 1); + } + + /*************************************** + * Support for operator ^= for bit arrays. + */ + BitArray opXorAssign(BitArray e2) + in + { + assert(len == e2.length); + } + body + { + auto dim = this.dim(); + + for (size_t i = 0; i < dim; i++) + ptr[i] ^= e2.ptr[i]; + return *this; + } + + unittest + { + debug(bitarray) printf("BitArray.opXorAssign unittest\n"); + + static bool[] ba = [1,0,1,0,1]; + static bool[] bb = [1,0,1,1,0]; + + BitArray a; a.init(ba); + BitArray b; b.init(bb); + + a ^= b; + assert(a[0] == 0); + assert(a[1] == 0); + assert(a[2] == 0); + assert(a[3] == 1); + assert(a[4] == 1); + } + + /*************************************** + * Support for operator -= for bit arrays. + * + * $(I a -= b) for BitArrays means the same thing as $(I a &= ~b). + */ + BitArray opSubAssign(BitArray e2) + in + { + assert(len == e2.length); + } + body + { + auto dim = this.dim(); + + for (size_t i = 0; i < dim; i++) + ptr[i] &= ~e2.ptr[i]; + return *this; + } + + unittest + { + debug(bitarray) printf("BitArray.opSubAssign unittest\n"); + + static bool[] ba = [1,0,1,0,1]; + static bool[] bb = [1,0,1,1,0]; + + BitArray a; a.init(ba); + BitArray b; b.init(bb); + + a -= b; + assert(a[0] == 0); + assert(a[1] == 0); + assert(a[2] == 0); + assert(a[3] == 0); + assert(a[4] == 1); + } + + /*************************************** + * Support for operator ~= for bit arrays. + */ + + BitArray opCatAssign(bool b) + { + length = len + 1; + (*this)[len - 1] = b; + return *this; + } + + unittest + { + debug(bitarray) printf("BitArray.opCatAssign unittest\n"); + + static bool[] ba = [1,0,1,0,1]; + + BitArray a; a.init(ba); + BitArray b; + + b = (a ~= true); + assert(a[0] == 1); + assert(a[1] == 0); + assert(a[2] == 1); + assert(a[3] == 0); + assert(a[4] == 1); + assert(a[5] == 1); + + assert(b == a); + } + + /*************************************** + * ditto + */ + + BitArray opCatAssign(BitArray b) + { + auto istart = len; + length = len + b.length; + for (auto i = istart; i < len; i++) + (*this)[i] = b[i - istart]; + return *this; + } + + unittest + { + debug(bitarray) printf("BitArray.opCatAssign unittest\n"); + + static bool[] ba = [1,0]; + static bool[] bb = [0,1,0]; + + BitArray a; a.init(ba); + BitArray b; b.init(bb); + BitArray c; + + c = (a ~= b); + assert(a.length == 5); + assert(a[0] == 1); + assert(a[1] == 0); + assert(a[2] == 0); + assert(a[3] == 1); + assert(a[4] == 0); + + assert(c == a); + } + + /*************************************** + * Support for binary operator ~ for bit arrays. + */ + BitArray opCat(bool b) + { + BitArray r; + + r = this.dup; + r.length = len + 1; + r[len] = b; + return r; + } + + /** ditto */ + BitArray opCat_r(bool b) + { + BitArray r; + + r.length = len + 1; + r[0] = b; + for (size_t i = 0; i < len; i++) + r[1 + i] = (*this)[i]; + return r; + } + + /** ditto */ + BitArray opCat(BitArray b) + { + BitArray r; + + r = this.dup(); + r ~= b; + return r; + } + + unittest + { + debug(bitarray) printf("BitArray.opCat unittest\n"); + + static bool[] ba = [1,0]; + static bool[] bb = [0,1,0]; + + BitArray a; a.init(ba); + BitArray b; b.init(bb); + BitArray c; + + c = (a ~ b); + assert(c.length == 5); + assert(c[0] == 1); + assert(c[1] == 0); + assert(c[2] == 0); + assert(c[3] == 1); + assert(c[4] == 0); + + c = (a ~ true); + assert(c.length == 3); + assert(c[0] == 1); + assert(c[1] == 0); + assert(c[2] == 1); + + c = (false ~ a); + assert(c.length == 3); + assert(c[0] == 0); + assert(c[1] == 1); + assert(c[2] == 0); + } +} diff -uNr gdc-0.17/d/phobos/std/boxer.d gdc-0.18/d/phobos/std/boxer.d --- gdc-0.17/d/phobos/std/boxer.d 2005-10-13 03:06:51.000000000 +0200 +++ gdc-0.18/d/phobos/std/boxer.d 2006-05-14 04:21:51.000000000 +0200 @@ -1,4 +1,62 @@ -/* This module is written by Burton Radons and placed into the public domain. */ +/** + * This module is a set of types and functions for converting any object (value + * or heap) into a generic box type, allowing the user to pass that object + * around without knowing what's in the box, and then allowing him to recover + * the value afterwards. + * + * Example: +--- +// Convert the integer 45 into a box. +Box b = box(45); + +// Recover the integer and cast it to real. +real r = unbox!(real)(b); +--- + * + * That is the basic interface and will usually be all that you need to + * understand. If it cannot unbox the object to the given type, it throws + * UnboxException. As demonstrated, it uses implicit casts to behave in the exact + * same way that static types behave. So for example, you can unbox from int to + * real, but you cannot unbox from real to int: that would require an explicit + * cast. + * + * This therefore means that attempting to unbox an int as a string will throw + * an error instead of formatting it. In general, you can call the toString method + * on the box and receive a good result, depending upon whether std.string.format + * accepts it. + * + * Boxes can be compared to one another and they can be used as keys for + * associative arrays. + * + * There are also functions for converting to and from arrays of boxes. + * + * Example: +--- +// Convert arguments into an array of boxes. +Box[] a = boxArray(1, 45.4, "foobar"); + +// Convert an array of boxes back into arguments. +TypeInfo[] arg_types; +void* arg_data; + +boxArrayToArguments(a, arg_types, arg_data); + +// Convert the arguments back into boxes using a +// different form of the function. +a = boxArray(arg_types, arg_data); +--- + * One use of this is to support a variadic function more easily and robustly; + * simply call "boxArray(_arguments, _argptr)", then do whatever you need to do + * with the array. + * + * Authors: + * Burton Radons + * License: + * Public Domain + * Macros: + * WIKI=Phobos/StdBoxer + */ + /* NOTE: This file has been patched from the original DMD distribution to work with the GDC compiler. @@ -15,7 +73,7 @@ version (GNU) private import std.stdarg; -/** These functions and types allow packing objects into generic containers + /* These functions and types allow packing objects into generic containers * and recovering them later. This comes into play in a wide spectrum of * utilities, such as with a scripting language, or as additional user data * for an object. @@ -59,12 +117,12 @@ * Finally, you can discover whether unboxing as a certain type is legal by * using the unboxable template or method: * - * bit unboxable!(T) (Box value); - * bit Box.unboxable(TypeInfo T); + * bool unboxable!(T) (Box value); + * bool Box.unboxable(TypeInfo T); */ /** Return the next type in an array typeinfo, or null if there is none. */ -private bit isArrayTypeInfo(TypeInfo type) +private bool isArrayTypeInfo(TypeInfo type) { char[] name = type.classinfo.name; return name.length >= 10 && name[9] == 'A' && name != "TypeInfo_AssociativeArray"; @@ -73,7 +131,8 @@ /** The type class returned from Box.findTypeClass; the order of entries is important. */ private enum TypeClass { - Bit, /**< bit */ + Bool, /**< bool */ + Bit = Bool, // for backwards compatibility Integer, /**< byte, ubyte, short, ushort, int, uint, long, ulong */ Float, /**< float, double, real */ Complex, /**< cfloat, cdouble, creal */ @@ -89,11 +148,14 @@ else version (GNU) version = DigitalMars_TypeInfo; -/** A box object contains a value in a generic fashion, allowing it to be - * passed from one place to another without having to know its type. It is - * created by calling the box function, and you can recover the value by - * instantiating the unbox template. - */ +/** + * Box is a generic container for objects (both value and heap), allowing the + * user to box them in a generic form and recover them later. + * A box object contains a value in a generic fashion, allowing it to be + * passed from one place to another without having to know its type. It is + * created by calling the box function, and you can recover the value by + * instantiating the unbox template. + */ struct Box { private TypeInfo p_type; /**< The type of the contained object. */ @@ -120,7 +182,8 @@ return TypeClass.Other; switch (type.classinfo.name[9]) { - case 'b': return TypeClass.Bit; + //case 'b': return TypeClass.Bit; + case 'x': return TypeClass.Bool; case 'g', 'h', 's', 't', 'i', 'k', 'l', 'm': return TypeClass.Integer; case 'f', 'd', 'e': return TypeClass.Float; case 'q', 'r', 'c': return TypeClass.Complex; @@ -133,7 +196,7 @@ /* Use the name returned from toString, which might (but hopefully doesn't) include an allocation. */ switch (type.toString) { - case "bit": return TypeClass.Bit; + case "bool": return TypeClass.Bool; case "byte", "ubyte", "short", "ushort", "int", "uint", "long", "ulong": return TypeClass.Integer; case "float", "real", "double": return TypeClass.Float; case "cfloat", "cdouble", "creal": return TypeClass.Complex; @@ -144,7 +207,7 @@ } /** Return whether this value could be unboxed as the given type without throwing. */ - bit unboxable(TypeInfo test) + bool unboxable(TypeInfo test) { if (type is test) return true; @@ -173,29 +236,40 @@ return (cast(TypeInfo_Pointer)type).next is (cast(TypeInfo_Pointer)test).next; if ((ta == tb && ta != TypeClass.Other) - || (ta == TypeClass.Bit && tb == TypeClass.Integer) + || (ta == TypeClass.Bool && tb == TypeClass.Integer) || (ta <= TypeClass.Integer && tb == TypeClass.Float) || (ta <= TypeClass.Imaginary && tb == TypeClass.Complex)) return true; return false; } - /** Return the type of the contained object. */ + /** + * Property for the type contained by the box. + * This is initially null and cannot be assigned directly. + * Returns: the type of the contained object. + */ TypeInfo type() { return p_type; } - /** Return the data array. */ + /** + * Property for the data pointer to the value of the box. + * This is initially null and cannot be assigned directly. + * Returns: the data array. + */ void[] data() { size_t size = type.tsize(); return size <= p_shortData.length ? p_shortData[0..size] : p_longData[0..size]; } - - /** Attempt to convert the object to a string by doing D formatting on it. - */ + + /** + * Attempt to convert the boxed value into a string using std.string.format; + * this will throw if that function cannot handle it. If the box is + * uninitialized then this returns "". + */ char[] toString() { if (type is null) @@ -228,7 +302,7 @@ return string; } - private bit opEqualsInternal(Box other, bit inverted) + private bool opEqualsInternal(Box other, bool inverted) { if (type != other.type) { @@ -259,16 +333,19 @@ assert (0); } - return cast(bit)type.equals(data, other.data); + return cast(bool)type.equals(data, other.data); } - - /** Implement the equals operator. */ - bit opEquals(Box other) + + /** + * Compare this box's value with another box. This implicitly casts if the + * types are different, identical to the regular type system. + */ + bool opEquals(Box other) { return opEqualsInternal(other, false); } - private float opCmpInternal(Box other, bit inverted) + private float opCmpInternal(Box other, bool inverted) { if (type != other.type) { @@ -313,20 +390,29 @@ return type.compare(data, other.data); } - - /** Implement the compare operator. */ + + /** + * Compare this box's value with another box. This implicitly casts if the + * types are different, identical to the regular type system. + */ float opCmp(Box other) { return opCmpInternal(other, false); } - - uint toHash() + + /** + * Return the value's hash. + */ + hash_t toHash() { return type.getHash(data); } } - -/** Create a box out of the first argument passed. */ + +/** + * Box the single argument passed to the function. If more or fewer than one + * argument is passed, this will assert. + */ Box box(...) in { @@ -355,7 +441,11 @@ return box(_arguments[0], _argptr); } -/** Assign the parameters, copying data as needed. */ +/** + * Box the explicitly-defined object. type must not be null; data must not be + * null if the type's size is greater than zero. + * The data is copied. + */ Box box(TypeInfo type, void* data) in { @@ -381,7 +471,9 @@ return (baseLength + int.sizeof - 1) & ~(int.sizeof - 1); } -/** Box each argument in the list. */ +/** + * Convert a list of arguments into a list of boxes. + */ Box[] boxArray(TypeInfo[] types, void* data) { Box[] array = new Box[types.length]; @@ -395,13 +487,17 @@ return array; } -/** Box each argument passed to the function, returning an array of boxes. */ + /** + * Box each argument passed to the function, returning an array of boxes. + */ Box[] boxArray(...) { return boxArray(_arguments, cast(void *) _argptr); } -/** Convert an array of boxes into an array of arguments. */ + /** + * Convert an array of boxes into an array of arguments. + */ void boxArrayToArguments(Box[] arguments, out TypeInfo[] types, out void* data) { size_t dataLength; @@ -423,16 +519,20 @@ } } -/** This is thrown if you try to unbox an incompatible type. */ +/** + * This class is thrown if unbox is unable to cast the value into the desired + * result. + */ class UnboxException : Exception { - /** The boxed object spawning the error. */ - Box object; - - /** The type that we tried to unbox as. */ - TypeInfo outputType; - - /** Assign parameters and the message. */ + Box object; /// This is the box that the user attempted to unbox. + + TypeInfo outputType; /// This is the type that the user attempted to unbox the value as. + + /** + * Assign parameters and create the message in the form + * "Could not unbox from type ... to ... ." + */ this(Box object, TypeInfo outputType) { this.object = object; @@ -473,8 +573,8 @@ return cast(T) *cast(long*) value.data; if (value.type is typeid(ulong)) return cast(T) *cast(ulong*) value.data; - if (value.type is typeid(bit)) - return cast(T) *cast(bit*) value.data; + if (value.type is typeid(bool)) + return cast(T) *cast(bool*) value.data; if (value.type is typeid(byte)) return cast(T) *cast(byte*) value.data; if (value.type is typeid(ubyte)) @@ -527,13 +627,28 @@ } } -/** This unbox template takes a template parameter and returns a function that - * takes a box object and returns the specified type. If it cannot cast to - * the type, it throws UnboxException. For example: - * - * Box y = box(4); - * int x = unbox!(int) (y); - */ +/** + * The unbox template takes a type parameter and returns a function that + * takes a box object and returns the specified type. + * + * To use it, instantiate the template with the desired result type, and then + * call the function with the box to convert. + * This will implicitly cast base types as necessary and in a way consistent + * with static types - for example, it will cast a boxed byte into int, but it + * won't cast a boxed float into short. + * + * Throws: UnboxException if it cannot cast + * + * Example: + * --- + * Box b = box(4.5); + * bit u = unboxable!(real)(b); // This is true. + * real r = unbox!(real)(b); + * + * Box y = box(4); + * int x = unbox!(int) (y); + * --- + */ template unbox(T) { T unbox(Box value) @@ -636,12 +751,13 @@ } } -/** Return whether the value can be unboxed to this type without throwing - * UnboxException. - */ +/** + * Return whether the value can be unboxed as the given type; if this returns + * false, attempting to do so will throw UnboxException. + */ template unboxable(T) { - bit unboxable(Box value) + bool unboxable(Box value) { return value.unboxable(typeid(T)); } @@ -653,7 +769,7 @@ T unboxTest(Box value) { T result; - bit unboxable = value.unboxable(typeid(T)); + bool unboxable = value.unboxable(typeid(T)); try result = unbox!(T) (value); catch (UnboxException error) @@ -680,7 +796,7 @@ Box a, b; /* Call the function, catch UnboxException, return that it threw correctly. */ - bit fails(void delegate()func) + bool fails(void delegate()func) { try func(); catch (UnboxException error) @@ -758,7 +874,7 @@ assert (box(4) > box(3.0)); assert (box(0+3i) < box(0+4i)); - /* Assert that casting from bit to int works. */ + /* Assert that casting from bool to int works. */ assert (1 == unboxTest!(int)(box(true))); assert (box(1) == box(true)); @@ -785,8 +901,8 @@ assert (unboxTest!(void*)(box(p))); // int[] assert (unboxTest!(void*)(box(new A))); // Object - /* Assert that we can't unbox an integer as bit. */ - assert (!unboxable!(bit) (box(4))); + /* Assert that we can't unbox an integer as bool. */ + assert (!unboxable!(bool) (box(4))); /* Assert that we can't unbox a struct as another struct. */ SA sa; diff -uNr gdc-0.17/d/phobos/std/c/darwin/ldblcompat.d gdc-0.18/d/phobos/std/c/darwin/ldblcompat.d --- gdc-0.17/d/phobos/std/c/darwin/ldblcompat.d 2005-10-02 16:17:55.000000000 +0200 +++ gdc-0.18/d/phobos/std/c/darwin/ldblcompat.d 2006-05-26 02:06:43.000000000 +0200 @@ -5,14 +5,17 @@ module std.c.darwin.ldblcompat; -version (GNU_WantLongDoubleFormat128) - version = GNU_UseLongDoubleFormat128; -else version (GNU_WantLongDoubleFormat64) - { } -else +version (PPC) { - version (GNU_LongDouble128) + version (GNU_WantLongDoubleFormat128) version = GNU_UseLongDoubleFormat128; + else version (GNU_WantLongDoubleFormat64) + { } + else + { + version (GNU_LongDouble128) + version = GNU_UseLongDoubleFormat128; + } } version (GNU_UseLongDoubleFormat128) diff -uNr gdc-0.17/d/phobos/std/c/dirent.d gdc-0.18/d/phobos/std/c/dirent.d --- gdc-0.17/d/phobos/std/c/dirent.d 2004-10-26 02:41:27.000000000 +0200 +++ gdc-0.18/d/phobos/std/c/dirent.d 2005-12-10 03:31:59.000000000 +0100 @@ -20,6 +20,7 @@ private import gcc.config; private import std.string; +private import gcc.config; extern(C) { @@ -37,6 +38,8 @@ dirent * readdir(DIR *); void rewinddir(DIR *); int closedir(DIR *); +Coff_t telldir(DIR* dir); +void seekdir(DIR* dir, Coff_t offset); } diff -uNr gdc-0.17/d/phobos/std/c/fenv.d gdc-0.18/d/phobos/std/c/fenv.d --- gdc-0.17/d/phobos/std/c/fenv.d 1970-01-01 01:00:00.000000000 +0100 +++ gdc-0.18/d/phobos/std/c/fenv.d 2006-05-13 21:05:42.000000000 +0200 @@ -0,0 +1,112 @@ + +/** + * C's <fenv.h> + * Authors: Walter Bright, Digital Mars, www.digitalmars.com + * License: Public Domain + * Macros: + * WIKI=Phobos/StdCFenv + */ + +module std.c.fenv; + +extern (C): + +/// Entire floating point environment + +struct fenv_t +{ + version (Windows) + { + ushort status; + ushort control; + ushort round; + ushort reserved[2]; + } + else version (linux) + { + ushort __control_word; + ushort __unused1; + ushort __status_word; + ushort __unused2; + ushort __tags; + ushort __unused3; + uint __eip; + ushort __cs_selector; + ushort __opcode; + uint __data_offset; + ushort __data_selector; + ushort __unused5; + } + else + { + static assert(0); + } +} + +alias int fexcept_t; /// Floating point status flags + +/// The various floating point exceptions +enum +{ + FE_INVALID = 1, /// + FE_DENORMAL = 2, /// + FE_DIVBYZERO = 4, /// + FE_OVERFLOW = 8, /// + FE_UNDERFLOW = 0x10, /// + FE_INEXACT = 0x20, /// + FE_ALL_EXCEPT = 0x3F, /// Mask of all the exceptions +} + +/// Rounding modes +enum +{ + FE_TONEAREST = 0, /// + FE_UPWARD = 0x800, /// + FE_DOWNWARD = 0x400, /// + FE_TOWARDZERO = 0xC00, /// +} + +version (Windows) +{ + extern fenv_t _FE_DFL_ENV; + + /// Default floating point environment + fenv_t* FE_DFL_ENV = &_FE_DFL_ENV; +} +else version (linux) +{ + /// Default floating point environment + fenv_t* FE_DFL_ENV = cast(fenv_t*)(-1); +} +else +{ + static assert(0); +} + +/// Floating point precision +enum +{ + FE_FLTPREC = 0, /// + FE_DBLPREC = 0x200, /// + FE_LDBLPREC = 0x300, /// +} + +int fetestexcept(int excepts); /// +int feraiseexcept(int excepts); /// +int feclearexcept(int excepts); /// +//int fegetexcept(fexcept_t *flagp,int excepts); /// +//int fesetexcept(fexcept_t *flagp,int excepts); /// +int fegetround(); /// +int fesetround(int round); /// +int fegetprec(); /// +int fesetprec(int prec); /// +int fegetenv(fenv_t *envp); /// +int fesetenv(fenv_t *envp); /// +//void feprocentry(fenv_t *envp); /// +//void feprocexit(const fenv_t *envp); /// + +int fegetexceptflag(fexcept_t *flagp,int excepts); /// +int fesetexceptflag(fexcept_t *flagp,int excepts); /// +int feholdexcept(fenv_t *envp); /// +int feupdateenv(fenv_t *envp); /// + diff -uNr gdc-0.17/d/phobos/std/c/linux/ldblcompat.d gdc-0.18/d/phobos/std/c/linux/ldblcompat.d --- gdc-0.17/d/phobos/std/c/linux/ldblcompat.d 1970-01-01 01:00:00.000000000 +0100 +++ gdc-0.18/d/phobos/std/c/linux/ldblcompat.d 2006-05-21 23:37:42.000000000 +0200 @@ -0,0 +1,25 @@ +/* In C, the stdio/stdlib function to use are determined by a test in cdefs.h. + Not exactly sure how math funcs are handled. */ + +module std.c.linux.ldblcompat; + +version (GNU_WantLongDoubleFormat128) + version = GNU_UseLongDoubleFormat128; +else version (GNU_WantLongDoubleFormat64) + { } +else +{ + version (GNU_LongDouble128) + version = GNU_UseLongDoubleFormat128; +} + +version (GNU_UseLongDoubleFormat128) +{ + static const bool __No_Long_Double_Math = false; + const char[] __LDBL_COMPAT_PFX = ""; +} +else +{ + static const bool __No_Long_Double_Math = true; + const char[] __LDBL_COMPAT_PFX = "__nldbl_"; +} diff -uNr gdc-0.17/d/phobos/std/c/linux/linux.d gdc-0.18/d/phobos/std/c/linux/linux.d --- gdc-0.17/d/phobos/std/c/linux/linux.d 2005-08-13 01:51:59.000000000 +0200 +++ gdc-0.18/d/phobos/std/c/linux/linux.d 2005-12-10 03:31:59.000000000 +0100 @@ -1,336 +1,11 @@ - -/* Written by Walter Bright and Christopher E. Miller - * www.digitalmars.com - * Placed into public domain. - */ +// This is a backwards compatibility module for the DMD std.c.linux.linux module std.c.linux.linux; +import std.c.unix.unix; +import std.c.dirent; import std.c.linux.linuxextern; -alias int pid_t; -alias int off_t; -alias uint mode_t; - -enum : int -{ - SIGHUP = 1, - SIGINT = 2, - SIGQUIT = 3, - SIGILL = 4, - SIGTRAP = 5, - SIGABRT = 6, - SIGIOT = 6, - SIGBUS = 7, - SIGFPE = 8, - SIGKILL = 9, - SIGUSR1 = 10, - SIGSEGV = 11, - SIGUSR2 = 12, - SIGPIPE = 13, - SIGALRM = 14, - SIGTERM = 15, - SIGSTKFLT = 16, - SIGCHLD = 17, - SIGCONT = 18, - SIGSTOP = 19, - SIGTSTP = 20, - SIGTTIN = 21, - SIGTTOU = 22, - SIGURG = 23, - SIGXCPU = 24, - SIGXFSZ = 25, - SIGVTALRM = 26, - SIGPROF = 27, - SIGWINCH = 28, - SIGPOLL = 29, - SIGIO = 29, - SIGPWR = 30, - SIGSYS = 31, - SIGUNUSED = 31, -} - -enum -{ - O_RDONLY = 0, - O_WRONLY = 1, - O_RDWR = 2, - O_CREAT = 0100, - O_EXCL = 0200, - O_TRUNC = 01000, - O_APPEND = 02000, -} - -struct struct_stat // distinguish it from the stat() function -{ - ulong st_dev; - ushort __pad1; - uint st_ino; - uint st_mode; - uint st_nlink; - uint st_uid; - uint st_gid; - ulong st_rdev; - ushort __pad2; - int st_size; - int st_blksize; - int st_blocks; - int st_atime; - uint __unused1; - int st_mtime; - uint __unused2; - int st_ctime; - uint __unused3; - uint __unused4; - uint __unused5; -} - -unittest -{ - assert(struct_stat.sizeof == 88); -} - -enum : int -{ - S_IFIFO = 0010000, - S_IFCHR = 0020000, - S_IFDIR = 0040000, - S_IFBLK = 0060000, - S_IFREG = 0100000, - S_IFLNK = 0120000, - S_IFSOCK = 0140000, - - S_IFMT = 0170000 -} - -extern (C) -{ - int access(char*, int); - int open(char*, int, ...); - int read(int, void*, int); - int write(int, void*, int); - int close(int); - int lseek(int, int, int); - int fstat(int, struct_stat*); - int lstat(char*, struct_stat*); - int stat(char*, struct_stat*); - int chdir(char*); - int mkdir(char*, int); - int rmdir(char*); - char* getcwd(char*, int); - int chmod(char*, mode_t); - int fork(); - int dup(int); - int dup2(int, int); - int pipe(int[2]); - pid_t wait(int*); - int waitpid(pid_t, int*, int); -} - -struct timeval -{ - int tv_sec; - int tv_usec; -} - -struct tm -{ - int tm_sec; - int tm_min; - int tm_hour; - int tm_mday; - int tm_mon; - int tm_year; - int tm_wday; - int tm_yday; - int tm_isdst; - int tm_gmtoff; - int tm_zone; -} - -extern (C) -{ - int gettimeofday(timeval*, void*); - int time(int*); - tm *localtime(int*); -} - -/**************************************************************/ -// Memory mapping from and - -enum -{ - PROT_NONE = 0, - PROT_READ = 1, - PROT_WRITE = 2, - PROT_EXEC = 4, -} - -// Memory mapping sharing types - -enum -{ MAP_SHARED = 1, - MAP_PRIVATE = 2, - MAP_TYPE = 0x0F, - MAP_FIXED = 0x10, - MAP_FILE = 0, - MAP_ANONYMOUS = 0x20, - MAP_ANON = 0x20, - MAP_GROWSDOWN = 0x100, - MAP_DENYWRITE = 0x800, - MAP_EXECUTABLE = 0x1000, - MAP_LOCKED = 0x2000, - MAP_NORESERVE = 0x4000, - MAP_POPULATE = 0x8000, - MAP_NONBLOCK = 0x10000, -} - -// Values for msync() - -enum -{ MS_ASYNC = 1, - MS_INVALIDATE = 2, - MS_SYNC = 4, -} - -// Values for mlockall() - -enum -{ - MCL_CURRENT = 1, - MCL_FUTURE = 2, -} - -// Values for mremap() - -enum -{ - MREMAP_MAYMOVE = 1, -} - -// Values for madvise - -enum -{ MADV_NORMAL = 0, - MADV_RANDOM = 1, - MADV_SEQUENTIAL = 2, - MADV_WILLNEED = 3, - MADV_DONTNEED = 4, -} - -extern (C) -{ -void* mmap(void*, size_t, int, int, int, off_t); -const void* MAP_FAILED = cast(void*)-1; - -int munmap(void*, size_t); -int mprotect(void*, size_t, int); -int msync(void*, size_t, int); -int madvise(void*, size_t, int); -int mlock(void*, size_t); -int munlock(void*, size_t); -int mlockall(int); -int munlockall(); -void* mremap(void*, size_t, size_t, int); -int mincore(void*, size_t, ubyte*); -int remap_file_pages(void*, size_t, int, size_t, int); -int shm_open(char*, int, int); -int shm_unlink(char*); -} - -extern(C) -{ - struct dirent - { - int d_ino; - off_t d_off; - ushort d_reclen; - ubyte d_type; - char[256] d_name; - } - - struct DIR - { - // Managed by OS. - } - - DIR* opendir(char* name); - int closedir(DIR* dir); - dirent* readdir(DIR* dir); - void rewinddir(DIR* dir); - off_t telldir(DIR* dir); - void seekdir(DIR* dir, off_t offset); -} - - -extern(C) -{ - private import std.intrinsic; - - - int select(int nfds, fd_set* readfds, fd_set* writefds, fd_set* errorfds, timeval* timeout); - int fcntl(int s, int f, ...); - - - enum - { - EINTR = 4, - EINPROGRESS = 115, - } - - - const uint FD_SETSIZE = 1024; - //const uint NFDBITS = 8 * int.sizeof; // DMD 0.110: 8 * (int).sizeof is not an expression - const int NFDBITS = 32; - - - struct fd_set - { - int[FD_SETSIZE / NFDBITS] fds_bits; - alias fds_bits __fds_bits; - } - - - int FDELT(int d) - { - return d / NFDBITS; - } - - - int FDMASK(int d) - { - return 1 << (d % NFDBITS); - } - - - // Removes. - void FD_CLR(int fd, fd_set* set) - { - btr(cast(uint*)&set.fds_bits.ptr[FDELT(fd)], cast(uint)(fd % NFDBITS)); - } - - - // Tests. - int FD_ISSET(int fd, fd_set* set) - { - return bt(cast(uint*)&set.fds_bits.ptr[FDELT(fd)], cast(uint)(fd % NFDBITS)); - } - - - // Adds. - void FD_SET(int fd, fd_set* set) - { - bts(cast(uint*)&set.fds_bits.ptr[FDELT(fd)], cast(uint)(fd % NFDBITS)); - } - - - // Resets to zero. - void FD_ZERO(fd_set* set) - { - set.fds_bits[] = 0; - } -} - extern (C) { /* From @@ -344,4 +19,3 @@ void* dlsym(void* handle, char* name); char* dlerror(); } - diff -uNr gdc-0.17/d/phobos/std/c/linux/linux.d.orig-dmd gdc-0.18/d/phobos/std/c/linux/linux.d.orig-dmd --- gdc-0.17/d/phobos/std/c/linux/linux.d.orig-dmd 1970-01-01 01:00:00.000000000 +0100 +++ gdc-0.18/d/phobos/std/c/linux/linux.d.orig-dmd 2006-05-14 04:21:51.000000000 +0200 @@ -0,0 +1,494 @@ + +/* Written by Walter Bright, Christopher E. Miller, and many others. + * www.digitalmars.com + * Placed into public domain. + */ + +module std.c.linux.linux; + +import std.c.linux.linuxextern; + +alias int pid_t; +alias int off_t; +alias uint mode_t; + +alias uint uid_t; +alias uint gid_t; + +enum : int +{ + SIGHUP = 1, + SIGINT = 2, + SIGQUIT = 3, + SIGILL = 4, + SIGTRAP = 5, + SIGABRT = 6, + SIGIOT = 6, + SIGBUS = 7, + SIGFPE = 8, + SIGKILL = 9, + SIGUSR1 = 10, + SIGSEGV = 11, + SIGUSR2 = 12, + SIGPIPE = 13, + SIGALRM = 14, + SIGTERM = 15, + SIGSTKFLT = 16, + SIGCHLD = 17, + SIGCONT = 18, + SIGSTOP = 19, + SIGTSTP = 20, + SIGTTIN = 21, + SIGTTOU = 22, + SIGURG = 23, + SIGXCPU = 24, + SIGXFSZ = 25, + SIGVTALRM = 26, + SIGPROF = 27, + SIGWINCH = 28, + SIGPOLL = 29, + SIGIO = 29, + SIGPWR = 30, + SIGSYS = 31, + SIGUNUSED = 31, +} + +enum +{ + O_RDONLY = 0, + O_WRONLY = 1, + O_RDWR = 2, + O_CREAT = 0100, + O_EXCL = 0200, + O_TRUNC = 01000, + O_APPEND = 02000, +} + +struct struct_stat // distinguish it from the stat() function +{ + ulong st_dev; + ushort __pad1; + uint st_ino; + uint st_mode; + uint st_nlink; + uint st_uid; + uint st_gid; + ulong st_rdev; + ushort __pad2; + int st_size; + int st_blksize; + int st_blocks; + int st_atime; + uint __unused1; + int st_mtime; + uint __unused2; + int st_ctime; + uint __unused3; + uint __unused4; + uint __unused5; +} + +unittest +{ + assert(struct_stat.sizeof == 88); +} + +enum : int +{ + S_IFIFO = 0010000, + S_IFCHR = 0020000, + S_IFDIR = 0040000, + S_IFBLK = 0060000, + S_IFREG = 0100000, + S_IFLNK = 0120000, + S_IFSOCK = 0140000, + + S_IFMT = 0170000 +} + +extern (C) +{ + int access(char*, int); + int open(char*, int, ...); + int read(int, void*, int); + int write(int, void*, int); + int close(int); + int lseek(int, int, int); + int fstat(int, struct_stat*); + int lstat(char*, struct_stat*); + int stat(char*, struct_stat*); + int chdir(char*); + int mkdir(char*, int); + int rmdir(char*); + char* getcwd(char*, int); + int chmod(char*, mode_t); + int fork(); + int dup(int); + int dup2(int, int); + int pipe(int[2]); + pid_t wait(int*); + int waitpid(pid_t, int*, int); +} + +struct timeval +{ + int tv_sec; + int tv_usec; +} + +struct tm +{ + int tm_sec; + int tm_min; + int tm_hour; + int tm_mday; + int tm_mon; + int tm_year; + int tm_wday; + int tm_yday; + int tm_isdst; + int tm_gmtoff; + int tm_zone; +} + +extern (C) +{ + int gettimeofday(timeval*, void*); + int time(int*); + tm *localtime(int*); +} + +/**************************************************************/ +// Memory mapping from and + +enum +{ + PROT_NONE = 0, + PROT_READ = 1, + PROT_WRITE = 2, + PROT_EXEC = 4, +} + +// Memory mapping sharing types + +enum +{ MAP_SHARED = 1, + MAP_PRIVATE = 2, + MAP_TYPE = 0x0F, + MAP_FIXED = 0x10, + MAP_FILE = 0, + MAP_ANONYMOUS = 0x20, + MAP_ANON = 0x20, + MAP_GROWSDOWN = 0x100, + MAP_DENYWRITE = 0x800, + MAP_EXECUTABLE = 0x1000, + MAP_LOCKED = 0x2000, + MAP_NORESERVE = 0x4000, + MAP_POPULATE = 0x8000, + MAP_NONBLOCK = 0x10000, +} + +// Values for msync() + +enum +{ MS_ASYNC = 1, + MS_INVALIDATE = 2, + MS_SYNC = 4, +} + +// Values for mlockall() + +enum +{ + MCL_CURRENT = 1, + MCL_FUTURE = 2, +} + +// Values for mremap() + +enum +{ + MREMAP_MAYMOVE = 1, +} + +// Values for madvise + +enum +{ MADV_NORMAL = 0, + MADV_RANDOM = 1, + MADV_SEQUENTIAL = 2, + MADV_WILLNEED = 3, + MADV_DONTNEED = 4, +} + +extern (C) +{ +void* mmap(void*, size_t, int, int, int, off_t); +const void* MAP_FAILED = cast(void*)-1; + +int munmap(void*, size_t); +int mprotect(void*, size_t, int); +int msync(void*, size_t, int); +int madvise(void*, size_t, int); +int mlock(void*, size_t); +int munlock(void*, size_t); +int mlockall(int); +int munlockall(); +void* mremap(void*, size_t, size_t, int); +int mincore(void*, size_t, ubyte*); +int remap_file_pages(void*, size_t, int, size_t, int); +int shm_open(char*, int, int); +int shm_unlink(char*); +} + +extern(C) +{ + + enum + { + DT_UNKNOWN = 0, + DT_FIFO = 1, + DT_CHR = 2, + DT_DIR = 4, + DT_BLK = 6, + DT_REG = 8, + DT_LNK = 10, + DT_SOCK = 12, + DT_WHT = 14, + } + + struct dirent + { + int d_ino; + off_t d_off; + ushort d_reclen; + ubyte d_type; + char[256] d_name; + } + + struct DIR + { + // Managed by OS. + } + + DIR* opendir(char* name); + int closedir(DIR* dir); + dirent* readdir(DIR* dir); + void rewinddir(DIR* dir); + off_t telldir(DIR* dir); + void seekdir(DIR* dir, off_t offset); +} + + +extern(C) +{ + private import std.intrinsic; + + + int select(int nfds, fd_set* readfds, fd_set* writefds, fd_set* errorfds, timeval* timeout); + int fcntl(int s, int f, ...); + + + enum + { + EINTR = 4, + EINPROGRESS = 115, + } + + + const uint FD_SETSIZE = 1024; + //const uint NFDBITS = 8 * int.sizeof; // DMD 0.110: 8 * (int).sizeof is not an expression + const int NFDBITS = 32; + + + struct fd_set + { + int[FD_SETSIZE / NFDBITS] fds_bits; + alias fds_bits __fds_bits; + } + + + int FDELT(int d) + { + return d / NFDBITS; + } + + + int FDMASK(int d) + { + return 1 << (d % NFDBITS); + } + + + // Removes. + void FD_CLR(int fd, fd_set* set) + { + btr(cast(uint*)&set.fds_bits.ptr[FDELT(fd)], cast(uint)(fd % NFDBITS)); + } + + + // Tests. + int FD_ISSET(int fd, fd_set* set) + { + return bt(cast(uint*)&set.fds_bits.ptr[FDELT(fd)], cast(uint)(fd % NFDBITS)); + } + + + // Adds. + void FD_SET(int fd, fd_set* set) + { + bts(cast(uint*)&set.fds_bits.ptr[FDELT(fd)], cast(uint)(fd % NFDBITS)); + } + + + // Resets to zero. + void FD_ZERO(fd_set* set) + { + set.fds_bits[] = 0; + } +} + +extern (C) +{ + /* From + * See http://www.opengroup.org/onlinepubs/007908799/xsh/dlsym.html + */ + + const int RTLD_NOW = 0x00002; // Correct for Red Hat 8 + + void* dlopen(char* file, int mode); + int dlclose(void* handle); + void* dlsym(void* handle, char* name); + char* dlerror(); +} + +extern (C) +{ + /* from + */ + + struct passwd + { + char *pw_name; + char *pw_passwd; + uid_t pw_uid; + gid_t pw_gid; + char *pw_gecos; + char *pw_dir; + char *pw_shell; + } + + int getpwnam_r(char*, passwd*, void*, size_t, passwd**); +} + +extern (C) +{ + /* pthread declarations taken from pthread headers and + http://svn.dsource.org/projects/bindings/trunk/pthreads.d + */ + + /* from bits/types.h + */ + + typedef int __time_t; + + /* from time.h + */ + + struct timespec + { + __time_t tv_sec; /* seconds */ + int tv_nsec; /* nanosecs. */ + } + + /* from bits/pthreadtypes.h + */ + + struct _pthread_descr_struct + { + /* Not defined in the headers ??? + Just needed here to typedef + the _pthread_descr pointer + */ + } + + typedef _pthread_descr_struct* _pthread_descr; + + struct _pthread_fastlock + { + int __status; + int __spinlock; + } + + typedef long __pthread_cond_align_t; + + struct pthread_cond_t + { + _pthread_fastlock __c_lock; + _pthread_descr __c_waiting; + char[48 + - _pthread_fastlock.sizeof + - _pthread_descr.sizeof + - __pthread_cond_align_t.sizeof + ] __padding; + __pthread_cond_align_t __align; + } + + struct pthread_condattr_t + { + int __dummy; + } + + struct pthread_mutex_t + { + int __m_reserved; + int __m_count; + _pthread_descr __m_owner; + int __m_kind; + _pthread_fastlock __m_lock; + } + + struct pthread_mutexattr_t + { + int __mutexkind; + } + + /* from pthread.h + */ + + int pthread_mutex_init(pthread_mutex_t*, pthread_mutexattr_t*); + int pthread_mutex_destroy(pthread_mutex_t*); + int pthread_mutex_trylock(pthread_mutex_t*); + int pthread_mutex_lock(pthread_mutex_t*); + int pthread_mutex_unlock(pthread_mutex_t*); + + int pthread_mutexattr_init(pthread_mutexattr_t*); + int pthread_mutexattr_destroy(pthread_mutexattr_t*); + + int pthread_cond_init(pthread_cond_t*, pthread_condattr_t*); + int pthread_cond_destroy(pthread_cond_t*); + int pthread_cond_signal(pthread_cond_t*); + int pthread_cond_wait(pthread_cond_t*, pthread_mutex_t*); + int pthread_cond_timedwait(pthread_cond_t*, pthread_mutex_t*, timespec*); +} + +extern (C) +{ + /* from semaphore.h + */ + + struct sem_t + { + _pthread_fastlock __sem_lock; + int __sem_value; + void* __sem_waiting; + } + + int sem_init(sem_t*, int, uint); + int sem_wait(sem_t*); + int sem_trywait(sem_t*); + int sem_post(sem_t*); + int sem_getvalue(sem_t*, int*); + int sem_destroy(sem_t*); +} + diff -uNr gdc-0.17/d/phobos/std/c/linux/socket.d gdc-0.18/d/phobos/std/c/linux/socket.d --- gdc-0.17/d/phobos/std/c/linux/socket.d 2005-04-28 23:12:43.000000000 +0200 +++ gdc-0.18/d/phobos/std/c/linux/socket.d 2006-03-12 16:25:36.000000000 +0100 @@ -359,8 +359,8 @@ int32_t ai_socktype; int32_t ai_protocol; size_t ai_addrlen; - char* ai_canonname; sockaddr* ai_addr; + char* ai_canonname; addrinfo* ai_next; } diff -uNr gdc-0.17/d/phobos/std/c/math.d gdc-0.18/d/phobos/std/c/math.d --- gdc-0.17/d/phobos/std/c/math.d 2005-10-13 03:06:51.000000000 +0200 +++ gdc-0.18/d/phobos/std/c/math.d 2006-05-13 21:05:42.000000000 +0200 @@ -1,11 +1,10 @@ /** - * Standard C math.h - * - * Copyright: Public Domain - */ - -/* www.digitalmars.com + * C's <math.h> + * Authors: Walter Bright, Digital Mars, www.digitalmars.com + * License: Public Domain + * Macros: + * WIKI=Phobos/StdCMath */ /* NOTE: This file has been patched from the original DMD distribution to @@ -18,42 +17,42 @@ extern (C): -alias float float_t; -alias double double_t; +alias float float_t; /// +alias double double_t; /// -const double HUGE_VAL = double.infinity; -const double HUGE_VALF = float.infinity; -const double HUGE_VALL = real.infinity; +const double HUGE_VAL = double.infinity; /// +const float HUGE_VALF = float.infinity; /// ditto +const real HUGE_VALL = real.infinity; /// ditto -const float INFINITY = float.infinity; -const float NAN = float.nan; +const float INFINITY = float.infinity; /// +const float NAN = float.nan; /// enum { FP_NANS, // extension FP_NANQ, // extension - FP_INFINITE, - FP_NAN = FP_NANQ, - FP_NORMAL = 3, - FP_SUBNORMAL = 4, - FP_ZERO = 5, + FP_INFINITE, /// + FP_NAN = FP_NANQ, /// + FP_NORMAL = 3, /// + FP_SUBNORMAL = 4, /// + FP_ZERO = 5, /// FP_EMPTY = 6, // extension FP_UNSUPPORTED = 7, // extension } enum { - FP_FAST_FMA = 0, - FP_FAST_FMAF = 0, - FP_FAST_FMAL = 0, + FP_FAST_FMA = 0, /// + FP_FAST_FMAF = 0, /// + FP_FAST_FMAL = 0, /// } -const int FP_ILOGB0 = int.min; -const int FP_ILOGBNAN = int.min; +const int FP_ILOGB0 = int.min; /// +const int FP_ILOGBNAN = int.min; /// -const int MATH_ERRNO = 1; -const int MATH_ERREXCEPT = 2; -const int math_errhandling = MATH_ERRNO | MATH_ERREXCEPT; +const int MATH_ERRNO = 1; /// +const int MATH_ERREXCEPT = 2; /// +const int math_errhandling = MATH_ERRNO | MATH_ERREXCEPT; /// version (GNU) { @@ -290,240 +289,245 @@ alias gcc.config.fminl fminl; alias gcc.config.fmal fmal; } else { -double acos(double x); -float acosf(float x); -real acosl(real x); - -double asin(double x); -float asinf(float x); -real asinl(real x); - -double atan(double x); -float atanf(float x); -real atanl(real x); - -double atan2(double y, double x); -float atan2f(float y, float x); -real atan2l(real y, real x); - -double cos(double x); -float cosf(float x); -real cosl(real x); - -double sin(double x); -float sinf(float x); -real sinl(real x); - -double tan(double x); -float tanf(float x); -real tanl(real x); - -double acosh(double x); -float acoshf(float x); -real acoshl(real x); - -double asinh(double x); -float asinhf(float x); -real asinhl(real x); - -double atanh(double x); -float atanhf(float x); -real atanhl(real x); - -double cosh(double x); -float coshf(float x); -real coshl(real x); - -double sinh(double x); -float sinhf(float x); -real sinhl(real x); - -double tanh(double x); -float tanhf(float x); -real tanhl(real x); - -double exp(double x); -float expf(float x); -real expl(real x); - -double exp2(double x); -float exp2f(float x); -real exp2l(real x); - -double expm1(double x); -float expm1f(float x); -real expm1l(real x); - -double frexp(double value, int *exp); -float frexpf(float value, int *exp); -real frexpl(real value, int *exp); - -int ilogb(double x); -int ilogbf(float x); -int ilogbl(real x); - -double ldexp(double x, int exp); -float ldexpf(float x, int exp); -real ldexpl(real x, int exp); - -double log(double x); -float logf(float x); -real logl(real x); - -double log10(double x); -float log10f(float x); -real log10l(real x); - -double log1p(double x); -float log1pf(float x); -real log1pl(real x); - -double log2(double x); -float log2f(float x); -real log2l(real x); - -double logb(double x); -float logbf(float x); -real logbl(real x); - -double modf(double value, double *iptr); -float modff(float value, float *iptr); -real modfl(real value, real *iptr); - -double scalbn(double x, int n); -float scalbnf(float x, int n); -real scalbnl(real x, int n); - -double scalbln(double x, int n); -float scalblnf(float x, int n); -real scalblnl(real x, int n); - -double cbrt(double x); -float cbrtf(float x); -real cbrtl(real x); - -double fabs(double x); -float fabsf(float x); -real fabsl(real x); - -double hypot(double x, double y); -float hypotf(float x, float y); -real hypotl(real x, real y); - -double pow(double x, double y); -float powf(float x, float y); -real powl(real x, real y); - -double sqrt(double x); -float sqrtf(float x); -real sqrtl(real x); - -double erf(double x); -float erff(float x); -real erfl(real x); - -double erfc(double x); -float erfcf(float x); -real erfcl(real x); - -double lgamma(double x); -float lgammaf(float x); -real lgammal(real x); - -double tgamma(double x); -float tgammaf(float x); -real tgammal(real x); - -double ceil(double x); -float ceilf(float x); -real ceill(real x); - -double floor(double x); -float floorf(float x); -real floorl(real x); - -double nearbyint(double x); -float nearbyintf(float x); -real nearbyintl(real x); - -double rint(double x); -float rintf(float x); -real rintl(real x); - -int lrint(double x); -int lrintf(float x); -int lrintl(real x); - -long llrint(double x); -long llrintf(float x); -long llrintl(real x); - -double round(double x); -float roundf(float x); -real roundl(real x); - -int lround(double x); -int lroundf(float x); -int lroundl(real x); - -long llround(double x); -long llroundf(float x); -long llroundl(real x); - -double trunc(double x); -float truncf(float x); -real truncl(real x); - -double fmod(double x, double y); -float fmodf(float x, float y); -real fmodl(real x, real y); - -double remainder(double x, double y); -float remainderf(float x, float y); -real remainderl(real x, real y); - -double remquo(double x, double y, int *quo); -float remquof(float x, float y, int *quo); -real remquol(real x, real y, int *quo); - -double copysign(double x, double y); -float copysignf(float x, float y); -real copysignl(real x, real y); - -double nan(char *tagp); -float nanf(char *tagp); -real nanl(char *tagp); - -double nextafter(double x, double y); -float nextafterf(float x, float y); -real nextafterl(real x, real y); - -double nexttoward(double x, real y); -float nexttowardf(float x, real y); -real nexttowardl(real x, real y); - -double fdim(double x, double y); -float fdimf(float x, float y); -real fdiml(real x, real y); - -double fmax(double x, double y); -float fmaxf(float x, float y); -real fmaxl(real x, real y); - -double fmin(double x, double y); -float fminf(float x, float y); -real fminl(real x, real y); - -double fma(double x, double y, double z); -float fmaf(float x, float y, float z); -real fmal(real x, real y, real z); +double acos(double x); /// +float acosf(float x); /// ditto +real acosl(real x); /// ditto + +double asin(double x); /// +float asinf(float x); /// ditto +real asinl(real x); /// ditto + +double atan(double x); /// +float atanf(float x); /// ditto +real atanl(real x); /// ditto + +double atan2(double y, double x); /// +float atan2f(float y, float x); /// ditto +real atan2l(real y, real x); /// ditto + +double cos(double x); /// +float cosf(float x); /// ditto +real cosl(real x); /// ditto + +double sin(double x); /// +float sinf(float x); /// ditto +real sinl(real x); /// ditto + +double tan(double x); /// +float tanf(float x); /// ditto +real tanl(real x); /// ditto + +double acosh(double x); /// +float acoshf(float x); /// ditto +real acoshl(real x); /// ditto + +double asinh(double x); /// +float asinhf(float x); /// ditto +real asinhl(real x); /// ditto + +double atanh(double x); /// +float atanhf(float x); /// ditto +real atanhl(real x); /// ditto + +double cosh(double x); /// +float coshf(float x); /// ditto +real coshl(real x); /// ditto + +double sinh(double x); /// +float sinhf(float x); /// ditto +real sinhl(real x); /// ditto + +double tanh(double x); /// +float tanhf(float x); /// ditto +real tanhl(real x); /// ditto + +double exp(double x); /// +float expf(float x); /// ditto +real expl(real x); /// ditto + +double exp2(double x); /// +float exp2f(float x); /// ditto +real exp2l(real x); /// ditto + +double expm1(double x); /// +float expm1f(float x); /// ditto +real expm1l(real x); /// ditto + +double frexp(double value, int *exp); /// +float frexpf(float value, int *exp); /// ditto +real frexpl(real value, int *exp); /// ditto + +int ilogb(double x); /// +int ilogbf(float x); /// ditto +int ilogbl(real x); /// ditto + +double ldexp(double x, int exp); /// +float ldexpf(float x, int exp); /// ditto +real ldexpl(real x, int exp); /// ditto + +double log(double x); /// +float logf(float x); /// ditto +real logl(real x); /// ditto + +double log10(double x); /// +float log10f(float x); /// ditto +real log10l(real x); /// ditto + +double log1p(double x); /// +float log1pf(float x); /// ditto +real log1pl(real x); /// ditto + +double log2(double x); /// +float log2f(float x); /// ditto +real log2l(real x); /// ditto + +double logb(double x); /// +float logbf(float x); /// ditto +real logbl(real x); /// ditto + +double modf(double value, double *iptr); /// +float modff(float value, float *iptr); /// ditto +real modfl(real value, real *iptr); /// ditto + +double scalbn(double x, int n); /// +float scalbnf(float x, int n); /// ditto +real scalbnl(real x, int n); /// ditto + +double scalbln(double x, int n); /// +float scalblnf(float x, int n); /// ditto +real scalblnl(real x, int n); /// ditto + +double cbrt(double x); /// +float cbrtf(float x); /// ditto +real cbrtl(real x); /// ditto + +double fabs(double x); /// +float fabsf(float x); /// ditto +real fabsl(real x); /// ditto + +double hypot(double x, double y); /// +float hypotf(float x, float y); /// ditto +real hypotl(real x, real y); /// ditto + +double pow(double x, double y); /// +float powf(float x, float y); /// ditto +real powl(real x, real y); /// ditto + +double sqrt(double x); /// +float sqrtf(float x); /// ditto +real sqrtl(real x); /// ditto + +double erf(double x); /// +float erff(float x); /// ditto +real erfl(real x); /// ditto + +double erfc(double x); /// +float erfcf(float x); /// ditto +real erfcl(real x); /// ditto + +double lgamma(double x); /// +float lgammaf(float x); /// ditto +real lgammal(real x); /// ditto + +double tgamma(double x); /// +float tgammaf(float x); /// ditto +real tgammal(real x); /// ditto + +double ceil(double x); /// +float ceilf(float x); /// ditto +real ceill(real x); /// ditto + +double floor(double x); /// +float floorf(float x); /// ditto +real floorl(real x); /// ditto + +double nearbyint(double x); /// +float nearbyintf(float x); /// ditto +real nearbyintl(real x); /// ditto + +double rint(double x); /// +float rintf(float x); /// ditto +real rintl(real x); /// ditto + +int lrint(double x); /// +int lrintf(float x); /// ditto +int lrintl(real x); /// ditto + +long llrint(double x); /// +long llrintf(float x); /// ditto +long llrintl(real x); /// ditto + +double round(double x); /// +float roundf(float x); /// ditto +real roundl(real x); /// ditto + +int lround(double x); /// +int lroundf(float x); /// ditto +int lroundl(real x); /// ditto + +long llround(double x); /// +long llroundf(float x); /// ditto +long llroundl(real x); /// ditto + +double trunc(double x); /// +float truncf(float x); /// ditto +real truncl(real x); /// ditto + +double fmod(double x, double y); /// +float fmodf(float x, float y); /// ditto +real fmodl(real x, real y); /// ditto + +double remainder(double x, double y); /// +float remainderf(float x, float y); /// ditto +real remainderl(real x, real y); /// ditto + +double remquo(double x, double y, int *quo); /// +float remquof(float x, float y, int *quo); /// ditto +real remquol(real x, real y, int *quo); /// ditto + +double copysign(double x, double y); /// +float copysignf(float x, float y); /// ditto +real copysignl(real x, real y); /// ditto + +double nan(char *tagp); /// +float nanf(char *tagp); /// ditto +real nanl(char *tagp); /// ditto + +double nextafter(double x, double y); /// +float nextafterf(float x, float y); /// ditto +real nextafterl(real x, real y); /// ditto + +double nexttoward(double x, real y); /// +float nexttowardf(float x, real y); /// ditto +real nexttowardl(real x, real y); /// ditto + +double fdim(double x, double y); /// +float fdimf(float x, float y); /// ditto +real fdiml(real x, real y); /// ditto + +double fmax(double x, double y); /// +float fmaxf(float x, float y); /// ditto +real fmaxl(real x, real y); /// ditto + +double fmin(double x, double y); /// +float fminf(float x, float y); /// ditto +real fminl(real x, real y); /// ditto + +double fma(double x, double y, double z); /// +float fmaf(float x, float y, float z); /// ditto +real fmal(real x, real y, real z); /// ditto } - +/// int isgreater(real x, real y) { return !(x !> y); } +/// int isgreaterequal(real x, real y) { return !(x !>= y); } +/// int isless(real x, real y) { return !(x !< y); } +/// int islessequal(real x, real y) { return !(x !<= y); } +/// int islessgreater(real x, real y) { return !(x !<> y); } +/// int isunordered(real x, real y) { return (x !<>= y); } diff -uNr gdc-0.17/d/phobos/std/c/process.d gdc-0.18/d/phobos/std/c/process.d --- gdc-0.17/d/phobos/std/c/process.d 2004-12-19 18:51:04.000000000 +0100 +++ gdc-0.18/d/phobos/std/c/process.d 2006-05-13 21:05:42.000000000 +0200 @@ -1,10 +1,15 @@ -/* Interface to the C header file process.h +/** + * C's <process.h> + * Authors: Walter Bright, Digital Mars, www.digitalmars.com + * License: Public Domain + * Macros: + * WIKI=Phobos/StdCProcess */ module std.c.process; -import std.c.stddef; +private import std.c.stddef; extern (C): @@ -18,16 +23,6 @@ int system(char *); -int spawnl(int, char *, char *,...); -int spawnle(int, char *, char *,...); -int spawnlp(int, char *, char *,...); -int spawnlpe(int, char *, char *,...); -int spawnv(int, char *, char **); -int spawnve(int, char *, char **, char **); -int spawnvp(int, char *, char **); -int spawnvpe(int, char *, char **, char **); - - enum { _P_WAIT, _P_NOWAIT, _P_OVERLAY }; int execl(char *, char *,...); @@ -45,33 +40,47 @@ int cwait(int *,int,int); int wait(int *); -uint _beginthread(void function(void *),uint,void *); +version (Windows) +{ + uint _beginthread(void function(void *),uint,void *); + + extern (Windows) alias uint (*stdfp)(void *); + + uint _beginthreadex(void* security, uint stack_size, + stdfp start_addr, void* arglist, uint initflag, + uint* thrdaddr); + + void _endthread(); + void _endthreadex(uint); + + int spawnl(int, char *, char *,...); + int spawnle(int, char *, char *,...); + int spawnlp(int, char *, char *,...); + int spawnlpe(int, char *, char *,...); + int spawnv(int, char *, char **); + int spawnve(int, char *, char **, char **); + int spawnvp(int, char *, char **); + int spawnvpe(int, char *, char **, char **); + + + int _wsystem(wchar_t *); + int _wspawnl(int, wchar_t *, wchar_t *, ...); + int _wspawnle(int, wchar_t *, wchar_t *, ...); + int _wspawnlp(int, wchar_t *, wchar_t *, ...); + int _wspawnlpe(int, wchar_t *, wchar_t *, ...); + int _wspawnv(int, wchar_t *, wchar_t **); + int _wspawnve(int, wchar_t *, wchar_t **, wchar_t **); + int _wspawnvp(int, wchar_t *, wchar_t **); + int _wspawnvpe(int, wchar_t *, wchar_t **, wchar_t **); + + int _wexecl(wchar_t *, wchar_t *, ...); + int _wexecle(wchar_t *, wchar_t *, ...); + int _wexeclp(wchar_t *, wchar_t *, ...); + int _wexeclpe(wchar_t *, wchar_t *, ...); + int _wexecv(wchar_t *, wchar_t **); + int _wexecve(wchar_t *, wchar_t **, wchar_t **); + int _wexecvp(wchar_t *, wchar_t **); + int _wexecvpe(wchar_t *, wchar_t **, wchar_t **); +} -extern (Windows) alias uint (*stdfp)(void *); -uint _beginthreadex(void* security, uint stack_size, - stdfp start_addr, void* arglist, uint initflag, - uint* thrdaddr); - -void _endthread(); -void _endthreadex(uint); - - -int _wsystem(wchar_t *); -int _wspawnl(int, wchar_t *, wchar_t *, ...); -int _wspawnle(int, wchar_t *, wchar_t *, ...); -int _wspawnlp(int, wchar_t *, wchar_t *, ...); -int _wspawnlpe(int, wchar_t *, wchar_t *, ...); -int _wspawnv(int, wchar_t *, wchar_t **); -int _wspawnve(int, wchar_t *, wchar_t **, wchar_t **); -int _wspawnvp(int, wchar_t *, wchar_t **); -int _wspawnvpe(int, wchar_t *, wchar_t **, wchar_t **); - -int _wexecl(wchar_t *, wchar_t *, ...); -int _wexecle(wchar_t *, wchar_t *, ...); -int _wexeclp(wchar_t *, wchar_t *, ...); -int _wexeclpe(wchar_t *, wchar_t *, ...); -int _wexecv(wchar_t *, wchar_t **); -int _wexecve(wchar_t *, wchar_t **, wchar_t **); -int _wexecvp(wchar_t *, wchar_t **); -int _wexecvpe(wchar_t *, wchar_t **, wchar_t **); diff -uNr gdc-0.17/d/phobos/std/c/skyos/compat.d gdc-0.18/d/phobos/std/c/skyos/compat.d --- gdc-0.17/d/phobos/std/c/skyos/compat.d 1970-01-01 01:00:00.000000000 +0100 +++ gdc-0.18/d/phobos/std/c/skyos/compat.d 2005-12-26 04:37:38.000000000 +0100 @@ -0,0 +1,39 @@ +module std.c.skyos.compat; +private import std.c.unix.unix; +private import std.c.skyos.skyos; + +enum { + TASK_CREATE_FLAG_WANT_WAIT_FOR = 0x00002000 +} + +// libpthread pthread_create has problems? +int pthread_create(pthread_t * pth, pthread_attr_t * attr, void* fn, void * arg) +{ + int tid = ThreadCreate("thread", TASK_CREATE_FLAG_WANT_WAIT_FOR, + cast(void *) fn, cast(uint) arg, 0, 0, 0, 0, 0, 0, 0, 0, 0); + if (tid) { + *pth = tid; + return 0; + } else { + return EAGAIN; + } +} +int pthread_join(pthread_t thread, void ** result) +{ + int v; + int r = ThreadWait(thread, & v); + if (r == thread) { + if (result) + *result = null; + return 0; + } else + return -1; +} + +pthread_t pthread_self() { return cast(pthread_t) ThreadGetPid(); } +int pthread_equal(pthread_t a, pthread_t b) { return a == b; } +int pthread_kill(pthread_t pth, int sig) { return kill(cast(pid_t) pth, sig); } +alias ThreadYield sched_yield; + +int pthread_suspend_np(pthread_t p) { return ThreadSuspend(p) == 0 ? 0 : -1; } +int pthread_continue_np(pthread_t p) { return ThreadResume(p) == 0 ? 0 : -1; } diff -uNr gdc-0.17/d/phobos/std/c/skyos/skyos.d gdc-0.18/d/phobos/std/c/skyos/skyos.d --- gdc-0.17/d/phobos/std/c/skyos/skyos.d 1970-01-01 01:00:00.000000000 +0100 +++ gdc-0.18/d/phobos/std/c/skyos/skyos.d 2005-12-26 04:37:38.000000000 +0100 @@ -0,0 +1,11 @@ +module std.c.skyos.skyos; + +extern(C): + +int ThreadCreate (char *ucName, uint uiFlags, void *fpFunction, uint arg1, uint arg2, uint arg3, uint arg4, uint arg5, uint arg6, uint arg7, uint arg8, uint arg9, uint arg10); +int ThreadWait (int iPid, int *iStatus); +int ThreadGetPid (); +int ThreadSuspend (int iPid); +int ThreadResume (int iPid); +void ThreadYield (); +int ThreadSleep (uint uiMilliseconds); diff -uNr gdc-0.17/d/phobos/std/c/stdarg.d gdc-0.18/d/phobos/std/c/stdarg.d --- gdc-0.17/d/phobos/std/c/stdarg.d 2005-10-02 16:17:55.000000000 +0200 +++ gdc-0.18/d/phobos/std/c/stdarg.d 2006-05-13 21:05:42.000000000 +0200 @@ -1,7 +1,10 @@ -/* - * Placed in public domain. - * Written by Hauke Duden and Walter Bright +/** + * C's <stdarg.h> + * Authors: Hauke Duden and Walter Bright, Digital Mars, www.digitalmars.com + * License: Public Domain + * Macros: + * WIKI=Phobos/StdCStdarg */ /* This is for use with extern(C) variable argument lists. */ @@ -33,7 +36,11 @@ void va_copy(out va_list dest, va_list src) { - dest = src; + static if ( is( dest T == T[1]) ) { + dest[0] = src[0]; + } else { + dest = src; + } } } diff -uNr gdc-0.17/d/phobos/std/c/stddef.d gdc-0.18/d/phobos/std/c/stddef.d --- gdc-0.17/d/phobos/std/c/stddef.d 2005-10-02 16:17:55.000000000 +0200 +++ gdc-0.18/d/phobos/std/c/stddef.d 2006-05-13 21:05:42.000000000 +0200 @@ -1,8 +1,10 @@ -/* - * Written by Walter Bright - * Digital Mars - * www.digitalmars.com - * Placed into Public Domain. + +/** + * C's <stdarg.h> + * Authors: Hauke Duden and Walter Bright, Digital Mars, www.digitalmars.com + * License: Public Domain + * Macros: + * WIKI=Phobos/StdCStdarg */ module std.c.stddef; diff -uNr gdc-0.17/d/phobos/std/c/stdio.d gdc-0.18/d/phobos/std/c/stdio.d --- gdc-0.17/d/phobos/std/c/stdio.d 2005-10-26 03:33:56.000000000 +0200 +++ gdc-0.18/d/phobos/std/c/stdio.d 2006-05-21 23:37:42.000000000 +0200 @@ -1,8 +1,10 @@ -/* - * Written by Walter Bright - * Digital Mars - * www.digitalmars.com - * Placed into Public Domain. + +/** + * C's <stdio.h> + * Authors: Walter Bright, Digital Mars, www.digitalmars.com + * License: Public Domain + * Macros: + * WIKI=Phobos/StdCStdio */ /* NOTE: This file has been patched from the original DMD distribution to @@ -33,15 +35,15 @@ } else version (Win32) { - const int _NFILE = 60; - const int BUFSIZ = 0x4000; - const int EOF = -1; - const int FOPEN_MAX = 20; - const int FILENAME_MAX = 256; // 255 plus NULL - const int TMP_MAX = 32767; - const int _SYS_OPEN = 20; - const int SYS_OPEN = _SYS_OPEN; - const wchar WEOF = 0xFFFF; + const int _NFILE = 60; /// + const int BUFSIZ = 0x4000; /// + const int EOF = -1; /// + const int FOPEN_MAX = 20; /// + const int FILENAME_MAX = 256; /// 255 plus NULL + const int TMP_MAX = 32767; /// + const int _SYS_OPEN = 20; /// + const int SYS_OPEN = _SYS_OPEN; /// + const wchar WEOF = 0xFFFF; /// } else version (linux) { @@ -97,7 +99,7 @@ } -alias _iobuf FILE; +alias _iobuf FILE; /// enum { @@ -172,11 +174,11 @@ else version (Win32) { // This works for DMD/DMC and MinGW/msvcrt - const FILE *stdin = &_iob[0]; - const FILE *stdout = &_iob[1]; - const FILE *stderr = &_iob[2]; - const FILE *stdaux = &_iob[3]; - const FILE *stdprn = &_iob[4]; + const FILE *stdin = &_iob[0]; /// + const FILE *stdout = &_iob[1]; /// + const FILE *stderr = &_iob[2]; /// + const FILE *stdaux = &_iob[3]; /// + const FILE *stdprn = &_iob[4]; /// } else version (aix) { @@ -224,63 +226,76 @@ } } -alias int fpos_t; +alias int fpos_t; /// -char * tmpnam(char *); -FILE * fopen(char *,char *); -FILE * _fsopen(char *,char *,int ); -FILE * freopen(char *,char *,FILE *); -int fseek(FILE *,int,int); -int ftell(FILE *); -char * fgets(char *,int,FILE *); -int fgetc(FILE *); -int _fgetchar(); -int fflush(FILE *); -int fclose(FILE *); -int fputs(char *,FILE *); -char * gets(char *); -int fputc(int,FILE *); -int _fputchar(int); -int puts(char *); -int ungetc(int,FILE *); -size_t fread(void *,size_t,size_t,FILE *); -size_t fwrite(void *,size_t,size_t,FILE *); -//int printf(char *,...); -int fprintf(FILE *,char *,...); -int vfprintf(FILE *,char *,va_list); -int vprintf(char *,va_list); -int sprintf(char *,char *,...); -int vsprintf(char *,char *,va_list); -int scanf(char *,...); -int fscanf(FILE *,char *,...); -int sscanf(char *,char *,...); -void setbuf(FILE *,char *); -int setvbuf(FILE *,char *,int,size_t); -int remove(char *); -int rename(char *,char *); -void perror(char *); -int fgetpos(FILE *,fpos_t *); -int fsetpos(FILE *,fpos_t *); -FILE * tmpfile(); +char * tmpnam(char *); /// +FILE * fopen(char *,char *); /// +FILE * _fsopen(char *,char *,int ); /// +FILE * freopen(char *,char *,FILE *); /// +int fseek(FILE *,int,int); /// +int ftell(FILE *); /// +char * fgets(char *,int,FILE *); /// +int fgetc(FILE *); /// +int _fgetchar(); /// +int fflush(FILE *); /// +int fclose(FILE *); /// +int fputs(char *,FILE *); /// +char * gets(char *); /// +int fputc(int,FILE *); /// +int _fputchar(int); /// +int puts(char *); /// +int ungetc(int,FILE *); /// +size_t fread(void *,size_t,size_t,FILE *); /// +size_t fwrite(void *,size_t,size_t,FILE *); /// +//int printf(char *,...); /// +int fprintf(FILE *,char *,...); /// +int vfprintf(FILE *,char *,va_list); /// +int vprintf(char *,va_list); /// +int sprintf(char *,char *,...); /// +int vsprintf(char *,char *,va_list); /// +int scanf(char *,...); /// +int fscanf(FILE *,char *,...); /// +int sscanf(char *,char *,...); /// +void setbuf(FILE *,char *); /// +int setvbuf(FILE *,char *,int,size_t); /// +int remove(char *); /// +int rename(char *,char *); /// +void perror(char *); /// +int fgetpos(FILE *,fpos_t *); /// +int fsetpos(FILE *,fpos_t *); /// +FILE * tmpfile(); /// int _rmtmp(); int _fillbuf(FILE *); int _flushbu(int, FILE *); -int getw(FILE *FHdl); -int putw(int Word, FILE *FilePtr); +int getw(FILE *FHdl); /// +int putw(int Word, FILE *FilePtr); /// +/// int getchar() { return getc(stdin); } +/// int putchar(int c) { return putc(c,stdout); } +/// int getc(FILE *fp) { return fgetc(fp); } +/// int putc(int c,FILE *fp) { return fputc(c,fp); } +version(PPC) + version(Linux) + version=PPCLinux; + version (Win32) { + /// int ferror(FILE *fp) { return fp._flag&_IOERR; } + /// int feof(FILE *fp) { return fp._flag&_IOEOF; } + /// void clearerr(FILE *fp) { fp._flag &= ~(_IOERR|_IOEOF); } + /// void rewind(FILE *fp) { fseek(fp,0L,SEEK_SET); fp._flag&=~_IOERR; } int _bufsize(FILE *fp) { return fp._bufsiz; } + /// int fileno(FILE *fp) { return fp._file; } int _snprintf(char *,size_t,char *,...); int _vsnprintf(char *,size_t,char *,va_list); @@ -312,6 +327,33 @@ pragma(GNU_asm,snprintf,"snprintf" ~ __DARWIN_LDBL_COMPAT); pragma(GNU_asm,vsnprintf,"vsnprintf" ~ __DARWIN_LDBL_COMPAT); } +else version (PPCLinux) +{ + private import std.c.linux.ldblcompat; + + alias gcc.config.ferror ferror; + alias gcc.config.feof feof; + alias gcc.config.clearerr clearerr; + alias gcc.config.rewind rewind; + alias gcc.config._bufsize _bufsize; + alias gcc.config.fileno fileno; + + int snprintf(char *, size_t, char *, ...); + int vsnprintf(char *, size_t, char *, va_list); + + // printf is declared in object, but it won't be fixed unless std.c.stdio is imported... + pragma(GNU_asm,printf,__LDBL_COMPAT_PFX ~ "printf"); + pragma(GNU_asm,fprintf,__LDBL_COMPAT_PFX ~ "fprintf"); + pragma(GNU_asm,vfprintf,__LDBL_COMPAT_PFX ~ "vfprintf"); + pragma(GNU_asm,vprintf,__LDBL_COMPAT_PFX ~ "vprintf"); + pragma(GNU_asm,sprintf,__LDBL_COMPAT_PFX ~ "sprintf"); + pragma(GNU_asm,vsprintf,__LDBL_COMPAT_PFX ~ "vsprintf"); + pragma(GNU_asm,scanf,__LDBL_COMPAT_PFX ~ "scanf"); + pragma(GNU_asm,fscanf,__LDBL_COMPAT_PFX ~ "fscanf"); + pragma(GNU_asm,sscanf,__LDBL_COMPAT_PFX ~ "sscanf"); + pragma(GNU_asm,snprintf,__LDBL_COMPAT_PFX ~ "snprintf"); + pragma(GNU_asm,vsnprintf,__LDBL_COMPAT_PFX ~ "vsnprintf"); +} else version (GNU) { alias gcc.config.ferror ferror; @@ -337,50 +379,54 @@ int vsnprintf(char *,size_t,char *,va_list); } -int unlink(char *); -FILE * fdopen(int, char *); -int fgetchar(); -int fputchar(int); -int fcloseall(); -int filesize(char *); -int flushall(); -int getch(); -int getche(); -int kbhit(); -char * tempnam (char *dir, char *pfx); +int unlink(char *); /// +FILE * fdopen(int, char *); /// +int fgetchar(); /// +int fputchar(int); /// +int fcloseall(); /// +int filesize(char *); /// +int flushall(); /// +int getch(); /// +int getche(); /// +int kbhit(); /// +char * tempnam (char *dir, char *pfx); /// -wchar_t * _wtmpnam(wchar_t *); +wchar_t * _wtmpnam(wchar_t *); /// FILE * _wfopen(wchar_t *, wchar_t *); FILE * _wfsopen(wchar_t *, wchar_t *, int); FILE * _wfreopen(wchar_t *, wchar_t *, FILE *); -wchar_t * fgetws(wchar_t *, int, FILE *); -int fputws(wchar_t *, FILE *); +wchar_t * fgetws(wchar_t *, int, FILE *); /// +int fputws(wchar_t *, FILE *); /// wchar_t * _getws(wchar_t *); int _putws(wchar_t *); -int wprintf(wchar_t *, ...); -int fwprintf(FILE *, wchar_t *, ...); -int vwprintf(wchar_t *, va_list); -int vfwprintf(FILE *, wchar_t *, va_list); -int swprintf(wchar_t *, wchar_t *, ...); -int vswprintf(wchar_t *, wchar_t *, va_list); +int wprintf(wchar_t *, ...); /// +int fwprintf(FILE *, wchar_t *, ...); /// +int vwprintf(wchar_t *, va_list); /// +int vfwprintf(FILE *, wchar_t *, va_list); /// +int swprintf(wchar_t *, wchar_t *, ...); /// +int vswprintf(wchar_t *, wchar_t *, va_list); /// int _snwprintf(wchar_t *, size_t, wchar_t *, ...); int _vsnwprintf(wchar_t *, size_t, wchar_t *, va_list); -int wscanf(wchar_t *, ...); -int fwscanf(FILE *, wchar_t *, ...); -int swscanf(wchar_t *, wchar_t *, ...); +int wscanf(wchar_t *, ...); /// +int fwscanf(FILE *, wchar_t *, ...); /// +int swscanf(wchar_t *, wchar_t *, ...); /// int _wremove(wchar_t *); void _wperror(wchar_t *); FILE * _wfdopen(int, wchar_t *); wchar_t * _wtempnam(wchar_t *, wchar_t *); -wchar_t fgetwc(FILE *); +wchar_t fgetwc(FILE *); /// wchar_t _fgetwchar_t(); -wchar_t fputwc(wchar_t, FILE *); +wchar_t fputwc(wchar_t, FILE *); /// wchar_t _fputwchar_t(wchar_t); -wchar_t ungetwc(wchar_t, FILE *); +wchar_t ungetwc(wchar_t, FILE *); /// +/// wchar_t getwchar_t() { return fgetwc(stdin); } +/// wchar_t putwchar_t(wchar_t c) { return fputwc(c,stdout); } +/// wchar_t getwc(FILE *fp) { return fgetwc(fp); } +/// wchar_t putwc(wchar_t c, FILE *fp) { return fputwc(c, fp); } -int fwide(FILE* fp, int mode); +int fwide(FILE* fp, int mode); /// diff -uNr gdc-0.17/d/phobos/std/c/stdlib.d gdc-0.18/d/phobos/std/c/stdlib.d --- gdc-0.17/d/phobos/std/c/stdlib.d 2005-09-09 23:27:05.000000000 +0200 +++ gdc-0.18/d/phobos/std/c/stdlib.d 2006-05-21 23:37:42.000000000 +0200 @@ -1,3 +1,11 @@ +/** + * C's <stdlib.h> + * Authors: Walter Bright, Digital Mars, www.digitalmars.com + * License: Public Domain + * Macros: + * WIKI=Phobos/StdCStdlib + */ + /* NOTE: This file has been patched from the original DMD distribution to work with the GDC compiler. @@ -7,6 +15,8 @@ module std.c.stdlib; +private import std.c.stddef; + extern (C): enum @@ -18,40 +28,45 @@ _MAX_EXT = 256, } +/// struct div_t { int quot,rem; } +/// struct ldiv_t { int quot,rem; } +/// struct lldiv_t { long quot,rem; } - div_t div(int,int); - ldiv_t ldiv(int,int); - lldiv_t lldiv(long, long); - - const int EXIT_SUCCESS = 0; - const int EXIT_FAILURE = 1; - - int atexit(void (*)()); - void exit(int); - void _exit(int); + div_t div(int,int); /// + ldiv_t ldiv(int,int); /// ditto + lldiv_t lldiv(long, long); /// ditto + + const int EXIT_SUCCESS = 0; /// + const int EXIT_FAILURE = 1; /// ditto + + int atexit(void (*)()); /// + void exit(int); /// ditto + void _exit(int); /// ditto version (GNU) { private import gcc.builtins; - alias gcc.builtins.__builtin_alloca alloca; + alias gcc.builtins.__builtin_alloca alloca; /// } else { - void *alloca(uint); + void *alloca(uint); /// } - void *calloc(uint, uint); - void *malloc(uint); - void *realloc(void *, uint); - void free(void *); + void *calloc(uint, uint); /// + void *malloc(uint); /// ditto + void *realloc(void *, uint); /// ditto + void free(void *); /// ditto void *bsearch(void *,void *,size_t,size_t, - int function(void *,void *)); + int function(void *,void *)); /// void qsort(void *base, uint nelems, uint elemsize, - int (*compare)(void *elem1, void *elem2)); + int (*compare)(void *elem1, void *elem2)); /// ditto - char* getenv(char*); + char* getenv(char*); /// + int setenv(char*, char*, int); /// ditto + void unsetenv(char*); /// ditto version (GNU) { @@ -59,40 +74,60 @@ alias gcc.config.RAND_MAX RAND_MAX; } - int rand(); - void srand(uint); - int random(int num); - void randomize(); + int rand(); /// + void srand(uint); /// ditto + int random(int num); /// ditto + void randomize(); /// ditto - int getErrno(); - int setErrno(int); + int getErrno(); /// ditto + int setErrno(int); /// ditto const int ERANGE = 34; // on both Windows and linux -double atof(char *); -int atoi(char *); -int atol(char *); -float strtof(char *,char **); -double strtod(char *,char **); +double atof(char *); /// +int atoi(char *); /// ditto +int atol(char *); /// ditto +float strtof(char *,char **); /// ditto +double strtod(char *,char **); /// ditto //real strtold(char *,char **); version (darwin) + version (GNU_Have_strtold) + version = darwin_strtold; +version(PPC) + version(Linux) + version=PPCLinux; +version (darwin_strtold) { private import std.c.darwin.ldblcompat; - real strtold(char *, char **); pragma(GNU_asm,strtold,"strtold"~__DARWIN_LDBL_COMPAT); + real strtold(char *, char **); /// ditto + pragma(GNU_asm,strtold,"strtold"~__DARWIN_LDBL_COMPAT); +} +else version (PPCLinux) +{ + private import std.c.linux.ldblcompat; + static if (std.c.linux.ldblcompat.__No_Long_Double_Math) + alias strtod strtold; /// ditto + else + alias gcc.config.cstrtold strtold; /// ditto } else { private import gcc.config; - alias gcc.config.cstrtold strtold; + alias gcc.config.cstrtold strtold; /// ditto } -long strtol(char *,char **,int); -uint strtoul(char *,char **,int); -long atoll(char *); -long strtoll(char *,char **,int); -ulong strtoull(char *,char **,int); +long strtol(char *,char **,int); /// ditto +uint strtoul(char *,char **,int); /// ditto +long atoll(char *); /// ditto +long strtoll(char *,char **,int); /// ditto +ulong strtoull(char *,char **,int); /// ditto char* itoa(int, char*, int); char* ultoa(uint, char*, int); +int mblen(char *s, size_t n); /// +int mbtowc(wchar_t *pwc, char *s, size_t n); /// ditto +int wctomb(char *s, wchar_t wc); /// ditto +size_t mbstowcs(wchar_t *pwcs, char *s, size_t n); /// ditto +size_t wcstombs(char *s, wchar_t *pwcs, size_t n); /// ditto diff -uNr gdc-0.17/d/phobos/std/c/string.d gdc-0.18/d/phobos/std/c/string.d --- gdc-0.17/d/phobos/std/c/string.d 1970-01-01 01:00:00.000000000 +0100 +++ gdc-0.18/d/phobos/std/c/string.d 2006-05-13 21:05:42.000000000 +0200 @@ -0,0 +1,70 @@ + +/** + * C's <string.h> + * Authors: Walter Bright, Digital Mars, www.digitalmars.com + * License: Public Domain + * Macros: + * WIKI=Phobos/StdCString + */ + +/* NOTE: This file has been patched from the original DMD distribution to + work with the GDC compiler. + + Modified by David Friedman, May 2006 +*/ + + +module std.c.string; + +extern (C): + +version (GNU) +{ + private import gcc.builtins; + alias __builtin_memcpy memcpy; /// + alias __builtin_strcpy strcpy; /// + alias __builtin_strncpy strncpy; /// + alias __builtin_strncat strncat; /// + alias __builtin_strncmp strncmp; /// + alias __builtin_strchr strchr; /// + alias __builtin_strcspn strcspn; /// + alias __builtin_strpbrk strpbrk; /// + alias __builtin_strrchr strrchr; /// + alias __builtin_strspn strspn; /// + alias __builtin_strstr strstr; /// + alias __builtin_memset memset; /// + alias __builtin_strlen strlen; /// + alias __builtin_strcmp strcmp; /// + alias __builtin_strcat strcat; /// + alias __builtin_memcmp memcmp; /// +} +else +{ +void* memcpy(void* s1, void* s2, size_t n); /// +char* strcpy(char* s1, char* s2); /// +char* strncpy(char* s1, char* s2, size_t n); /// +char* strncat(char* s1, char* s2, size_t n); /// +int strncmp(char* s1, char* s2, size_t n); /// +char* strchr(char* s, int c); /// +size_t strcspn(char* s1, char* s2); /// +char* strpbrk(char* s1, char* s2); /// +char* strrchr(char* s, int c); /// +size_t strspn(char* s1, char* s2); /// +char* strstr(char* s1, char* s2); /// +void* memset(void* s, int c, size_t n); /// +int strlen(char* s); /// +int strcmp(char* s1, char* s2); /// +char* strcat(char* s1, char* s2); /// +int memcmp(void* s1, void* s2, size_t n); /// +} +void* memmove(void* s1, void* s2, size_t n); /// +size_t strxfrm(char* s1, char* s2, size_t n); /// +int strcoll(char* s1, char* s2); /// +void* memchr(void* s, int c, size_t n); /// +char* strtok(char* s1, char* s2); /// +char* strerror(int errnum); /// + +version (Windows) +{ + int memicmp(char* s1, char* s2, size_t n); /// +} diff -uNr gdc-0.17/d/phobos/std/c/time.d gdc-0.18/d/phobos/std/c/time.d --- gdc-0.17/d/phobos/std/c/time.d 2004-12-19 18:51:04.000000000 +0100 +++ gdc-0.18/d/phobos/std/c/time.d 2006-05-13 21:05:42.000000000 +0200 @@ -1,12 +1,15 @@ -/* Written by Walter Bright - * www.digitalmars.com - * Placed into public domain. +/** + * C's <time.h> + * Authors: Walter Bright, Digital Mars, www.digitalmars.com + * License: Public Domain + * Macros: + * WIKI=Phobos/StdCString */ module std.c.time; -import std.c.stddef; +private import std.c.stddef; extern (C): diff -uNr gdc-0.17/d/phobos/std/c/windows/windows.d gdc-0.18/d/phobos/std/c/windows/windows.d --- gdc-0.17/d/phobos/std/c/windows/windows.d 2005-08-13 01:51:59.000000000 +0200 +++ gdc-0.18/d/phobos/std/c/windows/windows.d 2006-05-14 04:21:51.000000000 +0200 @@ -2708,4 +2708,11 @@ export int wsprintfA(LPSTR, LPCSTR, ...); export int wsprintfW(LPWSTR, LPCWSTR, ...); + +const uint INFINITE = uint.max; +const uint WAIT_OBJECT_0 = 0; + +export HANDLE CreateSemaphoreA(LPSECURITY_ATTRIBUTES lpSemaphoreAttributes, LONG lInitialCount, LONG lMaximumCount, LPCTSTR lpName); +export HANDLE OpenSemaphoreA(DWORD dwDesiredAccess, BOOL bInheritHandle, LPCTSTR lpName); +export BOOL ReleaseSemaphore(HANDLE hSemaphore, LONG lReleaseCount, LPLONG lpPreviousCount); } diff -uNr gdc-0.17/d/phobos/std/compiler.d gdc-0.18/d/phobos/std/compiler.d --- gdc-0.17/d/phobos/std/compiler.d 2005-10-13 03:06:51.000000000 +0200 +++ gdc-0.18/d/phobos/std/compiler.d 2006-04-16 17:13:30.000000000 +0200 @@ -1,15 +1,15 @@ /** * Macros: - * WIKI = StdCompiler + * WIKI = Phobos/StdCompiler */ -/* Written by Walter Bright - * www.digitalmars.com - * Placed into Public Domain +/** + * Identify the compiler used and its various features. + * Authors: Walter Bright, www.digitalmars.com + * License: Public Domain */ -// Identify the compiler used and its various features. module std.compiler; diff -uNr gdc-0.17/d/phobos/std/conv.d gdc-0.18/d/phobos/std/conv.d --- gdc-0.17/d/phobos/std/conv.d 2005-05-29 23:09:19.000000000 +0200 +++ gdc-0.18/d/phobos/std/conv.d 2006-05-14 03:05:56.000000000 +0200 @@ -1,12 +1,51 @@ -// Written by Walter Bright -// Copyright (c) 2002-2003 Digital Mars -// All Rights Reserved -// www.digitalmars.com -// Some parts contributed by David L. Davis - -// Conversion building blocks. These differ from the C equivalents by -// checking for overflow and not allowing whitespace. +/* + * Copyright (C) 2002-2006 by Digital Mars, www.digitalmars.com + * Written by Walter Bright + * Some parts contributed by David L. Davis + * + * This software is provided 'as-is', without any express or implied + * warranty. In no event will the authors be held liable for any damages + * arising from the use of this software. + * + * Permission is granted to anyone to use this software for any purpose, + * including commercial applications, and to alter it and redistribute it + * freely, subject to the following restrictions: + * + * o The origin of this software must not be misrepresented; you must not + * claim that you wrote the original software. If you use this software + * in a product, an acknowledgment in the product documentation would be + * appreciated but is not required. + * o Altered source versions must be plainly marked as such, and must not + * be misrepresented as being the original software. + * o This notice may not be removed or altered from any source + * distribution. + */ + +/*********** + * Conversion building blocks. These differ from the C equivalents + * atoi() and atol() by + * checking for overflow and not allowing whitespace. + * + * For conversion to signed types, the grammar recognized is: + *
    +$(I Integer):
    +    $(I Sign UnsignedInteger)
    +    $(I UnsignedInteger)
    +
    +$(I Sign):
    +    $(B +)
    +    $(B -)
    + * 
    + * For conversion to signed types, the grammar recognized is: + *
    +$(I UnsignedInteger):
    +    $(I DecimalDigit)
    +    $(I DecimalDigit) $(I UnsignedInteger)
    + * 
    + * Macros: + * WIKI=Phobos/StdConv + */ module std.conv; @@ -18,8 +57,11 @@ //debug=conv; // uncomment to turn on debugging printf's -/************** Exceptions ****************/ +/* ************* Exceptions *************** */ +/** + * Thrown on conversion errors, which happens on deviation from the grammar. + */ class ConvError : Error { this(char[] s) @@ -33,6 +75,9 @@ throw new ConvError(s); } +/** + * Thrown on conversion overflow errors. + */ class ConvOverflowError : Error { this(char[] s) @@ -47,9 +92,7 @@ } /*************************************************************** - * Convert character string to int. - * Grammar: - * ['+'|'-'] digit {digit} + * Convert character string to the return type. */ int toInt(char[] s) @@ -173,9 +216,7 @@ /******************************************************* - * Convert character string to uint. - * Grammar: - * digit {digit} + * ditto */ uint toUint(char[] s) @@ -269,10 +310,8 @@ } } -/*************************************************************** - * Convert character string to long. - * Grammar: - * ['+'|'-'] digit {digit} +/******************************************************* + * ditto */ long toLong(char[] s) @@ -402,9 +441,7 @@ /******************************************************* - * Convert character string to ulong. - * Grammar: - * digit {digit} + * ditto */ ulong toUlong(char[] s) @@ -506,10 +543,8 @@ } -/*************************************************************** - * Convert character string to short. - * Grammar: - * ['+'|'-'] digit {digit} +/******************************************************* + * ditto */ short toShort(char[] s) @@ -592,9 +627,7 @@ /******************************************************* - * Convert character string to ushort. - * Grammar: - * digit {digit} + * ditto */ ushort toUshort(char[] s) @@ -671,10 +704,8 @@ } -/*************************************************************** - * Convert character string to byte. - * Grammar: - * ['+'|'-'] digit {digit} +/******************************************************* + * ditto */ byte toByte(char[] s) @@ -757,9 +788,7 @@ /******************************************************* - * Convert character string to ubyte. - * Grammar: - * digit {digit} + * ditto */ ubyte toUbyte(char[] s) @@ -836,10 +865,22 @@ } -/*************************************************************** - * Convert character string to float. +/******************************************************* + * ditto */ +version (skyos) +{ + float strtof(char * s, char ** ep) { + return strtod(s, ep); + } +} + +static if (real.sizeof > double.sizeof) + private alias strtold _conv_strtold; +else + private alias strtod _conv_strtold; + float toFloat(in char[] s) { float f; @@ -901,8 +942,8 @@ assert(toString(f) == toString(float.nan)); } -/*************************************************************** - * Convert character string to double. +/******************************************************* + * ditto */ double toDouble(in char[] s) @@ -969,10 +1010,8 @@ //assert(cast(real)d == cast(real)double.nan); } -/*************************************************************** - * Convert character string to real. - * Grammar: - * ['+'|'-'] digit {digit} +/******************************************************* + * ditto */ real toReal(in char[] s) { @@ -990,7 +1029,7 @@ // BUG: should set __locale_decpoint to "." for DMC setErrno(0); - f = strtold(sz, &endptr); + f = _conv_strtold(sz, &endptr); if (getErrno() == ERANGE) goto Lerr; if (endptr && (endptr == sz || *endptr != 0)) @@ -1051,8 +1090,8 @@ * Should it match what toString(ifloat) does with the 'i' suffix? */ -/*************************************************************** - * Convert character string to ifloat. +/******************************************************* + * ditto */ ifloat toIfloat(in char[] s) @@ -1089,8 +1128,8 @@ assert(feq(cast(ireal)ift, cast(ireal)ifloat.nan)); } -/*************************************************************** - * Convert character string to idouble. +/******************************************************* + * ditto */ idouble toIdouble(in char[] s) @@ -1128,8 +1167,8 @@ assert(toString(id) == toString(idouble.nan)); } -/*************************************************************** - * Convert character string to ireal. +/******************************************************* + * ditto */ ireal toIreal(in char[] s) @@ -1168,10 +1207,9 @@ assert(toString(ir) == toString(ireal.nan)); } -/*************************************************************** - * Convert character string to cfloat. - * Grammar: - * ['+'|'-'] digit {digit} + +/******************************************************* + * ditto */ cfloat toCfloat(in char[] s) { @@ -1180,7 +1218,7 @@ real r1; real r2; cfloat cf; - bit b = 0; + bool b = 0; char* endptr; if (!s.length) @@ -1193,11 +1231,11 @@ // atof(s1); endptr = &s1[s1.length - 1]; - r1 = strtold(s1, &endptr); + r1 = _conv_strtold(s1, &endptr); // atof(s2); endptr = &s2[s2.length - 1]; - r2 = strtold(s2, &endptr); + r2 = _conv_strtold(s2, &endptr); cf = cast(cfloat)(r1 + (r2 * 1.0i)); @@ -1249,10 +1287,8 @@ assert(feq(cast(creal)cf, cast(creal)cfloat.nan)); } -/*************************************************************** - * Convert character string to cdouble. - * Grammar: - * ['+'|'-'] digit {digit} +/******************************************************* + * ditto */ cdouble toCdouble(in char[] s) { @@ -1261,7 +1297,7 @@ real r1; real r2; cdouble cd; - bit b = 0; + bool b = 0; char* endptr; if (!s.length) @@ -1274,11 +1310,11 @@ // atof(s1); endptr = &s1[s1.length - 1]; - r1 = strtold(s1, &endptr); + r1 = _conv_strtold(s1, &endptr); // atof(s2); endptr = &s2[s2.length - 1]; - r2 = strtold(s2, &endptr); //atof(s2); + r2 = _conv_strtold(s2, &endptr); //atof(s2); cd = cast(cdouble)(r1 + (r2 * 1.0i)); @@ -1326,10 +1362,8 @@ assert(feq(cast(creal)cd, cast(creal)cdouble.nan)); } -/*************************************************************** - * Convert character string to creal. - * Grammar: - * ['+'|'-'] digit {digit} +/******************************************************* + * ditto */ creal toCreal(in char[] s) { @@ -1338,7 +1372,7 @@ real r1; real r2; creal cr; - bit b = 0; + bool b = 0; char* endptr; if (!s.length) @@ -1351,11 +1385,11 @@ // atof(s1); endptr = &s1[s1.length - 1]; - r1 = strtold(s1, &endptr); + r1 = _conv_strtold(s1, &endptr); // atof(s2); endptr = &s2[s2.length - 1]; - r2 = strtold(s2, &endptr); //atof(s2); + r2 = _conv_strtold(s2, &endptr); //atof(s2); //writefln("toCreal() r1=%g, r2=%g, s1=\"%s\", s2=\"%s\", nan=%g", // r1, r2, s1, s2, creal.nan); @@ -1420,12 +1454,12 @@ } -/*************************************************************** +/* ************************************************************** * Splits a complex float (cfloat, cdouble, and creal) into two workable strings. * Grammar: * ['+'|'-'] string floating-point digit {digit} */ -private bit getComplexStrings(in char[] s, out char[] s1, out char[] s2) +private bool getComplexStrings(in char[] s, out char[] s1, out char[] s2) { int len = s.length; @@ -1474,24 +1508,24 @@ // feq() functions now used only in unittesting -/**************************************** +/* *************************************** * Main function to compare reals with given precision */ -private bit feq(in real rx, in real ry, in real precision) +private bool feq(in real rx, in real ry, in real precision) { if (rx == ry) return 1; if (isnan(rx)) - return cast(bit)isnan(ry); + return cast(bool)isnan(ry); if (isnan(ry)) return 0; - return cast(bit)(fabs(rx - ry) <= precision); + return cast(bool)(fabs(rx - ry) <= precision); } -/**************************************** +/* *************************************** * (Note: Copied here from std.math's mfeq() function for unittesting) * Simple function to compare two floating point values * to a specified precision. @@ -1499,24 +1533,24 @@ * 1 match * 0 nomatch */ -private bit feq(in real r1, in real r2) +private bool feq(in real r1, in real r2) { if (r1 == r2) return 1; if (isnan(r1)) - return cast(bit)isnan(r2); + return cast(bool)isnan(r2); if (isnan(r2)) return 0; - return cast(bit)(feq(r1, r2, 0.000001L)); + return cast(bool)(feq(r1, r2, 0.000001L)); } -/**************************************** +/* *************************************** * compare ireals with given precision */ -private bit feq(in ireal r1, in ireal r2) +private bool feq(in ireal r1, in ireal r2) { real rx = cast(real)r1; real ry = cast(real)r2; @@ -1525,7 +1559,7 @@ return 1; if (isnan(rx)) - return cast(bit)isnan(ry); + return cast(bool)isnan(ry); if (isnan(ry)) return 0; @@ -1533,10 +1567,10 @@ return feq(rx, ry, 0.000001L); } -/**************************************** +/* *************************************** * compare creals with given precision */ -private bit feq(in creal r1, in creal r2) +private bool feq(in creal r1, in creal r2) { real r1a = fabs(cast(real)r1.re - cast(real)r2.re); real r2b = fabs(cast(real)r1.im - cast(real)r2.im); @@ -1546,7 +1580,7 @@ return 1; if (isnan(r1a)) - return cast(bit)isnan(r2b); + return cast(bool)isnan(r2b); if (isnan(r2b)) return 0; diff -uNr gdc-0.17/d/phobos/std/cover.d gdc-0.18/d/phobos/std/cover.d --- gdc-0.17/d/phobos/std/cover.d 1970-01-01 01:00:00.000000000 +0100 +++ gdc-0.18/d/phobos/std/cover.d 2006-04-16 17:13:30.000000000 +0200 @@ -0,0 +1,183 @@ +/* + * Copyright (C) 2005-2006 by Digital Mars, www.digitalmars.com + * Written by Walter Bright + * + * This software is provided 'as-is', without any express or implied + * warranty. In no event will the authors be held liable for any damages + * arising from the use of this software. + * + * Permission is granted to anyone to use this software for any purpose, + * including commercial applications, and to alter it and redistribute it + * freely, in both source and binary form, subject to the following + * restrictions: + * + * o The origin of this software must not be misrepresented; you must not + * claim that you wrote the original software. If you use this software + * in a product, an acknowledgment in the product documentation would be + * appreciated but is not required. + * o Altered source versions must be plainly marked as such, and must not + * be misrepresented as being the original software. + * o This notice may not be removed or altered from any source + * distribution. + */ + +/** + * Code coverage analyzer. + * Bugs: + * $(UL + * $(LI the execution counters are 32 bits in size, and can overflow) + * $(LI inline asm statements are not counted) + * ) + * Macros: + * WIKI = Phobos/StdCover + */ + +module std.cover; + +private import std.stdio; +private import std.file; +private import std.bitarray; + +private +{ + struct Cover + { + char[] filename; + BitArray valid; + uint[] data; + } + + Cover[] gdata; + char[] srcpath; + char[] dstpath; + bool merge; +} + +/*********************************** + * Set path to where source files are located. + */ + +void setSourceDir(char[] pathname) +{ + srcpath = pathname; +} + +/*********************************** + * Set path to where listing files are to be written. + */ + +void setDestDir(char[] pathname) +{ + srcpath = pathname; +} + +/*********************************** + * Set merge mode. + * Params: + * flag = true means new data is summed with existing data in the + * listing file; false means a new listing file is always + * created. + */ + +void setMerge(bool flag) +{ + merge = flag; +} + +extern (C) void _d_cover_register(char[] filename, BitArray valid, uint[] data) +{ + //printf("_d_cover_register()\n"); + //printf("\tfilename = '%.*s'\n", filename); + + Cover c; + c.filename = filename; + c.valid = valid; + c.data = data; + + gdata ~= c; +} + +static ~this() +{ + //printf("cover.~this()\n"); + + foreach (Cover c; gdata) + { + //printf("filename = '%.*s'\n", c.filename); + + // Generate source file name + char[] srcfilename = std.path.join(srcpath, c.filename); + + char[] buf = cast(char[])std.file.read(srcfilename); + char[][] lines = std.string.splitlines(buf); + + // Generate listing file name + char[] lstfilename = std.path.addExt(std.path.getBaseName(c.filename), "lst"); + + if (merge && exists(lstfilename) && isfile(lstfilename)) + { + char[] lst = cast(char[])std.file.read(lstfilename); + char[][] lstlines = std.string.splitlines(lst); + + for (size_t i = 0; i < lstlines.length; i++) + { + if (i >= c.data.length) + break; + int count = 0; + foreach (char c; lstlines[i]) + { + switch (c) + { case ' ': + continue; + case '0': case '1': case '2': case '3': case '4': + case '5': case '6': case '7': case '8': case '9': + count = count * 10 + c - '0'; + continue; + default: + break; + } + break; + } + //printf("[%d] %d\n", i, count); + c.data[i] += count; + } + } + + FILE *flst = std.c.stdio.fopen(lstfilename, "wb"); + if (!flst) + throw new std.file.FileException(lstfilename, "cannot open for write"); + + uint nno; + uint nyes; + + for (int i = 0; i < c.data.length; i++) + { + //printf("[%2d] = %u\n", i, c.data[i]); + if (i < lines.length) + { + uint n = c.data[i]; + char[] line = lines[i]; + line = std.string.expandtabs(line); + if (n == 0) + { + if (c.valid[i]) + { nno++; + fwritefln(flst, "0000000|%s", line); + } + else + fwritefln(flst, " |%s", line); + } + else + { nyes++; + fwritefln(flst, "%7s|%s", n, line); + } + } + } + + if (nyes + nno) // no divide by 0 bugs + fwritefln(flst, "%s is %s%% covered", c.filename, (nyes * 100) / (nyes + nno)); + + std.c.stdio.fclose(flst); + } +} + diff -uNr gdc-0.17/d/phobos/std/cstream.d gdc-0.18/d/phobos/std/cstream.d --- gdc-0.17/d/phobos/std/cstream.d 2005-06-22 05:13:40.000000000 +0200 +++ gdc-0.18/d/phobos/std/cstream.d 2006-05-14 03:05:56.000000000 +0200 @@ -1,66 +1,135 @@ -// Written by Ben Hinkle and put in the public domain. +/** + * The std.cstream module bridges std.c.stdio (or std.stdio) and std.stream. + * Both std.c.stdio and std.stream are publicly imported by std.cstream. + * Authors: Ben Hinkle + * License: Public Domain + * Macros: + * WIKI=Phobos/StdCstream + */ + +module std.cstream; import std.stream; import std.c.stdio; -// wraps a FILE* in a stream class +/** + * A Stream wrapper for a C file of type FILE*. + */ class CFile : Stream { FILE* cfile; - // Construct a CFile from the given FILE* with mode and optional seekable state + /** + * Create the stream wrapper for the given C file. + * Params: + * mode = a bitwise combination of $(B FileMode.In) for a readable file + * and $(B FileMode.Out) for a writeable file. + * seekable = indicates if the stream should be _seekable. + */ this(FILE* cfile, FileMode mode, bool seekable = false) { super(); this.file = cfile; - readable = cast(bit)(mode & FileMode.In); - writeable = cast(bit)(mode & FileMode.Out); + readable = cast(bool)(mode & FileMode.In); + writeable = cast(bool)(mode & FileMode.Out); this.seekable = seekable; } + /** + * Closes the stream. + */ ~this() { close(); } + /** + * Property to get or set the underlying file for this stream. + * Setting the file marks the stream as open. + */ FILE* file() { return cfile; } + + /** + * Ditto + */ void file(FILE* cfile) { this.cfile = cfile; isopen = true; } + /** + * Overrides of the $(B Stream) methods to call the underlying $(B FILE*) + * C functions. + */ override void flush() { fflush(cfile); } + + /** + * Ditto + */ override void close() { if (isopen) fclose(cfile); isopen = readable = writeable = seekable = false; } + + /** + * Ditto + */ override bool eof() { return cast(bool)(readEOF || feof(cfile)); } + + /** + * Ditto + */ override char getc() { return cast(char)fgetc(cfile); } + + /** + * Ditto + */ override char ungetc(char c) { return cast(char)std.c.stdio.ungetc(c,cfile); } + + /** + * Ditto + */ override size_t readBlock(void* buffer, size_t size) { size_t n = fread(buffer,1,size,cfile); - readEOF = cast(bit)(n == 0); + readEOF = cast(bool)(n == 0); return n; } + + /** + * Ditto + */ override size_t writeBlock(void* buffer, size_t size) { return fwrite(buffer,1,size,cfile); } + + /** + * Ditto + */ override ulong seek(long offset, SeekPos rel) { readEOF = false; if (fseek(cfile,cast(int)offset,rel) != 0) throw new SeekException("unable to move file pointer"); return ftell(cfile); } + + /** + * Ditto + */ override void writeLine(char[] s) { writeString(s); writeString("\n"); } + + /** + * Ditto + */ override void writeLineW(wchar[] s) { writeStringW(s); writeStringW("\n"); } + // run a few tests unittest { FILE* f = fopen("stream.txt","w"); @@ -135,8 +204,20 @@ } } -// standard IO devices -CFile din, dout, derr; +/** + * CFile wrapper of std.c.stdio.stdin (not seekable). + */ +CFile din; + +/** + * CFile wrapper of std.c.stdio.stdout (not seekable). + */ +CFile dout; + +/** + * CFile wrapper of std.c.stdio.stderr (not seekable). + */ +CFile derr; static this() { // open standard I/O devices diff -uNr gdc-0.17/d/phobos/std/ctype.d gdc-0.18/d/phobos/std/ctype.d --- gdc-0.17/d/phobos/std/ctype.d 2005-04-28 23:12:43.000000000 +0200 +++ gdc-0.18/d/phobos/std/ctype.d 2006-05-14 03:05:56.000000000 +0200 @@ -1,44 +1,87 @@ - /* - * Copyright (C) 2004-2005 by Digital Mars, www.digitalmars.com - * Written by Walter Bright - * - * This software is provided 'as-is', without any express or implied - * warranty. In no event will the authors be held liable for any damages - * arising from the use of this software. - * - * Permission is granted to anyone to use this software for any purpose, - * including commercial applications, and to alter it and redistribute it - * freely, in both source and binary form, subject to the following - * restrictions: - * - * o The origin of this software must not be misrepresented; you must not - * claim that you wrote the original software. If you use this software - * in a product, an acknowledgment in the product documentation would be - * appreciated but is not required. - * o Altered source versions must be plainly marked as such, and must not - * be misrepresented as being the original software. - * o This notice may not be removed or altered from any source - * distribution. + * Placed into the Public Domain. + * Digital Mars, www.digitalmars.com + * Written by Walter Bright */ -// Simple ASCII char classification functions +/** + * Simple ASCII character classification functions. + * For Unicode classification, see $(LINK2 std_uni.html, std.uni). + * References: + * $(LINK2 http://www.digitalmars.com/d/ascii-table.html, ASCII Table), + * $(LINK2 http://en.wikipedia.org/wiki/Ascii, Wikipedia) + * Macros: + * WIKI=Phobos/StdCtype + */ module std.ctype; +/** + * Returns !=0 if c is a letter in the range (0..9, a..z, A..Z). + */ int isalnum(dchar c) { return (c <= 0x7F) ? _ctype[c] & (_ALP|_DIG) : 0; } + +/** + * Returns !=0 if c is an ascii upper or lower case letter. + */ int isalpha(dchar c) { return (c <= 0x7F) ? _ctype[c] & (_ALP) : 0; } + +/** + * Returns !=0 if c is a control character. + */ int iscntrl(dchar c) { return (c <= 0x7F) ? _ctype[c] & (_CTL) : 0; } + +/** + * Returns !=0 if c is a digit. + */ int isdigit(dchar c) { return (c <= 0x7F) ? _ctype[c] & (_DIG) : 0; } + +/** + * Returns !=0 if c is lower case ascii letter. + */ int islower(dchar c) { return (c <= 0x7F) ? _ctype[c] & (_LC) : 0; } + +/** + * Returns !=0 if c is a punctuation character. + */ int ispunct(dchar c) { return (c <= 0x7F) ? _ctype[c] & (_PNC) : 0; } + +/** + * Returns !=0 if c is a space, tab, vertical tab, form feed, + * carriage return, or linefeed. + */ int isspace(dchar c) { return (c <= 0x7F) ? _ctype[c] & (_SPC) : 0; } + +/** + * Returns !=0 if c is an upper case ascii character. + */ int isupper(dchar c) { return (c <= 0x7F) ? _ctype[c] & (_UC) : 0; } + +/** + * Returns !=0 if c is a hex digit (0..9, a..f, A..F). + */ int isxdigit(dchar c) { return (c <= 0x7F) ? _ctype[c] & (_HEX) : 0; } + +/** + * Returns !=0 if c is a printing character except for the space character. + */ int isgraph(dchar c) { return (c <= 0x7F) ? _ctype[c] & (_ALP|_DIG|_PNC) : 0; } + +/** + * Returns !=0 if c is a printing character except for the space character. + */ int isprint(dchar c) { return (c <= 0x7F) ? _ctype[c] & (_ALP|_DIG|_PNC|_BLK) : 0; } + +/** + * Returns !=0 if c is in the ascii character set, i.e. in the range 0..0x7F. + */ int isascii(dchar c) { return c <= 0x7F; } + +/** + * If c is an upper case ascii character, + * return the lower case equivalent, otherwise return c. + */ dchar tolower(dchar c) out (result) { @@ -49,6 +92,11 @@ return isupper(c) ? c + (cast(dchar)'a' - 'A') : c; } + +/** + * If c is a lower case ascii character, + * return the upper case equivalent, otherwise return c. + */ dchar toupper(dchar c) out (result) { diff -uNr gdc-0.17/d/phobos/std/date.d gdc-0.18/d/phobos/std/date.d --- gdc-0.17/d/phobos/std/date.d 2005-11-28 05:17:52.000000000 +0100 +++ gdc-0.18/d/phobos/std/date.d 2006-05-14 04:21:51.000000000 +0200 @@ -3,8 +3,11 @@ * Dates are represented in several formats. The date implementation revolves * around a central type, d_time, from which other formats are converted to and * from. + * Dates are calculated using the Gregorian calendar. + * References: + * $(LINK2 http://en.wikipedia.org/wiki/Gregorian_calendar, Gregorian calendar (Wikipedia)) * Macros: - * WIKI = StdDate + * WIKI = Phobos/StdDate */ // Copyright (c) 1999-2005 by Digital Mars @@ -38,21 +41,25 @@ /** * A value for d_time that does not represent a valid time. */ -d_time d_time_nan = long.min; +const d_time d_time_nan = long.min; +/** + * Time broken down into its components. + */ struct Date { - int year = int.min; // our "nan" Date value - int month; // 1..12 - int day; // 1..31 - int hour; // 0..23 - int minute; // 0..59 - int second; // 0..59 - int ms; // 0..999 - int weekday; // 0: not specified - // 1..7: Sunday..Saturday - int tzcorrection = int.min; // -1200..1200 correction in hours + int year = int.min; /// use int.min as "nan" year value + int month; /// 1..12 + int day; /// 1..31 + int hour; /// 0..23 + int minute; /// 0..59 + int second; /// 0..59 + int ms; /// 0..999 + int weekday; /// 0: not specified + /// 1..7: Sunday..Saturday + int tzcorrection = int.min; /// -1200..1200 correction in hours + /// Parse date out of string s[] and store it in this Date instance. void parse(char[] s) { DateParse dp; @@ -81,11 +88,13 @@ const char[] daystr = "SunMonTueWedThuFriSat"; const char[] monstr = "JanFebMarAprMayJunJulAugSepOctNovDec"; -int mdays[12] = [ 0,31,59,90,120,151,181,212,243,273,304,334 ]; +const int[12] mdays = [ 0,31,59,90,120,151,181,212,243,273,304,334 ]; /******************************** * Compute year and week [1..53] from t. The ISO 8601 week 1 is the first week * of the year that includes January 4. Monday is the first day of the week. + * References: + * $(LINK2 http://en.wikipedia.org/wiki/ISO_8601, ISO 8601 (Wikipedia)) */ void toISO8601YearWeek(d_time t, out int year, out int week) @@ -222,11 +231,17 @@ return cast(d_time)msPerDay * DayFromYear(y); } +/***************************** + * Calculates the year from the d_time t. + */ + int YearFromTime(d_time t) { int y; // Hazard a guess - y = 1970 + cast(int) (t / (365.2425 * msPerDay)); + //y = 1970 + cast(int) (t / (365.2425 * msPerDay)); + // Use integer only math + y = 1970 + cast(int) (t / (3652425 * (msPerDay / 10000))); if (TimeFromYear(y) <= t) { @@ -244,11 +259,30 @@ return y; } +/******************************* + * Determines if d_time t is a leap year. + * + * A leap year is every 4 years except years ending in 00 that are not + * divsible by 400. + * + * Returns: !=0 if it is a leap year. + * + * References: + * $(LINK2 http://en.wikipedia.org/wiki/Leap_year, Wikipedia) + */ + int inLeapYear(d_time t) { return LeapYear(YearFromTime(t)); } +/***************************** + * Calculates the month from the d_time t. + * + * Returns: Integer in the range 0..11, where + * 0 represents January and 11 represents December. + */ + int MonthFromTime(d_time t) { int day; @@ -298,14 +332,17 @@ else if (day < 365) month = 11; else - { assert(0); - month = -1; // keep /W4 happy - } + assert(0); } } return month; } +/******************************* + * Compute which day in a month a d_time t is. + * Returns: + * Integer in the range 1..31 + */ int DateFromTime(d_time t) { int day; @@ -334,11 +371,16 @@ case 11: date = day - 333 - leap; break; default: assert(0); - date = -1; // keep /W4 happy } return date; } +/******************************* + * Compute which day of the week a d_time t is. + * Returns: + * Integer in the range 0..6, where 0 represents Sunday + * and 6 represents Saturday. + */ int WeekDay(d_time t) { int w; @@ -366,7 +408,8 @@ return t - LocalTZA - DaylightSavingTA(t - LocalTZA); } -d_time MakeTime(int hour, int min, int sec, int ms) + +d_time MakeTime(d_time hour, d_time min, d_time sec, d_time ms) { return hour * TicksPerHour + min * TicksPerMinute + @@ -375,7 +418,7 @@ } -d_time MakeDay(int year, int month, int date) +d_time MakeDay(d_time year, d_time month, d_time date) { d_time t; int y; int m; @@ -659,6 +702,14 @@ //return c.time.time(null) * TicksPerSecond; } + static d_time FILETIME2d_time(FILETIME *ft) + { SYSTEMTIME st; + + if (!FileTimeToSystemTime(ft, &st)) + return d_time_nan; + return SYSTEMTIME2d_time(&st, 0); + } + static d_time SYSTEMTIME2d_time(SYSTEMTIME *st, d_time t) { d_time n; diff -uNr gdc-0.17/d/phobos/std/demangle.d gdc-0.18/d/phobos/std/demangle.d --- gdc-0.17/d/phobos/std/demangle.d 2005-11-28 05:17:52.000000000 +0100 +++ gdc-0.18/d/phobos/std/demangle.d 2006-04-16 17:13:30.000000000 +0200 @@ -5,6 +5,12 @@ */ /**** * Demangle D mangled names. + * Macros: + * WIKI = Phobos/StdDemangle + */ + +/* Author: + * Walter Bright, Digital Mars, www.digitalmars.com */ module std.demangle; @@ -39,7 +45,7 @@ int main() { char[] buffer; - bit inword; + bool inword; int c; while ((c = fgetc(stdin)) != EOF) @@ -119,7 +125,7 @@ name[ni + 2] == 'T') { size_t nisave = ni; - bit err; + bool err; ni += 3; try { @@ -169,6 +175,7 @@ { case 'v': p = "void"; goto L1; case 'b': p = "bit"; goto L1; + case 'x': p = "bool"; goto L1; case 'g': p = "byte"; goto L1; case 'h': p = "ubyte"; goto L1; case 's': p = "short"; goto L1; diff -uNr gdc-0.17/d/phobos/std/file.d gdc-0.18/d/phobos/std/file.d --- gdc-0.17/d/phobos/std/file.d 2005-11-28 05:17:52.000000000 +0100 +++ gdc-0.18/d/phobos/std/file.d 2006-05-14 03:16:44.000000000 +0200 @@ -1,6 +1,6 @@ /** * Macros: - * WIKI = StdFile + * WIKI = Phobos/StdFile */ /* @@ -29,15 +29,17 @@ /* NOTE: This file has been patched from the original DMD distribution to work with the GDC compiler. - Modified by David Friedman, September 2004 + Modified by David Friedman, March 2006 */ module std.file; private import std.c.stdio; private import std.c.stdlib; +private import std.c.string; private import std.path; private import std.string; +private import std.regexp; /* =========================== Win32 ======================= */ @@ -48,6 +50,7 @@ private import std.utf; private import std.windows.syserror; private import std.windows.charset; +private import std.date; int useWfuncs = 1; @@ -89,6 +92,8 @@ /******************************************** * Read file name[], return array of bytes read. + * Throws: + * FileException on error. */ void[] read(char[] name) @@ -141,6 +146,7 @@ /********************************************* * Write buffer[] to file name[]. + * Throws: FileException on error. */ void write(char[] name, void[] buffer) @@ -182,6 +188,7 @@ /********************************************* * Append buffer[] to file name[]. + * Throws: FileException on error. */ void append(char[] name, void[] buffer) @@ -225,6 +232,7 @@ /*************************************************** * Rename file from[] to to[]. + * Throws: FileException on error. */ void rename(char[] from, char[] to) @@ -242,6 +250,7 @@ /*************************************************** * Delete file name[]. + * Throws: FileException on error. */ void remove(char[] name) @@ -259,6 +268,7 @@ /*************************************************** * Get size of file name[]. + * Throws: FileException on error. */ ulong getSize(char[] name) @@ -312,6 +322,7 @@ /*************************************************** * Get file name[] attributes. + * Throws: FileException on error. */ uint getAttributes(char[] name) @@ -330,7 +341,8 @@ } /**************************************************** - * Is name[] a file? Error if name[] doesn't exist. + * Is name[] a file? + * Throws: FileException if name[] doesn't exist. */ int isfile(char[] name) @@ -339,7 +351,8 @@ } /**************************************************** - * Is name[] a directory? Error if name[] doesn't exist. + * Is name[] a directory? + * Throws: FileException if name[] doesn't exist. */ int isdir(char[] name) @@ -349,6 +362,7 @@ /**************************************************** * Change directory to pathname[]. + * Throws: FileException on error. */ void chdir(char[] pathname) @@ -367,6 +381,7 @@ /**************************************************** * Make directory pathname[]. + * Throws: FileException on error. */ void mkdir(char[] pathname) @@ -385,6 +400,7 @@ /**************************************************** * Remove directory pathname[]. + * Throws: FileException on error. */ void rmdir(char[] pathname) @@ -403,6 +419,7 @@ /**************************************************** * Get current directory. + * Throws: FileException on error. */ char[] getcwd() @@ -414,7 +431,7 @@ wchar c; len = GetCurrentDirectoryW(0, &c); - if (!len) + if (!len) goto Lerr; dir = new wchar[len]; len = GetCurrentDirectoryW(len, dir); @@ -443,7 +460,91 @@ } /*************************************************** + * Directory Entry + */ + +struct DirEntry +{ + char[] name; /// file or directory name + ulong size = ~0UL; /// size of file in bytes + d_time creationTime = d_time_nan; /// time of file creation + d_time lastAccessTime = d_time_nan; /// time file was last accessed + d_time lastWriteTime = d_time_nan; /// time file was last written to + uint attributes; // Windows file attributes OR'd together + + void init(char[] path, WIN32_FIND_DATA *fd) + { + wchar[] wbuf; + size_t clength; + size_t wlength; + size_t n; + + clength = std.string.strlen(fd.cFileName); + + // Convert cFileName[] to unicode + wlength = MultiByteToWideChar(0,0,fd.cFileName,clength,null,0); + if (wlength > wbuf.length) + wbuf.length = wlength; + n = MultiByteToWideChar(0,0,fd.cFileName,clength,cast(wchar*)wbuf,wlength); + assert(n == wlength); + // toUTF8() returns a new buffer + name = std.path.join(path, std.utf.toUTF8(wbuf[0 .. wlength])); + + size = (cast(ulong)fd.nFileSizeHigh << 32) | fd.nFileSizeLow; + creationTime = std.date.FILETIME2d_time(&fd.ftCreationTime); + lastAccessTime = std.date.FILETIME2d_time(&fd.ftLastAccessTime); + lastWriteTime = std.date.FILETIME2d_time(&fd.ftLastWriteTime); + attributes = fd.dwFileAttributes; + } + + void init(char[] path, WIN32_FIND_DATAW *fd) + { + size_t clength = std.string.wcslen(fd.cFileName); + name = std.path.join(path, std.utf.toUTF8(fd.cFileName[0 .. clength])); + size = (cast(ulong)fd.nFileSizeHigh << 32) | fd.nFileSizeLow; + creationTime = std.date.FILETIME2d_time(&fd.ftCreationTime); + lastAccessTime = std.date.FILETIME2d_time(&fd.ftLastAccessTime); + lastWriteTime = std.date.FILETIME2d_time(&fd.ftLastWriteTime); + attributes = fd.dwFileAttributes; + } + + /**** + * Return !=0 if DirEntry is a directory. + */ + int isdir() + { + return attributes & FILE_ATTRIBUTE_DIRECTORY; + } + + /**** + * Return !=0 if DirEntry is a file. + */ + int isfile() + { + return !(attributes & FILE_ATTRIBUTE_DIRECTORY); + } +} + + +/*************************************************** * Return contents of directory pathname[]. + * The names in the contents do not include the pathname. + * Throws: FileException on error + * Example: + * This program lists all the files and subdirectories in its + * path argument. + * ---- + * import std.stdio; + * import std.file; + * + * void main(char[][] args) + * { + * char[][] dirs = std.file.listdir(args[1]); + * + * foreach (char[] d; dirs) + * writefln(d); + * } + * ---- */ char[][] listdir(char[] pathname) @@ -460,10 +561,165 @@ return result; } + +/***************************************************** + * Return all the files in the directory and its subdirectories + * that match pattern or regular expression r. + * Params: + * pathname = Directory name + * pattern = String with wildcards, such as $(RED "*.d"). The supported + * wildcard strings are described under fnmatch() in + * $(LINK2 std_path.html, std.path). + * r = Regular expression, for more powerful _pattern matching. + * Example: + * This program lists all the files with a "d" extension in + * the path passed as the first argument. + * ---- + * import std.stdio; + * import std.file; + * + * void main(char[][] args) + * { + * char[][] d_source_files = std.file.listdir(args[1], "*.d"); + * + * foreach (char[] d; d_source_files) + * writefln(d); + * } + * ---- + * A regular expression version that searches for all files with "d" or + * "obj" extensions: + * ---- + * import std.stdio; + * import std.file; + * import std.regexp; + * + * void main(char[][] args) + * { + * char[][] d_source_files = std.file.listdir(args[1], RegExp(r"\.(d|obj)$")); + * + * foreach (char[] d; d_source_files) + * writefln(d); + * } + * ---- + */ + +char[][] listdir(char[] pathname, char[] pattern) +{ char[][] result; + + bool callback(DirEntry* de) + { + if (de.isdir) + listdir(de.name, &callback); + else + { if (std.path.fnmatch(de.name, pattern)) + result ~= de.name; + } + return true; // continue + } + + listdir(pathname, &callback); + return result; +} + +/** Ditto */ + +char[][] listdir(char[] pathname, RegExp r) +{ char[][] result; + + bool callback(DirEntry* de) + { + if (de.isdir) + listdir(de.name, &callback); + else + { if (r.test(de.name)) + result ~= de.name; + } + return true; // continue + } + + listdir(pathname, &callback); + return result; +} + +/****************************************************** + * For each file and directory name in pathname[], + * pass it to the callback delegate. + * Params: + * callback = Delegate that processes each + * filename in turn. Returns true to + * continue, false to stop. + * Example: + * This program lists all the files in its + * path argument, including the path. + * ---- + * import std.stdio; + * import std.path; + * import std.file; + * + * void main(char[][] args) + * { + * char[] pathname = args[1]; + * char[][] result; + * + * bool listing(char[] filename) + * { + * result ~= std.path.join(pathname, filename); + * return true; // continue + * } + * + * listdir(pathname, &listing); + * + * foreach (char[] name; result) + * writefln("%s", name); + * } + * ---- + */ + void listdir(char[] pathname, bool delegate(char[] filename) callback) { + bool listing(DirEntry* de) + { + return callback(std.path.getBaseName(de.name)); + } + + listdir(pathname, &listing); +} + +/****************************************************** + * For each file and directory DirEntry in pathname[], + * pass it to the callback delegate. + * Params: + * callback = Delegate that processes each + * DirEntry in turn. Returns true to + * continue, false to stop. + * Example: + * This program lists all the files in its + * path argument and all subdirectories thereof. + * ---- + * import std.stdio; + * import std.file; + * + * void main(char[][] args) + * { + * bool callback(DirEntry* de) + * { + * if (de.isdir) + * listdir(de.name, &callback); + * else + * writefln(de.name); + * return true; + * } + * + * listdir(args[1], &callback); + * } + * ---- + */ + +void listdir(char[] pathname, bool delegate(DirEntry* de) callback) +{ char[] c; HANDLE h; + DirEntry de; c = std.path.join(pathname, "*.*"); if (useWfuncs) @@ -473,20 +729,24 @@ h = FindFirstFileW(std.utf.toUTF16z(c), &fileinfo); if (h != INVALID_HANDLE_VALUE) { - do - { int clength; - - // Skip "." and ".." - if (std.string.wcscmp(fileinfo.cFileName, ".") == 0 || - std.string.wcscmp(fileinfo.cFileName, "..") == 0) - continue; - - clength = std.string.wcslen(fileinfo.cFileName); - // toUTF8() returns a new buffer - if (!callback(std.utf.toUTF8(fileinfo.cFileName[0 .. clength]))) - break; - } while (FindNextFileW(h,&fileinfo) != FALSE); - FindClose(h); + try + { + do + { + // Skip "." and ".." + if (std.string.wcscmp(fileinfo.cFileName, ".") == 0 || + std.string.wcscmp(fileinfo.cFileName, "..") == 0) + continue; + + de.init(pathname, &fileinfo); + if (!callback(&de)) + break; + } while (FindNextFileW(h,&fileinfo) != FALSE); + } + finally + { + FindClose(h); + } } } else @@ -496,30 +756,24 @@ h = FindFirstFileA(toMBSz(c), &fileinfo); if (h != INVALID_HANDLE_VALUE) // should we throw exception if invalid? { - wchar[] wbuf; - do - { int clength; - int wlength; - int n; - - // Skip "." and ".." - if (std.string.strcmp(fileinfo.cFileName, ".") == 0 || - std.string.strcmp(fileinfo.cFileName, "..") == 0) - continue; - - clength = std.string.strlen(fileinfo.cFileName); - - // Convert cFileName[] to unicode - wlength = MultiByteToWideChar(0,0,fileinfo.cFileName,clength,null,0); - if (wlength > wbuf.length) - wbuf.length = wlength; - n = MultiByteToWideChar(0,0,fileinfo.cFileName,clength,cast(wchar*)wbuf,wlength); - assert(n == wlength); - // toUTF8() returns a new buffer - if (!callback(std.utf.toUTF8(wbuf[0 .. wlength]))) - break; - } while (FindNextFileA(h,&fileinfo) != FALSE); - FindClose(h); + try + { + do + { + // Skip "." and ".." + if (std.string.strcmp(fileinfo.cFileName, ".") == 0 || + std.string.strcmp(fileinfo.cFileName, "..") == 0) + continue; + + de.init(pathname, &fileinfo); + if (!callback(&de)) + break; + } while (FindNextFileA(h,&fileinfo) != FALSE); + } + finally + { + FindClose(h); + } } } } @@ -559,29 +813,14 @@ /* =========================== linux ======================= */ -// else version (GNU) -/* - { - version (Unix) { - private import std.c.unix.unix; - } - } - */ - -version (linux) { - version = Unix; -} - -version (Unix) +// version (linux) +else version (Unix) { - version (GNU) { - private import std.c.unix.unix; - alias std.c.unix.unix unix; - } else version (linux) { - private import std.c.linux.linux; - alias std.c.linux.linux unix; - } +private import std.c.unix.unix; +private import std.date; + +alias std.c.unix.unix unix; extern (C) char* strerror(int); @@ -929,10 +1168,115 @@ buf[] = p[0 .. len]; std.c.stdlib.free(p); return buf; - } + } + +} + +/*************************************************** + * Directory Entry + */ + +struct DirEntry +{ + char[] name; /// file or directory name + ulong _size = ~0UL; // size of file in bytes + d_time _creationTime = d_time_nan; // time of file creation + d_time _lastAccessTime = d_time_nan; // time file was last accessed + d_time _lastWriteTime = d_time_nan; // time file was last written to + version (GNU) + typeof(struct_stat.st_mode) _st_mode; + else + ubyte d_type; + ubyte didstat; // done lazy evaluation of stat() + + void init(char[] path, dirent *fd) + { size_t len = std.string.strlen(fd.d_name); + name = std.path.join(path, fd.d_name[0 .. len]); + version(GNU) + { } + else + d_type = fd.d_type; + didstat = 0; + } + + int isdir() + { + version(GNU) + { + if (!didstat) + doStat(); + return (_st_mode & S_IFMT) == S_IFDIR; + } + else + return d_type & DT_DIR; + } + + int isfile() + { + version(GNU) + { + if (!didstat) + doStat(); + return (_st_mode & S_IFMT) == S_IFREG; + } + else + return d_type & DT_REG; + } + + ulong size() + { + if (!didstat) + doStat(); + return _size; + } + + d_time creationTime() + { + if (!didstat) + doStat(); + return _creationTime; + } + + d_time lastAccessTime() + { + if (!didstat) + doStat(); + return _lastAccessTime; + } + + d_time lastWriteTime() + { + if (!didstat) + doStat(); + return _lastWriteTime; + } + + /* This is to support lazy evaluation, because doing stat's is + * expensive and not always needed. + */ + void doStat() + { + int fd; + struct_stat statbuf; + char* namez; + + namez = toStringz(name); + if (std.c.unix.unix.stat(namez, &statbuf)) + { + //printf("\tstat error, errno = %d\n",getErrno()); + return; + } + _size = statbuf.st_size; + _creationTime = statbuf.st_ctime * std.date.TicksPerSecond; + _lastAccessTime = statbuf.st_atime * std.date.TicksPerSecond; + _lastWriteTime = statbuf.st_mtime * std.date.TicksPerSecond; + _st_mode = statbuf.st_mode; + didstat = 1; + } } + /*************************************************** * Return contents of directory. */ @@ -951,26 +1295,79 @@ return result; } +char[][] listdir(char[] pathname, char[] pattern) +{ char[][] result; + + bool callback(DirEntry* de) + { + if (de.isdir) + listdir(de.name, &callback); + else + { if (std.path.fnmatch(de.name, pattern)) + result ~= de.name; + } + return true; // continue + } + + listdir(pathname, &callback); + return result; +} + +char[][] listdir(char[] pathname, RegExp r) +{ char[][] result; + + bool callback(DirEntry* de) + { + if (de.isdir) + listdir(de.name, &callback); + else + { if (r.test(de.name)) + result ~= de.name; + } + return true; // continue + } + + listdir(pathname, &callback); + return result; +} + void listdir(char[] pathname, bool delegate(char[] filename) callback) { + bool listing(DirEntry* de) + { + return callback(std.path.getBaseName(de.name)); + } + + listdir(pathname, &listing); +} + +void listdir(char[] pathname, bool delegate(DirEntry* de) callback) +{ DIR* h; dirent* fdata; - + DirEntry de; + h = opendir(toStringz(pathname)); if (h) { - while((fdata = readdir(h)) != null) + try { - // Skip "." and ".." - if (!std.string.strcmp(fdata.d_name, ".") || - !std.string.strcmp(fdata.d_name, "..")) - continue; - - int len = std.string.strlen(fdata.d_name); - if (!callback(fdata.d_name[0 .. len].dup)) - break; + while((fdata = readdir(h)) != null) + { + // Skip "." and ".." + if (!std.string.strcmp(fdata.d_name, ".") || + !std.string.strcmp(fdata.d_name, "..")) + continue; + + de.init(pathname, fdata); + if (!callback(&de)) + break; + } + } + finally + { + closedir(h); } - closedir(h); } else { @@ -980,16 +1377,15 @@ /*************************************************** * Copy a file. + * Bugs: + * If the file is very large, this won't work. + * Doesn't maintain the file timestamps. */ void copy(char[] from, char[] to) { void[] buffer; - /* If the file is very large, this won't work, but - * it's a good start. - * BUG: it should maintain the file timestamps - */ buffer = read(from); write(to, buffer); delete buffer; diff -uNr gdc-0.17/d/phobos/std/format.d gdc-0.18/d/phobos/std/format.d --- gdc-0.17/d/phobos/std/format.d 2005-12-02 02:00:23.000000000 +0100 +++ gdc-0.18/d/phobos/std/format.d 2006-05-21 23:37:42.000000000 +0200 @@ -3,7 +3,7 @@ * It's comparable to C99's vsprintf(). * * Macros: - * WIKI = StdFormat + * WIKI = Phobos/StdFormat */ /* @@ -36,6 +36,7 @@ private import std.utf; private import std.c.stdlib; +private import std.c.string; private import std.string; version (Windows) @@ -53,8 +54,11 @@ version (DigitalMarsC) { // This is DMC's internal floating point formatting function - extern (C) char* function(int c, int flags, int precision, real* pdval, - char* buf, int* psl, int width) __pfloatfmt; + extern (C) + { + extern char* function(int c, int flags, int precision, real* pdval, + char* buf, int* psl, int width) __pfloatfmt; + } } else { @@ -85,6 +89,7 @@ { Tvoid = 'v', Tbit = 'b', + Tbool = 'x', Tbyte = 'g', Tubyte = 'h', Tshort = 's', @@ -128,12 +133,15 @@ private TypeInfo primitiveTypeInfo(Mangle m) { TypeInfo ti; + switch (m) { case Mangle.Tvoid: ti = typeid(void);break; case Mangle.Tbit: ti = typeid(bit);break; + case Mangle.Tbool: + ti = typeid(bool);break; case Mangle.Tbyte: ti = typeid(byte);break; case Mangle.Tubyte: @@ -329,7 +337,7 @@
    The corresponding argument is formatted in a manner consistent with its type:
    -
    $(B bit) +
    $(B bool)
    The result is 'true' or 'false'.
    integral types
    The $(B %d) format is used. @@ -355,7 +363,7 @@ and is formatted as an integer. If the argument is a signed type and the $(I FormatChar) is $(B d) it is converted to a signed string of characters, otherwise it is treated as - unsigned. An argument of type $(B bit) is formatted as '1' + unsigned. An argument of type $(B bool) is formatted as '1' or '0'. The base used is binary for $(B b), octal for $(B o), decimal for $(B d), and hexadecimal for $(B x) or $(B X). @@ -387,7 +395,7 @@ The $(B f) format is used if the exponent for an $(B e) format is greater than -5 and less than the $(I Precision). The $(I Precision) specifies the number of significant - digits, and defaults to one. + digits, and defaults to six. Trailing zeros are elided after the decimal point, if the fractional part is zero then no decimal point is generated. @@ -461,7 +469,7 @@ void formatArg(char fc) { - bit vbit; + bool vbit; ulong vnumber; char vchar; dchar vdchar; @@ -613,7 +621,8 @@ switch (m) { case Mangle.Tbit: - vbit = va_arg!(bit)(argptr); + case Mangle.Tbool: + vbit = va_arg!(bool)(argptr); if (fc != 's') { vnumber = vbit; goto Lnumber; @@ -700,7 +709,8 @@ goto Lputstr; case Mangle.Tpointer: - vnumber = cast(ulong)va_arg!(void*)(argptr); + vnumber = cast(size_t)va_arg!(void*)(argptr); + uc = 1; flags |= FL0pad; if (!(flags & FLprecision)) { flags |= FLprecision; @@ -713,14 +723,22 @@ case Mangle.Tfloat: case Mangle.Tifloat: if (fc == 'x' || fc == 'X') - goto Luint; + { + float f = va_arg!(float)(argptr); + vnumber = *cast(uint*)&f; + goto Lnumber; + } vreal = va_arg!(float)(argptr); goto Lreal; case Mangle.Tdouble: case Mangle.Tidouble: if (fc == 'x' || fc == 'X') - goto Lulong; + { + double f = va_arg!(double)(argptr); + vnumber = *cast(ulong*)&f; + goto Lnumber; + } vreal = va_arg!(double)(argptr); goto Lreal; @@ -766,6 +784,8 @@ dchar[] sd = va_arg!(dchar[])(argptr); s = toUTF8(sd); Lputstr: + if (fc != 's') + throw new FormatError("string"); if (flags & FLprecision && precision < s.length) s = s[0 .. precision]; putstr(s); @@ -794,7 +814,8 @@ switch (m) { case Mangle.Tbit: - vbit = *cast(bit*)(p_args); p_args += bit.sizeof; // int.sizeof, etc.? + case Mangle.Tbool: + vbit = *cast(bool*)(p_args); p_args += bool.sizeof; // int.sizeof, etc.? if (fc != 's') { vnumber = vbit; goto Lnumber; @@ -882,7 +903,8 @@ case Mangle.Tpointer: alias void * void_ponter_t; - vnumber = cast(ulong)*cast(void**)p_args; p_args += void_ponter_t.sizeof; + vnumber = cast(size_t)*cast(void**)p_args; p_args += void_ponter_t.sizeof; + uc = 1; flags |= FL0pad; if (!(flags & FLprecision)) { flags |= FLprecision; @@ -949,6 +971,8 @@ dchar[] sd = *cast(dchar[]*)p_args; p_args += array_t.sizeof; s = toUTF8(sd); PLputstr: + if (fc != 's') + throw new FormatError("string"); if (flags & FLprecision && precision < s.length) s = s[0 .. precision]; putstr(s); @@ -1020,10 +1044,31 @@ goto Lerror; } + if (!signed) + { + switch (m) + { + case Mangle.Tbyte: + vnumber &= 0xFF; + break; + + case Mangle.Tshort: + vnumber &= 0xFFFF; + break; + + case Mangle.Tint: + vnumber &= 0xFFFFFFFF; + break; + + default: + break; + } + } + if (flags & FLprecision && fc != 'p') flags &= ~FL0pad; - if (vnumber < 10) + if (vnumber < base) { if (vnumber == 0 && precision == 0 && flags & FLprecision && !(fc == 'o' && flags & FLhash)) @@ -1031,7 +1076,7 @@ putstr(null); return; } - if (vnumber < base) + if (precision == 0 || !(flags & FLprecision)) { vchar = '0' + vnumber; goto L2; } @@ -1335,6 +1380,9 @@ s = std.string.format("%7.4g:", 12.678); assert(s == " 12.68:"); + s = std.string.format("%7.4g:", 12.678L); + assert(s == " 12.68:"); + s = std.string.format("%04f|%05d|%#05x|%#5x",-4.,-10,1,1); assert(s == "-4.000000|-0010|0x001| 0x1"); @@ -1385,15 +1433,61 @@ r = std.string.format("%8s", s[0..5]); assert(r == " hello"); - int[] arr = new int[4]; - arr[0] = 100; - arr[1] = -999; - arr[3] = 0; - r = std.string.format(arr); + byte[] arrbyte = new byte[4]; + arrbyte[0] = 100; + arrbyte[1] = -99; + arrbyte[3] = 0; + r = std.string.format(arrbyte); + assert(r == "[100,-99,0,0]"); + + ubyte[] arrubyte = new ubyte[4]; + arrubyte[0] = 100; + arrubyte[1] = 200; + arrubyte[3] = 0; + r = std.string.format(arrubyte); + assert(r == "[100,200,0,0]"); + + short[] arrshort = new short[4]; + arrshort[0] = 100; + arrshort[1] = -999; + arrshort[3] = 0; + r = std.string.format(arrshort); + assert(r == "[100,-999,0,0]"); + r = std.string.format("%s",arrshort); + assert(r == "[100,-999,0,0]"); + + ushort[] arrushort = new ushort[4]; + arrushort[0] = 100; + arrushort[1] = 20_000; + arrushort[3] = 0; + r = std.string.format(arrushort); + assert(r == "[100,20000,0,0]"); + + int[] arrint = new int[4]; + arrint[0] = 100; + arrint[1] = -999; + arrint[3] = 0; + r = std.string.format(arrint); assert(r == "[100,-999,0,0]"); - r = std.string.format("%s",arr); + r = std.string.format("%s",arrint); assert(r == "[100,-999,0,0]"); + long[] arrlong = new long[4]; + arrlong[0] = 100; + arrlong[1] = -999; + arrlong[3] = 0; + r = std.string.format(arrlong); + assert(r == "[100,-999,0,0]"); + r = std.string.format("%s",arrlong); + assert(r == "[100,-999,0,0]"); + + ulong[] arrulong = new ulong[4]; + arrulong[0] = 100; + arrulong[1] = 999; + arrulong[3] = 0; + r = std.string.format(arrulong); + assert(r == "[100,999,0,0]"); + char[][] arr2 = new char[][4]; arr2[0] = "hello"; arr2[1] = "world"; @@ -1401,5 +1495,94 @@ r = std.string.format(arr2); assert(r == "[hello,world,,foo]"); + r = std.string.format("%.8d", 7); + assert(r == "00000007"); + r = std.string.format("%.8x", 10); + assert(r == "0000000a"); + + r = std.string.format("%-3d", 7); + assert(r == "7 "); + + r = std.string.format("%*d", -3, 7); + assert(r == "7 "); + + r = std.string.format("%.*d", -3, 7); + assert(r == "7"); + + typedef int myint; + myint m = -7; + r = std.string.format(m); + assert(r == "-7"); + + r = std.string.format("abc"c); + assert(r == "abc"); + r = std.string.format("def"w); + assert(r == "def"); + r = std.string.format("ghi"d); + assert(r == "ghi"); + + void* p = cast(void*)0xDEADBEEF; + r = std.string.format(p); + assert(r == "DEADBEEF"); + + r = std.string.format("%#x", 0xabcd); + assert(r == "0xabcd"); + r = std.string.format("%#X", 0xABCD); + assert(r == "0XABCD"); + + r = std.string.format("%#o", 012345); + assert(r == "012345"); + r = std.string.format("%o", 9); + assert(r == "11"); + + r = std.string.format("%+d", 123); + assert(r == "+123"); + r = std.string.format("%+d", -123); + assert(r == "-123"); + r = std.string.format("% d", 123); + assert(r == " 123"); + r = std.string.format("% d", -123); + assert(r == "-123"); + + r = std.string.format("%%"); + assert(r == "%"); + + r = std.string.format("%d", true); + assert(r == "1"); + r = std.string.format("%d", false); + assert(r == "0"); + + r = std.string.format("%d", 'a'); + assert(r == "97"); + wchar wc = 'a'; + r = std.string.format("%d", wc); + assert(r == "97"); + dchar dc = 'a'; + r = std.string.format("%d", dc); + assert(r == "97"); + + byte b = byte.max; + r = std.string.format("%x", b); + assert(r == "7f"); + r = std.string.format("%x", ++b); + assert(r == "80"); + r = std.string.format("%x", ++b); + assert(r == "81"); + + short sh = short.max; + r = std.string.format("%x", sh); + assert(r == "7fff"); + r = std.string.format("%x", ++sh); + assert(r == "8000"); + r = std.string.format("%x", ++sh); + assert(r == "8001"); + + i = int.max; + r = std.string.format("%x", i); + assert(r == "7fffffff"); + r = std.string.format("%x", ++i); + assert(r == "80000000"); + r = std.string.format("%x", ++i); + assert(r == "80000001"); } diff -uNr gdc-0.17/d/phobos/std/gc.d gdc-0.18/d/phobos/std/gc.d --- gdc-0.17/d/phobos/std/gc.d 2005-04-28 23:12:43.000000000 +0200 +++ gdc-0.18/d/phobos/std/gc.d 2006-05-14 03:05:56.000000000 +0200 @@ -1,21 +1,75 @@ -// Copyright (c) 1999-2003 by Digital Mars -// All Rights Reserved -// written by Walter Bright -// www.digitalmars.com +/* + * Copyright (C) 1999-2006 by Digital Mars, www.digitalmars.com + * Written by Walter Bright + * + * This software is provided 'as-is', without any express or implied + * warranty. In no event will the authors be held liable for any damages + * arising from the use of this software. + * + * Permission is granted to anyone to use this software for any purpose, + * including commercial applications, and to alter it and redistribute it + * freely, subject to the following restrictions: + * + * o The origin of this software must not be misrepresented; you must not + * claim that you wrote the original software. If you use this software + * in a product, an acknowledgment in the product documentation would be + * appreciated but is not required. + * o Altered source versions must be plainly marked as such, and must not + * be misrepresented as being the original software. + * o This notice may not be removed or altered from any source + * distribution. + */ + + +/** + * The garbage collector normally works behind the scenes without needing any + * specific interaction. These functions are for advanced applications that + * benefit from tuning the operation of the collector. + * Macros: + * WIKI=Phobos/StdGc + */ module std.gc; import gcstats; +/** + * Add p to list of roots. Roots are references to memory allocated by the + collector that are maintained in memory outside the collector pool. The garbage + collector will by default look for roots in the stacks of each thread, the + registers, and the default static data segment. If roots are held elsewhere, + use addRoot() or addRange() to tell the collector not to free the memory it + points to. + */ void addRoot(void *p); // add p to list of roots + +/** + * Remove p from list of roots. + */ void removeRoot(void *p); // remove p from list of roots +/** + * Add range to scan for roots. + */ void addRange(void *pbot, void *ptop); // add range to scan for roots + +/** + * Remove range. + */ void removeRange(void *pbot); // remove range /*********************************** * Run a full garbage collection cycle. + * + * The collector normally runs synchronously with a storage allocation request + (i.e. it never happens when in code that does not allocate memory). In some + circumstances, for example when a particular task is finished, it is convenient + to explicitly run the collector and free up all memory used by that task. It + can also be helpful to run a collection before starting a new task that would + be annoying if it ran a collection in the middle of that task. Explicitly + running a collection can also be done in a separate very low priority thread, + so that if the program is idly waiting for input, memory can be cleaned up. */ void fullCollect(); @@ -27,17 +81,31 @@ */ void genCollect(); + void genCollectNoStack(); -void minimize(); // minimize physical memory usage +/** + * Minimizes physical memory usage + */ +void minimize(); /*************************************** - * Disable and enable collections. They must be - * a matched pair, and can nest. + * disable() temporarilly disables garbage collection cycle, enable() + * then reenables them. + * + * This is used for brief time + critical sections of code, so the amount of time it will take is predictable. + If the collector runs out of memory while it is disabled, it will throw an + OutOfMemory exception. The disable() function calls can be nested, but must be + matched with corresponding enable() calls. * By default collections are enabled. */ void disable(); + +/** + * ditto + */ void enable(); void getStats(out GCStats stats); diff -uNr gdc-0.17/d/phobos/std/intrinsic.d gdc-0.18/d/phobos/std/intrinsic.d --- gdc-0.17/d/phobos/std/intrinsic.d 2004-12-19 18:51:04.000000000 +0100 +++ gdc-0.18/d/phobos/std/intrinsic.d 2006-05-14 03:05:56.000000000 +0200 @@ -1,33 +1,80 @@ -// Copyright (c) 1999-2003 by Digital Mars -// All Rights Reserved // written by Walter Bright // www.digitalmars.com +// Placed into the public domain /* NOTE: This file has been patched from the original DMD distribution to work with the GDC compiler. - Modified by David Friedman, September 2004 + Modified by David Friedman, May 2006 */ -/* These functions are built-in intrinsics to the compiler. +/** These functions are built-in intrinsics to the compiler. + * + Intrinsic functions are functions built in to the compiler, + usually to take advantage of specific CPU features that + are inefficient to handle via external functions. + The compiler's optimizer and code generator are fully + integrated in with intrinsic functions, bringing to bear + their full power on them. + This can result in some surprising speedups. + * Macros: + * WIKI=Phobos/StdIntrinsic */ module std.intrinsic; +/** + * Scans the bits in v starting with bit 0, looking + * for the first set bit. + * Returns: + * The bit number of the first bit set. + * The return value is undefined if v is zero. + */ version (GNU) -{ -int bsf(uint v) -{ - uint m = 1; - uint i; - for (i = 0; i < 32; i++,m<<=1) { - if (v&m) - return i; + int bsf(uint v) + { + uint m = 1; + uint i; + for (i = 0; i < 32; i++,m<<=1) { + if (v&m) + return i; + } + return i; // supposed to be undefined } - return i; // supposed to be undefined -} +else + int bsf(uint v); + +/** + * Scans the bits in v from the most significant bit + * to the least significant bit, looking + * for the first set bit. + * Returns: + * The bit number of the first bit set. + * The return value is undefined if v is zero. + * Example: + * --- + * import std.intrinsic; + * + * int main() + * { + * uint v; + * int x; + * + * v = 0x21; + * x = bsf(v); + * printf("bsf(x%x) = %d\n", v, x); + * x = bsr(v); + * printf("bsr(x%x) = %d\n", v, x); + * return 0; + * } + * --- + * Output: + * bsf(x21) = 0
    + * bsr(x21) = 5 + */ +version (GNU) int bsr(uint v) { uint m = 0x80000000; @@ -38,60 +85,180 @@ } return i; // supposed to be undefined } +else + int bsr(uint v); + +/** + * Tests the bit. + */ +version (GNU) int bt(uint *p, uint bitnum) { - return (*p & (1<btc(array, 35)); + printf("array = [0]:x%x, [1]:x%x\n", array[0], array[1]); + + printf("btc(array, 35) = %d\n", btc(array, 35)); + printf("array = [0]:x%x, [1]:x%x\n", array[0], array[1]); + + printf("bts(array, 35) = %d\n", bts(array, 35)); + printf("array = [0]:x%x, [1]:x%x\n", array[0], array[1]); + + printf("btr(array, 35) = %d\n", btr(array, 35)); + printf("array = [0]:x%x, [1]:x%x\n", array[0], array[1]); + + printf("bt(array, 1) = %d\n", bt(array, 1)); + printf("array = [0]:x%x, [1]:x%x\n", array[0], array[1]); + + return 0; +} + * --- + * Output: +
    +btc(array, 35) = 0
    +array = [0]:x2, [1]:x108
    +btc(array, 35) = -1
    +array = [0]:x2, [1]:x100
    +bts(array, 35) = 0
    +array = [0]:x2, [1]:x108
    +btr(array, 35) = -1
    +array = [0]:x2, [1]:x100
    +bt(array, 1) = -1
    +array = [0]:x2, [1]:x100
    +
    + */ +version (GNU) int bts(uint *p, uint bitnum) { - int result = *p & (1<>>8)|((v&0xFF000000)>>>24); } +else + uint bswap(uint v); -ubyte inp(uint p) { return 0; } -ushort inpw(uint p) { return 0; } -uint inpl(uint p) { return 0; } -ubyte outp(uint p, ubyte v) { return v; } -ushort outpw(uint p, ushort v) { return v; } -uint outpl(uint p, uint v) { return v; } -} +/** + * Reads I/O port at port_address. + */ +version (GNU) + ubyte inp(uint p) { return 0; } else -{ -int bsf(uint v); -int bsr(uint v); -int bt(uint *p, uint bitnum); -int btc(uint *p, uint bitnum); -int btr(uint *p, uint bitnum); -int bts(uint *p, uint bitnum); + ubyte inp(uint port_address); -uint bswap(uint v); +/** + * ditto + */ +version (GNU) + ushort inpw(uint p) { return 0; } +else + ushort inpw(uint port_address); -ubyte inp(uint); -ushort inpw(uint); -uint inpl(uint); - -ubyte outp(uint, ubyte); -ushort outpw(uint, ushort); -uint outpl(uint, uint); -} +/** + * ditto + */ +version (GNU) + uint inpl(uint p) { return 0; } +else + uint inpl(uint port_address); + + +/** + * Writes and returns value to I/O port at port_address. + */ +version (GNU) + ubyte outp(uint p, ubyte v) { return v; } +else + ubyte outp(uint port_address, ubyte value); + +/** + * ditto + */ +version (GNU) + ushort outpw(uint p, ushort v) { return v; } +else + ushort outpw(uint port_address, ushort value); + +/** + * ditto + */ +version (GNU) + uint outpl(uint p, uint v) { return v; } +else + uint outpl(uint port_address, uint value); diff -uNr gdc-0.17/d/phobos/std/loader.d gdc-0.18/d/phobos/std/loader.d --- gdc-0.17/d/phobos/std/loader.d 2005-08-12 04:32:44.000000000 +0200 +++ gdc-0.18/d/phobos/std/loader.d 2006-05-26 02:06:43.000000000 +0200 @@ -8,7 +8,7 @@ * * Author: Matthew Wilson * - * License: (Licensed under the Synesis Software Standard Source License) + * License: * * Copyright (C) 2002-2004, Synesis Software Pty Ltd. * @@ -20,25 +20,19 @@ * email: submissions@synsoft.org for submissions * admin@synsoft.org for other enquiries * - * Redistribution and use in source and binary forms, with or - * without modification, are permitted provided that the following - * conditions are met: - * - * (i) Redistributions of source code must retain the above - * copyright notice and contact information, this list of - * conditions and the following disclaimer. - * - * (ii) Any derived versions of this software (howsoever modified) - * remain the sole property of Synesis Software. - * - * (iii) Any derived versions of this software (howsoever modified) - * remain subject to all these conditions. - * - * (iv) Neither the name of Synesis Software nor the names of any - * subdivisions, employees or agents of Synesis Software, nor the - * names of any other contributors to this software may be used to - * endorse or promote products derived from this software without - * specific prior written permission. + * Permission is granted to anyone to use this software for any purpose, + * including commercial applications, and to alter it and redistribute it + * freely, in both source and binary form, subject to the following + * restrictions: + * + * - The origin of this software must not be misrepresented; you must not + * claim that you wrote the original software. If you use this software + * in a product, an acknowledgment in the product documentation would be + * appreciated but is not required. + * - Altered source versions must be plainly marked as such, and must not + * be misrepresented as being the original software. + * - This notice may not be removed or altered from any source + * distribution. * * This source code is provided by Synesis Software "as is" and any * warranties, whether expressed or implied, including, but not @@ -101,6 +95,7 @@ */ private import std.string; +private import std.c.string; private import std.c.stdlib; private import std.c.stdio; diff -uNr gdc-0.17/d/phobos/std/math2.d gdc-0.18/d/phobos/std/math2.d --- gdc-0.17/d/phobos/std/math2.d 2005-11-27 17:28:26.000000000 +0100 +++ gdc-0.18/d/phobos/std/math2.d 2006-04-16 17:13:30.000000000 +0200 @@ -30,12 +30,12 @@ * compare floats with given precision */ -bit feq(real a, real b) +bool feq(real a, real b) { return feq(a, b, 0.000001); } -bit feq(real a, real b, real eps) +bool feq(real a, real b, real eps) { return abs(a - b) <= eps; } @@ -689,6 +689,7 @@ * Hyperbolic arccosine */ +/+ real acosh(real x) { if (x <= 1) @@ -704,11 +705,13 @@ assert(acosh(0.5) == 0); assert(feq(acosh(std.math.cosh(3)), 3)); } ++/ /************************************* * Hyperbolic arcsine */ +/+ real asinh(real x) { if (!x) @@ -731,11 +734,12 @@ assert(asinh(0) == 0); assert(feq(asinh(std.math.sinh(3)), 3)); } ++/ /************************************* * Hyperbolic arctangent */ - +/+ real atanh(real x) { if (!x) @@ -758,6 +762,7 @@ assert(atanh(0) == 0); assert(feq(atanh(std.math.tanh(0.5)), 0.5)); } ++/ /************************************* * Hyperbolic arccotangent @@ -804,7 +809,7 @@ while (s[i] == '\t' || s[i] == ' ') if (++i >= s.length) return real.nan; - bit neg = false; + bool neg = false; if (s[i] == '-') { neg = true; @@ -814,7 +819,7 @@ i++; if (i >= s.length) return real.nan; - bit hex; + bool hex; if (s[s.length - 1] == 'h') { hex = true; @@ -902,7 +907,7 @@ } if (++i >= s.length) return real.nan; - bit eneg = false; + bool eneg = false; if (s[i] == '-') { eneg = true; diff -uNr gdc-0.17/d/phobos/std/math.d gdc-0.18/d/phobos/std/math.d --- gdc-0.17/d/phobos/std/math.d 2005-11-27 17:28:26.000000000 +0100 +++ gdc-0.18/d/phobos/std/math.d 2006-04-26 05:23:05.000000000 +0200 @@ -2,16 +2,22 @@ /** * Macros: - * WIKI = StdMath + * WIKI = Phobos/StdMath * * TABLE_SV = * * $0
    Special Values
    + * SVH = $(TR $(TH $1) $(TH $2)) + * SV = $(TR $(TD $1) $(TD $2)) * * NAN = $(RED NAN) * SUP = $0 * GAMMA = Γ * INTEGRAL = ∫ + * INTEGRATE = $(BIG ∫$(SMALL $1)$2) + * POWER = $1$2 + * BIGSUM = $(BIG Σ $2$(SMALL $1)) + * CHOOSE = $(BIG () $(SMALL $1)$(SMALL $2) $(BIG )) */ /* @@ -68,10 +74,6 @@ // Some functions are missing from msvcrt... version (Windows) version = GNU_msvcrt_math; - - version (X86) - version (D_InlineAsm) - version = UseAsmX86; } class NotImplemented : Error @@ -114,6 +116,80 @@ /*********************************** + * Calculates the absolute value + * + * For complex numbers, abs(z) = sqrt( $(POWER z.re, 2) + $(POWER z.im, 2) ) + * = hypot(z.re, z.im). + */ +real abs(real x) +{ + return fabs(x); +} + +/** ditto */ +long abs(long x) +{ + return x>=0 ? x : -x; +} + +/** ditto */ +int abs(int x) +{ + return x>=0 ? x : -x; +} + +/** ditto */ +real abs(creal z) +{ + return hypot(z.re, z.im); +} + +/** ditto */ +real abs(ireal y) +{ + return fabs(y.im); +} + + +unittest +{ + assert(isPosZero(abs(-0.0L))); + assert(isnan(abs(real.nan))); + assert(abs(-real.infinity) == real.infinity); + assert(abs(-3.2Li) == 3.2L); + assert(abs(71.6Li) == 71.6L); + assert(abs(-56) == 56); + assert(abs(2321312L) == 2321312L); + assert(mfeq(abs(-1+1i), sqrt(2.0), .0000001)); +} + +/*********************************** + * Complex conjugate + * + * conj(x + iy) = x - iy + * + * Note that z * conj(z) = $(POWER z.re, 2) - $(POWER z.im, 2) + * is always a real number + */ +creal conj(creal z) +{ + return z.re - z.im*1i; +} + +/** ditto */ +ireal conj(ireal y) +{ + return -y; +} + +unittest +{ + assert(conj(7 + 3i) == 7-3i); + ireal z = -3.2Li; + assert(conj(z) == -z); +} + +/*********************************** * Returns cosine of x. x is in radians. * * $(TABLE_SV @@ -121,6 +197,8 @@ * $(TR $(TD $(NAN)) $(TD $(NAN)) $(TD yes) ) * $(TR $(TD ±∞) $(TD $(NAN)) $(TD yes) ) * ) + * Bugs: + * Results are undefined if |x| >= $(POWER 2,64). */ version(GNU) alias gcc.config.cosl cos; else @@ -135,6 +213,8 @@ * ±0.0 ±0.0 no * ±∞ $(NAN) yes * ) + * Bugs: + * Results are undefined if |x| >= $(POWER 2,64). */ version(GNU) alias gcc.config.sinl sin; else @@ -345,6 +425,105 @@ //real asinh(real x) { return std.c.math.asinhl(x); } //real atanh(real x) { return std.c.math.atanhl(x); } +/*********************************** + * Calculates the inverse hyperbolic cosine of x. + * + * Mathematically, acosh(x) = log(x + sqrt( x*x - 1)) + * + * $(TABLE_DOMRG + * $(DOMAIN 1..∞) + * $(RANGE 1..log(real.max), ∞) ) + * $(TABLE_SV + * $(SVH x, acosh(x) ) + * $(SV $(NAN), $(NAN) ) + * $(SV <1, $(NAN) ) + * $(SV 1, 0 ) + * $(SV +∞,+∞) + * ) + */ +real acosh(real x) +{ + if (x > 1/real.epsilon) + return LN2 + log(x); + else + return log(x + sqrt(x*x - 1)); +} + +unittest +{ + assert(isnan(acosh(0.9))); + assert(isnan(acosh(real.nan))); + assert(acosh(1)==0.0); + assert(acosh(real.infinity) == real.infinity); +} + +/*********************************** + * Calculates the inverse hyperbolic sine of x. + * + * Mathematically, + * --------------- + * asinh(x) = log( x + sqrt( x*x + 1 )) // if x >= +0 + * asinh(x) = -log(-x + sqrt( x*x + 1 )) // if x <= -0 + * ------------- + * + * $(TABLE_SV + * $(SVH x, asinh(x) ) + * $(SV $(NAN), $(NAN) ) + * $(SV ±0, ±0 ) + * $(SV ±∞,±∞) + * ) + */ +real asinh(real x) +{ + if (fabs(x) > 1 / real.epsilon) // beyond this point, x*x + 1 == x*x + return copysign(LN2 + log(fabs(x)), x); + else + { + // sqrt(x*x + 1) == 1 + x * x / ( 1 + sqrt(x*x + 1) ) + return copysign(log1p(fabs(x) + x*x / (1 + sqrt(x*x + 1)) ), x); + } +} + +unittest +{ + assert(isPosZero(asinh(0.0))); + assert(isNegZero(asinh(-0.0))); + assert(asinh(real.infinity) == real.infinity); + assert(asinh(-real.infinity) == -real.infinity); + assert(isnan(asinh(real.nan))); +} + +/*********************************** + * Calculates the inverse hyperbolic tangent of x, + * returning a value from ranging from -1 to 1. + * + * Mathematically, atanh(x) = log( (1+x)/(1-x) ) / 2 + * + * + * $(TABLE_DOMRG + * $(DOMAIN -∞..∞) + * $(RANGE -1..1) ) + * $(TABLE_SV + * $(SVH x, acosh(x) ) + * $(SV $(NAN), $(NAN) ) + * $(SV ±0, ±0) + * $(SV -∞, -0) + * ) + */ +real atanh(real x) +{ + // log( (1+x)/(1-x) ) == log ( 1 + (2*x)/(1-x) ) + return copysign(0.5 * log1p( 2 * x / (1 - x) ), x); +} + +unittest +{ + assert(isPosZero(atanh(0.0))); + assert(isNegZero(atanh(-0.0))); + assert(isnan(atanh(real.nan))); + //assert(isNegZero(atanh(-real.infinity))); +} + /***************************************** * Returns x rounded to a long value using the current rounding mode. * If the integer value of x is @@ -684,9 +863,9 @@ * If x is subnormal, it is treated as if it were normalized. * For a positive, finite x: * - *
    - * 1 <= x * FLT_RADIX$(SUP -logb(x)) < FLT_RADIX 
    - * 
    + * ----- + * 1 <= $(I x) * FLT_RADIX$(SUP -logb(x)) < FLT_RADIX + * ----- * * $(TABLE_SV * x logb(x) Divide by 0? @@ -903,14 +1082,13 @@ * Returns the base e (2.718...) logarithm of the absolute * value of the gamma function of the argument. * - * For reals, lgamma is equivalent to log(fabs(tgamma(x))). + * For reals, lgamma is equivalent to log(fabs(gamma(x))). * * $(TABLE_SV - * x log$(GAMMA)(x) invalid? - * NaN NaN yes + * x lgamma(x) invalid? + * $(NAN) $(NAN) yes * integer <= 0 +∞ yes - * 1, 2 +0.0 no - * ±∞ +∞ no + * ±∞ +∞ no * ) */ /* Documentation prepared by Don Clugston */ @@ -922,26 +1100,28 @@ } /*********************************** - * The gamma function, $(GAMMA)(x) + * The Gamma function, $(GAMMA)(x) * - * Generalizes the factorial function to real and complex numbers. + * $(GAMMA)(x) is a generalisation of the factorial function + * to real and complex numbers. * Like x!, $(GAMMA)(x+1) = x*$(GAMMA)(x). * * Mathematically, if z.re > 0 then * $(GAMMA)(z) =$(INTEGRAL)0tz-1e-tdt * * $(TABLE_SV - * x $(GAMMA)(x) invalid? - * NAN NAN yes - * ±0.0 ±∞ yes - * integer > 0 (x-1)! no - * integer < 0 NAN yes - * +∞ +∞ no - * -∞ NAN yes + * x $(GAMMA)(x) invalid? + * $(NAN) $(NAN) yes + * ±0.0 ±∞ yes + * integer > 0 (x-1)! no + * integer < 0 $(NAN) yes + * +∞ +∞ no + * -∞ $(NAN) yes * ) * * References: - * cephes, $(LINK http://en.wikipedia.org/wiki/Gamma_function) + * $(LINK http://en.wikipedia.org/wiki/Gamma_function), + * $(LINK http://www.netlib.org/cephes/ldoubdoc.html#gamma) */ /* Documentation prepared by Don Clugston */ version (GNU_Need_tgamma) @@ -1062,7 +1242,7 @@ /**************************************************** * Returns the integer portion of x, dropping the fractional portion. * - * This is also know as "chop" rounding. + * This is also known as "chop" rounding. */ version (GNU_Need_trunc) { @@ -1649,15 +1829,21 @@ return fabs(x - y) <= precision; } -version (X86) +// Returns true if x is +0.0 (This function is used in unit tests) +bool isPosZero(real x) { -// These routines assume Intel 80-bit floating point format + return (x == 0) && (signbit(x) == 0); +} -private int iabs(int i) +// Returns true if x is -0.0 (This function is used in unit tests) +bool isNegZero(real x) { - return i >= 0 ? i : -i; + return (x == 0) && signbit(x); } - + +version (X86) +{ +// These routines assume Intel 80-bit floating point format /************************************** * To what precision is x equal to y? @@ -1779,60 +1965,64 @@ } body { - version (none/*D_InlineAsm*/) + version (D_InlineAsm_X86) { - asm // assembler by W. Bright + // GCC always allocates 12 bytes for extended float + version (none) { - // EDX = (A.length - 1) * real.sizeof - mov ECX,A[EBP] ; // ECX = A.length - dec ECX ; - lea EDX,[ECX][ECX*8] ; - add EDX,ECX ; - add EDX,A+4[EBP] ; - fld real ptr [EDX] ; // ST0 = coeff[ECX] - jecxz return_ST ; - fld x[EBP] ; // ST0 = x - fxch ST(1) ; // ST1 = x, ST0 = r - align 4 ; - L2: fmul ST,ST(1) ; // r *= x - fld real ptr -10[EDX] ; - sub EDX,10 ; // deg-- - faddp ST(1),ST ; - dec ECX ; - jne L2 ; - fxch ST(1) ; // ST1 = r, ST0 = x - fstp ST(0) ; // dump x - align 4 ; - return_ST: ; - ; + asm // assembler by W. Bright + { + // EDX = (A.length - 1) * real.sizeof + mov ECX,A[EBP] ; // ECX = A.length + dec ECX ; + lea EDX,[ECX][ECX*8] ; + add EDX,ECX ; + add EDX,A+4[EBP] ; + fld real ptr [EDX] ; // ST0 = coeff[ECX] + jecxz return_ST ; + fld x[EBP] ; // ST0 = x + fxch ST(1) ; // ST1 = x, ST0 = r + align 4 ; + L2: fmul ST,ST(1) ; // r *= x + fld real ptr -10[EDX] ; + sub EDX,10 ; // deg-- + faddp ST(1),ST ; + dec ECX ; + jne L2 ; + fxch ST(1) ; // ST1 = r, ST0 = x + fstp ST(0) ; // dump x + align 4 ; + return_ST: ; + ; + } } - } - else version (UseAsmX86) - { - asm // above code with modifications for GCC + else { - // EDX = (A.length - 1) * real.sizeof - mov ECX,A[EBP] ; // ECX = A.length - dec ECX ; - lea EDX,[ECX][ECX*2] ; - lea EDX,[EDX*4] ; - add EDX,A+4[EBP] ; - fld real ptr [EDX] ; // ST0 = coeff[ECX] - jecxz return_ST ; - fld x ; // ST0 = x - fxch ST(1) ; // ST1 = x, ST0 = r - align 4 ; - L2: fmul ST,ST(1) ; // r *= x - fld real ptr -12[EDX] ; - sub EDX,12 ; // deg-- - faddp ST(1),ST ; - dec ECX ; - jne L2 ; - fxch ST(1) ; // ST1 = r, ST0 = x - fstp ST(0) ; // dump x - align 4 ; - return_ST: ; - ; + asm // above code with modifications for GCC + { + // EDX = (A.length - 1) * real.sizeof + mov ECX,A[EBP] ; // ECX = A.length + dec ECX ; + lea EDX,[ECX][ECX*2] ; + lea EDX,[EDX*4] ; + add EDX,A+4[EBP] ; + fld real ptr [EDX] ; // ST0 = coeff[ECX] + jecxz return_ST ; + fld x ; // ST0 = x + fxch ST(1) ; // ST1 = x, ST0 = r + align 4 ; + L2: fmul ST,ST(1) ; // r *= x + fld real ptr -12[EDX] ; + sub EDX,12 ; // deg-- + faddp ST(1),ST ; + dec ECX ; + jne L2 ; + fxch ST(1) ; // ST1 = r, ST0 = x + fstp ST(0) ; // dump x + align 4 ; + return_ST: ; + ; + } } } else diff -uNr gdc-0.17/d/phobos/std/md5.d gdc-0.18/d/phobos/std/md5.d --- gdc-0.17/d/phobos/std/md5.d 2005-10-24 23:48:04.000000000 +0200 +++ gdc-0.18/d/phobos/std/md5.d 2006-05-14 01:38:32.000000000 +0200 @@ -19,7 +19,7 @@ * $(LINK2 http://en.wikipedia.org/wiki/Md5, Wikipedia on MD5) * * Macros: - * WIKI = StdMd5 + * WIKI = Phobos/StdMd5 */ /++++++++++++++++++++++++++++++++ @@ -30,9 +30,11 @@ // RSA Data Security, Inc. MD5 Message-Digest Algorithm. import std.md5; -import std.string; -import std.c.stdio; -import std.stdio; + +private import std.stdio; +private import std.string; +private import std.c.stdio; +private import std.c.string; int main(char[][] args) { @@ -55,7 +57,7 @@ else { context.start(); - while ((len = fread(buffer, 1, buffer.size, file)) != 0) + while ((len = fread(buffer, 1, buffer.sizeof, file)) != 0) context.update(buffer[0 .. len]); context.finish(digest); fclose(file); @@ -267,7 +269,7 @@ /* Transform as many times as possible. */ if (inputLen >= partLen) { - memcpy(&buffer[index], input, partLen); + std.c.string.memcpy(&buffer[index], input, partLen); transform (buffer); for (i = partLen; i + 63 < inputLen; i += 64) @@ -280,7 +282,7 @@ /* Buffer remaining input */ if (inputLen - i) - memcpy(&buffer[index], &input[i], inputLen-i); + std.c.string.memcpy(&buffer[index], &input[i], inputLen-i); } /** MD5 finalization. Ends an MD5 message-digest operation, writing the @@ -309,7 +311,7 @@ Encode (digest, state, 16); /* Zeroize sensitive information. */ - memset (this, 0, MD5_CTX.sizeof); + std.c.string.memset (this, 0, MD5_CTX.sizeof); } /* MD5 basic transformation. Transforms state based on block. diff -uNr gdc-0.17/d/phobos/std/mmfile.d gdc-0.18/d/phobos/std/mmfile.d --- gdc-0.17/d/phobos/std/mmfile.d 2005-10-02 16:17:55.000000000 +0200 +++ gdc-0.18/d/phobos/std/mmfile.d 2006-05-14 04:21:51.000000000 +0200 @@ -1,11 +1,13 @@ // Copyright (c) 2004 by Digital Mars // All Rights Reserved -// written by Walter Bright and Matthew Wilson (Sysesis Software Pty Ltd.) +// written by Walter Bright and Matthew Wilson (Synesis Software Pty Ltd.) // www.digitalmars.com // www.synesis.com.au/software -/* - * Memory mapped files. +/** + * Read and write memory mapped files. + * Macros: + * WIKI=Phobos/StdMmfile */ /* NOTE: This file has been patched from the original DMD distribution to @@ -35,35 +37,75 @@ { // http://msdn.microsoft.com/library/default.asp?url=/library/en-us/sysinfo/base/getversion.asp dwVersion = GetVersion(); } + + private const bool Have_MMFile = true; // private for now... } else version (Unix) { - private import std.c.unix.unix; - alias std.c.unix.unix unix; + version (GNU_Unix_Have_MMap) + { + private import std.c.unix.unix; + alias std.c.unix.unix unix; + + version = unix_mm; + private const bool Have_MMFile = true; + } + else + { + private const bool Have_MMFile = false; + } + } else { - static assert(0); + private const bool Have_MMFile = false; + // Can't simply fail because std.stream imports this module. + //static assert(0); } - +/** + * MmFile objects control the memory mapped file resource. + */ class MmFile { + /** + * The mode the memory mapped file is opened with. + */ enum Mode - { Read, // read existing file - ReadWriteNew, // delete existing file, write new file - ReadWrite, // read/write existing file, create if not existing - ReadCopyOnWrite, // read/write existing file, copy on write + { Read, /// read existing file + ReadWriteNew, /// delete existing file, write new file + ReadWrite, /// read/write existing file, create if not existing + ReadCopyOnWrite, /// read/write existing file, copy on write } - /* Open for reading + /** + * Open memory mapped file filename for reading. + * File is closed when the object instance is deleted. + * Throws: + * std.file.FileException */ this(char[] filename) { this(filename, Mode.Read, 0, null); } - /* Open + /** + * Open memory mapped file filename in mode. + * File is closed when the object instance is deleted. + * Params: + * filename = name of the file. + * If null, an anonymous file mapping is created. + * mode = access mode defined above. + * size = the size of the file. If 0, it is taken to be the + * size of the existing file. + * address = the preferred address to map the file to, + * although the system is not required to honor it. + * If null, the system selects the most convenient address. + * window = preferred block size of the amount of data to map at one time + * with 0 meaning map the entire file. The window size must be a + * multiple of the memory allocation page size. + * Throws: + * std.file.FileException */ this(char[] filename, Mode mode, ulong size, void* address, size_t window = 0) @@ -185,7 +227,7 @@ errNo(); } - else version (Unix) + else version (unix_mm) { char* namez = toStringz(filename); void* p; @@ -266,7 +308,11 @@ errNo(); } - data = p[0 .. size]; + data = p[0 .. initial_map]; + } + else static if (! Have_MMFile) + { + throw new FileException("This system does support memory mapped files"); } else { @@ -274,6 +320,9 @@ } } + /** + * Flushes pending output and closes the memory mapped file. + */ ~this() { debug (MMFILE) printf("MmFile.~this()\n"); @@ -288,12 +337,15 @@ errNo(); hFile = INVALID_HANDLE_VALUE; } - else version (Unix) + else version (unix_mm) { if (fd != -1 && unix.close(fd) == -1) errNo(); fd = -1; } + else static if (! Have_MMFile) + { + } else { static assert(0); @@ -310,7 +362,7 @@ { FlushViewOfFile(data, data.length); } - else version (Unix) + else version (unix_mm) { int i; @@ -318,30 +370,45 @@ if (i != 0) errNo(); } + else static if (! Have_MMFile) + { + } else { static assert(0); } } + /** + * Gives size in bytes of the memory mapped file. + */ ulong length() { debug (MMFILE) printf("MmFile.length()\n"); return size; } + /** + * Read-only property returning the file mode. + */ Mode mode() { debug (MMFILE) printf("MmFile.mode()\n"); return mMode; } + /** + * Returns entire file contents as an array. + */ void[] opSlice() { debug (MMFILE) printf("MmFile.opSlice()\n"); return opSlice(0,size); } + /** + * Returns slice of file contents as an array. + */ void[] opSlice(ulong i1, ulong i2) { debug (MMFILE) printf("MmFile.opSlice(%lld, %lld)\n", i1, i2); @@ -351,7 +418,9 @@ return data[off1 .. off2]; } - + /** + * Returns byte at index i in file. + */ ubyte opIndex(ulong i) { debug (MMFILE) printf("MmFile.opIndex(%lld)\n", i); @@ -360,6 +429,9 @@ return (cast(ubyte[])data)[off]; } + /** + * Sets and returns byte at index i in file to value. + */ ubyte opIndexAssign(ubyte value, ulong i) { debug (MMFILE) printf("MmFile.opIndex(%lld, %d)\n", i, value); @@ -388,7 +460,7 @@ if (data && UnmapViewOfFile(data) == FALSE && (dwVersion & 0x80000000) == 0) errNo(); - } else { + } else version (unix_mm) { if (data && munmap(cast(void*)data, data.length) != 0) errNo(); } @@ -406,7 +478,7 @@ uint hi = cast(uint)(start>>32); p = MapViewOfFileEx(hFileMap, dwDesiredAccess, hi, cast(uint)start, len, address); if (!p) errNo(); - } else { + } else version (unix_mm) { p = mmap(address, len, prot, flags, fd, start); if (p == MAP_FAILED) errNo(); } @@ -467,13 +539,16 @@ HANDLE hFileMap = null; uint dwDesiredAccess; } - else version (Unix) + else version (unix_mm) { int fd; int prot; int flags; int fmode; } + else static if (! Have_MMFile) + { + } else { static assert(0); @@ -490,6 +565,10 @@ { throw new FileException(filename, getErrno()); } + else static if (! Have_MMFile) + { + throw new FileException(filename, "MMFile unsupported"); + } else { static assert(0); @@ -498,6 +577,8 @@ } unittest { + static if (Have_MMFile) + { const size_t K = 1024; size_t win = 64*K; // assume the page size is 64K version(Win32) { @@ -526,4 +607,5 @@ assert( data2[length-1] == 'b' ); delete mf; std.file.remove("testing.txt"); + } } diff -uNr gdc-0.17/d/phobos/std/openrj.d gdc-0.18/d/phobos/std/openrj.d --- gdc-0.17/d/phobos/std/openrj.d 2005-06-22 05:13:40.000000000 +0200 +++ gdc-0.18/d/phobos/std/openrj.d 2006-05-14 04:21:51.000000000 +0200 @@ -29,11 +29,20 @@ * - This notice may not be removed or altered from any source * distribution. * - * ////////////////////////////////////////////////////////////////////////// */ + * ////////////////////////////////////////////////////////////////////////// + * Altered by Walter Bright. + */ -/* \file std/openrj.d Open-RJ/D mapping for the D standard library +/** + * Open-RJ mapping for the D standard library. * + * Authors: + * Matthew Wilson + * References: + * $(LINK2 http://www.openrj.org/, Open-RJ) + * Macros: + * WIKI=Phobos/StdOpenrj */ /* ///////////////////////////////////////////////////////////////////////////// @@ -58,7 +67,7 @@ * Version information */ -/// This'll be moved out to somewhere common soon +// This'll be moved out to somewhere common soon private struct Version { @@ -86,7 +95,7 @@ * Structs */ -/// This'll be moved out to somewhere common soon +// This'll be moved out to somewhere common soon private struct EnumString { @@ -132,10 +141,13 @@ /** Flags that moderate the creation of Databases */ public enum ORJ_FLAG { - ORDER_FIELDS = 0x0001 /*!< Arranges the fields in alphabetical order */ - , ELIDE_BLANK_RECORDS = 0x0002 /*!< Causes blank records to be ignored */ + ORDER_FIELDS = 0x0001, /// Arranges the fields in alphabetical order + ELIDE_BLANK_RECORDS = 0x0002, /// Causes blank records to be ignored } +/** + * + */ public char[] toString(ORJ_FLAG f) { const EnumString strings[] = @@ -150,17 +162,20 @@ /** General error codes */ public enum ORJRC { - SUCCESS = 0 /*!< Operation was successful */ - , CANNOT_OPEN_JAR_FILE /*!< The given file does not exist, or cannot be accessed */ - , NO_RECORDS /*!< The database file contained no records */ - , OUT_OF_MEMORY /*!< The API suffered memory exhaustion */ - , BAD_FILE_READ /*!< A read operation failed */ - , PARSE_ERROR /*!< Parsing of the database file failed due to a syntax error */ - , INVALID_INDEX /*!< An invalid index was specified */ - , UNEXPECTED /*!< An unexpected condition was encountered */ - , INVALID_CONTENT /*!< The database file contained invalid content */ + SUCCESS = 0, /// Operation was successful + CANNOT_OPEN_JAR_FILE, /// The given file does not exist, or cannot be accessed + NO_RECORDS, /// The database file contained no records + OUT_OF_MEMORY, /// The API suffered memory exhaustion + BAD_FILE_READ, /// A read operation failed + PARSE_ERROR, /// Parsing of the database file failed due to a syntax error + INVALID_INDEX, /// An invalid index was specified + UNEXPECTED, /// An unexpected condition was encountered + INVALID_CONTENT, /// The database file contained invalid content } +/** + * + */ public char[] toString(ORJRC f) { const EnumString strings[] = @@ -182,13 +197,16 @@ /** Parsing error codes */ public enum ORJ_PARSE_ERROR { - SUCCESS = 0 /*!< Parsing was successful */ - , RECORD_SEPARATOR_IN_CONTINUATION /*!< A record separator was encountered during a content line continuation */ - , UNFINISHED_LINE /*!< The last line in the database was not terminated by a line-feed */ - , UNFINISHED_FIELD /*!< The last field in the database file was not terminated by a record separator */ - , UNFINISHED_RECORD /*!< The last record in the database file was not terminated by a record separator */ + SUCCESS = 0, /// Parsing was successful + RECORD_SEPARATOR_IN_CONTINUATION, /// A record separator was encountered during a content line continuation + UNFINISHED_LINE, /// The last line in the database was not terminated by a line-feed + UNFINISHED_FIELD, /// The last field in the database file was not terminated by a record separator + UNFINISHED_RECORD, /// The last record in the database file was not terminated by a record separator } +/** + * + */ public char[] toString(ORJ_PARSE_ERROR f) { const EnumString strings[] = @@ -207,24 +225,29 @@ * Classes */ +/** + * + */ class OpenRJException : public Exception { -/// \name Construction -/// @{ +/* \name Construction */ + protected: this(char[] message) { super(message); } -/// @} + } +/** + * + */ class DatabaseException : public OpenRJException { -/// \name Construction -/// @{ +/* \name Construction */ private: this(char[] details, ORJRC rc) { @@ -289,24 +312,33 @@ super(message); } -/// @} -/// \name Attributes -/// @{ +/* \name Attributes */ public: + + /** + * + */ ORJRC rc() { return m_rc; } + + /** + * + */ ORJ_PARSE_ERROR parseError() { return m_pe; } + + /** + * + */ int lineNum() { return m_lineNum; } -/// @} // Members private: @@ -315,30 +347,32 @@ ORJ_PARSE_ERROR m_pe; } +/** + * + */ class InvalidKeyException : public OpenRJException { -/// \name Construction -/// @{ +/* \name Construction */ private: this(char[] message) { super(message); } -/// @} } +/** + * + */ class InvalidTypeException : public OpenRJException { -/// \name Construction -/// @{ +/* \name Construction */ private: this(char[] message) { super(message); } -/// @} } /* ///////////////////////////////////////////////////////////////////////////// @@ -348,8 +382,8 @@ /// Represents a field in the database class Field { -/// \name Construction -/// @{ +/* \name Construction */ + private: this(char[] name, char[] value/* , Record record */) in @@ -363,27 +397,39 @@ m_value = value; /* m_record = record; */ } -/// @} -/// \name Attributes -/// @{ + +/* \name Attributes */ + public: + + /** + * + */ final char[] name() { return m_name; } + + /** + * + */ final char[] value() { return m_value; } + + /** + * + */ Record record() { return m_record; } -/// @} -/// \name Comparison -/// @{ + +/* \name Comparison */ + /+ public: int opCmp(Object rhs) @@ -419,7 +465,7 @@ return res; } +/ -/// @} + // Members private: @@ -431,16 +477,16 @@ /// Represents a record in the database, consisting of a set of fields class Record { -/// \name Types -/// @{ +/* \name Types */ + public: alias object.size_t size_type; alias object.size_t index_type; alias object.ptrdiff_t difference_type; -/// @} -/// \name Construction -/// @{ + +/* \name Construction */ + private: this(Field[] fields, uint flags, Database database) { @@ -461,26 +507,39 @@ m_database = database; } -/// @} -/// \name Attributes -/// @{ + +/* \name Attributes */ + public: + + /** + * + */ uint numFields() { return m_fields.length; } + /** + * + */ uint length() { return numFields(); } + /** + * + */ Field[] fields() { return m_fields.dup; } + /** + * + */ Field opIndex(index_type index) in { @@ -491,11 +550,17 @@ return m_fields[index]; } + /** + * + */ char[] opIndex(char[] fieldName) { return getField(fieldName).value; } + /** + * + */ Field getField(char[] fieldName) in { @@ -513,6 +578,9 @@ return field; } + /** + * + */ Field findField(char[] fieldName) in { @@ -525,20 +593,30 @@ return (null is pfield) ? null : *pfield; } + /** + * + */ int hasField(char[] fieldName) { return null !is findField(fieldName); } + /** + * + */ Database database() { return m_database; } -/// @} -/// \name Enumeration -/// @{ + +/* \name Enumeration */ + public: + + /** + * + */ int opApply(int delegate(inout Field field) dg) { int result = 0; @@ -556,6 +634,9 @@ return result; } + /** + * + */ int opApply(int delegate(in char[] name, in char[] value) dg) { int result = 0; @@ -572,7 +653,7 @@ return result; } -/// @} + // Members private: @@ -581,18 +662,22 @@ Database m_database; } + +/** + * + */ class Database { -/// \name Types -/// @{ +/* \name Types */ + public: alias object.size_t size_type; alias object.size_t index_type; alias object.ptrdiff_t difference_type; -/// @} -/// \name Construction -/// @{ + +/* \name Construction */ + private: void init_(char[][] lines, uint flags) { @@ -726,6 +811,10 @@ m_numLines = lines.length; } public: + + /** + * + */ this(char[] memory, uint flags) { char[][] lines = split(memory, "\n"); @@ -733,52 +822,83 @@ init_(lines, flags); } + /** + * + */ this(char[][] lines, uint flags) { init_(lines, flags); } -/// @} -/// \name Attributes -/// @{ + +/* \name Attributes */ + public: + + /** + * + */ size_type numRecords() { return m_records.length; } + + /** + * + */ size_type numFields() { return m_fields.length; } + + /** + * + */ size_type numLines() { return m_numLines; } -/// @} -/// \name Attributes -/// @{ + +/* \name Attributes */ + public: + + /** + * + */ uint flags() { return m_flags; } + /** + * + */ Record[] records() { return m_records.dup; } + /** + * + */ Field[] fields() { return m_fields.dup; } + /** + * + */ uint length() { return numRecords(); } + /** + * + */ Record opIndex(index_type index) in { @@ -788,11 +908,15 @@ { return m_records[index]; } -/// @} -/// \name Searching -/// @{ + +/* \name Searching */ + public: + + /** + * + */ Record[] getRecordsContainingField(char[] fieldName) { Record[] records; @@ -808,6 +932,9 @@ return records; } + /** + * + */ Record[] getRecordsContainingField(char[] fieldName, char[] fieldValue) { Record[] records; @@ -861,11 +988,15 @@ return records; } -/// @} -/// \name Enumeration -/// @{ + +/* \name Enumeration */ + public: + + /** + * + */ int opApply(int delegate(inout Record record) dg) { int result = 0; @@ -882,6 +1013,10 @@ return result; } + + /** + * + */ int opApply(int delegate(inout Field field) dg) { int result = 0; @@ -898,7 +1033,7 @@ return result; } -/// @} + // Members private: diff -uNr gdc-0.17/d/phobos/std/outbuffer.d gdc-0.18/d/phobos/std/outbuffer.d --- gdc-0.17/d/phobos/std/outbuffer.d 2005-10-02 16:17:55.000000000 +0200 +++ gdc-0.18/d/phobos/std/outbuffer.d 2006-04-16 17:13:30.000000000 +0200 @@ -4,7 +4,7 @@ * Boilerplate: * $(std_boilerplate.html) * Macros: - * WIKI = StdOutbuffer + * WIKI = Phobos/StdOutbuffer * Copyright: * Copyright (c) 2001-2005 by Digital Mars * All Rights Reserved @@ -249,22 +249,24 @@ char* f; uint psize; int count; + va_list args_copy; f = toStringz(format); p = buffer; psize = buffer.length; for (;;) { + va_copy(args_copy, args); version(Win32) { - count = _vsnprintf(p,psize,f,args); + count = _vsnprintf(p,psize,f,args_copy); if (count != -1) break; psize *= 2; p = cast(char *) alloca(psize); // buffer too small, try again with larger size } else version(GNU) { - count = vsnprintf(p,psize,f,args); + count = vsnprintf(p,psize,f,args_copy); if (count == -1) psize *= 2; else if (count >= psize) @@ -275,7 +277,7 @@ } else version(linux) { - count = vsnprintf(p,psize,f,args); + count = vsnprintf(p,psize,f,args_copy); if (count == -1) psize *= 2; else if (count >= psize) diff -uNr gdc-0.17/d/phobos/std/path.d gdc-0.18/d/phobos/std/path.d --- gdc-0.17/d/phobos/std/path.d 2005-10-13 03:06:51.000000000 +0200 +++ gdc-0.18/d/phobos/std/path.d 2006-04-26 05:23:05.000000000 +0200 @@ -1,43 +1,73 @@ /** * Macros: - * WIKI = StdPath + * WIKI = Phobos/StdPath * Copyright: - * Copyright (c) 2001-2005 by Digital Mars - * All Rights Reserved + * Placed into public domain. * www.digitalmars.com + * + * Grzegorz Adam Hankiewicz added some documentation. + * + * This module is used to parse file names. All the operations + * work only on strings; they don't perform any input/output + * operations. This means that if a path contains a directory name + * with a dot, functions like getExt() will work with it just as + * if it was a file. To differentiate these cases, + * use the std.file module first (i.e. std.file.isDir()). */ /* NOTE: This file has been patched from the original DMD distribution to work with the GDC compiler. - Modified by David Friedman, September 2004 + Modified by David Friedman, March 2006 */ -// File name parsing - module std.path; //debug=path; // uncomment to turn on debugging printf's +//private import std.stdio; private import std.string; -version(Win32) +version(Unix) +{ + private import std.c.stdlib; + private import std.c.unix.unix; + private import std.outofmemory; +} + +version(Windows) { - const char[1] sep = "\\"; /// String used to separate directory names in a path. - const char[1] altsep = "/"; /// Alternate version of sep[], used in Windows. - const char[1] pathsep = ";"; /// Path separator string. + /** String used to separate directory names in a path. Under + * Windows this is a backslash, under Linux a slash. */ + const char[1] sep = "\\"; + /** Alternate version of sep[] used in Windows (a slash). Under + * Linux this is empty. */ + const char[1] altsep = "/"; + /** Path separator string. A semi colon under Windows, a colon + * under Linux. */ + const char[1] pathsep = ";"; + /** String used to separate lines, \r\n under Windows and \n + * under Linux. */ const char[2] linesep = "\r\n"; /// String used to separate lines. const char[1] curdir = "."; /// String representing the current directory. const char[2] pardir = ".."; /// String representing the parent directory. } else version(Unix) { - const char[1] sep = "/"; /// String used to separate directory names in a path. - const char[0] altsep; /// Alternate version of sep[], used in Windows. - const char[1] pathsep = ":"; /// Path separator string. - const char[1] linesep = "\n"; /// String used to separate lines. + /** String used to separate directory names in a path. Under + * Windows this is a backslash, under Linux a slash. */ + const char[1] sep = "/"; + /** Alternate version of sep[] used in Windows (a slash). Under + * Linux this is empty. */ + const char[0] altsep; + /** Path separator string. A semi colon under Windows, a colon + * under Linux. */ + const char[1] pathsep = ":"; + /** String used to separate lines, \r\n under Windows and \n + * under Linux. */ + const char[1] linesep = "\n"; const char[1] curdir = "."; /// String representing the current directory. const char[2] pardir = ".."; /// String representing the parent directory. } @@ -46,10 +76,48 @@ static assert(0); } +/***************************** + * Compare file names. + * Returns: + * + *
    < 0 filename1 < filename2 + *
    = 0 filename1 == filename2 + *
    > 0 filename1 > filename2 + *
    + */ + +version (Windows) alias std.string.cmp fcmp; + +version (Unix) alias std.string.icmp fcmp; /************************** - * Get extension. - * For example, "d:\path\foo.bat" returns "bat". + * Extracts the extension from a filename or path. + * + * This function will search fullname from the end until the + * first dot, path separator or first character of fullname is + * reached. Under Windows, the drive letter separator (colon) + * also terminates the search. + * + * Returns: If a dot was found, characters to its right are + * returned. If a path separator was found, or fullname didn't + * contain any dots or path separators, returns null. + * + * Throws: Nothing. + * + * Examples: + * ----- + * version(Win32) + * { + * getExt(r"d:\path\foo.bat") // "bat" + * getExt(r"d:\path.two\bar") // null + * } + * version(linux) + * { + * getExt(r"/home/user.name/bar.") // "" + * getExt(r"d:\\path.two\\bar") // "two\\bar" + * getExt(r"/home/user/.resource") // "resource" + * } + * ----- */ char[] getExt(char[] fullname) @@ -117,8 +185,101 @@ } /************************** - * Get base name. - * For example, "d:\path\foo.bat" returns "foo.bat". + * Returns the extensionless version of a filename or path. + * + * This function will search fullname from the end until the + * first dot, path separator or first character of fullname is + * reached. Under Windows, the drive letter separator (colon) + * also terminates the search. + * + * Returns: If a dot was found, characters to its left are + * returned. If a path separator was found, or fullname didn't + * contain any dots or path separators, returns null. + * + * Throws: Nothing. + * + * Examples: + * ----- + * version(Win32) + * { + * getName(r"d:\path\foo.bat") => "d:\path\foo" + * getName(r"d:\path.two\bar") => null + * } + * version(linux) + * { + * getName("/home/user.name/bar.") => "/home/user.name/bar" + * getName(r"d:\path.two\bar") => "d:\path" + * getName("/home/user/.resource") => "/home/user/" + * } + * ----- + */ + +char[] getName(char[] fullname) +{ + uint i; + + i = fullname.length; + while (i > 0) + { + if (fullname[i - 1] == '.') + return fullname[0 .. i - 1]; + i--; + version(Win32) + { + if (fullname[i] == ':' || fullname[i] == '\\') + break; + } + version(Unix) + { + if (fullname[i] == '/') + break; + } + } + return null; +} + +unittest +{ + debug(path) printf("path.getName.unittest\n"); + int i; + char[] result; + + result = getName("foo.bar"); + i = cmp(result, "foo"); + assert(i == 0); + + result = getName("d:\\path.two\\bar"); + version (Win32) + i = cmp(result, null); + version (linux) + i = cmp(result, "d:\\path"); + assert(i == 0); +} + +/************************** + * Extracts the base name of a path. + * + * This function will search fullname from the end until the + * first path separator or first character of fullname is + * reached. Under Windows, the drive letter separator (colon) + * also terminates the search. + * + * Returns: If a path separator was found, all the characters to its + * right are returned. Otherwise, fullname is returned. + * + * Throws: Nothing. + * + * Examples: + * ----- + * version(Win32) + * { + * getBaseName(r"d:\path\foo.bat") => "foo.bat" + * } + * version(linux) + * { + * getBaseName("/home/user.name/bar.") => "bar." + * } + * ----- */ char[] getBaseName(char[] fullname) @@ -152,7 +313,7 @@ int i; char[] result; - version (Win32) + version (Windows) result = getBaseName("d:\\path\\foo.bat"); version (Unix) result = getBaseName("/path/foo.bat"); @@ -160,7 +321,7 @@ i = cmp(result, "foo.bat"); assert(i == 0); - version (Win32) + version (Windows) result = getBaseName("a\\b"); version (Unix) result = getBaseName("a/b"); @@ -170,8 +331,34 @@ /************************** - * Get directory name. - * For example, "d:\path\foo.bat" returns "d:\path". + * Extracts the directory part of a path. + * + * This function will search fullname from the end until the + * first path separator or first character of fullname is + * reached. Under Windows, the drive letter separator (colon) + * also terminates the search. + * + * Returns: If a path separator was found, all the characters to its + * left are returned. Otherwise, fullname is returned. + * + * Under Windows, the found path separator will be included in the + * returned string if it is preceeded by a colon. + * + * Throws: Nothing. + * + * Examples: + * ----- + * version(Win32) + * { + * getDirName(r"d:\path\foo.bat") => "d:\path" + * getDirName(getDirName(r"d:\path\foo.bat")) => "d:\" + * } + * version(linux) + * { + * getDirName("/home/user") => "/home" + * getDirName(getDirName("/home/user")) => "" + * } + * ----- */ char[] getDirName(char[] fullname) @@ -207,8 +394,21 @@ /******************************** - * Get drive. - * For example, "d:\path\foo.bat" returns "d:". + * Extracts the drive letter of a path. + * + * This function will search fullname for a colon from the beginning. + * + * Returns: If a colon is found, all the characters to its left + * plus the colon are returned. Otherwise, null is returned. + * + * Under Linux, this function always returns null immediately. + * + * Throws: Nothing. + * + * Examples: + * ----- + * getDrive(r"d:\path\foo.bat") => "d:" + * ----- */ char[] getDrive(char[] fullname) @@ -236,8 +436,24 @@ } /**************************** - * If filename doesn't already have an extension, - * append the extension ext and return the result. + * Appends a default extension to a filename. + * + * This function first searches filename for an extension and + * appends ext if there is none. ext should not have any leading + * dots, one will be inserted between filename and ext if filename + * doesn't already end with one. + * + * Returns: filename if it contains an extension, otherwise filename + * + ext. + * + * Throws: Nothing. + * + * Examples: + * ----- + * defaultExt("foo.txt", "raw") => "foo.txt" + * defaultExt("foo.", "raw") => "foo.raw" + * defaultExt("bar", "raw") => "bar.raw" + * ----- */ char[] defaultExt(char[] filename, char[] ext) @@ -258,8 +474,26 @@ /**************************** - * Strip any existing extension off of filename and add the new extension ext. - * Return the result. + * Adds or replaces an extension to a filename. + * + * This function first searches filename for an extension and + * replaces it with ext if found. If there is no extension, ext + * will be appended. ext should not have any leading dots, one will + * be inserted between filename and ext if filename doesn't already + * end with one. + * + * Returns: filename + ext if filename is extensionless. Otherwise + * strips filename's extension off, appends ext and returns the + * result. + * + * Throws: Nothing. + * + * Examples: + * ----- + * addExt("foo.txt", "raw") => "foo.raw" + * addExt("foo.", "raw") => "foo.raw" + * addExt("bar", "raw") => "bar.raw" + * ----- */ char[] addExt(char[] filename, char[] ext) @@ -284,18 +518,83 @@ /************************************* - * Return !=0 if path is absolute (i.e. it starts from the root directory). + * Checks if path is absolute. + * + * Returns: non-zero if the path starts from the root directory (Linux) or + * drive letter and root directory (Windows), + * zero otherwise. + * + * Throws: Nothing. + * + * Examples: + * ----- + * version(Win32) + * { + * isabs(r"relative\path") => 0 + * isabs(r"\relative\path") => 0 + * isabs(r"d:\absolute") => 1 + * } + * version(linux) + * { + * isabs("/home/user") => 1 + * isabs("foo") => 0 + * } + * ----- */ int isabs(char[] path) { char[] d = getDrive(path); - return d.length < path.length && path[d.length] == sep[0]; + version (Windows) + { + return d.length && d.length < path.length && path[d.length] == sep[0]; + } + else + return d.length < path.length && path[d.length] == sep[0]; +} + +unittest +{ + debug(path) printf("path.isabs.unittest\n"); + + version (Windows) + { + assert(isabs(r"relative\path") == 0); + assert(isabs(r"\relative\path") == 0); + assert(isabs(r"d:\absolute") == 1); + } + version (linux) + { + assert(isabs("/home/user") == 1); + assert(isabs("foo") == 0); + } } /************************************* - * Join two path components p1 and p2 and return the result. + * Joins two path components. + * + * If p1 doesn't have a trailing path separator, one will be appended + * to it before concatting p2. + * + * Returns: p1 ~ p2. However, if p2 is an absolute path, only p2 + * will be returned. + * + * Throws: Nothing. + * + * Examples: + * ----- + * version(Win32) + * { + * join(r"c:\foo", "bar") => "c:\foo\bar" + * join("foo", r"d:\bar") => "d:\bar" + * } + * version(linux) + * { + * join("/foo/", "bar") => "/foo/bar" + * join("/foo", "/bar") => "/bar" + * } + * ----- */ char[] join(char[] p1, char[] p2) @@ -440,8 +739,28 @@ /********************************* - * Match file name characters c1 and c2. - * Case sensitivity depends on the operating system. + * Matches filename characters. + * + * Under Windows, the comparison is done ignoring case. Under Linux + * an exact match is performed. + * + * Returns: non zero if c1 matches c2, zero otherwise. + * + * Throws: Nothing. + * + * Examples: + * ----- + * version(Win32) + * { + * fncharmatch('a', 'b') => 0 + * fncharmatch('A', 'a') => 1 + * } + * version(linux) + * { + * fncharmatch('a', 'b') => 0 + * fncharmatch('A', 'a') => 0 + * } + * ----- */ int fncharmatch(dchar c1, dchar c2) @@ -472,19 +791,50 @@ } /************************************ - * Match filename with pattern, using the following wildcards: + * Matches a pattern against a filename. * - * - *
    * match 0 or more characters - *
    ? match any character - *
    [chars] match any character that appears between the [] - *
    [!chars] match any character that does not appear between the [! ] - *
    + * Some characters of pattern have special a meaning (they are + * meta-characters) and can't be escaped. These are: + *

    + * + * + * + * + * + * + * + * + *
    *Matches 0 or more instances of any character.
    ?Matches exactly one instances of any character.
    [chars]Matches one instance of any character that appears + * between the brackets.
    [!chars]Matches one instance of any character that does not appear + * between the brackets after the exclamation mark.

    + * Internally individual character comparisons are done calling + * fncharmatch(), so its rules apply here too. Note that path + * separators and dots don't stop a meta-character from matching + * further portions of the filename. * - * Matching is case sensitive on a file system that is case sensitive. + * Returns: non zero if pattern matches filename, zero otherwise. * - * Returns: - * !=0 for match + * See_Also: fncharmatch(). + * + * Throws: Nothing. + * + * Examples: + * ----- + * version(Win32) + * { + * fnmatch("foo.bar", "*") => 1 + * fnmatch(r"foo/foo\bar", "f*b*r") => 1 + * fnmatch("foo.bar", "f?bar") => 0 + * fnmatch("Goo.bar", "[fg]???bar") => 1 + * fnmatch(r"d:\foo\bar", "d*foo?bar") => 1 + * } + * version(linux) + * { + * fnmatch("Go*.bar", "[fg]???bar") => 0 + * fnmatch("/foo*home/bar", "?foo*bar") => 1 + * fnmatch("foobar", "foo?bar") => 1 + * } + * ----- */ int fnmatch(char[] filename, char[] pattern) @@ -616,3 +966,281 @@ assert(!fnmatch("foo.bar", "[!fg]*bar")); assert(!fnmatch("foo.bar", "[fg]???baz")); } + +/** + * Performs tilde expansion in paths. + * + * There are two ways of using tilde expansion in a path. One + * involves using the tilde alone or followed by a path separator. In + * this case, the tilde will be expanded with the value of the + * environment variable HOME. The second way is putting + * a username after the tilde (i.e. ~john/Mail). Here, + * the username will be searched for in the user database + * (i.e. /etc/passwd on Unix systems) and will expand to + * whatever path is stored there. The username is considered the + * string after the tilde ending at the first instance of a path + * separator. + * + * Note that using the ~user syntax may give different + * values from just ~ if the environment variable doesn't + * match the value stored in the user database. + * + * When the environment variable version is used, the path won't + * be modified if the environment variable doesn't exist or it + * is empty. When the database version is used, the path won't be + * modified if the user doesn't exist in the database or there is + * not enough memory to perform the query. + * + * Returns: inputPath with the tilde expanded, or just inputPath + * if it could not be expanded. + * For Windows, expandTilde() merely returns its argument inputPath. + * + * Throws: std.OutOfMemory if there is not enough memory to perform + * the database lookup for the ~user syntax. + * + * Examples: + * ----- + * import std.path; + * + * void process_file(char[] filename) + * { + * char[] path = expandTilde(filename); + * ... + * } + * ----- + * + * ----- + * import std.path; + * + * const char[] RESOURCE_DIR_TEMPLATE = "~/.applicationrc"; + * char[] RESOURCE_DIR; // This gets expanded in main(). + * + * int main(char[][] args) + * { + * RESOURCE_DIR = expandTilde(RESOURCE_DIR_TEMPLATE); + * ... + * } + * ----- + * Version: Available since v0.143. + * Authors: Grzegorz Adam Hankiewicz, Thomas Kühne. + */ + +char[] expandTilde(char[] inputPath) +{ + version(Unix) + { + static assert(sep.length == 1); + + // Return early if there is no tilde in path. + if (inputPath.length < 1 || inputPath[0] != '~') + return inputPath; + + if (inputPath.length == 1 || inputPath[1] == sep[0]) + return expandFromEnvironment(inputPath); + else + return expandFromDatabase(inputPath); + } + else version(Windows) + { + // Put here real windows implementation. + return inputPath; + } + else + { + static assert(0); // Guard. Implement on other platforms. + } +} + + +unittest +{ + debug(path) printf("path.expandTilde.unittest\n"); + + version (Unix) + { + // Retrieve the current home variable. + char* c_home = getenv("HOME"); + + // Testing when there is no environment variable. + unsetenv("HOME"); + assert(expandTilde("~/") == "~/"); + assert(expandTilde("~") == "~"); + + // Testing when an environment variable is set. + int ret = setenv("HOME", "dmd/test\0", 1); + assert(ret == 0); + assert(expandTilde("~/") == "dmd/test/"); + assert(expandTilde("~") == "dmd/test"); + + // The same, but with a variable ending in a slash. + ret = setenv("HOME", "dmd/test/\0", 1); + assert(ret == 0); + assert(expandTilde("~/") == "dmd/test/"); + assert(expandTilde("~") == "dmd/test"); + + // Recover original HOME variable before continuing. + if (c_home) + setenv("HOME", c_home, 1); + else + unsetenv("HOME"); + + // Test user expansion for root. Are there unices without /root? + /* + assert(expandTilde("~root") == "/root"); + assert(expandTilde("~root/") == "/root/"); + */ + assert(expandTilde("~Idontexist/hey") == "~Idontexist/hey"); + } +} + +version (Unix) +{ + +/** + * Replaces the tilde from path with the environment variable HOME. + */ +private char[] expandFromEnvironment(char[] path) +{ + assert(path.length >= 1); + assert(path[0] == '~'); + + // Get HOME and use that to replace the tilde. + char* home = getenv("HOME"); + if (home == null) + return path; + + return combineCPathWithDPath(home, path, 1); +} + + +/** + * Joins a path from a C string to the remainder of path. + * + * The last path separator from c_path is discarded. The result + * is joined to path[char_pos .. length] if char_pos is smaller + * than length, otherwise path is not appended to c_path. + */ +private char[] combineCPathWithDPath(char* c_path, char[] path, int char_pos) +{ + assert(c_path != null); + assert(path.length > 0); + assert(char_pos >= 0); + + // Search end of C string + size_t end = std.string.strlen(c_path); + + // Remove trailing path separator, if any + if (end && c_path[end - 1] == sep[0]) + end--; + + // Create our own copy, as lifetime of c_path is undocumented + char[] cp = c_path[0 .. end].dup; + + // Do we append something from path? + if (char_pos < path.length) + cp ~= path[char_pos .. length]; + + return cp; +} + + +/** + * Replaces the tilde from path with the path from the user database. + */ +private char[] expandFromDatabase(char[] path) +{ + assert(path.length > 2 || (path.length == 2 && path[1] != sep[0])); + assert(path[0] == '~'); + + // Extract username, searching for path separator. + char[] username; + int last_char = find(path, sep[0]); + + if (last_char == -1) + { + username = path[1 .. length] ~ '\0'; + last_char = username.length + 1; + } + else + { + username = path[1 .. last_char] ~ '\0'; + } + assert(last_char > 1); + + version (GNU_Unix_Have_getpwnam_r) + { + + // Reserve C memory for the getpwnam_r() function. + passwd result; + int extra_memory_size = 5 * 1024; + void* extra_memory; + + while (1) + { + extra_memory = std.c.stdlib.malloc(extra_memory_size); + if (extra_memory == null) + goto Lerror; + + // Obtain info from database. + passwd *verify; + std.c.stdlib.setErrno(0); + if (getpwnam_r(username, &result, cast(char*) extra_memory, extra_memory_size, + &verify) == 0) + { + // Failure if verify doesn't point at result. + if (verify != &result) + // username is not found, so return path[] + goto Lnotfound; + break; + } + + switch (std.c.stdlib.getErrno()) { + case 0: + case ENOENT: + case ESRCH: + case EBADF: + case EPERM: + goto Lnotfound; + case ERANGE: + break; + default: + // not just out of memory: EMFILE, ENFILE too + goto Lerror; + } + + // extra_memory isn't large enough + std.c.stdlib.free(extra_memory); + extra_memory_size *= 2; + } + + path = combineCPathWithDPath(result.pw_dir, path, last_char); + +Lnotfound: + std.c.stdlib.free(extra_memory); + return path; + +Lerror: + // Errors are going to be caused by running out of memory + if (extra_memory) + std.c.stdlib.free(extra_memory); + _d_OutOfMemory(); + return null; + + } + else + { + passwd * result; + + /* This does not guarantee another thread will not + use getpwnam at the same time */ + synchronized { + result = getpwnam(username); + } + + if (result) + path = combineCPathWithDPath(result.pw_dir, path, last_char); + return path; + } +} + +} diff -uNr gdc-0.17/d/phobos/std/process.d gdc-0.18/d/phobos/std/process.d --- gdc-0.17/d/phobos/std/process.d 2005-05-29 23:09:19.000000000 +0200 +++ gdc-0.18/d/phobos/std/process.d 2006-05-14 01:38:32.000000000 +0200 @@ -30,14 +30,25 @@ Modified by David Friedman, October 2004 */ +/** + * Macros: + * WIKI=Phobos/StdProcess + */ module std.process; private import std.c.stdlib; +private import std.c.string; private import std.string; private import std.c.process; +/** + * Execute command in a _command shell. + * + * Returns: exit status of command + */ + int system(char[] command) { return std.c.process.system(toStringz(command)); @@ -55,24 +66,107 @@ /* ========================================================== */ -version (GNU_Need_spawnvp) -{ - // TODO: implement -} -else -{ +//version (Windows) +//{ +// int spawnvp(int mode, char[] pathname, char[][] argv) +// { +// char** argv_ = cast(char**)alloca((char*).sizeof * (1 + argv.length)); +// +// toAStringz(argv, argv_); +// +// return std.c.process.spawnvp(mode, toStringz(pathname), argv_); +// } +//} + +// Incorporating idea (for spawnvp() on linux) from Dave Fladebo + +alias std.c.process._P_WAIT P_WAIT; +alias std.c.process._P_NOWAIT P_NOWAIT; + int spawnvp(int mode, char[] pathname, char[][] argv) { char** argv_ = cast(char**)alloca((char*).sizeof * (1 + argv.length)); toAStringz(argv, argv_); - return std.c.process.spawnvp(mode, toStringz(pathname), argv_); -} + version(Unix) + { + return _spawnvp(mode, toStringz(pathname), argv_); + } + else + { + return std.c.process.spawnvp(mode, toStringz(pathname), argv_); + } } +version(Unix) +{ +private import std.c.unix.unix; +int _spawnvp(int mode, char *pathname, char **argv) +{ + int retval = 0; + pid_t pid = fork(); + + if(!pid) + { // child + std.c.process.execvp(pathname, argv); + goto Lerror; + } + else if(pid > 0) + { // parent + if(mode == _P_NOWAIT) + { + retval = pid; // caller waits + } + else + { + while(1) + { + int status; + pid_t wpid = waitpid(pid, &status, 0); + if(exited(status)) + { + retval = exitstatus(status); + break; + } + else if(signaled(status)) + { + retval = -termsig(status); + break; + } + else if(stopped(status)) // ptrace support + continue; + else + goto Lerror; + } + } + + return retval; + } + +Lerror: + retval = getErrno; + throw new Exception("Cannot spawn " ~ toString(pathname) ~ "; " ~ toString(strerror(retval)) ~ " [errno " ~ toString(retval) ~ "]"); +} // _spawnvp +private +{ +bool stopped(int status) { return cast(bool)((status & 0xff) == 0x7f); } +bool signaled(int status) { return cast(bool)((cast(char)((status & 0x7f) + 1) >> 1) > 0); } +int termsig(int status) { return status & 0x7f; } +bool exited(int status) { return cast(bool)((status & 0x7f) == 0); } +int exitstatus(int status) { return (status & 0xff00) >> 8; } +} // private +} // version(linux) + /* ========================================================== */ +/** + * Execute program specified by pathname, passing it the arguments (argv) + * and the environment (envp), returning the exit status. + * The 'p' versions of exec search the PATH environment variable + * setting for the program. + */ + int execv(char[] pathname, char[][] argv) { char** argv_ = cast(char**)alloca((char*).sizeof * (1 + argv.length)); @@ -82,6 +176,7 @@ return std.c.process.execv(toStringz(pathname), argv_); } +/** ditto */ int execve(char[] pathname, char[][] argv, char[][] envp) { char** argv_ = cast(char**)alloca((char*).sizeof * (1 + argv.length)); @@ -93,6 +188,7 @@ return std.c.process.execve(toStringz(pathname), argv_, envp_); } +/** ditto */ int execvp(char[] pathname, char[][] argv) { char** argv_ = cast(char**)alloca((char*).sizeof * (1 + argv.length)); @@ -102,6 +198,7 @@ return std.c.process.execvp(toStringz(pathname), argv_); } +/** ditto */ int execvpe(char[] pathname, char[][] argv, char[][] envp) { version (GNU_Need_execvpe) diff -uNr gdc-0.17/d/phobos/std/random.d gdc-0.18/d/phobos/std/random.d --- gdc-0.17/d/phobos/std/random.d 2005-10-13 03:06:51.000000000 +0200 +++ gdc-0.18/d/phobos/std/random.d 2006-04-16 17:13:30.000000000 +0200 @@ -1,6 +1,6 @@ /** * Macros: - * WIKI = StdRandom + * WIKI = Phobos/StdRandom */ // random.d diff -uNr gdc-0.17/d/phobos/std/recls.d gdc-0.18/d/phobos/std/recls.d --- gdc-0.17/d/phobos/std/recls.d 2005-06-22 05:13:40.000000000 +0200 +++ gdc-0.18/d/phobos/std/recls.d 1970-01-01 01:00:00.000000000 +0100 @@ -1,1120 +0,0 @@ -/* ///////////////////////////////////////////////////////////////////////////// - * File: recls.d - * - * Purpose: D mapping for the recls library. recls is a platform-independent - * recursive search library. It is mapped to several languages, - * including D. recls was written by Matthew Wilson, as the first - * exemplar for his "Positive Integration" column in C/C++ User's - * Journal. - * - * Created 10th Octover 2003 - * Updated: 27th November 2003 - * - * Author: Matthew Wilson - * - * License: (Licensed under the Synesis Software Standard Source License) - * - * Copyright (C) 2002-2003, Synesis Software Pty Ltd. - * - * All rights reserved. - * - * www: http://www.recls.org/ - * http://www.synesis.com.au/software - * http://www.synsoft.org/ - * - * email: admin@recls.org - * - * Redistribution and use in source and binary forms, with or - * without modification, are permitted provided that the following - * conditions are met: - * - * (i) Redistributions of source code must retain the above - * copyright notice and contact information, this list of - * conditions and the following disclaimer. - * - * (ii) Any derived versions of this software (howsoever modified) - * remain the sole property of Synesis Software. - * - * (iii) Any derived versions of this software (howsoever modified) - * remain subject to all these conditions. - * - * (iv) Neither the name of Synesis Software nor the names of any - * subdivisions, employees or agents of Synesis Software, nor the - * names of any other contributors to this software may be used to - * endorse or promote products derived from this software without - * specific prior written permission. - * - * This source code is provided by Synesis Software "as is" and any - * warranties, whether expressed or implied, including, but not - * limited to, the implied warranties of merchantability and - * fitness for a particular purpose are disclaimed. In no event - * shall the Synesis Software be liable for any direct, indirect, - * incidental, special, exemplary, or consequential damages - * (including, but not limited to, procurement of substitute goods - * or services; loss of use, data, or profits; or business - * interruption) however caused and on any theory of liability, - * whether in contract, strict liability, or tort (including - * negligence or otherwise) arising in any way out of the use of - * this software, even if advised of the possibility of such - * damage. - * - * ////////////////////////////////////////////////////////////////////////// */ - -/* NOTE: This file has been patched from the original DMD distribution to - work with the GDC compiler. - - Modified by David Friedman, September 2004 -*/ - - - -//////////////////////////////////////////////////////////////////////////////// -// Module - -module std.recls; - -//////////////////////////////////////////////////////////////////////////////// -// Imports - -import std.string; - -version (Unix) -{ - private import std.c.unix.unix; -} -else version (linux) -{ - private import std.c.time; - private import std.c.linux.linux; -} - -//////////////////////////////////////////////////////////////////////////////// -// Public types - -private alias int recls_sint32_t; -/// Unsigned 32-bit integer, used for flags -public alias uint recls_uint32_t; -/// boolean type, used in the recls API functions -public typedef int recls_bool_t; -/// boolean type, used in the recls class mappings -public alias recls_bool_t boolean; - -version(Windows) -{ - /// Win32 time type - public struct recls_time_t - { - uint dwLowDateTime; - uint dwHighDateTime; - }; - - /// Win32 file size type - alias ulong recls_filesize_t; -} -else version(Unix) -{ - /// UNIX time type - typedef time_t recls_time_t; - - /// UNIX file size type - typedef off_t recls_filesize_t; -} -else version(linux) -{ - /// UNIX time type - typedef time_t recls_time_t; - - /// UNIX file size type - typedef off_t recls_filesize_t; -} - -/// The recls search handle type. -public typedef void *hrecls_t; -/// The recls entry handle type. -public typedef void *recls_info_t; -/// The recls entry process callback function parameter type. */ -public typedef void *recls_process_fn_param_t; - -/// The return code of the recls API -public typedef recls_sint32_t recls_rc_t; - -/// Returns non-zero if the given return code represents a failure condition. -public recls_bool_t RECLS_FAILED(recls_rc_t rc) -{ - return cast(recls_bool_t)(rc < 0); -} - -/// Returns non-zero if the given return code represents a success condition. -public recls_bool_t RECLS_SUCCEEDED(recls_rc_t rc) -{ - return cast(recls_bool_t)!RECLS_FAILED(rc); -} - -//////////////////////////////////////////////////////////////////////////////// -// Values - -/** General success code */ -public const recls_rc_t RECLS_RC_OK = cast(recls_rc_t)(0); - -/** Return code that indicates that there is no more data available from an otherwise valid search. */ -public const recls_rc_t RECLS_RC_NO_MORE_DATA = cast(recls_rc_t)(-1004); - -/// The flags used to moderate the recls search behaviour -public enum RECLS_FLAG -{ - RECLS_F_FILES = 0x00000001 /*!< Include files in search. Included by default if none specified */ - , RECLS_F_DIRECTORIES = 0x00000002 /*!< Include directories in search. Not currently supported. */ - , RECLS_F_LINKS = 0x00000004 /*!< Include links in search. Ignored in Win32. */ - , RECLS_F_DEVICES = 0x00000008 /*!< Include devices in search. Not currently supported. */ - , RECLS_F_TYPEMASK = 0x00000FFF - , RECLS_F_RECURSIVE = 0x00010000 /*!< Searches given directory and all sub-directories */ - , RECLS_F_NO_FOLLOW_LINKS = 0x00020000 /*!< Does not expand links */ - , RECLS_F_DIRECTORY_PARTS = 0x00040000 /*!< Fills out the directory parts. Supported from version 1.1.1 onwards. */ - , RECLS_F_DETAILS_LATER = 0x00080000 /*!< Does not fill out anything other than the path. Not currently supported. */ -}; - -//////////////////////////////////////////////////////////////////////////////// -// Private recls API declarations - -extern (Windows) -{ - private recls_rc_t Recls_Search( char *searchRoot - , char *pattern - , recls_uint32_t flags - , hrecls_t *phSrch); - - typedef int (*hrecls_process_fn_t)(recls_info_t info, recls_process_fn_param_t param); - - private recls_rc_t Recls_SearchProcess( char *searchRoot - , char *pattern - , recls_uint32_t flags - , hrecls_process_fn_t pfn - , recls_process_fn_param_t param); - - private void Recls_SearchClose(in hrecls_t hSrch); - - private recls_rc_t Recls_GetNext(in hrecls_t hSrch); - - private recls_rc_t Recls_GetDetails(in hrecls_t hSrch, out recls_info_t pinfo); - - private recls_rc_t Recls_GetNextDetails(in hrecls_t hSrch, out recls_info_t pinfo); - - private void Recls_CloseDetails(in recls_info_t fileInfo); - - private recls_rc_t Recls_CopyDetails(in recls_info_t fileInfo, in recls_info_t *pinfo); - - private recls_rc_t Recls_OutstandingDetails(in hrecls_t hSrch, out recls_uint32_t count); - - private recls_rc_t Recls_GetLastError(in hrecls_t hSrch); - - private int Recls_GetErrorString(in recls_rc_t rc, in char *buffer, in uint cchBuffer); - - private int Recls_GetLastErrorString(in hrecls_t hSrch, in char *buffer, in uint cchBuffer); - - private uint Recls_GetPathProperty(in recls_info_t fileInfo, in char *buffer, in uint cchBuffer); - -version(Windows) -{ - private void Recls_GetDriveProperty(in recls_info_t fileInfo, out char chDrive); -} - - private uint Recls_GetDirectoryProperty(in recls_info_t fileInfo, in char *buffer, in uint cchBuffer); - - private uint Recls_GetDirectoryPathProperty(in recls_info_t fileInfo, in char *buffer, in uint cchBuffer); - - private uint Recls_GetFileProperty(in recls_info_t fileInfo, in char *buffer, in uint cchBuffer); - -version(Windows) -{ - private uint Recls_GetShortFileProperty(in recls_info_t fileInfo, in char *buffer, in uint cchBuffer); -} - - private uint Recls_GetFileNameProperty(in recls_info_t fileInfo, in char *buffer, in uint cchBuffer); - - private uint Recls_GetFileExtProperty(in recls_info_t fileInfo, in char *buffer, in uint cchBuffer); - - private uint Recls_GetDirectoryPartProperty(in recls_info_t fileInfo, in int part, in char *buffer, in uint cchBuffer); - - private recls_bool_t Recls_IsFileReadOnly(in recls_info_t fileInfo); - - private recls_bool_t Recls_IsFileDirectory(in recls_info_t fileInfo); - - private recls_bool_t Recls_IsFileLink(in recls_info_t fileInfo); - - private void Recls_GetSizeProperty(in recls_info_t fileInfo, recls_filesize_t *size); - - private recls_time_t Recls_GetCreationTime(in recls_info_t fileInfo); - - private recls_time_t Recls_GetModificationTime(in recls_info_t fileInfo); - - private recls_time_t Recls_GetLastAccessTime(in recls_info_t fileInfo); - - private recls_time_t Recls_GetLastStatusChangeTime(in recls_info_t fileInfo); - -} - -//////////////////////////////////////////////////////////////////////////////// -// Public functions - -/// Creates a search -/// -/// \param searchRoot -/// \param pattern -/// \param flags -/// \param hSrch -/// \return -/// \retval - -public recls_rc_t Search_Create(in char[] searchRoot, in char[] pattern, in int flags, out hrecls_t hSrch) -{ - return Recls_Search(toStringz(searchRoot), toStringz(pattern), flags, &hSrch); -} - -/+ -private extern(Windows) int process_fn(recls_info_t entry, recls_process_fn_param_t p) -{ - return dg(Entry._make_Entry(entry), p); -} - -public recls_rc_t Search_Process( in char[] searchRoot - , in char[] pattern - , in int flags - , int delegate(in Entry entry, recls_process_fn_param_t param) dg - , recls_process_fn_param_t param) -{ -/* extern(Windows) int process_fn(recls_info_t entry, recls_process_fn_param_t p) - { - return dg(Entry._make_Entry(entry), p); - } - */ - return Recls_SearchProcess(searchRoot, pattern, flags, process_fn, param); -} -+/ - -/// Advances the given search to the next position -/// -/// \param hSrch handle identifying the search -/// \return return code indicating status of the operation -/// \return RECLS_ -public recls_rc_t Search_GetNext(in hrecls_t hSrch) -{ - return Recls_GetNext(hSrch); -} - -/// Closes the given search -/// -/// \param hSrch handle identifying the search -public void Search_Close(inout hrecls_t hSrch) -{ - Recls_SearchClose(hSrch); - - hSrch = null; -} - -public recls_rc_t Search_GetEntry(in hrecls_t hSrch, out recls_info_t entry) -{ - return Recls_GetDetails(hSrch, entry); -} - -public recls_rc_t Search_GetNextEntry(in hrecls_t hSrch, out recls_info_t entry) -{ - return Recls_GetNextDetails(hSrch, entry); -} - -public void Search_CloseEntry(inout recls_info_t entry) -{ - Recls_CloseDetails(entry); - - entry = null; -} - -public recls_info_t Search_CopyEntry(in recls_info_t entry) -{ - recls_info_t copy; - - if(RECLS_FAILED(Recls_CopyDetails(entry, ©))) - { - copy = null; - } - - return copy; -} - -public recls_rc_t Search_OutstandingDetails(in hrecls_t hSrch, out recls_uint32_t count) -{ - return Recls_OutstandingDetails(hSrch, count); -} - -public recls_rc_t Search_GetLastError(in hrecls_t hSrch) -{ - return Recls_GetLastError(hSrch); -} - -public char[] Search_GetErrorString(in recls_rc_t rc) -{ - uint cch = Recls_GetErrorString(rc, null, 0); - char[] err = new char[cch]; - - cch = Recls_GetErrorString(rc, err, err.length); - - assert(cch <= err.length); - - return err; -} - -public char[] Search_GetEntryPath(in recls_info_t entry) -in -{ - assert(null !is entry); -} -body -{ - uint cch = Recls_GetPathProperty(entry, null, 0); - char[] path = new char[cch]; - - cch = Recls_GetPathProperty(entry, path, path.length); - - assert(cch <= path.length); - - return path; -} - -version(Windows) -{ -public char Search_GetEntryDrive(in recls_info_t entry) -in -{ - assert(null !is entry); -} -body -{ - char chDrive; - - return (Recls_GetDriveProperty(entry, chDrive), chDrive); -} -} - -public char[] Search_GetEntryDirectory(in recls_info_t entry) -in -{ - assert(null !is entry); -} -body -{ - uint cch = Recls_GetDirectoryProperty(entry, null, 0); - char[] str = new char[cch]; - - cch = Recls_GetDirectoryProperty(entry, str, str.length); - - assert(cch <= str.length); - - return str; -} - -public char[] Search_GetEntryDirectoryPath(in recls_info_t entry) -in -{ - assert(null !is entry); -} -body -{ - uint cch = Recls_GetDirectoryPathProperty(entry, null, 0); - char[] str = new char[cch]; - - cch = Recls_GetDirectoryPathProperty(entry, str, str.length); - - assert(cch <= str.length); - - return str; -} - -public char[] Search_GetEntryFile(in recls_info_t entry) -in -{ - assert(null !is entry); -} -body -{ - uint cch = Recls_GetFileProperty(entry, null, 0); - char[] str = new char[cch]; - - cch = Recls_GetFileProperty(entry, str, str.length); - - assert(cch <= str.length); - - return str; -} - -version(Windows) -{ -public char[] Search_GetEntryShortFile(in recls_info_t entry) -in -{ - assert(null !is entry); -} -body -{ - uint cch = Recls_GetShortFileProperty(entry, null, 0); - char[] str = new char[cch]; - - cch = Recls_GetShortFileProperty(entry, str, str.length); - - assert(cch <= str.length); - - return str; -} -} -else -{ -public char[] Search_GetEntryShortFile(in recls_info_t entry) -{ - return Search_GetEntryFile(entry); -} -} - -public char[] Search_GetEntryFileName(in recls_info_t entry) -in -{ - assert(null !is entry); -} -body -{ - uint cch = Recls_GetFileNameProperty(entry, null, 0); - char[] str = new char[cch]; - - cch = Recls_GetFileNameProperty(entry, str, str.length); - - assert(cch <= str.length); - - return str; -} - -public char[] Search_GetEntryFileExt(in recls_info_t entry) -in -{ - assert(null !is entry); -} -body -{ - uint cch = Recls_GetFileExtProperty(entry, null, 0); - char[] str = new char[cch]; - - cch = Recls_GetFileExtProperty(entry, str, str.length); - - assert(cch <= str.length); - - return str; -} - -public char[][] Search_GetEntryDirectoryParts(in recls_info_t entry) -in -{ - assert(null !is entry); -} -body -{ - uint cParts = Recls_GetDirectoryPartProperty(entry, -1, null, 0); - char[][] parts = new char[][cParts]; - - for(int i = 0; i < cParts; ++i) - { - uint cch = Recls_GetDirectoryPartProperty(entry, i, null, 0); - char[] str = new char[cch]; - - cch = Recls_GetDirectoryPartProperty(entry, i, str, str.length); - - assert(cch <= str.length); - - parts[i] = str; - } - - return parts; -} - -public boolean Search_IsEntryReadOnly(in recls_info_t entry) -in -{ - assert(null !is entry); -} -body -{ - return Recls_IsFileReadOnly(entry); -} - -public boolean Search_IsEntryDirectory(in recls_info_t entry) -in -{ - assert(null !is entry); -} -body -{ - return Recls_IsFileDirectory(entry); -} - -public boolean Search_IsEntryLink(in recls_info_t entry) -in -{ - assert(null !is entry); -} -body -{ - return Recls_IsFileLink(entry); -} - -public recls_filesize_t Search_GetEntrySize(in recls_info_t entry) -in -{ - assert(null !is entry); -} -body -{ - recls_filesize_t size; - - //return (Recls_GetSizeProperty(entry, &size), size); - Recls_GetSizeProperty(entry, &size); - return size; -} - -public recls_time_t Search_GetEntryCreationTime(in recls_info_t entry) -in -{ - assert(null !is entry); -} -body -{ - return Recls_GetCreationTime(entry); -} - -public recls_time_t Search_GetEntryModificationTime(in recls_info_t entry) -in -{ - assert(null !is entry); -} -body -{ - return Recls_GetModificationTime(entry); -} - -public recls_time_t Search_GetEntryLastAccessTime(in recls_info_t entry) -in -{ - assert(null !is entry); -} -body -{ - return Recls_GetLastAccessTime(entry); -} - -public recls_time_t Search_GetEntryLastStatusChangeTime(in recls_info_t entry) -in -{ - assert(null !is entry); -} -body -{ - return Recls_GetLastStatusChangeTime(entry); -} - -//////////////////////////////////////////////////////////////////////////////// -// Classes - -/// Represents a search -public class Search -{ -/// \name Construction -public: - /// Create a search object with the given searchRoot, pattern and flags - /// - /// \param searchRoot The root directory of the search. If null, or the empty string, the current directory is assumed - /// \param pattern The search pattern. If null, or the empty string, all entries are returned - /// \param flags The flags with moderate the search - this(in char[] searchRoot, in char[] pattern, in uint flags) - { - m_searchRoot = searchRoot; - m_pattern = pattern; - m_flags = flags; - } - -/// \name Types -public: - class Enumerator - { - public: - this(hrecls_t hSrch, recls_rc_t lastError) - { - m_hSrch = hSrch; - m_lastError = lastError; - } - public: - ~this() - { - if(null != m_hSrch) - { - Search_Close(m_hSrch); - } - } - - public: - boolean HasEntry() - { - return RECLS_SUCCEEDED(m_lastError); - } - - Entry CurrentEntry() - in - { - assert(null !is m_hSrch); - } - body - { - recls_info_t entry; - recls_rc_t rc = Search_GetEntry(m_hSrch, entry); - - m_lastError = rc; - - try - { - return Entry._make_Entry(entry); - } - finally - { - Search_CloseEntry(entry); - } - } - - recls_rc_t LastError() - { - return m_lastError; - } - - public: - boolean GetNextEntry() - in - { - assert(null != m_hSrch); - } - body - { - recls_rc_t rc = Search_GetNext(m_hSrch); - - m_lastError = rc; - - if(RECLS_FAILED(rc)) - { - Search_Close(m_hSrch); - - if(RECLS_RC_NO_MORE_DATA != rc) - { - // throw new ReclsException("Search continuation failed", rc); - } - } - - return RECLS_SUCCEEDED(rc); - } - - /// Members - private: - hrecls_t m_hSrch; // NOTE THAT D DOES STRONG TYPEDEFS (see true-typedefs) - recls_rc_t m_lastError; - } - -/// Operations -public: - Enumerator Enumerate() - { - hrecls_t hSrch; - recls_rc_t rc = Search_Create(m_searchRoot, m_pattern, m_flags, hSrch); - - try - { - return new Enumerator(hSrch, rc); - } - catch(Exception x) - { - Search_Close(hSrch); - - throw x; - } - } - -public: - int opApply(int delegate(inout Entry entry) dg) - { - int result = 0; - hrecls_t hSrch; - recls_rc_t rc = Search_Create(m_searchRoot, m_pattern, m_flags, hSrch); - recls_info_t entry; - - do - { - if(RECLS_FAILED(rc)) - { - if(RECLS_RC_NO_MORE_DATA != rc) - { - // throw new ReclsException("Search continuation failed", rc); - } - - result = 1; - } - else - { - rc = Search_GetEntry(hSrch, entry); - - if(RECLS_FAILED(rc)) - { - if(RECLS_RC_NO_MORE_DATA != rc) - { - // throw new ReclsException("Search continuation failed", rc); - } - - result = 1; - } - else - { - try - { - Entry e = Entry._make_Entry(entry); - - result = dg(e); - } - finally - { - Search_CloseEntry(entry); - } - } - - rc = Search_GetNextEntry(hSrch, entry); - } - - } while(result == 0); - - return result; - } - -/// Members -private: - char[] m_searchRoot; - char[] m_pattern; - uint m_flags; -} - -/* public class Boolean -{ -public: - this(boolean value) - { - m_value = value; - } - - op() - { - return m_value != 0; - } - -private: - boolean m_value; -} - */ - -/// Represents a search entry -public class Entry -{ - invariant - { - if(null != m_entry) - { - // Now do all the checks to verify that the various components of the path are valid - - // Since we cannot call member functions (as that would end up in recursion) - // the only thing we can do is to "test" the validity of the entry handle, so - // we just add a reference, and then release it - recls_info_t entry = Search_CopyEntry(m_entry); - - assert(null !is entry); - - Recls_CloseDetails(entry); - } - } - -private: - /// This is necessary, because DMD 0.73 generates code - /// that goes into an infinite loop when creating an - /// Entry instance with a non-null entry - static Entry _make_Entry(recls_info_t entry) - { - recls_info_t copy = Search_CopyEntry(entry); - Entry e = null; - - try - { - e = new Entry(null); - - e.m_entry = entry; - } - catch(Exception x) - { - Search_CloseEntry(copy); - - throw x; - } - - return e; - } - - this(recls_info_t entry) - { - m_entry = entry; - } - ~this() - { - if(null !is m_entry) - { - Search_CloseEntry(m_entry); - } - } - -public: - /// The full path of the entry - /// - /// \note For "/usr/include/recls/recls_assert.h" this would yield "/usr/include/recls/recls_assert.h" - char[] GetPath() - in - { - assert(null !is m_entry); - } - body - { - return Search_GetEntryPath(m_entry); - } - /// The full path of the entry - /// - /// \note For "/usr/include/recls/recls_assert.h" this would yield "/usr/include/recls/recls_assert.h" - char[] Path() - in - { - assert(null !is m_entry); - } - body - { - return Search_GetEntryPath(m_entry); - } -version(Windows) -{ - /// The drive component of the entry's path - /// - /// \note For "H:\Dev\include\recls\recls_assert.h" this would yield 'H' - char Drive() - in - { - assert(null !is m_entry); - } - body - { - return Search_GetEntryDrive(m_entry); - } -} // version(Windows) - /// The directory component of the entry's path - /// - /// \note For "/usr/include/recls/recls_assert.h" this would yield "/usr/include/recls/" - char[] Directory() - in - { - assert(null !is m_entry); - } - body - { - return Search_GetEntryDirectory(m_entry); - } - /// The full location component of the entry's path. - /// - /// \note This is everything before the filename+fileext. On Win32 systems for "H:\Dev\include\recls\recls_assert.h" this would yield "H:\Dev\include\recls\" - char[] DirectoryPath() - in - { - assert(null !is m_entry); - } - body - { - return Search_GetEntryDirectoryPath(m_entry); - } - /// An array of strings representing the parts of the Directory property - /// - /// \note For "/usr/include/recls/recls_assert.h" this would yield [ "/", "usr/", "include/", "recls/"] - char[][] DirectoryParts() - in - { - assert(null !is m_entry); - } - body - { - return Search_GetEntryDirectoryParts(m_entry); - } - /// The file component of the entry's path - /// - /// \note For "/usr/include/recls/recls_assert.h" this would yield "recls_assert.h" - char[] File() - in - { - assert(null !is m_entry); - } - body - { - return Search_GetEntryFile(m_entry); - } - /// The short equivalent of the entry's File property - /// - /// \note On Win32 systems, this is the 8.3 form, e.g. "recls_~1.h". On other systems this is identical to the File property - char[] ShortFile() - in - { - assert(null !is m_entry); - } - body - { - return Search_GetEntryShortFile(m_entry); - } - /// The file name component of the entry's path - /// - /// \note For "/usr/include/recls/recls_assert.h" this would yield "recls_assert" - char[] FileName() - in - { - assert(null !is m_entry); - } - body - { - return Search_GetEntryFileName(m_entry); - } - /// The file extension component of the entry's path - /// - /// \note For "/usr/include/recls/recls_assert.h" this would yield "h" - char[] FileExt() - in - { - assert(null !is m_entry); - } - body - { - return Search_GetEntryFileExt(m_entry); - } - - /// The time the entry was created - recls_time_t CreationTime() - in - { - assert(null !is m_entry); - } - body - { - return Search_GetEntryCreationTime(m_entry); - } - /// The time the entry was last modified - recls_time_t ModificationTime() - in - { - assert(null !is m_entry); - } - body - { - return Search_GetEntryModificationTime(m_entry); - } - /// The time the entry was last accessed - recls_time_t LastAccessTime() - in - { - assert(null !is m_entry); - } - body - { - return Search_GetEntryLastAccessTime(m_entry); - } - /// The time the entry's last status changed - recls_time_t LastStatusChangeTime() - in - { - assert(null !is m_entry); - } - body - { - return Search_GetEntryLastStatusChangeTime(m_entry); - } - - /// The size of the entry - recls_filesize_t Size() - in - { - assert(null !is m_entry); - } - body - { - return Search_GetEntrySize(m_entry); - } - - /// Indicates whether the entry is read-only - boolean IsReadOnly() - in - { - assert(null !is m_entry); - } - body - { - return Search_IsEntryReadOnly(m_entry); - } - /// Indicates whether the entry is a directory - boolean IsDirectory() - in - { - assert(null !is m_entry); - } - body - { - return Search_IsEntryDirectory(m_entry); - } - /// Indicates whether the entry is a link - boolean IsLink() - in - { - assert(null !is m_entry); - } - body - { - return Search_IsEntryLink(m_entry); - } - -/// Members -private: - recls_info_t m_entry; -} - -//////////////////////////////////////////////////////////////////////////////// - -unittest -{ - Search search = new Search(".", "*.*", RECLS_FLAG.RECLS_F_RECURSIVE); - - foreach(Entry entry; search) - { - entry.Path(); -version(Windows) -{ - entry.Drive(); -} // version(Windows) - entry.Directory(); - entry.DirectoryPath(); - entry.DirectoryParts(); - entry.File(); - entry.ShortFile(); - entry.FileName(); - entry.FileExt(); - entry.CreationTime(); - entry.ModificationTime(); - entry.LastAccessTime(); - entry.LastStatusChangeTime(); - entry.Size(); - entry.IsReadOnly(); - entry.IsDirectory(); - entry.IsLink(); - } -} - -//////////////////////////////////////////////////////////////////////////////// diff -uNr gdc-0.17/d/phobos/std/regexp.d gdc-0.18/d/phobos/std/regexp.d --- gdc-0.17/d/phobos/std/regexp.d 2005-04-28 23:12:43.000000000 +0200 +++ gdc-0.18/d/phobos/std/regexp.d 2006-05-14 04:21:51.000000000 +0200 @@ -29,6 +29,41 @@ Modified by David Friedman, September 2004 */ +/********************************************** + * $(LINK2 ../../../ctg/regular.html, Regular expressions) + * are a powerful method of string pattern matching. + * The regular expression + * language used is the same as that commonly used, however, some of the very + * advanced forms may behave slightly differently. + * + * In the following guide, $(I pattern)[] refers to a + * $(LINK2 ../../../ctg/regular.html, regular expression). + * The $(I attributes)[] refers to + a string controlling the interpretation + of the regular expression. + It consists of a sequence of one or more + of the following characters: + + + + + + + + +
    Attribute + Action +
    $(B g) + global; repeat over the whole input string +
    $(B i) + case insensitive +
    $(B m) + treat as multiple lines separated by newlines +
    + + * Macros: + * WIKI = StdRegexp + */ /* Escape sequences: @@ -68,16 +103,26 @@ { import std.c.stdio; import std.c.stdlib; + import std.c.string; import std.string; import std.ctype; import std.outbuffer; + import std.bitarray; + import std.intrinsic; } +/** Regular expression to extract an _email address */ +const char[] email = + r"[a-zA-Z]([.]?([[a-zA-Z0-9_]-]+)*)?@([[a-zA-Z0-9_]\-_]+\.)+[a-zA-Z]{2,6}"; + +/** Regular expression to extract a _url */ +const char[] url = r"(([h|H][t|T]|[f|F])[t|T][p|P]([s|S]?)\:\/\/|~/|/)?([\w]+:\w+@)?(([a-zA-Z]{1}([\w\-]+\.)+([\w]{2,5}))(:[\d]{1,5})?)?((/?\w+/)+|/?)(\w+\.[\w]{3,4})?([,]\w+)*((\?\w+=\w+)?(&\w+=\w+)*([,]\w*)*)?"; + /************************************ - * One of these gets thrown on compilation error + * One of these gets thrown on compilation errors */ -class RegExpError : Error +class RegExpException : Exception { this(char[] msg) { @@ -93,14 +138,380 @@ private alias char rchar; // so we can make a wchar version +/****************************************************** + * Search string for matches with regular expression + * pattern with attributes. + * Replace each match with string generated from format. + * Params: + * string = String to search. + * pattern = Regular expression pattern. + * format = Replacement string format. + * attributes = Regular expression attributes. + * Returns: the resulting string. + */ + +char[] sub(char[] string, char[] pattern, char[] format, char[] attributes = null) +{ + RegExp r = new RegExp(pattern, attributes); + char[] result = r.replace(string, format); + delete r; + return result; +} + +unittest +{ + debug(regexp) printf("regexp.sub.unittest\n"); + + char[] r = sub("hello", "ll", "ss"); + assert(r == "hesso"); +} + +/******************************************************* + * Search string for matches with regular expression + * pattern with attributes. + * Pass each match to delegate dg. + * Replace each match with the return value from dg. + * Params: + * string = String to search. + * pattern = Regular expression pattern. + * dg = Delegate + * attributes = Regular expression attributes. + * Returns: the resulting string. + */ + +char[] sub(char[] string, char[] pattern, char[] delegate(RegExp) dg, char[] attributes = null) +{ + RegExp r = new RegExp(pattern, attributes); + rchar[] result; + int lastindex; + int offset; + + result = string; + lastindex = 0; + offset = 0; + while (r.test(string, lastindex)) + { + int so = r.pmatch[0].rm_so; + int eo = r.pmatch[0].rm_eo; + + rchar[] replacement = dg(r); + + // Optimize by using std.string.replace if possible - Dave Fladebo + rchar[] slice = result[offset + so .. offset + eo]; + if (r.attributes & RegExp.REA.global && // global, so replace all + !(r.attributes & RegExp.REA.ignoreCase) && // not ignoring case + !(r.attributes & RegExp.REA.multiline) && // not multiline + pattern == slice && // simple pattern (exact match, no special characters) + format == replacement) // simple format, not $ formats + { + debug(regexp) + printf("pattern: %.*s, slice: %.*s, format: %.*s, replacement: %.*s\n",pattern,result[offset + so .. offset + eo],format,replacement); + result = std.string.replace(result,slice,replacement); + break; + } + + result = replaceSlice(result, result[offset + so .. offset + eo], replacement); + + if (r.attributes & RegExp.REA.global) + { + offset += replacement.length - (eo - so); + + if (lastindex == eo) + lastindex++; // always consume some source + else + lastindex = eo; + } + else + break; + } + delete r; + + return result; +} + +unittest +{ + debug(regexp) printf("regexp.sub.unittest\n"); + + char[] foo(RegExp r) { return "ss"; } + + char[] r = sub("hello", "ll", delegate char[](RegExp r) { return "ss"; }); + assert(r == "hesso"); +} + + +/************************************************* + * Search string[] for first match with pattern[] with attributes[]. + * Params: + * string = String to search. + * pattern = Regular expression pattern. + * attributes = Regular expression attributes. + * Returns: + * index into string[] of match if found, -1 if no match. + */ + +int find(rchar[] string, char[] pattern, char[] attributes = null) +{ + int i = -1; + + RegExp r = new RegExp(pattern, attributes); + if (r.test(string)) + { + i = r.pmatch[0].rm_so; + } + delete r; + return i; +} + +unittest +{ + debug(regexp) printf("regexp.find.unittest\n"); + + int i; + i = find("xabcy", "abc"); + assert(i == 1); + i = find("cba", "abc"); + assert(i == -1); +} + + + +/************************************************* + * Search string[] for last match with pattern[] with attributes[]. + * Params: + * string = String to search. + * pattern = Regular expression pattern. + * attributes = Regular expression attributes. + * Returns: + * index into string[] of match if found, -1 if no match. + */ + +int rfind(rchar[] string, char[] pattern, char[] attributes = null) +{ + int i = -1; + int lastindex = 0; + + RegExp r = new RegExp(pattern, attributes); + while (r.test(string, lastindex)) + { int eo = r.pmatch[0].rm_eo; + i = r.pmatch[0].rm_so; + if (lastindex == eo) + lastindex++; // always consume some source + else + lastindex = eo; + } + delete r; + return i; +} + +unittest +{ + int i; + + debug(regexp) printf("regexp.rfind.unittest\n"); + i = rfind("abcdefcdef", "c"); + assert(i == 6); + i = rfind("abcdefcdef", "cd"); + assert(i == 6); + i = rfind("abcdefcdef", "x"); + assert(i == -1); + i = rfind("abcdefcdef", "xy"); + assert(i == -1); + i = rfind("abcdefcdef", ""); + assert(i == 10); +} + + +/******************************************** + * Split string[] into an array of strings, using the regular + * expression pattern[] with attributes[] as the separator. + * string = String to search. + * pattern = Regular expression pattern. + * attributes = Regular expression attributes. + * Returns: + * array of slices into string[] + */ + +char[][] split(char[] string, char[] pattern, char[] attributes = null) +{ + RegExp r = new RegExp(pattern, attributes); + char[][] result = r.split(string); + delete r; + return result; +} + +unittest +{ + debug(regexp) printf("regexp.split.unittest()\n"); + char[][] result; + + result = split("ab", "a*"); + assert(result.length == 2); + assert(result[0] == ""); + assert(result[1] == "b"); +} + +/**************************************************** + * Search string[] for first match with pattern[] with attributes[]. + * Params: + * string = String to search. + * pattern = Regular expression pattern. + * attributes = Regular expression attributes. + * Returns: + * corresponding RegExp if found, null if not. + * Example: + * --- + * import std.stdio; + * import std.regexp; + * + * void main() + * { + * if (m; std.regexp.search("abcdef", "c")) + * { + * writefln("%s[%s]%s", m.pre, m.match(0), m.post); + * } + * } + * // Prints: + * // ab[c]def + * --- + */ + +RegExp search(char[] string, char[] pattern, char[] attributes = null) +{ + RegExp r = new RegExp(pattern, attributes); + + if (r.test(string)) + { + } + else + { delete r; + r = null; + } + return r; +} + +/* ********************************* RegExp ******************************** */ + +/***************************** + * RegExp is a class to handle regular expressions. + * + * It is the core foundation for adding powerful string pattern matching + * capabilities to programs like grep, text editors, awk, sed, etc. + */ class RegExp { - public this(rchar[] pattern, rchar[] attributes) + /***** + * Construct a RegExp object. Compile pattern + * with attributes into + * an internal form for fast execution. + * Params: + * pattern = regular expression + * attributes = _attributes + * Throws: RegExpException if there are any compilation errors. + */ + public this(rchar[] pattern, rchar[] attributes = null) { pmatch = (&gmatch)[0 .. 1]; compile(pattern, attributes); } + /***** + * Generate instance of RegExp. + * Params: + * pattern = regular expression + * attributes = _attributes + * Throws: RegExpException if there are any compilation errors. + */ + public static RegExp opCall(rchar[] pattern, rchar[] attributes = null) + { + return new RegExp(pattern, attributes); + } + + /************************************ + * Set up for start of foreach loop. + * Returns: + * search() returns instance of RegExp set up to _search string[]. + * Example: + * --- + * import std.stdio; + * import std.regexp; + * + * void main() + * { + * foreach(m; RegExp("ab").search("abcabcabab")) + * { + * writefln("%s[%s]%s", m.pre, m.match(0), m.post); + * } + * } + * // Prints: + * // [ab]cabcabab + * // abc[ab]cabab + * // abcabc[ab]ab + * // abcabcab[ab] + * --- + */ + + public RegExp search(rchar[] string) + { + input = string; + pmatch[0].rm_eo = 0; + return this; + } + + /** ditto */ + public int opApply(int delegate(inout RegExp) dg) + { + int result; + RegExp r = this; + + while (test()) + { + result = dg(r); + if (result) + break; + } + + return result; + } + + /****************** + * Retrieve match n. + * + * n==0 means the matched substring, n>0 means the + * n'th parenthesized subexpression. + * if n is larger than the number of parenthesized subexpressions, + * null is returned. + */ + public char[] match(size_t n) + { + if (n >= pmatch.length) + return null; + else + { size_t rm_so, rm_eo; + rm_so = pmatch[n].rm_so; + rm_eo = pmatch[n].rm_eo; + if (rm_so == rm_eo) + return null; + return input[rm_so .. rm_eo]; + } + } + + /******************* + * Return the slice of the input that precedes the matched substring. + */ + public char[] pre() + { + return input[0 .. pmatch[0].rm_so]; + } + + /******************* + * Return the slice of the input that follows the matched substring. + */ + public char[] post() + { + return input[pmatch[0].rm_eo .. $]; + } + uint re_nsub; // number of parenthesized subexpression matches regmatch_t[] pmatch; // array [re_nsub + 1] @@ -186,8 +597,8 @@ private uint inf = ~0u; -/********************************* - * Throws RegExpError on error +/* ******************************** + * Throws RegExpException on error */ public void compile(rchar[] pattern, rchar[] attributes) @@ -346,10 +757,9 @@ } /************************************************* - * Search string[] for match. + * Search string[] for match with regular expression. * Returns: - * >=0 index of match - * -1 no match + * index of match if successful, -1 if not found */ public int find(rchar[] string) @@ -364,7 +774,7 @@ return i; } -deprecated alias find search; +//deprecated alias find search; unittest { @@ -382,8 +792,8 @@ /************************************************* * Search string[] for match. * Returns: - * if global, return same value as exec(string) - * if not global, return array of all matches + * If global attribute, return same value as exec(string). + * If not global attribute, return array of all matches. */ public rchar[][] match(rchar[] string) @@ -436,10 +846,10 @@ /************************************************* * Find regular expression matches in string[]. Replace those matches - * with a new string composed of format[] merged with the result of the + * with a new _string composed of format[] merged with the result of the * matches. * If global, replace all matches. Otherwise, replace first match. - * Return the new string. + * Returns: the new _string */ public rchar[] replace(rchar[] string, rchar[] format) @@ -460,6 +870,21 @@ int eo = pmatch[0].rm_eo; rchar[] replacement = replace(format); + + // Optimize by using std.string.replace if possible - Dave Fladebo + rchar[] slice = result[offset + so .. offset + eo]; + if (attributes & REA.global && // global, so replace all + !(attributes & REA.ignoreCase) && // not ignoring case + !(attributes & REA.multiline) && // not multiline + pattern == slice && // simple pattern (exact match, no special characters) + format == replacement) // simple format, not $ formats + { + debug(regexp) + printf("pattern: %.*s, slice: %.*s, format: %.*s, replacement: %.*s\n",pattern,result[offset + so .. offset + eo],format,replacement); + result = std.string.replace(result,slice,replacement); + break; + } + result = replaceSlice(result, result[offset + so .. offset + eo], replacement); if (attributes & REA.global) @@ -509,7 +934,8 @@ } /************************************************* - * Search string[] for next match. + * Pick up where last exec(string) or exec() left off, + * searching string[] for next match. * Returns: * array of slices into string[] representing matches */ @@ -535,9 +961,7 @@ /************************************************ * Search string[] for match. - * Returns: - * 0 no match - * !=0 match + * Returns: 0 for no match, !=0 for match */ public int test(rchar[] string) @@ -546,10 +970,8 @@ } /************************************************ - * Pick up where last test() left off, and search again. - * Returns: - * 0 no match - * !=0 match + * Pick up where last test(string) or test() left off, and search again. + * Returns: 0 for no match, !=0 for match */ public int test() @@ -558,10 +980,8 @@ } /************************************************ - * Test input[] starting at startindex against compiled in pattern[]. - * Returns: - * 0 no match - * !=0 match + * Test string[] starting at startindex against regular expression. + * Returns: 0 for no match, !=0 for match */ public int test(char[] string, int startindex) @@ -993,7 +1413,7 @@ c1 = input[src]; //printf("[x%02x]=x%02x, x%02x\n", c1 >> 3, ((&program[pc + 1 + 4])[c1 >> 3] ), (1 << (c1 & 7))); if (c1 <= pu[0] && - !((&(program[pc + 1 + 4]))[c1 >> 3] & (1 << (c1 & 7)))) + !bt(cast(uint*)&(program[pc + 1 + 4]), c1)) // assumes BitArray implementation goto Lnomatch; pc += 1 + 2 * ushort.sizeof + len; break; @@ -1008,7 +1428,7 @@ c1 = input[src]; if (c1 > pu[0]) goto Lnomatch; - if (!((&program[pc + 1 + 4])[c1 >> 3] & (1 << (c1 & 7)))) + if (!bt(cast(uint*)&(program[pc + 1 + 4]), c1)) // assumes BitArray implementation goto Lnomatch; src++; pc += 1 + 2 * ushort.sizeof + len; @@ -1023,7 +1443,7 @@ len = pu[1]; c1 = input[src]; if (c1 <= pu[0] && - ((&program[pc + 1 + 4])[c1 >> 3] & (1 << (c1 & 7)))) + bt(cast(uint*)&(program[pc + 1 + 4]), c1)) // assumes BitArray implementation goto Lnomatch; src++; pc += 1 + 2 * ushort.sizeof + len; @@ -1734,7 +2154,7 @@ uint maxb; OutBuffer buf; ubyte* base; - bit[] bits; + BitArray bits; this(OutBuffer buf) { @@ -1746,6 +2166,7 @@ void setbitmax(uint u) { uint b; + //printf("setbitmax(x%x), maxc = x%x\n", u, maxc); if (u > maxc) { maxc = u; @@ -1758,8 +2179,10 @@ base = &buf.data[u]; maxb = b + 1; // %% moved array recreate out of this condition + bits.ptr = cast(uint*)this.base; } - bits = (cast(bit*)this.base)[0 .. maxc + 1]; + //bits = (cast(bit*)this.base)[0 .. maxc + 1]; + bits.len = maxc + 1; } } @@ -1966,7 +2389,7 @@ debug(regexp) printf("error: %.*s\n", msg); //assert(0); //*(char*)0=0; - throw new RegExpError(msg); + throw new RegExpException(msg); } // p is following the \ char @@ -2095,11 +2518,10 @@ void optimize() { ubyte[] prog; - int i; debug(regexp) printf("RegExp.optimize()\n"); prog = buf.toBytes(); - for (i = 0; 1;) + for (size_t i = 0; 1;) { //printf("\tprog[%d] = %d, %d\n", i, prog[i], REstring); switch (prog[i]) @@ -2179,10 +2601,9 @@ uint n; uint m; ubyte* pop; - int i; //printf("RegExp.starrchars(prog = %p, progend = %p)\n", prog, progend); - for (i = 0; i < prog.length;) + for (size_t i = 0; i < prog.length;) { switch (prog[i]) { @@ -2346,73 +2767,40 @@ /* ==================== replace ======================= */ -/************************************ - * This version of replace() uses: - * & replace with the match - * \n replace with the nth parenthesized match, n is 1..9 - * \c replace with char c +/*********************** + * After a match is found with test(), this function + * will take the match results and, using the format + * string, generate and return a new string. + * The format string has the formatting characters: + * + $(TR $(TH Format) $(TH Replaced With)) + $(TR + $(TD $(B $$)) $(TD $) + ) + $(TR + $(TD $(B $&)) $(TD The matched substring.) + ) + $(TR + $(TD $(B $`)) $(TD The portion of string that precedes the matched substring.) + ) + $(TR + $(TD $(B $')) $(TD The portion of string that follows the matched substring.) + ) + $(TR + $(TD $(B $n)) $(TD The nth capture, where n is a single digit 1-9 + and $n is not followed by a decimal digit.) + ) + $(TR + $(TD $(B $nn)) $(TD The nnth capture, where nn is a two-digit decimal + number 01-99. + If nnth capture is undefined or more than the number + of parenthesized subexpressions, use the empty + string instead.) + ) +
    + Any other $ are left as is. */ -public rchar[] replaceOld(rchar[] format) -{ - OutBuffer buf; - rchar[] result; - rchar c; - -//printf("replace: this = %p so = %d, eo = %d\n", this, pmatch[0].rm_so, pmatch[0].rm_eo); -//printf("3input = '%.*s'\n", input); - buf = new OutBuffer(); - buf.reserve(format.length * rchar.sizeof); - for (uint i; i < format.length; i++) - { - c = format[i]; - switch (c) - { - case '&': -//printf("match = '%.*s'\n", input[pmatch[0].rm_so .. pmatch[0].rm_eo]); - buf.write(input[pmatch[0].rm_so .. pmatch[0].rm_eo]); - break; - - case '\\': - if (i + 1 < format.length) - { - c = format[++i]; - if (c >= '1' && c <= '9') - { uint i; - - i = c - '0'; - if (i <= re_nsub && pmatch[i].rm_so != pmatch[i].rm_eo) - buf.write(input[pmatch[i].rm_so .. pmatch[i].rm_eo]); - break; - } - } - buf.write(c); - break; - - default: - buf.write(c); - break; - } - } - result = cast(rchar[])buf.toBytes(); - return result; -} - -// This version of replace uses: -// $$ $ -// $& The matched substring. -// $` The portion of string that precedes the matched substring. -// $' The portion of string that follows the matched substring. -// $n The nth capture, where n is a single digit 1-9 -// and $n is not followed by a decimal digit. -// $nn The nnth capture, where nn is a two-digit decimal -// number 01-99. -// If nnth capture is undefined or more than the number -// of parenthesized subexpressions, use the empty -// string instead. -// -// Any other $ are left as is. - public rchar[] replace(rchar[] format) { return replace3(format, input, pmatch[0 .. re_nsub + 1]); @@ -2422,31 +2810,28 @@ private static rchar[] replace3(rchar[] format, rchar[] input, regmatch_t[] pmatch) { - OutBuffer buf; rchar[] result; - rchar c; uint c2; int rm_so; int rm_eo; int i; - int f; // printf("replace3(format = '%.*s', input = '%.*s')\n", format, input); - buf = new OutBuffer(); - buf.reserve(format.length * rchar.sizeof); - for (f = 0; f < format.length; f++) + result.length = format.length; + result.length = 0; + for (size_t f = 0; f < format.length; f++) { - c = format[f]; + auto c = format[f]; L1: if (c != '$') { - buf.write(c); + result ~= c; continue; } ++f; if (f == format.length) { - buf.write(cast(rchar)'$'); + result ~= '$'; break; } c = format[f]; @@ -2474,8 +2859,8 @@ { if (i == 0) { - buf.write(cast(rchar)'$'); - buf.write(c); + result ~= '$'; + result ~= c; continue; } } @@ -2488,8 +2873,8 @@ } if (i == 0) { - buf.write(cast(rchar)'$'); - buf.write(c); + result ~= '$'; + result ~= c; c = c2; goto L1; } @@ -2504,211 +2889,79 @@ Lstring: if (rm_so != rm_eo) - buf.write(input[rm_so .. rm_eo]); + result ~= input[rm_so .. rm_eo]; break; default: - buf.write(cast(rchar)'$'); - buf.write(c); + result ~= '$'; + result ~= c; break; } } - result = cast(rchar[])buf.toBytes(); return result; } -} - -/**************************************************** - * Search str for regular expression pattern. - * If match, return a RegExp for the match. - * If no match, return null. - */ - -RegExp search(char[] str, char[] pattern, char[] attributes = null) -{ - RegExp r = new RegExp(pattern, attributes); - - if (r.test(str)) - { - } - else - { delete r; - r = null; - } - return r; -} - - -/****************************************************** - * Search str for pattern, replace occurrences with format. - */ - -char[] sub(char[] str, char[] pattern, char[] format, char[] attributes = null) -{ - RegExp r = new RegExp(pattern, attributes); - char[] result = r.replace(str, format); - delete r; - return result; -} - -unittest -{ - debug(regexp) printf("regexp.sub.unittest\n"); - - char[] r = sub("hello", "ll", "ss"); - assert(r == "hesso"); -} - -/******************************************************* - * Search str for pattern, replace occurrences with string - * returned from dg. +/************************************ + * Like replace(char[] format), but uses old style formatting: + + + + + + + +
    Format + Description +
    & + replace with the match +
    \n + replace with the nth parenthesized match, n is 1..9 +
    \c + replace with char c. +
    */ -char[] sub(char[] str, char[] pattern, char[] delegate(RegExp) dg, char[] attributes = null) +public rchar[] replaceOld(rchar[] format) { - RegExp r = new RegExp(pattern, attributes); rchar[] result; - int lastindex; - int offset; - result = str; - lastindex = 0; - offset = 0; - while (r.test(str, lastindex)) +//printf("replace: this = %p so = %d, eo = %d\n", this, pmatch[0].rm_so, pmatch[0].rm_eo); +//printf("3input = '%.*s'\n", input); + result.length = format.length; + result.length = 0; + for (size_t i; i < format.length; i++) { - int so = r.pmatch[0].rm_so; - int eo = r.pmatch[0].rm_eo; + auto c = format[i]; + switch (c) + { + case '&': +//printf("match = '%.*s'\n", input[pmatch[0].rm_so .. pmatch[0].rm_eo]); + result ~= input[pmatch[0].rm_so .. pmatch[0].rm_eo]; + break; - rchar[] replacement = dg(r); - result = replaceSlice(result, result[offset + so .. offset + eo], replacement); + case '\\': + if (i + 1 < format.length) + { + c = format[++i]; + if (c >= '1' && c <= '9') + { uint i; - if (r.attributes & RegExp.REA.global) - { - offset += replacement.length - (eo - so); + i = c - '0'; + if (i <= re_nsub && pmatch[i].rm_so != pmatch[i].rm_eo) + result ~= input[pmatch[i].rm_so .. pmatch[i].rm_eo]; + break; + } + } + result ~= c; + break; - if (lastindex == eo) - lastindex++; // always consume some source - else - lastindex = eo; + default: + result ~= c; + break; } - else - break; } - delete r; - return result; } -unittest -{ - debug(regexp) printf("regexp.sub.unittest\n"); - - char[] foo(RegExp r) { return "ss"; } - - char[] r = sub("hello", "ll", delegate char[](RegExp r) { return "ss"; }); - assert(r == "hesso"); } - -/************************************************* - * Search string[] for match with pattern[]. - * Returns: - * >=0 index of match - * -1 no match - */ - -int find(rchar[] string, char[] pattern, char[] attributes = null) -{ - int i = -1; - - RegExp r = new RegExp(pattern, attributes); - if (r.test(string)) - { - i = r.pmatch[0].rm_so; - } - delete r; - return i; -} - -unittest -{ - debug(regexp) printf("regexp.find.unittest\n"); - - int i; - i = find("xabcy", "abc"); - assert(i == 1); - i = find("cba", "abc"); - assert(i == -1); -} - - - -/************************************************* - * Search string[] for last match with pattern[]. - * Returns: - * >=0 index of match - * -1 no match - */ - -int rfind(rchar[] string, char[] pattern, char[] attributes = null) -{ - int i = -1; - int lastindex = 0; - - RegExp r = new RegExp(pattern, attributes); - while (r.test(string, lastindex)) - { int eo = r.pmatch[0].rm_eo; - i = r.pmatch[0].rm_so; - if (lastindex == eo) - lastindex++; // always consume some source - else - lastindex = eo; - } - delete r; - return i; -} - -unittest -{ - int i; - - debug(regexp) printf("regexp.rfind.unittest\n"); - i = rfind("abcdefcdef", "c"); - assert(i == 6); - i = rfind("abcdefcdef", "cd"); - assert(i == 6); - i = rfind("abcdefcdef", "x"); - assert(i == -1); - i = rfind("abcdefcdef", "xy"); - assert(i == -1); - i = rfind("abcdefcdef", ""); - assert(i == 10); -} - - -/******************************************** - * Split string[] into an array of strings, using the regular - * expression as the separator. - * Returns: - * array of slices into string[] - */ - -char[][] split(char[] string, char[] pattern, char[] attributes = null) -{ - RegExp r = new RegExp(pattern, attributes); - char[][] result = r.split(string); - delete r; - return result; -} - -unittest -{ - debug(regexp) printf("regexp.split.unittest()\n"); - char[][] result; - - result = split("ab", "a*"); - assert(result.length == 2); - assert(result[0] == ""); - assert(result[1] == "b"); -} diff -uNr gdc-0.17/d/phobos/std/socket.d gdc-0.18/d/phobos/std/socket.d --- gdc-0.17/d/phobos/std/socket.d 2005-06-22 05:13:40.000000000 +0200 +++ gdc-0.18/d/phobos/std/socket.d 2006-05-14 03:05:56.000000000 +0200 @@ -30,15 +30,31 @@ Modified by David Friedman, April 2005 */ +/** + * Notes: For Win32 systems, link with ws2_32.lib. + * Example: See /dmd/samples/d/listener.d. + * Authors: Christopher E. Miller + * Macros: + * WIKI=Phobos/StdSocket + */ + module std.socket; -private import std.string, std.stdint, std.c.stdlib; +private import std.string, std.stdint, std.c.string, std.c.stdlib; version(Unix) { version = BsdSockets; } + +version (skyos) { /* nothging */ } +else +{ + version = have_getservbyport; + version = have_getprotobynumber; +} + version(Win32) { @@ -77,9 +93,10 @@ } +/// Base exception thrown from a Socket. class SocketException: Exception { - int errorCode; // Platform-specific error code. + int errorCode; /// Platform-specific error code. this(char[] msg, int err = 0) @@ -133,47 +150,58 @@ } } - +/** + * The communication domain used to resolve an address. + */ enum AddressFamily: int { - UNSPEC = AF_UNSPEC, - UNIX = AF_UNIX, - INET = AF_INET, - IPX = AF_IPX, - APPLETALK = AF_APPLETALK, - INET6 = AF_INET6, + UNSPEC = AF_UNSPEC, /// + UNIX = AF_UNIX, /// local communication + INET = AF_INET, /// internet protocol version 4 + IPX = AF_IPX, /// novell IPX + APPLETALK = AF_APPLETALK, /// appletalk + INET6 = AF_INET6, // internet protocol version 6 } +/** + * Communication semantics + */ enum SocketType: int { - STREAM = SOCK_STREAM, - DGRAM = SOCK_DGRAM, - RAW = SOCK_RAW, - RDM = SOCK_RDM, - SEQPACKET = SOCK_SEQPACKET, + STREAM = SOCK_STREAM, /// sequenced, reliable, two-way communication-based byte streams + DGRAM = SOCK_DGRAM, /// connectionless, unreliable datagrams with a fixed maximum length; data may be lost or arrive out of order + RAW = SOCK_RAW, /// raw protocol access + RDM = SOCK_RDM, /// reliably-delivered message datagrams + SEQPACKET = SOCK_SEQPACKET, /// sequenced, reliable, two-way connection-based datagrams with a fixed maximum length } +/** + * Protocol + */ enum ProtocolType: int { - IP = IPPROTO_IP, - ICMP = IPPROTO_ICMP, - IGMP = IPPROTO_IGMP, - GGP = IPPROTO_GGP, - TCP = IPPROTO_TCP, - PUP = IPPROTO_PUP, - UDP = IPPROTO_UDP, - IDP = IPPROTO_IDP, - IPV6 = IPPROTO_IPV6, + IP = IPPROTO_IP, /// internet protocol version 4 + ICMP = IPPROTO_ICMP, /// internet control message protocol + IGMP = IPPROTO_IGMP, /// internet group management protocol + GGP = IPPROTO_GGP, /// gateway to gateway protocol + TCP = IPPROTO_TCP, /// transmission control protocol + PUP = IPPROTO_PUP, /// PARC universal packet protocol + UDP = IPPROTO_UDP, /// user datagram protocol + IDP = IPPROTO_IDP, /// Xerox NS protocol + IPV6 = IPPROTO_IPV6, /// internet protocol version 6 } +/** + * Protocol is a class for retrieving protocol information. + */ class Protocol { - ProtocolType type; - char[] name; - char[][] aliases; + ProtocolType type; /// These members are populated when one of the following functions are called without failure: + char[] name; /// ditto + char[][] aliases; /// ditto void populate(protoent* proto) @@ -202,8 +230,8 @@ } } - - bit getProtocolByName(char[] name) + /** Returns false on failure */ + bool getProtocolByName(char[] name) { protoent* proto; proto = getprotobyname(toStringz(name)); @@ -214,15 +242,21 @@ } + /** Returns false on failure */ // Same as getprotobynumber(). - bit getProtocolByType(ProtocolType type) + bool getProtocolByType(ProtocolType type) { + version (have_getprotobynumber) + { protoent* proto; proto = getprotobynumber(type); if(!proto) return false; populate(proto); return true; + } + else + return false; } } @@ -239,12 +273,16 @@ } +/** + * Service is a class for retrieving service information. + */ class Service { + /** These members are populated when one of the following functions are called without failure: */ char[] name; - char[][] aliases; - ushort port; - char[] protocolName; + char[][] aliases; /// ditto + ushort port; /// ditto + char[] protocolName; /// ditto void populate(servent* serv) @@ -274,8 +312,11 @@ } } - - bit getServiceByName(char[] name, char[] protocolName) + /** + * If a protocol name is omitted, any protocol will be matched. + * Returns: false on failure. + */ + bool getServiceByName(char[] name, char[] protocolName) { servent* serv; serv = getservbyname(toStringz(name), toStringz(protocolName)); @@ -287,7 +328,8 @@ // Any protocol name will be matched. - bit getServiceByName(char[] name) + /// ditto + bool getServiceByName(char[] name) { servent* serv; serv = getservbyname(toStringz(name), null); @@ -298,26 +340,38 @@ } - bit getServiceByPort(ushort port, char[] protocolName) + /// ditto + bool getServiceByPort(ushort port, char[] protocolName) { + version (have_getservbyport) + { servent* serv; serv = getservbyport(port, toStringz(protocolName)); if(!serv) return false; populate(serv); return true; + } + else + return false; } // Any protocol name will be matched. - bit getServiceByPort(ushort port) + /// ditto + bool getServiceByPort(ushort port) { + version (have_getservbyport) + { servent* serv; serv = getservbyport(port, null); if(!serv) return false; populate(serv); return true; + } + else + return false; } } @@ -341,9 +395,12 @@ } +/** + * Base exception thrown from an InternetHost. + */ class HostException: Exception { - int errorCode; + int errorCode; /// Platform-specific error code. this(char[] msg, int err = 0) @@ -353,12 +410,15 @@ } } - +/** + * InternetHost is a class for resolving IPv4 addresses. + */ class InternetHost { + /** These members are populated when one of the following functions are called without failure: */ char[] name; - char[][] aliases; - uint32_t[] addrList; + char[][] aliases; /// ditto + uint32_t[] addrList; /// ditto void validHostent(hostent* he) @@ -416,8 +476,10 @@ } } - - bit getHostByName(char[] name) + /** + * Resolve host name. Returns false if unable to resolve. + */ + bool getHostByName(char[] name) { hostent* he = gethostbyname(toStringz(name)); if(!he) @@ -428,7 +490,10 @@ } - bit getHostByAddr(uint addr) + /** + * Resolve IPv4 address number. Returns false if unable to resolve. + */ + bool getHostByAddr(uint addr) { uint x = htonl(addr); hostent* he = gethostbyaddr(&x, 4, cast(int)AddressFamily.INET); @@ -440,8 +505,12 @@ } - //shortcut - bit getHostByAddr(char[] addr) + /** + * Same as previous, but addr is an IPv4 address string in the + * dotted-decimal form $(I a.b.c.d). + * Returns false if unable to resolve. + */ + bool getHostByAddr(char[] addr) { uint x = inet_addr(std.string.toStringz(addr)); hostent* he = gethostbyaddr(&x, 4, cast(int)AddressFamily.INET); @@ -478,6 +547,9 @@ } +/** + * Base exception thrown from an Address. + */ class AddressException: Exception { this(char[] msg) @@ -487,15 +559,20 @@ } +/** + * Address is an abstract class for representing a network addresses. + */ abstract class Address { protected sockaddr* name(); protected int nameLen(); - AddressFamily addressFamily(); - char[] toString(); + AddressFamily addressFamily(); /// Family of this address. + char[] toString(); /// Human readable string representing this address. } - +/** + * + */ class UnknownAddress: Address { protected: @@ -528,6 +605,10 @@ } +/** + * InternetAddress is a class that represents an IPv4 (internet protocol version + * 4) address and port. + */ class InternetAddress: Address { protected: @@ -552,31 +633,35 @@ public: - const uint ADDR_ANY = INADDR_ANY; - const uint ADDR_NONE = INADDR_NONE; - const ushort PORT_ANY = 0; - + const uint ADDR_ANY = INADDR_ANY; /// Any IPv4 address number. + const uint ADDR_NONE = INADDR_NONE; /// An invalid IPv4 address number. + const ushort PORT_ANY = 0; /// Any IPv4 port number. + /// Overridden to return AddressFamily.INET. AddressFamily addressFamily() { return cast(AddressFamily)AddressFamily.INET; } - + /// Returns the IPv4 port number. ushort port() { return ntohs(sin.sin_port); } - + /// Returns the IPv4 address number. uint addr() { return ntohl(sin.sin_addr.s_addr); } - - //-port- can be PORT_ANY - //-addr- is an IP address or host name + /** + * Params: + * addr = an IPv4 address string in the dotted-decimal form a.b.c.d, + * or a host name that will be resolved using an InternetHost + * object. + * port = may be PORT_ANY as stated below. + */ this(char[] addr, ushort port) { uint uiaddr = parse(addr); @@ -592,41 +677,48 @@ sin.sin_port = htons(port); } - + /** + * Construct a new Address. addr may be ADDR_ANY (default) and port may + * be PORT_ANY, and the actual numbers may not be known until a connection + * is made. + */ this(uint addr, ushort port) { sin.sin_addr.s_addr = htonl(addr); sin.sin_port = htons(port); } - + /// ditto this(ushort port) { sin.sin_addr.s_addr = 0; //any, "0.0.0.0" sin.sin_port = htons(port); } - + /// Human readable string representing the IPv4 address in dotted-decimal form. char[] toAddrString() { return std.string.toString(inet_ntoa(sin.sin_addr)).dup; } - + /// Human readable string representing the IPv4 port. char[] toPortString() { return std.string.toString(port()); } - + /// Human readable string representing the IPv4 address and port in the form $(I a.b.c.d:e). char[] toString() { return toAddrString() ~ ":" ~ toPortString(); } - - //-addr- is an IP address in the format "a.b.c.d" - //returns ADDR_NONE on failure + /** + * Parse an IPv4 address string in the dotted-decimal form $(I a.b.c.d) + * and return the number. + * If the string is not a legitimate IPv4 address, + * ADDR_NONE is returned. + */ static uint parse(char[] addr) { return ntohl(inet_addr(std.string.toStringz(addr))); @@ -641,6 +733,7 @@ } +/** */ class SocketAcceptException: SocketException { this(char[] msg, int err = 0) @@ -649,30 +742,32 @@ } } - +/// How a socket is shutdown: enum SocketShutdown: int { - RECEIVE = SD_RECEIVE, - SEND = SD_SEND, - BOTH = SD_RECEIVE, + RECEIVE = SD_RECEIVE, /// socket receives are disallowed + SEND = SD_SEND, /// socket sends are disallowed + BOTH = SD_RECEIVE, /// both RECEIVE and SEND } +/// Flags may be OR'ed together: enum SocketFlags: int { - NONE = 0, + NONE = 0, /// no flags specified - OOB = MSG_OOB, //out of band - PEEK = MSG_PEEK, //only for receiving - DONTROUTE = MSG_DONTROUTE, //only for sending + OOB = MSG_OOB, /// out-of-band stream data + PEEK = MSG_PEEK, /// peek at incoming data without removing it from the queue, only for receiving + DONTROUTE = MSG_DONTROUTE, /// data should not be subject to routing; this flag may be ignored. Only for sending } +/// Duration timeout value. extern(C) struct timeval { // D interface - int seconds; - int microseconds; + int seconds; /// Number of seconds. + int microseconds; /// Number of additional microseconds. // C interface deprecated @@ -683,7 +778,7 @@ } -//a set of sockets for Socket.select() +/// A collection of sockets for use with Socket.select. class SocketSet { private: @@ -729,6 +824,8 @@ public: + + /// Set the maximum amount of sockets that may be added. this(uint max) { version(Win32) @@ -746,13 +843,13 @@ } } - + /// Uses the default maximum for the system. this() { this(FD_SETSIZE); } - + /// Reset the SocketSet so that there are 0 Sockets in the collection. void reset() { version(Win32) @@ -806,38 +903,38 @@ } } - + /// Add a Socket to the collection. Adding more than the maximum has dangerous side affects. void add(Socket s) { add(s.sock); } - void remove(socket_t s) { FD_CLR(s, _fd_set); } + /// Remove this Socket from the collection. void remove(Socket s) { remove(s.sock); } - int isSet(socket_t s) { return FD_ISSET(s, _fd_set); } + /// Returns nonzero if this Socket is in the collection. int isSet(Socket s) { return isSet(s.sock); } - - // Max sockets that can be added, like FD_SETSIZE. + + // Return maximum amount of sockets that can be added, like FD_SETSIZE. uint max() { version(Win32) @@ -875,21 +972,23 @@ } +/// The level at which a socket option is defined: enum SocketOptionLevel: int { - SOCKET = SOL_SOCKET, - IP = ProtocolType.IP, - ICMP = ProtocolType.ICMP, - IGMP = ProtocolType.IGMP, - GGP = ProtocolType.GGP, - TCP = ProtocolType.TCP, - PUP = ProtocolType.PUP, - UDP = ProtocolType.UDP, - IDP = ProtocolType.IDP, - IPV6 = ProtocolType.IPV6, + SOCKET = SOL_SOCKET, /// socket level + IP = ProtocolType.IP, /// internet protocol version 4 level + ICMP = ProtocolType.ICMP, /// + IGMP = ProtocolType.IGMP, /// + GGP = ProtocolType.GGP, /// + TCP = ProtocolType.TCP, /// transmission control protocol level + PUP = ProtocolType.PUP, /// + UDP = ProtocolType.UDP, /// user datagram protocol level + IDP = ProtocolType.IDP, /// + IPV6 = ProtocolType.IPV6, /// internet protocol version 6 level } +/// Linger information for use with SocketOption.LINGER. extern(C) struct linger { version (BsdSockets) @@ -901,8 +1000,8 @@ // D interface version(Win32) { - uint16_t on; - uint16_t time; + uint16_t on; /// Nonzero for on. + uint16_t time; /// Linger time. } else version(BsdSockets) { @@ -928,29 +1027,35 @@ } } + +/// Specifies a socket option: enum SocketOption: int { - DEBUG = SO_DEBUG, - BROADCAST = SO_BROADCAST, - REUSEADDR = SO_REUSEADDR, - LINGER = SO_LINGER, - OOBINLINE = SO_OOBINLINE, - SNDBUF = SO_SNDBUF, - RCVBUF = SO_RCVBUF, - DONTROUTE = SO_DONTROUTE, + DEBUG = SO_DEBUG, /// record debugging information + BROADCAST = SO_BROADCAST, /// allow transmission of broadcast messages + REUSEADDR = SO_REUSEADDR, /// allow local reuse of address + LINGER = SO_LINGER, /// linger on close if unsent data is present + OOBINLINE = SO_OOBINLINE, /// receive out-of-band data in band + SNDBUF = SO_SNDBUF, /// send buffer size + RCVBUF = SO_RCVBUF, /// receive buffer size + DONTROUTE = SO_DONTROUTE, /// do not route // SocketOptionLevel.TCP: - TCP_NODELAY = .TCP_NODELAY, + TCP_NODELAY = .TCP_NODELAY, /// disable the Nagle algorithm for send coalescing // SocketOptionLevel.IPV6: - IPV6_UNICAST_HOPS = .IPV6_UNICAST_HOPS, - IPV6_MULTICAST_IF = .IPV6_MULTICAST_IF, - IPV6_MULTICAST_LOOP = .IPV6_MULTICAST_LOOP, - IPV6_JOIN_GROUP = .IPV6_JOIN_GROUP, - IPV6_LEAVE_GROUP = .IPV6_LEAVE_GROUP, + IPV6_UNICAST_HOPS = .IPV6_UNICAST_HOPS, /// + IPV6_MULTICAST_IF = .IPV6_MULTICAST_IF, /// + IPV6_MULTICAST_LOOP = .IPV6_MULTICAST_LOOP, /// + IPV6_JOIN_GROUP = .IPV6_JOIN_GROUP, /// + IPV6_LEAVE_GROUP = .IPV6_LEAVE_GROUP, /// } +/** + * Socket is a class that creates a network communication endpoint using the + * Berkeley sockets interface. + */ class Socket { private: @@ -958,7 +1063,7 @@ AddressFamily _family; version(Win32) - bit _blocking = false; + bool _blocking = false; /// Property to get or set whether the socket is blocking or nonblocking. // For use with accepting(). @@ -968,6 +1073,12 @@ public: + + /** + * Create a blocking socket. If a single protocol type exists to support + * this socket type within the address family, the ProtocolType may be + * omitted. + */ this(AddressFamily af, SocketType type, ProtocolType protocol) { sock = cast(socket_t)socket(af, type, protocol); @@ -979,12 +1090,14 @@ // A single protocol exists to support this socket type within the // protocol family, so the ProtocolType is assumed. + /// ditto this(AddressFamily af, SocketType type) { this(af, type, cast(ProtocolType)0); // Pseudo protocol number. } + /// ditto this(AddressFamily af, SocketType type, char[] protocolName) { protoent* proto; @@ -1008,7 +1121,7 @@ } - bit blocking() // getter + bool blocking() // getter { version(Win32) { @@ -1021,7 +1134,7 @@ } - void blocking(bit byes) // setter + void blocking(bool byes) // setter { version(Win32) { @@ -1048,27 +1161,32 @@ throw new SocketException("Unable to set socket blocking", _lasterr()); } - + + /// Get the socket's address family. AddressFamily addressFamily() // getter { return _family; } - - bit isAlive() // getter + /// Property that indicates if this is a valid, alive socket. + bool isAlive() // getter { int type, typesize = type.sizeof; return !getsockopt(sock, SOL_SOCKET, SO_TYPE, cast(char*)&type, &typesize); } - + /// Associate a local address with this socket. void bind(Address addr) { if(_SOCKET_ERROR == .bind(sock, addr.name(), addr.nameLen())) throw new SocketException("Unable to bind socket", _lasterr()); } - + /** + * Establish a connection. If the socket is blocking, connect waits for + * the connection to be made. If the socket is nonblocking, connect + * returns immediately and the connection attempt is still in progress. + */ void connect(Address to) { if(_SOCKET_ERROR == .connect(sock, to.name(), to.nameLen())) @@ -1097,15 +1215,23 @@ } } - - //need to bind() first + /** + * Listen for an incoming connection. bind must be called before you can + * listen. The backlog is a request of how many pending incoming + * connections are queued until accept'ed. + */ void listen(int backlog) { if(_SOCKET_ERROR == .listen(sock, backlog)) throw new SocketException("Unable to listen on socket", _lasterr()); } - + /** + * Called by accept when a new Socket must be created for a new + * connection. To use a derived class, override this method and return an + * instance of your class. The returned Socket's handle must not be set; + * Socket has a protected constructor this() to use in this situation. + */ // Override to use a derived class. // The returned socket's handle must not be set. protected Socket accepting() @@ -1113,7 +1239,11 @@ return new Socket; } - + /** + * Accept an incoming connection. If the socket is blocking, accept + * waits for a connection request. Throws SocketAcceptException if unable + * to accept. See accepting for use with derived classes. + */ Socket accept() { socket_t newsock; @@ -1143,7 +1273,7 @@ return newSocket; } - + /// Disables sends and/or receives. void shutdown(SocketShutdown how) { .shutdown(sock, cast(int)how); @@ -1162,7 +1292,12 @@ } } - + + /** + * Immediately drop any connections and release socket resources. + * Calling shutdown before close is recommended for connection-oriented + * sockets. The Socket object is no longer usable after close. + */ //calling shutdown() before this is recommended //for connection-oriented sockets void close() @@ -1188,7 +1323,7 @@ } - // Returns the local machine's host name. Idea from mango. + /// Returns the local machine's host name. Idea from mango. static char[] hostName() // getter { char[256] result; // Host names are limited to 255 chars. @@ -1197,7 +1332,7 @@ return std.string.toString(cast(char*)result).dup; } - + /// Remote endpoint Address. Address remoteAddress() { Address addr = newFamilyObject(); @@ -1208,7 +1343,7 @@ return addr; } - + /// Local endpoint Address. Address localAddress() { Address addr = newFamilyObject(); @@ -1219,10 +1354,14 @@ return addr; } - + /// Send or receive error code. const int ERROR = _SOCKET_ERROR; - + /** + * Send data on the connection. Returns the number of bytes actually + * sent, or ERROR on failure. If the socket is blocking and there is no + * buffer space left, send waits. + */ //returns number of bytes actually sent, or -1 on error int send(void[] buf, SocketFlags flags) { @@ -1230,20 +1369,22 @@ return sent; } - + /// ditto int send(void[] buf) { return send(buf, SocketFlags.NONE); } - + /** + * Send data to a specific destination Address. If the destination address is not specified, a connection must have been made and that address is used. If the socket is blocking and there is no buffer space left, sendTo waits. + */ int sendTo(void[] buf, SocketFlags flags, Address to) { int sent = .sendto(sock, buf, buf.length, cast(int)flags, to.name(), to.nameLen()); return sent; } - + /// ditto int sendTo(void[] buf, Address to) { return sendTo(buf, SocketFlags.NONE, to); @@ -1251,6 +1392,7 @@ //assumes you connect()ed + /// ditto int sendTo(void[] buf, SocketFlags flags) { int sent = .sendto(sock, buf, buf.length, cast(int)flags, null, 0); @@ -1259,12 +1401,19 @@ //assumes you connect()ed + /// ditto int sendTo(void[] buf) { return sendTo(buf, SocketFlags.NONE); } - + + /** + * Receive data on the connection. Returns the number of bytes actually + * received, 0 if the remote side has closed the connection, or ERROR on + * failure. If the socket is blocking, receive waits until there is data + * to be received. + */ //returns number of bytes actually received, 0 on connection closure, or -1 on error int receive(void[] buf, SocketFlags flags) { @@ -1275,13 +1424,15 @@ return read; } - + /// ditto int receive(void[] buf) { return receive(buf, SocketFlags.NONE); } - + /** + * Receive data and get the remote endpoint Address. Returns the number of bytes actually received, 0 if the remote side has closed the connection, or ERROR on failure. If the socket is blocking, receiveFrom waits until there is data to be received. + */ int receiveFrom(void[] buf, SocketFlags flags, out Address from) { if(!buf.length) //return 0 and don't think the connection closed @@ -1295,6 +1446,7 @@ } + /// ditto int receiveFrom(void[] buf, out Address from) { return receiveFrom(buf, SocketFlags.NONE, from); @@ -1302,6 +1454,7 @@ //assumes you connect()ed + /// ditto int receiveFrom(void[] buf, SocketFlags flags) { if(!buf.length) //return 0 and don't think the connection closed @@ -1313,12 +1466,14 @@ //assumes you connect()ed + /// ditto int receiveFrom(void[] buf) { return receiveFrom(buf, SocketFlags.NONE); } - + + /// Get a socket option. Returns the number of bytes written to result. //returns the length, in bytes, of the actual result - very different from getsockopt() int getOption(SocketOptionLevel level, SocketOption option, void[] result) { @@ -1328,21 +1483,22 @@ return len; } - - // Common case for integer and boolean options. + + /// Common case of getting integer and boolean options. int getOption(SocketOptionLevel level, SocketOption option, out int32_t result) { return getOption(level, option, (&result)[0 .. 1]); } - - + + + /// Get the linger option. int getOption(SocketOptionLevel level, SocketOption option, out linger result) { //return getOption(cast(SocketOptionLevel)SocketOptionLevel.SOCKET, SocketOption.LINGER, (&result)[0 .. 1]); return getOption(level, option, (&result)[0 .. 1]); } - + // Set a socket option. void setOption(SocketOptionLevel level, SocketOption option, void[] value) { if(_SOCKET_ERROR == .setsockopt(sock, cast(int)level, cast(int)option, value, value.length)) @@ -1350,20 +1506,24 @@ } - // Common case for integer and boolean options. + /// Common case for setting integer and boolean options. void setOption(SocketOptionLevel level, SocketOption option, int32_t value) { setOption(level, option, (&value)[0 .. 1]); } - - + + + /// Set the linger option. void setOption(SocketOptionLevel level, SocketOption option, linger value) { //setOption(cast(SocketOptionLevel)SocketOptionLevel.SOCKET, SocketOption.LINGER, (&value)[0 .. 1]); setOption(level, option, (&value)[0 .. 1]); } - + + /** + * Wait for a socket to change status. A wait timeout timeval or int microseconds may be specified; if a timeout is not specified or the timeval is null, the maximum timeout is used. The timeval timeout has an unspecified value when select returns. Returns the number of sockets with status changes, 0 on timeout, or -1 on interruption. If the return value is greater than 0, the SocketSets are updated to only contain the sockets having status changes. For a connecting socket, a write status change means the connection is established and it's able to send. For a listening socket, a read status change means there is an incoming connection request and it's able to accept. + */ //SocketSet's updated to include only those sockets which an event occured //returns the number of events, 0 on timeout, or -1 on interruption //for a connect()ing socket, writeability means connected @@ -1375,12 +1535,12 @@ //make sure none of the SocketSet's are the same object if(checkRead) { - assert(checkRead !is checkWrite); - assert(checkRead !is checkError); + assert(checkRead !is checkWrite); + assert(checkRead !is checkError); } if(checkWrite) { - assert(checkWrite !is checkError); + assert(checkWrite !is checkError); } } body @@ -1456,8 +1616,9 @@ return result; } - - + + + /// ditto static int select(SocketSet checkRead, SocketSet checkWrite, SocketSet checkError, int microseconds) { timeval tv; @@ -1467,6 +1628,7 @@ } + /// ditto //maximum timeout static int select(SocketSet checkRead, SocketSet checkWrite, SocketSet checkError) { @@ -1475,7 +1637,7 @@ /+ - bit poll(events) + bool poll(events) { int WSAEventSelect(socket_t s, WSAEVENT hEventObject, int lNetworkEvents); // Winsock 2 ? int poll(pollfd* fds, int nfds, int timeout); // Unix ? @@ -1484,14 +1646,16 @@ } +/// TcpSocket is a shortcut class for a TCP Socket. class TcpSocket: Socket { + /// Constructs a blocking TCP Socket. this(AddressFamily family) { super(family, SocketType.STREAM, ProtocolType.TCP); } - + /// Constructs a blocking TCP Socket. this() { this(cast(AddressFamily)AddressFamily.INET); @@ -1499,6 +1663,7 @@ //shortcut + /// Constructs a blocking TCP Socket and connects to an InternetAddress. this(Address connectTo) { this(connectTo.addressFamily()); @@ -1507,14 +1672,17 @@ } +/// UdpSocket is a shortcut class for a UDP Socket. class UdpSocket: Socket { + /// Constructs a blocking UDP Socket. this(AddressFamily family) { super(family, SocketType.DGRAM, ProtocolType.UDP); } + /// Constructs a blocking UDP Socket. this() { this(cast(AddressFamily)AddressFamily.INET); diff -uNr gdc-0.17/d/phobos/std/socketstream.d gdc-0.18/d/phobos/std/socketstream.d --- gdc-0.17/d/phobos/std/socketstream.d 2005-06-22 05:13:40.000000000 +0200 +++ gdc-0.18/d/phobos/std/socketstream.d 2006-05-14 04:21:51.000000000 +0200 @@ -18,18 +18,39 @@ 3. This notice may not be removed or altered from any source distribution. */ +/************** + * SocketStream is a stream for a blocking, + * connected Socket. + * + * For Win32 systems, link with ws2_32.lib. + * + * Example: + * See /dmd/samples/d/htmlget.d + * Authors: Christopher E. Miller + * References: + * $(LINK2 std_stream.html, std.stream) + * Macros: WIKI=Phobos/StdSocketstream + */ module std.socketstream; private import std.stream; private import std.socket; +/************** + * SocketStream is a stream for a blocking, + * connected Socket. + */ class SocketStream: Stream { - private: + private: Socket sock; - public: + public: + + /** + * Constructs a SocketStream with the specified Socket and FileMode flags. + */ this(Socket sock, FileMode mode) { if(mode & FileMode.In) @@ -40,17 +61,26 @@ this.sock = sock; } + /** + * Uses mode FileMode.In | FileMode.Out. + */ this(Socket sock) { writeable = readable = true; this.sock = sock; } + /** + * Property to get the Socket that is being streamed. + */ Socket socket() { return sock; } + /** + * Attempts to read the entire block, waiting if necessary. + */ override uint readBlock(void* _buffer, uint size) { ubyte* buffer = cast(ubyte*)_buffer; @@ -62,12 +92,15 @@ return size; len = sock.receive(buffer[0 .. size]); - readEOF = cast(bit)(len == 0); + readEOF = cast(bool)(len == 0); if(len < 0) len = 0; return len; } + /** + * Attempts to write the entire block, waiting if necessary. + */ override uint writeBlock(void* _buffer, uint size) { ubyte* buffer = cast(ubyte*)_buffer; @@ -78,23 +111,33 @@ return size; len = sock.send(buffer[0 .. size]); - readEOF = cast(bit)(len == 0); + readEOF = cast(bool)(len == 0); if(len < 0) len = 0; return len; } + /** + * + */ override ulong seek(long offset, SeekPos whence) { throw new SeekException("Cannot seek a socket."); return 0; } + /** + * Does not return the entire stream because that would + * require the remote connection to be closed. + */ override char[] toString() { return sock.toString(); } + /** + * Close the Socket. + */ override void close() { sock.close(); diff -uNr gdc-0.17/d/phobos/std/stdarg.d gdc-0.18/d/phobos/std/stdarg.d --- gdc-0.17/d/phobos/std/stdarg.d 2005-10-02 16:17:55.000000000 +0200 +++ gdc-0.18/d/phobos/std/stdarg.d 2005-12-25 18:45:12.000000000 +0100 @@ -37,3 +37,7 @@ } } +private import std.c.stdarg; +/* The existence of std.stdarg.va_copy isn't standard. Prevent + conflicts by using '__'. */ +alias std.c.stdarg.va_copy __va_copy; diff -uNr gdc-0.17/d/phobos/std/stdint.d gdc-0.18/d/phobos/std/stdint.d --- gdc-0.17/d/phobos/std/stdint.d 2004-10-26 02:41:27.000000000 +0200 +++ gdc-0.18/d/phobos/std/stdint.d 2006-05-13 21:05:42.000000000 +0200 @@ -1,7 +1,120 @@ -/* Written by Walter Bright - * www.digitalmars.com - * Placed into Public Domain +/** + * + D constrains integral types to specific sizes. But efficiency + of different sizes varies from machine to machine, + pointer sizes vary, and the maximum integer size varies. + stdint offers a portable way of trading off size + vs efficiency, in a manner compatible with the stdint.h + definitions in C. + + The exact aliases are types of exactly the specified number of bits. + The at least aliases are at least the specified number of bits + large, and can be larger. + The fast aliases are the fastest integral type supported by the + processor that is at least as wide as the specified number of bits. + + The aliases are: + + + + + + + + + + +
    Exact Alias + Description + At Least Alias + Description + Fast Alias + Description +
    int8_t + exactly 8 bits signed + int_least8_t + at least 8 bits signed + int_fast8_t + fast 8 bits signed +
    uint8_t + exactly 8 bits unsigned + uint_least8_t + at least 8 bits unsigned + uint_fast8_t + fast 8 bits unsigned + +
    int16_t + exactly 16 bits signed + int_least16_t + at least 16 bits signed + int_fast16_t + fast 16 bits signed +
    uint16_t + exactly 16 bits unsigned + uint_least16_t + at least 16 bits unsigned + uint_fast16_t + fast 16 bits unsigned + +
    int32_t + exactly 32 bits signed + int_least32_t + at least 32 bits signed + int_fast32_t + fast 32 bits signed +
    uint32_t + exactly 32 bits unsigned + uint_least32_t + at least 32 bits unsigned + uint_fast32_t + fast 32 bits unsigned + +
    int64_t + exactly 64 bits signed + int_least64_t + at least 64 bits signed + int_fast64_t + fast 64 bits signed +
    uint64_t + exactly 64 bits unsigned + uint_least64_t + at least 64 bits unsigned + uint_fast64_t + fast 64 bits unsigned +
    + + The ptr aliases are integral types guaranteed to be large enough + to hold a pointer without losing bits: + + + + +
    Alias + Description +
    intptr_t + signed integral type large enough to hold a pointer +
    uintptr_t + unsigned integral type large enough to hold a pointer +
    + + The max aliases are the largest integral types: + + + + +
    Alias + Description +
    intmax_t + the largest signed integral type +
    uintmax_t + the largest unsigned integral type +
    + + * Authors: Walter Bright, www.digitalmars.com + * License: Public Domain + * Macros: + * WIKI=Phobos/StdStdint */ module std.stdint; diff -uNr gdc-0.17/d/phobos/std/stdio.d gdc-0.18/d/phobos/std/stdio.d --- gdc-0.17/d/phobos/std/stdio.d 2005-08-13 01:51:59.000000000 +0200 +++ gdc-0.18/d/phobos/std/stdio.d 2006-04-16 17:13:30.000000000 +0200 @@ -10,6 +10,14 @@ Modified by David Friedman, September 2004 */ +/******************************** + * Standard I/O functions that extend $(B std.c.stdio). + * $(B std.c.stdio) is automatically imported when importing + * $(B std.stdio). + * Macros: + * WIKI=Phobos/StdStdio + */ + module std.stdio; import std.c.stdio; @@ -130,21 +138,42 @@ } +/*********************************** + * Arguments are formatted per the + * $(LINK2 std_format.html#format-string, format strings) + * and written to $(B stdout). + */ + void writef(...) { writefx(stdout, _arguments, _argptr, 0); } +/*********************************** + * Same as $(B writef), but a newline is appended + * to the output. + */ + void writefln(...) { writefx(stdout, _arguments, _argptr, 1); } +/*********************************** + * Same as $(B writef), but output is sent to the + * stream fp instead of $(B stdout). + */ + void fwritef(FILE* fp, ...) { writefx(fp, _arguments, _argptr, 0); } +/*********************************** + * Same as $(B writefln), but output is sent to the + * stream fp instead of $(B stdout). + */ + void fwritefln(FILE* fp, ...) { writefx(fp, _arguments, _argptr, 1); diff -uNr gdc-0.17/d/phobos/std/stream.d gdc-0.18/d/phobos/std/stream.d --- gdc-0.17/d/phobos/std/stream.d 2005-10-13 03:06:51.000000000 +0200 +++ gdc-0.18/d/phobos/std/stream.d 2006-05-14 04:21:51.000000000 +0200 @@ -1,6 +1,6 @@ /** * Macros: - * WIKI = StdStream + * WIKI = Phobos/StdStream */ /* @@ -386,15 +386,15 @@ private import std.string, crc32, std.c.stdlib, std.c.stdio; // stream abilities - bit readable = false; /// Indicates whether this stream can be read from. - bit writeable = false; /// Indicates whether this stream can be written to. - bit seekable = false; /// Indicates whether this stream can be seeked within. - protected bit isopen = true; /// Indicates whether this stream is open. + bool readable = false; /// Indicates whether this stream can be read from. + bool writeable = false; /// Indicates whether this stream can be written to. + bool seekable = false; /// Indicates whether this stream can be seeked within. + protected bool isopen = true; /// Indicates whether this stream is open. - protected bit readEOF = false; /// Indicates whether this stream is at eof + protected bool readEOF = false; /// Indicates whether this stream is at eof /// after the last read attempt. - protected bit prevCr = false; /// For a non-seekable stream indicates that + protected bool prevCr = false; /// For a non-seekable stream indicates that /// the last readLine or readLineW ended on a /// '\r' character. @@ -718,7 +718,7 @@ } if (fmt[i] == '%') { // a field i++; - bit suppress = false; + bool suppress = false; if (fmt[i] == '*') { // suppress assignment suppress = true; i++; @@ -751,7 +751,7 @@ c = getc(); count++; } - bit neg = false; + bool neg = false; if (c == '-') { neg = true; c = getc(); @@ -852,7 +852,7 @@ c = getc(); count++; } - bit neg = false; + bool neg = false; if (c == '-') { neg = true; c = getc(); @@ -887,7 +887,7 @@ c = getc(); count++; if (width) { - bit expneg = false; + bool expneg = false; if (c == '-') { expneg = true; width--; @@ -1124,15 +1124,17 @@ char* f = toStringz(format); size_t psize = buffer.length; size_t count; + va_list args_copy; while (true) { + __va_copy(args_copy, args); version (Win32) { - count = _vsnprintf(p, psize, f, args); + count = _vsnprintf(p, psize, f, args_copy); if (count != -1) break; psize *= 2; p = cast(char*) alloca(psize); } else version (Unix) { - count = vsnprintf(p, psize, f, args); + count = vsnprintf(p, psize, f, args_copy); if (count == -1) psize *= 2; else if (count >= psize) @@ -1259,7 +1261,7 @@ } // returns true if end of stream is reached, false otherwise - bit eof() { + bool eof() { // for unseekable streams we only know the end when we read it if (readEOF && !ungetAvailable()) return true; @@ -1376,7 +1378,7 @@ /// Property indicating when this stream closes to close the source stream as /// well. /// Defaults to true. - bit nestClose = true; + bool nestClose = true; /// Construct a FilterStream for the given source. this(Stream source) { @@ -1465,7 +1467,7 @@ ubyte[] buffer; // buffer, if any uint bufferCurPos; // current position in buffer uint bufferLen; // amount of data in buffer - bit bufferDirty = false; + bool bufferDirty = false; uint bufferSourcePos; // position in buffer of source stream position ulong streamPos; // absolute position in source stream @@ -1623,6 +1625,7 @@ return streamPos-bufferSourcePos+bufferCurPos; } + // Buffered readLine - Dave Fladebo // reads a line, terminated by either CR, LF, CR/LF, or EOF // reusing the memory in buffer if result will fit, otherwise // will reallocate (using concatenation) @@ -1806,8 +1809,8 @@ this(HANDLE hFile, FileMode mode) { super(); this.hFile = hFile; - readable = cast(bit)(mode & FileMode.In); - writeable = cast(bit)(mode & FileMode.Out); + readable = cast(bool)(mode & FileMode.In); + writeable = cast(bool)(mode & FileMode.Out); version(Windows) { seekable = GetFileType(hFile) == 1; // FILE_TYPE_DISK } else { @@ -1841,8 +1844,8 @@ int access, share, createMode; parseMode(mode, access, share, createMode); seekable = true; - readable = cast(bit)(mode & FileMode.In); - writeable = cast(bit)(mode & FileMode.Out); + readable = cast(bool)(mode & FileMode.In); + writeable = cast(bool)(mode & FileMode.Out); version (Win32) { if (std.file.useWfuncs) { hFile = CreateFileW(std.utf.toUTF16z(filename), access, share, @@ -2084,33 +2087,33 @@ */ class BufferedFile: BufferedStream { - // opens file for reading + /// opens file for reading this() { super(new File()); } - // opens file in requested mode and buffer size + /// opens file in requested mode and buffer size this(char[] filename, FileMode mode = FileMode.In, uint bufferSize = DefaultBufferSize) { super(new File(filename,mode),bufferSize); } - // opens file for reading with requested buffer size + /// opens file for reading with requested buffer size this(File file, uint bufferSize = DefaultBufferSize) { super(file,bufferSize); } - // opens existing handle; use with care! + /// opens existing handle; use with care! this(HANDLE hFile, FileMode mode, uint buffersize) { super(new File(hFile,mode),buffersize); } - // opens file in requested mode + /// opens file in requested mode void open(char[] filename, FileMode mode = FileMode.In) { File sf = cast(File)s; sf.open(filename,mode); resetSource(); } - // creates file in requested mode + /// creates file in requested mode void create(char[] filename, FileMode mode = FileMode.Out) { File sf = cast(File)s; sf.create(filename,mode); @@ -2747,7 +2750,7 @@ ulong pos; // our position relative to low ulong low; // low stream offset. ulong high; // high stream offset. - bit bounded; // upper-bounded by high. + bool bounded; // upper-bounded by high. } /*** @@ -2915,18 +2918,18 @@ } // helper functions -private bit iswhite(char c) { +private bool iswhite(char c) { return c == ' ' || c == '\t' || c == '\r' || c == '\n'; } -private bit isdigit(char c) { +private bool isdigit(char c) { return c >= '0' && c <= '9'; } -private bit isoctdigit(char c) { +private bool isoctdigit(char c) { return c >= '0' && c <= '7'; } -private bit ishexdigit(char c) { +private bool ishexdigit(char c) { return isdigit(c) || (c >= 'A' && c <= 'F') || (c >= 'a' && c <= 'f'); } diff -uNr gdc-0.17/d/phobos/std/string.d gdc-0.18/d/phobos/std/string.d --- gdc-0.17/d/phobos/std/string.d 2005-11-28 05:17:52.000000000 +0100 +++ gdc-0.18/d/phobos/std/string.d 2006-05-18 02:05:55.000000000 +0200 @@ -11,7 +11,7 @@ * are done, the returned string is a copy. * * Macros: - * WIKI = StdString + * WIKI = Phobos/StdString * Copyright: * Public Domain */ @@ -36,6 +36,7 @@ private import std.stdio; private import std.c.stdio; private import std.c.stdlib; +private import std.c.string; private import std.utf; private import std.uni; private import std.array; @@ -45,44 +46,11 @@ extern (C) { - // Functions from the C library. - version (GNU) // should be: GNU_Use_Builtins / -f[no-]builtins - { - private import gcc.builtins; - alias __builtin_strlen strlen; - alias __builtin_strcmp strcmp; - alias __builtin_strcat strcat; - alias __builtin_memcmp memcmp; - alias __builtin_strcpy strcpy; - alias __builtin_strstr strstr; - alias __builtin_strchr strchr; - alias __builtin_strrchr strrchr; - alias __builtin_memcpy memcpy; - //alias __builtin_memmove memmove;// not in 3.3 - alias __builtin_memset memset; - } - else - { - int strlen(char *); - int strcmp(char *, char *); - char* strcat(char *, char *); - int memcmp(void *, void *, uint); - char *strcpy(char *, char *); - char *strstr(char *, char *); - char *strchr(char *, char); - char *strrchr(char *, char); - void *memcpy(void *, void *, uint); - void *memset(void *, uint, uint); - } - void *memmove(void *, void *, uint); - int memicmp(char *, char *, uint); - char *memchr(char *, char, uint); - char* strerror(int); - int wcslen(wchar *); int wcscmp(wchar *, wchar *); } + /* ************* Exceptions *************** */ /// Thrown on errors in string functions. @@ -108,14 +76,21 @@ const dchar LS = '\u2028'; /// UTF line separator const dchar PS = '\u2029'; /// UTF paragraph separator +/// Newline sequence for this system +version (Windows) + const char[2] newline = "\r\n"; +else version (Unix) + const char[2] newline = "\n"; + /********************************** * Returns !=0 if c is whitespace */ int iswhite(dchar c) { - return (c <= 0x7F) ? find(whitespace, c) != -1 - : (c == PS || c == LS); + return (c <= 0x7F) + ? find(whitespace, c) != -1 + : (c == PS || c == LS); } /********************************* @@ -133,9 +108,8 @@ real atof(char[] s) { char* endptr; - real result; - result = strtold(toStringz(s), &endptr); + auto result = strtold(toStringz(s), &endptr); return result; } @@ -143,15 +117,15 @@ * Compare two strings. cmp is case sensitive, icmp is case insensitive. * Returns: * - *
    < 0 s1 < s2 - *
    = 0 s1 == s2 - *
    > 0 s1 > s2 + * $(TR $(TD < 0) $(TD s1 < s2)) + * $(TR $(TD = 0) $(TD s1 == s2)) + * $(TR $(TD > 0) $(TD s1 > s2)) *
    */ int cmp(char[] s1, char[] s2) { - size_t len = s1.length; + auto len = s1.length; int result; //printf("cmp('%.*s', '%.*s')\n", s1, s2); @@ -169,7 +143,7 @@ int icmp(char[] s1, char[] s2) { - size_t len = s1.length; + auto len = s1.length; int result; if (s2.length < len) @@ -303,11 +277,9 @@ int find(char[] s, dchar c) { - char* p; - if (c <= 0x7F) { // Plain old ASCII - p = memchr(s, c, s.length); + auto p = cast(char*)memchr(s, c, s.length); if (p) return p - cast(char *)s; else @@ -533,17 +505,17 @@ } body { - size_t sublength = sub.length; + auto sublength = sub.length; if (sublength == 0) return 0; if (s.length >= sublength) { - char c = sub[0]; + auto c = sub[0]; if (sublength == 1) { - char *p = memchr(s, c, s.length); + auto p = cast(char*)memchr(s, c, s.length); if (p) return p - &s[0]; } @@ -557,7 +529,7 @@ for (size_t i = 0; i < imax; i++) { - char *p = memchr(&s[i], c, imax - i); + char *p = cast(char*)memchr(&s[i], c, imax - i); if (!p) break; i = p - &s[0]; @@ -608,7 +580,7 @@ } body { - size_t sublength = sub.length; + auto sublength = sub.length; int i; if (sublength == 0) @@ -617,7 +589,7 @@ if (s.length < sublength) return -1; - char c = sub[0]; + auto c = sub[0]; if (sublength == 1) { i = ifind(s, c); @@ -631,7 +603,7 @@ for (i = 0; i < imax; i++) { - int j = ifind(s[i .. imax], c); + auto j = ifind(s[i .. imax], c); if (j == -1) return -1; i += j; @@ -848,7 +820,7 @@ changed = 0; for (i = 0; i < s.length; i++) { - char c = s[i]; + auto c = s[i]; if ('A' <= c && c <= 'Z') { if (!changed) @@ -903,7 +875,7 @@ changed = 0; for (i = 0; i < s.length; i++) { - char c = s[i]; + auto c = s[i]; if ('a' <= c && c <= 'z') { if (!changed) @@ -1020,12 +992,10 @@ char[] capwords(char[] s) { char[] r; - int inword; - int i; - int istart; + bool inword = false; + size_t istart = 0; + size_t i; - istart = 0; - inword = 0; for (i = 0; i < s.length; i++) { switch (s[i]) @@ -1039,7 +1009,7 @@ if (inword) { r ~= capitalize(s[istart .. i]); - inword = 0; + inword = false; } break; @@ -1049,7 +1019,7 @@ if (r.length) r ~= ' '; istart = i; - inword = 1; + inword = true; } break; } @@ -1089,7 +1059,7 @@ if (s.length == 1) r[] = s[0]; else - { size_t len = s.length; + { auto len = s.length; for (size_t i = 0; i < n * len; i += len) { @@ -1126,23 +1096,22 @@ char[] join(char[][] words, char[] sep) { - size_t len; - uint seplen; - uint i; - uint j; char[] result; if (words.length) { - len = 0; + size_t len = 0; + size_t i; + for (i = 0; i < words.length; i++) len += words[i].length; - seplen = sep.length; + auto seplen = sep.length; len += (words.length - 1) * seplen; result = new char[len]; + size_t j; i = 0; while (true) { @@ -1188,12 +1157,11 @@ char[][] split(char[] s) { - uint i; - uint istart; - int inword; + size_t i; + size_t istart = 0; + bool inword = false; char[][] words; - inword = 0; for (i = 0; i < s.length; i++) { switch (s[i]) @@ -1207,14 +1175,14 @@ if (inword) { words ~= s[istart .. i]; - inword = 0; + inword = false; } break; default: if (!inword) { istart = i; - inword = 1; + inword = true; } break; } @@ -1255,8 +1223,8 @@ } body { - uint i; - uint j; + size_t i; + size_t j; char[][] words; i = 0; @@ -1264,14 +1232,14 @@ { if (delim.length == 1) { char c = delim[0]; - uint nwords = 0; - char *p = &s[0]; - char *pend = p + s.length; + size_t nwords = 0; + char* p = &s[0]; + char* pend = p + s.length; while (true) { nwords++; - p = memchr(p, c, pend - p); + p = cast(char*)memchr(p, c, pend - p); if (!p) break; p++; @@ -1286,7 +1254,7 @@ i = 0; while (true) { - p = memchr(&s[i], c, s.length - i); + p = cast(char*)memchr(&s[i], c, s.length - i); if (!p) { words[wordi] = s[i .. s.length]; @@ -1305,7 +1273,7 @@ assert(wordi + 1 == nwords); } else - { uint nwords = 0; + { size_t nwords = 0; while (true) { @@ -1552,10 +1520,10 @@ char[] chomp(char[] s, char[] delimiter = null) { if (delimiter is null) - { size_t len = s.length; + { auto len = s.length; if (len) - { char c = s[len - 1]; + { auto c = s[len - 1]; if (c == '\r') // if ends in CR len--; @@ -1619,7 +1587,7 @@ */ char[] chop(char[] s) -{ size_t len = s.length; +{ auto len = s.length; if (len) { @@ -1743,9 +1711,11 @@ { char[] p; int i; - int istart; + size_t istart; //printf("replace('%.*s','%.*s','%.*s')\n", s, from, to); + if (from.length == 0) + return s; istart = 0; while (istart < s.length) { @@ -1775,6 +1745,10 @@ r = replace(s, from, to); i = cmp(r, "This is a silly silly list"); assert(i == 0); + + r = replace(s, "", to); + i = cmp(r, "This is a foo foo list"); + assert(i == 0); } /***************************** @@ -2184,7 +2158,7 @@ { char[] r; int count; - bit[256] deltab; + bool[256] deltab; deltab[] = false; foreach (char c; delchars) @@ -2236,7 +2210,7 @@ * Convert to char[]. */ -char[] toString(bit b) +char[] toString(bool b) { return b ? "true" : "false"; } @@ -2342,15 +2316,15 @@ char[] r; int i; - r = toString(0ul); + r = toString(0uL); i = cmp(r, "0"); assert(i == 0); - r = toString(9ul); + r = toString(9uL); i = cmp(r, "9"); assert(i == 0); - r = toString(123ul); + r = toString(123uL); i = cmp(r, "123"); assert(i == 0); } @@ -2447,27 +2421,27 @@ char[] r; int i; - r = toString(0l); + r = toString(0L); i = cmp(r, "0"); assert(i == 0); - r = toString(9l); + r = toString(9L); i = cmp(r, "9"); assert(i == 0); - r = toString(123l); + r = toString(123L); i = cmp(r, "123"); assert(i == 0); - r = toString(-0l); + r = toString(-0L); i = cmp(r, "0"); assert(i == 0); - r = toString(-9l); + r = toString(-9L); i = cmp(r, "-9"); assert(i == 0); - r = toString(-123l); + r = toString(-123L); i = cmp(r, "-123"); assert(i == 0); } @@ -2481,16 +2455,21 @@ char[20] buffer; sprintf(buffer, "%g", d); - return toString(buffer).dup; + return std.string.toString(buffer).dup; } /// ditto +static if (real.sizeof != double.sizeof) + private static const char[] _longDoubleFormat = "L"; +else + private static const char[] _longDoubleFormat = ""; + char[] toString(real r) { char[20] buffer; - sprintf(buffer, "%Lg", r); - return toString(buffer).dup; + sprintf(buffer, "%"~_longDoubleFormat~"g", r); + return std.string.toString(buffer).dup; } /// ditto @@ -2502,7 +2481,7 @@ char[21] buffer; sprintf(buffer, "%gi", d); - return toString(buffer).dup; + return std.string.toString(buffer).dup; } /// ditto @@ -2510,8 +2489,8 @@ { char[21] buffer; - sprintf(buffer, "%Lgi", r); - return toString(buffer).dup; + sprintf(buffer, "%"~_longDoubleFormat~"gi", r); + return std.string.toString(buffer).dup; } /// ditto @@ -2523,7 +2502,7 @@ char[20 + 1 + 20 + 1] buffer; sprintf(buffer, "%g+%gi", d.re, d.im); - return toString(buffer).dup; + return std.string.toString(buffer).dup; } /// ditto @@ -2531,8 +2510,8 @@ { char[20 + 1 + 20 + 1] buffer; - sprintf(buffer, "%Lg+%Lgi", r.re, r.im); - return toString(buffer).dup; + sprintf(buffer, "%"~_longDoubleFormat~"g+%"~_longDoubleFormat~"gi", r.re, r.im); + return std.string.toString(buffer).dup; } /****************************************** @@ -2927,13 +2906,13 @@ dchar lastc; size_t lasti; int run; - int changed; + bool changed; foreach (size_t i, dchar c; s) { if (run && lastc == c) { - changed = 1; + changed = true; } else if (pattern is null || inPattern(c, pattern)) { @@ -3794,9 +3773,9 @@ * leftmost column, which is numbered starting from 0. */ -int column(char[] string, int tabsize = 8) +size_t column(char[] string, int tabsize = 8) { - int column; + size_t column; foreach (dchar c; string) { diff -uNr gdc-0.17/d/phobos/std/syserror.d gdc-0.18/d/phobos/std/syserror.d --- gdc-0.17/d/phobos/std/syserror.d 2005-04-28 23:12:43.000000000 +0200 +++ gdc-0.18/d/phobos/std/syserror.d 2006-05-13 21:05:42.000000000 +0200 @@ -10,6 +10,7 @@ deprecated class SysError { private import std.c.stdio; + private import std.c.string; private import std.string; static char[] msg(uint errcode) diff -uNr gdc-0.17/d/phobos/std/system.d gdc-0.18/d/phobos/std/system.d --- gdc-0.17/d/phobos/std/system.d 2004-10-26 02:41:27.000000000 +0200 +++ gdc-0.18/d/phobos/std/system.d 2006-05-14 03:05:56.000000000 +0200 @@ -1,7 +1,10 @@ -/* Written by Walter Bright - * www.digitalmars.com - * Placed into Public Domain +/** + * Information about the target operating system, environment, and CPU + * Authors: Walter Bright, www.digitalmars.com + * License: Public Domain + * Macros: + * WIKI = Phobos/StdSystem */ /* NOTE: This file has been patched from the original DMD distribution to @@ -47,18 +50,25 @@ { Windows95 = 1, Windows98, + WindowsME, WindowsNT, Windows2000, + WindowsXP, RedHatLinux, } - // Big-endian or Little-endian? + /// Byte order endiannes - enum Endian { BigEndian, LittleEndian } + enum Endian + { + BigEndian, /// big endian byte order + LittleEndian /// little endian byte order + } version(LittleEndian) { + /// Native system endiannes Endian endian = Endian.LittleEndian; } else @@ -69,7 +79,7 @@ // The rest should get filled in dynamically at runtime -OS os = OS.WindowsNT; +OS os = OS.WindowsXP; // Operating system version as in // os_major.os_minor diff -uNr gdc-0.17/d/phobos/std/thread.d gdc-0.18/d/phobos/std/thread.d --- gdc-0.17/d/phobos/std/thread.d 2005-06-22 05:13:40.000000000 +0200 +++ gdc-0.18/d/phobos/std/thread.d 2006-05-14 04:21:51.000000000 +0200 @@ -1,5 +1,5 @@ /* - * Copyright (C) 2002-2004 by Digital Mars, www.digitalmars.com + * Copyright (C) 2002-2006 by Digital Mars, www.digitalmars.com * Written by Walter Bright * * This software is provided 'as-is', without any express or implied @@ -26,6 +26,18 @@ Modified by David Friedman, September 2004 */ +/************************** + * The thread module defines the class $(B Thread). + * + * $(B Thread) is the basis + * for writing multithreaded applications. Each thread + * has a unique instance of class $(B Thread) associated with it. + * It is important to use the $(B Thread) class to create and manage + * threads as the garbage collector needs to know about all the threads. + * Macros: + * WIKI=Phobos/StdThread + */ + module std.thread; //debug=thread; @@ -44,11 +56,17 @@ stdfp start_addr, void* arglist, uint initflag, thread_id* thrdaddr); -// This is equivalent to a HANDLE from windows.d +/** + * The type of the thread handle used by the operating system. + * For Windows, it is equivalent to a HANDLE from windows.d. + */ alias HANDLE thread_hdl; alias uint thread_id; +/** + * Thrown for errors. + */ class ThreadError : Error { this(char[] s) @@ -57,27 +75,52 @@ } } +/** + * One of these is created for each thread. + */ class Thread { - this() + /** + * Constructor used by classes derived from Thread that override main(). + * The optional stacksize parameter default value of 0 will cause threads + * to be created with the default size for the executable - Dave Fladebo + */ + this(size_t stacksize = 0) { + this.stacksize = stacksize; } - this(int (*fp)(void *), void *arg) + /** + * Constructor used by classes derived from Thread that override run(). + */ + this(int (*fp)(void *), void *arg, size_t stacksize = 0) { this.fp = fp; this.arg = arg; + this.stacksize = stacksize; } - this(int delegate() dg) + /** + * Constructor used by classes derived from Thread that override run(). + */ + this(int delegate() dg, size_t stacksize = 0) { this.dg = dg; + this.stacksize = stacksize; } + /** + * The handle to this thread assigned by the operating system. This is set + * to thread_id.init if the thread hasn't been started yet. + */ thread_hdl hdl; - thread_id id; + void* stackBottom; + /** + * Create a new thread and start it running. The new thread initializes + * itself and then calls run(). start() can only be called once. + */ void start() { if (state != TS.INITIAL) @@ -101,7 +144,7 @@ } state = TS.RUNNING; - hdl = _beginthreadex(null, 0, &threadstart, this, 0, &id); + hdl = _beginthreadex(null, cast(uint)stacksize, &threadstart, this, 0, &id); if (hdl == cast(thread_hdl)0) { state = TS.TERMINATED; allThreads[idx] = null; @@ -110,6 +153,12 @@ } } + /** + * Entry point for a thread. If not overridden, it calls the function + * pointer fp and argument arg passed in the constructor, or the delegate + * dg. + * Returns: the thread exit code, which is normally 0. + */ int run() { if (fp) @@ -118,6 +167,12 @@ return dg(); } + /***************************** + * Wait for this thread to terminate. + * Simply returns if thread has already terminated. + * Throws: $(B ThreadError) if the thread hasn't begun yet or + * is called on itself. + */ void wait() { if (this is getThis()) @@ -129,6 +184,12 @@ } } + /***************************** + * Wait for this thread to terminate. + * Simply returns if thread has already terminated. + * Throws: $(B ThreadError) if the thread hasn't begun yet or + * is called on itself. + */ void wait(uint milliseconds) { if (this is getThis()) @@ -140,26 +201,39 @@ } } + /** + * The state of a thread. + */ enum TS { - INITIAL, - RUNNING, - TERMINATED + INITIAL, /// The thread hasn't been started yet. + RUNNING, /// The thread is running or paused. + TERMINATED /// The thread has ended. } + /** + * Returns the state of a thread. + */ TS getState() { return state; } + /** + * The priority of a thread. + */ enum PRIORITY { - INCREASE, - DECREASE, - IDLE, - CRITICAL + INCREASE, /// Increase thread priority + DECREASE, /// Decrease thread priority + IDLE, /// Assign thread low priority + CRITICAL /// Assign thread high priority } + /** + * Adjust the priority of this thread. + * Throws: ThreadError if cannot set priority + */ void setPriority(PRIORITY p) { int nPriority; @@ -184,6 +258,19 @@ error("set priority"); } + /** + * Returns non-zero if this thread is the current thread. + */ + int isSelf() + { + //printf("id = %d, self = %d\n", id, pthread_self()); + return (id == GetCurrentThreadId()); + } + + /** + * Returns a reference to the Thread for the thread that called the + * function. + */ static Thread getThis() { thread_id id; @@ -207,23 +294,35 @@ return result; } + /** + * Returns an array of all the threads currently running. + */ static Thread[] getAll() { return allThreads[0 .. allThreadsDim]; } + /** + * Suspend execution of this thread. + */ void pause() { if (state != TS.RUNNING || SuspendThread(hdl) == 0xFFFFFFFF) error("cannot pause"); } + /** + * Resume execution of this thread. + */ void resume() { if (state != TS.RUNNING || ResumeThread(hdl) == 0xFFFFFFFF) error("cannot resume"); } + /** + * Suspend execution of all threads but this thread. + */ static void pauseAll() { if (nthreads > 1) @@ -240,6 +339,9 @@ } } + /** + * Resume execution of all paused threads. + */ static void resumeAll() { if (nthreads > 1) @@ -256,11 +358,17 @@ } } + /** + * Give up the remainder of this thread's time slice. + */ static void yield() { Sleep(0); } + /** + * + */ static uint nthreads = 1; private: @@ -271,6 +379,8 @@ TS state; int idx = -1; // index into allThreads[] + thread_id id; + size_t stacksize = 0; int (*fp)(void *); void *arg; @@ -283,7 +393,7 @@ } - /************************************************ + /* *********************************************** * This is just a wrapper to interface between C rtl and Thread.run(). */ @@ -397,6 +507,18 @@ private import std.c.unix.unix; private import gcc.builtins; +version (skyos) +{ + private import std.c.skyos.skyos; + private import std.c.skyos.compat; + alias std.c.skyos.compat.pthread_create pthread_create; + alias std.c.skyos.compat.pthread_join pthread_join; + alias std.c.skyos.compat.pthread_self pthread_self; + alias std.c.skyos.compat.pthread_kill pthread_kill; + alias std.c.skyos.compat.pthread_equal pthread_equal; + alias std.c.skyos.compat.sched_yield sched_yield; +} + version (GNU_pthread_suspend) { // nothing @@ -419,19 +541,30 @@ class Thread { - this() + // The optional stacksize parameter default value of 0 will cause threads + // to be created with the default pthread size - Dave Fladebo + this(size_t stacksize = 0) { + init(stacksize); } - this(int (*fp)(void *), void *arg) + this(int (*fp)(void *), void *arg, size_t stacksize = 0) { this.fp = fp; this.arg = arg; + init(stacksize); } - this(int delegate() dg) + this(int delegate() dg, size_t stacksize = 0) { this.dg = dg; + init(stacksize); + } + + ~this() + { + pthread_cond_destroy(&waitCond); + pthread_mutex_destroy(&waitMtx); } pthread_t id; @@ -462,7 +595,9 @@ state = TS.RUNNING; int result; //printf("creating thread x%x\n", this); - result = pthread_create(&id, null, &threadstart, this); + //result = pthread_create(&id, null, &threadstart, this); + // Create with thread attributes to allow non-default stack size - Dave Fladebo + result = pthread_create(&id, &threadAttrs, &threadstart, this); if (result) { state = TS.TERMINATED; allThreads[idx] = null; @@ -497,16 +632,53 @@ void wait(uint milliseconds) { - wait(); - /+ not implemented + // Implemented for POSIX systems by Dave Fladebo if (this is getThis()) error("wait on self"); if (state == TS.RUNNING) - { DWORD dw; + { + timespec ts; + timeval tv; - dw = WaitForSingleObject(hdl, milliseconds); + alias typeof(tv.tv_sec) __time_t; + + pthread_mutex_lock(&waitMtx); + gettimeofday(&tv, null); + ts.tv_sec = cast(__time_t)tv.tv_sec + cast(__time_t)(milliseconds / 1_000); + ts.tv_nsec = (tv.tv_usec * 1_000) + ((milliseconds % 1_000) * 1_000_000); + if (ts.tv_nsec > 1_000_000_000) + { + ts.tv_sec += 1; + ts.tv_nsec -= 1_000_000_000; + } + if (pthread_cond_timedwait(&waitCond, &waitMtx, &ts)) + { + int oldstate, oldtype; + pthread_setcancelstate(PTHREAD_CANCEL_ENABLE, &oldstate); + pthread_setcanceltype(PTHREAD_CANCEL_ASYNCHRONOUS, &oldtype); + + if (pthread_cancel(id)) // thread was not completed in the timeout period, cancel it + { + pthread_mutex_unlock(&waitMtx); + error("cannot terminate thread via timed wait"); + } + + pthread_setcancelstate(oldstate, null); + pthread_setcanceltype(oldtype, null); + + state = TS.TERMINATED; + allThreads[idx] = null; + idx = -1; + nthreads--; + + pthread_mutex_unlock(&waitMtx); + } + else + { + pthread_mutex_unlock(&waitMtx); + wait(); // condition has been signalled as complete (see threadstart()), terminate normally + } } - +/ } enum TS @@ -567,7 +739,7 @@ Thread result; //printf("getThis(), allThreadsDim = %d\n", allThreadsDim); - synchronized (threadLock) + //synchronized (threadLock) { id = pthread_self(); //printf("id = %d\n", id); @@ -643,6 +815,9 @@ { Thread tthis = getThis(); + synchronized (threadLock) + { + for (int i = 0; i < allThreadsDim; i++) { Thread t; @@ -650,6 +825,8 @@ if (t && t !is tthis && t.state == TS.RUNNING) t.pause(); } + + } } } else @@ -660,6 +837,9 @@ Thread tthis = getThis(); int npause = 0; + synchronized (threadLock) + { + for (int i = 0; i < allThreadsDim; i++) { Thread t; @@ -674,6 +854,8 @@ npause++; // count of paused threads } } + + } // Wait for each paused thread to acknowledge while (npause--) @@ -712,7 +894,12 @@ static uint allThreadsDim; static Object threadLock; - static Thread[/*_POSIX_THREAD_THREADS_MAX*/ 100] allThreads; + + // Set max to Windows equivalent for compatibility. + // pthread_create will fail gracefully if stack limit + // is reached prior to allThreads max. + static Thread[0x400] allThreads; + version (GNU_pthread_suspend) { // nothing @@ -726,6 +913,10 @@ int idx = -1; // index into allThreads[] int flags = 0; + pthread_attr_t threadAttrs; + pthread_mutex_t waitMtx; + pthread_cond_t waitCond; + int (*fp)(void *); void *arg; @@ -736,6 +927,24 @@ throw new ThreadError(msg); } + void init(size_t stackSize) + { + // set to default values regardless + // passing this as the 2nd arg. for pthread_create() + // w/o setting an attribute is equivalent to passing null. + pthread_attr_init(&threadAttrs); + if (stackSize > 0) + { + if (pthread_attr_setstacksize(&threadAttrs,stackSize)) + error("cannot set stack size"); + } + + if (pthread_mutex_init(&waitMtx, null)) + error("cannot initialize wait mutex"); + + if (pthread_cond_init(&waitCond, null)) + error("cannot initialize wait condition"); + } /************************************************ * This is just a wrapper to interface between C rtl and Thread.run(). @@ -752,9 +961,14 @@ // before pthread_create() sets it. t.id = pthread_self(); + version(skyos) + installSignalHandlers(); + t.stackBottom = getESP(); try { + if(t.state == TS.RUNNING) + pthread_cond_signal(&t.waitCond); // signal the wait condition (see the timed wait function) result = t.run(); } catch (Object o) @@ -765,10 +979,13 @@ } debug (thread) printf("Ending thread %d\n", t.idx); - t.state = TS.TERMINATED; - allThreads[t.idx] = null; - t.idx = -1; - nthreads--; + synchronized (threadLock) + { + t.state = TS.TERMINATED; + allThreads[t.idx] = null; + t.idx = -1; + nthreads--; + } return cast(void*)result; } @@ -800,7 +1017,22 @@ { /* Install signal handlers so we can suspend/resume threads */ + installSignalHandlers(); + } + + return; + + } + version (GNU_pthread_suspend) + { + // nothing + } + else + { + + private static void installSignalHandlers() + { int result; sigaction_t sigact; result = sigfillset(&sigact.sa_mask); @@ -817,21 +1049,13 @@ if (! flagSuspend.create()) goto Lfail; - } - - return; - Lfail: - getThis().error("cannot initialize threads"); - } + return; + Lfail: + getThis().error("cannot initialize threads"); + } - version (GNU_pthread_suspend) - { - // nothing - } - else - { - + /********************************** * This gets called when a thread gets SIGUSR1. */ @@ -844,7 +1068,6 @@ assert(sig == SIGUSR1); - // %% moved call to sem_post sigset_t sigmask; result = sigfillset(&sigmask); @@ -878,9 +1101,9 @@ static void* getESP() { - // TODO add builtin for using stack_pointer_rtx - int dummy; - void * p = & dummy + 1; // +1 doesn't help much; also assume stack grows down + // TODO add builtin for using stack_pointer_rtx + int dummy; + void * p = & dummy + 1; // +1 doesn't help much; also assume stack grows down return p; } } @@ -889,512 +1112,7 @@ } -/* ================================ linux ================================= */ - -else version (linux) -{ - -private import std.c.linux.linux; -private import std.c.linux.linuxextern; - -alias uint pthread_t; -extern (C) alias void (*__sighandler_t)(int); - -struct sigset_t -{ - uint __val[1024 / (8 * uint.sizeof)]; -} - -struct sigaction_t -{ - __sighandler_t sa_handler; - sigset_t sa_mask; - int sa_flags; - void (*sa_restorer)(); -} - -struct _pthread_fastlock -{ - int __status; - int __spinlock; -} - -struct sem_t -{ - _pthread_fastlock __sem_lock; - int __sem_value; - void* __sem_waiting; -} - -unittest -{ - assert(sigset_t.sizeof == 128); - assert(sigaction_t.sizeof == 140); - assert(sem_t.sizeof == 16); -} - -extern (C) -{ - int pthread_create(pthread_t*, void*, void* (*)(void*), void*); - int pthread_join(pthread_t, void**); - int pthread_kill(pthread_t, int); - pthread_t pthread_self(); - int pthread_equal(pthread_t, pthread_t); - int sem_wait(sem_t*); - int sem_init(sem_t*, int, uint); - int sem_post(sem_t*); - int sched_yield(); - int sigfillset(sigset_t*); - int sigdelset(sigset_t*, int); - int sigaction(int, sigaction_t*, sigaction_t*); - int sigsuspend(sigset_t*); -} - -class ThreadError : Error -{ - this(char[] s) - { - super("Thread error: " ~ s); - } -} - -class Thread +else { - this() - { - } - - this(int (*fp)(void *), void *arg) - { - this.fp = fp; - this.arg = arg; - } - - this(int delegate() dg) - { - this.dg = dg; - } - - pthread_t id; - void* stackBottom; - void* stackTop; - - void start() - { - if (state != TS.INITIAL) - error("already started"); - - synchronized (threadLock) - { - for (int i = 0; 1; i++) - { - if (i == allThreads.length) - error("too many threads"); - if (!allThreads[i]) - { allThreads[i] = this; - idx = i; - if (i >= allThreadsDim) - allThreadsDim = i + 1; - break; - } - } - nthreads++; - - state = TS.RUNNING; - int result; - //printf("creating thread x%x\n", this); - result = pthread_create(&id, null, &threadstart, this); - if (result) - { state = TS.TERMINATED; - allThreads[idx] = null; - idx = -1; - error("failed to start"); // BUG: should report errno - } - } // %% changed end of sync region - //printf("t = x%x, id = %d\n", this, id); - } - - int run() - { - if (fp) - return fp(arg); - else if (dg) - return dg(); - } - - void wait() - { - if (this is getThis()) - error("wait on self"); - if (state == TS.RUNNING) - { int result; - void *value; - - result = pthread_join(id, &value); - if (result) - error("failed to wait"); - } - } - - void wait(uint milliseconds) - { - wait(); - /+ not implemented - if (this is getThis()) - error("wait on self"); - if (state == TS.RUNNING) - { DWORD dw; - - dw = WaitForSingleObject(hdl, milliseconds); - } - +/ - } - - enum TS - { - INITIAL, - RUNNING, - TERMINATED - } - - TS getState() - { - return state; - } - - enum PRIORITY - { - INCREASE, - DECREASE, - IDLE, - CRITICAL - } - - void setPriority(PRIORITY p) - { - /+ not implemented - int nPriority; - - switch (p) - { - case PRIORITY.INCREASE: - nPriority = THREAD_PRIORITY_ABOVE_NORMAL; - break; - case PRIORITY.DECREASE: - nPriority = THREAD_PRIORITY_BELOW_NORMAL; - break; - case PRIORITY.IDLE: - nPriority = THREAD_PRIORITY_IDLE; - break; - case PRIORITY.CRITICAL: - nPriority = THREAD_PRIORITY_TIME_CRITICAL; - break; - } - - if (SetThreadPriority(hdl, nPriority) == THREAD_PRIORITY_ERROR_RETURN) - error("set priority"); - +/ - } - - int isSelf() - { - //printf("id = %d, self = %d\n", id, pthread_self()); - return pthread_equal(pthread_self(), id); - } - - static Thread getThis() - { - pthread_t id; - Thread result; - - //printf("getThis(), allThreadsDim = %d\n", allThreadsDim); - synchronized (threadLock) - { - id = pthread_self(); - //printf("id = %d\n", id); - for (int i = 0; i < allThreadsDim; i++) - { - Thread t = allThreads[i]; - //printf("allThreads[%d] = x%x, id = %d\n", i, t, (t ? t.id : 0)); - if (t && pthread_equal(id, t.id)) - { - return t; - } - } - } - printf("didn't find it\n"); - assert(result); - return result; - } - - static Thread[] getAll() - { - return allThreads[0 .. allThreadsDim]; - } - - void pause() - { - if (state == TS.RUNNING) - { int result; - - result = pthread_kill(id, SIGUSR1); - if (result) - error("cannot pause"); - else - sem_wait(&flagSuspend); // wait for acknowledgement - } - else - error("cannot pause"); - } - - void resume() - { - if (state == TS.RUNNING) - { int result; - - result = pthread_kill(id, SIGUSR2); - if (result) - error("cannot resume"); - } - else - error("cannot resume"); - } - - static void pauseAll() - { - if (nthreads > 1) - { - Thread tthis = getThis(); - int npause = 0; - - for (int i = 0; i < allThreadsDim; i++) - { Thread t; - - t = allThreads[i]; - if (t && t !is tthis && t.state == TS.RUNNING) - { int result; - - result = pthread_kill(t.id, SIGUSR1); - if (result) - getThis().error("cannot pause"); - else - npause++; // count of paused threads - } - } - - // Wait for each paused thread to acknowledge - while (npause--) - { - sem_wait(&flagSuspend); - } - } - } - - static void resumeAll() - { - if (nthreads > 1) - { - Thread tthis = getThis(); - - for (int i = 0; i < allThreadsDim; i++) - { Thread t; - - t = allThreads[i]; - if (t && t !is tthis && t.state == TS.RUNNING) - t.resume(); - } - } - } - - static void yield() - { - sched_yield(); - } - - static uint nthreads = 1; - - private: - - static uint allThreadsDim; - static Object threadLock; - static Thread[/*_POSIX_THREAD_THREADS_MAX*/ 100] allThreads; - static sem_t flagSuspend; - - TS state; - int idx = -1; // index into allThreads[] - int flags = 0; - - int (*fp)(void *); - void *arg; - - int delegate() dg; - - void error(char[] msg) - { - throw new ThreadError(msg); - } - - - /************************************************ - * This is just a wrapper to interface between C rtl and Thread.run(). - */ - - extern (C) static void *threadstart(void *p) - { - Thread t = cast(Thread)p; - int result; - - debug (thread) printf("Starting thread x%x (%d)\n", t, t.idx); - - // Need to set t.id here, because thread is off and running - // before pthread_create() sets it. - t.id = pthread_self(); - - t.stackBottom = getESP(); - try - { - result = t.run(); - } - catch (Object o) - { - printf("Error: "); - o.print(); - result = 1; - } - - debug (thread) printf("Ending thread %d\n", t.idx); - t.state = TS.TERMINATED; - allThreads[t.idx] = null; - t.idx = -1; - nthreads--; - return cast(void*)result; - } - - - /************************************** - * Create a Thread for global main(). - */ - - static void thread_init() - { - threadLock = new Object(); - - Thread t = new Thread(); - - t.state = TS.RUNNING; - t.id = pthread_self(); - - version (none) - { - // See discussion: http://autopackage.org/forums/viewtopic.php?t=22 - static void** libc_stack_end; - - if (libc_stack_end == libc_stack_end.init) - { - void* handle = dlopen(null, RTLD_NOW); - libc_stack_end = cast(void **)dlsym(handle, "__libc_stack_end"); - dlclose(handle); - } - t.stackBottom = *libc_stack_end; - } - else - { - t.stackBottom = cast(void*)__libc_stack_end; - } - - assert(!allThreads[0]); - allThreads[0] = t; - allThreadsDim = 1; - t.idx = 0; - - /* Install signal handlers so we can suspend/resume threads - */ - - int result; - sigaction_t sigact; - result = sigfillset(&sigact.sa_mask); - if (result) - goto Lfail; - sigact.sa_handler = &pauseHandler; - result = sigaction(SIGUSR1, &sigact, null); - if (result) - goto Lfail; - sigact.sa_handler = &resumeHandler; - result = sigaction(SIGUSR2, &sigact, null); - if (result) - goto Lfail; - - result = sem_init(&flagSuspend, 0, 0); - if (result) - goto Lfail; - - return; - - Lfail: - getThis().error("cannot initialize threads"); - } - - /********************************** - * This gets called when a thread gets SIGUSR1. - */ - - extern (C) static void pauseHandler(int sig) - { int result; - - // Save all registers on the stack so they'll be scanned by the GC - asm - { - pusha ; - } - - assert(sig == SIGUSR1); - // %% moved call to sem_post - - sigset_t sigmask; - result = sigfillset(&sigmask); - assert(result == 0); - result = sigdelset(&sigmask, SIGUSR2); - assert(result == 0); - - Thread t = getThis(); - t.stackTop = getESP(); - t.flags &= ~1; - sem_post(&flagSuspend); - while (1) - { - sigsuspend(&sigmask); // suspend until SIGUSR2 - if (t.flags & 1) // ensure it was resumeHandler() - break; - } - - // Restore all registers - asm - { - popa ; - } - } - - /********************************** - * This gets called when a thread gets SIGUSR2. - */ - - extern (C) static void resumeHandler(int sig) - { - Thread t = getThis(); - - t.flags |= 1; - } - - static void* getESP() - { - asm - { naked ; - mov EAX,ESP ; - ret ; - } - } + static assert(0); } - - -} - diff -uNr gdc-0.17/d/phobos/std/typeinfo/ti_Aa.d gdc-0.18/d/phobos/std/typeinfo/ti_Aa.d --- gdc-0.17/d/phobos/std/typeinfo/ti_Aa.d 2005-10-13 03:06:51.000000000 +0200 +++ gdc-0.18/d/phobos/std/typeinfo/ti_Aa.d 2006-05-14 01:38:32.000000000 +0200 @@ -1,5 +1,8 @@ +module std.typeinfo.Aa; + private import std.string; +private import std.c.string; // char[] @@ -7,9 +10,9 @@ { char[] toString() { return "char[]"; } - uint getHash(void *p) + hash_t getHash(void *p) { char[] s = *cast(char[]*)p; - uint hash = 0; + hash_t hash = 0; version (all) { diff -uNr gdc-0.17/d/phobos/std/typeinfo/ti_Abit.d gdc-0.18/d/phobos/std/typeinfo/ti_Abit.d --- gdc-0.17/d/phobos/std/typeinfo/ti_Abit.d 2005-10-13 03:06:51.000000000 +0200 +++ gdc-0.18/d/phobos/std/typeinfo/ti_Abit.d 2006-03-12 23:08:56.000000000 +0100 @@ -1,4 +1,6 @@ +module std.typeinfo.ti_Abit; + private import std.string; // bit[] diff -uNr gdc-0.17/d/phobos/std/typeinfo/ti_AC.d gdc-0.18/d/phobos/std/typeinfo/ti_AC.d --- gdc-0.17/d/phobos/std/typeinfo/ti_AC.d 2005-10-13 03:06:51.000000000 +0200 +++ gdc-0.18/d/phobos/std/typeinfo/ti_AC.d 2006-05-14 03:05:56.000000000 +0200 @@ -1,13 +1,12 @@ - -private import std.string; +module std.typeinfo.ti_AC; // Object[] class TypeInfo_AC : TypeInfo { - uint getHash(void *p) + hash_t getHash(void *p) { Object[] s = *cast(Object[]*)p; - uint hash = 0; + hash_t hash = 0; foreach (Object o; s) { diff -uNr gdc-0.17/d/phobos/std/typeinfo/ti_Acdouble.d gdc-0.18/d/phobos/std/typeinfo/ti_Acdouble.d --- gdc-0.17/d/phobos/std/typeinfo/ti_Acdouble.d 2005-10-13 03:06:51.000000000 +0200 +++ gdc-0.18/d/phobos/std/typeinfo/ti_Acdouble.d 2006-05-14 03:05:56.000000000 +0200 @@ -21,7 +21,8 @@ * distribution. */ -private import std.string; +module std.typeinfo.ti_Acdouble; + private import std.typeinfo.ti_cdouble; // cdouble[] @@ -30,11 +31,11 @@ { char[] toString() { return "cdouble[]"; } - uint getHash(void *p) + hash_t getHash(void *p) { cdouble[] s = *cast(cdouble[]*)p; size_t len = s.length; cdouble *str = s; - uint hash = 0; + hash_t hash = 0; while (len) { diff -uNr gdc-0.17/d/phobos/std/typeinfo/ti_Acfloat.d gdc-0.18/d/phobos/std/typeinfo/ti_Acfloat.d --- gdc-0.17/d/phobos/std/typeinfo/ti_Acfloat.d 2005-10-13 03:06:51.000000000 +0200 +++ gdc-0.18/d/phobos/std/typeinfo/ti_Acfloat.d 2006-05-14 03:05:56.000000000 +0200 @@ -21,7 +21,8 @@ * distribution. */ -private import std.string; +module std.typeinfo.ti_Acfloat; + private import std.typeinfo.ti_cfloat; // cfloat[] @@ -30,11 +31,11 @@ { char[] toString() { return "cfloat[]"; } - uint getHash(void *p) + hash_t getHash(void *p) { cfloat[] s = *cast(cfloat[]*)p; size_t len = s.length; cfloat *str = s; - uint hash = 0; + hash_t hash = 0; while (len) { diff -uNr gdc-0.17/d/phobos/std/typeinfo/ti_Acreal.d gdc-0.18/d/phobos/std/typeinfo/ti_Acreal.d --- gdc-0.17/d/phobos/std/typeinfo/ti_Acreal.d 2005-10-13 03:06:51.000000000 +0200 +++ gdc-0.18/d/phobos/std/typeinfo/ti_Acreal.d 2006-05-14 03:05:56.000000000 +0200 @@ -21,7 +21,8 @@ * distribution. */ -private import std.string; +module std.typeinfo.ti_Acreal; + private import std.typeinfo.ti_creal; // creal[] @@ -30,11 +31,11 @@ { char[] toString() { return "creal[]"; } - uint getHash(void *p) + hash_t getHash(void *p) { creal[] s = *cast(creal[]*)p; size_t len = s.length; creal *str = s; - uint hash = 0; + hash_t hash = 0; while (len) { diff -uNr gdc-0.17/d/phobos/std/typeinfo/ti_Adchar.d gdc-0.18/d/phobos/std/typeinfo/ti_Adchar.d --- gdc-0.17/d/phobos/std/typeinfo/ti_Adchar.d 2005-10-13 03:06:51.000000000 +0200 +++ gdc-0.18/d/phobos/std/typeinfo/ti_Adchar.d 2006-05-14 01:38:32.000000000 +0200 @@ -1,5 +1,7 @@ -private import std.string; +module std.typeinfo.ti_Adchar; + +private import std.c.string; // dchar[] @@ -7,11 +9,11 @@ { char[] toString() { return "dchar[]"; } - uint getHash(void *p) + hash_t getHash(void *p) { dchar[] s = *cast(dchar[]*)p; size_t len = s.length; dchar *str = s; - uint hash = 0; + hash_t hash = 0; while (len) { diff -uNr gdc-0.17/d/phobos/std/typeinfo/ti_Adouble.d gdc-0.18/d/phobos/std/typeinfo/ti_Adouble.d --- gdc-0.17/d/phobos/std/typeinfo/ti_Adouble.d 2005-10-13 03:06:51.000000000 +0200 +++ gdc-0.18/d/phobos/std/typeinfo/ti_Adouble.d 2006-05-14 03:05:56.000000000 +0200 @@ -21,7 +21,8 @@ * distribution. */ -private import std.string; +module std.typeinfo.ti_Adouble; + private import std.typeinfo.ti_double; // double[] @@ -30,11 +31,11 @@ { char[] toString() { return "double[]"; } - uint getHash(void *p) + hash_t getHash(void *p) { double[] s = *cast(double[]*)p; size_t len = s.length; double *str = s; - uint hash = 0; + hash_t hash = 0; while (len) { diff -uNr gdc-0.17/d/phobos/std/typeinfo/ti_Afloat.d gdc-0.18/d/phobos/std/typeinfo/ti_Afloat.d --- gdc-0.17/d/phobos/std/typeinfo/ti_Afloat.d 2005-10-13 03:06:51.000000000 +0200 +++ gdc-0.18/d/phobos/std/typeinfo/ti_Afloat.d 2006-05-14 03:05:56.000000000 +0200 @@ -21,7 +21,8 @@ * distribution. */ -private import std.string; +module std.typeinfo.ti_Afloat; + private import std.typeinfo.ti_float; // float[] @@ -30,11 +31,11 @@ { char[] toString() { return "float[]"; } - uint getHash(void *p) + hash_t getHash(void *p) { float[] s = *cast(float[]*)p; size_t len = s.length; float *str = s; - uint hash = 0; + hash_t hash = 0; while (len) { diff -uNr gdc-0.17/d/phobos/std/typeinfo/ti_Ag.d gdc-0.18/d/phobos/std/typeinfo/ti_Ag.d --- gdc-0.17/d/phobos/std/typeinfo/ti_Ag.d 2005-10-13 03:06:51.000000000 +0200 +++ gdc-0.18/d/phobos/std/typeinfo/ti_Ag.d 2006-05-14 03:05:56.000000000 +0200 @@ -1,5 +1,7 @@ -private import std.string; +module std.typeinfo.ti_Ag; + +private import std.c.string; // byte[] @@ -7,11 +9,11 @@ { char[] toString() { return "byte[]"; } - uint getHash(void *p) + hash_t getHash(void *p) { byte[] s = *cast(byte[]*)p; size_t len = s.length; byte *str = s; - uint hash = 0; + hash_t hash = 0; while (1) { diff -uNr gdc-0.17/d/phobos/std/typeinfo/ti_Aint.d gdc-0.18/d/phobos/std/typeinfo/ti_Aint.d --- gdc-0.17/d/phobos/std/typeinfo/ti_Aint.d 2005-10-13 03:06:51.000000000 +0200 +++ gdc-0.18/d/phobos/std/typeinfo/ti_Aint.d 2006-05-14 01:38:32.000000000 +0200 @@ -1,5 +1,7 @@ -private import std.string; +module std.typeinfo.ti_Aint; + +private import std.c.string; // int[] @@ -7,11 +9,11 @@ { char[] toString() { return "int[]"; } - uint getHash(void *p) + hash_t getHash(void *p) { int[] s = *cast(int[]*)p; size_t len = s.length; int *str = s; - uint hash = 0; + hash_t hash = 0; while (len) { diff -uNr gdc-0.17/d/phobos/std/typeinfo/ti_Along.d gdc-0.18/d/phobos/std/typeinfo/ti_Along.d --- gdc-0.17/d/phobos/std/typeinfo/ti_Along.d 2005-10-13 03:06:51.000000000 +0200 +++ gdc-0.18/d/phobos/std/typeinfo/ti_Along.d 2006-05-14 01:38:32.000000000 +0200 @@ -1,5 +1,7 @@ -private import std.string; +module std.typeinfo.ti_Along; + +private import std.c.string; // long[] @@ -7,11 +9,11 @@ { char[] toString() { return "long[]"; } - uint getHash(void *p) + hash_t getHash(void *p) { long[] s = *cast(long[]*)p; size_t len = s.length; long *str = s; - uint hash = 0; + hash_t hash = 0; while (len) { diff -uNr gdc-0.17/d/phobos/std/typeinfo/ti_Areal.d gdc-0.18/d/phobos/std/typeinfo/ti_Areal.d --- gdc-0.17/d/phobos/std/typeinfo/ti_Areal.d 2005-10-13 03:06:51.000000000 +0200 +++ gdc-0.18/d/phobos/std/typeinfo/ti_Areal.d 2006-05-14 03:05:56.000000000 +0200 @@ -1,5 +1,5 @@ /* - * Copyright (C) 2004-2005 by Digital Mars, www.digitalmars.com + * Copyright (C) 2004-2006 by Digital Mars, www.digitalmars.com * Written by Walter Bright * * This software is provided 'as-is', without any express or implied @@ -21,7 +21,8 @@ * distribution. */ -private import std.string; +module std.typeinfo.ti_Areal; + private import std.typeinfo.ti_real; // real[] @@ -30,11 +31,11 @@ { char[] toString() { return "real[]"; } - uint getHash(void *p) + hash_t getHash(void *p) { real[] s = *cast(real[]*)p; size_t len = s.length; real *str = s; - uint hash = 0; + hash_t hash = 0; while (len) { diff -uNr gdc-0.17/d/phobos/std/typeinfo/ti_Ashort.d gdc-0.18/d/phobos/std/typeinfo/ti_Ashort.d --- gdc-0.17/d/phobos/std/typeinfo/ti_Ashort.d 2005-10-13 03:06:51.000000000 +0200 +++ gdc-0.18/d/phobos/std/typeinfo/ti_Ashort.d 2006-05-14 03:05:56.000000000 +0200 @@ -1,5 +1,7 @@ -private import std.string; +module std.typeinfo.ti_Ashort; + +private import std.c.string; // short[] @@ -7,11 +9,11 @@ { char[] toString() { return "short[]"; } - uint getHash(void *p) + hash_t getHash(void *p) { short[] s = *cast(short[]*)p; size_t len = s.length; short *str = s; - uint hash = 0; + hash_t hash = 0; while (1) { diff -uNr gdc-0.17/d/phobos/std/typeinfo/ti_Aubyte.d gdc-0.18/d/phobos/std/typeinfo/ti_Aubyte.d --- gdc-0.17/d/phobos/std/typeinfo/ti_Aubyte.d 2005-10-13 03:06:51.000000000 +0200 +++ gdc-0.18/d/phobos/std/typeinfo/ti_Aubyte.d 2006-05-14 03:05:56.000000000 +0200 @@ -1,5 +1,8 @@ +module std.typeinfo.ti_Aubyte; + private import std.string; +private import std.c.string; // ubyte[] @@ -7,11 +10,11 @@ { char[] toString() { return "ubyte[]"; } - uint getHash(void *p) + hash_t getHash(void *p) { ubyte[] s = *cast(ubyte[]*)p; size_t len = s.length; ubyte *str = s; - uint hash = 0; + hash_t hash = 0; while (1) { @@ -77,3 +80,10 @@ { char[] toString() { return "void[]"; } } + +// bool[] + +class TypeInfo_Ax : TypeInfo_Ah +{ + char[] toString() { return "bool[]"; } +} diff -uNr gdc-0.17/d/phobos/std/typeinfo/ti_Auint.d gdc-0.18/d/phobos/std/typeinfo/ti_Auint.d --- gdc-0.17/d/phobos/std/typeinfo/ti_Auint.d 2005-10-13 03:06:51.000000000 +0200 +++ gdc-0.18/d/phobos/std/typeinfo/ti_Auint.d 2006-05-14 01:38:32.000000000 +0200 @@ -1,5 +1,7 @@ -private import std.string; +module std.typeinfo.ti_Auint; + +private import std.c.string; // uint[] @@ -7,11 +9,11 @@ { char[] toString() { return "uint[]"; } - uint getHash(void *p) + hash_t getHash(void *p) { uint[] s = *cast(uint[]*)p; size_t len = s.length; uint *str = s; - uint hash = 0; + hash_t hash = 0; while (len) { diff -uNr gdc-0.17/d/phobos/std/typeinfo/ti_Aulong.d gdc-0.18/d/phobos/std/typeinfo/ti_Aulong.d --- gdc-0.17/d/phobos/std/typeinfo/ti_Aulong.d 2005-10-13 03:06:51.000000000 +0200 +++ gdc-0.18/d/phobos/std/typeinfo/ti_Aulong.d 2006-05-14 01:38:32.000000000 +0200 @@ -1,5 +1,7 @@ -private import std.string; +module std.typeinfo.ti_Aulong; + +private import std.c.string; // ulong[] @@ -7,11 +9,11 @@ { char[] toString() { return "ulong[]"; } - uint getHash(void *p) + hash_t getHash(void *p) { ulong[] s = *cast(ulong[]*)p; size_t len = s.length; ulong *str = s; - uint hash = 0; + hash_t hash = 0; while (len) { diff -uNr gdc-0.17/d/phobos/std/typeinfo/ti_Aushort.d gdc-0.18/d/phobos/std/typeinfo/ti_Aushort.d --- gdc-0.17/d/phobos/std/typeinfo/ti_Aushort.d 2005-10-13 03:06:51.000000000 +0200 +++ gdc-0.18/d/phobos/std/typeinfo/ti_Aushort.d 2006-05-14 03:05:56.000000000 +0200 @@ -1,5 +1,7 @@ -private import std.string; +module std.typeinfo.ti_Aushort; + +private import std.c.string; // ushort[] @@ -7,11 +9,11 @@ { char[] toString() { return "ushort[]"; } - uint getHash(void *p) + hash_t getHash(void *p) { ushort[] s = *cast(ushort[]*)p; size_t len = s.length; ushort *str = s; - uint hash = 0; + hash_t hash = 0; while (1) { diff -uNr gdc-0.17/d/phobos/std/typeinfo/ti_Awchar.d gdc-0.18/d/phobos/std/typeinfo/ti_Awchar.d --- gdc-0.17/d/phobos/std/typeinfo/ti_Awchar.d 2005-10-13 03:06:51.000000000 +0200 +++ gdc-0.18/d/phobos/std/typeinfo/ti_Awchar.d 2006-05-14 01:38:32.000000000 +0200 @@ -1,5 +1,7 @@ -private import std.string; +module std.typeinfo.ti_Awchar; + +private import std.c.string; // wchar[] @@ -7,11 +9,11 @@ { char[] toString() { return "wchar[]"; } - uint getHash(void *p) + hash_t getHash(void *p) { wchar[] s = *cast(wchar[]*)p; size_t len = s.length; wchar *str = s; - uint hash = 0; + hash_t hash = 0; while (1) { diff -uNr gdc-0.17/d/phobos/std/typeinfo/ti_bit.d gdc-0.18/d/phobos/std/typeinfo/ti_bit.d --- gdc-0.17/d/phobos/std/typeinfo/ti_bit.d 2005-10-13 03:06:51.000000000 +0200 +++ gdc-0.18/d/phobos/std/typeinfo/ti_bit.d 2006-03-12 23:08:56.000000000 +0100 @@ -1,6 +1,8 @@ // bit +module std.typeinfo.ti_bit; + class TypeInfo_b : TypeInfo { char[] toString() { return "bit"; } diff -uNr gdc-0.17/d/phobos/std/typeinfo/ti_byte.d gdc-0.18/d/phobos/std/typeinfo/ti_byte.d --- gdc-0.17/d/phobos/std/typeinfo/ti_byte.d 2005-10-13 03:06:51.000000000 +0200 +++ gdc-0.18/d/phobos/std/typeinfo/ti_byte.d 2006-05-14 01:38:32.000000000 +0200 @@ -1,11 +1,13 @@ // byte +module std.typeinfo.ti_byte; + class TypeInfo_g : TypeInfo { char[] toString() { return "byte"; } - uint getHash(void *p) + hash_t getHash(void *p) { return *cast(byte *)p; } diff -uNr gdc-0.17/d/phobos/std/typeinfo/ti_C.d gdc-0.18/d/phobos/std/typeinfo/ti_C.d --- gdc-0.17/d/phobos/std/typeinfo/ti_C.d 2005-10-13 03:06:51.000000000 +0200 +++ gdc-0.18/d/phobos/std/typeinfo/ti_C.d 2006-05-14 03:05:56.000000000 +0200 @@ -21,13 +21,13 @@ * distribution. */ -private import std.string; +module std.typeinfo.ti_C; // Object class TypeInfo_C : TypeInfo { - uint getHash(void *p) + hash_t getHash(void *p) { Object o = *cast(Object*)p; assert(o); diff -uNr gdc-0.17/d/phobos/std/typeinfo/ti_cdouble.d gdc-0.18/d/phobos/std/typeinfo/ti_cdouble.d --- gdc-0.17/d/phobos/std/typeinfo/ti_cdouble.d 2005-10-13 03:06:51.000000000 +0200 +++ gdc-0.18/d/phobos/std/typeinfo/ti_cdouble.d 2006-05-14 01:38:32.000000000 +0200 @@ -1,11 +1,13 @@ // cdouble +module std.typeinfo.ti_cdouble; + class TypeInfo_r : TypeInfo { char[] toString() { return "cdouble"; } - uint getHash(void *p) + hash_t getHash(void *p) { return (cast(uint *)p)[0] + (cast(uint *)p)[1] + (cast(uint *)p)[2] + (cast(uint *)p)[3]; diff -uNr gdc-0.17/d/phobos/std/typeinfo/ti_cfloat.d gdc-0.18/d/phobos/std/typeinfo/ti_cfloat.d --- gdc-0.17/d/phobos/std/typeinfo/ti_cfloat.d 2005-10-13 03:06:51.000000000 +0200 +++ gdc-0.18/d/phobos/std/typeinfo/ti_cfloat.d 2006-05-14 01:38:32.000000000 +0200 @@ -1,11 +1,13 @@ // cfloat +module std.typeinfo.ti_cfloat; + class TypeInfo_q : TypeInfo { char[] toString() { return "cfloat"; } - uint getHash(void *p) + hash_t getHash(void *p) { return (cast(uint *)p)[0] + (cast(uint *)p)[1]; } diff -uNr gdc-0.17/d/phobos/std/typeinfo/ti_char.d gdc-0.18/d/phobos/std/typeinfo/ti_char.d --- gdc-0.17/d/phobos/std/typeinfo/ti_char.d 2005-10-13 03:06:51.000000000 +0200 +++ gdc-0.18/d/phobos/std/typeinfo/ti_char.d 2006-05-14 01:38:32.000000000 +0200 @@ -1,10 +1,11 @@ +module std.typeinfo.ti_char; class TypeInfo_a : TypeInfo { char[] toString() { return "char"; } - uint getHash(void *p) + hash_t getHash(void *p) { return *cast(char *)p; } diff -uNr gdc-0.17/d/phobos/std/typeinfo/ti_creal.d gdc-0.18/d/phobos/std/typeinfo/ti_creal.d --- gdc-0.17/d/phobos/std/typeinfo/ti_creal.d 2005-10-13 03:06:51.000000000 +0200 +++ gdc-0.18/d/phobos/std/typeinfo/ti_creal.d 2006-05-14 01:38:32.000000000 +0200 @@ -1,11 +1,13 @@ // creal +module std.typeinfo.ti_creal; + class TypeInfo_c : TypeInfo { char[] toString() { return "creal"; } - uint getHash(void *p) + hash_t getHash(void *p) { return (cast(uint *)p)[0] + (cast(uint *)p)[1] + (cast(uint *)p)[2] + (cast(uint *)p)[3] + diff -uNr gdc-0.17/d/phobos/std/typeinfo/ti_dchar.d gdc-0.18/d/phobos/std/typeinfo/ti_dchar.d --- gdc-0.17/d/phobos/std/typeinfo/ti_dchar.d 2005-10-13 03:06:51.000000000 +0200 +++ gdc-0.18/d/phobos/std/typeinfo/ti_dchar.d 2006-05-14 01:38:32.000000000 +0200 @@ -1,11 +1,13 @@ // dchar +module std.typeinfo.ti_dchar; + class TypeInfo_w : TypeInfo { char[] toString() { return "dchar"; } - uint getHash(void *p) + hash_t getHash(void *p) { return *cast(dchar *)p; } diff -uNr gdc-0.17/d/phobos/std/typeinfo/ti_delegate.d gdc-0.18/d/phobos/std/typeinfo/ti_delegate.d --- gdc-0.17/d/phobos/std/typeinfo/ti_delegate.d 2005-10-13 03:06:51.000000000 +0200 +++ gdc-0.18/d/phobos/std/typeinfo/ti_delegate.d 2006-05-14 01:38:32.000000000 +0200 @@ -1,11 +1,13 @@ // delegate +module std.typeinfo.ti_delegate; + alias void delegate(int) dg; class TypeInfo_D : TypeInfo { - uint getHash(void *p) + hash_t getHash(void *p) { long l = *cast(long *)p; return cast(uint)(l + (l >> 32)); diff -uNr gdc-0.17/d/phobos/std/typeinfo/ti_double.d gdc-0.18/d/phobos/std/typeinfo/ti_double.d --- gdc-0.17/d/phobos/std/typeinfo/ti_double.d 2005-10-13 03:06:51.000000000 +0200 +++ gdc-0.18/d/phobos/std/typeinfo/ti_double.d 2006-05-14 01:38:32.000000000 +0200 @@ -1,13 +1,15 @@ // double +module std.typeinfo.ti_double; + private import std.math; class TypeInfo_d : TypeInfo { char[] toString() { return "double"; } - uint getHash(void *p) + hash_t getHash(void *p) { return (cast(uint *)p)[0] + (cast(uint *)p)[1]; } diff -uNr gdc-0.17/d/phobos/std/typeinfo/ti_float.d gdc-0.18/d/phobos/std/typeinfo/ti_float.d --- gdc-0.17/d/phobos/std/typeinfo/ti_float.d 2005-10-13 03:06:51.000000000 +0200 +++ gdc-0.18/d/phobos/std/typeinfo/ti_float.d 2006-05-14 01:38:32.000000000 +0200 @@ -1,13 +1,15 @@ // float +module std.typeinfo.ti_float; + private import std.math; class TypeInfo_f : TypeInfo { char[] toString() { return "float"; } - uint getHash(void *p) + hash_t getHash(void *p) { return *cast(uint *)p; } diff -uNr gdc-0.17/d/phobos/std/typeinfo/ti_idouble.d gdc-0.18/d/phobos/std/typeinfo/ti_idouble.d --- gdc-0.17/d/phobos/std/typeinfo/ti_idouble.d 2005-04-28 23:12:43.000000000 +0200 +++ gdc-0.18/d/phobos/std/typeinfo/ti_idouble.d 2006-03-12 23:08:56.000000000 +0100 @@ -1,6 +1,8 @@ // idouble +module std.typeinfo.ti_idouble; + private import std.typeinfo.ti_double; class TypeInfo_p : TypeInfo_d diff -uNr gdc-0.17/d/phobos/std/typeinfo/ti_ifloat.d gdc-0.18/d/phobos/std/typeinfo/ti_ifloat.d --- gdc-0.17/d/phobos/std/typeinfo/ti_ifloat.d 2005-04-28 23:12:43.000000000 +0200 +++ gdc-0.18/d/phobos/std/typeinfo/ti_ifloat.d 2006-03-12 23:08:56.000000000 +0100 @@ -1,6 +1,8 @@ // ifloat +module std.typeinfo.ti_ifloat; + private import std.typeinfo.ti_float; class TypeInfo_o : TypeInfo_f diff -uNr gdc-0.17/d/phobos/std/typeinfo/ti_int.d gdc-0.18/d/phobos/std/typeinfo/ti_int.d --- gdc-0.17/d/phobos/std/typeinfo/ti_int.d 2005-10-13 03:06:51.000000000 +0200 +++ gdc-0.18/d/phobos/std/typeinfo/ti_int.d 2006-05-14 01:38:32.000000000 +0200 @@ -1,11 +1,13 @@ // int +module std.typeinfo.ti_int; + class TypeInfo_i : TypeInfo { char[] toString() { return "int"; } - uint getHash(void *p) + hash_t getHash(void *p) { return *cast(uint *)p; } diff -uNr gdc-0.17/d/phobos/std/typeinfo/ti_ireal.d gdc-0.18/d/phobos/std/typeinfo/ti_ireal.d --- gdc-0.17/d/phobos/std/typeinfo/ti_ireal.d 2005-04-28 23:12:43.000000000 +0200 +++ gdc-0.18/d/phobos/std/typeinfo/ti_ireal.d 2006-03-12 23:08:56.000000000 +0100 @@ -1,6 +1,8 @@ // ireal +module std.typeinfo.ti_ireal; + private import std.typeinfo.ti_real; class TypeInfo_j : TypeInfo_e diff -uNr gdc-0.17/d/phobos/std/typeinfo/ti_long.d gdc-0.18/d/phobos/std/typeinfo/ti_long.d --- gdc-0.17/d/phobos/std/typeinfo/ti_long.d 2005-10-13 03:06:51.000000000 +0200 +++ gdc-0.18/d/phobos/std/typeinfo/ti_long.d 2006-05-14 01:38:32.000000000 +0200 @@ -1,11 +1,13 @@ // long +module std.typeinfo.ti_long; + class TypeInfo_l : TypeInfo { char[] toString() { return "long"; } - uint getHash(void *p) + hash_t getHash(void *p) { return *cast(uint *)p + (cast(uint *)p)[1]; } diff -uNr gdc-0.17/d/phobos/std/typeinfo/ti_ptr.d gdc-0.18/d/phobos/std/typeinfo/ti_ptr.d --- gdc-0.17/d/phobos/std/typeinfo/ti_ptr.d 2005-10-13 03:06:51.000000000 +0200 +++ gdc-0.18/d/phobos/std/typeinfo/ti_ptr.d 2006-05-14 01:38:32.000000000 +0200 @@ -1,9 +1,11 @@ // pointer +module std.typeinfo.ti_ptr; + class TypeInfo_P : TypeInfo { - uint getHash(void *p) + hash_t getHash(void *p) { return cast(uint)*cast(void* *)p; } diff -uNr gdc-0.17/d/phobos/std/typeinfo/ti_real.d gdc-0.18/d/phobos/std/typeinfo/ti_real.d --- gdc-0.17/d/phobos/std/typeinfo/ti_real.d 2005-10-13 03:06:51.000000000 +0200 +++ gdc-0.18/d/phobos/std/typeinfo/ti_real.d 2006-05-14 01:38:32.000000000 +0200 @@ -1,13 +1,15 @@ // real +module std.typeinfo.ti_real; + private import std.math; class TypeInfo_e : TypeInfo { char[] toString() { return "real"; } - uint getHash(void *p) + hash_t getHash(void *p) { return (cast(uint *)p)[0] + (cast(uint *)p)[1] + (cast(ushort *)p)[4]; } diff -uNr gdc-0.17/d/phobos/std/typeinfo/ti_short.d gdc-0.18/d/phobos/std/typeinfo/ti_short.d --- gdc-0.17/d/phobos/std/typeinfo/ti_short.d 2005-10-13 03:06:51.000000000 +0200 +++ gdc-0.18/d/phobos/std/typeinfo/ti_short.d 2006-05-14 01:38:32.000000000 +0200 @@ -1,11 +1,13 @@ // short +module std.typeinfo.ti_short; + class TypeInfo_s : TypeInfo { char[] toString() { return "short"; } - uint getHash(void *p) + hash_t getHash(void *p) { return *cast(short *)p; } diff -uNr gdc-0.17/d/phobos/std/typeinfo/ti_ubyte.d gdc-0.18/d/phobos/std/typeinfo/ti_ubyte.d --- gdc-0.17/d/phobos/std/typeinfo/ti_ubyte.d 2005-10-13 03:06:51.000000000 +0200 +++ gdc-0.18/d/phobos/std/typeinfo/ti_ubyte.d 2006-05-14 01:38:32.000000000 +0200 @@ -1,11 +1,13 @@ // ubyte +module std.typeinfo.ti_ubyte; + class TypeInfo_h : TypeInfo { char[] toString() { return "ubyte"; } - uint getHash(void *p) + hash_t getHash(void *p) { return *cast(ubyte *)p; } @@ -35,3 +37,7 @@ } } +class TypeInfo_x : TypeInfo_h +{ + char[] toString() { return "bool"; } +} diff -uNr gdc-0.17/d/phobos/std/typeinfo/ti_uint.d gdc-0.18/d/phobos/std/typeinfo/ti_uint.d --- gdc-0.17/d/phobos/std/typeinfo/ti_uint.d 2005-10-13 03:06:51.000000000 +0200 +++ gdc-0.18/d/phobos/std/typeinfo/ti_uint.d 2006-05-14 01:38:32.000000000 +0200 @@ -1,11 +1,13 @@ // uint +module std.typeinfo.ti_uint; + class TypeInfo_k : TypeInfo { char[] toString() { return "uint"; } - uint getHash(void *p) + hash_t getHash(void *p) { return *cast(uint *)p; } diff -uNr gdc-0.17/d/phobos/std/typeinfo/ti_ulong.d gdc-0.18/d/phobos/std/typeinfo/ti_ulong.d --- gdc-0.17/d/phobos/std/typeinfo/ti_ulong.d 2005-10-13 03:06:51.000000000 +0200 +++ gdc-0.18/d/phobos/std/typeinfo/ti_ulong.d 2006-05-14 01:38:32.000000000 +0200 @@ -1,11 +1,13 @@ // ulong +module std.typeinfo.ti_ulong; + class TypeInfo_m : TypeInfo { char[] toString() { return "ulong"; } - uint getHash(void *p) + hash_t getHash(void *p) { return *cast(uint *)p + (cast(uint *)p)[1]; } diff -uNr gdc-0.17/d/phobos/std/typeinfo/ti_ushort.d gdc-0.18/d/phobos/std/typeinfo/ti_ushort.d --- gdc-0.17/d/phobos/std/typeinfo/ti_ushort.d 2005-10-13 03:06:51.000000000 +0200 +++ gdc-0.18/d/phobos/std/typeinfo/ti_ushort.d 2006-05-14 01:38:32.000000000 +0200 @@ -1,11 +1,13 @@ // ushort +module std.typeinfo.ti_ushort; + class TypeInfo_t : TypeInfo { char[] toString() { return "ushort"; } - uint getHash(void *p) + hash_t getHash(void *p) { return *cast(ushort *)p; } diff -uNr gdc-0.17/d/phobos/std/typeinfo/ti_void.d gdc-0.18/d/phobos/std/typeinfo/ti_void.d --- gdc-0.17/d/phobos/std/typeinfo/ti_void.d 2005-10-13 03:06:51.000000000 +0200 +++ gdc-0.18/d/phobos/std/typeinfo/ti_void.d 2006-05-14 01:38:32.000000000 +0200 @@ -1,11 +1,13 @@ // void +module std.typeinfo.ti_void; + class TypeInfo_v : TypeInfo { char[] toString() { return "void"; } - uint getHash(void *p) + hash_t getHash(void *p) { assert(0); return *cast(byte *)p; diff -uNr gdc-0.17/d/phobos/std/typeinfo/ti_wchar.d gdc-0.18/d/phobos/std/typeinfo/ti_wchar.d --- gdc-0.17/d/phobos/std/typeinfo/ti_wchar.d 2005-10-13 03:06:51.000000000 +0200 +++ gdc-0.18/d/phobos/std/typeinfo/ti_wchar.d 2006-05-14 01:38:32.000000000 +0200 @@ -1,10 +1,12 @@ +module std.typeinfo.ti_wchar; + class TypeInfo_u : TypeInfo { char[] toString() { return "wchar"; } - uint getHash(void *p) + hash_t getHash(void *p) { return *cast(wchar *)p; } diff -uNr gdc-0.17/d/phobos/std/uni.d gdc-0.18/d/phobos/std/uni.d --- gdc-0.17/d/phobos/std/uni.d 2005-10-02 16:17:55.000000000 +0200 +++ gdc-0.18/d/phobos/std/uni.d 2006-05-14 03:05:56.000000000 +0200 @@ -1,6 +1,26 @@ +/* + * Placed into the Public Domain. + * Digital Mars, www.digitalmars.com + * Written by Walter Bright + */ + +/** + * Simple Unicode character classification functions. + * For ASCII classification, see $(LINK2 std_ctype.html, std.ctype). + * Macros: + * WIKI=Phobos/StdUni + * References: + * $(LINK2 http://www.digitalmars.com/d/ascii-table.html, ASCII Table), + * $(LINK2 http://en.wikipedia.org/wiki/Unicode, Wikipedia), + * $(LINK2 http://www.unicode.org, The Unicode Consortium) + */ + module std.uni; +/** + * Returns !=0 if c is a Unicode lower case character. + */ int isUniLower(dchar c) { if (c <= 0x7F) @@ -9,6 +29,9 @@ return isUniAlpha(c) && c == toUniLower(c); } +/** + * Returns !=0 if c is a Unicode upper case character. + */ int isUniUpper(dchar c) { if (c <= 0x7F) @@ -17,6 +40,10 @@ return isUniAlpha(c) && c == toUniUpper(c); } +/** + * If c is a Unicode upper case character, return the lower case + * equivalent, otherwise return c. + */ dchar toUniLower(dchar c) { if (c >= 'A' && c <= 'Z') @@ -79,6 +106,10 @@ return c; } +/** + * If c is a Unicode lower case character, return the upper case + * equivalent, otherwise return c. + */ dchar toUniUpper(dchar c) { if (c >= 'a' && c <= 'z') @@ -143,7 +174,7 @@ /******************************* - * Return !=0 if unicode alpha. + * Return !=0 if u is a Unicode alpha character. */ int isUniAlpha(dchar u) diff -uNr gdc-0.17/d/phobos/std/uri.d gdc-0.18/d/phobos/std/uri.d --- gdc-0.17/d/phobos/std/uri.d 2005-04-28 23:12:43.000000000 +0200 +++ gdc-0.18/d/phobos/std/uri.d 2006-04-16 17:13:30.000000000 +0200 @@ -1,5 +1,5 @@ /* - * Copyright (C) 2004-2005 by Digital Mars, www.digitalmars.com + * Copyright (C) 2004-2006 by Digital Mars, www.digitalmars.com * Written by Walter Bright * * This software is provided 'as-is', without any express or implied @@ -21,6 +21,21 @@ * distribution. */ +/************************* + * Encode and decode Uniform Resource Identifiers (URIs). + * URIs are used in internet transfer protocols. + * Valid URI characters consist of letters, digits, + * and the characters $(B ;/?:@&=+$,-_.!~*'()) + * Reserved URI characters are $(B ;/?:@&=+$,) + * Escape sequences consist of $(B %) followed by two hex digits. + * + * See_Also: + * $(LINK2 http://www.ietf.org/rfc/rfc3986.txt, RFC 3986)
    + * $(LINK2 http://en.wikipedia.org/wiki/Uniform_resource_identifier, Wikipedia) + * Macros: + * WIKI = Phobos/StdUri + */ + module std.uri; //debug=uri; // uncomment to turn on debugging printf's @@ -30,6 +45,7 @@ private import std.ctype; private import std.c.stdlib; private import std.utf; +private import std.stdio; class URIerror : Error { @@ -104,9 +120,13 @@ { char* R2; Rsize *= 2; - R2 = cast(char *)alloca(Rsize * char.sizeof); - if (!R2) - goto LthrowURIerror; + if (Rsize > 1024) + R2 = new char[Rsize]; + else + { R2 = cast(char *)alloca(Rsize * char.sizeof); + if (!R2) + goto LthrowURIerror; + } R2[0..Rlen] = R[0..Rlen]; R = R2; } @@ -175,9 +195,13 @@ { char *R2; Rsize = 2 * (Rlen + L * 3); - R2 = cast(char *)alloca(Rsize * char.sizeof); - if (!R2) - goto LthrowURIerror; + if (Rsize > 1024) + R2 = new char[Rsize]; + else + { R2 = cast(char *)alloca(Rsize * char.sizeof); + if (!R2) + goto LthrowURIerror; + } R2[0..Rlen] = R[0..Rlen]; R = R2; } @@ -229,9 +253,13 @@ // Preallocate result buffer R guaranteed to be large enough for result Rsize = len; - R = cast(dchar *)alloca(Rsize * dchar.sizeof); - if (!R) - goto LthrowURIerror; + if (Rsize > 1024 / dchar.sizeof) + R = new dchar[Rsize]; + else + { R = cast(dchar *)alloca(Rsize * dchar.sizeof); + if (!R) + goto LthrowURIerror; + } Rlen = 0; for (k = 0; k != len; k++) @@ -319,6 +347,12 @@ return null; } +/************************************* + * Decodes the URI string encodedURI into a UTF-8 string and returns it. + * Escape sequences that resolve to reserved URI characters are not replaced. + * Escape sequences that resolve to the '#' character are not replaced. + */ + char[] decode(char[] encodedURI) { dchar[] s; @@ -327,6 +361,11 @@ return std.utf.toUTF8(s); } +/******************************* + * Decodes the URI string encodedURI into a UTF-8 string and returns it. All + * escape sequences are decoded. + */ + char[] decodeComponent(char[] encodedURIComponent) { dchar[] s; @@ -335,6 +374,11 @@ return std.utf.toUTF8(s); } +/***************************** + * Encodes the UTF-8 string uri into a URI and returns that URI. Any character + * not a valid URI character is escaped. The '#' character is not escaped. + */ + char[] encode(char[] uri) { dchar[] s; @@ -343,6 +387,11 @@ return URI_Encode(s, URI_Reserved | URI_Hash | URI_Alpha | URI_Digit | URI_Mark); } +/******************************** + * Encodes the UTF-8 string uriComponent into a URI and returns that URI. + * Any character not a letter, digit, or one of -_.!~*'() is escaped. + */ + char[] encodeComponent(char[] uriComponent) { dchar[] s; @@ -360,10 +409,10 @@ char[] r; r = encode(s); - //printf("r = '%.*s'\n", r); + debug(uri) printf("r = '%.*s'\n", r); assert(r == t); r = decode(t); - //printf("r = '%.*s'\n", r); + debug(uri) printf("r = '%.*s'\n", r); assert(r == s); r = encode( decode("%E3%81%82%E3%81%82") ); @@ -372,4 +421,14 @@ r = encodeComponent("c++"); //printf("r = '%.*s'\n", r); assert(r == "c%2B%2B"); + + // char[] str = new char[10_000_000]; // Belongs in testgc.d? 8-\ + char[] str = new char[10_000]; + str[] = 'A'; + r = encodeComponent(str); + foreach (char c; r) + assert(c == 'A'); + + r = decode("%41%42%43"); + debug(uri) writefln(r); } diff -uNr gdc-0.17/d/phobos/std/utf.d gdc-0.18/d/phobos/std/utf.d --- gdc-0.17/d/phobos/std/utf.d 2005-11-28 05:17:52.000000000 +0100 +++ gdc-0.18/d/phobos/std/utf.d 2006-04-16 17:13:30.000000000 +0200 @@ -36,6 +36,8 @@ * $(LINK2 http://en.wikipedia.org/wiki/Unicode, Wikipedia)
    * $(LINK http://www.cl.cam.ac.uk/~mgk25/unicode.html#utf-8)
    * $(LINK http://anubis.dkuug.dk/JTC1/SC2/WG2/docs/n1335) + * Macros: + * WIKI = Phobos/StdUtf */ module std.utf; @@ -80,7 +82,7 @@ * Returns: true if it is, false if not. */ -bit isValidDchar(dchar c) +bool isValidDchar(dchar c) { /* Note: FFFE and FFFF are specifically permitted by the * Unicode standard for application internal use, but are not diff -uNr gdc-0.17/d/phobos/std/windows/charset.d gdc-0.18/d/phobos/std/windows/charset.d --- gdc-0.17/d/phobos/std/windows/charset.d 2005-11-28 05:17:52.000000000 +0100 +++ gdc-0.18/d/phobos/std/windows/charset.d 2006-04-16 17:13:30.000000000 +0200 @@ -2,6 +2,8 @@ /** * Support UTF-8 on Windows 95, 98 and ME systems. + * Macros: + * WIKI = Phobos/StdWindowsCharset */ module std.windows.charset; @@ -83,7 +85,7 @@ * 0 - ANSI, * 1 - OEM, * 2 - Mac - * Authors: Steward Gordon, Walter Bright + * Authors: Stewart Gordon, Walter Bright */ char[] fromMBSz(char* s, int codePage = 0) diff -uNr gdc-0.17/d/phobos/std/windows/registry.d gdc-0.18/d/phobos/std/windows/registry.d --- gdc-0.17/d/phobos/std/windows/registry.d 2004-10-26 02:41:27.000000000 +0200 +++ gdc-0.18/d/phobos/std/windows/registry.d 2006-05-26 02:06:43.000000000 +0200 @@ -8,7 +8,7 @@ * * Author: Matthew Wilson * - * License: (Licensed under the Synesis Software Standard Source License) + * License: * * Copyright (C) 2002-2004, Synesis Software Pty Ltd. * @@ -20,25 +20,19 @@ * email: submissions@synsoft.org for submissions * admin@synsoft.org for other enquiries * - * Redistribution and use in source and binary forms, with or - * without modification, are permitted provided that the following - * conditions are met: - * - * (i) Redistributions of source code must retain the above - * copyright notice and contact information, this list of - * conditions and the following disclaimer. - * - * (ii) Any derived versions of this software (howsoever modified) - * remain the sole property of Synesis Software. - * - * (iii) Any derived versions of this software (howsoever modified) - * remain subject to all these conditions. - * - * (iv) Neither the name of Synesis Software nor the names of any - * subdivisions, employees or agents of Synesis Software, nor the - * names of any other contributors to this software may be used to - * endorse or promote products derived from this software without - * specific prior written permission. + * Permission is granted to anyone to use this software for any purpose, + * including commercial applications, and to alter it and redistribute it + * freely, in both source and binary form, subject to the following + * restrictions: + * + * - The origin of this software must not be misrepresented; you must not + * claim that you wrote the original software. If you use this software + * in a product, an acknowledgment in the product documentation would be + * appreciated but is not required. + * - Altered source versions must be plainly marked as such, and must not + * be misrepresented as being the original software. + * - This notice may not be removed or altered from any source + * distribution. * * This source code is provided by Synesis Software "as is" and any * warranties, whether expressed or implied, including, but not diff -uNr gdc-0.17/d/phobos/std/windows/syserror.d gdc-0.18/d/phobos/std/windows/syserror.d --- gdc-0.17/d/phobos/std/windows/syserror.d 2005-04-28 23:12:43.000000000 +0200 +++ gdc-0.18/d/phobos/std/windows/syserror.d 2006-03-12 15:56:29.000000000 +0100 @@ -5,6 +5,7 @@ module std.windows.syserror; +private import std.windows.charset; private import std.c.windows.windows; char[] sysErrorString(uint errcode) @@ -27,7 +28,16 @@ /* Remove \r\n from error string */ if (r >= 2) r -= 2; - result = buffer[0..r].dup; + + /* Create 0 terminated copy on GC heap because fromMBSz() + * may return it. + */ + result = new char[r + 1]; + result[0 .. r] = buffer[0 .. r]; + result[r] = 0; + + result = std.windows.charset.fromMBSz(result.ptr); + LocalFree(cast(HLOCAL)buffer); return result; } diff -uNr gdc-0.17/d/phobos/std/zip.d gdc-0.18/d/phobos/std/zip.d --- gdc-0.17/d/phobos/std/zip.d 2005-10-24 23:48:04.000000000 +0200 +++ gdc-0.18/d/phobos/std/zip.d 2006-04-16 17:13:30.000000000 +0200 @@ -12,7 +12,7 @@ * ) * * Macros: - * WIKI = StdZip + * WIKI = Phobos/StdZip */ module std.zip; diff -uNr gdc-0.17/d/phobos/std/zlib.d gdc-0.18/d/phobos/std/zlib.d --- gdc-0.17/d/phobos/std/zlib.d 2005-10-24 23:48:04.000000000 +0200 +++ gdc-0.18/d/phobos/std/zlib.d 2006-04-16 17:13:30.000000000 +0200 @@ -5,7 +5,7 @@ * $(LINK2 http://en.wikipedia.org/wiki/Zlib, Wikipedia) * * Macros: - * WIKI = StdZlib + * WIKI = Phobos/StdZlib */ diff -uNr gdc-0.17/d/phobos/std.ddoc gdc-0.18/d/phobos/std.ddoc --- gdc-0.17/d/phobos/std.ddoc 2005-11-28 05:17:52.000000000 +0100 +++ gdc-0.18/d/phobos/std.ddoc 2006-05-18 02:05:55.000000000 +0200 @@ -52,6 +52,7 @@  std.boxer
     std.compiler
     std.conv
    std.cover
     std.ctype
     std.date
     std.demangle
    @@ -67,7 +68,6 @@  std.path
     std.process
     std.random
    std.recls
     std.regexp
     std.socket
     std.socketstream
    @@ -78,19 +78,27 @@  std.string
     std.system
     std.thread
    std.uni
     std.uri
     std.utf
     std.zip
     std.zlib
    std.c.fenv
    std.c.math
    std.c.process
    std.c.stdarg
    std.c.stddef
    std.c.stdio
    std.c.stdlib
    std.c.string
    std.c.time
    std.c.wcharh
     std.windows.charset

    std.windows

    std.linux

    -std.c
    std.c.stdio
    -
    std.c.windows

    std.c.linux
    @@ -119,7 +127,7 @@ /**/google_ad_width = 728; /**/google_ad_height = 90; /**/google_ad_format = "728x90_as"; -/**/google_ad_channel =""; +/**/google_ad_channel ="6203743411"; /**/google_page_url = document.location; //-->