rusEFI
The most advanced open source ECU
Loading...
Searching...
No Matches
Functions | Variables
tunerstudio.cpp File Reference

Detailed Description

Binary protocol implementation.

This implementation would not happen without the documentation provided by Jon Zeeff (jon@z.nosp@m.eeff.nosp@m..com)

Integration with EFI Analytics Tuner Studio software

Tuner Studio has a really simple protocol, a minimal implementation capable of displaying current engine state on the gauges would require only two commands: queryCommand and ochGetCommand

queryCommand: Communication initialization command. TunerStudio sends a single byte H ECU response: One of the known ECU id strings.

ochGetCommand: Request for output channels state.TunerStudio sends a single byte O ECU response: A snapshot of output channels as described in [OutputChannels] section of the .ini file The length of this block is 'ochBlockSize' property of the .ini file

These two commands are enough to get working gauges. In order to start configuring the ECU using tuner studio, three more commands should be implemented:

See also https://www.efianalytics.com/TunerStudio/docs/EFI%20Analytics%20ECU%20Definition%20files.pdf

Date
Oct 22, 2013
Author
Andrey Belomutskiy, (c) 2012-2020

This file is part of rusEfi - see http://rusefi.com

rusEfi is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 3 of the License, or (at your option) any later version.

rusEfi is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details.

You should have received a copy of the GNU General Public License along with this program. If not, see http://www.gnu.org/licenses/.

This file is part of rusEfi - see http://rusefi.com

rusEfi is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 3 of the License, or (at your option) any later version.

rusEfi is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details.

You should have received a copy of the GNU General Public License along with this program. If not, see http://www.gnu.org/licenses/.

Definition in file tunerstudio.cpp.

Functions

static void printErrorCounters ()
 
static void printScatterList (TsChannelBase *tsChannel)
 
static void resetTs ()
 
static void printTsStats (void)
 
static void setTsSpeed (int value)
 
void tunerStudioDebug (TsChannelBase *tsChannel, const char *msg)
 
static uint8_t * getWorkingPageAddr (TsChannelBase *tsChannel, size_t page, size_t offset)
 
static constexpr size_t getTunerStudioPageSize (size_t page)
 
static bool validateOffsetCount (size_t page, size_t offset, size_t count, TsChannelBase *tsChannel)
 
static void sendOkResponse (TsChannelBase *tsChannel)
 
void sendErrorCode (TsChannelBase *tsChannel, uint8_t code, const char *msg)
 
PUBLIC_API_WEAK bool isBoardAskingTriggerTsRefresh ()
 
bool needToTriggerTsRefresh ()
 
void onApplyPreset ()
 
PUBLIC_API_WEAK bool isTouchingVe (uint16_t offset, uint16_t count)
 
static void onCalibrationWrite (uint16_t page, uint16_t offset, uint16_t count)
 
bool isTouchingArea (uint16_t offset, uint16_t count, int areaStart, int areaSize)
 
void requestBurn ()
 
static void handleBurnCommand (TsChannelBase *tsChannel, uint16_t page)
 
static bool isKnownCommand (char command)
 
static void handleTestCommand (TsChannelBase *tsChannel)
 
static void handleGetConfigErorr (TsChannelBase *tsChannel)
 
static int tsProcessOne (TsChannelBase *tsChannel)
 
void tunerStudioError (TsChannelBase *tsChannel, const char *msg)
 
static void handleGetVersion (TsChannelBase *tsChannel)
 
static void handleGetText (TsChannelBase *tsChannel)
 
bool isTuningVeNow ()
 
void startTunerStudioConnectivity ()
 

Variables

TunerStudio tsInstance
 
tunerstudio_counters_s tsState
 
CommandHandler console_line_callback
 

Function Documentation

◆ getTunerStudioPageSize()

static constexpr size_t getTunerStudioPageSize ( size_t  page)
staticconstexpr

Definition at line 191 of file tunerstudio.cpp.

191 {
192 switch (page) {
193 case TS_PAGE_SETTINGS:
194 return TOTAL_CONFIG_SIZE;
195#if EFI_TS_SCATTER
196 case TS_PAGE_SCATTER_OFFSETS:
197 return PAGE_SIZE_1;
198#endif
199#if EFI_LTFT_CONTROL
200 case TS_PAGE_LTFT_TRIMS:
201 return ltftGetTsPageSize();
202#endif
203 default:
204 return 0;
205 }
206}
size_t ltftGetTsPageSize()
uint16_t page
Definition tunerstudio.h:0

Referenced by validateOffsetCount().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ getWorkingPageAddr()

static uint8_t * getWorkingPageAddr ( TsChannelBase tsChannel,
size_t  page,
size_t  offset 
)
static

Definition at line 169 of file tunerstudio.cpp.

169 {
170 // TODO: validate offset?
171 switch (page) {
172 case TS_PAGE_SETTINGS:
173 // TODO: why engineConfiguration, not config
174 // TS has access to whole persistent_config_s
175 return (uint8_t*)engineConfiguration + offset;
176#if EFI_TS_SCATTER
177 case TS_PAGE_SCATTER_OFFSETS:
178 return (uint8_t *)tsChannel->page1.highSpeedOffsets + offset;
179#endif
180#if EFI_LTFT_CONTROL
181 case TS_PAGE_LTFT_TRIMS:
182 return (uint8_t *)ltftGetTsPage() + offset;
183#endif
184 default:
185// technical dept: TS seems to try to read the 3 pages sequentially, does not look like we properly handle 'EFI_TS_SCATTER=FALSE'
186 tunerStudioError(tsChannel, "ERROR: page address out of range");
187 return nullptr;
188 }
189}
static constexpr engine_configuration_s * engineConfiguration
void * ltftGetTsPage()
uint16_t highSpeedOffsets[TS_SCATTER_OFFSETS_COUNT]
void tunerStudioError(TsChannelBase *tsChannel, const char *msg)
uint16_t offset
Definition tunerstudio.h:0

Referenced by TunerStudio::handleCrc32Check(), TunerStudio::handlePageReadCommand(), and TunerStudio::handleWriteChunkCommand().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ handleBurnCommand()

static void handleBurnCommand ( TsChannelBase tsChannel,
uint16_t  page 
)
static

'Burn' command is a command to commit the changes

Definition at line 463 of file tunerstudio.cpp.

463 {
464 if (page == TS_PAGE_SETTINGS) {
465 Timer t;
466 t.reset();
467
469
470 efiPrintf("TS -> Burn");
472
473 // problem: 'popular vehicles' dialog has 'Burn' which is very NOT helpful on that dialog
474 // since users often click both buttons producing a conflict between ECU desire to change settings
475 // and TS desire to send TS calibration snapshot into ECU
476 // Skip the burn if a preset was just loaded - we don't want to overwrite it
477 // [tag:popular_vehicle]
478 if (!needToTriggerTsRefresh()) {
479 requestBurn();
480 }
481 efiPrintf("Burned in %.1fms", t.getElapsedSeconds() * 1e3);
482#if EFI_TS_SCATTER
483 } else if (page == TS_PAGE_SCATTER_OFFSETS) {
484 /* do nothing */
485#endif
486 } else {
487 sendErrorCode(tsChannel, TS_RESPONSE_OUT_OF_RANGE, "ERROR: Burn invalid page");
488 return;
489 }
490
491 tsChannel->writeCrcResponse(TS_RESPONSE_BURN_OK);
492}
void writeCrcResponse(uint8_t responseCode)
bool validateConfigOnStartUpOrBurn()
bool needToTriggerTsRefresh()
tunerstudio_counters_s tsState
void sendErrorCode(TsChannelBase *tsChannel, uint8_t code, const char *msg)
void requestBurn()

Referenced by TunerStudio::handleCrcCommand().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ handleGetConfigErorr()

static void handleGetConfigErorr ( TsChannelBase tsChannel)
static

Definition at line 548 of file tunerstudio.cpp.

548 {
549 const char* errorMessage = hasFirmwareError() ? getCriticalErrorMessage() : getConfigErrorMessage();
550 if (strlen(errorMessage) == 0) {
551 // Check for engine's warning code
553 }
554 tsChannel->sendResponse(TS_CRC, reinterpret_cast<const uint8_t*>(errorMessage), strlen(errorMessage), true);
555}
EngineState engineState
Definition engine.h:344
WarningCodeState warnings
void sendResponse(ts_response_format_e mode, const uint8_t *buffer, int size, bool allowLongPackets=false)
const char * getWarningMessage()
Definition engine2.cpp:107
static EngineAccessor engine
Definition engine.h:413
const char * getCriticalErrorMessage()
const char * getConfigErrorMessage()
@ TS_CRC

Referenced by TunerStudio::handleCrcCommand().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ handleGetText()

static void handleGetText ( TsChannelBase tsChannel)
static

Definition at line 781 of file tunerstudio.cpp.

781 {
783
785
786 size_t outputSize;
787 const char* output = swapOutputBuffers(&outputSize);
788#if EFI_SIMULATOR
789 logMsg("get test sending [%d]\r\n", outputSize);
790#endif
791
792 tsChannel->writeCrcPacket(TS_RESPONSE_OK, reinterpret_cast<const uint8_t*>(output), outputSize, true);
793#if EFI_SIMULATOR
794 logMsg("sent [%d]\r\n", outputSize);
795#endif // EFI_SIMULATOR
796}
virtual void writeCrcPacket(uint8_t responseCode, const uint8_t *buf, size_t size, bool allowLongPackets=false)
const char * swapOutputBuffers(size_t *actualOutputBufferSize)
void printOverallStatus()

Referenced by TunerStudio::handleCrcCommand().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ handleGetVersion()

static void handleGetVersion ( TsChannelBase tsChannel)
static

Definition at line 774 of file tunerstudio.cpp.

774 {
775 char versionBuffer[32];
776 chsnprintf(versionBuffer, sizeof(versionBuffer), "%s v%d@%u", FRONTEND_TITLE_BAR_NAME, getRusEfiVersion(), SIGNATURE_HASH);
777 tsChannel->sendResponse(TS_CRC, (const uint8_t *) versionBuffer, strlen(versionBuffer) + 1);
778}
int getRusEfiVersion()

Referenced by TunerStudio::handleCrcCommand().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ handleTestCommand()

static void handleTestCommand ( TsChannelBase tsChannel)
static

rusEfi own test command

this is NOT a standard TunerStudio command, this is my own extension of the protocol to simplify troubleshooting

Definition at line 521 of file tunerstudio.cpp.

521 {
523 char testOutputBuffer[64];
524 /**
525 * this is NOT a standard TunerStudio command, this is my own
526 * extension of the protocol to simplify troubleshooting
527 */
528 tunerStudioDebug(tsChannel, "got T (Test)");
529 tsChannel->write((const uint8_t*)QUOTE(SIGNATURE_HASH), sizeof(QUOTE(SIGNATURE_HASH)));
530
531 chsnprintf(testOutputBuffer, sizeof(testOutputBuffer), " %d %d", engine->engineState.warnings.lastErrorCode, tsState.testCommandCounter);
532 tsChannel->write((const uint8_t*)testOutputBuffer, strlen(testOutputBuffer));
533
534 chsnprintf(testOutputBuffer, sizeof(testOutputBuffer), " uptime=%ds ", (int)getTimeNowS());
535 tsChannel->write((const uint8_t*)testOutputBuffer, strlen(testOutputBuffer));
536
537 chsnprintf(testOutputBuffer, sizeof(testOutputBuffer), __DATE__ " %s\r\n", PROTOCOL_TEST_RESPONSE_TAG);
538 tsChannel->write((const uint8_t*)testOutputBuffer, strlen(testOutputBuffer));
539
540 if (hasFirmwareError()) {
541 const char* error = getCriticalErrorMessage();
542 chsnprintf(testOutputBuffer, sizeof(testOutputBuffer), "error=%s\r\n", error);
543 tsChannel->write((const uint8_t*)testOutputBuffer, strlen(testOutputBuffer));
544 }
545 tsChannel->flush();
546}
virtual void flush()
virtual void write(const uint8_t *buffer, size_t size, bool isEndOfPacket=false)=0
ObdCode lastErrorCode
efitimesec_t getTimeNowS()
Current system time in seconds (32 bits)
Definition efitime.cpp:42
void tunerStudioDebug(TsChannelBase *tsChannel, const char *msg)

Referenced by TunerStudio::handleCrcCommand(), and TunerStudio::handlePlainCommand().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ isBoardAskingTriggerTsRefresh()

PUBLIC_API_WEAK bool isBoardAskingTriggerTsRefresh ( )

Definition at line 261 of file tunerstudio.cpp.

261 {
262 return false;
263}

◆ isKnownCommand()

static bool isKnownCommand ( char  command)
static

Definition at line 496 of file tunerstudio.cpp.

496 {
497 return command == TS_HELLO_COMMAND || command == TS_READ_COMMAND || command == TS_OUTPUT_COMMAND
498 || command == TS_BURN_COMMAND
499 || command == TS_CHUNK_WRITE_COMMAND || command == TS_EXECUTE
500 || command == TS_IO_TEST_COMMAND
501#if EFI_SIMULATOR
502 || command == TS_SIMULATE_CAN
503#endif // EFI_SIMULATOR
504#if EFI_TS_SCATTER
505 || command == TS_GET_SCATTERED_GET_COMMAND
506#endif
507 || command == TS_SET_LOGGER_SWITCH
508 || command == TS_GET_COMPOSITE_BUFFER_DONE_DIFFERENTLY
509 || command == TS_GET_TEXT
510 || command == TS_CRC_CHECK_COMMAND
511 || command == TS_GET_FIRMWARE_VERSION
512 || command == TS_PERF_TRACE_BEGIN
513 || command == TS_PERF_TRACE_GET_BUFFER
514 || command == TS_GET_CONFIG_ERROR
515 || command == TS_QUERY_BOOTLOADER;
516}

Referenced by tsProcessOne().

Here is the caller graph for this function:

◆ isTouchingArea()

bool isTouchingArea ( uint16_t  offset,
uint16_t  count,
int  areaStart,
int  areaSize 
)

Definition at line 283 of file tunerstudio.cpp.

283 {
284 if (offset + count < areaStart) {
285 // we are touching below for instance VE table
286 return false;
287 }
288 if (offset > areaStart + areaSize) {
289 // we are touching after for instance VE table
290 return false;
291 }
292 // else - we are touching it!
293 return true;
294}
uint16_t count
Definition tunerstudio.h:1

Referenced by isTouchingVe().

Here is the caller graph for this function:

◆ isTouchingVe()

PUBLIC_API_WEAK bool isTouchingVe ( uint16_t  offset,
uint16_t  count 
)

Definition at line 273 of file tunerstudio.cpp.

273 {
274 return isTouchingArea(offset, count, offsetof(persistent_config_s, veTable), sizeof(config->veTable));
275}
static constexpr persistent_config_s * config
scaled_channel< uint16_t, 10, 1 > veTable[VE_LOAD_COUNT][VE_RPM_COUNT]
bool isTouchingArea(uint16_t offset, uint16_t count, int areaStart, int areaSize)

Referenced by onCalibrationWrite().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ isTuningVeNow()

bool isTuningVeNow ( )

Definition at line 1039 of file tunerstudio.cpp.

1039 {
1041 !calibrationsVeWriteTimer.hasElapsedSec(TunerDetectorUtils::getUserEnteredTuningDetector());
1042}
static uint8_t getUserEnteredTuningDetector()
static bool isTuningDetectorUndefined()

Referenced by checkIfTuningVeNow(), and TpsAccelEnrichment::getTpsEnrichment().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ needToTriggerTsRefresh()

bool needToTriggerTsRefresh ( )

Definition at line 265 of file tunerstudio.cpp.

265 {
266 return !engine->engineTypeChangeTimer.hasElapsedSec(1);
267}
Timer engineTypeChangeTimer
Definition engine.h:309

Referenced by handleBurnCommand(), TunerStudio::handleWriteChunkCommand(), and updateTunerStudioState().

Here is the caller graph for this function:

◆ onApplyPreset()

void onApplyPreset ( )

Definition at line 269 of file tunerstudio.cpp.

269 {
271}

Referenced by applyPreset().

Here is the caller graph for this function:

◆ onCalibrationWrite()

static void onCalibrationWrite ( uint16_t  page,
uint16_t  offset,
uint16_t  count 
)
static

Definition at line 277 of file tunerstudio.cpp.

277 {
278 if ((page == TS_PAGE_SETTINGS) && isTouchingVe(offset, count)) {
279 calibrationsVeWriteTimer.reset();
280 }
281}
PUBLIC_API_WEAK bool isTouchingVe(uint16_t offset, uint16_t count)

Referenced by TunerStudio::handleWriteChunkCommand().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ printErrorCounters()

static void printErrorCounters ( )
static

Definition at line 100 of file tunerstudio.cpp.

100 {
101 efiPrintf("TunerStudio size=%d / total=%d / errors=%d / H=%d / O=%d / P=%d / B=%d / 9=%d",
105 efiPrintf("TunerStudio C=%d",
107 efiPrintf("TunerStudio errors: underrun=%d / overrun=%d / crc=%d / unrecognized=%d / outofrange=%d / other=%d",
110}
TunerStudioOutputChannels outputChannels
Definition engine.h:109

Referenced by printTsStats(), and tunerStudioError().

Here is the caller graph for this function:

◆ printScatterList()

static void printScatterList ( TsChannelBase tsChannel)
static

Definition at line 117 of file tunerstudio.cpp.

117 {
118 efiPrintf("Scatter list (global)");
119 for (size_t i = 0; i < TS_SCATTER_OFFSETS_COUNT; i++) {
120 uint16_t packed = tsChannel->highSpeedOffsets[i];
121 uint16_t type = packed >> 13;
122 uint16_t offset = packed & 0x1FFF;
123
124 if (type == 0)
125 continue;
126 size_t size = 1 << (type - 1);
127
128 efiPrintf("%02d offset 0x%04x size %d", i, offset, size);
129 }
130}
composite packet size

◆ printTsStats()

static void printTsStats ( void  )
static

Definition at line 142 of file tunerstudio.cpp.

142 {
143#ifdef EFI_CONSOLE_RX_BRAIN_PIN
144 efiPrintf("Primary UART RX %s", hwPortname(EFI_CONSOLE_RX_BRAIN_PIN));
145 efiPrintf("Primary UART TX %s", hwPortname(EFI_CONSOLE_TX_BRAIN_PIN));
146#endif /* EFI_CONSOLE_RX_BRAIN_PIN */
147
148#if EFI_USB_SERIAL
150#endif // EFI_USB_SERIAL
151
153
154 // TODO: find way to get all tsChannel
155 //printScatterList();
156}
void printUsbConnectorStats()
const char * hwPortname(brain_pin_e brainPin)
static void printErrorCounters()

Referenced by setTsSpeed(), and startTunerStudioConnectivity().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ requestBurn()

void requestBurn ( )

Definition at line 449 of file tunerstudio.cpp.

449 {
450#if !EFI_UNIT_TEST
452
453#if EFI_CONFIGURATION_STORAGE
455#endif /* EFI_CONFIGURATION_STORAGE */
456#endif // !EFI_UNIT_TEST
457}
void onBurnRequest()
void setNeedToWriteConfiguration()

Referenced by configureRusefiLuaHooks(), handleBurnCommand(), initFlash(), and unlockEcu().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ resetTs()

static void resetTs ( )
static

Definition at line 138 of file tunerstudio.cpp.

138 {
139 memset(&tsState, 0, sizeof(tsState));
140}

Referenced by startTunerStudioConnectivity().

Here is the caller graph for this function:

◆ sendErrorCode()

void sendErrorCode ( TsChannelBase tsChannel,
uint8_t  code,
const char msg 
)

Definition at line 226 of file tunerstudio.cpp.

226 {
227 //TODO uncomment once I have test it myself
228 UNUSED(msg);
229 //if (msg != DO_NOT_LOG) {
230 // efiPrintf("TS <- Err: %d [%s]", code, msg);
231 //}
232
233 switch (code) {
234 case TS_RESPONSE_UNDERRUN:
236 break;
237 case TS_RESPONSE_OVERRUN:
239 break;
240 case TS_RESPONSE_CRC_FAILURE:
242 break;
243 case TS_RESPONSE_UNRECOGNIZED_COMMAND:
245 break;
246 case TS_RESPONSE_OUT_OF_RANGE:
248 break;
249 default:
251 break;
252 }
253
254 tsChannel->writeCrcResponse(code);
255}
uint8_t code
Definition bluetooth.cpp:40
UNUSED(samplingTimeSeconds)

Referenced by handleBurnCommand(), tsProcessOne(), and validateOffsetCount().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ sendOkResponse()

static void sendOkResponse ( TsChannelBase tsChannel)
static

Definition at line 222 of file tunerstudio.cpp.

222 {
223 tsChannel->sendResponse(TS_CRC, nullptr, 0);
224}

Referenced by TunerStudio::handleCrcCommand(), and TunerStudio::handleWriteChunkCommand().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ setTsSpeed()

static void setTsSpeed ( int  value)
static

Definition at line 158 of file tunerstudio.cpp.

Referenced by startTunerStudioConnectivity().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ startTunerStudioConnectivity()

void startTunerStudioConnectivity ( )

Definition at line 1044 of file tunerstudio.cpp.

1044 {
1045 // Assert tune & output channel struct sizes
1046 static_assert(sizeof(persistent_config_s) == TOTAL_CONFIG_SIZE, "TS datapage size mismatch");
1047 // useful trick if you need to know how far off is the static_assert
1048 //char (*__kaboom)[sizeof(persistent_config_s)] = 1;
1049 // another useful trick
1050 //static_assert(offsetof (engine_configuration_s,HD44780_e) == 700);
1051
1052 memset(&tsState, 0, sizeof(tsState));
1053
1054 addConsoleAction("tsinfo", printTsStats);
1055 addConsoleAction("reset_ts", resetTs);
1056 addConsoleActionI("set_ts_speed", setTsSpeed);
1057
1058#if EFI_BLUETOOTH_SETUP
1059 // module initialization start (it waits for disconnect and then communicates to the module)
1060 // Usage: "bluetooth_hc06 <baud> <name> <pincode>"
1061 // Example: "bluetooth_hc06 38400 rusefi 1234"
1062 // bluetooth_jdy 115200 alphax 1234
1063 addConsoleActionSSS("bluetooth_hc05", [](const char *baudRate, const char *name, const char *pinCode) {
1064 bluetoothStart(BLUETOOTH_HC_05, baudRate, name, pinCode);
1065 });
1066 addConsoleActionSSS("bluetooth_hc06", [](const char *baudRate, const char *name, const char *pinCode) {
1067 bluetoothStart(BLUETOOTH_HC_06, baudRate, name, pinCode);
1068 });
1069 addConsoleActionSSS("bluetooth_bk", [](const char *baudRate, const char *name, const char *pinCode) {
1070 bluetoothStart(BLUETOOTH_BK3231, baudRate, name, pinCode);
1071 });
1072 addConsoleActionSSS("bluetooth_jdy", [](const char *baudRate, const char *name, const char *pinCode) {
1073 bluetoothStart(BLUETOOTH_JDY_3x, baudRate, name, pinCode);
1074 });
1075 addConsoleActionSSS("bluetooth_jdy31", [](const char *baudRate, const char *name, const char *pinCode) {
1076 bluetoothStart(BLUETOOTH_JDY_31, baudRate, name, pinCode);
1077 });
1078#endif /* EFI_BLUETOOTH_SETUP */
1079}
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
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.
static void setTsSpeed(int value)
static void resetTs()

Referenced by runRusEfi().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ tsProcessOne()

static int tsProcessOne ( TsChannelBase tsChannel)
static

Definition at line 609 of file tunerstudio.cpp.

609 {
610 assertStack("communication", ObdCode::STACK_USAGE_COMMUNICATION, EXPECTED_REMAINING_STACK, -1);
611
612 if (!tsChannel->isReady()) {
613 chThdSleepMilliseconds(10);
614 return -1;
615 }
616
618
619 uint8_t firstByte;
620 size_t received = tsChannel->readTimeout(&firstByte, 1, TS_COMMUNICATION_TIMEOUT);
621#if EFI_SIMULATOR
622 logMsg("received %d\r\n", received);
623#endif // EFI_SIMULATOR
624
625 if (received != 1) {
626 //tunerStudioError("ERROR: no command");
627#if EFI_BLUETOOTH_SETUP
628 if (tsChannel == getBluetoothChannel()) {
629 // no data in a whole second means time to disconnect BT
630 // assume there's connection loss and notify the bluetooth init code
632 }
633#endif /* EFI_BLUETOOTH_SETUP */
634 tsChannel->in_sync = false;
635 return -1;
636 }
637
638 if (tsInstance.handlePlainCommand(tsChannel, firstByte)) {
639 return 0;
640 }
641
642 uint8_t secondByte;
643 /* second byte should be received within minimal delay */
644 received = tsChannel->readTimeout(&secondByte, 1, TS_COMMUNICATION_TIMEOUT_SHORT);
645 if (received != 1) {
646 tunerStudioError(tsChannel, "TS: ERROR: no second byte");
647 tsChannel->in_sync = false;
648 return -1;
649 }
650
651 uint16_t incomingPacketSize = firstByte << 8 | secondByte;
652 size_t expectedSize = incomingPacketSize + TS_PACKET_TAIL_SIZE;
653
654 if ((incomingPacketSize == 0) || (expectedSize > sizeof(tsChannel->scratchBuffer))) {
655 if (tsChannel->in_sync) {
656 efiPrintf("process_ts: channel=%s invalid size: %d", tsChannel->name, incomingPacketSize);
657 tunerStudioError(tsChannel, "process_ts: ERROR: packet size");
658 /* send error only if previously we were in sync */
659 sendErrorCode(tsChannel, TS_RESPONSE_OUT_OF_RANGE, "invalid size");
660 }
661 tsChannel->in_sync = false;
662 return -1;
663 }
664
665 char command;
666 if (tsChannel->in_sync) {
667 /* we are in sync state, packet size should be correct so lets receive full packet and then check if command is supported
668 * otherwise (if abort reception in middle of packet) it will break synchronization and cause error on next packet */
669 received = tsChannel->readTimeout((uint8_t*)(tsChannel->scratchBuffer), expectedSize, TS_COMMUNICATION_TIMEOUT);
670 command = tsChannel->scratchBuffer[0];
671
672 if (received != expectedSize) {
673 /* print and send error as we were in sync */
674 efiPrintf("Got only %d bytes while expecting %d for command 0x%02x", received,
675 expectedSize, command);
676 tunerStudioError(tsChannel, "ERROR: not enough bytes in stream");
677 // MS serial protocol spec: There was a timeout before all data was received. (25ms per character.)
678 sendErrorCode(tsChannel, TS_RESPONSE_UNDERRUN, "underrun");
679 tsChannel->in_sync = false;
680 return -1;
681 }
682
683 if (!isKnownCommand(command)) {
684 /* print and send error as we were in sync */
685 efiPrintf("unexpected command %x", command);
686 sendErrorCode(tsChannel, TS_RESPONSE_UNRECOGNIZED_COMMAND, "unknown");
687 tsChannel->in_sync = false;
688 return -1;
689 }
690 } else {
691 /* receive only command byte to check if it is supported */
692 received = tsChannel->readTimeout((uint8_t*)(tsChannel->scratchBuffer), 1, TS_COMMUNICATION_TIMEOUT_SHORT);
693 command = tsChannel->scratchBuffer[0];
694
695 if (!isKnownCommand(command)) {
696 /* do not report any error as we are not in sync */
697 return -1;
698 }
699
700 received = tsChannel->readTimeout((uint8_t*)(tsChannel->scratchBuffer) + 1, expectedSize - 1, TS_COMMUNICATION_TIMEOUT);
701 if (received != expectedSize - 1) {
702 /* do not report any error as we are not in sync */
703 return -1;
704 }
705 }
706
707#if EFI_SIMULATOR
708 logMsg("command %c\r\n", command);
709#endif
710
711 uint32_t expectedCrc = *(uint32_t*) (tsChannel->scratchBuffer + incomingPacketSize);
712
713 expectedCrc = SWAP_UINT32(expectedCrc);
714
715 uint32_t actualCrc = crc32(tsChannel->scratchBuffer, incomingPacketSize);
716 if (actualCrc != expectedCrc) {
717 /* send error only if previously we were in sync */
718 if (tsChannel->in_sync) {
719 efiPrintf("TunerStudio: command %c actual CRC %x/expected %x", tsChannel->scratchBuffer[0],
720 (unsigned int)actualCrc, (unsigned int)expectedCrc);
721 tunerStudioError(tsChannel, "ERROR: CRC issue");
722 sendErrorCode(tsChannel, TS_RESPONSE_CRC_FAILURE, "crc_issue");
723 tsChannel->in_sync = false;
724 }
725 return -1;
726 }
727
728 /* we were able to receive known command with correct crc and size! */
729 tsChannel->in_sync = true;
730
731 int success = tsInstance.handleCrcCommand(tsChannel, tsChannel->scratchBuffer, incomingPacketSize);
732
733 if (!success) {
734 efiPrintf("got unexpected TunerStudio command %x:%c", command, command);
735 return -1;
736 }
737
738 return 0;
739}
void bluetoothSoftwareDisconnectNotify(SerialTsChannelBase *tsChannel)
virtual bool isReady() const
const char * name
char scratchBuffer[scratchBuffer_SIZE+30]
virtual size_t readTimeout(uint8_t *buffer, size_t size, int timeout)=0
bool handlePlainCommand(TsChannelBase *tsChannel, uint8_t command)
int handleCrcCommand(TsChannelBase *tsChannel, char *data, int incomingPacketSize)
uint32_t SWAP_UINT32(uint32_t x)
Definition efilib.h:27
@ STACK_USAGE_COMMUNICATION
static bool isKnownCommand(char command)
TunerStudio tsInstance
SerialTsChannelBase * getBluetoothChannel()

Referenced by TunerstudioThread::ThreadTask().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ tunerStudioDebug()

void tunerStudioDebug ( TsChannelBase tsChannel,
const char msg 
)

Definition at line 163 of file tunerstudio.cpp.

163 {
164#if EFI_TUNER_STUDIO_VERBOSE
165 efiPrintf("%s: %s", tsChannel->name, msg);
166#endif /* EFI_TUNER_STUDIO_VERBOSE */
167}

Referenced by TunerStudio::handleCrcCommand(), TunerStudio::handlePlainCommand(), handleTestCommand(), and tunerStudioError().

Here is the caller graph for this function:

◆ tunerStudioError()

void tunerStudioError ( TsChannelBase tsChannel,
const char msg 
)

Definition at line 762 of file tunerstudio.cpp.

762 {
763 tunerStudioDebug(tsChannel, msg);
766}

Referenced by getWorkingPageAddr(), TunerStudio::handleCrc32Check(), TunerStudio::handleCrcCommand(), TunerStudio::handlePageReadCommand(), TunerStudio::handleWriteChunkCommand(), tsProcessOne(), and validateOffsetCount().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ validateOffsetCount()

static bool validateOffsetCount ( size_t  page,
size_t  offset,
size_t  count,
TsChannelBase tsChannel 
)
static

Definition at line 210 of file tunerstudio.cpp.

210 {
211 size_t allowedSize = getTunerStudioPageSize(page);
212 if (offset + count > allowedSize) {
213 efiPrintf("TS: Project mismatch? Too much configuration requested %d+%d>%d", offset, count, allowedSize);
214 tunerStudioError(tsChannel, "ERROR: out of range");
215 sendErrorCode(tsChannel, TS_RESPONSE_OUT_OF_RANGE, "bad_offset");
216 return true;
217 }
218
219 return false;
220}
static constexpr size_t getTunerStudioPageSize(size_t page)

Referenced by TunerStudio::handleCrc32Check(), TunerStudio::handlePageReadCommand(), and TunerStudio::handleWriteChunkCommand().

Here is the call graph for this function:
Here is the caller graph for this function:

Variable Documentation

◆ console_line_callback

CommandHandler console_line_callback
extern

Definition at line 53 of file console_io.cpp.

Referenced by TunerStudio::handleExecuteCommand(), and startConsole().

◆ tsInstance

TunerStudio tsInstance

Definition at line 607 of file tunerstudio.cpp.

Referenced by tsProcessOne().

◆ tsState

Go to the source code of this file.