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

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

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

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

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

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

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

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

1041 {
1042 int tuningDetector = engineConfiguration->isTuningDetectorEnabled ? 0 : 20;
1043 return !calibrationsVeWriteTimer.hasElapsedSec(tuningDetector);
1044}

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(), handleCommandX14(), and vinStrategy().

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

450 {
451#if !EFI_UNIT_TEST
453
454#if EFI_CONFIGURATION_STORAGE
456#endif /* EFI_CONFIGURATION_STORAGE */
457#endif // !EFI_UNIT_TEST
458}
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 1046 of file tunerstudio.cpp.

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

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

764 {
765 tunerStudioDebug(tsChannel, msg);
768}

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

Referenced by tsProcessOne().

◆ tsState

Go to the source code of this file.