Shop OBEX P1 Docs P2 Docs Learn Events
Prop2 ROM code - Page 15 — Parallax Forums

Prop2 ROM code

11315171819

Comments

  • jmgjmg Posts: 15,140
    edited 2016-10-18 22:49
    Rayman wrote: »
    Is this still about pushing serial with RC oscillator to the limit?
    Isn't it better just to load a tiny code at 115200 that starts up the PLL and then goes to 3 MBaud?

    Does not sound like a speed issue to me, more a multiple ISR issue - Chip wants to have AutoBaud live-trim, and that will occur at all baud speeds.

    From Chip's other posts, the Serial speed is now above the SHA calculate speed, so physical baud speed is not a ceiling anymore.
    With the new fractional baud feature, the physical limit for Autobaud should be around 3MBd, well above SHA speed.

    There is still benefit in having good AutoBaud, fast Smart Pin access, and compact Auto-Baud trim, as that frees CPU cycles for the SHA.

    In posts in other threads, I've expanded on using the special properties of 0x55 as the Auto-Baud trim, which means you do not need to have two ISR's firing at all.

    This uses SmartPins in the x-count timed capture mode (X=5), and each RXINT simply checks/reads and re-arms capture HW.
    If it finds the unique 0x55 Capture signature, then it can refresh the baud trim.

    Initial AutoBaud uses tFF,tRR dual edge-edge timing mode, to allow Terminal-visible Autobaud start chars.
  • cgraceycgracey Posts: 14,133
    edited 2016-10-19 02:06
    evanh wrote: »
    My experience is setups that have 7-bit data (Which I do run into still) always have parity too.

    That's interesting. That would actually work okay. Not as simple as 8-N-1, but still allows for transmission values which have single high-to-low transitions for automatic resync. And we would know if we received a bad value. Something to consider, I guess. The "@" character ($40, P=1) would transmit as ...10000000111...
  • cgraceycgracey Posts: 14,133
    edited 2016-10-19 02:14
    jmg wrote: »
    cgracey wrote: »
    I'm having a devil of a time with the serial autobaud, still. There are very infrequent data errors that I believe are due to interplay between the autobaud ISR and the receiver ISR*. They trip over each other every so often. I'm kind of back to the drawing board.

    Did you look at my suggestion of using 0x55 for Auto-Baud trim ?
    That means you do NOT need to have two ISRs firing at all.
    This uses SmartPins in the x-count timed capture mode (X=5), and 0x55 has a unique signature, visible in a single value, that RXINT simply reads and re-arms.
    cgracey wrote: »
    Question for now: Does anybody know if using 7-bit serial is problematic, as opposed to the more common 8-bit? I think, long ago, 7-bit was quite the standard, but can all modern systems be expected to handle it? It gives us more options for autobauding, as now the MSB could be set, making single-pulse word transmissions possible, which are super for re-syncing. Any dangers calling for 7-N-1 serial (could also be 8-N-1 with MSB set)?

    I would avoid niche things like 7-N-1, as many USB UARTS will barf on that, but I'm less concerned about using the whole ASCII table. (ie MSB set is fine)

    My earlier suggestions used 0xFE and 0xFF as Autobaud chars, as they are highly baud-skew tolerant, but I morphed that into the dual-edge capture of tRR, tFF to allow your wish of Terminal friendly characters.

    My current preference is to use "@" and "x" as AutoBaud FIRST chars, which are spare in my 64b encode, and these allow a t8 capture, which should mesh better with the fractional baud rate.
    This is better technically than t7. "U"(0x55) is used to AutoBaud-track

    Can you give more info on how the fractional baud applies to the bit-slots ?

    * Addit: I would suggest you 'park' a copy of the dual ISR, for later inspection, in case the issue is hardware related.
    I decided running both interrupts during RX would consume valuable cycles, and in a somewhat erratic-in-time manner, so the 0x55 trim was chosen instead.


    Getting by on one interrupt would be 10x better. This interrupt conundrum I'm dealing with is exactly the kind of thing that makes interrupts something to avoid.

    I'm hard-coding the baud to 1M right now to make sure there is not some other problem.
  • cgraceycgracey Posts: 14,133
    Yep. With a fixed 1M baud, I cannot get it to fail. It was definitely the autobaud interrupt that was causing problems.

    Jmg, question: How do you know when to capture the $55 transitions, since those bytes may be spaced apart. The whole problem is divining the start bit, especially amid continuous data.
  • jmgjmg Posts: 15,140
    edited 2016-10-19 03:06
    cgracey wrote: »
    Jmg, question: How do you know when to capture the $55 transitions, since those bytes may be spaced apart. The whole problem is divining the start bit, especially amid continuous data.

    In my notes, I have this split into two distinct AutoBaud operations
    ; 0x40 "@" : tRR = 2, tFF =8 Margins: -6b,+6b = usable
    ; 0x78 "x" : tRR = 5, tFF =8 Margins: -3b,+3b = usable,
    
     INT_RISE:  // AutoBAUD-First, repeat until valid, then disable this code - SmartPin Edge-Edge captures
     tRR = CaptRR()
     tFF = CaptFF()
     IF tRR >= tFF THEN  // Framing error/bad phase 
       RETI
     ELSE   // can add more limit tests if desired, this code expects "x" or "@" and simply slice-tests for "x" or "@"
       Disable INT_RISE   
       IF tFF*7 > tRR*16 THEN  // Decide which, tFF is always t8, slice at 3.5/8
          TwoPin_AutoBaud(tFF) // Start UART, tFF based fractional Baud, Two Pin mode
          TxSend(TwoPinACK)  
       ELSE  
          OnePin_AutoBaud(tFF) // Start UART, tFF based fractional Baud, One Pin mode
          TxSend(OnePinACK)  
       END	  
     END
     
     INT_RX:  // ONLY this interrupt is active during Data flows
       IF  CaptReady() THEN  // Start =\_, capture on 5th _/=, (X=5), nothing ready for < 5 _/=
         t9 = ReadCapt()
         AutoBaudRetrim(t9)
       END
       ReadCaptReArm()  // ALWAYS ReArm, any counts < 5 are flushed, and Smart Pin capture is reset
    // process rx Char   
    

    The first, coarse autobaud operation, uses 2 Smart pins, and captures tRR and tFF, then derives Baud from that.
    Importantly, this can exclude mid-byte reset exit, and has a wide dynamic range.
    It can also readily use more than one AutoBaud value, to signal OnePin / Two Pin.

    Once that coarse is done, then 0x55 becomes active, along with RXINT, and that is finer tracking-trim.

    That checking is made on the Rx Stop bit, and this does expect the finer tracking means you cannot lose Rx Sync

    I doubt the RC osc can drift enough between 0x55 characters, to go outside the 0x55 catch range. ( > 5%)
    You can insert as many 0x55's as you like. eg every 2.5ms SHA frame.

    The smart pin modes deeper details are unclear in the docs, but this capture requires that the Smart Pin has a mode that can
    a) Start on falling edge A
    b) Count 5 rising edges on B
    c) capture time from a) on 5th edge, and hold result until read, or re-armed. (clears B counter)


  • jmgjmg Posts: 15,140
    cgracey wrote: »
    Yep. With a fixed 1M baud, I cannot get it to fail. It was definitely the autobaud interrupt that was causing problems.
    One thought - did you check the fractional baud operation, & try that 1MBd with those increments ? (in case fractional baud, which is quite new, has problems)

  • Cluso99Cluso99 Posts: 18,066
    As long as 115,200 baud is robust, anything else will be a bonus. A 2 stage loader will solve big files.

    IMHO, this is getting way more compilcated than it needs to be.

    When using one interrupt to retime the start bit, it is simple enough to initialise on any ASCII character with the LSB=1. Just measure the start bit, and ensure the character fits the ASCII chart.

    That is why the "AT" & "at" command set was used in modems - when the micros were slow.
    IIRC 8p1 was supported, and I think 7p1 too. Of course 2 stops were allowed on receive by default. Not sure if sending was always sent as 2 stop or there was an Sxx setting. "p"=parity as follows: N= no parity, E=even parity, O=odd parity, M=mark parity="1", S=space parity="0".
    Worked brilliantly!
  • jmgjmg Posts: 15,140
    jmg wrote: »
    The smart pin modes deeper details are unclear in the docs, but this capture requires that the Smart Pin has a mode that can
    a) Start on falling edge A
    b) Count 5 rising edges on B
    c) capture time from a) on 5th edge, and hold result until read, or re-armed. (clears B counter)
    Another variant of this Single SmartPin 0x55 t9 capture, would be one that is armed, and then measures time for 5 falling edges (X=5).
    That would give t8 result, and may be closer to the SmartPin "For X periods, count time" mode in the DOCs ?
    This also needs to hold until read.

  • jmgjmg Posts: 15,140
    edited 2016-10-19 05:08
    Cluso99 wrote: »
    As long as 115,200 baud is robust, anything else will be a bonus.
    Chip already has 1MBd working, it just needs Autobaud firming up,
    Cluso99 wrote: »
    IMHO, this is getting way more compilcated than it needs to be.
    Dual interrupts is complex, but the design I have above only needs one interrupt. Very simple.
    Cluso99 wrote: »
    When using one interrupt to retime the start bit, it is simple enough to initialise on any ASCII character with the LSB=1. Just measure the start bit, and ensure the character fits the ASCII chart.
    However, something that simplistic has it's own shortcomings.
    * It pairs poorly with Fractional Baud, because it simply lacks precision.
    * It has no tolerance to mid-char phase errors, unless you redefine the "A".
    Even then, you are still unsure when to start the UART.

    In contrast, the tRR,tFF design above makes use of the smart-pins, and
    * Pairs well with Fractional Baud feature, as it has t8 Precision
    * Retries on phase errors and can discriminate AutoBaud chars, and starts the UART in the correct place.


    With SmartPins on the P2 already used to help this, I'm sure this is very close.
    Just needs a fine-tune pass down to a single RX interrupt, and a Smart-Pin tracking mode, that measures over more than just one bit.
    My reading of the DOCs has that capability already in the SmartPins.
  • cgraceycgracey Posts: 14,133
    jmg wrote: »
    cgracey wrote: »
    Yep. With a fixed 1M baud, I cannot get it to fail. It was definitely the autobaud interrupt that was causing problems.
    One thought - did you check the fractional baud operation, & try that 1MBd with those increments ? (in case fractional baud, which is quite new, has problems)

    I did a thorough test yesterday of the fractional baud, since I was thinking that perhaps there was something wrong with it. It works perfectly. There was some interplay between ISRs that was breaking things - even at 115,200 baud.
  • jmgjmg Posts: 15,140
    cgracey wrote: »
    I did a thorough test yesterday of the fractional baud, since I was thinking that perhaps there was something wrong with it. It works perfectly. There was some interplay between ISRs that was breaking things - even at 115,200 baud.
    Good to have it proven :)

    How exactly does the Fractional portion map to the available bit-slots in every byte ?
  • cgraceycgracey Posts: 14,133
    jmg wrote: »
    cgracey wrote: »
    I did a thorough test yesterday of the fractional baud, since I was thinking that perhaps there was something wrong with it. It works perfectly. There was some interplay between ISRs that was breaking things - even at 115,200 baud.
    Good to have it proven :)

    How exactly does the Fractional portion map to the available bit-slots in every byte ?

    Those fractional-number bits feed an NCO which updates on every whole-number countdown/reload. If the NCO is overflowing on the countdown/reload, an extra clock is elapsed. The NCO does not get reset, at any time. So, that fractional baud rate persists across all data.
  • cgraceycgracey Posts: 14,133
    edited 2016-10-19 11:33
    Jmg, I found yet another way to autobaud.

    The problem has been that by the time we recognize the autobaud byte at a high baud rate, a new start bit has already begun, so it's too late to reset the serial receiver pin in time for it to catch that next byte.

    I found a way to deal with this: Have the autobaud character used twice in a row. You recognize the 1st one, and then wait through the expected transitions as the 2nd one comes through, resetting and releasing the serial receiver pin on the last low-to-high transition, so that it is ready before the start bit of the next byte. I used '@@' for this, since it is not a common character and very easy to sense ('@' = $40 = ..10000000101.. = 8FF:2RR).

    This works perfectly now, as there is no entanglement between ISR's. Each ISR runs independent of the other.

    Here is what a short download looks like:

    @@Prop_Txt 0 0 0 0 +/cj9v37I/YlJoD/KIBm/fD/n/0~

    Here are the new autobaud and serial receiver ISR's. There are actually 3 different autobaud ISR's that switch in sequence:
    '
    '
    ' Autobaud ISR
    '		  falls |---8---|
    ' 1st and 2nd $40 -> ..10000000101..10000000101..
    '			 rises |2|
    '
    ' ISR 'a'	runs on 2nd rise in 1st '@'	checks for '@', if '@' then ISR 'b' next
    ' ISR 'b'	runs on 1st rise in 2nd '@'	resets receiver, sets baud, ISR 'c' next
    ' ISR 'c'	runs on 2nd rise in 2nd '@'	enables receiver, ISR 'a' next
    '
    autobaud_isr_a	rdpin	a0,#rx_tne		'2	get fall-to-fall time	(8x if $40)
    		rdpin	a1,#rx_tpe		'2	get rise-to-rise time	(2x if $40)
    
    		shl	a0,#10			'2	normalize both times for comparison
    		shl	a1,#12			'2
    		sub	a1,a0			'2	get absolute difference between normalized times
    		abs	a1			'2
    		shr	a0,#5			'2	if time/32 > difference, got $40 ('@')
    		cmp	a0,a1		wc	'2
    
    	if_nc	mov	ijmp1,#autobaud_isr_b	'2	if "@", ISR 'b' next
    
    		reti1				'4	exit
    
    
    autobaud_isr_b	dirl	#rx_rcv			'2	reset receiver
    		akpin	#rx_tpe			'2	acknowledge pin
    		rolbyte	a0,#7,#0		'2	set 8 bit word size
    		wxpin	a0,#rx_rcv		'2	set receiver baud rate and word size
    		mov	ijmp1,#autobaud_isr_c	'2	ISR 'c' next
    		reti1				'4	exit
    
    
    autobaud_isr_c	dirh	#rx_rcv			'2	enable receiver before next start bit
    		akpin	#rx_tpe			'2	acknowledge pin
    		mov	t0,a0			'2	save baud rate for transmitter
    		mov	ijmp1,#autobaud_isr_a	'2	ISR 'a' next
    		reti1				'4	exit
    '
    '
    ' Receiver ISR
    '
    receiver_isr	rdpin	a2,#rx_rcv		'get byte from pin
    		shr	a2,#24			'shift byte down
    		wrlut	a2,head			'write byte to circular buffer in lut
    		incmod	head,#lut_btop		'increment buffer head
    		reti2				'exit
    

    At 20MHz, this can handle 2_000_000-8-N-2.

    Those '@@' characters are filtered out before parsing, so you can put them in your download data as often as you want.

    The last thing I need to do is make sure that the serial receiver buffer doesn't overrun at high baud rates when those SHA-256 block hashes occur every 64 data bytes. I'll test it with the Base64 code, since that's the densest.
  • cgraceycgracey Posts: 14,133
    I was able to use the RESI1 instruction, instead of the MOV+RETI1 combo to resume on the next interrupt:
    '
    '
    ' Autobaud ISR
    '		  falls |---8---|
    ' 1st and 2nd $40 -> ..10000000101..10000000101..
    '			 rises |2|
    '
    ' ISR 'a'	runs on 2nd rise in 1st '@'	checks for '@', if '@' then ISR 'b' next
    ' ISR 'b'	runs on 1st rise in 2nd '@'	resets receiver, sets baud, ISR 'c' next
    ' ISR 'c'	runs on 2nd rise in 2nd '@'	enables receiver, ISR 'a' next
    '
    autobaud_isr_a	rdpin	a0,#rx_tne		'2	get fall-to-fall time	(8x if $40)
    		rdpin	a1,#rx_tpe		'2	get rise-to-rise time	(2x if $40)
    
    		shl	a0,#10			'2	normalize both times for comparison
    		shl	a1,#12			'2
    		sub	a1,a0			'2	get absolute difference between normalized times
    		abs	a1			'2
    		shr	a0,#5			'2	if time/32 > difference, got $40 ('@')
    		cmp	a0,a1		wc	'2
    
    	if_c	reti1				'2/4	if not '@', exit
    
    		resi1				'4	got '@', resume on next interrupt
    
    autobaud_isr_b	dirl	#rx_rcv			'2	reset receiver
    		akpin	#rx_tpe			'2	acknowledge pin
    		rolbyte	a0,#7,#0		'2	set 8 bit word size
    		wxpin	a0,#rx_rcv		'2	set receiver baud rate and word size
    
    		resi1				'4	resume on next interrupt
    
    autobaud_isr_c	dirh	#rx_rcv			'2	enable receiver before next start bit
    		akpin	#rx_tpe			'2	acknowledge pin
    		mov	t0,a0			'2	save baud rate for transmitter
    		mov	ijmp1,#autobaud_isr_a	'2	ISR 'a' next
    
    		reti1				'4	exit
    
  • jmgjmg Posts: 15,140
    edited 2016-10-19 19:35
    cgracey wrote: »
    The problem has been that by the time we recognize the autobaud byte at a high baud rate, a new start bit has already begun, so it's too late to reset the serial receiver pin in time for it to catch that next byte.
    ....
    At 20MHz, this can handle 2_000_000-8-N-2.

    2MHz is a nice number :)

    What is the imposed upper Baud, with 2 Stop bits, without the 3-sequence doubled "@@" interrupts ?

    Did you try 0x55 AutoBaud-trim, via SmartPin mode change ?

    Running those AutoBaud interrupts live during data-stream seems complex, and costly in cycles, which are better used in SHA ?

    It also mandates the data always has a pair of "@@", or at least, "@" followed by a 2-edge character, since the second test is less-strict.

    Locking in those Pairs could get tricky, in a working system ?

    Imagine you reset a P2, then release, and start sending "@@", with any spacing.
    This is a typical MCU/PC host (and also why I think an AutoBAUD ACK char needs to be sent)

    When P2 comes out of reset, it can do so in any phase, and so can miss part/all of first @, and now, all others are out of phase.
    autobaud_isr_a is Phase tolerant, but it must have an exactly-2-edge character following, that it waits for.

    I guess with an ACK, the first out of reset code can become a stream of single "@", that pair-up in the P2
    REPEAT
     RateDelay
     Send("@")
     PauseRxEnable
    UNTIL RxRdy AND (RxChar = ACK)
    
    That's pretty much what my MCU code does already, in both OnePin and TwoPin cases.
    PC code needs a little more care, as the rate delay needs to ensure the USB-UART can reply if this is the last-needed-"@".
    PC-USB latency is in the order of 1ms (FS) or 125us (HS), not sure what WiFi or Bluetooth adds to this, but probably something rather variable :(

    Removing that pairing dictate, makes this more latency tolerant. Bonus/overflow '@' of any number, are now simply atomic NOPs.

    One Reset exit is done, I'd suggest use the single 0x55, as more robust, and it can disable all autobaud_isr, for highest CPU cycles.
  • jmgjmg Posts: 15,140
    cgracey wrote: »
    The last thing I need to do is make sure that the serial receiver buffer doesn't overrun at high baud rates when those SHA-256 block hashes occur every 64 data bytes. I'll test it with the Base64 code, since that's the densest.

    Base64 is the densest, but HEX is the slowest, so HEX can require a higher baud rate, to still meet SHA timing.

    AutoBaud needs to be comfortably higher than this, (by maybe a 2:1 margin, as some systems have more coarse baud options), but it does not need to be 3x or more capable.

    For 2.5ms nominal times, I get numbers like :
    Of course, as you free more cycles for SHA, that 2.5ms can shrink, which pushes up these values.

    For HEX streams "HH ", one DataByte per 3 Chars
    11*(3)*(64/2.5m) = 844800 2 Stop Bits, hex
    10*(3)*(64/2.5m) = 768000 1 Stop Bit hex

    Faster SHA of 2ms
    11*(3)*(64/2.0m) = 1056000 2 Stop Bits,
    10*(3)*(64/2.0m) = 960000 1 Stop Bit

    or, Packed hex stream (strips " ")
    11*(2)*(64/2.5m) = 563200 2 Stop Bits,
    10*(2)*(64/2.5m) = 512000 1 Stop Bit


    For Base64, 3 data bytes in 4 chars
    11*(4/3)*(64/2.5m) = 375466.666 2 Stop Bits,
    10*(4/3)*(64/2.5m) = 341333.333 1 Stop Bit
  • jmgjmg Posts: 15,140
    edited 2016-10-19 20:29
    cgracey wrote: »
    autobaud_isr_a	rdpin	a0,#rx_tne		'2	get fall-to-fall time	(8x if $40)
    		rdpin	a1,#rx_tpe		'2	get rise-to-rise time	(2x if $40)
    
    		shl	a0,#10			'2	normalize both times for comparison
    		shl	a1,#12			'2
    		sub	a1,a0			'2	get absolute difference between normalized times
    		abs	a1			'2
    		shr	a0,#5			'2	if time/32 > difference, got $40 ('@')
    		cmp	a0,a1		wc	'2
    
    	if_c	reti1				'2/4	if not '@', exit
    

    My gut says this is tight... so running that time/32 code, to check for measurement quanta on the t2 value, gives this
    (you need to reject 2:7, which is one part in 28 different from 2:8, so t/32 is reasonable ie t/16 is not going to reject 2:7)
     St8=8*(20M/1.2M) << 10   St8 = 136533
     St2=(0+2*(20M/1.2M))<<12 St2 = 136533
     abs(St8-St2)-(St8 >> 5)  ans = -4266 
     St2=(1+2*(20M/1.2M))<<12 St2 = 140629
     abs(St8-St2)-(St8 >> 5)  ans = -170   OK 1.2Mb can tolerate a +1/-1 variance on t2
     St2=(-1+2*(20M/1.2M))<<12 St2 = 132437
     abs(St8-St2)-(St8 >> 5)  ans = -170
    
    
     St8=8*(20M/1.25M) << 10   St8 = 131072
     St2=(0+2*(20M/1.25M))<<12 St2 = 131072
     abs(St8-St2)-(St8 >> 5)   ans = -4096
     St2=(1+2*(20M/1.25M))<<12 St2 = 135168
     abs(St8-St2)-(St8 >> 5)   ans = 0   Limit 1.25Mb case for a +1/-1 variance on t2
     St2=(-1+2*(20M/1.25M))<<12 St2 = 126976
     abs(St8-St2)-(St8 >> 5)   ans = 0
    

    ie because you are leveraging that one part in 32 test, from a narrow/poor precision t2 capture, variance in that t2 capture of +/- one SysCLK, seems to impose an upper Baud limit of 1.25MBd ? for the valid char test ?

    The Baud itself, is worked from the t8 value, so it is of higher quality - but it may never pass the valid @ test.

    The first char does not need a test as strict as time/32, but that is imposed by the need to use "@" live.
    My code above, expects "@" and rejects bad-phase, and then simply slices for OnePin/TwoPin AutoBaud test.
    It does not try to do an 'exactly == "@" test.

    Looks like another good argument to using 0x55 (SmartPin X-edge counter mode) in the live case instead. This valid test is 5 edges inside a whole Char time, which only 0x55 meets.


  • cgraceycgracey Posts: 14,133
    Jmg, good point about the RR=2 in $40 ('@') being too low quality. I am going to redo it using $7E ('~'), which has RR=7 and FF=8.

    If you look at each ISR time, they are all very low.

    I really think that an initial-plus-maintenance autobaud is not the way to go, because there will be some cases where several seconds, or even hours or days, will elapse between data. Therefore, something that can occur at any time to resolutely set the baud is desirable.
  • evanhevanh Posts: 15,126
    Would the "P" work as a single character calibration? Hex code $50, 01010000 (BE) 00001010 (LE). It would save having to add extra to the commands. I assume the autobauding doesn't have to be a white space character?
  • jmgjmg Posts: 15,140
    edited 2016-10-19 21:43
    cgracey wrote: »
    Jmg, good point about the RR=2 in $40 ('@') being too low quality. I am going to redo it using $7E ('~'), which has RR=7 and FF=8.
    That should be better, I'll check that.

    addit : yes, seems somewhere just over 4MBd is the measurement +/-1 effect limit now, (I guess it is actually 1.25*3.5 = 4.375MBd)
    That's now well clear of imposing any limit on the design.

    cgracey wrote: »
    If you look at each ISR time, they are all very low.

    True, but the capture INTs fire on every rising edge, which can be 3-4-5 times per char.
    The longer autobaud_isr_a one will be where it repeats, until a ValidChar passes.
    cgracey wrote: »
    I really think that an initial-plus-maintenance autobaud is not the way to go, because there will be some cases where several seconds, or even hours or days, will elapse between data. Therefore, something that can occur at any time to resolutely set the baud is desirable.

    Hmm, I can understand that desire, but would most systems not have a reset-control also associated with download ?
    If you really want/expect scenarios of "even hours or days, will elapse between data", maybe there is some way to get 0x55 to work as both ?
  • cgraceycgracey Posts: 14,133
    edited 2016-10-19 21:46
    evanh wrote: »
    Would the "P" work as a single character calibration? Hex code $50, 01010000 (BE) 00001010 (LE). It would save having to add extra to the commands. I assume the autobauding doesn't have to be a white space character?

    One problem with $50 is that there are two points at which a false start bit could be seen. These other values we've been using only have one false point by having a single, contiguous group of 1's in the data.

    What would be very important would be to be able to place that group of 1's up against the start bit, but in 8-bit serial, that means characters over $7F, which are not consistently possible to (easily) generate, due to filtering that occurs from libraries and programming language conventions. If we could go to seven-bit serial, even '@' would do this: ..1000000011.. That is important, because two such characters in a row will always result in a proper sync by the receiver. I'd really like to just go seven bits, like 7-N-1, or even 7-MARK-1, which would be 8-bit with the MSB always set, giving us two effective start bits, which is ideal.
  • jmgjmg Posts: 15,140
    edited 2016-10-19 23:42
    cgracey wrote: »
    I'd really like to just go seven bits, like 7-N-1, or even 7-MARK-1, which would be 8-bit with the MSB always set, giving us two effective start bits, which is ideal.
    That's likely to be rather too niche.... :(

    Here is another approach, it buys one more bit time, which is really the only remaining fishhook here.
    ie we really want to avoid that double-char pairing.
    ; 0x40 "@" : tLL = 7, tFF =8
    ; =======\_s_._0_._1_._2_._3_._4_._5_/=6=\_7_/=P==T=\_s_._0_._1_._2_._3_._4_._5_/=6=\_7_/=P=
    ; tFF    |s                           8  |r    2+T  |r                          8   |r  2+T |r   << INT on this one
    ; tLL    |g                         7|e  |1  |f                            8+T  |r    2 |r      
    ;        f             OK tLL:7b,tFF:8b -^          ^- Err:tLL:1,tFF:2b+T(bad phase)
    ; tLL,tFF Margins: 7:8, 1:2(+T) = usable  
    

    This uses "@", but now captures tFF and tLL (gated low time) Bad phase is detectable.

    autobaud_isr_a Interrupt is on tFF, which is one clock earlier, buying time for the Autobaud char check maths.

    At 2 stop bits, there is now 3-bit times, from measurement capture, to possible first RxD edge. (2 bit times at one stop bit)

    At very low baud, it may need to wait for the stop-bit rise, if the uart does not like being enabled with RxD=L.
    If the SmartPin uart starts on a proper falling edge =\_, then that would not be needed.


  • cgraceycgracey Posts: 14,133
    Jmg, that is excellent!!!

    So, $40 ('@') transmits as such: ..10000000101..

    We would interrupt on the fall-to-fall and have a low-time measurement waiting from the previous run of seven 0's. The fall-to-fall would be 8x and the low-time would be 7x. We would be landing on the MSB which is 0, about to be followed by the stop bit which is 1. We can reset the serial receiver smart pin right then, because it actually waits for a high-to-low transition before registering a start bit. This would be, like you said, a one-character solution: simply '@'.
  • jmgjmg Posts: 15,140
    cgracey wrote: »
    Jmg, that is excellent!!!

    So, $40 ('@') transmits as such: ..10000000101..

    We would interrupt on the fall-to-fall and have a low-time measurement waiting from the previous run of seven 0's. The fall-to-fall would be 8x and the low-time would be 7x. We would be landing on the MSB which is 0, about to be followed by the stop bit which is 1. We can reset the serial receiver smart pin right then, because it actually waits for a high-to-low transition before registering a start bit. This would be, like you said, a one-character solution: simply '@'.

    Sounding good, one minor detail I see, is the new sense of 7/8 has to reject 6/7 and 9/10, which bumps that time/32 to time/64
    and that drops the gain we had to 4.375MBd back to ~2.15MBd - which I think is still comfortably above SHA rates ?

    cgracey wrote: »
    We would interrupt on the fall-to-fall and have a low-time measurement waiting from the previous run of seven 0's.
    Yes. I've assumed this is single buffered, so the result is readable, while a new one is being collected ?

  • cgraceycgracey Posts: 14,133
    jmg wrote: »
    cgracey wrote: »
    Jmg, that is excellent!!!

    So, $40 ('@') transmits as such: ..10000000101..

    We would interrupt on the fall-to-fall and have a low-time measurement waiting from the previous run of seven 0's. The fall-to-fall would be 8x and the low-time would be 7x. We would be landing on the MSB which is 0, about to be followed by the stop bit which is 1. We can reset the serial receiver smart pin right then, because it actually waits for a high-to-low transition before registering a start bit. This would be, like you said, a one-character solution: simply '@'.

    Sounding good, one minor detail I see, is the new sense of 7/8 has to reject 6/7 and 9/10, which bumps that time/32 to time/64
    and that drops the gain we had to 4.375MBd back to ~2.15MBd - which I think is still comfortably above SHA rates ?

    cgracey wrote: »
    We would interrupt on the fall-to-fall and have a low-time measurement waiting from the previous run of seven 0's.
    Yes. I've assumed this is single buffered, so the result is readable, while a new one is being collected ?
    jmg wrote: »
    cgracey wrote: »
    Jmg, that is excellent!!!

    So, $40 ('@') transmits as such: ..10000000101..

    We would interrupt on the fall-to-fall and have a low-time measurement waiting from the previous run of seven 0's. The fall-to-fall would be 8x and the low-time would be 7x. We would be landing on the MSB which is 0, about to be followed by the stop bit which is 1. We can reset the serial receiver smart pin right then, because it actually waits for a high-to-low transition before registering a start bit. This would be, like you said, a one-character solution: simply '@'.

    Sounding good, one minor detail I see, is the new sense of 7/8 has to reject 6/7 and 9/10, which bumps that time/32 to time/64
    and that drops the gain we had to 4.375MBd back to ~2.15MBd - which I think is still comfortably above SHA rates ?

    cgracey wrote: »
    We would interrupt on the fall-to-fall and have a low-time measurement waiting from the previous run of seven 0's.
    Yes. I've assumed this is single buffered, so the result is readable, while a new one is being collected ?

    How about using $20 as the autobaud character in the same way, and making the assumption that the MSB is low, too, since $A0 should never be sent? This would mean stuffing a $20 into the receiver buffer and finding a way to inhibit an in-progress receiver ISR from also modifying the buffer. This is what I was having trouble with before: the receiver ISR seemed to get interrupted by the autobaud ISR in the case where the autobaud ISR actually identified the autobaud character and attempted to stuff the $20.
  • cgraceycgracey Posts: 14,133
    I think that to do this, the serial receiver needs to be handled in the same interrupt as the autobaud. Using $20 would give us at least THREE bit periods to reset the receiver smart pin. That's plenty.
  • jmgjmg Posts: 15,140
    edited 2016-10-20 19:56
    cgracey wrote: »
    How about using $20 as the autobaud character in the same way, and making the assumption that the MSB is low, too, since $A0 should never be sent? This would mean stuffing a $20 into the receiver buffer and finding a way to inhibit an in-progress receiver ISR from also modifying the buffer. This is what I was having trouble with before: the receiver ISR seemed to get interrupted by the autobaud ISR in the case where the autobaud ISR actually identified the autobaud character and attempted to stuff the $20.

    Do you mean as well as the "@", or instead of the "@".
    My instinct would be to avoid a delineation character like " ", which form part of normal messages, but to allow users to choose when they do the Autobaud-refresh. (also see below, where AutoBaud char may reset parser)

    $20 is now 7 bit times, not 8, so the precision is lower, (and so is upper baud) and it fits less well with the AutoBAUD fractions.

    cgracey wrote: »
    I think that to do this, the serial receiver needs to be handled in the same interrupt as the autobaud. Using $20 would give us at least THREE bit periods to reset the receiver smart pin. That's plenty.

    What is the actual needed SHA time ? - ie what ceiling baud rates are being imposed by that ?

    Is the extra bit time the "@" buys not enough, to re-phase the baud clock. (with 2 stop bits ?)

    What do to with any active/ending Rx, depends on how large a "catch range / drift range " you want.

    To me 5-10% seems ok, with most tracking steps < 4%, so Rx is also valid, but if you want a full 30%, that's an added complexity.

    I'm still not sure there is a real use-case for this very wide tracking, as most cases I can think of would control reset with Boot.
    Is your desire for hours-days of drift tolerance realistic use ?

    Tracking drift during a common download I can see is useful, but here refresh times can be under 1 second, and so have smaller increments.
    eg RX is unlikely to be corrupted.
    This is where the 0x55 re-sync shines, as it has minimal overhead, freeing cycles for SHA work, thus speeding boot times.

    For very wide catch ranges, I think there will always be issues - eg, if the SysCLK has sped up since last re-set, RxINT can move much earlier, and it will also have a corrupt value. In that extreme case, skewed RxINT (SysCLK based) can even precede the capture INT (Data based).

    For those larger ranges, I think you need to do more than just adjust the Baud-setting.
    You would need to reset the UART-state engine, and maybe even reset the parser (ie require that a AutoBaud is more aggressive, and always has a fresh command following, so cannot embed within data.)

    If SysCLK has slowed down significantly, the RxINT is pushed right, so more time exists, but you still need to reset the UART, in order to catch the start bit you know is close, but the UART thinks is further away.

  • jmgjmg Posts: 15,140
    Further thoughts to this larger catch range, being the only remaining issue ...

    I'd suggest doing a ROM release with the preamble AutoBaud and the 0x55 Smart Pin tracking.

    This has the simplest download-code, and runs a single interrupt during Download, but I admit it cannot manage very large steps in P2 OSC.
    I think most uses cases will reset, (manually, or via control line, as in P1), then download, so large deviations between AutoBaud are unlikely, and hours/days of drift tolerance are not a 'in demand' feature.

    This will work fine on P2 FPGAs and you can test the Step Size and Tracking slew speeds in such a release, (by deliberate Baud Skew) in parallel with measuring the Test Chip Actual RC Osc curves with Vcc/Temp.

    Meanwhile, others can test USB with the new 2 cycle port access.
  • cgraceycgracey Posts: 14,133
    I've got it working at 2M baud, with a few more innovations, but I've encountered what seems like a cog hardware bug. I'm totally stumped right now.
  • Cluso99Cluso99 Posts: 18,066
    cgracey wrote: »
    I've got it working at 2M baud, with a few more innovations, but I've encountered what seems like a cog hardware bug. I'm totally stumped right now.
    Then it's time to give yourself a change!

    Work out what you require on the test pcb. Perhaps I can help with the layout?
Sign In or Register to comment.