EmbeddedRelated.com
Blogs

Introduction to Microcontrollers - Ada - 7 Segments and Catching Errors

Mike SilvaSeptember 22, 20145 comments

Quick Links

7 Segments the Ada Way

Here is the Ada version (I should say AN Ada version) of the 7 segment multiplexing code presented in the last installment.  The hardware now is the STM32F407 Discover board, which is a Cortex M4F board.  There are lots of differences in GPIO and timer setup, but if you understoold the previous code in C you should not have much trouble understanding this code in Ada.

As interesting as the Ada approach to the task is the Ada ability to detect runtime errors, as demonstrated in both planned and unplanned ways, described below.

Ada is still new to me, so no doubt I'm not taking full advantage of the language and am writing far too much "C in Ada".  That's a problem with starting any new language, especially a powerful one.

Zipped source files 

Some Details

Timer 6 is used to generate our 2.5ms multiplexing interrupts, chosen because it's one of the least-capable timers on the chip.  Save the better timers for what they're better at.  The ISR is a procedure inside an Ada protected object called TimerP and attached to the correct interrupt vector.  There are other helper subprograms (remember, a subprogram can be either a function - returns something - or a procedure - returns nothing) inside the package that contains the protected object.  One procedure takes the supplied value to be displayed and converts it into the proper format for the 7 segment display.  Another procedure adjusts the display update rate between 100/second (400/sec interrupts) and 1/second (4/sec interrupts).

The main program loop uses the Ada runtime (using delay until) to establish a 100ms loop.  Each pass through this loop the counter value or the display update rate is passed to the timer code to be displayed.  Also each pass, the four buttons are read as before.  This time there is a little difference in the button operation, as now the 4 button actions are clear, start/stop, update rate decrease and update rate increase.  Because one button is now used as a start/stop toggle, a bit more logic is required in handling that button.  Before it was OK, if the button was held down, to perform STOP...STOP...STOP...STOP... each pass through the loop, but we don't want to perform STOP...START...STOP...START... on a held-down button, hence the additional logic needed.

The 100ms main loop could easily have been done by counting 40 of the 2.5ms interrupts, but then the loop timing becomes dependent upon the digit update timing.  In the previous version we avoided this by using a 2nd timer for the main loop, and then by using 1 timer with two leapfrog match interrupts.  In Ada it makes a lot of sense to use the built-in delay capability for the 100ms loop, because that (the use of delay until) then frees up the processor for executing other tasks.  It is also not hardware-specific, and there's something to be said for keeping the hardware-specific code as limited and contained as possible.

Finally, note how the 8 segment lines are once more divided among 3 ports(!).  In Ada I really like the idiom of Boolean packed arrays and array slices for this sort of thing.  I think it makes the bit assignments much more clear.  I could have declared the segment values array directly as packed boolean arrays, but I thought that would add too much clutter (lots of True, True, False, True, False...), so I declare them as Bytes initialized with base-2 constants, and use unchecked conversions to turn the Bytes into packed boolean arrays to do the bit array slicing.  I do the same thing in a few other places, where I just thought it was a lot easier and cleaner to encode a boolean array value as a Word or HWord.

Here's leds.adb, where I've written some new GPIO initialization procedures to make the details of setting up the GPIO a little more manageable: 

-- leds.adb

with Ada.Unchecked_Conversion;

with LCD;
with MUX_Timer;

package body LEDs is


   function As_Word is new Ada.Unchecked_Conversion
     (Source => User_LED, Target => Word);


   procedure On (This : User_LED) is
   begin
      GPIOD.BSRR := As_Word (This);
   end On;


   procedure Off (This : User_LED) is
   begin
      GPIOD.BSRR := Shift_Left (As_Word (This), 16);
   end Off;


   All_LEDs_On  : constant Word := Green'Enum_Rep or Red'Enum_Rep or
                                   Blue'Enum_Rep  or Orange'Enum_Rep;

   pragma Compile_Time_Error
     (All_LEDs_On /= 16#F000#,
      "Invalid representation for All_LEDs_On");

   All_LEDs_Off : constant Word := Shift_Left (All_LEDs_On, 16);


   procedure All_Off is
   begin
      GPIOD.BSRR := All_LEDs_Off;
   end All_Off;


   procedure All_On is
   begin
      GPIOD.BSRR := All_LEDs_On;
   end All_On;

   procedure Init_GPIO(GPIO : in out GPIO_Register; I : Natural;
                     Mode : Bits_2;
                     Otype : Bits_1;
                     Speed : Bits_2;
                    PUtype : Bits_2) is
   begin
      GPIO.MODER   (I) := Mode;
      GPIO.OTYPER  (I) := Otype;
      GPIO.OSPEEDR (I) := Speed;
      GPIO.PUPDR   (I) := PUtype;
   end Init_GPIO;

   procedure Init_GPIO(GPIO : in out GPIO_Register; LO : Natural; HI : Natural;
                     Mode : Bits_2;
                     Otype : Bits_1;
                     Speed : Bits_2;
                     PUtype : Bits_2) is
   begin
      for I in LO..HI loop
        Init_GPIO(GPIO, I, Mode, Otype, Speed, PUtype);
      end loop;
   end Init_GPIO;

   procedure Init_GPIO(GPIO : in out GPIO_Register; Sel : Bits_16;
                     Mode : Bits_2;
                     Otype : Bits_1;
                     Speed : Bits_2;
                     PUtype : Bits_2) is
   begin
      for I in Sel'Range loop
        if Sel(I) then
           Init_GPIO(GPIO, I, Mode, Otype, Speed, PUtype);
        end if;
      end loop;
   end Init_GPIO;

   procedure Initialize is
      RCC_AHB1ENR_GPIOB : constant Word := 2#0_0010#;
      RCC_AHB1ENR_GPIOC : constant Word := 2#0_0100#;
      RCC_AHB1ENR_GPIOD : constant Word := 2#0_1000#;
      RCC_AHB1ENR_GPIOE : constant Word := 2#1_0000#;
      GPIO_B_Sel        : constant HWord := 2#1111_0000_0010_0011#; --12-15, 5, 0-1
      GPIO_C_Sel        : constant HWord := 2#0000_1001_0101_0110#;
      GPIO_D_Sel        : constant HWord := 2#1111_0000_1100_1100#; --12-15, 6-7, 2-3
   begin
      --  Enable clock for GPIO-D and GPIO-E
      RCC.AHB1ENR := RCC.AHB1ENR
       or RCC_AHB1ENR_GPIOB
       or RCC_AHB1ENR_GPIOC
        or RCC_AHB1ENR_GPIOD
        or RCC_AHB1ENR_GPIOE;
      -- Configure B segment outputs and digit outputs
      Init_GPIO(GPIOB, B16_From_HW(GPIO_B_Sel),
              Mode_OUT,
              Type_PP,
              Speed_2MHz,
              No_Pull);
      -- Configure C segment outputs and LED outputs
      Init_GPIO(GPIOC, B16_From_HW(GPIO_C_Sel),
              Mode_OUT,
              Type_PP,
              Speed_2MHz,
              No_Pull);
      -- Configure D segment outputs
      Init_GPIO(GPIOD, B16_From_HW(GPIO_D_Sel),
              Mode_OUT,
              Type_PP,
              Speed_2MHz,
              No_Pull);
      --  Configure PE4-9 (4-7 LCD data, 8 LCD RW, 9 LCD E
      Init_GPIO(GPIOE, 4, 9,
              Mode_OUT,
              Type_PP,
              Speed_25MHz,
              No_Pull);
      --  Configure PE2
      Init_GPIO(GPIOE, 2,
              Mode_OUT,
              Type_PP,
              Speed_25MHz,
              No_Pull);
      --  Configure PE15
      Init_GPIO(GPIOE, 15,
              Mode_OUT,
              Type_PP,
              Speed_2MHz,
              No_Pull);
      -- Configure PE10-13 (button inputs)
      Init_GPIO(GPIOE, MUX_Timer.B_CLEAR, MUX_Timer.B_FAST,
              Mode_IN,
              Type_PP,      -- don't care
              Speed_2MHz,   -- don't care
              Pull_Up);
   end Initialize;


begin
   Initialize;
   MUX_Timer.Init;
   LCD.LCD_Init;
end LEDs;

Here's MUX_Timer.adb, which has the ISR protected object and all other display formatting and multiplexing code:

-- Timer package

with Ada.Interrupts.Names;
with Registers;                   use Registers;
with STM32F4;                     use STM32F4;
with STM32F4.Timer;

package body MUX_Timer is

   -- the 4 digit enable bits, in the same order as Digit_Vals below
   Digit_Bit : constant array(DIGIT) of Word := (16#1000#, 16#2000#, 16#4000#, 16#8000#);

   -- the 4 digits to be displayed.  These are indexes into array Segs below
   Digit_Vals  : array(DIGIT) of SEG_INDEX := (others => SEG_INDEX'Last);

   -- segment patterns for the 10 digits and Blank (Segment A is LSB)
   Segs  : constant array(SEG_INDEX) of Byte := (16#3F#, 16#06#, 16#5B#, 16#4F#, 16#66#,
                                           16#6D#, 16#7D#, 16#07#, 16#7F#, 16#6F#,
                                            16#00#);

   protected TimerP is
      pragma Interrupt_Priority;

   private
      -- which digit is now being displayed
      Cur_Digit : DIGIT := 0;

      procedure Interrupt_Handler;
      pragma Attach_Handler
         (Interrupt_Handler,
          Ada.Interrupts.Names.TIM6_DAC_Interrupt);

   end TimerP;

   protected body TimerP is

      -- handler for Timer 6
      procedure Interrupt_Handler is
        -- these clear the segment outputs (spread over 3 ports!)
        Clear_B   : constant Word := 16#03_0000#;
        Clear_C   : constant Word := 16#06_0000#;
        Clear_D   : constant Word := 16#CC_0000#;
        B8        : Bits_8;
        W32       : Bits_32;
      begin
         --  Clear interrupt
        TIM6.SR := TIM6.SR - STM32F4.Timer.UIF;
        -- turn off current digit
        GPIOB.BSRR := Shift_Left(Digit_Bit(Cur_Digit), 16);
        -- clear all segment outputs
        GPIOB.BSRR := Clear_B;
        GPIOC.BSRR := Clear_C;
        GPIOD.BSRR := Clear_D;
        -- advance to next digit (3 rolls over to 0)
        Cur_Digit := Cur_Digit + 1;
        -- get next segment pattern in form of boolean array
        B8 := B8_From_B(Segs(Digit_Vals(Cur_Digit)));
        -- set port C segment outputs
        W32(0..31) := (others => False);
        W32(1..2) := B8(6..7);
        GPIOC.BSRR := W_From_B32(W32);
        -- set port B segment outputs
        W32(0..31) := (others => False);
        W32(0..1) := B8(4..5);
        GPIOB.BSRR := W_From_B32(W32);
        -- set port D segment outputs
        W32(0..31) := (others => False);
        W32(6..7) := B8(2..3);
        W32(2..3) := B8(0..1);
        GPIOD.BSRR := W_From_B32(W32);
        -- enable our new current digit
        GPIOB.BSRR := Digit_Bit(Cur_Digit);
      end Interrupt_Handler;
   end TimerP;

   -- config Timer 6 to generate 2.5ms interrupts
   procedure Init is
   begin
      RCC.APB1ENR := RCC.APB1ENR or TIM6EN; -- Timer 6 enable
      TIM6.PSC  := CLK_US - 1;              -- 2x 42MHz
      TIM6.CR1  := STM32F4.Timer.URS;
      TIM6.DIER := TIM6.DIER or STM32F4.Timer.UIE;
      Set_Interrupt_Time(UPDATE_RATE'Last);
   end Init;

   -- enable Timer 6
   procedure Enable is
   begin
      TIM6.CR1  := TIM6.CR1 or STM32F4.Timer.CEN;  -- enable timer
   end Enable;

   procedure Set_Val(Value : DISP_VAL; Blank_LZ : Boolean) is
      Val       : Natural;
      Digit_Val : Natural;
      Digit     : Natural;
      BLZ       : Boolean := Blank_LZ;
   begin
      Val := Natural(Value);
     Digit_Val := Val / 1000;
      if (Digit_val = 0) and BLZ then
        Digit := Blank;
      else
        Digit := Digit_Val;
        BLZ := False;
      end if;
      Digit_Vals(0) := SEG_INDEX(Digit);
      Val := Val mod 1000;

      Digit_Val := Val / 100;
      if (Digit_val = 0) and BLZ then
        Digit := Blank;
      else
        Digit := Digit_Val;
        BLZ := False;
      end if;
      Digit_Vals(1) := SEG_INDEX(Digit);
      Val := Val mod 100;

      Digit_Val := Val / 10;
      if (Digit_val = 0) and BLZ then
        Digit := Blank;
      else
        Digit := Digit_Val;
      end if;
      Digit_Vals(2) := SEG_INDEX(Digit);
      Val := Val mod 10;

      Digit := Val;
      Digit_Vals(3) := SEG_INDEX(Digit);
   end Set_Val;

   procedure Set_Interrupt_Time(Per_Sec : UPDATE_RATE) is
   begin
      TIM6.ARR := HWord(((1_000_000/PRE_US)/(4 * Integer(Per_Sec))) - 1);
   end Set_Interrupt_Time;


end MUX_Timer;

And finally, the main loop:

-- sevenseg.adb

with Last_Chance_Handler;  pragma Unreferenced (Last_Chance_Handler);
with System;
with Ada.Real_Time; use Ada.Real_Time;
with Registers;     use Registers;
with LEDs;          use LEDs;
with MUX_Timer;     use MUX_Timer;
with STM32F4;       use STM32F4;

procedure SevenSeg is
   pragma Priority (System.Priority'First);
   Next_Time : Time := Clock;
   Tenths    : DISP_VAL := 0;
   Per_Sec   : UPDATE_RATE := 100;
   Buttons   : Bits_32;
   Rate      : Boolean := False; -- True when showing rate, False showing Tenths
   Stop      : Boolean := False;
   Last_Stop : Boolean := False;
begin
   On(Green);
   MUX_Timer.Enable;
   loop
      MUX_Timer.Set_Interrupt_Time(Per_Sec);

      Buttons := B32_From_W(not GPIOE.IDR); -- read buttons @ 10..13
      if Buttons(B_CLEAR) then
        Tenths := 0;
        Rate := False;  -- showing tenths, not display rate
      end if;

      if Buttons(B_SS) and not Last_Stop then  -- found a leading button edge
        Stop := not Stop;
        Rate := False;  -- showing tenths, not display rate
      end if;
      Last_Stop := Buttons(B_SS);
      if not Stop then
        Tenths := Tenths + 1;
      end if;

      if Buttons(B_SLOW) then  -- slow down
        Per_Sec := Per_Sec - 1;
        Rate := True;  -- showing display rate
      end if;

      if Buttons(B_FAST) then  -- speed up
        Per_Sec := Per_Sec + 1;
        Rate := True;  -- showing display rate
      end if;

      if Rate then
        -- pass current time in 1/10 sec units to timer display
        MUX_Timer.Set_Val(DISP_VAL(Per_Sec), False);
      else
        -- pass current time in 1/10 sec units to timer display
        MUX_Timer.Set_Val(Tenths, True);
      end if;

     -- calculate next 100ms clock point and sleep until then
      Next_Time := Next_Time + Milliseconds(100);
      delay until Next_Time;
   end loop;
end SevenSeg;

Gotcha!

One of the many benefits of Ada is that the compiler can generate automatic checks to determine if any variable goes out of its assigned limits.  This includes, but is not limited to, array indexes (no buffer overruns in Ada!).  If such a variable does go out of its assigned limits, an exception is generated.  Like all exceptions, this exception can be caught ("handled" is the Ada term) locally, or it can propagate and be handled in an outer scope.  Because the propagation of exceptions involves substantial code and time resources, it is not allowed in the Ravenscar profile, but there is a "last chance handler" that will catch any exceptions your code does not handle in the local context.

The AdaCore last chance handler for their ARM product identifies the source file and line where the exception occurred, so all you have to do is write code to communicate that info to the user.  Because we have our LCD display working, it was easy to write this exception info to the display.

To generate an exception we can simply cause a "Constraint Error" by incrementing (or decrementing) a ranged value beyond its legal range.  In sevenseg.adb we have a ranged value for our display update rate, declared as 1..100, so if we just go beyond those bounds we should get an error and get our exception message on the display pointing us exactly to the offending line.  Now that is civilized programming!  It's a somewhat contrived error, intended to display Ada's exception handling, but in the midst of testing it the Ada runtime also caught a real live out of range error.  More about that later.  Here's the last chance handler writing to the LCD:

-- last_chance_handler.adb

with System.Storage_Elements;  use System.Storage_Elements;
with Ada.Unchecked_Conversion;
with LEDs;                     use LEDs;
with LCD;                      use LCD;

package body Last_Chance_Handler is

   type Char_Pointer is access all Character;
   for Char_Pointer'Storage_Size use 0;

   function As_Char_Pointer is
      new Ada.Unchecked_Conversion (Integer_Address, Char_Pointer);

   -------------------------
   -- Last_Chance_Handler --
   -------------------------

   procedure Last_Chance_Handler (Msg : System.Address; Line : Integer) is
--      pragma Unreferenced (Msg, Line);
      P : Integer_Address;
   begin
      Off (Green);
      Off (Orange);
      Off (Blue);
      On (Red);
      --  No return procedure.
      pragma Warnings (Off, "*rewritten as loop");
      
      P := To_Integer (Msg);
      LCD_Clear;
      LCD_Put_String("--Exception--");
      LCD_Goto(0, 2);
      
      loop
         LCD_Put_Char (As_Char_Pointer (P).all);
         P := P + 1;
         exit when As_Char_Pointer (P).all = ASCII.Nul;
      end loop;
      
      LCD_Put_String(" " & Integer'Image(Line));
      
      <<spin>> goto spin;   -- yes, a goto!
      pragma Warnings (On, "*rewritten as loop");
   end Last_Chance_Handler;

end Last_Chance_Handler;

Second Things First!

I wanted to write here about a classic type of bug that the Ada runtime caught for me, but first I'll talk about another bug, one that no language could have discovered.  In testing the slow/fast buttons I ran into another bug, and this is a bug that I knew could happen and I planned to code against, but somehow I forgot.  The problem can occur when you make your ARR value (or any match register value) smaller while the timer is running.  If you're unlucky (and you will be!), you will write out the smaller value after the timer has passed that new value, so the timer will run all the way to its natural overflow (2^16 or 2^32 counts) before giving normal operation again.

To give some concrete numbers, suppose your ARR register is set to 2000, and your CNT is now passing 1500 as you load the ARR register with 1000.  The CNT will never see the 2000 that was in ARR, and will run until natural overflow before seeing the new 1000 ARR value.  As you can see, this problem always happens when loading ARR values that are smaller than the current ARR value, if the load happens when CNT is in the range between the two values.  To see the bug, lower the update rate down close to one, then hold the "faster" button down.  You'll see one or more times that a single digit stops and glows, then normal behavior continues.  This is the digit that was being displayed when the timer ran to natural overflow, resulting in it being displayed for much longer than it should have been.  The bug will be much more visually evident with a timer clock (PRE_US) of 5 rather than 1, but it will happen in either case.  See the next section to understand this comment.

Often the timer hardware will have a way to avoid this problem, in the form of a shadow or buffer register that holds the new ARR value and only loads it when the timer goes to zero (it is always safe to load a match register at this point).  This is the bit that I meant to set in the timer configuration (the bit, ARPE, forces the use of a preload register), but forgot.  The other solution, that works in 99% of cases, is to manually load the new ARR value in the timer interrupt ISR.  In the ISR you know the timer value is very near to 0 - near as in how many timer ticks have happened since the timer interrupt was raised and responded to, and your ARR-setting code is reached.  This might be a microsecond or two.  As long as the new ARR value is beyond that, you're safe to load it in the ISR.  In our case, the smallest ARR value we load is equivalent to 2.5ms or 2500us, so we would be completely safe in loading ARR in the first few microseconds after the timer has rolled over to zero.

To fix the bug by using the built-in preload register, in MUX_Timer.adb procedure Init replace the line

TIM6.CR1 := STM32F4.Timer.URS;

with

TIM6.CR1  := STM32F4.Timer.URS or STM32F4.Timer.ARPE;  -- loads ARR synchronously 

Now, on to that unintended but classic bug that Ada did catch.

Busted By My Own Code!

Well, I continued to test and tried to run the display update rate all the way down to 1 and then 0 to generate an exception, but things didn't go exactly as planned.  I ran the update rate down, starting from 100/sec, and after a while I got an exception, but it was not in going from 1 to 0 update rate as expected, and it was not in the file I expected.  The exception actually occurred going from 4 to 3 update rate, and was in the procedure Set_Interrupt_Time, on this line:

 TIM6.ARR := HWord(((1_000_000/PRE_US)/(4 * Integer(Per_Sec))) - 1);

Once I looked at the offending line I immediately knew the problem.  For a 1us prescaler output clock and update rates <= 3, the calculation produces a value larger than the largest value that can fit into a 16-bit unsigned register (for 3 the calculation is 83,332).  The exception was generated in the conversion of the calculated value, 83,332, to a 16-bit HWord.  This is similar to a C cast, but of course with the addition of all appropriate range checks.  C would just have produced an erroneous value and ruined your weekend.

The solution is simple, especially given the versatility of this timer hardware.  Calculating backwards, an update rate of 1/sec translates into an interrupt rate of once every 250ms (250,000us).  With our 1us prescaler output we can't stick that number in our 16-bit ARR register.  A quick inspection suggests changing the prescaler output to 5us, which would yield a max ARR value of 50,000 (actually, 49,999), a number within our 16-bit range.  I'm a big fan of fully configurable prescalers and the nice round numbers they produce!  So making that simple change (from PRE_US := 1 to PRE_US := 5) fixes the problem and now the code does actually raise the errors I wanted to demonstrate, when trying to go below 1 or above 100 updates/sec.  Try switching PRE_US back to 1 and you'll see the bug discussed, as you try to go from 4 to 3.

Here's a video showing the behavior of the code, and both types of Constraint Error that were caught.

So What?

I am pretty certain some out there are thinking "So what?  Those would have been simple errors to find in C also." That might be true, at least for an experienced programmer (it's a very small program, after all), but it is also very much beside the point, IMO.  Some bugs take minutes to find and fix, others take days or weeks.  Can you guarantee that you will only ever introduce the former bugs?  Every bug prevented, or caught sooner rather than later, is an advantage in a competitive world.  A developer or a company that consistently spends less time and money fixing bugs will be more productive and will do better in the marketplace, that's just basic bean-counting math.

If your CEO came by and asked if you are using the most productive tools available, what would your answer be?  If you are your own CEO, have you asked yourself that question?



[ - ]
Comment by AstroJerrySeptember 21, 2014
Great article Mike. My article on Ada and the ARM Cortex went live today on "Electronic Design" at:
http://electronicdesign.com/dev-tools/armed-and-ready

I completely agree with you on the advantages of finding errors with Ada. Most are caught during compile which makes extensive debugging less needed.
[ - ]
Comment by Brian DrummondSeptember 27, 2014
It can be spooky how accurately the exception points to the actual error! When it happens to you, that alone makes a compelling case for switching to Ada...

If you're interested, I have another 7-segment display driver (actually a 1970s style digital watch) in Ada, running on a much smaller processor - the MSP430 - the complete watch is just under a kilobyte...

It's in the "examples" at http://sourceforge.net/projects/msp430ada/ which needs updating for newer gcc versions now the MSP430 is an official target (and to show the real watch PCBs ... at 33mm diameter, it's a pretty small Ada target ). This is stalled because the "unofficial" MSP430 backend for gcc4.7 still produces tighter code than official gcc4.9...
[ - ]
Comment by BillyBitsSeptember 27, 2014
Great Stuff. But I think I found an error in your listings.

<> goto spin; -- yes, a goto!

I think it should be...

<> goto spin; --yes, a corrected goto.

The purists must be rolling their eyes over the use of a goto and the perfectionists are rolling their eyes over the error.

Keep up the good code.
[ - ]
Comment by BillyBitsSeptember 27, 2014
Now I see what's going on the web page is eating the Ada label syntax! My apologies.
[ - ]
Comment by JarnoDecember 18, 2015
Hello to all,

I would like to create a Open Source project for a reliable Flight Controller for Multicopters in Ada and Cortex-M4. It will mainly base on a CAN Bus, a serial (for the IMU) and PWM out, nothing else. For this project I'm looking for contributors and Ada-ARM experts. I also feel it would be a good think to create a "group" or "forum" dedicated on Ada-ARM. Anyone interested in it? I have development Hardware to give away :)
On interest please drop me an email: jarno@a2tech.it

To post reply to a comment, click on the 'reply' button attached to each comment. To post a new comment (not a reply to a comment) check out the 'Write a Comment' tab at the top of the comments.

Please login (on the right) if you already have an account on this platform.

Otherwise, please use this form to register (free) an join one of the largest online community for Electrical/Embedded/DSP/FPGA/ML engineers: