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

uint8_t ts_blank_page_placeholder [256]
 
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 195 of file tunerstudio.cpp.

195 {
196 switch (page) {
197 case TS_PAGE_SETTINGS:
198 return TOTAL_CONFIG_SIZE;
199#if EFI_TS_SCATTER
200 case TS_PAGE_SCATTER_OFFSETS:
201 return PAGE_SIZE_1;
202#else
203 case TS_PAGE_SCATTER_OFFSETS:
204 // min read from TS seems to be 256b?
205 return 256;
206#endif
207#if EFI_LTFT_CONTROL
208 case TS_PAGE_LTFT_TRIMS:
209 return ltftGetTsPageSize();
210#endif
211 default:
212 return 0;
213 }
214}
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 171 of file tunerstudio.cpp.

171 {
172 // TODO: validate offset?
173 switch (page) {
174 case TS_PAGE_SETTINGS:
175 // TODO: why engineConfiguration, not config
176 // TS has access to whole persistent_config_s
177 return (uint8_t*)engineConfiguration + offset;
178#if EFI_TS_SCATTER
179 case TS_PAGE_SCATTER_OFFSETS:
180 return (uint8_t *)tsChannel->page1.highSpeedOffsets + offset;
181#else
182 case TS_PAGE_SCATTER_OFFSETS:
183 return (uint8_t *)&ts_blank_page_placeholder;
184#endif
185#if EFI_LTFT_CONTROL
186 case TS_PAGE_LTFT_TRIMS:
187 return (uint8_t *)ltftGetTsPage() + offset;
188#endif
189 default:
190 tunerStudioError(tsChannel, "ERROR: page address out of range");
191 return nullptr;
192 }
193}
static constexpr engine_configuration_s * engineConfiguration
void * ltftGetTsPage()
uint16_t highSpeedOffsets[TS_SCATTER_OFFSETS_COUNT]
uint8_t ts_blank_page_placeholder[256]
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 471 of file tunerstudio.cpp.

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

555 {
556 const char* errorMessage = hasFirmwareError() ? getCriticalErrorMessage() : getConfigErrorMessage();
557 if (strlen(errorMessage) == 0) {
558 // Check for engine's warning code
560 }
561 tsChannel->sendResponse(TS_CRC, reinterpret_cast<const uint8_t*>(errorMessage), strlen(errorMessage), true);
562}
EngineState engineState
Definition engine.h:352
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:421
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 787 of file tunerstudio.cpp.

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

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

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

269 {
270 return false;
271}

◆ isKnownCommand()

static bool isKnownCommand ( char  command)
static

Definition at line 503 of file tunerstudio.cpp.

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

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

291 {
292 if (offset + count < areaStart) {
293 // we are touching below for instance VE table
294 return false;
295 }
296 if (offset > areaStart + areaSize) {
297 // we are touching after for instance VE table
298 return false;
299 }
300 // else - we are touching it!
301 return true;
302}
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 281 of file tunerstudio.cpp.

281 {
282 return isTouchingArea(offset, count, offsetof(persistent_config_s, veTable), sizeof(config->veTable));
283}
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 1044 of file tunerstudio.cpp.

1044 {
1045 int tuningDetector = engineConfiguration->isTuningDetectorEnabled ? 0 : 20;
1046 return !calibrationsVeWriteTimer.hasElapsedSec(tuningDetector);
1047}

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

Here is the caller graph for this function:

◆ needToTriggerTsRefresh()

bool needToTriggerTsRefresh ( )

Definition at line 273 of file tunerstudio.cpp.

273 {
274 return !engine->engineTypeChangeTimer.hasElapsedSec(1);
275}
Timer engineTypeChangeTimer
Definition engine.h:317

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

Here is the caller graph for this function:

◆ onApplyPreset()

void onApplyPreset ( )

Definition at line 277 of file tunerstudio.cpp.

277 {
279}

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

285 {
286 if ((page == TS_PAGE_SETTINGS) && isTouchingVe(offset, count)) {
287 calibrationsVeWriteTimer.reset();
288 }
289}
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:113

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

457 {
458#if !EFI_UNIT_TEST
460
461#if EFI_CONFIGURATION_STORAGE
463#endif /* EFI_CONFIGURATION_STORAGE */
464#endif // !EFI_UNIT_TEST
465}
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 234 of file tunerstudio.cpp.

234 {
235 //TODO uncomment once I have test it myself
236 UNUSED(msg);
237 //if (msg != DO_NOT_LOG) {
238 // efiPrintf("TS <- Err: %d [%s]", code, msg);
239 //}
240
241 switch (code) {
242 case TS_RESPONSE_UNDERRUN:
244 break;
245 case TS_RESPONSE_OVERRUN:
247 break;
248 case TS_RESPONSE_CRC_FAILURE:
250 break;
251 case TS_RESPONSE_UNRECOGNIZED_COMMAND:
253 break;
254 case TS_RESPONSE_OUT_OF_RANGE:
256 break;
257 default:
259 break;
260 }
261
262 tsChannel->writeCrcResponse(code);
263}
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 230 of file tunerstudio.cpp.

230 {
231 tsChannel->sendResponse(TS_CRC, nullptr, 0);
232}

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

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

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

Here is the caller graph for this function:

◆ tunerStudioError()

void tunerStudioError ( TsChannelBase tsChannel,
const char msg 
)

Definition at line 768 of file tunerstudio.cpp.

768 {
769 tunerStudioDebug(tsChannel, msg);
772}

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

218 {
219 size_t allowedSize = getTunerStudioPageSize(page);
220 if (offset + count > allowedSize) {
221 efiPrintf("TS: Project mismatch? Too much configuration requested %d+%d>%d", offset, count, allowedSize);
222 tunerStudioError(tsChannel, "ERROR: out of range");
223 sendErrorCode(tsChannel, TS_RESPONSE_OUT_OF_RANGE, "bad_offset");
224 return true;
225 }
226
227 return false;
228}
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().

◆ ts_blank_page_placeholder

uint8_t ts_blank_page_placeholder[256]

Definition at line 169 of file tunerstudio.cpp.

Referenced by getWorkingPageAddr().

◆ tsInstance

TunerStudio tsInstance

Definition at line 613 of file tunerstudio.cpp.

Referenced by tsProcessOne().

◆ tsState

Go to the source code of this file.