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 190 of file tunerstudio.cpp.

190 {
191 switch (page) {
192 case TS_PAGE_SETTINGS:
193 return TOTAL_CONFIG_SIZE;
194#if EFI_TS_SCATTER
195 case TS_PAGE_SCATTER_OFFSETS:
196 return PAGE_SIZE_1;
197#endif
198#if EFI_LTFT_CONTROL
199 case TS_PAGE_LTFT_TRIMS:
200 return ltftGetTsPageSize();
201#endif
202 default:
203 return 0;
204 }
205}
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 168 of file tunerstudio.cpp.

168 {
169 // TODO: validate offset?
170 switch (page) {
171 case TS_PAGE_SETTINGS:
172 // TODO: why engineConfiguration, not config
173 // TS has access to whole persistent_config_s
174 return (uint8_t*)engineConfiguration + offset;
175#if EFI_TS_SCATTER
176 case TS_PAGE_SCATTER_OFFSETS:
177 return (uint8_t *)tsChannel->page1.highSpeedOffsets + offset;
178#endif
179#if EFI_LTFT_CONTROL
180 case TS_PAGE_LTFT_TRIMS:
181 return (uint8_t *)ltftGetTsPage() + offset;
182#endif
183 default:
184// technical dept: TS seems to try to read the 3 pages sequentially, does not look like we properly handle 'EFI_TS_SCATTER=FALSE'
185 tunerStudioError(tsChannel, "ERROR: page address out of range");
186 return nullptr;
187 }
188}
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 462 of file tunerstudio.cpp.

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

547 {
548 const char* errorMessage = hasFirmwareError() ? getCriticalErrorMessage() : getConfigErrorMessage();
549 if (strlen(errorMessage) == 0) {
550 // Check for engine's warning code
552 }
553 tsChannel->sendResponse(TS_CRC, reinterpret_cast<const uint8_t*>(errorMessage), strlen(errorMessage), true);
554}
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 780 of file tunerstudio.cpp.

780 {
782
784
785 size_t outputSize;
786 const char* output = swapOutputBuffers(&outputSize);
787#if EFI_SIMULATOR
788 logMsg("get test sending [%d]\r\n", outputSize);
789#endif
790
791 tsChannel->writeCrcPacket(TS_RESPONSE_OK, reinterpret_cast<const uint8_t*>(output), outputSize, true);
792#if EFI_SIMULATOR
793 logMsg("sent [%d]\r\n", outputSize);
794#endif // EFI_SIMULATOR
795}
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 773 of file tunerstudio.cpp.

773 {
774 char versionBuffer[32];
775 chsnprintf(versionBuffer, sizeof(versionBuffer), "%s v%d@%u", FRONTEND_TITLE_BAR_NAME, getRusEfiVersion(), SIGNATURE_HASH);
776 tsChannel->sendResponse(TS_CRC, (const uint8_t *) versionBuffer, strlen(versionBuffer) + 1);
777}
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 520 of file tunerstudio.cpp.

520 {
522 char testOutputBuffer[64];
523 /**
524 * this is NOT a standard TunerStudio command, this is my own
525 * extension of the protocol to simplify troubleshooting
526 */
527 tunerStudioDebug(tsChannel, "got T (Test)");
528 tsChannel->write((const uint8_t*)QUOTE(SIGNATURE_HASH), sizeof(QUOTE(SIGNATURE_HASH)));
529
530 chsnprintf(testOutputBuffer, sizeof(testOutputBuffer), " %d %d", engine->engineState.warnings.lastErrorCode, tsState.testCommandCounter);
531 tsChannel->write((const uint8_t*)testOutputBuffer, strlen(testOutputBuffer));
532
533 chsnprintf(testOutputBuffer, sizeof(testOutputBuffer), " uptime=%ds ", (int)getTimeNowS());
534 tsChannel->write((const uint8_t*)testOutputBuffer, strlen(testOutputBuffer));
535
536 chsnprintf(testOutputBuffer, sizeof(testOutputBuffer), __DATE__ " %s\r\n", PROTOCOL_TEST_RESPONSE_TAG);
537 tsChannel->write((const uint8_t*)testOutputBuffer, strlen(testOutputBuffer));
538
539 if (hasFirmwareError()) {
540 const char* error = getCriticalErrorMessage();
541 chsnprintf(testOutputBuffer, sizeof(testOutputBuffer), "error=%s\r\n", error);
542 tsChannel->write((const uint8_t*)testOutputBuffer, strlen(testOutputBuffer));
543 }
544 tsChannel->flush();
545}
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 260 of file tunerstudio.cpp.

260 {
261 return false;
262}

◆ isKnownCommand()

static bool isKnownCommand ( char  command)
static

Definition at line 495 of file tunerstudio.cpp.

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

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 282 of file tunerstudio.cpp.

282 {
283 if (offset + count < areaStart) {
284 // we are touching below for instance VE table
285 return false;
286 }
287 if (offset > areaStart + areaSize) {
288 // we are touching after for instance VE table
289 return false;
290 }
291 // else - we are touching it!
292 return true;
293}
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 272 of file tunerstudio.cpp.

272 {
273 return isTouchingArea(offset, count, offsetof(persistent_config_s, veTable), sizeof(config->veTable));
274}
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 1038 of file tunerstudio.cpp.

1038 {
1039 int tuningDetector = engineConfiguration->isTuningDetectorEnabled ? 0 : 20;
1040 return !calibrationsVeWriteTimer.hasElapsedSec(tuningDetector);
1041}

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

Here is the caller graph for this function:

◆ needToTriggerTsRefresh()

bool needToTriggerTsRefresh ( )

Definition at line 264 of file tunerstudio.cpp.

264 {
265 return !engine->engineTypeChangeTimer.hasElapsedSec(1);
266}
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 268 of file tunerstudio.cpp.

268 {
270}

Referenced by applyPreset(), and handleCommandX14().

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 276 of file tunerstudio.cpp.

276 {
277 if ((page == TS_PAGE_SETTINGS) && isTouchingVe(offset, count)) {
278 calibrationsVeWriteTimer.reset();
279 }
280}
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 99 of file tunerstudio.cpp.

99 {
100 efiPrintf("TunerStudio size=%d / total=%d / errors=%d / H=%d / O=%d / P=%d / B=%d / 9=%d",
104 efiPrintf("TunerStudio C=%d",
106 efiPrintf("TunerStudio errors: underrun=%d / overrun=%d / crc=%d / unrecognized=%d / outofrange=%d / other=%d",
109}
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 116 of file tunerstudio.cpp.

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

◆ printTsStats()

static void printTsStats ( void  )
static

Definition at line 141 of file tunerstudio.cpp.

141 {
142#ifdef EFI_CONSOLE_RX_BRAIN_PIN
143 efiPrintf("Primary UART RX %s", hwPortname(EFI_CONSOLE_RX_BRAIN_PIN));
144 efiPrintf("Primary UART TX %s", hwPortname(EFI_CONSOLE_TX_BRAIN_PIN));
145#endif /* EFI_CONSOLE_RX_BRAIN_PIN */
146
147#if EFI_USB_SERIAL
149#endif // EFI_USB_SERIAL
150
152
153 // TODO: find way to get all tsChannel
154 //printScatterList();
155}
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 448 of file tunerstudio.cpp.

448 {
449#if !EFI_UNIT_TEST
451
452#if EFI_CONFIGURATION_STORAGE
454#endif /* EFI_CONFIGURATION_STORAGE */
455#endif // !EFI_UNIT_TEST
456}
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 137 of file tunerstudio.cpp.

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

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 225 of file tunerstudio.cpp.

225 {
226 //TODO uncomment once I have test it myself
227 UNUSED(msg);
228 //if (msg != DO_NOT_LOG) {
229 // efiPrintf("TS <- Err: %d [%s]", code, msg);
230 //}
231
232 switch (code) {
233 case TS_RESPONSE_UNDERRUN:
235 break;
236 case TS_RESPONSE_OVERRUN:
238 break;
239 case TS_RESPONSE_CRC_FAILURE:
241 break;
242 case TS_RESPONSE_UNRECOGNIZED_COMMAND:
244 break;
245 case TS_RESPONSE_OUT_OF_RANGE:
247 break;
248 default:
250 break;
251 }
252
253 tsChannel->writeCrcResponse(code);
254}
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 221 of file tunerstudio.cpp.

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

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 157 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 1043 of file tunerstudio.cpp.

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

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

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

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 761 of file tunerstudio.cpp.

761 {
762 tunerStudioDebug(tsChannel, msg);
765}

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 209 of file tunerstudio.cpp.

209 {
210 size_t allowedSize = getTunerStudioPageSize(page);
211 if (offset + count > allowedSize) {
212 efiPrintf("TS: Project mismatch? Too much configuration requested %d+%d>%d", offset, count, allowedSize);
213 tunerStudioError(tsChannel, "ERROR: out of range");
214 sendErrorCode(tsChannel, TS_RESPONSE_OUT_OF_RANGE, "bad_offset");
215 return true;
216 }
217
218 return false;
219}
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 606 of file tunerstudio.cpp.

Referenced by tsProcessOne().

◆ tsState

Go to the source code of this file.