rusEFI
The most advanced open source ECU
Loading...
Searching...
No Matches
tunerstudio.cpp
Go to the documentation of this file.
1/**
2 * @file tunerstudio.cpp
3 * @brief Binary protocol implementation
4 *
5 * This implementation would not happen without the documentation
6 * provided by Jon Zeeff (jon@zeeff.com)
7 *
8 *
9 * @brief Integration with EFI Analytics Tuner Studio software
10 *
11 * Tuner Studio has a really simple protocol, a minimal implementation
12 * capable of displaying current engine state on the gauges would
13 * require only two commands: queryCommand and ochGetCommand
14 *
15 * queryCommand:
16 * Communication initialization command. TunerStudio sends a single byte H
17 * ECU response:
18 * One of the known ECU id strings.
19 *
20 * ochGetCommand:
21 * Request for output channels state.TunerStudio sends a single byte O
22 * ECU response:
23 * A snapshot of output channels as described in [OutputChannels] section of the .ini file
24 * The length of this block is 'ochBlockSize' property of the .ini file
25 *
26 * These two commands are enough to get working gauges. In order to start configuring the ECU using
27 * tuner studio, three more commands should be implemented:
28 *
29 * See also https://www.efianalytics.com/TunerStudio/docs/EFI%20Analytics%20ECU%20Definition%20files.pdf
30 *
31 *
32 * @date Oct 22, 2013
33 * @author Andrey Belomutskiy, (c) 2012-2020
34 *
35 * This file is part of rusEfi - see http://rusefi.com
36 *
37 * rusEfi is free software; you can redistribute it and/or modify it under the terms of
38 * the GNU General Public License as published by the Free Software Foundation; either
39 * version 3 of the License, or (at your option) any later version.
40 *
41 * rusEfi is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without
42 * even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
43 * GNU General Public License for more details.
44 *
45 * You should have received a copy of the GNU General Public License along with this program.
46 * If not, see <http://www.gnu.org/licenses/>.
47 *
48 *
49 * This file is part of rusEfi - see http://rusefi.com
50 *
51 * rusEfi is free software; you can redistribute it and/or modify it under the terms of
52 * the GNU General Public License as published by the Free Software Foundation; either
53 * version 3 of the License, or (at your option) any later version.
54 *
55 * rusEfi is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without
56 * even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
57 * GNU General Public License for more details.
58 *
59 * You should have received a copy of the GNU General Public License along with this program.
60 * If not, see <http://www.gnu.org/licenses/>.
61 *
62 */
63
64#include "pch.h"
65
66
67#include "tunerstudio.h"
68#include "tunerstudio_impl.h"
69
71#include "flash_main.h"
72
73#include "tunerstudio_io.h"
74#include "malfunction_central.h"
75#include "console_io.h"
76#include "bluetooth.h"
77#include "tunerstudio_io.h"
78#include "trigger_scope.h"
79#include "electronic_throttle.h"
80#include "live_data.h"
81#include "efi_quote.h"
82
83#include <string.h>
84#include "bench_test.h"
85#include "status_loop.h"
86#include "mmc_card.h"
88
89#if EFI_SIMULATOR
90#include "rusEfiFunctionalTest.h"
91#endif /* EFI_SIMULATOR */
92
93#if EFI_TUNER_STUDIO
94
95static void printErrorCounters() {
96 efiPrintf("TunerStudio size=%d / total=%d / errors=%d / H=%d / O=%d / P=%d / B=%d",
99 efiPrintf("TunerStudio W=%d / C=%d", tsState.writeValueCommandCounter,
101 efiPrintf("TunerStudio errors: underrun=%d / overrun=%d / crc=%d / unrecognized=%d / outofrange=%d / other=%d",
104}
105
106static void printScatterList() {
107 efiPrintf("Scatter list (global)");
108 for (int i = 0; i < HIGH_SPEED_COUNT; i++) {
109 uint16_t packed = engineConfiguration->highSpeedOffsets[i];
110 uint16_t type = packed >> 13;
111 uint16_t offset = packed & 0x1FFF;
112
113 if (type == 0)
114 continue;
115 size_t size = 1 << (type - 1);
116
117 efiPrintf("%02d offset 0x%04x size %d", i, offset, size);
118 }
119}
120
121/* 1S */
122#define TS_COMMUNICATION_TIMEOUT TIME_MS2I(1000)
123/* 10mS when receiving byte by byte */
124#define TS_COMMUNICATION_TIMEOUT_SHORT TIME_MS2I(10)
125
126static void resetTs() {
127 memset(&tsState, 0, sizeof(tsState));
128}
129
130static void printTsStats(void) {
131#ifdef EFI_CONSOLE_RX_BRAIN_PIN
132 efiPrintf("Primary UART RX %s", hwPortname(EFI_CONSOLE_RX_BRAIN_PIN));
133 efiPrintf("Primary UART TX %s", hwPortname(EFI_CONSOLE_TX_BRAIN_PIN));
134#endif /* EFI_CONSOLE_RX_BRAIN_PIN */
135
136#if EFI_USB_SERIAL
138#endif // EFI_USB_SERIAL
139
141
143}
144
145static void setTsSpeed(int value) {
147 printTsStats();
148}
149
150void tunerStudioDebug(TsChannelBase* tsChannel, const char *msg) {
151#if EFI_TUNER_STUDIO_VERBOSE
152 efiPrintf("%s: %s", tsChannel->name, msg);
153#endif /* EFI_TUNER_STUDIO_VERBOSE */
154}
155
157 return (uint8_t*)engineConfiguration;
158}
159
160static void sendOkResponse(TsChannelBase *tsChannel) {
161 tsChannel->sendResponse(TS_CRC, nullptr, 0);
162}
163
164void sendErrorCode(TsChannelBase *tsChannel, uint8_t code, const char *msg) {
165//TODO uncomment once I have test it myself if (msg != DO_NOT_LOG) {
166// efiPrintf("TS <- Err: %d [%s]", code, msg);
167// }
168
169 switch (code) {
170 case TS_RESPONSE_UNDERRUN:
172 break;
173 case TS_RESPONSE_OVERRUN:
175 break;
176 case TS_RESPONSE_CRC_FAILURE:
178 break;
179 case TS_RESPONSE_UNRECOGNIZED_COMMAND:
181 break;
182 case TS_RESPONSE_OUT_OF_RANGE:
184 break;
185 default:
187 break;
188 }
189
190 tsChannel->writeCrcResponse(code);
191}
192
193void TunerStudio::sendErrorCode(TsChannelBase* tsChannel, uint8_t code, const char *msg) {
194 ::sendErrorCode(tsChannel, code, msg);
195}
196
197bool validateOffsetCount(size_t offset, size_t count, TsChannelBase* tsChannel);
198
199PUBLIC_API_WEAK bool isBoardAskingTriggerTsRefresh() {
200 return false;
201}
202
204 return !engine->engineTypeChangeTimer.hasElapsedSec(1);
205}
206
209}
210
211/**
212 * This command is needed to make the whole transfer a bit faster
213 */
214void TunerStudio::handleWriteChunkCommand(TsChannelBase* tsChannel, uint16_t page, uint16_t offset, uint16_t count,
215 void *content) {
217
218 efiPrintf("TS -> Page %d write chunk offset %d count %d (output_count=%d)",
219 page, offset, count, tsState.outputChannelsCommandCounter);
220
221 if (page == 0) {
222 if (isLockedFromUser()) {
223 sendErrorCode(tsChannel, TS_RESPONSE_UNRECOGNIZED_COMMAND, "locked");
224 return;
225 }
226
227 if (validateOffsetCount(offset, count, tsChannel)) {
228 tunerStudioError(tsChannel, "ERROR: WR out of range");
229 sendErrorCode(tsChannel, TS_RESPONSE_OUT_OF_RANGE);
230 return;
231 }
232
233 // Skip the write if a preset was just loaded - we don't want to overwrite it
234 if (!needToTriggerTsRefresh()) {
235 uint8_t * addr = (uint8_t *) (getWorkingPageAddr() + offset);
236 memcpy(addr, content, count);
237 }
238 // Force any board configuration options that humans shouldn't be able to change
240
241 sendOkResponse(tsChannel);
242 } else {
243 sendErrorCode(tsChannel, TS_RESPONSE_OUT_OF_RANGE, "ERROR: WR invalid page");
244 }
245}
246
247void TunerStudio::handleCrc32Check(TsChannelBase *tsChannel, uint16_t offset, uint16_t count) {
249
250 // Ensure we are reading from in bounds
251 if (validateOffsetCount(offset, count, tsChannel)) {
252 tunerStudioError(tsChannel, "ERROR: CRC out of range");
253 sendErrorCode(tsChannel, TS_RESPONSE_OUT_OF_RANGE);
254 return;
255 }
256
257#if EFI_TS_SCATTER
258 /*
259 * highSpeedOffsets is noMsqSave, but located on settings page,
260 * zero highSpeedOffsets as TS expect all noMsqSave data to be zero during CRC matching
261 * TODO:
262 * Move highSpeedOffsets to separate page as it is done on MS devices
263 * Zero highSpeedOffsets on start and reconnect
264 * TODO:
265 * Is Crc check command good sing of new TS session?
266 * TODO:
267 * Support settings pages!
268 */
270#endif // EFI_TS_SCATTER
271
272 const uint8_t* start = getWorkingPageAddr() + offset;
273
274 uint32_t crc = SWAP_UINT32(crc32(start, count));
275 tsChannel->sendResponse(TS_CRC, (const uint8_t *) &crc, 4);
276 efiPrintf("TS <- Get CRC offset %d count %d result %08x", offset, count, (unsigned int)crc);
277}
278
279#if EFI_TS_SCATTER
281 int totalResponseSize = 0;
282 for (int i = 0; i < HIGH_SPEED_COUNT; i++) {
283 uint16_t packed = engineConfiguration->highSpeedOffsets[i];
284 uint16_t type = packed >> 13;
285
286 size_t size = type == 0 ? 0 : 1 << (type - 1);
287#if EFI_SIMULATOR
288// printf("handleScatteredReadCommand 0x%x %d %d\n", packed, size, offset);
289#endif /* EFI_SIMULATOR */
290 totalResponseSize += size;
291 }
292#if EFI_SIMULATOR
293// printf("totalResponseSize %d\n", totalResponseSize);
294#endif /* EFI_SIMULATOR */
295
296
297 // Command part of CRC
298 uint32_t crc = tsChannel->writePacketHeader(TS_RESPONSE_OK, totalResponseSize);
299
300 uint8_t dataBuffer[8];
301 for (int i = 0; i < HIGH_SPEED_COUNT; i++) {
302 uint16_t packed = engineConfiguration->highSpeedOffsets[i];
303 uint16_t type = packed >> 13;
304 uint16_t offset = packed & 0x1FFF;
305
306 if (type == 0)
307 continue;
308 size_t size = 1 << (type - 1);
309
310 // write each data point and CRC incrementally
311 copyRange(dataBuffer, getLiveDataFragments(), offset, size);
312 tsChannel->write(dataBuffer, size, false);
313 crc = crc32inc((void*)dataBuffer, crc, size);
314 }
315#if EFI_SIMULATOR
316// printf("CRC %x\n", crc);
317#endif /* EFI_SIMULATOR */
318 // now write total CRC
319 *(uint32_t*)dataBuffer = SWAP_UINT32(crc);
320 tsChannel->write(reinterpret_cast<uint8_t*>(dataBuffer), 4, true);
321 tsChannel->flush();
322}
323#endif // EFI_TS_SCATTER
324
325void TunerStudio::handlePageReadCommand(TsChannelBase* tsChannel, uint16_t page, uint16_t offset, uint16_t count) {
327
328 efiPrintf("TS <- Page %d read chunk offset %d count %d", page, offset, count);
329
330 if (page == 0) {
331 if (validateOffsetCount(offset, count, tsChannel)) {
332 tunerStudioError(tsChannel, "ERROR: RD out of range");
333 sendErrorCode(tsChannel, TS_RESPONSE_OUT_OF_RANGE);
334 return;
335 }
336
337 uint8_t* addr;
338 if (isLockedFromUser()) {
339 // to have rusEFI console happy just send all zeros within a valid packet
340 addr = (uint8_t*)&tsChannel->scratchBuffer + TS_PACKET_HEADER_SIZE;
341 memset(addr, 0, count);
342 } else {
343 addr = getWorkingPageAddr() + offset;
344 }
345 tsChannel->sendResponse(TS_CRC, addr, count);
346#if EFI_TUNER_STUDIO_VERBOSE
347// efiPrintf("Sending %d done", count);
348#endif
349 } else {
350 sendErrorCode(tsChannel, TS_RESPONSE_OUT_OF_RANGE, "ERROR: RD invalid page");
351 }
352}
353#endif // EFI_TUNER_STUDIO
354
356#if !EFI_UNIT_TEST
358
359#if EFI_CONFIGURATION_STORAGE
361#endif /* EFI_CONFIGURATION_STORAGE */
362#endif // !EFI_UNIT_TEST
363}
364
365#if EFI_TUNER_STUDIO
366
367namespace {
368 Timer calibrationsWriteTimer;
369}
370
371/**
372 * 'Burn' command is a command to commit the changes
373 */
374static void handleBurnCommand(TsChannelBase* tsChannel) {
375 Timer t;
376 t.reset();
377
379
380 efiPrintf("TS -> Burn");
382
383 // Skip the burn if a preset was just loaded - we don't want to overwrite it
384 if (!needToTriggerTsRefresh()) {
385 requestBurn();
386 }
387
388 tsChannel->writeCrcResponse(TS_RESPONSE_BURN_OK);
389 efiPrintf("Burned in %.1fms", t.getElapsedSeconds() * 1e3);
390}
391
392#if (EFI_PROD_CODE || EFI_SIMULATOR)
393
394static bool isKnownCommand(char command) {
395 return command == TS_HELLO_COMMAND || command == TS_READ_COMMAND || command == TS_OUTPUT_COMMAND
396 || command == TS_BURN_COMMAND || command == TS_SINGLE_WRITE_COMMAND
397 || command == TS_CHUNK_WRITE_COMMAND || command == TS_EXECUTE
398 || command == TS_IO_TEST_COMMAND
399#if EFI_SIMULATOR
400 || command == TS_SIMULATE_CAN
401#endif // EFI_SIMULATOR
402#if EFI_TS_SCATTER
403 || command == TS_GET_SCATTERED_GET_COMMAND
404#endif
405 || command == TS_SET_LOGGER_SWITCH
406 || command == TS_GET_COMPOSITE_BUFFER_DONE_DIFFERENTLY
407 || command == TS_GET_TEXT
408 || command == TS_CRC_CHECK_COMMAND
409 || command == TS_GET_FIRMWARE_VERSION
410 || command == TS_PERF_TRACE_BEGIN
411 || command == TS_PERF_TRACE_GET_BUFFER
412 || command == TS_GET_CONFIG_ERROR
413 || command == TS_QUERY_BOOTLOADER;
414}
415
416/**
417 * rusEfi own test command
418 */
419static void handleTestCommand(TsChannelBase* tsChannel) {
421 char testOutputBuffer[64];
422 /**
423 * this is NOT a standard TunerStudio command, this is my own
424 * extension of the protocol to simplify troubleshooting
425 */
426 tunerStudioDebug(tsChannel, "got T (Test)");
427 tsChannel->write((const uint8_t*)QUOTE(SIGNATURE_HASH), sizeof(QUOTE(SIGNATURE_HASH)));
428
429 chsnprintf(testOutputBuffer, sizeof(testOutputBuffer), " %d %d", engine->engineState.warnings.lastErrorCode, tsState.testCommandCounter);
430 tsChannel->write((const uint8_t*)testOutputBuffer, strlen(testOutputBuffer));
431
432 chsnprintf(testOutputBuffer, sizeof(testOutputBuffer), " uptime=%ds ", (int)getTimeNowS());
433 tsChannel->write((const uint8_t*)testOutputBuffer, strlen(testOutputBuffer));
434
435 chsnprintf(testOutputBuffer, sizeof(testOutputBuffer), __DATE__ " %s\r\n", PROTOCOL_TEST_RESPONSE_TAG);
436 tsChannel->write((const uint8_t*)testOutputBuffer, strlen(testOutputBuffer));
437
438 if (hasFirmwareError()) {
439 const char* error = getCriticalErrorMessage();
440 chsnprintf(testOutputBuffer, sizeof(testOutputBuffer), "error=%s\r\n", error);
441 tsChannel->write((const uint8_t*)testOutputBuffer, strlen(testOutputBuffer));
442 }
443 tsChannel->flush();
444}
445
446/**
447 * this command is part of protocol initialization
448 *
449 * Query with CRC takes place while re-establishing connection
450 * Query without CRC takes place on TunerStudio startup
451 */
454 const char *signature = getTsSignature();
455
456 efiPrintf("TS <- Query signature: %s", signature);
457 tsChannel->sendResponse(mode, (const uint8_t *)signature, strlen(signature) + 1);
458}
459
460/**
461 * handle non CRC wrapped command
462 *
463 * @return true if legacy command was processed, false otherwise
464 */
465bool TunerStudio::handlePlainCommand(TsChannelBase* tsChannel, uint8_t command) {
466 // Bail fast if guaranteed not to be a plain command
467 if (command == 0) {
468 return false;
469 } else if (command == TS_HELLO_COMMAND || command == TS_QUERY_COMMAND) {
470 // We interpret 'Q' as TS_HELLO_COMMAND, since TS uses hardcoded 'Q' during ECU detection (scan all serial ports)
471 efiPrintf("Got naked Query command");
472 handleQueryCommand(tsChannel, TS_PLAIN);
473 return true;
474 } else if (command == TS_TEST_COMMAND || command == 'T') {
475 handleTestCommand(tsChannel);
476 return true;
477 } else if (command == TS_COMMAND_F) {
478 /**
479 * http://www.msextra.com/forums/viewtopic.php?f=122&t=48327
480 * Response from TS support: This is an optional command *
481 * "The F command is used to find what ini. file needs to be loaded in TunerStudio to match the controller.
482 * If you are able to just make your firmware ignore the command that would work.
483 * Currently on some firmware versions the F command is not used and is just ignored by the firmware as a unknown command."
484 */
485
486 tunerStudioDebug(tsChannel, "not ignoring F");
487 tsChannel->write((const uint8_t *)TS_PROTOCOL, strlen(TS_PROTOCOL));
488 tsChannel->flush();
489 return true;
490 } else {
491 // This wasn't a valid command
492 return false;
493 }
494}
495
497
498static int tsProcessOne(TsChannelBase* tsChannel) {
499 assertStack("communication", ObdCode::STACK_USAGE_COMMUNICATION, EXPECTED_REMAINING_STACK, -1);
500
501 if (!tsChannel->isReady()) {
502 chThdSleepMilliseconds(10);
503 return -1;
504 }
505
507
508 uint8_t firstByte;
509 size_t received = tsChannel->readTimeout(&firstByte, 1, TS_COMMUNICATION_TIMEOUT);
510#if EFI_SIMULATOR
511 logMsg("received %d\r\n", received);
512#endif // EFI_SIMULATOR
513
514 if (received != 1) {
515// tunerStudioError("ERROR: no command");
516#if EFI_BLUETOOTH_SETUP
517 if (tsChannel == getBluetoothChannel()) {
518 // no data in a whole second means time to disconnect BT
519 // assume there's connection loss and notify the bluetooth init code
521 }
522#endif /* EFI_BLUETOOTH_SETUP */
523 tsChannel->in_sync = false;
524 return -1;
525 }
526
527 if (tsInstance.handlePlainCommand(tsChannel, firstByte)) {
528 return 0;
529 }
530
531 uint8_t secondByte;
532 /* second byte should be received within minimal delay */
533 received = tsChannel->readTimeout(&secondByte, 1, TS_COMMUNICATION_TIMEOUT_SHORT);
534 if (received != 1) {
535 tunerStudioError(tsChannel, "TS: ERROR: no second byte");
536 tsChannel->in_sync = false;
537 return -1;
538 }
539
540 uint16_t incomingPacketSize = firstByte << 8 | secondByte;
541 size_t expectedSize = incomingPacketSize + TS_PACKET_TAIL_SIZE;
542
543 if ((incomingPacketSize == 0) || (expectedSize > sizeof(tsChannel->scratchBuffer))) {
544 if (tsChannel->in_sync) {
545 efiPrintf("process_ts: channel=%s invalid size: %d", tsChannel->name, incomingPacketSize);
546 tunerStudioError(tsChannel, "process_ts: ERROR: packet size");
547 /* send error only if previously we were in sync */
548 sendErrorCode(tsChannel, TS_RESPONSE_OUT_OF_RANGE, "invalid size");
549 }
550 tsChannel->in_sync = false;
551 return -1;
552 }
553
554 char command;
555 if (tsChannel->in_sync) {
556 /* we are in sync state, packet size should be correct so lets receive full packet and then check if command is supported
557 * otherwise (if abort reception in middle of packet) it will break synchronization and cause error on next packet */
558 received = tsChannel->readTimeout((uint8_t*)(tsChannel->scratchBuffer), expectedSize, TS_COMMUNICATION_TIMEOUT);
559 command = tsChannel->scratchBuffer[0];
560
561 if (received != expectedSize) {
562 /* print and send error as we were in sync */
563 efiPrintf("Got only %d bytes while expecting %d for command 0x%02x", received,
564 expectedSize, command);
565 tunerStudioError(tsChannel, "ERROR: not enough bytes in stream");
566 // MS serial protocol spec: There was a timeout before all data was received. (25ms per character.)
567 sendErrorCode(tsChannel, TS_RESPONSE_UNDERRUN, "underrun");
568 tsChannel->in_sync = false;
569 return -1;
570 }
571
572 if (!isKnownCommand(command)) {
573 /* print and send error as we were in sync */
574 efiPrintf("unexpected command %x", command);
575 sendErrorCode(tsChannel, TS_RESPONSE_UNRECOGNIZED_COMMAND, "unknown");
576 tsChannel->in_sync = false;
577 return -1;
578 }
579 } else {
580 /* receive only command byte to check if it is supported */
581 received = tsChannel->readTimeout((uint8_t*)(tsChannel->scratchBuffer), 1, TS_COMMUNICATION_TIMEOUT_SHORT);
582 command = tsChannel->scratchBuffer[0];
583
584 if (!isKnownCommand(command)) {
585 /* do not report any error as we are not in sync */
586 return -1;
587 }
588
589 received = tsChannel->readTimeout((uint8_t*)(tsChannel->scratchBuffer) + 1, expectedSize - 1, TS_COMMUNICATION_TIMEOUT);
590 if (received != expectedSize - 1) {
591 /* do not report any error as we are not in sync */
592 return -1;
593 }
594 }
595
596#if EFI_SIMULATOR
597 logMsg("command %c\r\n", command);
598#endif
599
600 uint32_t expectedCrc = *(uint32_t*) (tsChannel->scratchBuffer + incomingPacketSize);
601
602 expectedCrc = SWAP_UINT32(expectedCrc);
603
604 uint32_t actualCrc = crc32(tsChannel->scratchBuffer, incomingPacketSize);
605 if (actualCrc != expectedCrc) {
606 /* send error only if previously we were in sync */
607 if (tsChannel->in_sync) {
608 efiPrintf("TunerStudio: command %c actual CRC %x/expected %x", tsChannel->scratchBuffer[0],
609 (unsigned int)actualCrc, (unsigned int)expectedCrc);
610 tunerStudioError(tsChannel, "ERROR: CRC issue");
611 sendErrorCode(tsChannel, TS_RESPONSE_CRC_FAILURE, "crc_issue");
612 tsChannel->in_sync = false;
613 }
614 return -1;
615 }
616
617 /* we were able to receive known command with correct crc and size! */
618 tsChannel->in_sync = true;
619
620 int success = tsInstance.handleCrcCommand(tsChannel, tsChannel->scratchBuffer, incomingPacketSize);
621
622 if (!success) {
623 efiPrintf("got unexpected TunerStudio command %x:%c", command, command);
624 return -1;
625 }
626
627 return 0;
628}
629
631 auto channel = setupChannel();
632
633 // No channel configured for this thread, cancel.
634 if (!channel || !channel->isConfigured()) {
635 return;
636 }
637
638 // Until the end of time, process incoming messages.
639 while (true) {
640 if (tsProcessOne(channel) == 0) {
641 onDataArrived(true);
642 } else {
643 onDataArrived(false);
644 }
645 }
646}
647
648#endif // EFI_PROD_CODE || EFI_SIMULATOR
650
651void tunerStudioError(TsChannelBase* tsChannel, const char *msg) {
652 tunerStudioDebug(tsChannel, msg);
655}
656
657#if EFI_PROD_CODE || EFI_SIMULATOR
658
660
661// see also handleQueryCommand
662// see also printVersionForConsole
663static void handleGetVersion(TsChannelBase* tsChannel) {
664 char versionBuffer[32];
665 chsnprintf(versionBuffer, sizeof(versionBuffer), "%s v%d@%u", FRONTEND_TITLE_BAR_NAME, getRusEfiVersion(), SIGNATURE_HASH);
666 tsChannel->sendResponse(TS_CRC, (const uint8_t *) versionBuffer, strlen(versionBuffer) + 1);
667}
668
669#if EFI_TEXT_LOGGING
670static void handleGetText(TsChannelBase* tsChannel) {
672
674
675 size_t outputSize;
676 const char* output = swapOutputBuffers(&outputSize);
677#if EFI_SIMULATOR
678 logMsg("get test sending [%d]\r\n", outputSize);
679#endif
680
681 tsChannel->writeCrcPacket(TS_RESPONSE_OK, reinterpret_cast<const uint8_t*>(output), outputSize, true);
682#if EFI_SIMULATOR
683 logMsg("sent [%d]\r\n", outputSize);
684#endif // EFI_SIMULATOR
685}
686#endif // EFI_TEXT_LOGGING
687
688void TunerStudio::handleExecuteCommand(TsChannelBase* tsChannel, char *data, int incomingPacketSize) {
689 data[incomingPacketSize] = 0;
690 char *trimmed = efiTrim(data);
691#if EFI_SIMULATOR
692 logMsg("execute [%s]\r\n", trimmed);
693#endif // EFI_SIMULATOR
694 (console_line_callback)(trimmed);
695
696 tsChannel->writeCrcResponse(TS_RESPONSE_OK);
697}
698
699int TunerStudio::handleCrcCommand(TsChannelBase* tsChannel, char *data, int incomingPacketSize) {
701
702 char command = data[0];
703 data++;
704
705 const uint16_t* data16 = reinterpret_cast<uint16_t*>(data);
706
707 // only few command have page argument, default page is 0
708 uint16_t page = 0;
709 uint16_t offset = 0;
710 uint16_t count = 0;
711
712 // command may not have offset field - keep safe default value
713 // not used by .ini at the moment TODO actually use that version of the command in the .ini
714 if (incomingPacketSize >= 3) {
715 offset = data16[0];
716 }
717 // command may not have count/size filed - keep safe default value
718 if (incomingPacketSize >= 5) {
719 count = data16[1];
720 }
721
722 switch(command)
723 {
724 case TS_OUTPUT_COMMAND:
725 if (incomingPacketSize == 1) {
726 // Read command with no offset and size - read whole livedata
727 count = TS_TOTAL_OUTPUT_SIZE;
728 }
729 cmdOutputChannels(tsChannel, offset, count);
730 break;
731 case TS_OUTPUT_ALL_COMMAND:
732 offset = 0;
733 count = TS_TOTAL_OUTPUT_SIZE;
734 // TS will not use this command until ochBlockSize is bigger than blockingFactor and prefer ochGetCommand :(
735 cmdOutputChannels(tsChannel, offset, count);
736 break;
737 case TS_HELLO_COMMAND:
738 tunerStudioDebug(tsChannel, "got Query command");
739 handleQueryCommand(tsChannel, TS_CRC);
740 break;
741 case TS_GET_FIRMWARE_VERSION:
742 handleGetVersion(tsChannel);
743 break;
744#if EFI_TEXT_LOGGING
745 case TS_GET_TEXT:
746 handleGetText(tsChannel);
747 break;
748#endif // EFI_TEXT_LOGGING
749 case TS_EXECUTE:
750 handleExecuteCommand(tsChannel, data, incomingPacketSize - 1);
751 break;
752 case TS_CHUNK_WRITE_COMMAND:
753 // command with no page argument, default page = 0
754 handleWriteChunkCommand(tsChannel, page, offset, count, data + sizeof(TunerStudioRWChunkRequest));
755 calibrationsWriteTimer.reset();
756 break;
757 case TS_SINGLE_WRITE_COMMAND:
758 // command with no page argument, default page = 0
759 // This command writes 1 byte
760 count = 1;
761 handleWriteChunkCommand(tsChannel, page, offset, count, data + sizeof(offset));
762 calibrationsWriteTimer.reset();
763 break;
764 case TS_GET_SCATTERED_GET_COMMAND:
765#if EFI_TS_SCATTER
767#else
768 criticalError("Slow/wireless mode not supported");
769#endif // EFI_TS_SCATTER
770 break;
771 case TS_CRC_CHECK_COMMAND:
772 handleCrc32Check(tsChannel, offset, count);
773 break;
774 case TS_BURN_COMMAND:
775 handleBurnCommand(tsChannel);
776 break;
777 case TS_READ_COMMAND:
778 // command with no page argument, default page = 0
779 handlePageReadCommand(tsChannel, page, offset, count);
780 break;
781 case TS_TEST_COMMAND:
782 [[fallthrough]];
783 case 'T':
784 handleTestCommand(tsChannel);
785 break;
786#if EFI_SIMULATOR
787 case TS_SIMULATE_CAN:
788 void handleWrapCan(TsChannelBase* tsChannel, char *data, int incomingPacketSize);
789 handleWrapCan(tsChannel, data, incomingPacketSize - 1);
790 break;
791#endif // EFI_SIMULATOR
792 case TS_IO_TEST_COMMAND:
793 {
794#if EFI_PROD_CODE
795 uint16_t subsystem = SWAP_UINT16(data16[0]);
796 uint16_t index = SWAP_UINT16(data16[1]);
797
798 executeTSCommand(subsystem, index);
799#endif /* EFI_PROD_CODE */
800 sendOkResponse(tsChannel);
801 }
802 break;
803#if EFI_TOOTH_LOGGER
804 case TS_SET_LOGGER_SWITCH:
805 switch(data[0]) {
806 case TS_COMPOSITE_ENABLE:
808 break;
809 case TS_COMPOSITE_DISABLE:
811 break;
812 case TS_COMPOSITE_READ:
813 {
814 auto toothBuffer = GetToothLoggerBufferNonblocking();
815
816 if (toothBuffer) {
817 tsChannel->sendResponse(TS_CRC, reinterpret_cast<const uint8_t*>(toothBuffer->buffer), toothBuffer->nextIdx * sizeof(composite_logger_s), true);
818
819 ReturnToothLoggerBuffer(toothBuffer);
820 } else {
821 // TS asked for a tooth logger buffer, but we don't have one to give it.
822 sendErrorCode(tsChannel, TS_RESPONSE_OUT_OF_RANGE, DO_NOT_LOG);
823 }
824 }
825 break;
826#ifdef TRIGGER_SCOPE
827 case TS_TRIGGER_SCOPE_ENABLE:
829 break;
830 case TS_TRIGGER_SCOPE_DISABLE:
832 break;
833 case TS_TRIGGER_SCOPE_READ:
834 {
835 const auto& buffer = triggerScopeGetBuffer();
836
837 if (buffer) {
838 tsChannel->sendResponse(TS_CRC, buffer.get<uint8_t>(), buffer.size(), true);
839 } else {
840 // TS asked for a tooth logger buffer, but we don't have one to give it.
841 sendErrorCode(tsChannel, TS_RESPONSE_OUT_OF_RANGE, DO_NOT_LOG);
842 }
843 }
844 break;
845#endif // TRIGGER_SCOPE
846 default:
847 // dunno what that was, send NAK
848 return false;
849 }
850
851 sendOkResponse(tsChannel);
852
853 break;
854 case TS_GET_COMPOSITE_BUFFER_DONE_DIFFERENTLY:
855 {
857
858 auto toothBuffer = GetToothLoggerBufferNonblocking();
859
860 if (toothBuffer) {
861 tsChannel->sendResponse(TS_CRC, reinterpret_cast<const uint8_t*>(toothBuffer->buffer), toothBuffer->nextIdx * sizeof(composite_logger_s), true);
862
863 ReturnToothLoggerBuffer(toothBuffer);
864 } else {
865 // TS asked for a tooth logger buffer, but we don't have one to give it.
866 sendErrorCode(tsChannel, TS_RESPONSE_OUT_OF_RANGE, DO_NOT_LOG);
867 }
868 }
869
870 break;
871#else // EFI_TOOTH_LOGGER
872 case TS_GET_COMPOSITE_BUFFER_DONE_DIFFERENTLY:
873 sendErrorCode(tsChannel, TS_RESPONSE_OUT_OF_RANGE, DO_NOT_LOG);
874 break;
875#endif /* EFI_TOOTH_LOGGER */
876#if ENABLE_PERF_TRACE
877 case TS_PERF_TRACE_BEGIN:
879 sendOkResponse(tsChannel);
880 break;
881 case TS_PERF_TRACE_GET_BUFFER:
882 {
883 auto trace = perfTraceGetBuffer();
884 tsChannel->sendResponse(TS_CRC, trace.get<uint8_t>(), trace.size(), true);
885 }
886
887 break;
888#else
889 case TS_PERF_TRACE_BEGIN:
890 criticalError("TS_PERF_TRACE not supported");
891 break;
892 case TS_PERF_TRACE_GET_BUFFER:
893 criticalError("TS_PERF_TRACE_GET_BUFFER not supported");
894 break;
895#endif /* ENABLE_PERF_TRACE */
896 case TS_GET_CONFIG_ERROR: {
897 const char* configError = hasFirmwareError()? getCriticalErrorMessage() : getConfigErrorMessage();
898 tsChannel->sendResponse(TS_CRC, reinterpret_cast<const uint8_t*>(configError), strlen(configError), true);
899 break;
900 }
901 case TS_QUERY_BOOTLOADER: {
902 uint8_t bldata = TS_QUERY_BOOTLOADER_NONE;
903#if EFI_USE_OPENBLT
904 bldata = TS_QUERY_BOOTLOADER_OPENBLT;
905#endif
906
907 tsChannel->sendResponse(TS_CRC, &bldata, 1, false);
908 break;
909 }
910 default:
911 sendErrorCode(tsChannel, TS_RESPONSE_UNRECOGNIZED_COMMAND, "unknown_command");
912static char tsErrorBuff[80];
913 chsnprintf(tsErrorBuff, sizeof(tsErrorBuff), "ERROR: ignoring unexpected command %d [%c]", command, command);
914 tunerStudioError(tsChannel, tsErrorBuff);
915 return false;
916 }
917
918 return true;
919}
920
921#endif // EFI_PROD_CODE || EFI_SIMULATOR
922
925 !calibrationsWriteTimer.hasElapsedSec(TunerDetectorUtils::getUserEnteredTuningDetector());
926}
927
929 // Assert tune & output channel struct sizes
930 static_assert(sizeof(persistent_config_s) == TOTAL_CONFIG_SIZE, "TS datapage size mismatch");
931// useful trick if you need to know how far off is the static_assert
932// char (*__kaboom)[sizeof(persistent_config_s)] = 1;
933// another useful trick
934// static_assert(offsetof (engine_configuration_s,HD44780_e) == 700);
935
936 memset(&tsState, 0, sizeof(tsState));
937
939 addConsoleAction("reset_ts", resetTs);
940 addConsoleActionI("set_ts_speed", setTsSpeed);
941
942#if EFI_BLUETOOTH_SETUP
943 // module initialization start (it waits for disconnect and then communicates to the module)
944 // Usage: "bluetooth_hc06 <baud> <name> <pincode>"
945 // Example: "bluetooth_hc06 38400 rusefi 1234"
946 // bluetooth_jdy 115200 alphax 1234
947 addConsoleActionSSS("bluetooth_hc05", [](const char *baudRate, const char *name, const char *pinCode) {
948 bluetoothStart(BLUETOOTH_HC_05, baudRate, name, pinCode);
949 });
950 addConsoleActionSSS("bluetooth_hc06", [](const char *baudRate, const char *name, const char *pinCode) {
951 bluetoothStart(BLUETOOTH_HC_06, baudRate, name, pinCode);
952 });
953 addConsoleActionSSS("bluetooth_bk", [](const char *baudRate, const char *name, const char *pinCode) {
954 bluetoothStart(BLUETOOTH_BK3231, baudRate, name, pinCode);
955 });
956 addConsoleActionSSS("bluetooth_jdy", [](const char *baudRate, const char *name, const char *pinCode) {
957 bluetoothStart(BLUETOOTH_JDY_3x, baudRate, name, pinCode);
958 });
959 addConsoleActionSSS("bluetooth_jdy31", [](const char *baudRate, const char *name, const char *pinCode) {
960 bluetoothStart(BLUETOOTH_JDY_31, baudRate, name, pinCode);
961 });
962#endif /* EFI_BLUETOOTH_SETUP */
963}
964
965#endif // EFI_TUNER_STUDIO
uint16_t channel
Definition adc_inputs.h:107
constexpr uint8_t addr
Definition ads1015.cpp:5
void setBoardConfigOverrides()
void executeTSCommand(uint16_t subsystem, uint16_t index)
Utility methods related to bench testing.
void bluetoothSoftwareDisconnectNotify(SerialTsChannelBase *tsChannel)
uint8_t code
Definition bluetooth.cpp:40
void bluetoothStart(bluetooth_module_e moduleType, const char *baudRate, const char *name, const char *pinCode)
@ BLUETOOTH_HC_05
Definition bluetooth.h:22
@ BLUETOOTH_BK3231
Definition bluetooth.h:27
@ BLUETOOTH_JDY_3x
Definition bluetooth.h:29
@ BLUETOOTH_JDY_31
Definition bluetooth.h:30
@ BLUETOOTH_HC_06
Definition bluetooth.h:23
size_t size() const
Definition big_buffer.h:43
const TBuffer * get() const
Definition big_buffer.h:34
EngineState engineState
Definition engine.h:330
Timer engineTypeChangeTimer
Definition engine.h:295
TunerStudioOutputChannels outputChannels
Definition engine.h:105
WarningCodeState warnings
virtual bool isReady() const
virtual void flush()
const char * name
char scratchBuffer[scratchBuffer_SIZE+30]
uint32_t writePacketHeader(const uint8_t responseCode, const size_t size)
void writeCrcResponse(uint8_t responseCode)
virtual void writeCrcPacket(uint8_t responseCode, const uint8_t *buf, size_t size, bool allowLongPackets=false)
virtual void write(const uint8_t *buffer, size_t size, bool isEndOfPacket=false)=0
virtual size_t readTimeout(uint8_t *buffer, size_t size, int timeout)=0
void sendResponse(ts_response_format_e mode, const uint8_t *buffer, int size, bool allowLongPackets=false)
static uint8_t getUserEnteredTuningDetector()
static bool isTuningDetectorUndefined()
void sendErrorCode(TsChannelBase *tsChannel, uint8_t code, const char *msg="")
void handleScatteredReadCommand(TsChannelBase *tsChannel)
bool handlePlainCommand(TsChannelBase *tsChannel, uint8_t command)
void handleQueryCommand(TsChannelBase *tsChannel, ts_response_format_e mode)
void cmdOutputChannels(TsChannelBase *tsChannel, uint16_t offset, uint16_t count) override
'Output' command sends out a snapshot of current values Gauges refresh
void handleCrc32Check(TsChannelBase *tsChannel, uint16_t offset, uint16_t count)
void handlePageReadCommand(TsChannelBase *tsChannel, uint16_t page, uint16_t offset, uint16_t count)
void handleWriteChunkCommand(TsChannelBase *tsChannel, uint16_t page, uint16_t offset, uint16_t count, void *content)
int handleCrcCommand(TsChannelBase *tsChannel, char *data, int incomingPacketSize)
void handleExecuteCommand(TsChannelBase *tsChannel, char *data, int incomingPacketSize)
virtual TsChannelBase * setupChannel()=0
void ThreadTask() override
ObdCode lastErrorCode
void addConsoleAction(const char *token, Void callback)
Register console action without parameters.
void addConsoleActionSSS(const char *token, VoidCharPtrCharPtrCharPtr callback)
void addConsoleActionI(const char *token, VoidInt callback)
Register a console command with one Integer parameter.
void onDataArrived(bool valid)
void(* CommandHandler)(char *)
Definition console_io.h:10
void printUsbConnectorStats()
char * efiTrim(char *param)
Definition efilib.cpp:39
uint32_t SWAP_UINT32(uint32_t x)
Definition efilib.h:27
uint16_t SWAP_UINT16(uint16_t x)
Definition efilib.h:22
efitimesec_t getTimeNowS()
Current system time in seconds (32 bits)
Definition efitime.cpp:42
static Engine *const engine
Definition engine.h:389
bool isLockedFromUser()
Definition engine2.cpp:263
void onBurnRequest()
static constexpr engine_configuration_s * engineConfiguration
bool validateConfigOnStartUpOrBurn()
const char * getCriticalErrorMessage()
void configError(const char *fmt,...)
const char * getConfigErrorMessage()
int getRusEfiVersion()
void setNeedToWriteConfiguration()
FragmentList getLiveDataFragments()
const char * swapOutputBuffers(size_t *actualOutputBufferSize)
Main logic header.
This data structure holds current malfunction codes.
@ STACK_USAGE_COMMUNICATION
const BigBufferHandle perfTraceGetBuffer()
void perfTraceEnable()
@ TunerStudioHandleCrcCommand
const char * hwPortname(brain_pin_e brainPin)
const char * getTsSignature()
Definition signature.cpp:31
void printOverallStatus()
composite packet size
void DisableToothLogger()
void EnableToothLogger()
CompositeBuffer * GetToothLoggerBufferNonblocking()
void ReturnToothLoggerBuffer(CompositeBuffer *buffer)
void EnableToothLoggerIfNotEnabled()
composite_logger_s
void triggerScopeEnable()
const BigBufferHandle & triggerScopeGetBuffer()
static BigBufferHandle buffer
void triggerScopeDisable()
static void handleBurnCommand(TsChannelBase *tsChannel)
static bool isKnownCommand(char command)
bool needToTriggerTsRefresh()
bool isTuningNow()
static void handleGetVersion(TsChannelBase *tsChannel)
tunerstudio_counters_s tsState
PUBLIC_API_WEAK bool isBoardAskingTriggerTsRefresh()
TunerStudio tsInstance
static void setTsSpeed(int value)
CommandHandler console_line_callback
static void resetTs()
void sendErrorCode(TsChannelBase *tsChannel, uint8_t code, const char *msg)
static void printScatterList()
static void handleGetText(TsChannelBase *tsChannel)
bool validateOffsetCount(size_t offset, size_t count, TsChannelBase *tsChannel)
void requestBurn()
void startTunerStudioConnectivity()
static void sendOkResponse(TsChannelBase *tsChannel)
static void handleTestCommand(TsChannelBase *tsChannel)
static int tsProcessOne(TsChannelBase *tsChannel)
void tunerStudioDebug(TsChannelBase *tsChannel, const char *msg)
static void printErrorCounters()
void onApplyPreset()
static void printTsStats(void)
uint8_t * getWorkingPageAddr()
void tunerStudioError(TsChannelBase *tsChannel, const char *msg)
ts_response_format_e
@ TS_CRC
@ TS_PLAIN
SerialTsChannelBase * getBluetoothChannel()