Split ili9341 into several files

* ili9341-device.ads - generic driver for display
* ili9341-spi_connector.ads - the chip with SPI interface
* ili9341-device-bitmap.ads - implement Bitmap API on the ILI9341 RAM
* ili9341-rgb_spi_device.ads - display with RGB interface
This commit is contained in:
Maxim Reznik 2023-11-10 13:06:54 +02:00
parent fd4e628835
commit 639e9031fb
11 changed files with 669 additions and 566 deletions

View File

@ -38,6 +38,8 @@ with STM32.SPI; use STM32.SPI;
with HAL.SPI;
with Ravenscar_Time;
package body Framebuffer_ILI9341 is
LCD_SPI : SPI_Port renames SPI_5;
@ -114,8 +116,9 @@ package body Framebuffer_ILI9341 is
Configure_Alternate_Function (LCD_RGB_AF9, GPIO_AF_LTDC_9);
-- Set LCD_CSX: Chip Unselect
-- Set LCD_CSX: Chip Unselect, LCD_RESET - inactive
Set (LCD_CSX);
Set (LCD_RESET);
end LCD_Pins_Init;
@ -131,7 +134,7 @@ package body Framebuffer_ILI9341 is
begin
LCD_Pins_Init;
LCD_SPI_Init;
Display.Device.Initialize (ILI9341.RGB_Mode);
Display.Device.Initialize (Ravenscar_Time.Delays);
Display.Initialize
(Width => LCD_WIDTH,
Height => LCD_HEIGHT,

View File

@ -31,10 +31,11 @@
with HAL; use HAL;
with HAL.Framebuffer; use HAL.Framebuffer;
with Ravenscar_Time;
with Framebuffer_LTDC;
private with ILI9341;
private with ILI9341.Device;
private with ILI9341.SPI_Connector;
private with STM32.GPIO;
private with STM32.Device;
@ -55,13 +56,17 @@ private
LCD_WRX_DCX : STM32.GPIO.GPIO_Point renames STM32.Device.PD13;
LCD_RESET : STM32.GPIO.GPIO_Point renames STM32.Device.PD12;
type Frame_Buffer
is limited new Framebuffer_LTDC.Frame_Buffer with record
Device : ILI9341.ILI9341_Device (STM32.Device.SPI_5'Access,
Chip_Select => LCD_CSX'Access,
WRX => LCD_WRX_DCX'Access,
Reset => LCD_RESET'Access,
Time => Ravenscar_Time.Delays);
package RGB_SPI_Device is new ILI9341.Device
(ILI9341_Connector => ILI9341.SPI_Connector.ILI9341_Connector,
Send_Command => ILI9341.SPI_Connector.Send_Command,
Connection => ILI9341.RGB,
Connector =>
(Port => STM32.Device.SPI_5'Access,
Chip_Select => LCD_CSX'Access,
WRX => LCD_WRX_DCX'Access));
type Frame_Buffer is limited new Framebuffer_LTDC.Frame_Buffer with record
Device : RGB_SPI_Device.ILI9341_Device;
end record;
end Framebuffer_ILI9341;

View File

@ -0,0 +1,149 @@
------------------------------------------------------------------------------
-- --
-- Copyright (C) 2015-2023, AdaCore --
-- --
-- Redistribution and use in source and binary forms, with or without --
-- modification, are permitted provided that the following conditions are --
-- met: --
-- 1. Redistributions of source code must retain the above copyright --
-- notice, this list of conditions and the following disclaimer. --
-- 2. Redistributions in binary form must reproduce the above copyright --
-- notice, this list of conditions and the following disclaimer in --
-- the documentation and/or other materials provided with the --
-- distribution. --
-- 3. Neither the name of the copyright holder nor the names of its --
-- contributors may be used to endorse or promote products derived --
-- from this software without specific prior written permission. --
-- --
-- THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS --
-- "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT --
-- LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR --
-- A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT --
-- HOLDER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, --
-- SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT --
-- LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, --
-- DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY --
-- THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT --
-- (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE --
-- OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. --
-- --
------------------------------------------------------------------------------
pragma Ada_2022;
with ILI9341.Regs; use ILI9341.Regs;
with Bitmap_Color_Conversion;
package body ILI9341.Device.Bitmap is
use HAL;
procedure Set_Cursor_Position
(From : HAL.Bitmap.Point;
To : HAL.Bitmap.Point);
----------------
-- Get_Bitmap --
----------------
function Get_Bitmap
(This : not null access ILI9341_Device) return Bitmap_Buffer is
begin
return (This, Source => 0);
end Get_Bitmap;
-----------
-- Pixel --
-----------
overriding
function Pixel
(This : Bitmap_Buffer;
Point : HAL.Bitmap.Point) return UInt32 is
begin
return Bitmap_Color_Conversion.Bitmap_Color_To_Word
(HAL.Bitmap.RGB_888, This.Pixel (Point));
end Pixel;
overriding
function Pixel
(This : Bitmap_Buffer;
Point : HAL.Bitmap.Point)
return HAL.Bitmap.Bitmap_Color
is
Color : HAL.Bitmap.Bitmap_Color := (HAL.Bitmap.White);
begin
Set_Cursor_Position (Point, Point);
Read_Pixels
(This => Connector,
Cmd => ILI9341_RAMRD,
Address => Color'Address,
Count => 1);
Color.Alpha := 255;
return Color;
end Pixel;
-------------------------
-- Set_Cursor_Position --
-------------------------
procedure Set_Cursor_Position
(From : HAL.Bitmap.Point;
To : HAL.Bitmap.Point)
is
X1_High : constant UInt8 := UInt8 (Shift_Right (UInt16 (From.X), 8));
X1_Low : constant UInt8 := UInt8 (UInt16 (From.X) and 16#FF#);
X2_High : constant UInt8 := UInt8 (Shift_Right (UInt16 (To.X), 8));
X2_Low : constant UInt8 := UInt8 (UInt16 (To.X) and 16#FF#);
Y1_High : constant UInt8 := UInt8 (Shift_Right (UInt16 (From.Y), 8));
Y1_Low : constant UInt8 := UInt8 (UInt16 (From.Y) and 16#FF#);
Y2_High : constant UInt8 := UInt8 (Shift_Right (UInt16 (To.Y), 8));
Y2_Low : constant UInt8 := UInt8 (UInt16 (To.Y) and 16#FF#);
begin
Send_Command
(Connector,
ILI9341_COLUMN_ADDR,
[X1_High, X1_Low, X2_High, X2_Low]);
Send_Command
(Connector,
ILI9341_PAGE_ADDR,
[Y1_High, Y1_Low, Y2_High, Y2_Low]);
end Set_Cursor_Position;
---------------
-- Set_Pixel --
---------------
overriding
procedure Set_Pixel
(This : in out Bitmap_Buffer;
Point : HAL.Bitmap.Point)
is
begin
Set_Cursor_Position (Point, Point);
Send_Command (Connector, ILI9341_GRAM, []);
Write_Pixels
(This => Connector,
Mode => HAL.Bitmap.RGB_888,
Address => This.Source'Address,
Count => 1,
Repeat => 1);
end Set_Pixel;
----------------
-- Set_Source --
----------------
overriding
procedure Set_Source
(This : in out Bitmap_Buffer; Native : UInt32) is
begin
This.Source := Native;
end Set_Source;
end ILI9341.Device.Bitmap;

View File

@ -0,0 +1,128 @@
------------------------------------------------------------------------------
-- --
-- Copyright (C) 2015-2023, AdaCore --
-- --
-- Redistribution and use in source and binary forms, with or without --
-- modification, are permitted provided that the following conditions are --
-- met: --
-- 1. Redistributions of source code must retain the above copyright --
-- notice, this list of conditions and the following disclaimer. --
-- 2. Redistributions in binary form must reproduce the above copyright --
-- notice, this list of conditions and the following disclaimer in --
-- the documentation and/or other materials provided with the --
-- distribution. --
-- 3. Neither the name of the copyright holder nor the names of its --
-- contributors may be used to endorse or promote products derived --
-- from this software without specific prior written permission. --
-- --
-- THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS --
-- "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT --
-- LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR --
-- A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT --
-- HOLDER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, --
-- SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT --
-- LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, --
-- DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY --
-- THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT --
-- (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE --
-- OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. --
-- --
------------------------------------------------------------------------------
-- This file provides the bitmap interface to the ILI9341 RAM.
with HAL;
with HAL.Bitmap;
with Soft_Drawing_Bitmap;
with System;
generic
with procedure Write_Pixels
(This : ILI9341_Connector;
Mode : HAL.Bitmap.Bitmap_Color_Mode;
Address : System.Address;
Count : Positive;
Repeat : Positive) is null;
-- Transfer to the display memory information about Count pixels located at
-- the specified Address, taking into account the representation format
-- Mode. Repeat the transfer the specified number of times.
with procedure Read_Pixels
(This : ILI9341_Connector;
Cmd : HAL.UInt8;
Address : System.Address;
Count : Positive) is null;
-- Read from the display memory information about Count pixels into the
-- location at the specified Address in RGB_888 color mode.
package ILI9341.Device.Bitmap is
subtype Parent is Soft_Drawing_Bitmap.Soft_Drawing_Bitmap_Buffer;
type Bitmap_Buffer
(Device : not null access ILI9341_Device) is new Parent with private;
function Get_Bitmap
(This : not null access ILI9341_Device) return Bitmap_Buffer;
overriding
function Width (This : Bitmap_Buffer) return Natural is (240);
overriding
function Height (This : Bitmap_Buffer) return Natural is (320);
overriding
function Swapped (This : Bitmap_Buffer) return Boolean is (False);
overriding
function Color_Mode
(This : Bitmap_Buffer) return HAL.Bitmap.Bitmap_Color_Mode is
(HAL.Bitmap.RGB_888);
overriding
function Mapped_In_RAM (This : Bitmap_Buffer) return Boolean is (False);
overriding
function Memory_Address (This : Bitmap_Buffer) return System.Address is
(System.Null_Address);
overriding
procedure Set_Source (This : in out Bitmap_Buffer; Native : HAL.UInt32);
overriding
procedure Set_Pixel
(This : in out Bitmap_Buffer;
Point : HAL.Bitmap.Point);
overriding
procedure Set_Pixel_Blend
(This : in out Bitmap_Buffer;
Point : HAL.Bitmap.Point) renames Set_Pixel;
overriding
function Pixel
(This : Bitmap_Buffer;
Point : HAL.Bitmap.Point) return HAL.UInt32;
overriding
function Pixel
(This : Bitmap_Buffer;
Point : HAL.Bitmap.Point)
return HAL.Bitmap.Bitmap_Color;
overriding
function Buffer_Size (This : Bitmap_Buffer) return Natural is
(This.Width * This.Height * 18 / 8);
private
type Bitmap_Buffer
(Device : not null access ILI9341_Device) is new Parent with
record
Source : HAL.UInt32;
end record;
overriding
function Source (This : Bitmap_Buffer) return HAL.UInt32 is (This.Source);
end ILI9341.Device.Bitmap;

View File

@ -0,0 +1,145 @@
------------------------------------------------------------------------------
-- --
-- Copyright (C) 2015-2023, AdaCore --
-- --
-- Redistribution and use in source and binary forms, with or without --
-- modification, are permitted provided that the following conditions are --
-- met: --
-- 1. Redistributions of source code must retain the above copyright --
-- notice, this list of conditions and the following disclaimer. --
-- 2. Redistributions in binary form must reproduce the above copyright --
-- notice, this list of conditions and the following disclaimer in --
-- the documentation and/or other materials provided with the --
-- distribution. --
-- 3. Neither the name of the copyright holder nor the names of its --
-- contributors may be used to endorse or promote products derived --
-- from this software without specific prior written permission. --
-- --
-- THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS --
-- "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT --
-- LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR --
-- A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT --
-- HOLDER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, --
-- SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT --
-- LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, --
-- DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY --
-- THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT --
-- (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE --
-- OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. --
-- --
------------------------------------------------------------------------------
pragma Ada_2022;
with ILI9341.Regs; use ILI9341.Regs;
package body ILI9341.Device is
---------------------
-- Disable_Display --
---------------------
procedure Disable_Display (This : in out ILI9341_Device) is
begin
Send_Command (Connector, ILI9341_DISPLAY_OFF, []);
end Disable_Display;
--------------------
-- Enable_Display --
--------------------
procedure Enable_Display (This : in out ILI9341_Device) is
begin
Send_Command (Connector, ILI9341_DISPLAY_ON, []);
end Enable_Display;
----------------
-- Initialize --
----------------
procedure Initialize
(This : ILI9341_Device;
Time : not null HAL.Time.Any_Delays)
is
Data renames Connector;
begin
Send_Command (Data, ILI9341_RESET, []);
Time.Delay_Milliseconds (5);
Send_Command
(Data, ILI9341_POWERA, [16#39#, 16#2C#, 16#00#, 16#34#, 16#02#]);
Send_Command (Data, ILI9341_POWERB, [16#00#, 16#C1#, 16#30#]);
Send_Command (Data, ILI9341_DTCA, [16#85#, 16#00#, 16#78#]);
Send_Command (Data, ILI9341_DTCB, [16#00#, 16#00#]);
Send_Command (Data, ILI9341_POWER_SEQ, [16#64#, 16#03#, 16#12#, 16#81#]);
Send_Command (Data, ILI9341_PRC, [16#20#]);
Send_Command (Data, ILI9341_POWER1, [16#23#]);
Send_Command (Data, ILI9341_POWER2, [16#10#]);
Send_Command (Data, ILI9341_VCOM1, [16#3E#, 16#28#]);
Send_Command (Data, ILI9341_VCOM2, [16#86#]);
Send_Command (Data, ILI9341_MAC, [16#C8#]);
Send_Command (Data, ILI9341_FRC, [16#00#, 16#18#]);
case Connection is
when RGB =>
Send_Command (Data, ILI9341_RGB_INTERFACE, [16#C2#]);
Send_Command (Data, ILI9341_INTERFACE, [16#01#, 16#00#, 16#06#]);
Send_Command (Data, ILI9341_DFC, [16#0A#, 16#A7#, 16#27#, 16#04#]);
when Serial | Parallel =>
Send_Command (Data, ILI9341_PIXEL_FORMAT, [16#55#]);
Send_Command (Data, ILI9341_DFC, [16#08#, 16#82#, 16#27#]);
end case;
Send_Command (Data, ILI9341_3GAMMA_EN, [16#00#]);
Send_Command
(Data, ILI9341_COLUMN_ADDR, [16#00#, 16#00#, 16#00#, 16#EF#]);
Send_Command (Data, ILI9341_PAGE_ADDR, [16#00#, 16#00#, 16#01#, 16#3F#]);
Send_Command (Data, ILI9341_GAMMA, [16#01#]);
Send_Command
(Data,
ILI9341_PGAMMA,
[16#0F#, 16#31#, 16#2B#, 16#0C#, 16#0E#, 16#08#, 16#4E#, 16#F1#,
16#37#, 16#07#, 16#10#, 16#03#, 16#0E#, 16#09#, 16#00#]);
Send_Command
(Data,
ILI9341_NGAMMA,
[16#00#, 16#0E#, 16#14#, 16#03#, 16#11#, 16#07#, 16#31#, 16#C1#,
16#48#, 16#08#, 16#0F#, 16#0C#, 16#31#, 16#36#, 16#0F#]);
Send_Command (Data, ILI9341_SLEEP_OUT, []);
Time.Delay_Milliseconds (150);
Send_Command (Data, ILI9341_DISPLAY_ON, []);
Send_Command (Data, ILI9341_GRAM, []);
end Initialize;
---------------------
-- Set_Orientation --
---------------------
procedure Set_Orientation
(This : in out ILI9341_Device;
To : Orientations)
is
Map : constant array (Orientations) of HAL.UInt8 :=
[Portrait_1 => 16#58#,
Portrait_2 => 16#88#,
Landscape_1 => 16#28#,
Landscape_2 => 16#E8#];
begin
if This.Orientation = To then
return;
end if;
Send_Command (Connector, ILI9341_MAC, [Map (To)]);
This.Orientation := To;
end Set_Orientation;
end ILI9341.Device;

View File

@ -0,0 +1,98 @@
------------------------------------------------------------------------------
-- --
-- Copyright (C) 2015-2023, AdaCore --
-- --
-- Redistribution and use in source and binary forms, with or without --
-- modification, are permitted provided that the following conditions are --
-- met: --
-- 1. Redistributions of source code must retain the above copyright --
-- notice, this list of conditions and the following disclaimer. --
-- 2. Redistributions in binary form must reproduce the above copyright --
-- notice, this list of conditions and the following disclaimer in --
-- the documentation and/or other materials provided with the --
-- distribution. --
-- 3. Neither the name of the copyright holder nor the names of its --
-- contributors may be used to endorse or promote products derived --
-- from this software without specific prior written permission. --
-- --
-- THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS --
-- "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT --
-- LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR --
-- A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT --
-- HOLDER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, --
-- SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT --
-- LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, --
-- DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY --
-- THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT --
-- (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE --
-- OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. --
-- --
-- This file is based on: --
-- --
-- @file ili9341.h --
-- @author MCD Application Team --
-- @version V1.0.2 --
-- @date 02-December-2014 --
-- @brief This file includes the LCD driver for ILI9341 LCD. --
-- --
-- COPYRIGHT(c) 2014 STMicroelectronics --
------------------------------------------------------------------------------
-- This file provides the generic implementation of the component driver for
-- the ILI9341 LCD on the STM32F429 Discovery boards, among others. Support
-- does not include the TFT hardware.
-- See the "a-Si TFT LCD Single Chip Driver" specification by ILITEK, file
-- name "ILI9341_DS_V1.02" for details.
with HAL;
with HAL.Time;
generic
type ILI9341_Connector is limited private;
-- The abstraction of the transport to ILI9341 chip
with procedure Send_Command
(This : ILI9341_Connector;
Cmd : HAL.UInt8;
Data : HAL.UInt8_Array);
-- Send an ILI9341 command and corresponding arguments if any
Connection : Interface_Kind;
-- The method of connection to ILI9341
Connector : ILI9341_Connector;
-- The transport to ILI9341 chip
package ILI9341.Device is
type ILI9341_Device is tagged limited private;
-- The 240x320 TFT LCD display
procedure Initialize
(This : ILI9341_Device;
Time : not null HAL.Time.Any_Delays);
-- Initializes the device. Afterward, the device is also enabled so there
-- is no immediate need to call Enable_Display.
type Orientations is
(Portrait_1, -- origin at lower right, text going right to left
Portrait_2, -- origin at upper left, text going left to right
Landscape_1, -- origin at lower left, text going up
Landscape_2); -- origin at upper right, text going down
procedure Set_Orientation
(This : in out ILI9341_Device;
To : Orientations);
procedure Enable_Display (This : in out ILI9341_Device);
procedure Disable_Display (This : in out ILI9341_Device);
private
type ILI9341_Device is tagged limited record
Orientation : Orientations := Portrait_1;
end record;
end ILI9341.Device;

View File

@ -1,6 +1,6 @@
------------------------------------------------------------------------------
-- --
-- Copyright (C) 2015-2016, AdaCore --
-- Copyright (C) 2015-2023, AdaCore --
-- --
-- Redistribution and use in source and binary forms, with or without --
-- modification, are permitted provided that the following conditions are --
@ -29,7 +29,8 @@
-- --
------------------------------------------------------------------------------
package ILI9341_Regs is
package ILI9341.Regs is
pragma Pure;
ILI9341_RESET : constant := 16#01#;
ILI9341_SLEEP_OUT : constant := 16#11#;
@ -39,6 +40,7 @@ package ILI9341_Regs is
ILI9341_COLUMN_ADDR : constant := 16#2A#;
ILI9341_PAGE_ADDR : constant := 16#2B#;
ILI9341_GRAM : constant := 16#2C#;
ILI9341_RAMRD : constant := 16#2E#;
ILI9341_MAC : constant := 16#36#;
ILI9341_PIXEL_FORMAT : constant := 16#3A#;
ILI9341_WDB : constant := 16#51#;
@ -62,4 +64,4 @@ package ILI9341_Regs is
ILI9341_INTERFACE : constant := 16#F6#;
ILI9341_PRC : constant := 16#F7#;
end ILI9341_Regs;
end ILI9341.Regs;

View File

@ -0,0 +1,66 @@
------------------------------------------------------------------------------
-- --
-- Copyright (C) 2015-2023, AdaCore --
-- --
-- Redistribution and use in source and binary forms, with or without --
-- modification, are permitted provided that the following conditions are --
-- met: --
-- 1. Redistributions of source code must retain the above copyright --
-- notice, this list of conditions and the following disclaimer. --
-- 2. Redistributions in binary form must reproduce the above copyright --
-- notice, this list of conditions and the following disclaimer in --
-- the documentation and/or other materials provided with the --
-- distribution. --
-- 3. Neither the name of the copyright holder nor the names of its --
-- contributors may be used to endorse or promote products derived --
-- from this software without specific prior written permission. --
-- --
-- THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS --
-- "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT --
-- LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR --
-- A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT --
-- HOLDER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, --
-- SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT --
-- LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, --
-- DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY --
-- THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT --
-- (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE --
-- OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. --
-- --
------------------------------------------------------------------------------
package body ILI9341.SPI_Connector is
------------------
-- Send_Command --
------------------
procedure Send_Command
(This : ILI9341_Connector;
Cmd : HAL.UInt8;
Data : HAL.UInt8_Array)
is
use HAL.SPI;
Status : SPI_Status;
begin
This.WRX.Clear;
This.Chip_Select.Clear;
This.Port.Transmit (SPI_Data_8b'(1 => Cmd), Status);
if Status /= Ok then
raise Program_Error;
end if;
if Data'Length > 0 then
This.WRX.Set;
This.Port.Transmit (SPI_Data_8b (Data), Status);
if Status /= Ok then
raise Program_Error;
end if;
end if;
This.Chip_Select.Set;
end Send_Command;
end ILI9341.SPI_Connector;

View File

@ -0,0 +1,50 @@
------------------------------------------------------------------------------
-- --
-- Copyright (C) 2015-2023, AdaCore --
-- --
-- Redistribution and use in source and binary forms, with or without --
-- modification, are permitted provided that the following conditions are --
-- met: --
-- 1. Redistributions of source code must retain the above copyright --
-- notice, this list of conditions and the following disclaimer. --
-- 2. Redistributions in binary form must reproduce the above copyright --
-- notice, this list of conditions and the following disclaimer in --
-- the documentation and/or other materials provided with the --
-- distribution. --
-- 3. Neither the name of the copyright holder nor the names of its --
-- contributors may be used to endorse or promote products derived --
-- from this software without specific prior written permission. --
-- --
-- THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS --
-- "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT --
-- LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR --
-- A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT --
-- HOLDER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, --
-- SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT --
-- LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, --
-- DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY --
-- THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT --
-- (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE --
-- OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. --
-- --
------------------------------------------------------------------------------
with HAL.SPI;
with HAL.GPIO;
package ILI9341.SPI_Connector is
type ILI9341_Connector is record
Port : HAL.SPI.Any_SPI_Port;
Chip_Select : HAL.GPIO.Any_GPIO_Point;
WRX : HAL.GPIO.Any_GPIO_Point;
end record;
-- ILI9341 connected over SPI
procedure Send_Command
(This : ILI9341_Connector;
Cmd : HAL.UInt8;
Data : HAL.UInt8_Array);
-- Send ILI9341 command over SPI
end ILI9341.SPI_Connector;

View File

@ -1,402 +0,0 @@
------------------------------------------------------------------------------
-- --
-- Copyright (C) 2015, AdaCore --
-- --
-- Redistribution and use in source and binary forms, with or without --
-- modification, are permitted provided that the following conditions are --
-- met: --
-- 1. Redistributions of source code must retain the above copyright --
-- notice, this list of conditions and the following disclaimer. --
-- 2. Redistributions in binary form must reproduce the above copyright --
-- notice, this list of conditions and the following disclaimer in --
-- the documentation and/or other materials provided with the --
-- distribution. --
-- 3. Neither the name of STMicroelectronics nor the names of its --
-- contributors may be used to endorse or promote products derived --
-- from this software without specific prior written permission. --
-- --
-- THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS --
-- "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT --
-- LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR --
-- A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT --
-- HOLDER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, --
-- SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT --
-- LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, --
-- DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY --
-- THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT --
-- (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE --
-- OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. --
-- --
-- --
-- This file is based on: --
-- --
-- @file ili9341.c --
-- @author MCD Application Team --
-- @version V1.0.2 --
-- @date 02-December-2014 --
-- @brief This file provides a set of functions needed to manage the --
-- L3GD20, ST MEMS motion sensor, 3-axis digital output --
-- gyroscope. --
-- --
-- COPYRIGHT(c) 2014 STMicroelectronics --
------------------------------------------------------------------------------
with Ada.Unchecked_Conversion;
with ILI9341_Regs; use ILI9341_Regs;
package body ILI9341 is
function As_UInt16 is new Ada.Unchecked_Conversion
(Source => Colors, Target => UInt16);
-------------------
-- Current_Width --
-------------------
function Current_Width (This : ILI9341_Device) return Natural is
(This.Selected_Width);
--------------------
-- Current_Height --
--------------------
function Current_Height (This : ILI9341_Device) return Natural is
(This.Selected_Height);
-------------------------
-- Current_Orientation --
-------------------------
function Current_Orientation (This : ILI9341_Device) return Orientations is
(This.Selected_Orientation);
----------------
-- Initialize --
----------------
procedure Initialize
(This : in out ILI9341_Device;
Mode : ILI9341_Mode)
is
begin
if This.Initialized then
return;
end if;
This.Chip_Select_High;
This.Init_LCD (Mode);
This.Selected_Width := Device_Width;
This.Selected_Height := Device_Height;
This.Selected_Orientation := Portrait_2;
This.Initialized := True;
end Initialize;
---------------
-- Set_Pixel --
---------------
procedure Set_Pixel
(This : in out ILI9341_Device;
X : Width;
Y : Height;
Color : Colors)
is
Color_High_UInt8 : constant UInt8 :=
UInt8 (Shift_Right (As_UInt16 (Color), 8));
Color_Low_UInt8 : constant UInt8 :=
UInt8 (As_UInt16 (Color) and 16#FF#);
begin
This.Set_Cursor_Position (X, Y, X, Y);
This.Send_Command (ILI9341_GRAM);
This.Send_Data (Color_High_UInt8);
This.Send_Data (Color_Low_UInt8);
end Set_Pixel;
----------
-- Fill --
----------
procedure Fill (This : in out ILI9341_Device; Color : Colors) is
Color_High_UInt8 : constant UInt8 :=
UInt8 (Shift_Right (As_UInt16 (Color), 8));
Color_Low_UInt8 : constant UInt8 :=
UInt8 (As_UInt16 (Color) and 16#FF#);
begin
This.Set_Cursor_Position (X1 => 0,
Y1 => 0,
X2 => This.Selected_Width - 1,
Y2 => This.Selected_Height - 1);
This.Send_Command (ILI9341_GRAM);
for N in 1 .. (Device_Width * Device_Height) loop
This.Send_Data (Color_High_UInt8);
This.Send_Data (Color_Low_UInt8);
end loop;
end Fill;
---------------------
-- Set_Orientation --
---------------------
procedure Set_Orientation (This : in out ILI9341_Device;
To : Orientations)
is
begin
This.Send_Command (ILI9341_MAC);
case To is
when Portrait_1 => This.Send_Data (16#58#);
when Portrait_2 => This.Send_Data (16#88#);
when Landscape_1 => This.Send_Data (16#28#);
when Landscape_2 => This.Send_Data (16#E8#);
end case;
case To is
when Portrait_1 | Portrait_2 =>
This.Selected_Width := Device_Width;
This.Selected_Height := Device_Height;
when Landscape_1 | Landscape_2 =>
This.Selected_Width := Device_Height;
This.Selected_Height := Device_Width;
end case;
This.Selected_Orientation := To;
end Set_Orientation;
--------------------
-- Enable_Display --
--------------------
procedure Enable_Display (This : in out ILI9341_Device) is
begin
This.Send_Command (ILI9341_DISPLAY_ON);
end Enable_Display;
---------------------
-- Disable_Display --
---------------------
procedure Disable_Display (This : in out ILI9341_Device) is
begin
This.Send_Command (ILI9341_DISPLAY_OFF);
end Disable_Display;
-------------------------
-- Set_Cursor_Position --
-------------------------
procedure Set_Cursor_Position
(This : in out ILI9341_Device;
X1 : Width;
Y1 : Height;
X2 : Width;
Y2 : Height)
is
X1_High : constant UInt8 := UInt8 (Shift_Right (UInt16 (X1), 8));
X1_Low : constant UInt8 := UInt8 (UInt16 (X1) and 16#FF#);
X2_High : constant UInt8 := UInt8 (Shift_Right (UInt16 (X2), 8));
X2_Low : constant UInt8 := UInt8 (UInt16 (X2) and 16#FF#);
Y1_High : constant UInt8 := UInt8 (Shift_Right (UInt16 (Y1), 8));
Y1_Low : constant UInt8 := UInt8 (UInt16 (Y1) and 16#FF#);
Y2_High : constant UInt8 := UInt8 (Shift_Right (UInt16 (Y2), 8));
Y2_Low : constant UInt8 := UInt8 (UInt16 (Y2) and 16#FF#);
begin
This.Send_Command (ILI9341_COLUMN_ADDR);
This.Send_Data (X1_High);
This.Send_Data (X1_Low);
This.Send_Data (X2_High);
This.Send_Data (X2_Low);
This.Send_Command (ILI9341_PAGE_ADDR);
This.Send_Data (Y1_High);
This.Send_Data (Y1_Low);
This.Send_Data (Y2_High);
This.Send_Data (Y2_Low);
end Set_Cursor_Position;
----------------------
-- Chip_Select_High --
----------------------
procedure Chip_Select_High (This : in out ILI9341_Device) is
begin
This.Chip_Select.Set;
end Chip_Select_High;
---------------------
-- Chip_Select_Low --
---------------------
procedure Chip_Select_Low (This : in out ILI9341_Device) is
begin
This.Chip_Select.Clear;
end Chip_Select_Low;
---------------
-- Send_Data --
---------------
procedure Send_Data (This : in out ILI9341_Device; Data : UInt8) is
Status : SPI_Status;
begin
This.WRX.Set;
This.Chip_Select_Low;
This.Port.Transmit (SPI_Data_8b'(1 => Data), Status);
if Status /= Ok then
raise Program_Error;
end if;
This.Chip_Select_High;
end Send_Data;
------------------
-- Send_Command --
------------------
procedure Send_Command (This : in out ILI9341_Device; Cmd : UInt8) is
Status : SPI_Status;
begin
This.WRX.Clear;
This.Chip_Select_Low;
This.Port.Transmit (SPI_Data_8b'(1 => Cmd), Status);
if Status /= Ok then
raise Program_Error;
end if;
This.Chip_Select_High;
end Send_Command;
--------------
-- Init_LCD --
--------------
procedure Init_LCD (This : in out ILI9341_Device;
Mode : ILI9341_Mode) is
begin
This.Reset.Set;
This.Send_Command (ILI9341_RESET);
This.Time.Delay_Milliseconds (5);
This.Send_Command (ILI9341_POWERA);
This.Send_Data (16#39#);
This.Send_Data (16#2C#);
This.Send_Data (16#00#);
This.Send_Data (16#34#);
This.Send_Data (16#02#);
This.Send_Command (ILI9341_POWERB);
This.Send_Data (16#00#);
This.Send_Data (16#C1#);
This.Send_Data (16#30#);
This.Send_Command (ILI9341_DTCA);
This.Send_Data (16#85#);
This.Send_Data (16#00#);
This.Send_Data (16#78#);
This.Send_Command (ILI9341_DTCB);
This.Send_Data (16#00#);
This.Send_Data (16#00#);
This.Send_Command (ILI9341_POWER_SEQ);
This.Send_Data (16#64#);
This.Send_Data (16#03#);
This.Send_Data (16#12#);
This.Send_Data (16#81#);
This.Send_Command (ILI9341_PRC);
This.Send_Data (16#20#);
This.Send_Command (ILI9341_POWER1);
This.Send_Data (16#23#);
This.Send_Command (ILI9341_POWER2);
This.Send_Data (16#10#);
This.Send_Command (ILI9341_VCOM1);
This.Send_Data (16#3E#);
This.Send_Data (16#28#);
This.Send_Command (ILI9341_VCOM2);
This.Send_Data (16#86#);
This.Send_Command (ILI9341_MAC);
This.Send_Data (16#C8#);
This.Send_Command (ILI9341_FRC);
This.Send_Data (16#00#);
This.Send_Data (16#18#);
case Mode is
when RGB_Mode =>
This.Send_Command (ILI9341_RGB_INTERFACE);
This.Send_Data (16#C2#);
This.Send_Command (ILI9341_INTERFACE);
This.Send_Data (16#01#);
This.Send_Data (16#00#);
This.Send_Data (16#06#);
This.Send_Command (ILI9341_DFC);
This.Send_Data (16#0A#);
This.Send_Data (16#A7#);
This.Send_Data (16#27#);
This.Send_Data (16#04#);
when SPI_Mode =>
This.Send_Command (ILI9341_PIXEL_FORMAT);
This.Send_Data (16#55#);
This.Send_Command (ILI9341_DFC);
This.Send_Data (16#08#);
This.Send_Data (16#82#);
This.Send_Data (16#27#);
end case;
This.Send_Command (ILI9341_3GAMMA_EN);
This.Send_Data (16#00#);
This.Send_Command (ILI9341_COLUMN_ADDR);
This.Send_Data (16#00#);
This.Send_Data (16#00#);
This.Send_Data (16#00#);
This.Send_Data (16#EF#);
This.Send_Command (ILI9341_PAGE_ADDR);
This.Send_Data (16#00#);
This.Send_Data (16#00#);
This.Send_Data (16#01#);
This.Send_Data (16#3F#);
This.Send_Command (ILI9341_GAMMA);
This.Send_Data (16#01#);
This.Send_Command (ILI9341_PGAMMA);
This.Send_Data (16#0F#);
This.Send_Data (16#31#);
This.Send_Data (16#2B#);
This.Send_Data (16#0C#);
This.Send_Data (16#0E#);
This.Send_Data (16#08#);
This.Send_Data (16#4E#);
This.Send_Data (16#F1#);
This.Send_Data (16#37#);
This.Send_Data (16#07#);
This.Send_Data (16#10#);
This.Send_Data (16#03#);
This.Send_Data (16#0E#);
This.Send_Data (16#09#);
This.Send_Data (16#00#);
This.Send_Command (ILI9341_NGAMMA);
This.Send_Data (16#00#);
This.Send_Data (16#0E#);
This.Send_Data (16#14#);
This.Send_Data (16#03#);
This.Send_Data (16#11#);
This.Send_Data (16#07#);
This.Send_Data (16#31#);
This.Send_Data (16#C1#);
This.Send_Data (16#48#);
This.Send_Data (16#08#);
This.Send_Data (16#0F#);
This.Send_Data (16#0C#);
This.Send_Data (16#31#);
This.Send_Data (16#36#);
This.Send_Data (16#0F#);
This.Send_Command (ILI9341_SLEEP_OUT);
case Mode is
when RGB_Mode =>
This.Time.Delay_Milliseconds (150);
when SPI_Mode =>
This.Time.Delay_Milliseconds (20);
end case;
-- document ILI9341_DS_V1.02, section 11.2, pg 205 says we need
-- either 120ms or 5ms, depending on the mode, but seems incorrect.
This.Send_Command (ILI9341_DISPLAY_ON);
This.Send_Command (ILI9341_GRAM);
end Init_LCD;
end ILI9341;

View File

@ -1,6 +1,6 @@
------------------------------------------------------------------------------
-- --
-- Copyright (C) 2015, AdaCore --
-- Copyright (C) 2015-2023, AdaCore --
-- --
-- Redistribution and use in source and binary forms, with or without --
-- modification, are permitted provided that the following conditions are --
@ -11,7 +11,7 @@
-- notice, this list of conditions and the following disclaimer in --
-- the documentation and/or other materials provided with the --
-- distribution. --
-- 3. Neither the name of STMicroelectronics nor the names of its --
-- 3. Neither the name of the copyright holder nor the names of its --
-- contributors may be used to endorse or promote products derived --
-- from this software without specific prior written permission. --
-- --
@ -27,158 +27,17 @@
-- (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE --
-- OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. --
-- --
-- This file is based on: --
-- --
-- @file ili9341.h --
-- @author MCD Application Team --
-- @version V1.0.2 --
-- @date 02-December-2014 --
-- @brief This file includes the LCD driver for ILI9341 LCD. --
-- --
-- COPYRIGHT(c) 2014 STMicroelectronics --
------------------------------------------------------------------------------
-- This file provides the component driver for the ILI9341 LCD on the
-- STM32F429 Discovery boards, among others. Support does not include the
-- TFT hardware.
-- See the "a-Si TFT LCD Single Chip Driver" specification by ILITEK, file
-- name "ILI9341_DS_V1.02" for details.
with HAL; use HAL;
with HAL.SPI; use HAL.SPI;
with HAL.GPIO; use HAL.GPIO;
with HAL.Time;
-- Root package for the ILI9341 - 320x240 RGB TFT LCD driver.
package ILI9341 is
pragma Pure;
type ILI9341_Device
(Port : not null access SPI_Port'Class;
Chip_Select : not null Any_GPIO_Point;
WRX : not null Any_GPIO_Point;
Reset : not null Any_GPIO_Point;
Time : not null HAL.Time.Any_Delays)
is tagged limited private;
type ILI9341_Mode is
(RGB_Mode,
SPI_Mode);
procedure Initialize
(This : in out ILI9341_Device;
Mode : ILI9341_Mode);
-- Initializes the device. Afterward, the device is also enabled so there
-- is no immediate need to call Enable_Display.
procedure Send_Command (This : in out ILI9341_Device; Cmd : UInt8);
procedure Send_Data (This : in out ILI9341_Device; Data : UInt8);
Device_Width : constant := 240;
Device_Height : constant := 320;
-- The operational upper bounds for width and height depend on the selected
-- orientation so these subtypes cannot specify an upper bound using the
-- device max height/width. In particular, if the orientation is rotated,
-- the width becomes the height, and vice versa. Hence these are mainly for
-- readability.
subtype Width is Natural;
subtype Height is Natural;
type Colors is
(Black,
Blue,
Light_Blue,
Green,
Cyan,
Gray,
Magenta,
Light_Green,
Brown,
Red,
Orange,
Yellow,
White);
for Colors use
(Black => 16#0000#,
Blue => 16#001F#,
Light_Blue => 16#051D#,
Green => 16#07E0#,
Cyan => 16#07FF#,
Gray => 16#7BEF#,
Magenta => 16#A254#,
Light_Green => 16#B723#,
Brown => 16#BBCA#,
Red => 16#F800#,
Orange => 16#FBE4#,
Yellow => 16#FFE0#,
White => 16#FFFF#);
procedure Set_Pixel
(This : in out ILI9341_Device;
X : Width;
Y : Height;
Color : Colors) with Inline;
procedure Fill (This : in out ILI9341_Device; Color : Colors);
-- Descriptions assume the USB power/debug connector at the top
type Orientations is
(Portrait_1, -- origin at lower right, text going right to left
Portrait_2, -- origin at upper left, text going left to right
Landscape_1, -- origin at lower left, text going up
Landscape_2); -- origin at upper right, text going down
procedure Set_Orientation
(This : in out ILI9341_Device;
To : Orientations);
procedure Enable_Display (This : in out ILI9341_Device);
procedure Disable_Display (This : in out ILI9341_Device);
-- These values reflect the currently selected orientation
function Current_Width (This : ILI9341_Device) return Natural
with Inline;
function Current_Height (This : ILI9341_Device) return Natural
with Inline;
function Current_Orientation (This : ILI9341_Device) return Orientations;
private
type ILI9341_Device
(Port : not null access SPI_Port'Class;
Chip_Select : not null Any_GPIO_Point;
WRX : not null Any_GPIO_Point;
Reset : not null Any_GPIO_Point;
Time : not null HAL.Time.Any_Delays)
is tagged limited record
Selected_Orientation : Orientations;
-- The following objects' upper bounds vary with the selected
-- orientation.
Selected_Width : Natural;
Selected_Height : Natural;
Initialized : Boolean := False;
end record;
procedure Set_Cursor_Position
(This : in out ILI9341_Device;
X1 : Width;
Y1 : Height;
X2 : Width;
Y2 : Height)
with Inline;
procedure Chip_Select_High (This : in out ILI9341_Device) with Inline;
procedure Chip_Select_Low (This : in out ILI9341_Device) with Inline;
procedure Init_LCD (This : in out ILI9341_Device;
Mode : ILI9341_Mode);
type Interface_Kind is
(Parallel,
Serial,
RGB);
-- Defines how the chip is connected to the MCU.
end ILI9341;