To replace each splat node with a sequence of pure Inter nodes having the same meaning, thus purging the tree of all raw I6 syntax entirely.


§1. Basic idea. Assimilation is a multi-stage process, but really this stage is the heart of it. We expect that resolve-conditional-compilation has already run, so that the splats in the tree represent directives which all have definite effect. With the conditional compilation splats gone, we are left with these:

ARRAY_I6DIR         ATTRIBUTE_I6DIR     CONSTANT_I6DIR      DEFAULT_I6DIR
FAKEACTION_I6DIR    GLOBAL_I6DIR        OBJECT_I6DIR        PROPERTY_I6DIR
ROUTINE_I6DIR       STUB_I6DIR          VERB_I6DIR

And we must turn those into splatless Inter code with the same effect. In some cases, notably ROUTINE_I6DIR which contains an entire Inform 6-notation function definition, that is quite a lot of work.

void CompileSplatsStage::create_pipeline_stage(void) {
    ParsingPipelines::new_stage(I"compile-splats", CompileSplatsStage::run, NO_STAGE_ARG, FALSE);
}

§2. We divide the task up into three traverses:

int CompileSplatsStage::run(pipeline_step *step) {
    compile_splats_state css;
    Initialise the CS state2.2;
    inter_tree *I = step->ephemera.tree;
    InterTree::traverse(I, CompileSplatsStage::visitor1, &css, NULL, SPLAT_IST);
    InterTree::traverse(I, CompileSplatsStage::visitor2, &css, NULL, 0);
    int errors_found = CompileSplatsStage::function_bodies(step, &css, I);
    if (errors_found) return FALSE;
    InterTree::traverse(I, CompileSplatsStage::visitor3, &css, NULL, SPLAT_IST);
    return TRUE;
}

§2.1. During this process, the following state is shared across all three traverses:

typedef struct compile_splats_state {
    struct pipeline_step *from_step;
    int no_assimilated_actions;
    int no_assimilated_directives;
    struct linked_list *function_bodies_to_compile;  of function_body_request
} compile_splats_state;

§2.2. Initialise the CS state2.2 =

    css.from_step = step;
    css.no_assimilated_actions = 0;
    css.no_assimilated_directives = 0;
    css.function_bodies_to_compile = NEW_LINKED_LIST(function_body_request);

§3. The three traverse functions share a great deal of their code, in fact. Note that we set the assimilation package to be the module containing whatever splat is being compiled.

void CompileSplatsStage::visitor1(inter_tree *I, inter_tree_node *P, void *state) {
    compile_splats_state *css = (compile_splats_state *) state;
    pipeline_step *step = css->from_step;
    if (P->W.instruction[ID_IFLD] == PACKAGE_IST) {
        inter_package *pack = PackageInstruction::at_this_head(P);
        inter_symbol *ptype = InterPackage::type(pack);
        if (Str::eq(InterSymbol::identifier(ptype), I"_module"))
            step->pipeline->ephemera.assimilation_modules[step->tree_argument] = pack;
    }
    if (P->W.instruction[ID_IFLD] == SPLAT_IST) {
        inter_ti directive = P->W.instruction[PLM_SPLAT_IFLD];
        switch (directive) {
            case PROPERTY_I6DIR:
            case ATTRIBUTE_I6DIR:
                Assimilate definition3.1;
                break;
            case ROUTINE_I6DIR:
            case STUB_I6DIR:
                Assimilate routine3.2;
                break;
        }
    }
}

void CompileSplatsStage::visitor2(inter_tree *I, inter_tree_node *P, void *state) {
    compile_splats_state *css = (compile_splats_state *) state;
    pipeline_step *step = css->from_step;
    if (P->W.instruction[ID_IFLD] == PACKAGE_IST) {
        inter_package *pack = PackageInstruction::at_this_head(P);
        inter_symbol *ptype = InterPackage::type(pack);
        if (Str::eq(InterSymbol::identifier(ptype), I"_module"))
            step->pipeline->ephemera.assimilation_modules[step->tree_argument] = pack;
    }
    if (P->W.instruction[ID_IFLD] == SPLAT_IST) {
        inter_ti directive = P->W.instruction[PLM_SPLAT_IFLD];
        switch (directive) {
            case ARRAY_I6DIR:
            case DEFAULT_I6DIR:
            case CONSTANT_I6DIR:
            case FAKEACTION_I6DIR:
            case OBJECT_I6DIR:
            case VERB_I6DIR:
                Assimilate definition3.1;
                break;
        }
    }
}

void CompileSplatsStage::visitor3(inter_tree *I, inter_tree_node *P, void *state) {
    compile_splats_state *css = (compile_splats_state *) state;
    pipeline_step *step = css->from_step;
    if (P->W.instruction[ID_IFLD] == PACKAGE_IST) {
        inter_package *pack = PackageInstruction::at_this_head(P);
        inter_symbol *ptype = InterPackage::type(pack);
        if (Str::eq(InterSymbol::identifier(ptype), I"_module"))
            step->pipeline->ephemera.assimilation_modules[step->tree_argument] = pack;
    }
    if (P->W.instruction[ID_IFLD] == SPLAT_IST) {
        inter_ti directive = P->W.instruction[PLM_SPLAT_IFLD];
        switch (directive) {
            case GLOBAL_I6DIR:
                Assimilate definition3.1;
                break;
        }
    }
}

§3.1. How definitions are assimilated. Assimilate definition3.1 =

    match_results mr = Regexp::create_mr();
    text_stream *identifier = NULL, *value = NULL;
    int proceed = TRUE;
    Parse text of splat for identifier and value3.1.1;
    if (proceed) {
        Insert sharps in front of fake action identifiers3.1.2;
        Perhaps compile something from this splat3.1.3;
        NodePlacement::remove(P);
    }
    Regexp::dispose_of(&mr);

§3.1.1. This code is used for a range of different Inform 6 syntaxes which create something with a given identifier name, and sometimes supply a value. For example,

    Constant Italian_Meringue_Temperature = 121;
    Fake_Action Bake;
    Attribute split;
    Object Compass "compass";

The following finds the identifier as the second token, i.e., after the directive keyword Constant or similar. Note that an Object declaration does not meaningfully have a value, even though a third token is present.

Parse text of splat for identifier and value3.1.1 =

    text_stream *S = Inode::ID_to_text(P, P->W.instruction[MATTER_SPLAT_IFLD]);
    if (directive == VERB_I6DIR) {
        if (Regexp::match(&mr, S, L" *%C+ (%c*?) *;%c*")) {
            identifier = I"assim_gv"; value = mr.exp[0];
        } else {
            LOG("Unable to parse start of VERB_I6DIR: '%S'\n", S); proceed = FALSE;
        }
    } else {
        if (Regexp::match(&mr, S, L" *%C+ *(%C+?)(--> *%c*?) *;%c*")) {
            identifier = mr.exp[0]; value = mr.exp[1];
        } else if (Regexp::match(&mr, S, L" *%C+ *(%C+?)(-> *%c*?) *;%c*")) {
            identifier = mr.exp[0]; value = mr.exp[1];
        } else if (Regexp::match(&mr, S, L" *%C+ (%C*?) *;%c*")) {
            identifier = mr.exp[0];
        } else if (Regexp::match(&mr, S, L" *%C+ (%C*) *= *(%c*?) *;%c*")) {
            identifier = mr.exp[0]; value = mr.exp[1];
        } else if (Regexp::match(&mr, S, L" *%C+ (%C*) (%c*?) *;%c*")) {
            identifier = mr.exp[0]; value = mr.exp[1];
        } else {
            LOG("Unable to parse start of constant: '%S'\n", S); proceed = FALSE;
        }
        if (directive == OBJECT_I6DIR) value = NULL;
    }
    Str::trim_all_white_space_at_end(identifier);

§3.1.2. An eccentricity of Inform 6 syntax is that fake action names ought to be given in the form Fake_Action ##Bake, but are not. The constant created by Fake_Action Bake is nevertheless ##Bake, so we take care of that here.

Insert sharps in front of fake action identifiers3.1.2 =

    if (directive == FAKEACTION_I6DIR) {
        text_stream *old = identifier;
        identifier = Str::new();
        WRITE_TO(identifier, "##%S", old);
    }

§3.1.3. The Inform 6 directive

    Default Vanilla_Pod 1;

is essentially equivalent to

    #Ifndef Vanilla_Pod;
    Constant Vanilla_Pod = 1;
    #Endif;

So this is a piece of conditional compilation in disguise, and should perhaps have been removed from the tree by the resolve-conditional-compilation stage. But in fact it's easier to handle it here.

Perhaps compile something from this splat3.1.3 =

    if (directive == DEFAULT_I6DIR) {
        if (Wiring::find_socket(I, identifier) == NULL) {
            directive = CONSTANT_I6DIR;
            Definitely compile something from this splat3.1.3.1;
        }
    } else {
        Definitely compile something from this splat3.1.3.1;
    }

§3.1.3.1. So if we're here, we have reduced the possibilities to:

ARRAY_I6DIR         ATTRIBUTE_I6DIR     CONSTANT_I6DIR      FAKEACTION_I6DIR
GLOBAL_I6DIR        OBJECT_I6DIR        PROPERTY_I6DIR      VERB_I6DIR

We basically do the same thing in all of these cases: decide where to put the result, declare a symbol for it, and then define that symbol.

Definitely compile something from this splat3.1.3.1 =

    inter_bookmark content_at;
    Work out where in the Inter tree to put the material we are making3.1.3.1.1;

    inter_symbol *made_s;
    Declare the Inter symbol for what we will shortly make3.1.3.1.2;
    if ((directive == ATTRIBUTE_I6DIR) || (directive == PROPERTY_I6DIR))
        Declare a property ID symbol to go with it3.1.3.1.3;

    Make a definition for made_s3.1.3.1.4;

§3.1.3.1.1. So, for example, Constant Vanilla_Pod = 1; might result in the symbol Vanilla_Pod being created and defined with a CONSTANT_IST Inter node, all inside the package /main/HypotheticalKit/constants/Vanilla_Pod_con.

Which frankly looks over-engineered for a simple constant, but some of these definitions are not so simple.

Work out where in the Inter tree to put the material we are making3.1.3.1.1 =

    text_stream *submodule_name = NULL;
    text_stream *suffix = NULL;
    inter_symbol *subpackage_type = NULL;
    Work out what submodule to put this new material into3.1.3.1.1.1;
    if (Str::len(submodule_name) > 0) {
        content_at = CompileSplatsStage::make_submodule(I, step, submodule_name, P);
        Create a little package within that submodule to hold the content3.1.3.1.1.2
    } else {
        content_at = InterBookmark::after_this_node(P);
    }

§3.1.3.1.1.1. Work out what submodule to put this new material into3.1.3.1.1.1 =

    switch (directive) {
        case VERB_I6DIR:
            subpackage_type = RunningPipelines::get_symbol(step, command_ptype_RPSYM);
            submodule_name = I"commands"; suffix = NULL; break;
        case ARRAY_I6DIR:
            submodule_name = I"arrays"; suffix = I"arr"; break;
        case CONSTANT_I6DIR:
        case FAKEACTION_I6DIR:
        case OBJECT_I6DIR:
            submodule_name = I"constants"; suffix = I"con"; break;
        case GLOBAL_I6DIR:
            submodule_name = I"variables"; suffix = I"var"; break;
        case ATTRIBUTE_I6DIR:
        case PROPERTY_I6DIR:
            subpackage_type = RunningPipelines::get_symbol(step, property_ptype_RPSYM);
            submodule_name = I"properties"; suffix = I"prop"; break;
    }
    if ((Str::len(submodule_name) > 0) && (subpackage_type == NULL))
        subpackage_type = RunningPipelines::get_symbol(step, plain_ptype_RPSYM);

§3.1.3.1.1.2. The practical effect of this is to create all the packages needed which are not already there.

Create a little package within that submodule to hold the content3.1.3.1.1.2 =

    TEMPORARY_TEXT(subpackage_name)
    if (suffix) {
        WRITE_TO(subpackage_name, "%S_%S", identifier, suffix);
    } else {
        WRITE_TO(subpackage_name, "assimilated_directive_%d",
            ++css->no_assimilated_directives);
    }
    inter_package *subpackage =
        Produce::make_subpackage(&content_at, subpackage_name, subpackage_type);
    InterBookmark::move_into_package(&content_at, subpackage);
    DISCARD_TEXT(subpackage_name)

§3.1.3.1.2. Now we declare made_s as a symbol inside this package.

Declare the Inter symbol for what we will shortly make3.1.3.1.2 =

    made_s = CompileSplatsStage::make_socketed_symbol(&content_at, identifier);
    if (Wiring::is_wired(made_s)) {
        inter_symbol *external_name = Wiring::wired_to(made_s);
        Wiring::wire_to(external_name, made_s);
        Wiring::wire_to(made_s, NULL);
    }
    SymbolAnnotation::set_b(made_s, ASSIMILATED_IANN, 1);
    if (directive == FAKEACTION_I6DIR) SymbolAnnotation::set_b(made_s, FAKE_ACTION_IANN, TRUE);
    if (directive == OBJECT_I6DIR) SymbolAnnotation::set_b(made_s, OBJECT_IANN, TRUE);
    if (directive == ATTRIBUTE_I6DIR) SymbolAnnotation::set_b(made_s, EITHER_OR_IANN, TRUE);
    if (directive == VERB_I6DIR) InterSymbol::set_flag(made_s, MAKE_NAME_UNIQUE_ISYMF);

§3.1.3.1.3. Declare a property ID symbol to go with it3.1.3.1.3 =

    inter_bookmark *IBM = &content_at;
    inter_symbol *id_s = CompileSplatsStage::make_socketed_symbol(IBM, I"property_id");
    InterSymbol::set_flag(id_s, MAKE_NAME_UNIQUE_ISYMF);
    Produce::guard(ConstantInstruction::new(IBM, id_s,
        InterTypes::unchecked(), InterValuePairs::number(0),
        (inter_ti) InterBookmark::baseline(IBM) + 1, NULL));

§3.1.3.1.4. Make a definition for made_s3.1.3.1.4 =

    inter_bookmark *IBM = &content_at;
    switch (directive) {
        case CONSTANT_I6DIR:
        case FAKEACTION_I6DIR:
        case OBJECT_I6DIR:
            Make a scalar constant in Inter3.1.3.1.4.1;
            break;
        case GLOBAL_I6DIR:
            Make a global variable in Inter3.1.3.1.4.2;
            break;
        case PROPERTY_I6DIR:
            Make a general property in Inter3.1.3.1.4.3;
            break;
        case ATTRIBUTE_I6DIR:
            Make an either-or property in Inter3.1.3.1.4.4;
            break;
        case VERB_I6DIR:
        case ARRAY_I6DIR:
            Make a list constant in Inter3.1.3.1.4.5;
            break;
    }

§3.1.3.1.4.1. Make a scalar constant in Inter3.1.3.1.4.1 =

    inter_ti B = (inter_ti) InterBookmark::baseline(IBM) + 1;
    inter_pair val = InterValuePairs::undef();
    Assimilate a value3.1.3.1.4.1.1;
    Produce::guard(ConstantInstruction::new(IBM, made_s,
        InterTypes::unchecked(), val, B, NULL));

§3.1.3.1.4.2. Make a global variable in Inter3.1.3.1.4.2 =

    inter_ti MID = InterSymbolsTable::id_from_symbol(I, InterBookmark::package(IBM), made_s);
    inter_ti B = (inter_ti) InterBookmark::baseline(IBM) + 1;
    inter_pair val = InterValuePairs::undef();
    Assimilate a value3.1.3.1.4.1.1;
    Produce::guard(VariableInstruction::new(IBM, MID,
        InterTypes::unchecked(), val, B, NULL));

§3.1.3.1.4.3. Make a general property in Inter3.1.3.1.4.3 =

    inter_ti MID = InterSymbolsTable::id_from_symbol(I, InterBookmark::package(IBM), made_s);
    inter_ti B = (inter_ti) InterBookmark::baseline(IBM) + 1;
    Produce::guard(PropertyInstruction::new(IBM, MID,
        InterTypes::unchecked(), B, NULL));

§3.1.3.1.4.4. Make an either-or property in Inter3.1.3.1.4.4 =

    inter_ti MID = InterSymbolsTable::id_from_symbol(I, InterBookmark::package(IBM), made_s);
    inter_ti B = (inter_ti) InterBookmark::baseline(IBM) + 1;
    Produce::guard(PropertyInstruction::new(IBM, MID,
        InterTypes::from_constructor_code(INT2_ITCONC), B, NULL));

§3.1.3.1.4.5. A typical Inform 6 array declaration looks like this:

    Array Example table 2 (-56) 17 "hey, I am typeless" ' ';
define MAX_ASSIMILATED_ARRAY_ENTRIES 10000

Make a list constant in Inter3.1.3.1.4.5 =

    match_results mr = Regexp::create_mr();
    text_stream *conts = NULL;
    inter_ti annot = INVALID_IANN;
    Work out the format of the array and the string of contents3.1.3.1.4.5.1;
    if (annot != INVALID_IANN) SymbolAnnotation::set_b(made_s, annot, TRUE);

    inter_pair val_pile[MAX_ASSIMILATED_ARRAY_ENTRIES];
    int no_assimilated_array_entries = 0;
    if (directive == ARRAY_I6DIR)
        Compile the string of array contents into the pile of values3.1.3.1.4.5.2
    else
        Compile the string of command grammar contents into the pile of values3.1.3.1.4.5.3;

    inter_ti B = (inter_ti) InterBookmark::baseline(IBM) + 1;
    Produce::guard(ConstantInstruction::new_list(IBM, made_s,
        InterTypes::from_constructor_code(LIST_ITCONC), CONST_LIST_FORMAT_COLLECTION,
        no_assimilated_array_entries, val_pile, B, NULL));
    Regexp::dispose_of(&mr);

§3.1.3.1.4.5.1. At this point value is table 2 (-56) 17 "hey, I am typeless" ' '. We want first to work out which of the several array formats this is (TABLEARRAY_IANN in this instance), then the contents 2 (-56) 17 "hey, I am typeless" ' '.

Work out the format of the array and the string of contents3.1.3.1.4.5.1 =

    if (directive == ARRAY_I6DIR) {
        if (Regexp::match(&mr, value, L" *--> *(%c*?) *")) {
            conts = mr.exp[0]; annot = INVALID_IANN;
        } else if (Regexp::match(&mr, value, L" *-> *(%c*?) *")) {
            conts = mr.exp[0]; annot = BYTEARRAY_IANN;
        } else if (Regexp::match(&mr, value, L" *table *(%c*?) *")) {
            conts = mr.exp[0]; annot = TABLEARRAY_IANN;
        } else if (Regexp::match(&mr, value, L" *buffer *(%c*?) *")) {
            conts = mr.exp[0]; annot = BUFFERARRAY_IANN;
        } else {
            LOG("Identifier = <%S>, Value = <%S>", identifier, value);
            PipelineErrors::kit_error("invalid Inform 6 array declaration", NULL);
        }
    } else {
        conts = value; annot = VERBARRAY_IANN;
    }

§3.1.3.1.4.5.2. The contents text is now tokenised, and each token produces an array entry.

Although it is legal in Inform 6 to write arrays like, say.

    Array Example --> 'a' + 2 (24);

where the entries are specified in a way using arithmetic operators, we won't support that here: the standard Inform kits do not need it, and it's hard to see why other kits would, either.

Compile the string of array contents into the pile of values3.1.3.1.4.5.2 =

    string_position spos = Str::start(conts);
    int finished = FALSE;
    while (finished == FALSE) {
        TEMPORARY_TEXT(value)
        Extract a token3.1.3.1.4.5.2.2;
        if (Str::eq(value, I"+"))
            PipelineErrors::kit_error("Inform 6 array declaration using operator '+'", NULL);
        if (Str::eq(value, I"-"))
            PipelineErrors::kit_error("Inform 6 array declaration using operator '-'", NULL);
        if (Str::eq(value, I"*"))
            PipelineErrors::kit_error("Inform 6 array declaration using operator '*'", NULL);
        if (Str::eq(value, I"/"))
            PipelineErrors::kit_error("Inform 6 array declaration using operator '/'", NULL);

        if (Str::len(value) > 0) {
            inter_pair val = InterValuePairs::undef();
            Assimilate a value3.1.3.1.4.1.1;
            Add value to the entry pile3.1.3.1.4.5.2.1;
        } else finished = TRUE;
        DISCARD_TEXT(value)
    }

§3.1.3.1.4.5.3. In command grammar introduced by Verb, the tokens * and / can occur without having any arithmetic meaning, so they must not be rejected. That's really why we treat this case as different, though we also treat keywords occurring after -> markers as being action names, and introduce ##s to their names. Thus in:

    Verb 'do' * 'something' -> Do;

the action name Do is converted automatically to ##Do, the actual identifier for the action.

Compile the string of command grammar contents into the pile of values3.1.3.1.4.5.3 =

    string_position spos = Str::start(conts);
    int NT = 0, next_is_action = FALSE, finished = FALSE;
    while (finished == FALSE) {
        TEMPORARY_TEXT(value)
        if (next_is_action) WRITE_TO(value, "##");
        Extract a token3.1.3.1.4.5.2.2;
        if (next_is_action) Ensure that a socket exists for this action name3.1.3.1.4.5.3.1;
        next_is_action = FALSE;
        if ((NT++ == 0) && (Str::eq(value, I"meta"))) {
            SymbolAnnotation::set_b(made_s, METAVERB_IANN, TRUE);
        } else if (Str::len(value) > 0) {
            inter_pair val = InterValuePairs::undef();
            Assimilate a value3.1.3.1.4.1.1;
            Add value to the entry pile3.1.3.1.4.5.2.1;
            if (Str::eq(value, I"->")) next_is_action = TRUE;
        } else finished = TRUE;
        DISCARD_TEXT(value)
    }

§3.1.3.1.4.5.3.1. So here value is something like ##ScriptOn, an action name. Maybe that has already been defined in the kit currently being compiked, in which case a socket for it already exists; but maybe not, in which case we have to create the action. This will be a package at, say, /main/HypotheticalKit/actions/assim_action_1 with three things in it:

Ensure that a socket exists for this action name3.1.3.1.4.5.3.1 =

    if (Wiring::find_socket(I, value) == NULL) {
        inter_bookmark IBM_d = CompileSplatsStage::make_submodule(I, step, I"actions", P);
        inter_bookmark *IBM = &IBM_d;

        inter_package *action_package;
        Make a package for the new action, inside the actions submodule3.1.3.1.4.5.3.1.1;
        InterBookmark::move_into_package(IBM, action_package);

        Make an action_id symbol in the action package3.1.3.1.4.5.3.1.2;
        Make the actual double-sharped action symbol3.1.3.1.4.5.3.1.3;
        Make a symbol equated to the function carrying out the action3.1.3.1.4.5.3.1.4;
    }

§3.1.3.1.4.5.3.1.1. Make a package for the new action, inside the actions submodule3.1.3.1.4.5.3.1.1 =

    inter_symbol *ptype = RunningPipelines::get_symbol(step, action_ptype_RPSYM);
    if (ptype == NULL) ptype = RunningPipelines::get_symbol(step, plain_ptype_RPSYM);
    TEMPORARY_TEXT(an)
    WRITE_TO(an, "assim_action_%d", ++css->no_assimilated_actions);
    action_package = Produce::make_subpackage(IBM, an, ptype);
    DISCARD_TEXT(an)

§3.1.3.1.4.5.3.1.2. Each action package has to contain an action_id symbol, which will eventually be defined as a unique ID for the action. But those unique IDs can only be assigned at link time — at this stage we cannot know what other actions exist in other compilation units. So we create action_id equal just to 0 for now.

Make an action_id symbol in the action package3.1.3.1.4.5.3.1.2 =

    inter_symbol *action_id_s = InterSymbolsTable::create_with_unique_name(
        InterBookmark::scope(IBM), I"action_id");
    inter_ti B = (inter_ti) InterBookmark::baseline(IBM) + 1;
    Produce::guard(ConstantInstruction::new(IBM, action_id_s,
        InterTypes::unchecked(), InterValuePairs::number(0), B, NULL));
    InterSymbol::set_flag(action_id_s, MAKE_NAME_UNIQUE_ISYMF);

§3.1.3.1.4.5.3.1.3. Make the actual double-sharped action symbol3.1.3.1.4.5.3.1.3 =

    inter_symbol *action_s = CompileSplatsStage::make_socketed_symbol(IBM, value);
    inter_ti B = (inter_ti) InterBookmark::baseline(IBM) + 1;
    Produce::guard(ConstantInstruction::new(IBM, action_s,
        InterTypes::unchecked(), InterValuePairs::number(10000), B, NULL));
    SymbolAnnotation::set_b(action_s, ACTION_IANN, 1);

§3.1.3.1.4.5.3.1.4. The Inter convention is that an action package should contain a function to carry it out; for ##ScriptOn, this would be called ScriptOnSub. In fact we don't actually define it here! We assume it has already been compiled, and that we can therefore simply create the function name ScriptOnSub here, equating it to a function definition elsewhere.

Make a symbol equated to the function carrying out the action3.1.3.1.4.5.3.1.4 =

    TEMPORARY_TEXT(fn_name)
    WRITE_TO(fn_name, "%SSub", value);
    Str::delete_first_character(fn_name);
    Str::delete_first_character(fn_name);
    inter_symbol *fn_s =
        InterSymbolsTable::create_with_unique_name(InterBookmark::scope(IBM), fn_name);
    inter_symbol *existing_fn_s = Wiring::find_socket(I, fn_name);
    if (existing_fn_s) Wiring::wire_to(fn_s, existing_fn_s);
    DISCARD_TEXT(fn_name)

§3.1.3.1.4.1.1. Assimilate a value3.1.3.1.4.1.1 =

    if (Str::len(value) > 0) {
        val = CompileSplatsStage::value(step, IBM, value,
            (directive == VERB_I6DIR)?TRUE:FALSE);
    } else {
        val = InterValuePairs::number(0);
    }

§3.1.3.1.4.5.2.1. Add value to the entry pile3.1.3.1.4.5.2.1 =

    if (no_assimilated_array_entries >= MAX_ASSIMILATED_ARRAY_ENTRIES) {
        PipelineErrors::kit_error("excessively long Verb or Extend", NULL);
        break;
    }
    val_pile[no_assimilated_array_entries] = val;
    no_assimilated_array_entries++;

§3.1.3.1.4.5.2.2. Extract a token3.1.3.1.4.5.2.2 =

    int squoted = FALSE, dquoted = FALSE, bracketed = 0;
    while ((Str::in_range(spos)) && (Characters::is_whitespace(Str::get(spos))))
        spos = Str::forward(spos);
    while (Str::in_range(spos)) {
        wchar_t c = Str::get(spos);
        if ((Characters::is_whitespace(c)) && (squoted == FALSE) &&
            (dquoted == FALSE) && (bracketed == 0)) break;
        if ((c == '\'') && (dquoted == FALSE)) squoted = (squoted)?FALSE:TRUE;
        if ((c == '\"') && (squoted == FALSE)) dquoted = (dquoted)?FALSE:TRUE;
        if ((c == '(') && (dquoted == FALSE) && (squoted == FALSE)) bracketed++;
        if ((c == ')') && (dquoted == FALSE) && (squoted == FALSE)) bracketed--;
        PUT_TO(value, c);
        spos = Str::forward(spos);
    }

§3.2. How functions are assimilated. Functions in Inform 6 are usually called "routines", and have a syntax like so:

    [ Example x y tmp;
       tmp = x*y;
       print "Product seems to be ", tmp, ".^";
    ];

We are concerned more with the surround than with the contents of the function in this section.

Assimilate routine3.2 =

    text_stream *identifier = NULL, *local_var_names = NULL, *body = NULL;
    match_results mr = Regexp::create_mr();
    if (P->W.instruction[PLM_SPLAT_IFLD] == ROUTINE_I6DIR) Parse the routine header3.2.1;
    if (P->W.instruction[PLM_SPLAT_IFLD] == STUB_I6DIR) Parse the stub directive3.2.2;
    if (identifier) {
        Turn this into a function package3.2.3;
        NodePlacement::remove(P);
    }

§3.2.1. Parse the routine header3.2.1 =

    text_stream *S = Inode::ID_to_text(P, P->W.instruction[MATTER_SPLAT_IFLD]);
    if (Regexp::match(&mr, S, L" *%[ *(%i+) *; *(%c*)")) {
        identifier = mr.exp[0]; body = mr.exp[1];
    } else if (Regexp::match(&mr, S, L" *%[ *(%i+) *(%c*?); *(%c*)")) {
        identifier = mr.exp[0]; local_var_names = mr.exp[1]; body = mr.exp[2];
    } else {
        PipelineErrors::kit_error("invalid Inform 6 routine declaration", NULL);
    }

§3.2.2. Another of Inform 6's shabby notations for conditional compilation in disguise is the Stub directive, which looks like so:

    Stub Example 2;

This means "if no Example routine exists, create one now, and give it two local variables". Such a stub routine contains no code, so it doesn't matter what these variables are called, of course. We rewrite so that it's as if the kit code had written:

    [ Example x1 x2;
        rfalse;
    ];

Note that here the compilation is unconditional. Because kits are precompiled, there's no sensible way to provide these only if they are not elsewhere provided. So this is no longer a useful directive, and it continues to be supported only to avoid throwing errors.

Parse the stub directive3.2.2 =

    text_stream *S = Inode::ID_to_text(P, P->W.instruction[MATTER_SPLAT_IFLD]);
    if (Regexp::match(&mr, S, L" *%C+ *(%i+) (%d+);%c*")) {
        identifier = mr.exp[0];
        local_var_names = Str::new();
        int N = Str::atoi(mr.exp[1], 0);
        if ((N<0) || (N>15)) N = 1;
        for (int i=1; i<=N; i++) WRITE_TO(local_var_names, "x%d ", i);
        body = Str::duplicate(I"rfalse; ];");
    } else PipelineErrors::kit_error("invalid Inform 6 Stub declaration", NULL);

§3.2.3. Function packages have a standardised shape in Inter, and though this is a matter of convention rather than a requirement, we will follow it here. So our Example function would be called at /main/HypotheticalKit/functions/Example_fn/call. The following makes two packages:

These have package types _function and _code respectively.

Turn this into a function package3.2.3 =

    inter_bookmark content_at = CompileSplatsStage::make_submodule(I, step, I"functions", P);
    inter_bookmark *IBM = &content_at;
    inter_package *OP, *IP;  outer and inner packages
    Create the outer function package3.2.3.1;
    Create an inner package for the code3.2.3.2;
    Create a symbol for calling the function3.2.3.3;

§3.2.3.1. Create the outer function package3.2.3.1 =

    inter_symbol *fnt = RunningPipelines::get_symbol(step, function_ptype_RPSYM);
    if (fnt == NULL) fnt = RunningPipelines::get_symbol(step, plain_ptype_RPSYM);
    TEMPORARY_TEXT(fname)
    WRITE_TO(fname, "%S_fn", identifier);
    OP = Produce::make_subpackage(IBM, fname, fnt);
    DISCARD_TEXT(fname)

§3.2.3.2. Create an inner package for the code3.2.3.2 =

    InterBookmark::move_into_package(IBM, OP);
    TEMPORARY_TEXT(bname)
    WRITE_TO(bname, "%S_B", identifier);
    IP = Produce::make_subpackage(IBM, bname,
        RunningPipelines::get_symbol(step, code_ptype_RPSYM));
    DISCARD_TEXT(bname)
    inter_bookmark inner_save = InterBookmark::snapshot(IBM);
    InterBookmark::move_into_package(IBM, IP);
    inter_bookmark block_bookmark = InterBookmark::snapshot(IBM);
    if (local_var_names) Create local variables within the inner package3.2.3.2.1;
    Create the outermost code block inside the inner package3.2.3.2.2;
    if (Str::len(body) > 0) Compile actual code into this code block3.2.3.2.3;
    *IBM = inner_save;

§3.2.3.2.1. Create local variables within the inner package3.2.3.2.1 =

    string_position spos = Str::start(local_var_names);
    while (TRUE) {
        TEMPORARY_TEXT(value)
        Extract a token3.1.3.1.4.5.2.2;
        if (Str::len(value) == 0) break;
        inter_symbol *loc_name =
            InterSymbolsTable::create_with_unique_name(InterPackage::scope(IP), value);
        InterSymbol::make_local(loc_name);
        inter_ti B = (inter_ti) InterBookmark::baseline(IBM) + 1;
        Produce::guard(LocalInstruction::new(IBM, loc_name, InterTypes::unchecked(), B, NULL));
        DISCARD_TEXT(value)
    }

§3.2.3.2.2. Create the outermost code block inside the inner package3.2.3.2.2 =

    Produce::guard(CodeInstruction::new(IBM,
        (int) (inter_ti) InterBookmark::baseline(IBM) + 1, NULL));

§3.2.3.2.3. Compile actual code into this code block3.2.3.2.3 =

    int L = Str::len(body) - 1;
    while ((L>0) && (Str::get_at(body, L) != ']')) L--;
    while ((L>0) && (Characters::is_whitespace(Str::get_at(body, L-1)))) L--;
    Str::truncate(body, L);
    inter_ti B = (inter_ti) InterBookmark::baseline(IBM) + 1;
    CompileSplatsStage::function_body(css, IBM, IP, B, body, block_bookmark, identifier);

§3.2.3.3. Create a symbol for calling the function3.2.3.3 =

    inter_symbol *function_name_s =
        CompileSplatsStage::make_socketed_symbol(IBM, identifier);
    SymbolAnnotation::set_b(function_name_s, ASSIMILATED_IANN, 1);
    inter_ti B = (inter_ti) InterBookmark::baseline(IBM) + 1;
    Produce::guard(ConstantInstruction::new(IBM, function_name_s,
        InterTypes::from_constructor_code(FUNCTION_ITCONC),
        InterValuePairs::functional(IP), B, NULL));

§4. Plumbing. Some convenient Inter utilities.

First, we make a symbol, and also install a socket to it. This essentially means that it will be visible to code outside of the current kit, making it a function, variable or constant which can be called or accessed from other kits or from the main program. (Compare C, where a function declared as static is visible only inside the current compilation unit; one declared without that keyword can be linked to.)

Note that if there is already a socket of the same name, we do not attempt to install another one. This will not in practice lead to problems, because the identifiers supplied to this function all come from identifiers in Inter kits, which have a single global namespace for functoons and variables anyway.

inter_symbol *CompileSplatsStage::make_socketed_symbol(inter_bookmark *IBM,
    text_stream *identifier) {
    inter_symbol *new_symbol = InterSymbolsTable::create_with_unique_name(
        InterBookmark::scope(IBM), identifier);
    if (Wiring::find_socket(InterBookmark::tree(IBM), identifier) == NULL)
        Wiring::socket(InterBookmark::tree(IBM), identifier, new_symbol);
    return new_symbol;
}

§5. Syppose we are assimilating HypotheticalKit, and we want to make sure that the package /main/HypotheticalKit/whatevers exists. Here /main/HypotheticalKit is a package of type _module, and /main/HypotheticalKit/whatevers should be a _submodule. Then we call this function, with name set to "whatevers". The return value is a bookmark to where we can write new code in the submodule.

Note that if the submodule already exists, there is nothing to create, and so we simply return a bookmark at the end of the existing submodule.

The function tries to fail safe in the remote contingency that the package type _submodule does not exist in the current tree. But if the tree has been properly initialised with the new stage, then it will. Similarly, it will fail safe if an assimilation package has not been set — but this is very unlikely to happen: see above.

inter_bookmark CompileSplatsStage::make_submodule(inter_tree *I, pipeline_step *step,
    text_stream *name, inter_tree_node *P) {
    if (RunningPipelines::get_symbol(step, submodule_ptype_RPSYM)) {
        inter_package *module_pack =
            step->pipeline->ephemera.assimilation_modules[step->tree_argument];
        if (module_pack) {
            inter_package *submodule_package = InterPackage::from_name(module_pack, name);
            if (submodule_package == NULL) {
                inter_bookmark IBM = InterBookmark::after_this_node(P);
                submodule_package = Produce::make_subpackage(&IBM, name,
                    RunningPipelines::get_symbol(step, submodule_ptype_RPSYM));
                if (submodule_package == NULL) internal_error("could not create submodule");
            }
            return InterBookmark::at_end_of_this_package(submodule_package);
        }
    }
    return InterBookmark::after_this_node(P);
}

§6. Inform 6 expressions in constant context. The following takes the text of a constant written in Inform 6 syntax, and stored in S, and compiles it to an Inter bytecode value pair. The meaning of these depends on the package they will end up living in, so that must be supplied as pack.

The flag Verbal is set if the expression came from a Verb directive, i.e., from command parser grammar: slightly different syntax applies there.

inter_pair CompileSplatsStage::value(pipeline_step *step, inter_bookmark *IBM, text_stream *S,
    int Verbal) {
    inter_tree *I = InterBookmark::tree(IBM);
    int from = 0, to = Str::len(S)-1;
    if ((Str::get_at(S, from) == '\'') && (Str::get_at(S, to) == '\'')) {
        if (to - from == 2)
            Parse this as a literal character6.1
        else if (Str::eq(S, I"'\\''"))
            Parse this as a literal single quotation mark6.2
        else
            Parse this as a single-quoted command grammar word6.3;
    }
    if ((Str::get_at(S, from) == '"') && (Str::get_at(S, to) == '"'))
        Parse this as a double-quoted string literal6.4;
    if (((Str::get_at(S, from) == '$') && (Str::get_at(S, from+1) == '+')) ||
        ((Str::get_at(S, from) == '$') && (Str::get_at(S, from+1) == '-')))
        Parse this as a real literal6.5;
    Attempt to parse this as a hex, binary or decimal literal6.6;
    Attempt to parse this as a boolean literal6.7;
    if (Verbal) Attempt to parse this as a command grammar token6.8;
    Attempt to parse this as an identifier name for something already defined by this kit6.9;
    Parse this as a possibly computed value6.10;
}

§6.1. Parse this as a literal character6.1 =

    wchar_t c = Str::get_at(S, from + 1);
    return InterValuePairs::number((inter_ti) c);

§6.2. Parse this as a literal single quotation mark6.2 =

    return InterValuePairs::number((inter_ti) '\'');

§6.3. Parse this as a single-quoted command grammar word6.3 =

    inter_ti plural = FALSE; int before_slashes = TRUE;
    TEMPORARY_TEXT(dw)
    LOOP_THROUGH_TEXT(pos, S)
        if ((pos.index > from) && (pos.index < to)) {
            if ((Str::get(pos) == '/') && (Str::get(Str::forward(pos)) == '/'))
                before_slashes = FALSE;
            if (before_slashes) {
                PUT_TO(dw, Str::get(pos));
            } else {
                if (Str::get(pos) == 'p') plural = TRUE;
            }
        }
    inter_pair val;
    if (plural) val = InterValuePairs::from_plural_dword(IBM, dw);
    else val = InterValuePairs::from_singular_dword(IBM, dw);
    DISCARD_TEXT(dw)
    return val;

§6.4. Parse this as a double-quoted string literal6.4 =

    TEMPORARY_TEXT(dw)
    LOOP_THROUGH_TEXT(pos, S)
        if ((pos.index > from) && (pos.index < to))
            PUT_TO(dw, Str::get(pos));
    inter_pair val = InterValuePairs::from_text(IBM, dw);
    DISCARD_TEXT(dw)
    return val;

§6.5. Parse this as a real literal6.5 =

    TEMPORARY_TEXT(rw)
    LOOP_THROUGH_TEXT(pos, S)
        if ((pos.index > from + 1) && (pos.index <= to))
            PUT_TO(rw, Str::get(pos));
    inter_pair val = InterValuePairs::real_from_I6_notation(IBM, rw);
    DISCARD_TEXT(rw)
    return val;

§6.6. Attempt to parse this as a hex, binary or decimal literal6.6 =

    int sign = 1, base = 10, bad = FALSE;
    if ((Str::get_at(S, from) == '(') && (Str::get_at(S, to) == ')')) { from++; to--; }
    while (Characters::is_whitespace(Str::get_at(S, from))) from++;
    while (Characters::is_whitespace(Str::get_at(S, to))) to--;
    if (Str::get_at(S, from) == '-') { sign = -1; from++; }
    else if (Str::get_at(S, from) == '$') {
        from++; base = 16;
        if (Str::get_at(S, from) == '$') {
            from++; base = 2;
        }
    }
    long long int N = 0;
    LOOP_THROUGH_TEXT(pos, S) {
        if (pos.index < from) continue;
        if (pos.index > to) continue;
        int c = Str::get(pos), d = 0;
        if ((c >= 'a') && (c <= 'z')) d = c-'a'+10;
        else if ((c >= 'A') && (c <= 'Z')) d = c-'A'+10;
        else if ((c >= '0') && (c <= '9')) d = c-'0';
        else { bad = TRUE; break; }
        if (d > base) { bad = TRUE; break; }
        N = base*N + (long long int) d;
        if (pos.index > 34) { bad = TRUE; break; }
    }
    if (bad == FALSE) {
        N = sign*N;
        return InterValuePairs::number((inter_ti) N);
    }

§6.7. Attempt to parse this as a boolean literal6.7 =

    if (Str::eq(S, I"true"))  return InterValuePairs::number(1);
    if (Str::eq(S, I"false")) return InterValuePairs::number(0);

§6.8. Attempt to parse this as a command grammar token6.8 =

    if (Str::eq(S, I"*"))
        return InterValuePairs::symbolic(IBM, RunningPipelines::ensure_symbol(step,
            verb_directive_divider_RPSYM, I"VERB_DIRECTIVE_DIVIDER"));
    if (Str::eq(S, I"->"))
        return InterValuePairs::symbolic(IBM, RunningPipelines::ensure_symbol(step,
            verb_directive_result_RPSYM, I"VERB_DIRECTIVE_RESULT"));
    if (Str::eq(S, I"reverse"))
        return InterValuePairs::symbolic(IBM, RunningPipelines::ensure_symbol(step,
            verb_directive_reverse_RPSYM, I"VERB_DIRECTIVE_REVERSE"));
    if (Str::eq(S, I"/"))
        return InterValuePairs::symbolic(IBM, RunningPipelines::ensure_symbol(step,
            verb_directive_slash_RPSYM, I"VERB_DIRECTIVE_SLASH"));
    if (Str::eq(S, I"special"))
        return InterValuePairs::symbolic(IBM, RunningPipelines::ensure_symbol(step,
            verb_directive_special_RPSYM, I"VERB_DIRECTIVE_SPECIAL"));
    if (Str::eq(S, I"number"))
        return InterValuePairs::symbolic(IBM, RunningPipelines::ensure_symbol(step,
            verb_directive_number_RPSYM, I"VERB_DIRECTIVE_NUMBER"));
    if (Str::eq(S, I"noun"))
        return InterValuePairs::symbolic(IBM, RunningPipelines::ensure_symbol(step,
            verb_directive_noun_RPSYM, I"VERB_DIRECTIVE_NOUN"));
    if (Str::eq(S, I"multi"))
        return InterValuePairs::symbolic(IBM, RunningPipelines::ensure_symbol(step,
            verb_directive_multi_RPSYM, I"VERB_DIRECTIVE_MULTI"));
    if (Str::eq(S, I"multiinside"))
        return InterValuePairs::symbolic(IBM, RunningPipelines::ensure_symbol(step,
            verb_directive_multiinside_RPSYM, I"VERB_DIRECTIVE_MULTIINSIDE"));
    if (Str::eq(S, I"multiheld"))
        return InterValuePairs::symbolic(IBM, RunningPipelines::ensure_symbol(step,
            verb_directive_multiheld_RPSYM, I"VERB_DIRECTIVE_MULTIHELD"));
    if (Str::eq(S, I"held"))
        return InterValuePairs::symbolic(IBM, RunningPipelines::ensure_symbol(step,
            verb_directive_held_RPSYM, I"VERB_DIRECTIVE_HELD"));
    if (Str::eq(S, I"creature"))
        return InterValuePairs::symbolic(IBM, RunningPipelines::ensure_symbol(step,
            verb_directive_creature_RPSYM, I"VERB_DIRECTIVE_CREATURE"));
    if (Str::eq(S, I"topic"))
        return InterValuePairs::symbolic(IBM, RunningPipelines::ensure_symbol(step,
            verb_directive_topic_RPSYM, I"VERB_DIRECTIVE_TOPIC"));
    if (Str::eq(S, I"multiexcept"))
        return InterValuePairs::symbolic(IBM, RunningPipelines::ensure_symbol(step,
            verb_directive_multiexcept_RPSYM, I"VERB_DIRECTIVE_MULTIEXCEPT"));
    match_results mr = Regexp::create_mr();
    if (Regexp::match(&mr, S, L"scope=(%i+)")) {
        inter_symbol *symb = Wiring::cable_end(Wiring::find_socket(I, mr.exp[0]));
        if (symb) {
            if (SymbolAnnotation::get_b(symb, SCOPE_FILTER_IANN) == FALSE)
                SymbolAnnotation::set_b(symb, SCOPE_FILTER_IANN, TRUE);
            return InterValuePairs::symbolic(IBM, symb);
        }
    }
    if (Regexp::match(&mr, S, L"noun=(%i+)")) {
        inter_symbol *symb = Wiring::cable_end(Wiring::find_socket(I, mr.exp[0]));
        if (symb) {
            if (SymbolAnnotation::get_b(symb, NOUN_FILTER_IANN) == FALSE)
                SymbolAnnotation::set_b(symb, NOUN_FILTER_IANN, TRUE);
            return InterValuePairs::symbolic(IBM, symb);
        }
    }

§6.9. Attempt to parse this as an identifier name for something already defined by this kit6.9 =

    inter_symbol *symb = Wiring::find_socket(I, S);
    if (symb) {
        return InterValuePairs::symbolic(IBM, symb);
    }

§6.10. At this point, maybe the reason we haven't yet recognised the constant S is that it's a computation like 6 + MAX_WEEBLES*4. This is quite legal in Inform 6, and the compiler performs constant-folding to evaluate them: so that's what we will emulate now. In practice, we are only going to understand fairly simple computations, but that will be enough for the kits normally used with Inform.

We do this by parsing S into a schema, whose tree will look roughly like this:

    PLUS_BIP
        6
        TIMES_BIP
            MAX_WEEBLES
            4

We then recurse down through this tree, constructing an Inter symbol for a constant which evaluates to the result of each operation. Here, then, we first define Computed_Constant_Value_1 as the multiplication, then define Computed_Constant_Value_2 as the addition, and that is what we use as our answer. Since we recurse depth-first, the subsidiary results are always made before they are needed.

Parse this as a possibly computed value6.10 =

    inter_schema *sch = ParsingSchemas::from_text(S);
    inter_symbol *result_s =
        CompileSplatsStage::compute_r(step, IBM, sch->node_tree);
    if (result_s == NULL)
        PipelineErrors::kit_error("Inform 6 constant in kit too complex", S);
    return InterValuePairs::symbolic(IBM, result_s);

§7. So this is the recursion. Note that we calculate \(-x\) as \(0 - x\), thus reducing unary subtraction to a case of binary subtraction.

inter_symbol *CompileSplatsStage::compute_r(pipeline_step *step,
    inter_bookmark *IBM, inter_schema_node *isn) {
    if (isn->isn_type == SUBEXPRESSION_ISNT)
        return CompileSplatsStage::compute_r(step, IBM, isn->child_node);
    if (isn->isn_type == OPERATION_ISNT) {
        inter_ti op = 0;
        if (isn->isn_clarifier == PLUS_BIP) op = CONST_LIST_FORMAT_SUM;
        else if (isn->isn_clarifier == TIMES_BIP) op = CONST_LIST_FORMAT_PRODUCT;
        else if (isn->isn_clarifier == MINUS_BIP) op = CONST_LIST_FORMAT_DIFFERENCE;
        else if (isn->isn_clarifier == DIVIDE_BIP) op = CONST_LIST_FORMAT_QUOTIENT;
        else if (isn->isn_clarifier == UNARYMINUS_BIP) Calculate unary minus7.2
        else return NULL;
        Calculate binary operation7.1;
    }
    if (isn->isn_type == EXPRESSION_ISNT) {
        inter_schema_token *t = isn->expression_tokens;
        if ((t == NULL) || (t->next)) internal_error("malformed EXPRESSION_ISNT");
        return CompileSplatsStage::compute_eval(step, IBM, t);
    }
    return NULL;
}

§7.1. Calculate binary operation7.1 =

    inter_symbol *i1 = CompileSplatsStage::compute_r(step, IBM, isn->child_node);
    inter_symbol *i2 = CompileSplatsStage::compute_r(step, IBM, isn->child_node->next_node);
    if ((i1 == NULL) || (i2 == NULL)) return NULL;
    return CompileSplatsStage::compute_binary_op(op, step, IBM, i1, i2);

§7.2. Calculate unary minus7.2 =

    inter_symbol *i2 = CompileSplatsStage::compute_r(step, IBM, isn->child_node);
    if (i2 == NULL) return NULL;
    return CompileSplatsStage::compute_binary_op(CONST_LIST_FORMAT_DIFFERENCE, step, IBM, NULL, i2);

§8. The binary operation \(x + y\) is "calculated" by forming a constant list with two entries, \(x\) and \(y\), and marking this list in Inter as a list whose meaning is the sum of the entries. (And similarly for the other three operations.) This is a sort of lazy evaluation: it means that the actual calculation will be done in whatever context Inter is being compiled for — for example, if all of this Inter is compiled to ANSI C, then it will eventually be a C compiler which actually works out the numerical value of \(x + y\).

Why do we do this? Why not simply calculate now, and get an explicit answer? The trouble is that one of \(x\) or \(y\) might be some symbol whose value is itself created by the downstream compiler. The meaning of this is the same on all platforms: the value is not.

There would be a case for optimising the following function to fold constants in cases where we can confidently do so (being careful of overflows and mindful of the word size), i.e., when \(x\) and \(y\) are literal numbers or symbols defined as literal numbers. That would produce more elegant Inter. But not really more efficient Inter.

inter_symbol *CompileSplatsStage::compute_binary_op(inter_ti op, pipeline_step *step,
    inter_bookmark *IBM, inter_symbol *i1, inter_symbol *i2) {
    inter_package *pack = InterBookmark::package(IBM);
    inter_symbol *result_s = CompileSplatsStage::new_ccv_symbol(pack);
    inter_ti MID = InterSymbolsTable::id_from_symbol_at_bookmark(IBM, result_s);
    inter_ti KID = InterTypes::to_TID(InterBookmark::scope(IBM), InterTypes::unchecked());
    inter_ti B = (inter_ti) InterBookmark::baseline(IBM) + 1;
    inter_tree_node *pair_list =
        Inode::new_with_3_data_fields(IBM, CONSTANT_IST, MID, KID, op, NULL, B);
    int pos = pair_list->W.extent;
    Inode::extend_instruction_by(pair_list, 4);
    if (i1) {
        InterValuePairs::set(pair_list, pos, InterValuePairs::symbolic(IBM, i1));
    } else {
        InterValuePairs::set(pair_list, pos, InterValuePairs::number(0));
    }
    if (i2) {
        InterValuePairs::set(pair_list, pos+2, InterValuePairs::symbolic(IBM, i2));
    } else {
        InterValuePairs::set(pair_list, pos+2, InterValuePairs::number(0));
    }
    Produce::guard(VerifyingInter::instruction(InterBookmark::package(IBM), pair_list));
    NodePlacement::move_to_moving_bookmark(pair_list, IBM);
    return result_s;
}

§9. So much for recursing down through the nodes of the Inter schema. Here are the leaves:

inter_symbol *CompileSplatsStage::compute_eval(pipeline_step *step,
    inter_bookmark *IBM, inter_schema_token *t) {
    inter_tree *I = InterBookmark::tree(IBM);
    switch (t->ist_type) {
        case NUMBER_ISTT:
        case BIN_NUMBER_ISTT:
        case HEX_NUMBER_ISTT: This leaf is a literal number of some kind9.1;
        case IDENTIFIER_ISTT: This leaf is a symbol name9.2;
    }
    return NULL;
}

§9.1. This leaf is a literal number of some kind9.1 =

    inter_package *pack = InterBookmark::package(IBM);
    inter_pair val;
    if (t->constant_number >= 0) {
        val = InterValuePairs::number((inter_ti) t->constant_number);
    } else {
        val = InterValuePairs::number_from_I6_notation(t->material);
        if (InterValuePairs::is_undef(val))
            return NULL;
    }
    inter_symbol *result_s = CompileSplatsStage::new_ccv_symbol(pack);
    inter_ti B = (inter_ti) InterBookmark::baseline(IBM) + 1;
    Produce::guard(ConstantInstruction::new(IBM, result_s,
        InterTypes::unchecked(), val, B, NULL));
    return result_s;

§9.2. This is the harder case by far, despite the brevity of the following code. Here we run into, say, MAX_ELEPHANTS, some identifier which clearly refers to something defined elsewhere. If it has already been defined in the kit being compiled, then there's a socket of that name already, and we can use that as the answer; similarly if it's an architectural constant such as WORDSIZE. Otherwise we must assume it will be declared either later or in another compilation unit, so we create a plug called MAX_ELEPHANTS and let the linker stage worry about what it means later on.

This leaf is a symbol name9.2 =

    inter_symbol *result_s = LargeScale::find_architectural_symbol(I, t->material);
    if (result_s) return result_s;
    result_s = Wiring::find_socket(I, t->material);
    if (result_s) return result_s;
    return Wiring::plug(I, t->material);

§10. The above algorithm needs a lot of names for partial results of expressions, all of which have to become Inter symbols. It really doesn't matter what these are called.

int ccs_count = 0;
inter_symbol *CompileSplatsStage::new_ccv_symbol(inter_package *pack) {
    TEMPORARY_TEXT(NN)
    WRITE_TO(NN, "Computed_Constant_Value_%d", ccs_count++);
    inter_symbol *result_s =
        InterSymbolsTable::symbol_from_name_creating(InterPackage::scope(pack), NN);
    InterSymbol::set_flag(result_s, MAKE_NAME_UNIQUE_ISYMF);
    DISCARD_TEXT(NN)
    return result_s;
}

§11. Delegating the work of compiling function bodies. Function bodies are by far the hardest things to compile. We delegate this first by storing up a list of requests to do the work:

typedef struct function_body_request {
    struct inter_bookmark position;
    struct inter_bookmark block_bookmark;
    struct package_request *enclosure;
    struct inter_package *block_package;
    int pass2_offset;
    struct text_stream *body;
    struct text_stream *identifier;
    CLASS_DEFINITION
} function_body_request;

int CompileSplatsStage::function_body(compile_splats_state *css, inter_bookmark *IBM,
    inter_package *block_package, inter_ti offset, text_stream *body, inter_bookmark bb,
    text_stream *identifier) {
    if (Str::is_whitespace(body)) return FALSE;
    function_body_request *req = CREATE(function_body_request);
    req->block_bookmark = bb;
    req->enclosure = Packaging::enclosure(InterBookmark::tree(IBM));
    req->position = Packaging::bubble_at(IBM);
    req->block_package = block_package;
    req->pass2_offset = (int) offset - 2;
    req->body = Str::duplicate(body);
    req->identifier = Str::duplicate(identifier);
    ADD_TO_LINKED_LIST(req, function_body_request, css->function_bodies_to_compile);
    return TRUE;
}

§12. ...Playing back through those requests here. Note that we turn the entire contents of the function — which can be very large, for example in the Inform kit CommandParserKit — as a single gigantic Inter schema sch.

int CompileSplatsStage::function_bodies(pipeline_step *step, compile_splats_state *css,
    inter_tree *I) {
    int errors_occurred = FALSE;
    function_body_request *req;
    LOOP_OVER_LINKED_LIST(req, function_body_request, css->function_bodies_to_compile) {
        LOGIF(SCHEMA_COMPILATION, "=======\n\nFunction (%S) len %d: '%S'\n\n",
            InterPackage::name(req->block_package), Str::len(req->body), req->body);
        inter_schema *sch = ParsingSchemas::from_text(req->body);
        if (LinkedLists::len(sch->parsing_errors) > 0) {
            CompileSplatsStage::report_kit_errors(sch, req);
        } else {
            if (Log::aspect_switched_on(SCHEMA_COMPILATION_DA)) InterSchemas::log(DL, sch);
            Compile this function body12.1;
        }
        if (LinkedLists::len(sch->parsing_errors) > 0) errors_occurred = TRUE;
    }
    return errors_occurred;
}

§12.1. And then we emit Inter code equivalent to sch:

Compile this function body12.1 =

    Produce::set_function(I, req->block_package);
    Packaging::set_state(I, &(req->position), req->enclosure);
    Produce::push_new_code_position(I, &(req->position));
    value_holster VH = Holsters::new(INTER_VOID_VHMODE);
    inter_symbols_table *scope1 = InterPackage::scope(req->block_package);
    inter_package *module_pack =
        step->pipeline->ephemera.assimilation_modules[step->tree_argument];
    inter_symbols_table *scope2 = InterPackage::scope(module_pack);
    identifier_finder finder = IdentifierFinders::common_names_only();
    IdentifierFinders::next_priority(&finder, scope1);
    IdentifierFinders::next_priority(&finder, scope2);
    EmitInterSchemas::emit(I, &VH, sch, finder, NULL, NULL, NULL);
    CompileSplatsStage::report_kit_errors(sch, req);
    Produce::pop_code_position(I);
    Produce::set_function(I, NULL);

§13. Either parsing or emitting can throw errors, so at both stages:

void CompileSplatsStage::report_kit_errors(inter_schema *sch, function_body_request *req) {
    if (LinkedLists::len(sch->parsing_errors) > 0) {
        schema_parsing_error *err;
        LOOP_OVER_LINKED_LIST(err, schema_parsing_error, sch->parsing_errors) {
            TEMPORARY_TEXT(msg)
            WRITE_TO(msg, "in function '%S': %S", req->identifier, err->message);
            PipelineErrors::kit_error("kit source error %S", msg);
            DISCARD_TEXT(msg)
        }
    }
}