Compiling more functions that don't call MainEvaluate

Use pure functions (Function) and "InlineExternalDefinitions" -> True:

g = #^2 &;
f = # + 1 &;

compiledFunction = 
  Compile[{{x, _Real, 0}}, f@g[x], 
   CompilationOptions -> {"InlineExternalDefinitions" -> True}];

CompilePrint[compiledFunction]


        1 argument
        1 Integer register
        4 Real registers
        Underflow checking off
        Overflow checking off
        Integer overflow checking on
        RuntimeAttributes -> {}

        R0 = A1
        I0 = 1
        Result = R3

1   R1 = R0
2   R2 = Square[ R1]
3   R1 = I0
4   R3 = R2 + R1
5   Return

If f and g are compiled functions themselves, use the "InlineCompiledFunctions" -> True option as well.

As Leonid mentions below, the reason why Set or SetDelayed definitions won't be inlined is that they might contain complex patterns (including patterns with conditions) and thus depend on the type of data passed to them.


Yes there is a way to use functions that use external non compiled functions.

It uses the step function of Mr.Wizard defined in the post How do I evaluate only one step of an expression?, in order to recursively expand the code that we want to compile until it uses only functions that Mathematica can compile. The technique discussed in the post How to inject an evaluated expression into a held expression? is also used.

The function ExpandCode needs two functions that tell it when a function should be expanded and when a function should be evaluated during the expansion.

Using the functions defined below we can do to solve the question

code = Hold[F[G[x]]]
codeExpand = ExpandCode[code]
compiledFunction2 = Function[codeExpanded, Compile[{{x, _Real}}, codeExpanded], HoldFirst] @@ codeExpand

The $CriteriaFunction used here is that a function name (symbol) should have upper case letters only. Note the use of pure function with HoldFirst attribute in order to avoid evaluation leaks.

And now the function compiledFunction2 doesn't call MainEvaluate and returns the right answer

compiledFunction2 // FastCompiledFunctionQ
compiledFunction2[2]

A more streamlined version of this for common cases using a function defined below

CompileExpand[{{x, _Real}}, F[G[x]]] // FastCompiledFunctionQ

Here's the main code and some advice are after it.

SetAttributes[STEP, {Flat, OneIdentity, HoldFirst}];
STEP[expr_] :=
    Module[{P},
        P = (P = Return[# (*/. HoldForm[x_] :> Defer[STEP[x]]*), TraceScan] &) &;
        TraceScan[P, expr, TraceDepth -> 1] 
    ];

ReleaseAllHold[expr_,firstLevel_:0,lastLevel_:Infinity] := Replace[expr, (Hold|HoldForm|HoldPattern|HoldComplete)[e___] :> e, {firstLevel, lastLevel}, Heads -> True];

SetAttributes[EVALUATE,HoldFirst];
EVALUATE[x_]:=x;

$CriteriaFunction =Function[symbol,UpperCaseQ@SymbolName@symbol,HoldFirst];
$FullEvalFunction=Function[symbol,symbol===EVALUATE,HoldFirst];

ExpandCode[code_]:=ReleaseAllHold[Quiet@ExpandCodeAux[code,$CriteriaFunction ,$FullEvalFunction], 1];

ExpandCodeAux[code_,criteria_,fullEval_]:=
    code /.
    (expr:(x_Symbol[___]) /; criteria@x :>
        RuleCondition[
            If[fullEval@x,
                expr
                ,
                With[{oneStep = HoldForm@Evaluate@STEP@expr},
                    If[oneStep===HoldForm@expr,
                        oneStep
                        ,
                        ExpandCodeAux[oneStep,criteria,fullEval]
                    ]
                ]
            ]
        ]
    );

SetAttributes[CompileExpand,HoldAll];   
CompileExpand[variables_,code_,otherVariables___]:=
    Function[
        codeExpanded
        ,
        Compile[variables,codeExpanded,otherVariables]
        ,
        HoldFirst
    ] @@ ExpandCode[Hold@code];

FastCompiledFunctionQ[function_CompiledFunction]:=
(
    Needs["CompiledFunctionTools`"];
    StringFreeQ[CompiledFunctionTools`CompilePrint@function,"MainEvaluate"]
)

(*Example*)
SetAttributes[{F,G},HoldAll];
F[x_] := G[x] + 2;
G[x_] := 3 x;
compiledFunction3=CompileExpand[{{x,_Real}},F[G[x]]+EVALUATE@Range@5,CompilationTarget->"WVM"]
compiledFunction3//FastCompiledFunctionQ
compiledFunction3[2]

Comments

  • You need to specify the type of the variables even if they are Real numbers (for example {{x,_Real}} and not x for a function of just one variable).
  • Works with any type of values : DownValues, UpValues, SubValues ... which means you can use auxiliary functions that use the pattern matcher in their definitions instead of just already compiled functions that sometimes don't mix well together, and still be able to compile without calls to MainEvaluate.
  • A function to be expanded can contain calls to other functions that will be expanded.
  • In order to avoid problems the functions that you want to expand should have a HoldAll attribute (SetAttributes[F,HoldAll] for example).
  • Some useful Compile arguments for speed {Parallelization->True,RuntimeAttributes->{Listable},CompilationTarget->"WVM",RuntimeOptions->"Speed",CompilationOptions->{"ExpressionOptimization"->True,"InlineCompiledFunctions"->True,"InlineExternalDefinitions"->True}
  • If you call many times a same relatively big function (for example an interpolation function that you have written), it can be best to use a CompiledFunctionCall as explained in this answer in order to avoid an exploding code size after code expansion.
  • It can be best to avoid "ExpressionOptimization" when the CompilationTarget target is "WVM" (the compilation is faster, especially as the size of the expanded code can be very big). When it's "C" it's better to optimize the expression.
  • Numeric functions don't have a HoldAll attribute and pose problems if you want to expand a function that is inside a numeric one. You can use InheritedBlock to circumvent this. For example

    blockedFunctions={Abs,Log,Power,Plus,Minus,Times,Max,UnitStep,Exp};
    
    With[{blockedFunctions=blockedFunctions},
        Internal`InheritedBlock[blockedFunctions,
            SetAttributes[#,HoldAll]&/@blockedFunctions;            
            ExpandCode[....]
        ]
    ]
    
  • If you use constant strings in your code you can replace them inside the code expanded with Real numbers (in order to return them together with a Real result in a List which will compile correctly, as you can't mix types in the result of a compiled function). For example

    Module[{cacheString,stringIndex=0.,codeExpandWithStringsReplaced},
       c:cacheString[s_] := c = ++stringIndex;      
       codeExpandWithStringsReplaced=codeExpand/.s_String:>RuleCondition[cacheString[s]];
       ...  
    ]
    

    And then cacheString can be used to convert the results returned by the compiled function back into strings. You need to access the keys and the values of cacheString, see here, or you can use and manipulate an Association in V10 instead of a symbol for cacheString.

  • A simple way to fully evaluate an expression during the code expansion is to enclose the expression between an EVALUATE function equal to the identity function.

    SetAttributes[EVALUATE,HoldFirst];
    EVALUATE[x_]:=x;
    $FullEvalFunction = Function[symbol,symbol===EVALUATE,HoldFirst];
    

    for example

    EVALUATE[Range@5]  
    

    EVALUATE also lets you avoid using With in order to insert constant parameters into the compiled code.

  • This code expansion can be used in order to have a fast compiled DSL (Domain Specific Language).

  • If you modify the $CriteriaFunction you can use Apply. This is an easier way to use Apply with Compile than in this question: Using Apply inside Compile.

    $CriteriaFunction=Function[symbol,UpperCaseQ@SymbolName@symbol||symbol===Apply,HoldFirst];  
    
    f=Compile[{{x,_Real}},F@@{x}]  
    f // FastCompiledFunctionQ (*False*)
    
    f=CompileExpand[{{x,_Real}},F@@{x}]  
    f // FastCompiledFunctionQ (*True*)  
    

    You can also use this syntax instead of redefining $CriteriaFunction.

    f = CompileExpand[{{x, _Real}}, STEP[F @@ {x}]] 
    f // FastCompiledFunctionQ (*True*)  
    

Your situation can be solved by Evaluate.

According to the documentation of Compile

You can use Compile[...,Evaluate[expr]] to specify that expr should be evaluated symbolically before compilation.

F[x_] := x + 2;
G[x_] := x;

ff = Compile[{x}, Evaluate@F[G[x]]];

<<CompiledFunctionTools`
CompilePrint@ff

result

        1 argument
        1 Integer register
        2 Real registers
        Underflow checking off
        Overflow checking off
        Integer overflow checking on
        RuntimeAttributes -> {}

        R0 = A1
        I0 = 2
        Result = R1

1   R1 = I0
2   R1 = R1 + R0
3   Return

Update

But the above only works when Evaluate is directly in the Compile, since Evaluate only works on the first level. For example, below code will call MainEvaluate

ff = Compile[{x}, x^2;Evaluate@F[G[x]]];

jkuczm provide a method which can conveniently deal with such situation, no matter the location of Evaluate. Many times it is very useful. I copy the method here.

we should define

ClearAll[deepEvaluate]
SetAttributes[deepEvaluate, HoldFirst]
deepEvaluate[expr_] := 
   Unevaluated[expr] /. HoldPattern[Evaluate][subExpr_] :> RuleCondition[subExpr]

Then

ff = Compile[{x}, x^2;Evaluate@F[G[x]]]//deepEvaluate;

Now ff//CompilePrint is free from MainEvaluate

        1 argument
        1 Integer register
        3 Real registers
        Underflow checking off
        Overflow checking off
        Integer overflow checking on
        RuntimeAttributes -> {}

        R0 = A1
        I0 = 2
        Result = R2

1   R1 = Square[ R0]
2   R2 = I0
3   R2 = R2 + R0
4   Return