changeset 414:ac1fcc138e42

Fixed issue with internal real representation, incorrect for non x86-32 architectures. Cleaned up CallExp::toElem, moved implementation to tocall.cpp providing a single procedure to call arbitrary D functions fairly easily.
author Tomas Lindquist Olsen <tomas.l.olsen@gmail.com>
date Mon, 28 Jul 2008 02:11:34 +0200
parents 1a9bdbd4ac60
children 76bf1eaaf4dc
files dmd/mars.h gen/classes.cpp gen/llvmhelpers.h gen/tocall.cpp gen/toir.cpp gen/tollvm.cpp gen/tollvm.h
diffstat 7 files changed, 394 insertions(+), 394 deletions(-) [+]
line wrap: on
line diff
--- a/dmd/mars.h	Sun Jul 27 18:52:40 2008 +0200
+++ b/dmd/mars.h	Mon Jul 28 02:11:34 2008 +0200
@@ -213,8 +213,14 @@
 #include "d-gcc-real.h"
 #else
 typedef long double real_t;
+// this should be enough
+#if defined(i386) || defined(__i386__) || defined(_WIN32) || defined(__MINGW32__)
 #define REAL_T_SIZE 12
 #define REAL_T_PAD 2
+#else
+#define REAL_T_SIZE sizeof(real_t)
+#define REAL_T_PAD 0
+#endif
 #endif
 
 // Modify OutBuffer::writewchar to write the correct size of wchar
--- a/gen/classes.cpp	Sun Jul 27 18:52:40 2008 +0200
+++ b/gen/classes.cpp	Mon Jul 28 02:11:34 2008 +0200
@@ -791,20 +791,22 @@
     LLValue* mem;
     if (newexp->onstack)
     {
-        mem = new llvm::AllocaInst(DtoType(tc)->getContainedType(0), "newclass_alloca", gIR->topallocapoint());
+        mem = new llvm::AllocaInst(DtoType(tc)->getContainedType(0), ".newclass_alloca", gIR->topallocapoint());
     }
     // custom allocator
     else if (newexp->allocator)
     {
-        DValue* res = DtoCallDFunc(newexp->allocator, newexp->newargs);
-        mem = DtoBitCast(res->getRVal(), DtoType(tc), "newclass_custom");
+        DtoForceDeclareDsymbol(newexp->allocator);
+        DFuncValue dfn(newexp->allocator, newexp->allocator->ir.irFunc->func);
+        DValue* res = DtoCallFunction(NULL, &dfn, newexp->newargs);
+        mem = DtoBitCast(res->getRVal(), DtoType(tc), ".newclass_custom");
     }
     // default allocator
     else
     {
         llvm::Function* fn = LLVM_D_GetRuntimeFunction(gIR->module, "_d_newclass");
-        mem = gIR->CreateCallOrInvoke(fn, tc->sym->ir.irStruct->classInfo, "newclass_gc_alloc")->get();
-        mem = DtoBitCast(mem, DtoType(tc), "newclass_gc");
+        mem = gIR->CreateCallOrInvoke(fn, tc->sym->ir.irStruct->classInfo, ".newclass_gc_alloc")->get();
+        mem = DtoBitCast(mem, DtoType(tc), ".newclass_gc");
     }
 
     // init
@@ -848,7 +850,9 @@
     if (newexp->member)
     {
         assert(newexp->arguments != NULL);
-        return DtoCallDFunc(newexp->member, newexp->arguments, tc, mem);
+        DtoForceDeclareDsymbol(newexp->member);
+        DFuncValue dfn(newexp->member, newexp->member->ir.irFunc->func, mem);
+        return DtoCallFunction(tc, &dfn, newexp->arguments);
     }
 
     // return default constructed class
--- a/gen/llvmhelpers.h	Sun Jul 27 18:52:40 2008 +0200
+++ b/gen/llvmhelpers.h	Mon Jul 28 02:11:34 2008 +0200
@@ -91,17 +91,32 @@
 // target stuff
 void findDefaultTarget();
 
-/**
- * Calls a D function (with D calling conv).
- * @param fdecl The FuncDeclaration to call
- * @param arguments The Array of ExpressionS to pass as arguments.
- * @param type Optionally the TypeClass of the 'this' arguement.
- * @param thismem Optionally the LLValue for the 'this' argument.
- * @return The function call's return value.
- */
-DValue* DtoCallDFunc(FuncDeclaration* fdecl, Array* arguments, TypeClass* type=0, LLValue* thismem=0);
-
 /// Converts any value to a boolean (llvm i1)
 LLValue* DtoBoolean(Loc& loc, DValue* dval);
 
+////////////////////////////////////////////
+// gen/tocall.cpp stuff below
+////////////////////////////////////////////
+
+/// convert DMD calling conv to LLVM
+unsigned DtoCallingConv(LINK l);
+
+///
+TypeFunction* DtoTypeFunction(Type* type);
+
+///
+DValue* DtoVaArg(Loc& loc, Type* type, Expression* valistArg);
+
+///
+LLValue* DtoCallableValue(DValue* fn);
+
+///
+const LLFunctionType* DtoExtractFunctionType(const LLType* type);
+
+///
+void DtoBuildDVarArgList(std::vector<LLValue*>& args, llvm::PAListPtr& palist, TypeFunction* tf, Expressions* arguments, size_t argidx);
+
+///
+DValue* DtoCallFunction(Type* resulttype, DValue* fnval, Expressions* arguments);
+
 #endif
--- a/gen/tocall.cpp	Sun Jul 27 18:52:40 2008 +0200
+++ b/gen/tocall.cpp	Mon Jul 28 02:11:34 2008 +0200
@@ -13,49 +13,340 @@
 
 //////////////////////////////////////////////////////////////////////////////////////////
 
-DValue* DtoCallDFunc(FuncDeclaration* fdecl, Array* arguments, TypeClass* type, LLValue* thismem)
+TypeFunction* DtoTypeFunction(Type* type)
+{
+    TypeFunction* tf = 0;
+    type = type->toBasetype();
+    if (type->ty == Tfunction)
+    {
+         tf = (TypeFunction*)type;
+    }
+    else if (type->ty == Tdelegate)
+    {
+        assert(type->next->ty == Tfunction);
+        tf = (TypeFunction*)type->next;
+    }
+    return tf;
+}
+
+//////////////////////////////////////////////////////////////////////////////////////////
+
+unsigned DtoCallingConv(LINK l)
 {
-    Logger::println("Calling function: %s", fdecl->toPrettyChars());
-    LOG_SCOPE;
+    if (l == LINKc || l == LINKcpp)
+        return llvm::CallingConv::C;
+    else if (l == LINKd || l == LINKdefault)
+        return llvm::CallingConv::Fast;
+    else if (l == LINKwindows)
+        return llvm::CallingConv::X86_StdCall;
+    else
+        assert(0 && "Unsupported calling convention");
+}
+
+//////////////////////////////////////////////////////////////////////////////////////////
+
+DValue* DtoVaArg(Loc& loc, Type* type, Expression* valistArg)
+{
+    DValue* expelem = valistArg->toElem(gIR);
+    const LLType* llt = DtoType(type);
+    if (DtoIsPassedByRef(type))
+        llt = getPtrToType(llt);
+    // issue a warning for broken va_arg instruction.
+    if (global.params.cpu != ARCHx86)
+        warning("%s: va_arg for C variadic functions is probably broken for anything but x86", loc.toChars());
+    // done
+    return new DImValue(type, gIR->ir->CreateVAArg(expelem->getLVal(), llt, "tmp"));
+}
+
+//////////////////////////////////////////////////////////////////////////////////////////
 
-    assert(fdecl);
-    DtoForceDeclareDsymbol(fdecl);
-    llvm::Function* fn = fdecl->ir.irFunc->func;
-    TypeFunction* tf = (TypeFunction*)DtoDType(fdecl->type);
+LLValue* DtoCallableValue(DValue* fn)
+{
+    Type* type = fn->getType()->toBasetype();
+    if (type->ty == Tfunction)
+    {
+        return fn->getRVal();
+    }
+    else if (type->ty == Tdelegate)
+    {
+        LLValue* dg = fn->getRVal();
+        LLValue* funcptr = DtoGEPi(dg, 0, 1);
+        return DtoLoad(funcptr);
+    }
+    else
+    {
+        assert(0 && "not a callable type");
+        return NULL;
+    }
+}
+
+//////////////////////////////////////////////////////////////////////////////////////////
+
+const LLFunctionType* DtoExtractFunctionType(const LLType* type)
+{
+    if (const LLFunctionType* fty = isaFunction(type))
+        return fty;
+    else if (const LLPointerType* pty = isaPointer(type))
+    {
+        if (const LLFunctionType* fty = isaFunction(pty->getElementType()))
+            return fty;
+    }
+    return NULL;
+}
+
+//////////////////////////////////////////////////////////////////////////////////////////
+
+void DtoBuildDVarArgList(std::vector<LLValue*>& args, llvm::PAListPtr& palist, TypeFunction* tf, Expressions* arguments, size_t argidx)
+{
+    Logger::println("doing d-style variadic arguments");
+
+    std::vector<const LLType*> vtypes;
 
-    llvm::PAListPtr palist;
+    // number of non variadic args
+    int begin = tf->parameters->dim;
+    Logger::println("num non vararg params = %d", begin);
+
+    // build struct with argument types (non variadic args)
+    for (int i=begin; i<arguments->dim; i++)
+    {
+        Expression* argexp = (Expression*)arguments->data[i];
+        vtypes.push_back(DtoType(argexp->type));
+        size_t sz = getABITypeSize(vtypes.back());
+        if (sz < PTRSIZE)
+            vtypes.back() = DtoSize_t();
+    }
+    const LLStructType* vtype = LLStructType::get(vtypes);
+    Logger::cout() << "d-variadic argument struct type:\n" << *vtype << '\n';
+    LLValue* mem = new llvm::AllocaInst(vtype,"_argptr_storage",gIR->topallocapoint());
 
-    int thisOffset = 0;
-    if (type || thismem)
+    // store arguments in the struct
+    for (int i=begin,k=0; i<arguments->dim; i++,k++)
     {
-        assert(type && thismem);
-        thisOffset = 1;
+        Expression* argexp = (Expression*)arguments->data[i];
+        if (global.params.llvmAnnotate)
+            DtoAnnotation(argexp->toChars());
+        LLValue* argdst = DtoGEPi(mem,0,k);
+        argdst = DtoBitCast(argdst, getPtrToType(DtoType(argexp->type)));
+        DtoVariadicArgument(argexp, argdst);
+    }
+
+    // build type info array
+    assert(Type::typeinfo->ir.irStruct->constInit);
+    const LLType* typeinfotype = DtoType(Type::typeinfo->type);
+    const LLArrayType* typeinfoarraytype = LLArrayType::get(typeinfotype,vtype->getNumElements());
+
+    llvm::GlobalVariable* typeinfomem =
+        new llvm::GlobalVariable(typeinfoarraytype, true, llvm::GlobalValue::InternalLinkage, NULL, "._arguments.storage", gIR->module);
+    Logger::cout() << "_arguments storage: " << *typeinfomem << '\n';
+
+    std::vector<LLConstant*> vtypeinfos;
+    for (int i=begin,k=0; i<arguments->dim; i++,k++)
+    {
+        Expression* argexp = (Expression*)arguments->data[i];
+        vtypeinfos.push_back(DtoTypeInfoOf(argexp->type));
     }
 
-    std::vector<LLValue*> args;
-    if (thisOffset)
-        args.push_back(thismem);
-    for (size_t i=0; i<arguments->dim; ++i)
+    // apply initializer
+    LLConstant* tiinits = llvm::ConstantArray::get(typeinfoarraytype, vtypeinfos);
+    typeinfomem->setInitializer(tiinits);
+
+    // put data in d-array
+    std::vector<LLConstant*> pinits;
+    pinits.push_back(DtoConstSize_t(vtype->getNumElements()));
+    pinits.push_back(llvm::ConstantExpr::getBitCast(typeinfomem, getPtrToType(typeinfotype)));
+    const LLType* tiarrty = DtoType(Type::typeinfo->type->arrayOf());
+    tiinits = llvm::ConstantStruct::get(pinits);
+    LLValue* typeinfoarrayparam = new llvm::GlobalVariable(tiarrty,
+        true, llvm::GlobalValue::InternalLinkage, tiinits, "._arguments.array", gIR->module);
+
+    // specify arguments
+    args.push_back(typeinfoarrayparam);
+    ++argidx;
+    args.push_back(gIR->ir->CreateBitCast(mem, getPtrToType(LLType::Int8Ty), "tmp"));
+    ++argidx;
+
+    // pass non variadic args
+    for (int i=0; i<begin; i++)
     {
-        Expression* ex = (Expression*)arguments->data[i];
         Argument* fnarg = Argument::getNth(tf->parameters, i);
-        DValue* argval = DtoArgument(fnarg, ex);
-        LLValue* a = argval->getRVal();
-        const LLType* aty = fn->getFunctionType()->getParamType(i+thisOffset);
-        if (a->getType() != aty)
-        {
-            Logger::cout() << "expected: " << *aty << '\n';
-            Logger::cout() << "got:      " << *a->getType() << '\n';
-            a = DtoBitCast(a, aty);
-        }
-        args.push_back(a);
-        if (fnarg && fnarg->llvmByVal)
-            palist = palist.addAttr(i+thisOffset+1, llvm::ParamAttr::ByVal); // return,this,args...
+        DValue* argval = DtoArgument(fnarg, (Expression*)arguments->data[i]);
+        args.push_back(argval->getRVal());
+
+        if (fnarg->llvmByVal)
+            palist = palist.addAttr(argidx, llvm::ParamAttr::ByVal);
+
+        ++argidx;
+    }
+}
+
+
+DValue* DtoCallFunction(Type* resulttype, DValue* fnval, Expressions* arguments)
+{
+    // the callee D type
+    Type* calleeType = fnval->getType();
+
+    // get func value if any
+    DFuncValue* dfnval = fnval->isFunc();
+
+    // handle special va_copy / va_end intrinsics
+    bool va_intrinsic = (dfnval && dfnval->func && (dfnval->func->llvmInternal == LLVMva_intrinsic));
+
+    // get function type info
+    TypeFunction* tf = DtoTypeFunction(calleeType);
+    assert(tf);
+
+    // misc
+    bool retinptr = tf->llvmRetInPtr;
+    bool usesthis = tf->llvmUsesThis;
+    bool delegatecall = (calleeType->toBasetype()->ty == Tdelegate);
+    bool nestedcall = (dfnval && dfnval->func && dfnval->func->isNested());
+    bool dvarargs = (tf->linkage == LINKd && tf->varargs == 1);
+
+    unsigned callconv = DtoCallingConv(tf->linkage);
+
+    // get callee llvm value
+    LLValue* callable = DtoCallableValue(fnval);
+    const LLFunctionType* callableTy = DtoExtractFunctionType(callable->getType());
+    assert(callableTy);
+
+    // get llvm argument iterator, for types
+    LLFunctionType::param_iterator argbegin = callableTy->param_begin();
+    LLFunctionType::param_iterator argiter = argbegin;
+
+    // handle implicit arguments
+    std::vector<LLValue*> args;
+
+    // return in hidden ptr is first
+    if (retinptr)
+    {
+        LLValue* retvar = new llvm::AllocaInst(argiter->get()->getContainedType(0), ".rettmp", gIR->topallocapoint());
+        ++argiter;
+        args.push_back(retvar);
     }
 
-    CallOrInvoke* call = gIR->CreateCallOrInvoke(fn, args.begin(), args.end(), "tmp");
-    call->setCallingConv(DtoCallingConv(LINKd));
+    // then comes the 'this' argument
+    if (dfnval && dfnval->vthis)
+    {
+        LLValue* thisarg = DtoBitCast(dfnval->vthis, argiter->get());
+        ++argiter;
+        args.push_back(thisarg);
+    }
+    // or a delegate context arg
+    else if (delegatecall)
+    {
+        LLValue* ctxarg = DtoLoad(DtoGEPi(fnval->getRVal(), 0,0));
+        assert(ctxarg->getType() == argiter->get());
+        ++argiter;
+        args.push_back(ctxarg);
+    }
+    // or a nested function context arg
+    else if (nestedcall)
+    {
+        LLValue* contextptr = DtoNestedContext(dfnval->func->toParent2()->isFuncDeclaration());
+        if (!contextptr)
+            contextptr = getNullPtr(getVoidPtrType());
+        else
+            contextptr = DtoBitCast(contextptr, getVoidPtrType());
+        ++argiter;
+        args.push_back(contextptr);
+    }
+
+    // handle the rest of the arguments based on param passing style
+    llvm::PAListPtr palist;
+
+    // variadic instrinsics need some custom casts
+    if (va_intrinsic)
+    {
+        size_t n = arguments->dim;
+        for (int i=0; i<n; i++)
+        {
+            Expression* exp = (Expression*)arguments->data[i];
+            DValue* expelem = exp->toElem(gIR);
+            // cast to va_list*
+            LLValue* val = DtoBitCast(expelem->getLVal(), getVoidPtrType());
+            ++argiter;
+            args.push_back(val);
+        }
+    }
+
+    // d style varargs needs a few more hidden arguments as well as special passing
+    else if (dvarargs)
+    {
+        DtoBuildDVarArgList(args, palist, tf, arguments, argiter-argbegin+1);
+    }
+
+    // otherwise we're looking at a normal function call
+    else
+    {
+        Logger::println("doing normal arguments");
+        for (int i=0; i<arguments->dim; i++) {
+            int j = argiter-argbegin;
+            Argument* fnarg = Argument::getNth(tf->parameters, i);
+            DValue* argval = DtoArgument(fnarg, (Expression*)arguments->data[i]);
+            LLValue* arg = argval->getRVal();
+            if (fnarg && arg->getType() != callableTy->getParamType(j))
+                arg = DtoBitCast(arg, callableTy->getParamType(j));
+            if (fnarg && fnarg->llvmByVal)
+                palist = palist.addAttr(j+1, llvm::ParamAttr::ByVal);
+            ++argiter;
+            args.push_back(arg);
+        }
+    }
+
+    #if 0
+    Logger::println("%d params passed", n);
+    for (int i=0; i<args.size(); ++i) {
+        assert(args[i]);
+        Logger::cout() << "arg["<<i<<"] = " << *args[i] << '\n';
+    }
+    #endif
+
+    // void returns cannot not be named
+    const char* varname = "";
+    if (callableTy->getReturnType() != LLType::VoidTy)
+        varname = "tmp";
+
+    //Logger::cout() << "Calling: " << *funcval << '\n';
+
+    // call the function
+    CallOrInvoke* call = gIR->CreateCallOrInvoke(callable, args.begin(), args.end(), varname);
+
+    // get return value
+    LLValue* retllval = (retinptr) ? args[0] : call->get();
+
+    // if the type of retllval is abstract, refine to concrete
+    if (retllval->getType()->isAbstract())
+        retllval = DtoBitCast(retllval, getPtrToType(DtoType(resulttype)), "retval");
+
+    // set calling convention
+    if (dfnval && dfnval->func)
+    {
+        int li = dfnval->func->llvmInternal;
+        if (li != LLVMintrinsic && li != LLVMva_start && li != LLVMva_intrinsic)
+        {
+            call->setCallingConv(callconv);
+        }
+    }
+    else
+    {
+        call->setCallingConv(callconv);
+    }
+
+    // param attrs
     call->setParamAttrs(palist);
 
-    return new DImValue(type, call->get(), false);
+    return new DImValue(resulttype, retllval, false);
 }
+
+
+
+
+
+
+
+
+
+
+
+
+
--- a/gen/toir.cpp	Sun Jul 27 18:52:40 2008 +0200
+++ b/gen/toir.cpp	Mon Jul 28 02:11:34 2008 +0200
@@ -851,353 +851,42 @@
 
 //////////////////////////////////////////////////////////////////////////////////////////
 
-// TODO: the method below could really use a cleanup/splitup
-
 DValue* CallExp::toElem(IRState* p)
 {
     Logger::print("CallExp::toElem: %s | %s\n", toChars(), type->toChars());
     LOG_SCOPE;
 
-    DValue* fn = e1->toElem(p);
-
-    TypeFunction* tf = 0;
-    Type* e1type = DtoDType(e1->type);
-
-    bool delegateCall = false;
-    LINK dlink = LINKd;
-
-    // hidden struct return parameter handling
-    bool retinptr = false;
-
-    // regular functions
-    if (e1type->ty == Tfunction) {
-        tf = (TypeFunction*)e1type;
-        if (tf->llvmRetInPtr) {
-            retinptr = true;
-        }
-        dlink = tf->linkage;
-    }
-
-    // delegates
-    else if (e1type->ty == Tdelegate) {
-        Logger::println("delegateTy = %s\n", e1type->toChars());
-        assert(e1type->next->ty == Tfunction);
-        tf = (TypeFunction*)e1type->next;
-        if (tf->llvmRetInPtr) {
-            retinptr = true;
-        }
-        dlink = tf->linkage;
-        delegateCall = true;
-    }
-
-    // invalid
-    else {
-        assert(tf);
-    }
-
-    // handling of special intrinsics
-    bool va_magic = false;
+    // get the callee value
+    DValue* fnval = e1->toElem(p);
+
+    // get func value if any
+    DFuncValue* dfnval = fnval->isFunc();
+
+    // handle magic intrinsics (mapping to instructions)
     bool va_intrinsic = false;
-    DFuncValue* dfv = fn->isFunc();
-    if (dfv && dfv->func) {
-        FuncDeclaration* fndecl = dfv->func;
-        // vararg intrinsic
-        if (fndecl->llvmInternal == LLVMva_intrinsic) {
-            va_magic = true;
-            va_intrinsic = true;
-        }
+    if (dfnval && dfnval->func)
+    {
+        FuncDeclaration* fndecl = dfnval->func;
         // va_start instruction
-        else if (fndecl->llvmInternal == LLVMva_start) {
-            va_magic = true;
+        if (fndecl->llvmInternal == LLVMva_start) {
+            // TODO
+            assert(0 && "va_start not yet implemented");
         }
         // va_arg instruction
         else if (fndecl->llvmInternal == LLVMva_arg) {
-            //Argument* fnarg = Argument::getNth(tf->parameters, 0);
-            Expression* exp = (Expression*)arguments->data[0];
-            DValue* expelem = exp->toElem(p);
-            Type* t = DtoDType(type);
-            const LLType* llt = DtoType(type);
-            if (DtoIsPassedByRef(t))
-                llt = getPtrToType(llt);
-            // TODO
-            // issue a warning for broken va_arg instruction.
-            if (strcmp(global.params.llvmArch, "x86") != 0) {
-                warning("%s: va_arg for C variadic functions is probably broken for anything but x86", loc.toChars());
-            }
-            // done
-            return new DImValue(type, p->ir->CreateVAArg(expelem->getLVal(),llt,"tmp"));
+            return DtoVaArg(loc, type, (Expression*)arguments->data[0]);
         }
-        // alloca
+        // C alloca
         else if (fndecl->llvmInternal == LLVMalloca) {
-            //Argument* fnarg = Argument::getNth(tf->parameters, 0);
             Expression* exp = (Expression*)arguments->data[0];
             DValue* expv = exp->toElem(p);
             if (expv->getType()->toBasetype()->ty != Tint32)
                 expv = DtoCast(loc, expv, Type::tint32);
-            LLValue* alloc = new llvm::AllocaInst(LLType::Int8Ty, expv->getRVal(), "alloca", p->scopebb());
-            // done
-            return new DImValue(type, alloc);
-        }
-    }
-
-    // args
-    size_t n = arguments->dim;
-    DFuncValue* dfn = fn->isFunc();
-    if (dfn && dfn->func && dfn->func->llvmInternal == LLVMva_start)
-        n = 1;
-    if (delegateCall || (dfn && dfn->vthis)) n++;
-    if (retinptr) n++;
-    if (tf->linkage == LINKd && tf->varargs == 1) n+=2;
-    if (dfn && dfn->func && dfn->func->isNested()) n++;
-
-    LLValue* funcval = fn->getRVal();
-    assert(funcval != 0);
-    std::vector<LLValue*> llargs(n, 0);
-
-    const LLFunctionType* llfnty = 0;
-
-    // TODO: review the stuff below, using the llvm type to choose seem like a bad idea. the D type should be used.
-    //
-    // normal function call
-    if (llvm::isa<LLFunctionType>(funcval->getType())) {
-        llfnty = llvm::cast<LLFunctionType>(funcval->getType());
-    }
-    // pointer to something
-    else if (isaPointer(funcval->getType())) {
-        // pointer to function pointer - I think this not really supposed to happen, but does :/
-        // seems like sometimes we get a func* other times a func**
-        if (isaPointer(funcval->getType()->getContainedType(0))) {
-            funcval = DtoLoad(funcval);
-        }
-        // function pointer
-        if (llvm::isa<LLFunctionType>(funcval->getType()->getContainedType(0))) {
-            //Logger::cout() << "function pointer type:\n" << *funcval << '\n';
-            llfnty = llvm::cast<LLFunctionType>(funcval->getType()->getContainedType(0));
-        }
-        // struct pointer - delegate
-        else if (isaStruct(funcval->getType()->getContainedType(0))) {
-            funcval = DtoGEPi(funcval,0,1);
-            funcval = DtoLoad(funcval);
-            const LLType* ty = funcval->getType()->getContainedType(0);
-            llfnty = llvm::cast<LLFunctionType>(ty);
-        }
-        // unknown
-        else {
-            Logger::cout() << "what kind of pointer are we calling? : " << *funcval->getType() << '\n';
-        }
-    }
-    else {
-        Logger::cout() << "what are we calling? : " << *funcval << '\n';
-    }
-    assert(llfnty);
-    //Logger::cout() << "Function LLVM type: " << *llfnty << '\n';
-
-    // argument handling
-    LLFunctionType::param_iterator argiter = llfnty->param_begin();
-    int j = 0;
-
-    // attrs
-    llvm::PAListPtr palist;
-
-    // hidden struct return arguments
-    // TODO: use sret param attr
-    if (retinptr) {
-        llargs[j] = new llvm::AllocaInst(argiter->get()->getContainedType(0),"rettmp",p->topallocapoint());
-        ++j;
-        ++argiter;
-    }
-
-    // this arguments
-    if (dfn && dfn->vthis) {
-        Logger::cout() << "This Call" << '\n';// func val:" << *funcval << '\n';
-        if (dfn->vthis->getType() != argiter->get()) {
-            //Logger::cout() << "value: " << *dfn->vthis << " totype: " << *argiter->get() << '\n';
-            llargs[j] = DtoBitCast(dfn->vthis, argiter->get());
-        }
-        else {
-            llargs[j] = dfn->vthis;
-        }
-        ++j;
-        ++argiter;
-    }
-    // delegate context arguments
-    else if (delegateCall) {
-        Logger::println("Delegate Call");
-        LLValue* contextptr = DtoGEPi(fn->getRVal(),0,0);
-        llargs[j] = DtoLoad(contextptr);
-        ++j;
-        ++argiter;
-    }
-    // nested call
-    else if (dfn && dfn->func && dfn->func->isNested()) {
-        Logger::println("Nested Call");
-        LLValue* contextptr = DtoNestedContext(dfn->func->toParent2()->isFuncDeclaration());
-        if (!contextptr)
-            contextptr = llvm::ConstantPointerNull::get(getPtrToType(LLType::Int8Ty));
-        llargs[j] = DtoBitCast(contextptr, getPtrToType(LLType::Int8Ty));
-        ++j;
-        ++argiter;
-    }
-
-    // va arg function special argument passing
-    if (va_magic)
-    {
-        size_t n = va_intrinsic ? arguments->dim : 1;
-        for (int i=0; i<n; i++,j++)
-        {
-            Argument* fnarg = Argument::getNth(tf->parameters, i);
-            Expression* exp = (Expression*)arguments->data[i];
-            DValue* expelem = exp->toElem(p);
-            llargs[j] = DtoBitCast(expelem->getLVal(), getPtrToType(LLType::Int8Ty));
+            return new DImValue(type, gIR->ir->CreateAlloca(LLType::Int8Ty, expv->getRVal(), ".alloca"));
         }
     }
-    // d variadic function
-    else if (tf->linkage == LINKd && tf->varargs == 1)
-    {
-        Logger::println("doing d-style variadic arguments");
-
-        size_t nimplicit = j;
-
-        std::vector<const LLType*> vtypes;
-
-        // number of non variadic args
-        int begin = tf->parameters->dim;
-        Logger::println("num non vararg params = %d", begin);
-
-        // build struct with argument types
-        for (int i=begin; i<arguments->dim; i++)
-        {
-            Argument* argu = Argument::getNth(tf->parameters, i);
-            Expression* argexp = (Expression*)arguments->data[i];
-            vtypes.push_back(DtoType(argexp->type));
-            size_t sz = getABITypeSize(vtypes.back());
-            if (sz < PTRSIZE)
-                vtypes.back() = DtoSize_t();
-        }
-        const LLStructType* vtype = LLStructType::get(vtypes);
-        Logger::cout() << "d-variadic argument struct type:\n" << *vtype << '\n';
-        LLValue* mem = new llvm::AllocaInst(vtype,"_argptr_storage",p->topallocapoint());
-
-        // store arguments in the struct
-        for (int i=begin,k=0; i<arguments->dim; i++,k++)
-        {
-            Expression* argexp = (Expression*)arguments->data[i];
-            if (global.params.llvmAnnotate)
-                DtoAnnotation(argexp->toChars());
-            LLValue* argdst = DtoGEPi(mem,0,k);
-            argdst = DtoBitCast(argdst, getPtrToType(DtoType(argexp->type)));
-            DtoVariadicArgument(argexp, argdst);
-        }
-
-        // build type info array
-        assert(Type::typeinfo->ir.irStruct->constInit);
-        const LLType* typeinfotype = DtoType(Type::typeinfo->type);
-        const LLArrayType* typeinfoarraytype = LLArrayType::get(typeinfotype,vtype->getNumElements());
-
-        llvm::GlobalVariable* typeinfomem =
-            new llvm::GlobalVariable(typeinfoarraytype, true, llvm::GlobalValue::InternalLinkage, NULL, "._arguments.storage", gIR->module);
-        Logger::cout() << "_arguments storage: " << *typeinfomem << '\n';
-
-        std::vector<LLConstant*> vtypeinfos;
-        for (int i=begin,k=0; i<arguments->dim; i++,k++)
-        {
-            Expression* argexp = (Expression*)arguments->data[i];
-            vtypeinfos.push_back(DtoTypeInfoOf(argexp->type));
-        }
-
-        // apply initializer
-        LLConstant* tiinits = llvm::ConstantArray::get(typeinfoarraytype, vtypeinfos);
-        typeinfomem->setInitializer(tiinits);
-
-        // put data in d-array
-        std::vector<LLConstant*> pinits;
-        pinits.push_back(DtoConstSize_t(vtype->getNumElements()));
-        pinits.push_back(llvm::ConstantExpr::getBitCast(typeinfomem, getPtrToType(typeinfotype)));
-        const LLType* tiarrty = llfnty->getParamType(j)->getContainedType(0);
-        tiinits = llvm::ConstantStruct::get(pinits);
-        LLValue* typeinfoarrayparam = new llvm::GlobalVariable(tiarrty,
-            true, llvm::GlobalValue::InternalLinkage, tiinits, "._arguments.array", gIR->module);
-
-        // specify arguments
-        llargs[j] = typeinfoarrayparam;;
-        j++;
-        llargs[j] = p->ir->CreateBitCast(mem, getPtrToType(LLType::Int8Ty), "tmp");
-        j++;
-
-        // pass non variadic args
-        for (int i=0; i<begin; i++)
-        {
-            Argument* fnarg = Argument::getNth(tf->parameters, i);
-            DValue* argval = DtoArgument(fnarg, (Expression*)arguments->data[i]);
-            llargs[j] = argval->getRVal();
-
-            if (fnarg->llvmByVal)
-                palist = palist.addAttr(j, llvm::ParamAttr::ByVal);
-
-            j++;
-        }
-
-        // make sure arg vector has the right size
-        llargs.resize(nimplicit+begin+2);
-    }
-    // normal function call
-    else
-    {
-        Logger::println("doing normal arguments");
-        for (int i=0; i<arguments->dim; i++,j++) {
-            Argument* fnarg = Argument::getNth(tf->parameters, i);
-            if (global.params.llvmAnnotate)
-                DtoAnnotation(((Expression*)arguments->data[i])->toChars());
-            DValue* argval = DtoArgument(fnarg, (Expression*)arguments->data[i]);
-            llargs[j] = argval->getRVal();
-            if (fnarg && llargs[j]->getType() != llfnty->getParamType(j)) {
-                llargs[j] = DtoBitCast(llargs[j], llfnty->getParamType(j));
-            }
-
-            if (fnarg && fnarg->llvmByVal)
-                palist = palist.addAttr(j+1, llvm::ParamAttr::ByVal);
-        }
-    }
-
-    #if 0
-    Logger::println("%d params passed", n);
-    for (int i=0; i<llargs.size(); ++i) {
-        assert(llargs[i]);
-        Logger::cout() << "arg["<<i<<"] = " << *llargs[i] << '\n';
-    }
-    #endif
-
-    // void returns cannot not be named
-    const char* varname = "";
-    if (llfnty->getReturnType() != LLType::VoidTy)
-        varname = "tmp";
-
-    //Logger::cout() << "Calling: " << *funcval << '\n';
-
-    // call the function
-    CallOrInvoke* call = gIR->CreateCallOrInvoke(funcval, llargs.begin(), llargs.end(), varname);
-
-    LLValue* retllval = (retinptr) ? llargs[0] : call->get();
-
-    // if the type of retllval is abstract, refine to concrete
-    if(retllval->getType()->isAbstract())
-        retllval = DtoBitCast(retllval, getPtrToType(DtoType(type)), "retval");
-
-    // set calling convention
-    if (dfn && dfn->func) {
-        int li = dfn->func->llvmInternal;
-        if (li != LLVMintrinsic && li != LLVMva_start && li != LLVMva_intrinsic) {
-            call->setCallingConv(DtoCallingConv(dlink));
-        }
-    }
-    else {
-        call->setCallingConv(DtoCallingConv(dlink));
-    }
-
-    // param attrs
-    call->setParamAttrs(palist);
-
-    return new DImValue(type, retllval, false);
+
+    return DtoCallFunction(type, fnval, arguments);
 }
 
 //////////////////////////////////////////////////////////////////////////////////////////
--- a/gen/tollvm.cpp	Sun Jul 27 18:52:40 2008 +0200
+++ b/gen/tollvm.cpp	Mon Jul 28 02:11:34 2008 +0200
@@ -283,20 +283,6 @@
 
 //////////////////////////////////////////////////////////////////////////////////////////
 
-unsigned DtoCallingConv(LINK l)
-{
-    if (l == LINKc || l == LINKcpp)
-        return llvm::CallingConv::C;
-    else if (l == LINKd || l == LINKdefault)
-        return llvm::CallingConv::Fast;
-    else if (l == LINKwindows)
-        return llvm::CallingConv::X86_StdCall;
-    else
-        assert(0 && "Unsupported calling convention");
-}
-
-//////////////////////////////////////////////////////////////////////////////////////////
-
 LLValue* DtoPointedType(LLValue* ptr, LLValue* val)
 {
     const LLType* ptrTy = ptr->getType()->getContainedType(0);
@@ -596,6 +582,16 @@
     return llvm::dyn_cast<LLStructType>(t);
 }
 
+const LLFunctionType* isaFunction(LLValue* v)
+{
+    return llvm::dyn_cast<LLFunctionType>(v->getType());
+}
+
+const LLFunctionType* isaFunction(const LLType* t)
+{
+    return llvm::dyn_cast<LLFunctionType>(t);
+}
+
 LLConstant* isaConstant(LLValue* v)
 {
     return llvm::dyn_cast<llvm::Constant>(v);
--- a/gen/tollvm.h	Sun Jul 27 18:52:40 2008 +0200
+++ b/gen/tollvm.h	Mon Jul 28 02:11:34 2008 +0200
@@ -34,9 +34,6 @@
 LLGlobalValue::LinkageTypes DtoInternalLinkage(Dsymbol* sym);
 LLGlobalValue::LinkageTypes DtoExternalLinkage(Dsymbol* sym);
 
-// convert DMD calling conv to LLVM
-unsigned DtoCallingConv(LINK l);
-
 // TODO: this one should be removed!!!
 LLValue* DtoPointedType(LLValue* ptr, LLValue* val);
 
@@ -77,6 +74,8 @@
 const LLArrayType* isaArray(const LLType* t);
 const LLStructType* isaStruct(LLValue* v);
 const LLStructType* isaStruct(const LLType* t);
+const LLFunctionType* isaFunction(LLValue* v);
+const LLFunctionType* isaFunction(const LLType* t);
 LLConstant* isaConstant(LLValue* v);
 LLConstantInt* isaConstantInt(LLValue* v);
 llvm::Argument* isaArgument(LLValue* v);