1# Dual control for the Lockheed1049h Super Constellation
2# Copyright (c) 2016 Ludovic Brenta <ludovic@ludovic-brenta.org>
3# Based on the dual control tools for FlightGear, by Anders Gidenstam.
4#
5# This program is free software; you can redistribute it and/or modify
6# it under the terms of the GNU General Public License as published by
7# the Free Software Foundation; either version 2 of the License, or
8# (at your option) any later version.
9#
10# This program is distributed in the hope that it will be useful,
11# but WITHOUT ANY WARRANTY; without even the implied warranty of
12# MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
13# GNU General Public License for more details.
14#
15# You should have received a copy of the GNU General Public License along
16# with this program; if not, write to the Free Software Foundation, Inc.,
17# 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA.
18
19######################################################################
20# Unlike some other aircraft, this dual control does not support a
21# pilot and a copilot, a situation that I find uninteresting.
22# Instead, it supports a pilot and a flight engineer.  The flight
23# engineer performs startup, engine and fuel management and is very
24# busy during all phases of flight.
25#
26# There are several flows of information between pilot and engineer,
27# some bidirectional.
28#
29# Pilot to engineer: aircraft position, velocity, orientation; control
30# surfaces, lights, fuel levels, fuel flow, BMEP (computed in the
31# pilot's aircraft with a property rule), i.e. everything that the
32# engineer needs to see and move with the aircraft and move the
33# instruments.  Some properties are already transmitted as part of the
34# multiplayer protocol, some others are already transmitted as part of
35# multiplayer support (see Lockheed1049h-set.xml); here we only add
36# the missing ones.
37#
38# Engineer to pilot: cowl flaps, propeller pitch, mixture, fuel
39# valves, fuel dump, battery switches, boost speed, engine start
40# switches.
41#
42# Bidirectional: throttle.
43#
44# When an engineer is connected, the pilot can *not* control the
45# engineer functions, except for the throttle.  In real life, pilots
46# would use the throttles only during taxi (i.e. differential throttle
47# to help steer the aircraft on the ground) then hand control over to
48# the engineer.
49
50var DCT = dual_control_tools;
51
52## Pilot/copilot aircraft identifiers. Used by dual_control.
53var pilot_type   = "Aircraft/Lockheed1049h/Models/Lockheed1049h.xml";
54var copilot_type = "Aircraft/Lockheed1049h/Models/L1049h-engineer.xml";
55var connected = 0;
56
57expand_string = func (s) {
58    # input: a string of the form "/foo/bar[0..8]/baz"
59    # output: a vector of strings of the form
60    #         [ "/foo/bar[0]/baz", ... , "/foo/bar[8]/baz" ]
61    var result = [];
62    var state = 0;
63    var low_bound = 0;
64    var high_bound = 0;
65    var prefix = "";
66    var suffix = "";
67    for (var j = 0; j < size (s); j += 1) {
68        var c = chr(s[j]);
69        if (state == 0) { # before '['
70            if (c == "[") { prefix = substr(s, 0, j+1); state = 1; }
71        }
72        else if (state == 1) { # between '[' and "..": extract low bound
73            if (c == "]") { suffix = c; state = 2; }
74            else if (c == ".") { state = 3; }
75            else {
76               var v = int(c);
77               if (v == nil) {
78                   print ("parse error in string '" ~ s ~ "' at index " ~ j
79                        ~ ": expected a number, found '" ~ c);
80                   return [];
81               }
82               low_bound = low_bound * 10 + v;
83            }
84        }
85        else if (state == 2) { # after ']': extract rest of string
86            suffix ~= c;
87        }
88        else if (state == 3) { # after first dot: expect a second dot
89            if (c == ".") { state = 4; }
90            else {
91               print ("parse error in string '" ~ s ~ "' at index " ~ j
92                        ~ ": expected a dot, found '" ~ c);
93               return [];
94            }
95        }
96        else if (state == 4) { # after second dot: expect digits or ']'
97           if (c == "]") { suffix = "]"; state = 2; }
98           else {
99               var v = int(c);
100               if (v == nil) {
101                   print ("parse error in string '" ~ s ~ "' at index " ~ j
102                        ~ ": expected a number, found '" ~ c);
103                   return [];
104               }
105               high_bound = high_bound * 10 + v;
106           }
107        }
108    }
109    if (high_bound == 0) { result = [s]; }
110    else if (high_bound < low_bound) {
111        print ("semantic error: high bound lower than low bound: ["
112               ~ low_bound ~ ".." ~ high_bound ~ "]");
113        return [];
114    }
115    else {
116        setsize (result, high_bound - low_bound + 1);
117        var r = 0;
118        for (var j = low_bound; j <= high_bound; j += 1) {
119            result[r] = prefix ~ j ~ suffix;
120            r += 1;
121        }
122    }
123    return result;
124}
125
126
127expand_vector = func (v, vector_name) {
128    var result = [];
129    foreach (var s; v) {
130        result ~= expand_string (s);
131    }
132    var sz = size (result);
133    print ("L1049h-dual-control: Expanded " ~ vector_name
134         ~ " into " ~ sz ~ " properties");
135    if (sz == 0) {
136        fgcommand ("exit");
137        # to make this error highly visible to the aircraft developer
138    }
139    if (sz > 127) {
140        print ("L1049h-dual-control: error: "
141             ~ "too many properties in a single string!");
142        # because the TDMEncoder encodes the index of each property into a
143        # single byte in the string.
144        fgcommand ("exit");
145    }
146    return result;
147}
148
149var key_value_pair_length = mp_broadcast.Binary.sizeOf["byte"]
150                          + mp_broadcast.Binary.sizeOf["double"];
151
152var TDMEncoder = {
153    new : func (inputs, dest) {
154        var m = {
155            parents : [ TDMEncoder, DCT.TDMEncoder.new (inputs, dest) ],
156            last_input_sent : 0,
157            message_counter : 0,
158            old_values : [],
159        };
160        return m;
161    },
162    send_all_properties : func () {
163        setsize (me.old_values, size (me.inputs));
164        forindex (var j; me.inputs) {
165            me.old_values[j] = { initialized: 0, value: nil };
166        }
167    },
168    send : func (msg, key) {
169        me.channel.send (msg);
170        me.last_input_sent = key + 1;
171        me.message_counter += 1;
172    },
173    update : func () {
174        if (!connected) { return; }
175        var msg = "";
176        var debug_msg = me.message_counter ~ ": sending properties at indexes:";
177        if (math.mod (me.message_counter, 100) == 0) {
178            me.send_all_properties();
179        }
180        forindex (var index; me.inputs) {
181            var key = math.mod (index + me.last_input_sent, size (me.inputs));
182            var v = me.inputs[key].getValue();
183            if (!me.old_values[key].initialized
184                or me.old_values[key].value != v) {
185                msg ~= mp_broadcast.Binary.encodeByte (key);
186                msg ~= mp_broadcast.Binary.encodeDouble (v);
187                debug_msg ~= " " ~ key
188                    ~ (me.old_values[key].initialized ?
189                       (me.old_values[key].value != v ? " (changed)" : " (resent)")
190                       : " (first sent)");
191                me.old_values[key] = { initialized: 1, value: v };
192            }
193            # Bug: there is a limit of 128 characters per string, so send the
194            # message before hitting this limit.  On the next update, we will
195            # send other key-value pairs.
196            #
197            # Bug: fgfs silently drops some properties from the packet if its
198            # total length exceeds 1200 bytes; this includes all the predefined
199            # properties as well as the inputs.  So, we conservatively restrict
200            # the length of any one string property to fewer than the maximum;
201            # even this does not guarantee that the packet length stays below
202            # 1200 bytes.
203            #
204            # Since we can send only a few properties at a time, bandwidth is
205            # severely restricted, so we send only the properties  whose value
206            # has changed.  Once every 10 messages, we re-send all properties.
207            if (size (msg) > 66 - key_value_pair_length) {
208                me.send (msg, key);
209                if (getprop ("/sim/multiplay/debug")) { print (debug_msg); }
210                return;
211            }
212        }
213        if (size (msg) > 0) {
214            me.send (msg, -1);
215        }
216    }
217};
218
219var TDMDecoder = {
220    new: func (src, remote_node, properties) {
221        var m = {
222            parents : [ TDMDecoder ],
223            channel : mp_broadcast.MessageChannel.new
224                        (src, func (msg) { m.process (msg); }),
225            properties : properties,
226            remote_node : remote_node };
227        return m;
228    },
229    process_key_value_pair: func (msg) {
230        var index = mp_broadcast.Binary.decodeByte (msg);
231        if (index < 0) { index += 128; } # I want an unsigned byte!
232        var value = mp_broadcast.Binary.decodeDouble (substr (msg, 1));
233        var node = me.remote_node.getNode (me.properties[index], 1);
234        node.setValue (value);
235    },
236    process: func (msg) {
237        if (!connected) { return; }
238        var j = 0;
239        while (j < size (msg)) {
240            me.process_key_value_pair (substr (msg, j, key_value_pair_length));
241            j += key_value_pair_length;
242        }
243    },
244    update: func () { me.channel.update(); }
245};
246
247
248var Translator = {
249    new : func (src = nil, dest = nil, factor = 1, offset = 0) {
250        print (debug.string (dest) ~ " := " ~ debug.string (src));
251        return { parents: [
252            Translator, DCT.Translator.new (src, dest, factor, offset)
253        ] };
254    }
255};
256
257var SwitchDecoder = {
258    new : func (src_node, dest_node, targets) {
259        # src_node: an input property containing a packed array of booleans
260        # dest_node: a node under which to fill target properties
261        # targets: a vector of property names under dest_node
262        return { parents : [ SwitchDecoder, DCT.SwitchDecoder.new (src_node, []) ],
263                 dest_node : dest_node,
264                 targets   : targets
265               };
266    },
267    update : func () {
268        # DCT.SwitchDecoder relies on an array of action functions; we instead
269        # decode into the targets.  Also, we decode every time we are called and
270        # do not rely on old values of the bits in the input property.
271        var value = me.src.getValue();
272        if (num (value) == nil) { return; } # presumably the other party is not sending yet
273        var t = getprop ("/sim/time/elapsed-sec"); # simulated time
274        if (value == me.old) {
275            if ((t - me.stable_since) < me.MIN_STABLE) {
276                # Wait until the value becomes stable
277            }
278            else {
279                foreach (var prop_name; me.targets) {
280                    var bit = math.mod (value, 2);
281                    me.dest_node.getNode (prop_name, 1).setBoolValue (bit);
282                    value = (value - bit) / 2;
283                }
284            }
285        }
286        else {
287            # value has changed, reset the stable counter
288            me.stable_since = t;
289            me.old = value;
290        }
291    }
292};
293
294
295var MultiBitIntEncoderDecoder = {
296    new : func (nodes, node, bits_per_int) {
297        # properties: a vector of property nodes; each is an int that will be encoded on bits_per_int bits.
298        # target_node: the target integer node.
299        me.check_multi_bit_prerequisites (nodes, bits_per_int);
300        var factor = 1;
301        for (var j = 1; j <= bits_per_int; j += 1) { factor *= 2; }
302        return { parents : [ MultiBitIntEncoder ],
303                 nodes : nodes,
304                 node  : node,
305                 factor : factor };
306    },
307    check_multi_bit_prerequisites : func (nodes, bits_per_int) {
308        if (num (bits_per_int) == nil or bits_per_int < 1) {
309            print ("MultiBitIntEncoder or Decoder: bits_per_int must be an integer and at least one");
310            fgcommand ("exit");
311        }
312        if (size (nodes) > int (32 / bits_per_int)) {
313            print ("MultiBitIntEncoder or Decoder: too many properties: " ~ debug.string (nodes)
314                   ~ ", bits_per_int=" ~ bits_per_int);
315            fgcommand ("exit");
316        }
317    }
318};
319
320var MultiBitIntEncoder = {
321    new : func (nodes, node, bits_per_int) {
322        return { parents : [ MultiBitIntEncoder, MultiBitIntEncoderDecoder.new (nodes, node, bits_per_int) ] };
323    },
324    update : func () {
325        var value = 0;
326        var party_not_sending_skip = 0;
327        forindex (var j; me.nodes) {
328           value += me.nodes[j].getValue ();
329           if (j < size (me.nodes) - 1) { value *= me.factor; }
330        }
331        me.node.setValue (value);
332    }
333};
334
335var MultiBitIntDecoder = {
336    new : func (nodes, node, bits_per_int) {
337        return { parents : [ MultiBitIntDecoder, MultiBitIntEncoderDecoder.new (nodes, node, bits_per_int) ],
338                 stable_since : 0,
339                 old_value : 0,
340                 MIN_STABLE : 0.2 };
341    },
342    update : func () {
343        var v = me.node.getValue();
344        if (num (v) == nil) { return; } # presumably the other party is not sending yet
345        var t = getprop ("/sim/time/elapsed-sec");
346        if (v == me.old_value) {
347            if ((t - me.stable_since) < me.MIN_STABLE) {
348                # Wait until the value becomes stable
349            }
350            else {
351                forindex (var j; me.nodes) {
352                    var one_value = math.mod (v, me.factor);
353                    me.nodes[size (me.nodes) - j - 1].setIntValue (one_value);
354                    v = (v - one_value) / me.factor;
355                }
356            }
357        }
358        else {
359            # value has changed, reset the stable counter
360            me.stable_since = t;
361            me.old_value = v;
362        }
363    }
364};
365
366
367var NormalizedFloatEncoderDecoder = {
368    # Encodes or Decodes four normalized floats into four fixed-point, 8-bit values packed in
369    # one 32-bit integer.
370    new : func (nodes, node) {
371        if (size (nodes) != 4) {
372            print ("NormalizedFloatEncoderDecoder requires exactly four nodes to encode or decode");
373            fgcommand ("exit");
374        }
375        return { parents : [ NormalizedFloatEncoderDecoder ],
376                 nodes   : nodes,
377                 node    : node };
378    }
379};
380
381var NormalizedFloatEncoder = {
382    new : func (nodes, node) {
383        return { parents : [ NormalizedFloatEncoder, NormalizedFloatEncoderDecoder.new (nodes, node) ] };
384    },
385    update : func () {
386        var v = 0;
387        forindex (var j; me.nodes) {
388            var one_value = me.nodes[j].getValue ();
389            if (one_value < 0 or one_value > 1) {
390                print ("NormalizedFloatEncoder: The property " ~ me.nodes[j].getPath() ~ " has a value outside [0..1]!");
391            }
392            else {
393                # I would like to encode each of the properties on 8 bits but Nasal does not have proper wraparound
394                # semantics; instead it has saturating arithmetic whereby any overflow causes the value to become
395                # -2**31 exacltly, losing any other significant bits.  Therefore we encode each property on only 7
396                # bits, the total value can thus never exceed 2**29.
397                v += int (one_value * 127);
398            }
399            if (j < size (me.nodes) - 1) {
400                v *= 128;
401            }
402        }
403        me.node.setIntValue (v);
404    }
405};
406
407var NormalizedFloatDecoder = {
408    new : func (nodes, node) {
409        return { parents : [ NormalizedFloatDecoder, NormalizedFloatEncoderDecoder.new (nodes, node) ],
410                 stable_since : 0,
411                 old_value : 0,
412                 MIN_STABLE : 0.2 }
413    },
414    update : func () {
415        var v = me.node.getValue ();
416        if (num (v) == nil) { return; }
417        var t = getprop ("/sim/time/elapsed-sec");
418        if (v < 0) { v += mp_broadcast.Binary.TWOTO31; }
419        if (v == me.old_value) {
420            if ((t - me.stable_since) < me.MIN_STABLE) {
421                # Wait until the value becomes stable
422            }
423            else {
424                forindex (var j; me.nodes) {
425                    var one_value = math.mod (v, 128);
426                    me.nodes[size (me.nodes) - j - 1].setDoubleValue (one_value / 127);
427                    v = (v - one_value) / 128;
428                }
429            }
430        }
431        else {
432            # value has changed, reset the stable counter
433            me.stable_since = t;
434            me.old_value = v;
435        }
436    }
437};
438
439getNodes = func (root_node, v) {
440    # v: a vector of strings with property names, like the result of
441    # expand_vector above.
442    # result: a vector of property nodes.
443    var result = [];
444    setsize (result, size (v));
445    forindex (var j; v) {
446        result[j] = root_node.getNode (v[j], 1);
447    }
448    return result;
449}
450
451check_properties = func (source_properties, transport_properties) {
452    var a = size (source_properties);
453    var b = size (transport_properties);
454    var min = a > b ? b : a;
455    var max = a > b ? a : b;
456    for (var j = 0; j < max; j += 1) {
457        if (j < min) {
458            print ("    " ~ source_properties[j]
459                ~ " <=> " ~ transport_properties[j]);
460        }
461        else if (j < a) {
462            print ("    " ~ source_properties[j] ~ " <=> ?");
463        }
464        else if (j < b) {
465            print ("                    ? <=> "
466                   ~ transport_properties[j]);
467        }
468    }
469    if (a != b) {
470        fgcommand ("exit");
471    }
472}
473
474
475var pilot_to_engineer_properties = expand_vector ([
476    # These are properties sent above and beyond the normal multiplayer
477    # properties that animate the model; they are intended only for the
478    # engineer.  Therefore, be sure to use generic properties that are
479    # not already used in Lockheed1049h-set.xml.
480    "controls/engines/engine[0]/propeller-pitch",
481    "engines/engine[0..3]/bmep",
482    "engines/engine[0..3]/cht-degf",
483    "engines/engine[0..3]/fuel-flow-gph",
484    "engines/engine[0..3]/mp-osi",
485    ], "pilot_to_engineer_properties");
486var pilot_to_engineer_properties_transmitted = expand_vector ([
487    "engines/engine[5]/rpm",
488    "engines/engine[0..3]/n1",
489    "engines/engine[5..8]/n1",
490    "engines/engine[0..3]/n2",
491    "engines/engine[5..8]/n2",
492    ], "pilot_to_engineer_properties_transmitted");
493check_properties (pilot_to_engineer_properties, pilot_to_engineer_properties_transmitted);
494
495var packed_mixture_properties = expand_vector ([ # these are sent both ways
496    "controls/engines/engine[0..3]/mixture"
497    ], "packed_mixture_properties");
498
499var packed_throttle_properties = expand_vector ([ # these are sent both ways
500    "controls/engines/engine[0..3]/throttle",
501    ], "packed_throttle_properties");
502
503var packed_2bit_int_properties = expand_vector ([ # these are sent both ways
504    "controls/engines/engine[0..3]/magnetos",
505    "controls/fuel/tankvalve[0..4]"
506    ], "packed_2bit_int_properties");
507
508var packed_3bit_int_properties = expand_vector ([ # these are sent both ways
509    "controls/fuel/enginevalve[0..3]",
510    "controls/fuel/jettison[0..1]/valve",
511    "controls/switches/engine-start-select",
512    ], "packed_3bit_int_properties");
513
514var packed_boolean_properties = expand_vector ([ # these are sent both ways
515    "controls/fuel/crossfeedvalve[0..3]",
516    "controls/switches/battery-cart",
517    "controls/switches/battery-ship",
518    "controls/switches/command-bell",
519    "controls/switches/engine-start",
520    "controls/switches/gen-apu",
521    "controls/switches/generator[0..3]",
522    "controls/switches/horn",
523    "controls/switches/no-smoking-signs",
524    "controls/switches/seat-belt-signs",
525    "fdm/jsbsim/propulsion/engine[0..3]/boost-speed",
526    ], "packed_boolean_properties");
527
528var pilot_to_engineer_properties_string0 = expand_vector ([
529    "consumables/fuel/tank[4..12]/level-gal_us",
530    "consumables/fuel/tank[4..12]/level-lbs",
531     # 0..3 are the engine fuel lines, not needed by the engineer
532    "consumables/fuel/total-fuel-lbs",
533    "controls/engines/engine[0..3]/cowl-flaps-norm",
534    "controls/flight/aileron",
535    "controls/flight/aileron-trim",
536    "controls/flight/elevator",
537    "controls/flight/elevator-trim",
538    "controls/flight/rudder",
539    "controls/flight/rudder-trim",
540    "engines/engine[0..3]/egt-degf",
541    "engines/engine[0..3]/est-fuelpress",
542    "engines/engine[0..3]/oil-pressure-psi",
543    "engines/engine[0..3]/oil-temperature-degf",
544    "instrumentation/slip-skid-ball/indicated-slip-skid",
545    "instrumentation/turn-indicator/indicated-turn-rate",
546    ], "pilot_to_engineer_properties_string0");
547
548var engineer_to_pilot_properties = expand_vector ([
549    # The properties that the engineer sends to the pilot
550    "consumables/fuel/tank[4..12]/level-gal_us",
551    "controls/engines/engine[0..3]/cowl-flaps-norm",
552    "controls/engines/engine[0]/propeller-pitch",
553    "controls/lighting/panel-norm",
554    ], "engineer_to_pilot_properties");
555var engineer_to_pilot_properties_transmitted = expand_vector ([
556    # The properties that are part of the default multiplayer protocol, and used
557    # to send the above properties.  The engineer uses an alias to write into
558    # the properties; the pilot uses a Translator to read them and write the
559    # values into its own properties.
560    "sim/multiplay/generic/float[4..12]",
561    "engines/engine[0..3]/n1",
562    "engines/engine[0]/rpm",
563    "sim/multiplay/generic/float[0]",
564    ], "engineer_to_pilot_properties_transmitted");
565check_properties (engineer_to_pilot_properties, engineer_to_pilot_properties_transmitted);
566
567pilot_connect_copilot = func (copilot) {
568    connected = 1;
569    var result = [
570        MultiBitIntDecoder.new (getNodes (copilot, packed_2bit_int_properties),
571                                copilot.getNode ("sim/multiplay/generic/int[3]", 1),
572                                2),
573        MultiBitIntDecoder.new (getNodes (copilot, packed_3bit_int_properties),
574                                copilot.getNode ("sim/multiplay/generic/int[4]", 1),
575                                3),
576        NormalizedFloatDecoder.new (getNodes (copilot, packed_mixture_properties),
577                                    copilot.getNode ("sim/multiplay/generic/int[5]", 1)),
578        NormalizedFloatDecoder.new (getNodes (copilot, packed_throttle_properties),
579                                    copilot.getNode ("sim/multiplay/generic/int[6]", 1)),
580        SwitchDecoder.new (copilot.getNode ("sim/multiplay/generic/int[19]", 1),
581                           copilot,
582                           packed_boolean_properties),
583    ];
584    forindex (var j; engineer_to_pilot_properties) {
585        var engineer_node = copilot.getNode (engineer_to_pilot_properties_transmitted[j]);
586        var pilot_node = props.globals.getNode (engineer_to_pilot_properties[j]);
587        result ~= [ DCT.MostRecentSelector.new (engineer_node, pilot_node, pilot_node, 0.01) ];
588    }
589    var rpm0 = props.globals.getNode ("controls/engines/engine[0]/propeller-pitch");
590    # propeller-pitch is special: propagate it to all other engines as there is only one command for all 4.
591    result ~= [
592        DCT.Translator.new (rpm0, props.globals.getNode ("controls/engines/engine[1]/propeller-pitch")),
593        DCT.Translator.new (rpm0, props.globals.getNode ("controls/engines/engine[2]/propeller-pitch")),
594        DCT.Translator.new (rpm0, props.globals.getNode ("controls/engines/engine[3]/propeller-pitch")) ];
595    foreach (var prop; packed_2bit_int_properties) {
596        var engineer_node = copilot.getNode (prop, "INT", 1);
597        var pilot_node = props.globals.getNode (prop, "INT", 1);
598        result ~= [ DCT.MostRecentSelector.new (engineer_node, pilot_node, pilot_node, 0.9) ];
599    }
600    foreach (var prop; packed_3bit_int_properties) {
601        var engineer_node = copilot.getNode (prop, "INT", 1);
602        var pilot_node = props.globals.getNode (prop, "INT", 1);
603        result ~= [ DCT.MostRecentSelector.new (engineer_node, pilot_node, pilot_node, 0.9) ];
604    }
605    foreach (var prop; packed_mixture_properties) {
606        var engineer_node = copilot.getNode (prop, "DOUBLE", 1);
607        var pilot_node = props.globals.getNode (prop, "DOUBLE", 1);
608        result ~= [ DCT.MostRecentSelector.new (engineer_node, pilot_node, pilot_node, 1 / 127) ];
609    }
610    foreach (var prop; packed_throttle_properties) {
611        var engineer_node = copilot.getNode (prop, "DOUBLE", 1);
612        var pilot_node = props.globals.getNode (prop, "DOUBLE", 1);
613        result ~= [ DCT.MostRecentSelector.new (engineer_node, pilot_node, pilot_node, 1 / 127) ];
614    }
615    foreach (var prop; packed_boolean_properties) {
616        var engineer_node = copilot.getNode (prop, "BOOL", 1);
617        var pilot_node = props.globals.getNode (prop, "BOOL", 1);
618        result ~= [ DCT.MostRecentSelector.new (engineer_node, pilot_node, pilot_node, 0.9) ];
619    }
620    var pilot_nodes = getNodes (props.globals, pilot_to_engineer_properties);
621    var mp_protocol_nodes = getNodes (props.globals, pilot_to_engineer_properties_transmitted);
622    forindex (var j; pilot_to_engineer_properties) {
623        result ~= [ DCT.Translator.new (pilot_nodes[j], mp_protocol_nodes[j]) ];
624    }
625    result ~= [
626        TDMEncoder.new (getNodes (props.globals, pilot_to_engineer_properties_string0),
627                        props.globals.getNode ("sim/multiplay/generic/string[0]", 1)),
628        MultiBitIntEncoder.new (getNodes (props.globals, packed_2bit_int_properties),
629                                props.globals.getNode ("sim/multiplay/generic/int[3]", 1),
630                                2),
631        MultiBitIntEncoder.new (getNodes (props.globals, packed_3bit_int_properties),
632                                props.globals.getNode ("sim/multiplay/generic/int[4]", 1),
633                                3),
634        NormalizedFloatEncoder.new (getNodes (props.globals, packed_mixture_properties),
635                                    props.globals.getNode  ("sim/multiplay/generic/int[5]", 1)),
636        NormalizedFloatEncoder.new (getNodes (props.globals, packed_throttle_properties),
637                                    props.globals.getNode  ("sim/multiplay/generic/int[6]", 1)),
638        DCT.SwitchEncoder.new (getNodes (props.globals, packed_boolean_properties),
639                               props.globals.getNode ("sim/multiplay/generic/int[2]", 1))
640    ];
641    return result;
642}
643
644pilot_disconnect_copilot = func () { connected = 0; }
645
646copilot_connect_pilot = func (pilot) {
647    connected = 1;
648    result = [
649        MultiBitIntDecoder.new (getNodes (pilot, packed_2bit_int_properties),
650                                pilot.getNode ("sim/multiplay/generic/int[3]", 1),
651                                2),
652        MultiBitIntDecoder.new (getNodes (pilot, packed_3bit_int_properties),
653                                pilot.getNode ("sim/multiplay/generic/int[4]", 1),
654                                3),
655        NormalizedFloatDecoder.new (getNodes (pilot, packed_mixture_properties),
656                                    pilot.getNode ("sim/multiplay/generic/int[5]", 1)),
657        NormalizedFloatDecoder.new (getNodes (pilot, packed_throttle_properties),
658                                    pilot.getNode ("sim/multiplay/generic/int[6]", 1)),
659        TDMDecoder.new (pilot.getNode ("sim/multiplay/generic/string[0]", 1),
660                        pilot,
661                        pilot_to_engineer_properties_string0),
662        SwitchDecoder.new (pilot.getNode ("sim/multiplay/generic/int[2]", 1),
663                           pilot,
664                           packed_boolean_properties)
665    ];
666    forindex (var j; engineer_to_pilot_properties) {
667        var transmitted_engineer_node = props.globals.getNode (engineer_to_pilot_properties_transmitted[j], 1);
668        var engineer_node = props.globals.getNode (engineer_to_pilot_properties[j], 1);
669        transmitted_engineer_node.alias (engineer_node);
670    }
671    forindex (var j; pilot_to_engineer_properties) {
672        var transmitted_pilot_node = pilot.getNode (pilot_to_engineer_properties_transmitted[j], 1);
673        var pilot_node = pilot.getNode (pilot_to_engineer_properties[j], 1);
674        pilot_node.alias (transmitted_pilot_node);
675    }
676    var rpm0 = pilot.getNode ("controls/engines/engine[0]/propeller-pitch");
677    # propeller-pitch is special: propagate it to all other engines as there is only one command for all 4.
678    result ~= [
679        DCT.Translator.new (rpm0, pilot.getNode ("controls/engines/engine[1]/propeller-pitch", 1)),
680        DCT.Translator.new (rpm0, pilot.getNode ("controls/engines/engine[2]/propeller-pitch", 1)),
681        DCT.Translator.new (rpm0, pilot.getNode ("controls/engines/engine[3]/propeller-pitch", 1)) ];
682    foreach (var prop; packed_2bit_int_properties) {
683        var pilot_node = pilot.getNode (prop, "INT", 1);
684        var engineer_node = props.globals.getNode (prop, "INT", 1);
685        result ~= [ DCT.MostRecentSelector.new (pilot_node, engineer_node, engineer_node, 0.9) ];
686    }
687    foreach (var prop; packed_3bit_int_properties) {
688        var pilot_node = pilot.getNode (prop, "INT", 1);
689        var engineer_node = props.globals.getNode (prop, "INT", 1);
690        result ~= [ DCT.MostRecentSelector.new (pilot_node, engineer_node, engineer_node, 0.9) ];
691    }
692    foreach (var prop; packed_boolean_properties) {
693        var engineer_node = pilot.getNode (prop, "BOOL", 1);
694        var pilot_node = props.globals.getNode (prop, "BOOL", 1);
695        result ~= [ DCT.MostRecentSelector.new (pilot_node, engineer_node, engineer_node, 0.1) ];
696    }
697    foreach (var prop; packed_mixture_properties) {
698        var engineer_node = pilot.getNode (prop, "DOUBLE", 1);
699        var pilot_node = props.globals.getNode (prop, "DOUBLE", 1);
700        result ~= [ DCT.MostRecentSelector.new (pilot_node, engineer_node, engineer_node, 1 / 127) ];
701    }
702    foreach (var prop; packed_throttle_properties) {
703        var engineer_node = pilot.getNode (prop, "DOUBLE", 1);
704        var pilot_node = props.globals.getNode (prop, "DOUBLE", 1);
705        result ~= [ DCT.MostRecentSelector.new (pilot_node, engineer_node, engineer_node, 1 / 127) ];
706    }
707    result ~= [
708        MultiBitIntEncoder.new (getNodes (props.globals, packed_2bit_int_properties),
709                                props.globals.getNode ("sim/multiplay/generic/int[3]", 1),
710                                2),
711        MultiBitIntEncoder.new (getNodes (props.globals, packed_3bit_int_properties),
712                                props.globals.getNode ("sim/multiplay/generic/int[4]", 1),
713                                3),
714        NormalizedFloatEncoder.new (getNodes (props.globals, packed_mixture_properties),
715                                props.globals.getNode ("sim/multiplay/generic/int[5]", 1)),
716        NormalizedFloatEncoder.new (getNodes (props.globals, packed_throttle_properties),
717                                props.globals.getNode ("sim/multiplay/generic/int[6]", 1)),
718        DCT.SwitchEncoder.new (getNodes (props.globals, packed_boolean_properties),
719                               props.globals.getNode ("sim/multiplay/generic/int[19]", 1))
720    ];
721    return result;
722}
723
724copilot_disconnect_pilot = func () { connected = 0; }
725