Rudra Lad
Published © GPL3+

NeoPixel WS2812b SPI driver with Ada on STM32F4 Discovery

An Ada driver to control ws2812b (aka NeoPixel) addressable RGB LEDs using SPI on STM32F4 discovery board.

IntermediateFull instructions provided2 hours3,209
NeoPixel WS2812b SPI driver with Ada on STM32F4 Discovery

Things used in this project

Hardware components

STMicroelectronics STM32F407 Discovery
×1
LED Strip, NeoPixel Digital RGB
LED Strip, NeoPixel Digital RGB
×1

Software apps and online services

GNAT Community
AdaCore GNAT Community

Hand tools and fabrication machines

Soldering iron (generic)
Soldering iron (generic)
Solder Wire, Lead Free
Solder Wire, Lead Free

Story

Read more

Code

neopixel_ws2812b_stm32_spi.gpr

ADA
with "../../../boards/stm32f407_discovery/stm32f407_discovery_full.gpr";

project neopixel_ws2812b_stm32_spi extends "../../shared/common/common.gpr" is

  for Runtime ("Ada") use STM32F407_Discovery_Full'Runtime ("Ada");
  for Target use "arm-eabi";
  for Main use ("main_test.adb",
                "fill_and_blink.adb",
                "monochrome_scroll.adb", 
                "fill_and_scroll.adb",
                "rainbow1_fill.adb",
                "rainbow2_swirl.adb",
                "cylon_eye.adb",
                "cylon_eye_inverted.adb",
                "converging_bars.adb",
                "diverging_bars.adb",
				        "fade.adb",
				        "fill_and_mirror.adb"
                );
  for Languages use ("Ada");
  for Source_Dirs use ("src");
  for Object_Dir use "obj";
  for Create_Missing_Dirs use "True";
   
  package Linker is
     for Default_Switches ("Ada") use ("-Wl,--print-memory-usage");
  end Linker;

  package Compiler renames STM32F407_Discovery_Full.Compiler;

end neopixel_ws2812b_stm32_spi;

Addressable_LEDs.ads

ADA
------------------------------------------------------------------------------
--                                                                          --
--                        Copyright (C) 2019, 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.   --
--                                                                          --
------------------------------------------------------------------------------

-- The implementation of this package Addressable_LEDs is inspired from the 
-- neopixel middleware package provided with Ada_Drivers_Library, here :
-- https://github.com/AdaCore/Ada_Drivers_Library/tree/master/middleware/src/neopixel 

with HAL; use HAL;


package Addressable_LEDs is

    type LED_Component is (LED_Red, LED_Green, LED_Blue, LED_White);
    
    subtype LED_Value is UInt8;
    
    -- more sequences can be added to below
    type LED_Mode is
        (GRB,   --  Most NeoPixel products (WS2812)
        RGB,   --  FLORA v1 (not v2) pixels
        RGBW); --  NeoPixel RGB+white products

    -- This refers to a value of single LED pixel
    type LED_Values is array (LED_Component) of LED_Value;

    -- Some commonly used colors
    Red    : constant LED_Values := (LED_Red => 255, others => 0);
    Orange : constant LED_Values := (LED_Red => 255, LED_Green => 165, others => 0);
    Yellow : constant LED_Values := (LED_Red | LED_Green => 255, others => 0);
    Green  : constant LED_Values := (LED_Green => 255, others => 0);
    Cyan   : constant LED_Values := (LED_Green | LED_Blue => 255, others => 0);
    Blue   : constant LED_Values := (LED_Blue  => 255, others => 0);
    Indigo : constant LED_Values := (LED_Red => 75, LED_Blue => 130, others => 0);
    Purple : constant LED_Values := (LED_Red | LED_Blue => 255, others => 0);
    White  : constant LED_Values := (others => 255);
    Black  : constant LED_Values := (others => 0);

    type Component_Indices is array (LED_Component) of Integer;
    Mode_Indices : constant array (LED_Mode) of Component_Indices :=
        (RGB  => (LED_Red => 0, LED_Green => 1, LED_Blue => 2, LED_White => -1),
        GRB  => (LED_Red => 1, LED_Green => 0, LED_Blue => 2, LED_White => -1),
        RGBW => (LED_Red => 0, LED_Green => 1, LED_Blue => 2, LED_White => 3));

    -- Stride contains BPP (number of "Bytes Per Pixel" ) for given LED_MODE
    Stride : constant array (LED_Mode) of Positive :=
        (RGBW => 4, others => 3);

    type LED_Strip (<>) is abstract tagged private;

    -- not decalring even an abstract funtion "Create" to create the object of this class.
    -- because future extension of this record type (LED_Strip) may require different set of 
    -- initialization paramaters, in such case this function can't be override.
    -- Hence, declare and define this function for each of the type extension.
    -- For example, derived type LED_Strip_SPI has parameter to pass access to SPI port being used.
    -- Similarly, if you are create an record extension for APA102 (aka Dotstars),
    -- then you would require to provide value of brightness.
    -- So, a single function can not cater for different future type extensions. 
    ------------------------------------------------------------------------------------------
    --function Create (Mode : LED_Mode; Count : Positive) return LED_Strip is abstract;

    function Get_Mode(Strip : LED_Strip) return LED_Mode;

    function Get_Count(Strip : LED_Strip) return Positive;

   --  Set the color of the designated pixel to the given color
    procedure Set_Color
        (Strip : out LED_Strip;
        Index : Natural;
        Color : LED_Values);

    --  Get the color of the designated pixel
    function Get_Color (Strip : LED_Strip; Index : Natural) return LED_Values;

    -- Transmit the bits to display the colors on LED strip.
    procedure Show(Strip : in out LED_Strip) is abstract;

private

    type LED_Strip (Mode : LED_Mode; Count : Positive; Buf_Last : Positive) is abstract tagged
        record
            Buffer : aliased UInt8_Array (0 .. Buf_Last);
        end record;
    
end Addressable_LEDs;

Addressable_LEDs.adb

ADA
------------------------------------------------------------------------------
--                                                                          --
--                        Copyright (C) 2019, 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 Addressable_LEDs is

    --------------
    -- Get_Mode --
    --------------

    function Get_Mode(Strip : LED_Strip) return LED_Mode is
    begin
        return Strip.Mode;
    end Get_Mode;


    ---------------
    -- Get_Count --
    ---------------

    function Get_Count(Strip : LED_Strip) return Positive is
    begin
        return Strip.Count;
    end Get_Count;


    ---------------
    -- Set_Color --
    ---------------

    procedure Set_Color
        (Strip : out LED_Strip;
        Index : Natural;
        Color : LED_Values)
    is
        pragma Assert (Index < Strip.Count);
        Base    : constant Natural := Index * Stride (Strip.Mode);
        Indices : constant Component_Indices := Mode_Indices (Strip.Mode);
    begin
        for J in LED_Red .. (if Strip.Mode = RGBW then LED_White else LED_Blue) loop
            Strip.Buffer (Base + Indices (J)) := Color (J);
        end loop;
    end Set_Color;

    ---------------
    -- Get_Color --
    ---------------

    function Get_Color (Strip : LED_Strip; Index : Natural) return LED_Values is
        pragma Assert (Index < Strip.Count);
        Color : LED_Values := (others => 0);
        Base    : constant Natural := Index * Stride (Strip.Mode);
        Indices : constant Component_Indices := Mode_Indices (Strip.Mode);
    begin
        for J in LED_Red .. (if Strip.Mode = RGBW then LED_White else LED_Blue) loop
            Color (J) := Strip.Buffer (Base + Indices (J));
        end loop;

        return Color;
    end Get_Color;

end Addressable_LEDs;

Addressable_LEDs-neopixel_spi.ads

ADA
with Addressable_LEDs; use Addressable_LEDs;
with HAL.SPI; use HAL.SPI;

package Addressable_LEDs.neopixel_spi is

    type LED_Strip_ws2812b_SPI(<>) is new LED_Strip with private;

    -- Here we declare "Create" funtion to Construct object of type "LED_Strip_SPI"
    function Create (Mode : LED_Mode; Count : Positive; Reset_Last : Positive; Port : not null Any_SPI_Port) return LED_Strip_ws2812b_SPI;

    -- overriding the abstract procedure defined for LED_Strip
    overriding
    procedure Show(Strip : in out LED_Strip_ws2812b_SPI);

private

    procedure Generate_BitStream(Strip : in out LED_Strip_ws2812b_SPI);

    procedure Flash_BitStream(Strip : in LED_Strip_ws2812b_SPI);

    --Bit_0 : constant UInt8 := 2#10000000#;     -- 128 in Decimal
    --Bit_1 : constant UInt8 := 2#11110000#;      -- 240 in Decimal
    -- Use the above two, if below two do not work as expected.
    Bit_0 : constant UInt8 := 2#11000000#;      -- 192 in Decimal
    Bit_1 : constant UInt8 := 2#11111000#;      -- 248 in Decimal
    Bit_Reset : constant UInt8 := 2#00000000#;

    type LED_Strip_ws2812b_SPI(Mode : LED_Mode; Count : Positive; Buf_Last : Positive; Bit_Last : Positive; Reset_Last : Positive; Port : not null Any_SPI_Port) is new LED_Strip(Mode => Mode, Count => Count, Buf_Last => Buf_Last) with
        record
            BitStream : aliased SPI_Data_8b (0 .. Bit_Last);
            ResetStream : aliased SPI_Data_8b (0 .. Reset_Last);
        end record;

end Addressable_LEDs.neopixel_spi;

Addressable_LEDs-neopixel_spi.adb

ADA
package body Addressable_LEDs.neopixel_spi is


    ------------
    -- Create --
    ------------

    function Create (Mode : LED_Mode; Count : Positive; Reset_Last : Positive; Port : not null Any_SPI_Port) return LED_Strip_ws2812b_SPI is
    begin
        return LED_Strip_ws2812b_SPI'(Mode     => Mode,
                                Count    => Count,
                                Buf_Last => Count * Stride (Mode) - 1,
                                Bit_Last => Count * Stride (Mode) * 8 - 1,
                                Reset_Last => Reset_Last,
                                Port => Port,
                                Buffer   => (others => 0),
                                BitStream => (others => Bit_0),
                                ResetStream => (others => Bit_Reset));
    end Create;

    
    ----------
    -- Show --
    ----------

    overriding
    procedure Show(Strip : in out LED_Strip_ws2812b_SPI) is
    begin
        Strip.Generate_BitStream;
        Strip.Flash_BitStream;
    end Show;


    ------------------------
    -- Generate_BitStream --
    ------------------------

    procedure Generate_BitStream(Strip : in out LED_Strip_ws2812b_SPI) is
        Base : Natural := 0;
        Indices : constant Component_Indices := Mode_Indices (Strip.Mode);
        BitStream_Index : Natural := 0;
        Buffer_Index : Natural := 0;
    begin
        iterate_pixels:
        for Pixel in Natural range 0 .. (Strip.Count - 1) loop
        Base := Pixel * Stride (Strip.Mode);

            iterate_components:
            for Component in LED_Red .. (if Strip.Mode = RGBW then LED_White else LED_Blue) loop
            Buffer_Index := Base + Indices(Component);

                iterate_bits:
                for bit_index in Natural range 0 .. 7 loop
                    BitStream_Index := ( 8 * Stride(Strip.Mode) * Pixel ) + ( 8 * Indices(Component) ) + bit_index;

                    if ( Strip.Buffer(Buffer_Index) and Shift_Left(2#00000001#, (7 - bit_index)) ) > 0 then
                        Strip.BitStream( BitStream_Index ) := Bit_1;
                    else
                        Strip.BitStream( BitStream_Index ) := Bit_0;
                    end if;

                end loop iterate_bits;

            end loop iterate_components;

        end loop iterate_pixels;
    end Generate_BitStream;

    ---------------------
    -- Flash_BitStream --
    ---------------------

    procedure Flash_BitStream(Strip : in LED_Strip_ws2812b_SPI) is
        Status : HAL.SPI.SPI_Status;
    begin
        Strip.Port.Transmit(Strip.ResetStream & Strip.BitStream & Strip.ResetStream , Status);
    end Flash_BitStream;


end Addressable_LEDs.neopixel_spi;

SPI_config.ads

ADA
with HAL; use HAL;
with HAL.SPI; --use HAL.SPI;
with STM32; use STM32;
with STM32.SPI; use STM32.SPI;
with STM32.GPIO;    use STM32.GPIO;
with STM32.Device;  use STM32.Device;


package SPI_config is

    -- No need to use SCK and MISO pins, 
    -- since we will transmitting only with MOSI pin

    Npxl_SPI : SPI_Port renames SPI_2;
    Npxl_SPI_AF : GPIO_Alternate_Function renames GPIO_AF_SPI2_5;
    --Npxl_SPI_SCK_Pin     : GPIO_Point renames PB13;
    --Npxl_SPI_MISO_Pin    : GPIO_Point renames PB14;
    Npxl_SPI_MOSI_Pin    : GPIO_Point renames PB15;


    procedure Initialize_NeoPixel;

end SPI_config;

SPI_config.adb

ADA
package body SPI_config is


    -------------------------
    -- Initialize_NeoPixel --
    -------------------------

    procedure Initialize_NeoPixel is
        procedure Init_SPI;
        procedure Init_GPIO;


        --------------
        -- Init_SPI --
        --------------

        procedure Init_SPI is
            Config : SPI_Configuration;
        begin
            Enable_Clock (Npxl_SPI);

            Config.Mode := Master;
            Config.Baud_Rate_Prescaler := BRP_8;        -- approx. 5.25 MHz
            Config.Clock_Polarity := Low;
            Config.Clock_Phase := P1Edge;
            Config.First_Bit := MSB;
            Config.CRC_Poly := 7;
            Config.Slave_Management := Software_Managed;
            Config.Direction := D1Line_Tx;
            Config.Data_Size := HAL.SPI.Data_Size_8b;

            Disable (Npxl_SPI);
            Configure (Npxl_SPI, Config);
            Enable (Npxl_SPI);
        end Init_SPI;


        ---------------
        -- Init_GPIO --
        ---------------

        procedure Init_GPIO is
            SPI_Point : constant GPIO_Point := Npxl_SPI_MOSI_Pin;
        begin
            Enable_Clock (SPI_Point);

            Configure_IO (SPI_Point,
                (Mode_AF,
                AF             => Npxl_SPI_AF,
                Resistors      => Floating,
                AF_Speed       => Speed_50MHz,
                AF_Output_Type => Push_Pull));

        end Init_GPIO;

    begin
        Init_GPIO;
        Init_SPI;
    end Initialize_NeoPixel;

end SPI_config;

LED_magic.ads

ADA
-- This package defines some very basic and useful functions
-- to manipulate the buffers conveniently.

-- The operations defined here are class wide (for LED_Strip class).
-- So any future type extension of LED_Strip,
-- which does not differ from the way LED_Strip works,
-- will be able to make use of this package.


with HAL; use HAL;
with Addressable_LEDs; use Addressable_LEDs;
with Ada.Text_IO; use Ada.Text_IO;
with Ada.Numerics; use Ada.Numerics;
with Ada.Numerics.Elementary_Functions; use Ada.Numerics.Elementary_Functions;

package LED_magic is

    -- Color Palette can be useful for storing a limited number of colors.
    -- and then transfer these colors to buffer for LED_Strip.
    type Color_Palette is array (Natural range <>) of LED_Values;
    type Angle_Degrees is mod 360;
   
    type Pixel_Mode is (Fill_Pixels, Unfill_Pixels);
    type Direction is (Forward, Backward); 
    type Effect_Mode is (Converge, Diverge);

    -- Fill all the pixels with given "Color"
    procedure Fill(Strip : out LED_Strip'Class; Color : LED_Values);

    -- Fill all the pixels between indices Start .. Stop, with given "Color"
    procedure Fill(Strip : out LED_Strip'Class; Color : LED_Values; Start : Natural; Stop : Natural);

    -- Rotate the buffer,
    -- Positive values rotate forwards and
    -- Negative values rotate backwards.
    procedure Rotate_Buffer(Strip : in out LED_Strip'Class; Steps : in Integer);

    -- Mirror the buffer.
    procedure Mirror_Buffer(Strip : in out LED_Strip'Class);

    -- "Magic_copy" (aka Modulo_Copy)
    -- Copies colors from "Src" Palette to "Dest" LED_Strip object's Buffer,
    -- Starting from "Offset_raw" index of Src mapping to index "0" of LED_Strip. 
    -- Takes care of different sizes of "Src" and "Dest" :
    -- i.  Repeats colors if Src'Length is Less than Dest'Length (in terms of colors).
    -- ii. Limits copy of further colors if Src'Length is greater than Dest'Length.
    procedure Magic_Copy (Src : in Color_Palette; Dest : out LED_Strip'Class; Offset_raw : in Integer := 0);

    -- Generate rainbow palette based on colors returned by "Colorwheel_8bit" function.
    procedure Generate_Rainbow1_Palette(Palette : out Color_Palette);

    -- Generate rainbow palette based on colors returned by "Colorwheel_3phase" function.
    procedure Generate_Rainbow2_Palette(Palette : out Color_Palette);

    -- Generates a monochromatic gradient palette.
    -- Where the first color is same as the passed argument "Color",
    -- last color is first color dimmed by value "Factor",
    -- and rest of the colors in between are simply linear distribution between first and last.
    procedure Generate_Monochromatic_Gradient_Palette (Palette : out Color_Palette; Color : in LED_Values; Factor : in Positive);

private

    procedure Rotate_Once_Forward(Strip : in out LED_Strip'Class);

    procedure Rotate_Once_Backward(Strip : in out LED_Strip'Class);

    -- returns a color based on 8-bit Colorwheel
    -- (max 256 possible colors).
    function ColorWheel_8bit (Pos : UInt8) return LED_Values;

    -- returns a color based on a 3-phase sinewave :
    -- (mutual phase difference of 120 degrees between each two phases)
    -- where R,G and B represent amplitude of sinewaves of respective phases (0, 120 and 240 degrees).
    -- Note that sinewaves are shifted up to avoid negative values.
    -- (max 360 possible colors)
    function ColorWheel_3phase (Pos : Angle_Degrees) return LED_Values;

end LED_magic;

LED_magic.adb

ADA
package body LED_magic is

    ----------
    -- Fill --
    ----------

    procedure Fill(Strip : out LED_Strip'Class; Color : LED_Values) is
    begin
        iterate_pixels:
        for pixel in Natural range 0 .. (Strip.Get_Count - 1) loop
            Strip.Set_color(pixel, Color);
        end loop iterate_pixels;
    end Fill;


    ----------
    -- Fill --
    ----------

    procedure Fill(Strip : out LED_Strip'Class; Color : LED_Values; Start : Natural; Stop : Natural) is
        pragma Assert (Start < Strip.Get_Count);
        pragma Assert (Stop < Strip.Get_Count);
        pragma Assert (Start <= Stop);
    begin
        iterate_pixels:
        for pixel in Natural range Start .. Stop loop
            Strip.Set_color(pixel, Color);
        end loop iterate_pixels;
    end Fill;


    -------------------
    -- Rotate_Buffer --
    -------------------

    procedure Rotate_Buffer(Strip : in out LED_Strip'Class; Steps : in Integer) is
        Steps_Absolute : constant Natural := (abs Steps) mod (Strip.Get_Count) ;
    begin
        if (Steps > 0) then

            loop_forward :
            for I in Natural range 1 .. Steps_Absolute loop
                Rotate_Once_Forward(Strip);
            end loop loop_forward;

        elsif (Steps < 0) then
            
            loop_backward :
            for I in Natural range 1 .. Steps_Absolute loop
                Rotate_Once_Backward(Strip);
            end loop loop_backward;
        
        else
            null;
        end if;
    end Rotate_Buffer;


    -------------------
    -- Mirror_Buffer --
    -------------------

    procedure Mirror_Buffer(Strip : in out LED_Strip'Class) is
        Middle_Index, Mirror_Index : Natural := 0;
        Color_Temp : LED_Values := Black;
        Count_N : constant Natural := Strip.Get_Count; 
    begin
        if ( (Strip.Get_Count mod 2) = 0) then
            Middle_Index := (Count_N / 2) - 1;
        else
            Middle_Index := (Count_N - 1) / 2;
        end if;

        loop_half :
        for I in Natural range 0 .. Middle_Index loop
            Mirror_Index := (Count_N - 1) - I;
            Color_Temp := Black;
            Color_Temp := Strip.Get_Color(I);
            Strip.Set_color(I, Strip.Get_Color(Mirror_Index));
            Strip.Set_color(Mirror_Index, Color_Temp);
        end loop loop_half;

    end Mirror_Buffer;


    -------------------------
    -- Rotate_Once_Forward --
    -------------------------

    procedure Rotate_Once_Forward(Strip : in out LED_Strip'Class) is
        Start : constant Natural := 0;
        Stop : constant Natural := Strip.Get_Count - 1;
        Last_Color : constant LED_Values := Strip.Get_Color(Stop);
    begin
        for I in reverse Natural range (Start + 1) .. Stop loop
            Strip.Set_color(I, Strip.Get_Color(I - 1));
        end loop;
        Strip.Set_color(Start, Last_Color);
    end Rotate_Once_Forward;


    --------------------------
    -- Rotate_Once_Backward --
    --------------------------

    procedure Rotate_Once_Backward(Strip : in out LED_Strip'Class) is
        Start : constant Natural := 0;
        Stop : constant Natural := Strip.Get_Count - 1;
        First_Color : constant LED_Values := Strip.Get_Color(Start);
    begin
        for I in Natural range Start .. (Stop - 1) loop
            Strip.Set_color(I, Strip.Get_Color(I + 1));
        end loop;
        Strip.Set_color(Stop, First_Color);
    end Rotate_Once_Backward;


    ----------------
    -- Magic_Copy --
    ----------------

    procedure Magic_Copy (Src : in Color_Palette; Dest : out LED_Strip'Class; Offset_Raw : in Integer := 0) is
        Src_Length : constant Natural := Src'Length;
        Dest_Length : constant Natural := Dest.Get_Count;
        Offset : constant Natural := Offset_Raw mod Src_Length;
        J : Natural := 0;
    begin
        iterate_pixels :
        for I in Natural range 0 .. (Dest_Length - 1) loop
            J := (I + Offset) mod Src_Length;
            Dest.Set_color(I, Src(J) );
        end loop iterate_pixels;

    end Magic_Copy;


    ---------------------
    -- ColorWheel_8bit --
    ---------------------

    function ColorWheel_8bit (Pos : UInt8) return LED_Values is
        Color_Out : LED_Values := Black;
        Pos_Temp : UInt8 := 0;
    begin
        if Pos < 85 then
            Pos_Temp := Pos;
            Color_Out := ( (Pos_Temp * 3) , (255 - ( Pos_Temp * 3 ) ) , 0, 0);
        elsif Pos < 170 then
            Pos_Temp := Pos - 85;
            Color_Out := ( (255 - ( Pos_Temp * 3 ) ) , 0, (Pos_Temp * 3) , 0);
        else
            Pos_Temp := Pos - 170;
            Color_Out := ( 0, (Pos_Temp * 3) , (255 - ( Pos_Temp * 3 ) ) , 0);
        end if;

        return Color_Out;
    end ColorWheel_8bit;


    -------------------------------
    -- Generate_Rainbow1_Palette --
    -------------------------------

    procedure Generate_Rainbow1_Palette(Palette : out Color_Palette) is
        Pos : UInt8 := 0;
        Pos_Temp : Float := 0.0;
        Palette_Length : constant Natural := Palette'Length;
        Color_Temp : LED_Values := Black;
    begin
        if Palette_Length > Natural(UInt8'Last) then         -- You can also put (UInt8'Last + 1)
            
            iterate_palette:
            for I in Palette'range loop
                Pos := UInt8(I mod 256);
                Color_Temp := ColorWheel_8bit(Pos);
                Palette(I) := Color_Temp;
            end loop iterate_palette;
        
        else
            linear_sampling:
            for I in Palette'range loop
                Pos_Temp := ( Float(I) * 255.0 ) / Float(Palette_Length);
                Pos := UInt8( Natural(Pos_Temp) mod 256 );
                Color_Temp := ColorWheel_8bit(Pos);
                Palette(I) := Color_Temp;
            end loop linear_sampling;
        end if;
    end Generate_Rainbow1_Palette;


    ----------------
    -- Deg_To_Rad --
    ----------------

    function Deg_To_Rad (Pos : Angle_Degrees) return Float is
    begin
        return (Float(Pos) * Float(Pi) ) / (180.0);
    end Deg_To_Rad;


    -----------------------
    -- ColorWheel_3phase --
    -----------------------

    function ColorWheel_3phase (Pos : Angle_Degrees) return LED_Values is
        Color_Out : LED_Values := Black;
        R_Out, G_out, B_Out : LED_Value := 0;
        Phase_Deg : Float := 0.0;
        Phase_Rad_Red, Phase_Rad_Green, Phase_Rad_Blue : Float := 0.0;
        Value_Red, Value_Green, Value_Blue : Float := 0.0; 
    begin

        Phase_Rad_Red := Deg_To_Rad(Pos + 0);
        Phase_Rad_Green := Deg_To_Rad(Pos + 120);
        Phase_Rad_Blue := Deg_To_Rad(Pos + 240);

        Value_Red := (255.0) * ( (Sin(Phase_Rad_Red) + 1.0) / 2.0);
        Value_Green := (255.0) * ( (Sin(Phase_Rad_Green) + 1.0) / 2.0);
        Value_Blue := (255.0) * ( (Sin(Phase_Rad_Blue) + 1.0) / 2.0);

        R_Out := LED_Value(Value_Red);
        G_out := LED_Value(Value_Green);
        B_Out := LED_Value(Value_Blue);

        Color_Out := (R_Out, G_out, B_Out, 0);
        return Color_Out;
    end ColorWheel_3phase;


    -------------------------------
    -- Generate_Rainbow2_Palette --
    -------------------------------

    procedure Generate_Rainbow2_Palette(Palette : out Color_Palette) is
        Pos : Angle_Degrees := 0;
        Pos_Temp : Float := 0.0;
        Palette_Length : constant Natural := Palette'Length;
        Color_Temp : LED_Values := Black;
    begin
        if Palette_Length > Natural(Angle_Degrees'Last) then

            iterate_palette:
            for I in Palette'range loop
                Pos := Angle_Degrees(I mod 360);
                Color_Temp := ColorWheel_3phase(Pos);
                Palette(I) := Color_Temp;
            end loop iterate_palette;

        else
            linear_sampling:
            for I in Palette'range loop
                Pos_Temp := ( Float(I) * 360.0 ) / Float(Palette_Length);
                Pos := Angle_Degrees( Natural(Pos_Temp) mod 360 );
                Color_Temp := ColorWheel_3phase(Pos);
                Palette(I) := Color_Temp;
            end loop linear_sampling;
        end if;
    end Generate_Rainbow2_Palette;


    ---------------------------------------------
    -- Generate_Monochromatic_Gradient_Palette --
    ---------------------------------------------

    procedure Generate_Monochromatic_Gradient_Palette (Palette : out Color_Palette; Color : in LED_Values; Factor : in Positive) is
        Palette_Length : constant Natural := Palette'Length;
        Factor_Dimming : constant Float := Float(Factor);
        R1 : constant Float := Float(Color(LED_Red));
        G1 : constant Float := Float(Color(LED_Green));
        B1 : constant Float := Float(Color(LED_Blue));
        W1 : constant Float := Float(Color(LED_White));
        R2 : constant Float := R1 / Factor_Dimming;
        G2 : constant Float := G1 / Factor_Dimming;
        B2 : constant Float := B1 / Factor_Dimming;
        W2 : constant Float := W1 / Factor_Dimming;
        R_Temp, G_Temp, B_Temp, W_Temp : Float := 0.0;
        R_Out, G_out, B_Out, W_Out : LED_Value := 0;
    begin
        iterate_palette:
        for I in Palette'range loop
            if Palette_Length > 1 then
                R_Temp := ( (R2 - R1) / ( Float(Palette_Length) - 1.0) ) * (Float(I) - 0.0) + R1;
                G_Temp := ( (G2 - G1) / ( Float(Palette_Length) - 1.0) ) * (Float(I) - 0.0) + G1;
                B_Temp := ( (B2 - B1) / ( Float(Palette_Length) - 1.0) ) * (Float(I) - 0.0) + B1;
                W_Temp := ( (W2 - W1) / ( Float(Palette_Length) - 1.0) ) * (Float(I) - 0.0) + W1;

                R_Out := LED_Value(R_Temp);
                G_out := LED_Value(G_Temp);
                B_Out := LED_Value(B_Temp);
                W_Out := LED_Value(W_Temp);

                Palette(I) := (R_Out, G_out, B_Out, W_Out);
            else
                Palette(I) := Color;
            end if;
        end loop iterate_palette;
    end Generate_Monochromatic_Gradient_Palette;


end LED_magic;

main_test.adb

ADA
with Addressable_LEDs; use Addressable_LEDs;
with Addressable_LEDs.neopixel_spi; use Addressable_LEDs.neopixel_spi;
with SPI_config; use SPI_config;
with Ada.Real_Time; use Ada.Real_Time;

procedure main_test is

    Strip_count : constant Positive := 5;
    Strip_mode : constant LED_Mode := GRB;
    Strip_1 : aliased LED_Strip_ws2812b_SPI := Create(Strip_mode, Strip_count, 8, Npxl_SPI'Access);

    procedure All_Off(Strip : out LED_Strip_ws2812b_SPI);

    procedure All_On(Strip : out LED_Strip_ws2812b_SPI);

    procedure All_Off(Strip : out LED_Strip_ws2812b_SPI) is
    begin
        for i in Natural range 0 .. (Strip.Get_Count - 1) loop
            Strip.Set_Color(i, Black);
        end loop;
    end All_Off;

    procedure All_On(Strip : out LED_Strip_ws2812b_SPI) is
    begin
        for i in Natural range 0 .. (Strip.Get_Count - 1) loop
            Strip.Set_Color(i, (100, 100, 100, 0));
        end loop;
    end All_On;

begin

    Initialize_NeoPixel;

    Set_Color(Strip_1, 0, (125, 0, 0, 0) );
    Set_Color(Strip_1, 1, (0, 110, 0, 0) );
    Strip_1.Set_Color(2, (100, 0, 115, 0));
    Strip_1.Set_Color(3, (0, 0, 80, 0));

    Strip_1.Set_Color(4, Strip_1.Get_Color(2));
   
    delay until Clock + Milliseconds(2000);
    Strip_1.Show;
    delay until Clock + Milliseconds(2000);

   loop
        All_Off(Strip_1);
        Strip_1.Show;
        delay until Clock + Milliseconds(500);

        All_On(Strip_1);
        Strip_1.Show;
        delay until Clock + Milliseconds(500);
   end loop;
   
   
end main_test;

fill_and_blink.adb

ADA
with Addressable_LEDs; use Addressable_LEDs;
with Addressable_LEDs.neopixel_spi; use Addressable_LEDs.neopixel_spi;
with HAL; use HAL;
with HAL.SPI; --use HAL.SPI;
with SPI_config; use SPI_config;
with LED_magic; use LED_magic;
with Ada.Real_Time; use Ada.Real_Time;


procedure fill_and_blink is

    Strip_count : constant Positive := 5;
    Strip_mode : constant LED_Mode := GRB;
    Strip_1 : aliased LED_Strip_ws2812b_SPI := Create(Strip_mode, Strip_count, 8, Npxl_SPI'Access);

begin

    Initialize_NeoPixel;

    loop
        Fill(Strip_1, (100, 0, 180, 0) );
        Strip_1.Show;
        delay until Clock + Milliseconds(500);

        Fill(Strip_1, (0, 0, 0, 0) );
        Strip_1.Show;
        delay until Clock + Milliseconds(500);
    end loop;


end fill_and_blink;

monochrome_scroll.adb

ADA
with Addressable_LEDs; use Addressable_LEDs;
with Addressable_LEDs.neopixel_spi; use Addressable_LEDs.neopixel_spi;
with SPI_config; use SPI_config;
with LED_magic; use LED_magic;
with Ada.Real_Time; use Ada.Real_Time;

procedure monochrome_scroll is

    Strip_count : constant Positive := 5;
    Strip_mode : constant LED_Mode := GRB;
    Strip_1 : aliased LED_Strip_ws2812b_SPI := Create(Strip_mode, Strip_count, 8, Npxl_SPI'Access);

    Color_1 : constant LED_values := (156, 0, 103, 0);
    Palette_1 : Color_Palette(0 .. Strip_count - 1);
    loop_index : Integer := 0;

begin

    Initialize_NeoPixel;
    Generate_Monochromatic_Gradient_Palette(Palette_1, Color_1, 5);

    loop
        Magic_Copy(Palette_1, Strip_1, loop_index);
        Strip_1.Show;
        loop_index := (loop_index + 1) mod Strip_count;
        delay until Clock + Milliseconds(100);
    end loop;

end monochrome_scroll;

fill_and_scroll.adb

ADA
with Addressable_LEDs; use Addressable_LEDs;
with Addressable_LEDs.neopixel_spi; use Addressable_LEDs.neopixel_spi;
with SPI_config; use SPI_config;
with LED_magic; use LED_magic;
with Ada.Real_Time; use Ada.Real_Time;

procedure fill_and_scroll is

    Strip_count : constant Positive := 5;
    Strip_mode : constant LED_Mode := GRB;
    Strip_1 : aliased LED_Strip_ws2812b_SPI := Create(Strip_mode, Strip_count, 8, Npxl_SPI'Access);

begin

    Initialize_NeoPixel;
    Set_Color(Strip_1, 0, (0, 125, 0, 0) );
    Set_Color(Strip_1, 1, (100, 100, 0, 0) );
    Set_Color(Strip_1, 2, (125, 0, 0, 0) );
    Set_Color(Strip_1, 3, (100, 0, 100, 0) );
    Set_Color(Strip_1, 4, (0, 0, 125, 0) );

    loop
        Strip_1.Show;
        Rotate_Buffer(Strip_1, 1);
        
        delay until Clock + Milliseconds(250);
    end loop;

end fill_and_scroll;

rainbow1_fill.adb

ADA
with Addressable_LEDs; use Addressable_LEDs;
with Addressable_LEDs.neopixel_spi; use Addressable_LEDs.neopixel_spi;
with SPI_config; use SPI_config;
with LED_magic; use LED_magic;
with Ada.Real_Time; use Ada.Real_Time;

procedure rainbow1_fill is

    Strip_count : constant Positive := 5;
    Strip_mode : constant LED_Mode := GRB;
    Strip_1 : aliased LED_Strip_ws2812b_SPI := Create(Strip_mode, Strip_count, 8, Npxl_SPI'Access);

    Palette_1 : Color_Palette(0 .. 19);
    Loop_Index : Integer := 0;

begin

    Initialize_NeoPixel;
    Generate_Rainbow1_Palette(Palette_1);

    Infinite :
    loop
        Fill(Strip_1, Palette_1(Loop_Index) );
        Strip_1.Show;
        Loop_Index := (Loop_Index + 1) mod (Palette_1'Length);

        delay until Clock + Milliseconds(100);
    end loop Infinite;


end rainbow1_fill;

rainbow2_swirl.adb

ADA
with Addressable_LEDs; use Addressable_LEDs;
with Addressable_LEDs.neopixel_spi; use Addressable_LEDs.neopixel_spi;
with SPI_config; use SPI_config;
with LED_magic; use LED_magic;
with Ada.Real_Time; use Ada.Real_Time;

procedure rainbow2_swirl is

    Strip_count : constant Positive := 5;
    Strip_mode : constant LED_Mode := GRB;
    Strip_1 : aliased LED_Strip_ws2812b_SPI := Create(Strip_mode, Strip_count, 8, Npxl_SPI'Access);

    Palette_1 : Color_Palette(0 .. 24);
    Loop_Index : Integer := 0;

begin

    Initialize_NeoPixel;
    Generate_Rainbow2_Palette(Palette_1);

    Infinite :
    loop
        Magic_Copy(Palette_1, Strip_1, Loop_Index);
        Strip_1.Show;
        Loop_Index := (Loop_Index - 1) mod (Palette_1'Length);

        delay until Clock + Milliseconds(50);
    end loop Infinite;

end rainbow2_swirl;

cylon_eye.adb

ADA
with Addressable_LEDs; use Addressable_LEDs;
with Addressable_LEDs.neopixel_spi; use Addressable_LEDs.neopixel_spi;
with SPI_config; use SPI_config;
with LED_magic; use LED_magic;
with Ada.Real_Time; use Ada.Real_Time;

procedure cylon_eye is

    Strip_count : constant Positive := 5;
    Strip_mode : constant LED_Mode := GRB;
    Strip_1 : aliased LED_Strip_ws2812b_SPI := Create(Strip_mode, Strip_count, 8, Npxl_SPI'Access);

    Color_1 : constant LED_values := (100, 0, 0, 0);
    Pos : Integer := 0;
    Dir : Direction := Forward;

begin

    Initialize_NeoPixel;
    
    Set_Color(Strip_1, 0, Color_1);
    Strip_1.Show;
    delay until Clock + Milliseconds(100);

    Infinite :
    loop
        
        if Dir = Forward then
            
            if Pos >= (Strip_1.Get_Count - 1) then
                Dir := Backward;
                Rotate_Buffer(Strip_1, -1);
                Pos := Pos - 1;
            else
                Dir := Forward;
                Rotate_Buffer(Strip_1, 1);
                Pos := Pos + 1;
            end if;

        else
            
            if Pos <= 0 then
                Dir := Forward;
                Rotate_Buffer(Strip_1, 1);
                Pos := Pos + 1;
            else
                Dir := Backward;
                Rotate_Buffer(Strip_1, -1);
                Pos := Pos - 1;
            end if;

        end if;

        Strip_1.Show;

        delay until Clock + Milliseconds(100);

    end loop Infinite;


end cylon_eye;

cylon_eye_inverted.adb

ADA
with Addressable_LEDs; use Addressable_LEDs;
with Addressable_LEDs.neopixel_spi; use Addressable_LEDs.neopixel_spi;
with SPI_config; use SPI_config;
with LED_magic; use LED_magic;
with Ada.Real_Time; use Ada.Real_Time;

procedure cylon_eye_inverted is

    Strip_count : constant Positive := 5;
    Strip_mode : constant LED_Mode := GRB;
    Strip_1 : aliased LED_Strip_ws2812b_SPI := Create(Strip_mode, Strip_count, 8, Npxl_SPI'Access);

    Color_1 : constant LED_values := (20, 0, 50, 0);
    Pos : Integer := 0;
    Dir : Direction := Forward;

begin

    Initialize_NeoPixel;
    
    Fill(Strip_1, Color_1);
    Set_Color(Strip_1, 0, (0, 0, 0, 0) );
    Strip_1.Show;
    delay until Clock + Milliseconds(150);

    Infinite :
    loop
        
        if Dir = Forward then
            
            if Pos >= (Strip_1.Get_Count - 1) then
                Dir := Backward;
                Rotate_Buffer(Strip_1, -1);
                Pos := Pos - 1;
            else
                Dir := Forward;
                Rotate_Buffer(Strip_1, 1);
                Pos := Pos + 1;
            end if;

        else
            
            if Pos <= 0 then
                Dir := Forward;
                Rotate_Buffer(Strip_1, 1);
                Pos := Pos + 1;
            else
                Dir := Backward;
                Rotate_Buffer(Strip_1, -1);
                Pos := Pos - 1;
            end if;

        end if;

        Strip_1.Show;

        delay until Clock + Milliseconds(150);

    end loop Infinite;


end cylon_eye_inverted;

converging_bars.adb

ADA
with Addressable_LEDs; use Addressable_LEDs;
with Addressable_LEDs.neopixel_spi; use Addressable_LEDs.neopixel_spi;
with SPI_config; use SPI_config;
with LED_magic; use LED_magic;
with Ada.Real_Time; use Ada.Real_Time;

procedure converging_bars is

    Strip_count : constant Positive := 5;
    Strip_mode : constant LED_Mode := GRB;
    Strip_1 : aliased LED_Strip_ws2812b_SPI := Create(Strip_mode, Strip_count, 8, Npxl_SPI'Access);

    Palette_1 : constant Color_Palette(0 .. 6) := ( (125, 0, 0, 0), (0, 125, 0, 0), (0, 0, 125, 0), (125, 125, 0, 0), (0, 125, 125, 0), (125, 0, 125, 0), (125, 125, 125, 0) );
    PixMode : Pixel_Mode := Fill_Pixels;
    Effect : constant Effect_Mode := Converge;
    Color_Index : Integer := 0;
    Current_Index, Mirror_Index, Middle_Index, Start_Index, Stop_Index : Integer := 0;
    Step_Difference : Integer := 0;

begin

    Initialize_NeoPixel;

    if ((Strip_1.Get_Count mod 2) = 0) then
        Middle_Index := (Strip_1.Get_Count / 2) - 1;
    else
        Middle_Index := (Strip_1.Get_Count - 1) / 2;
    end if;

    if Effect = Converge then
        Start_Index := 0;
        Stop_Index := Middle_Index;
        Current_Index := Start_Index;
        Mirror_Index := (Strip_1.Get_Count - 1) - Current_Index;
        Step_Difference := 1;
    else
        Start_Index := Middle_Index;
        Stop_Index := 0;
        Current_Index := Start_Index;
        Mirror_Index := (Strip_1.Get_Count - 1) - Current_Index;
        Step_Difference := -1;
    end if;

    Infinite :
    loop

        if PixMode = Fill_Pixels then
            Set_Color(Strip_1, Current_Index, Palette_1(Color_Index) );
            Set_Color(Strip_1, Mirror_Index, Palette_1(Color_Index) );
        else
            Set_Color(Strip_1, Current_Index, (0, 0, 0, 0) );
            Set_Color(Strip_1, Mirror_Index, (0, 0, 0, 0) );
        end if;

        if Current_Index = Stop_Index then
            Current_Index := Start_Index;
            Mirror_Index := (Strip_1.Get_Count - 1) - Current_Index;

            if PixMode = Fill_Pixels then
                PixMode := Unfill_Pixels;
            else
                PixMode := Fill_Pixels;
                Color_Index := (Color_Index + 1) mod (Palette_1'Length);
            end if;
        else
            Current_Index := Current_Index + Step_Difference;
            Mirror_Index := (Strip_1.Get_Count - 1) - Current_Index;
        end if;

        Strip_1.Show;

        delay until Clock + Milliseconds(150);

    end loop Infinite;


end converging_bars;

diverging_bars.adb

ADA
-- diverging_bars

with Addressable_LEDs; use Addressable_LEDs;
with Addressable_LEDs.neopixel_spi; use Addressable_LEDs.neopixel_spi;
with SPI_config; use SPI_config;
with LED_magic; use LED_magic;
with Ada.Real_Time; use Ada.Real_Time;

procedure diverging_bars is

    Strip_count : constant Positive := 5;
    Strip_mode : constant LED_Mode := GRB;
    Strip_1 : aliased LED_Strip_ws2812b_SPI := Create(Strip_mode, Strip_count, 8, Npxl_SPI'Access);

    Palette_1 : constant Color_Palette(0 .. 6) := ( (125, 0, 0, 0), (0, 125, 0, 0), (0, 0, 125, 0), (125, 125, 0, 0), (0, 125, 125, 0), (125, 0, 125, 0), (125, 125, 125, 0) );
    PixMode : Pixel_Mode := Fill_Pixels;
    Effect : constant Effect_Mode := Diverge;
    Color_Index : Integer := 0;
    Current_Index, Mirror_Index, Middle_Index, Start_Index, Stop_Index : Integer := 0;
    Step_Difference : Integer := 0;

begin

    Initialize_NeoPixel;

    if ((Strip_1.Get_Count mod 2) = 0) then
        Middle_Index := (Strip_1.Get_Count / 2) - 1;
    else
        Middle_Index := (Strip_1.Get_Count - 1) / 2;
    end if;

    if Effect = Converge then
        Start_Index := 0;
        Stop_Index := Middle_Index;
        Current_Index := Start_Index;
        Mirror_Index := (Strip_1.Get_Count - 1) - Current_Index;
        Step_Difference := 1;
    else
        Start_Index := Middle_Index;
        Stop_Index := 0;
        Current_Index := Start_Index;
        Mirror_Index := (Strip_1.Get_Count - 1) - Current_Index;
        Step_Difference := -1;
    end if;

    Infinite :
    loop

        if PixMode = Fill_Pixels then
            Set_Color(Strip_1, Current_Index, Palette_1(Color_Index) );
            Set_Color(Strip_1, Mirror_Index, Palette_1(Color_Index) );
        else
            Set_Color(Strip_1, Current_Index, (0, 0, 0, 0) );
            Set_Color(Strip_1, Mirror_Index, (0, 0, 0, 0) );
        end if;

        if Current_Index = Stop_Index then
            Current_Index := Start_Index;
            Mirror_Index := (Strip_1.Get_Count - 1) - Current_Index;

            if PixMode = Fill_Pixels then
                PixMode := Unfill_Pixels;
            else
                PixMode := Fill_Pixels;
                Color_Index := (Color_Index + 1) mod (Palette_1'Length);
            end if;
        else
            Current_Index := Current_Index + Step_Difference;
            Mirror_Index := (Strip_1.Get_Count - 1) - Current_Index;
        end if;

        Strip_1.Show;

        delay until Clock + Milliseconds(150);

    end loop Infinite;


end diverging_bars;

fade.adb

ADA
with Addressable_LEDs; use Addressable_LEDs;
with Addressable_LEDs.neopixel_spi; use Addressable_LEDs.neopixel_spi;
with SPI_config; use SPI_config;
with LED_magic; use LED_magic;
with Ada.Real_Time; use Ada.Real_Time;


procedure Fade is

    Strip_count : constant Positive := 5;
    Strip_mode : constant LED_Mode := GRB;
    Strip_1 : aliased LED_Strip_ws2812b_SPI := Create(Strip_mode, Strip_count, 8, Npxl_SPI'Access);

    Color_1 : constant LED_values := (100, 100, 0, 0);
    Palette_1 : Color_Palette(0 .. 30);
    Loop_Index : Integer := Palette_1'First;
    Diff : Integer := 1;

begin

    Initialize_NeoPixel;
    Generate_Monochromatic_Gradient_Palette(Palette_1, Color_1, 101);

    infinite :
    loop

        Fill(Strip_1, Palette_1(Loop_Index) );
        Strip_1.Show;

        if (Loop_Index = Palette_1'Last) then
            Diff := -1;
        elsif (Loop_Index = Palette_1'First) then
            Diff := 1;
        end if;

        Loop_Index := Loop_Index + Diff;

        delay until Clock + Milliseconds(40);

    end loop infinite;

end Fade;

fill_and_mirror.adb

ADA
with Addressable_LEDs; use Addressable_LEDs;
with Addressable_LEDs.neopixel_spi; use Addressable_LEDs.neopixel_spi;
with SPI_config; use SPI_config;
with LED_magic; use LED_magic;
with Ada.Real_Time; use Ada.Real_Time;


procedure fill_and_mirror is

    Strip_count : constant Positive := 5;
    Strip_mode : constant LED_Mode := GRB;
    Strip_1 : aliased LED_Strip_ws2812b_SPI := Create(Strip_mode, Strip_count, 8, Npxl_SPI'Access);

begin

    Initialize_NeoPixel;
    Set_Color(Strip_1, 0, (100, 0, 0, 0) );
    Set_Color(Strip_1, 1, (100, 0, 0, 0) );
    Set_Color(Strip_1, 2, (100, 100, 100, 0) );
    Set_Color(Strip_1, 3, (0, 0, 100, 0) );
    Set_Color(Strip_1, 4, (0, 0, 100, 0) );

    infinite :
    loop
        Strip_1.Show;
        Mirror_Buffer(Strip_1);

        delay until Clock + Milliseconds(500);
    end loop infinite;

end fill_and_mirror;

neopixel_ws2812b_SPI.zip

ADA
No preview (download only).

Credits

Rudra Lad

Rudra Lad

7 projects • 14 followers

Comments