+ some common drivers

This commit is contained in:
Vovanium 2024-03-28 19:44:21 +03:00
parent bba8664dac
commit 334868ac49
10 changed files with 467 additions and 4 deletions

View File

@ -1,4 +1,4 @@
project Embedded_STM32F429Disco_Library extends "stm32f4_library" is
project Embedded_STM32F429Disco_Library extends "stm32f4_driver_library" is
Runtime := "embedded-stm32f429disco";
@ -6,7 +6,7 @@ project Embedded_STM32F429Disco_Library extends "stm32f4_library" is
for Runtime("ada") use Runtime;
for Object_Dir use STM32_Common'Object_Dir & "/" & Runtime;
for Library_Dir use STM32_Common'Library_Dir & "/" & Runtime;
for Source_Dirs use STM32F4_Library'Source_Dirs;
for Source_Dirs use STM32F4_Driver_Library'Source_Dirs;
for Library_Name use "stm32";
end Embedded_STM32F429Disco_Library;

View File

@ -1,4 +1,4 @@
project Embedded_STM32F4_Library extends "stm32f4_library" is
project Embedded_STM32F4_Library extends "stm32f4_driver_library" is
Runtime := "embedded-stm32f4";
@ -6,7 +6,7 @@ project Embedded_STM32F4_Library extends "stm32f4_library" is
for Runtime("ada") use Runtime;
for Object_Dir use STM32_Common'Object_Dir & "/" & Runtime;
for Library_Dir use STM32_Common'Library_Dir & "/" & Runtime;
for Source_Dirs use STM32F4_Library'Source_Dirs;
for Source_Dirs use STM32F4_Driver_Library'Source_Dirs;
for Library_Name use "stm32";
end Embedded_STM32F4_Library;

View File

@ -0,0 +1,3 @@
abstract project STM32F4_Driver_Library extends "stm32f4_library.gpr" is
for Source_Dirs use STM32F4_Library'Source_Dirs & ("../source/f4/drivers", "../source/drivers");
end STM32F4_Driver_Library;

View File

@ -0,0 +1,21 @@
package body STM32.Circular_Buffers is
procedure Enqueue (B : in out Circular_Buffer; E : in Element_Type) is
begin
B.Data (B.Head) := E;
B.Head := (B.Head + 1) mod (B.Capacity + 1);
end Enqueue;
procedure Dequeue (B : in out Circular_Buffer; E : out Element_Type) is
begin
E := B.Data (B.Tail);
B.Tail := (B.Tail + 1) mod (B.Capacity + 1);
end Dequeue;
procedure Clear (B : in out Circular_Buffer) is
begin
B.Head := 0;
B.Tail := 0;
end Clear;
end STM32.Circular_Buffers;

View File

@ -0,0 +1,33 @@
generic
type Element_Type is private;
package STM32.Circular_Buffers is
type Circular_Buffer (Capacity : Positive) is private;
function Is_Empty (B : Circular_Buffer) return Boolean;
function Is_Full (B : Circular_Buffer) return Boolean;
procedure Enqueue (B : in out Circular_Buffer; E : in Element_Type)
with Pre => not Is_Full (B), Post => not Is_Empty (B);
procedure Dequeue (B : in out Circular_Buffer; E : out Element_Type)
with Pre => not Is_Empty (B), Post => not Is_Full (B);
procedure Clear (B : in out Circular_Buffer);
private
type Element_Array is array (Natural range <>) of Element_Type;
type Circular_Buffer (Capacity : Positive) is record
Head : Natural := 0;
Tail : Natural := 0;
Data : Element_Array (0 .. Capacity);
end record;
function Is_Empty (B : Circular_Buffer) return Boolean
is (B.Head = B.Tail);
function Is_Full (B : Circular_Buffer) return Boolean
is ((B.Head + 1) mod (B.Capacity + 1) = B.Tail);
end STM32.Circular_Buffers;

View File

@ -0,0 +1,30 @@
with Ada.Streams;
use Ada.Streams;
package STM32.Stream_Drivers is
type Stream_Driver is synchronized interface;
procedure Read (
Driver : in out Stream_Driver;
Item : out Stream_Element_Array;
Last : out Stream_Element_Offset) is abstract;
-- Reads some data from input stream
-- Will block until any data available or some other specified event occur
procedure Read_Immediate (
Driver : in out Stream_Driver;
Data : out Stream_Element_Array;
Last : out Stream_Element_Offset) is abstract;
-- Reads some data from input stream
-- Will not block
procedure Write (
Driver : in out Stream_Driver;
Data : in Stream_Element_Array;
Last : out Stream_Element_Offset) is abstract;
-- Writes data to output stream
-- Will block until it can write some data (bay be not all)
private
end STM32.Stream_Drivers;

View File

@ -0,0 +1,115 @@
package body STM32.SPIs.PIO_Drivers is
-- Buffer description
-- Get .-DR<-. Put
-- ^ v | v
-- +------------+ +-------------------+
-- | | | |
-- +------------+ +-------------------+
-- ^ ^ ^ ^
-- Rx_Tail Rx_Head Tx_Tail Tx_Head
protected body Driver is
procedure Interrupt_Handler is
begin
if Registers.SR.TXE then
if Tx_Head /= Tx_Tail then
Registers.DR := Unsigned_16 (Buffer (Tx_Tail));
Tx_Tail := (Tx_Tail + 1) mod (Buffer_Size + 1);
else
declare
R : Control_Register_2 := Registers.CR2;
begin
R.TXEIE := False;
Registers.CR2 := R;
end;
end if;
end if;
if Registers.SR.RXNE then
Buffer (Rx_Head) := Data_Type (Registers.DR);
Rx_Head := (Rx_Head + 1) mod (Buffer_Size + 1);
end if;
-- will not overflow as amount of received data will not exceed transmitted.
end Interrupt_Handler;
function Next (A : Natural) return Natural is ((A + 1) mod (Buffer_Size + 1));
entry Get (Data : out Data_Type; Got : out Boolean) when Rx_Tail /= Rx_Head or Rx_Tail = Tx_Head
-- second condition is to return when no transmission active
is
begin
Got := Rx_Tail /= Tx_Head;
if Got then
Data := Buffer (Rx_Tail);
Rx_Tail := (Rx_Tail + 1) mod (Buffer_Size + 1);
Full := False;
end if;
end Get;
function Is_Full return Boolean is (Next (Tx_Head) = Rx_Tail);
entry Put (Data : in Data_Type) when not Full
is
begin
Buffer (Tx_Head) := Data;
Tx_Head := (Tx_Head + 1) mod (Buffer_Size + 1);
declare
R : Control_Register_2 := Registers.CR2;
begin
R.TXEIE := True;
R.RXNEIE := True;
Registers.CR2 := R;
end;
Full := Is_Full;
end Put;
procedure Read_Immediate (
Data : out Stream_Element_Array;
Last : out Stream_Element_Offset)
is
begin
Last := Data'First - 1;
while Last < Data'Last and then Rx_Tail /= Tx_Head loop
Last := Last + 1;
Data (Last) := Stream_Element (Buffer (Rx_Tail));
Rx_Tail := Next (Rx_Tail);
end loop;
if Last /= Data'First - 1 then
Full := False;
end if;
end Read_Immediate;
entry Read (
Data : out Stream_Element_Array;
Last : out Stream_Element_Offset)
when Rx_Tail /= Rx_Head or Rx_Tail = Tx_Head is
begin
Read_Immediate (Data, Last);
end Read;
entry Write (
Data : in Stream_Element_Array;
Last : out Stream_Element_Offset)
when not Full is
begin
Last := Data'First - 1;
while Last < Data'Last and then not Is_Full loop
Last := Last + 1;
Buffer (Tx_Head) := Data_Type (Data (Last));
Tx_Head := Next (Tx_Head);
end loop;
Full := Is_Full;
declare
R : Control_Register_2 := Registers.CR2;
begin
R.TXEIE := True;
R.RXNEIE := True;
Registers.CR2 := R;
end;
end Write;
end Driver;
end STM32.SPIs.PIO_Drivers;

View File

@ -0,0 +1,58 @@
with Ada.Streams;
use Ada.Streams;
with Ada.Interrupts;
use Ada.Interrupts;
with Interfaces;
use Interfaces;
with STM32.Stream_Drivers;
package STM32.SPIs.PIO_Drivers is
subtype Data_Type is Unsigned_8; -- 8 or 16 bits are used depending on mode
type Data_Array is array (Natural range <>) of Data_Type;
protected type Driver (
Interrupt : Ada.Interrupts.Interrupt_Id;
Registers : access STM32.SPIs.SPI_Registers;
Buffer_Size : Positive;
Bus_Frequency : access function return Positive)
is new Stream_Drivers.Stream_Driver with
procedure Interrupt_Handler with Attach_Handler => Interrupt;
-- An ISR
entry Get (
Data : out Data_Type;
Got : out Boolean);
-- Get the data from the receiver
entry Put (
Data : in Data_Type);
-- Put the data to the transmitter
overriding procedure Read_Immediate (
Data : out Stream_Element_Array;
Last : out Stream_Element_Offset);
-- Get the already available data from the receiver
overriding entry Read (
Data : out Stream_Element_Array;
Last : out Stream_Element_Offset);
-- Get the data from the receiver
overriding entry Write (
Data : in Stream_Element_Array;
Last : out Stream_Element_Offset);
-- Put the data to the transmitter
private
Tx_Head,
Tx_Tail,
Rx_Head,
Rx_Tail : Natural := 0;
Full : Boolean := False;
Buffer : Data_Array (0 .. Buffer_Size);
end Driver;
end STM32.SPIs.PIO_Drivers;

View File

@ -0,0 +1,116 @@
with STM32.USARTs;
use STM32.USARTs;
package body STM32.USARTs.PIO_Drivers is
protected body USART_Driver is
procedure Interrupt_Handler is
D : Interfaces.Unsigned_32;
E : Interfaces.Unsigned_16;
begin
if Registers.SR.RXNE then
D := Registers.DR;
if CB.Is_Full (Rx_Buffer) then
Rx_Overflow := True;
else
CB.Enqueue (Rx_Buffer, Unsigned_16 (D));
end if;
Rx_Ready := True;
end if;
if Registers.SR.TXE then
if CB.Is_Empty (Tx_Buffer) then -- no more to send
declare
R : Control_Register_1 := Registers.CR1;
begin
R.TXEIE := False;
Registers.CR1 := R;
end; -- Disable interrupt, to avoid entring ISR again
else
CB.Dequeue (Tx_Buffer, E);
Registers.DR := Unsigned_32 (E);
end if;
Tx_Ready := True;
end if;
end Interrupt_Handler;
procedure Enable (A : Boolean) is
CR1 : Control_Register_1 := Registers.CR1;
begin
if A then
CR1.TE := True;
CR1.RE := True;
CR1.RXNEIE := True;
end if;
Registers.CR1 := CR1;
CR1.UE := A;
Registers.CR1 := CR1;
end Enable;
--
-- Receiver
--
procedure Update_Rx_Ready is
begin
Rx_Ready := (not CB.Is_Empty (Rx_Buffer)) or Rx_Time_Out;
end Update_Rx_Ready;
procedure Receiver_Time_Out is
begin
Rx_Time_Out := True;
Update_Rx_Ready;
end Receiver_Time_Out;
procedure Receiver_Time_Out_Reset is
begin
Rx_Time_Out := False;
Update_Rx_Ready;
end Receiver_Time_Out_Reset;
function Receiver_Timed_Out return Boolean is (Rx_Time_Out);
procedure Read_Immediate (Data : out Stream_Element_Array; Last : out Stream_Element_Offset) is
D : Data_Type;
begin
Last := Data'First - 1;
while Last < Data'Last and then (not CB.Is_Empty (Rx_Buffer)) loop
Last := Last + 1;
CB.Dequeue (Rx_Buffer, D);
Data (Last) := Stream_Element (D);
end loop;
Update_Rx_Ready;
end;
entry Read (Data : out Stream_Element_Array; Last : out Stream_Element_Offset) when Rx_Ready is
begin
Read_Immediate (Data, Last);
end;
--
-- Transmitter
--
entry Write (Data : in Stream_Element_Array; Last : out Stream_Element_Offset) when Tx_Ready is
begin
Last := Data'First - 1;
while Last < Data'Last and then (not CB.Is_Full (Tx_Buffer)) loop
Last := Last + 1;
CB.Enqueue (Tx_Buffer, Data_Type (Data (Last)));
end loop;
Tx_Ready := not CB.Is_Full (Tx_Buffer);
declare
R : Control_Register_1 := Registers.CR1;
begin
R.TXEIE := True;
Registers.CR1 := R;
end; -- Enable interrupt (it will occur immediately if UART is not busy)
end Write;
end USART_Driver;
end STM32.USARTs.PIO_Drivers;

View File

@ -0,0 +1,87 @@
with Ada.Streams;
use Ada.Streams;
with Ada.Interrupts;
use Ada.Interrupts;
with Interfaces;
use Interfaces;
with STM32.Circular_Buffers;
with STM32.Stream_Drivers;
package STM32.USARTs.PIO_Drivers is
subtype Data_Type is Unsigned_16; -- 8 or 9 bits are used depending on mode
-- (also special value for BREAK may be used (in future))
package CB is new Circular_Buffers (Data_Type);
type USART_Mode is (
UART_Full_Duplex_Mode,
UART_Half_Duplex_Mode
);
protected type USART_Driver (
Interrupt : Ada.Interrupts.Interrupt_Id;
Registers : access STM32.USARTs.USART_Registers;
Rx_Buffer_Size,
Tx_Buffer_Size : Positive;
Bus_Frequency : access function return Positive
) is new Stream_Drivers.Stream_Driver with
--
-- Common
--
procedure Enable (A : Boolean);
-- Enable or disable the port
-- Note: there's no method to detect if transmission or receiving
-- is active, thus user should stop operations manually
-- before chainging any parameters
procedure Interrupt_Handler with Attach_Handler => Interrupt;
-- An ISR
--
-- Receiver
--
procedure Receiver_Time_Out;
-- Call it to stop waiting
-- (There's no internal timeout timer but this can be called from external one)
procedure Receiver_Time_Out_Reset;
-- Reset time out status (to allow waiting again)
function Receiver_Timed_Out
return Boolean;
-- Get time out status
overriding procedure Read_Immediate (
Data : out Stream_Element_Array;
Last : out Stream_Element_Offset);
-- Get the already available data from the receiver
overriding entry Read (
Data : out Stream_Element_Array;
Last : out Stream_Element_Offset);
-- Get the data from the receiver
--
-- Transmitter
--
overriding entry Write (
Data : in Stream_Element_Array;
Last : out Stream_Element_Offset);
-- Put the data to the transmitter
private
Rx_Ready : Boolean := False; -- Set when data is arrived or time out or some error occured
Rx_Overflow : Boolean := False;
Rx_Time_Out : Boolean := False;
Tx_Ready : Boolean := True;
Rx_Buffer : CB.Circular_Buffer (Rx_Buffer_Size);
Tx_Buffer : CB.Circular_Buffer (Tx_Buffer_Size);
end USART_Driver;
end STM32.USARTs.PIO_Drivers;